Added DGEN to ISO and create file associatons.
[kolibrios.git] / kernel / trunk / core / heap.inc
blobba593a07ccc15886d455c70bb911b61aa7f2fbd2
1 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2 ;;                                                              ;;
3 ;; Copyright (C) KolibriOS team 2004-2022. All rights reserved. ;;
4 ;; Distributed under terms of the GNU General Public License    ;;
5 ;;                                                              ;;
6 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
8 $Revision$
11 struct  MEM_BLOCK
12         list            LHEAD
13         next_block      dd ? ;+8
14         prev_block      dd ? ;+4
15         base            dd ? ;+16
16         size            dd ? ;+20
17         flags           dd ? ;+24
18         handle          dd ? ;+28
19 ends
21 MEM_BLOCK_RESERVED  = 0x02      ; Will be allocated on first access (lazy allocation)
22 MEM_BLOCK_FREE      = 0x04
23 MEM_BLOCK_USED      = 0x08
24 MEM_BLOCK_DONT_FREE = 0x10
26 macro calc_index op
27 {          shr op, 12
28         dec     op
29         cmp     op, 63
30         jna     @f
31         mov     op, 63
32 @@:
35 align 4
36 md:
37 .add_to_used:
38         mov     eax, [esi + MEM_BLOCK.base]
39         mov     ebx, [esi + MEM_BLOCK.base]
40         shr     ebx, 6
41         add     eax, ebx
42         shr     ebx, 6
43         add     eax, ebx
44         shr     eax, 12
45         and     eax, 63
46         inc     [mem_hash_cnt + eax*4]
48         lea     ecx, [mem_used_list + eax*8]
49         list_add esi, ecx
50         mov     [esi + MEM_BLOCK.flags], MEM_BLOCK_USED
51         mov     eax, [esi + MEM_BLOCK.size]
52         sub     [heap_free], eax
53         ret
54 align 4
55 .find_used:
56         mov     ecx, eax
57         mov     ebx, eax
58         shr     ebx, 6
59         add     ecx, ebx
60         shr     ebx, 6
61         add     ecx, ebx
62         shr     ecx, 12
63         and     ecx, 63
65         lea     ebx, [mem_used_list + ecx*8]
66         mov     esi, ebx
67 .next:
68         mov     esi, [esi + MEM_BLOCK.list.next]
69         cmp     esi, ebx
70         je      .fail
72         cmp     eax, [esi + MEM_BLOCK.base]
73         jne     .next
75         ret
76 .fail:
77         xor     esi, esi
78         ret
80 align 4
81 .del_from_used:
82         call    .find_used
83         test    esi, esi
84         jz      .done
86         cmp     [esi + MEM_BLOCK.flags], MEM_BLOCK_USED
87         jne     .fatal
89         dec     [mem_hash_cnt + ecx*4]
90         list_del esi
91 .done:
92         ret
93 .fatal:                            ;FIXME panic here
94         xor     esi, esi
95         ret
97 ;Initial heap state
99 ; + heap_size               terminator        MEM_BLOCK_USED
100 ; + 4096*MEM_BLOCK.sizeof   free space        MEM_BLOCK_FREE
101 ;HEAP_BASE                heap_descriptors  MEM_BLOCK_USED
104 align 4
105 proc init_kernel_heap
107         mov     ecx, 64
108         mov     edi, mem_block_list
109   @@:
110         mov     eax, edi
111         stosd
112         stosd
113         loop    @B
115         mov     ecx, 64
116         mov     edi, mem_used_list
117   @@:
118         mov     eax, edi
119         stosd
120         stosd
121         loop    @B
123         stdcall alloc_pages, dword 32
125         or      eax, PG_SWR
126         mov     ebx, HEAP_BASE
127         mov     ecx, 32
128         call    commit_pages
130         mov     edi, HEAP_BASE                     ;descriptors
131         mov     ebx, HEAP_BASE + sizeof.MEM_BLOCK      ;free space
132         mov     ecx, HEAP_BASE + sizeof.MEM_BLOCK*2    ;terminator
134         xor     eax, eax
135         mov     [edi + MEM_BLOCK.next_block], ebx
136         mov     [edi + MEM_BLOCK.prev_block], eax
137         mov     [edi + MEM_BLOCK.list.next], eax
138         mov     [edi + MEM_BLOCK.list.prev], eax
139         mov     [edi + MEM_BLOCK.base], HEAP_BASE
140         mov     [edi + MEM_BLOCK.size], 4096*sizeof.MEM_BLOCK
141         mov     [edi + MEM_BLOCK.flags], MEM_BLOCK_USED
143         mov     [ecx + MEM_BLOCK.next_block], eax
144         mov     [ecx + MEM_BLOCK.prev_block], ebx
145         mov     [ecx + MEM_BLOCK.list.next], eax
146         mov     [ecx + MEM_BLOCK.list.prev], eax
147         mov     [ecx + MEM_BLOCK.base], eax
148         mov     [ecx + MEM_BLOCK.size], eax
149         mov     [ecx + MEM_BLOCK.flags], MEM_BLOCK_USED
151         mov     [ebx + MEM_BLOCK.next_block], ecx
152         mov     [ebx + MEM_BLOCK.prev_block], edi
153         mov     [ebx + MEM_BLOCK.base], HEAP_BASE + 4096*sizeof.MEM_BLOCK
155         mov     ecx, [pg_data.kernel_pages]
156         shl     ecx, 12
157         sub     ecx, HEAP_BASE-OS_BASE + 4096*sizeof.MEM_BLOCK
158         mov     [heap_size], ecx
159         mov     [heap_free], ecx
160         mov     [ebx + MEM_BLOCK.size], ecx
161         mov     [ebx + MEM_BLOCK.flags], MEM_BLOCK_FREE
163         mov     [mem_block_mask], eax
164         mov     [mem_block_mask + 4], 0x80000000
166         mov     ecx, mem_block_list + 63*8
167         list_add ebx, ecx
169         mov     ecx, 4096-3-1
170         mov     eax, HEAP_BASE + sizeof.MEM_BLOCK*4
172         mov     [next_memblock], HEAP_BASE + sizeof.MEM_BLOCK *3
173  @@:
174         mov     [eax - sizeof.MEM_BLOCK], eax
175         add     eax, sizeof.MEM_BLOCK
176         loop    @B
178         mov     dword[eax - sizeof.MEM_BLOCK], 0
180         mov     ecx, heap_mutex
181         call    mutex_init
182         mov     [heap_blocks], 4094
183         mov     [free_blocks], 4093
184         ret
185 endp
187 ; param
188 ;  eax= required size
190 ; retval
191 ;  edi= memory block descriptor
192 ;  ebx= descriptor index
194 align 4
195 get_small_block:
196         mov     ecx, eax
197         shr     ecx, 12
198         dec     ecx
199         cmp     ecx, 63
200         jle     .get_index
201         mov     ecx, 63
202   .get_index:
203         lea     esi, [mem_block_mask]
204         xor     ebx, ebx
205         or      edx, -1
207         cmp     ecx, 32
208         jb      .bit_test
210         sub     ecx, 32
211         add     ebx, 32
212         add     esi, 4
213   .bit_test:
214         shl     edx, cl
215         and     edx, [esi]
216   .find:
217         bsf     edi, edx
218         jz      .high_mask
219         add     ebx, edi
220         lea     ecx, [mem_block_list + ebx*8]
221         mov     edi, ecx
222   .next:
223         mov     edi, [edi + MEM_BLOCK.list.next]
224         cmp     edi, ecx
225         je      .err
226         cmp     eax, [edi + MEM_BLOCK.size]
227         ja      .next
228         ret
229   .err:
230         xor     edi, edi
231         ret
233   .high_mask:
234         add     esi, 4
235         cmp     esi, mem_block_mask + 8
236         jae     .err
237         add     ebx, 32
238         mov     edx, [esi]
239         jmp     .find
242 align 4
243 free_mem_block:
245         mov     ebx, [next_memblock]
246         mov     [eax], ebx
247         mov     [next_memblock], eax
249         xor     ebx, ebx
250         mov     dword[eax + 4], ebx
251         mov     dword[eax + 8], ebx
252         mov     dword[eax + 12], ebx
253         mov     dword[eax + 16], ebx
254 ;           mov dword[eax + 20], 0     ;don't clear block size
255         mov     dword[eax + 24], ebx
256         mov     dword[eax + 28], ebx
258         inc     [free_blocks]
260         ret
262 align 4
263 proc alloc_kernel_space stdcall, size:dword
264            local block_ind:DWORD
266         push    ebx
267         push    esi
268         push    edi
270         mov     eax, [size]
271         add     eax, 4095
272         and     eax, not 4095
273         mov     [size], eax
275         cmp     eax, [heap_free]
276         ja      .error
278         spin_lock_irqsave heap_mutex
280         mov     eax, [size]
282         call    get_small_block ; eax
283         test    edi, edi
284         jz      .error_unlock
286         cmp     [edi + MEM_BLOCK.flags], MEM_BLOCK_FREE
287         jne     .error_unlock
289         mov     [block_ind], ebx  ;index of allocated block
291         mov     eax, [edi + MEM_BLOCK.size]
292         cmp     eax, [size]
293         je      .m_eq_size
295         mov     esi, [next_memblock]    ;new memory block
296         test    esi, esi
297         jz      .error_unlock
299         dec     [free_blocks]
300         mov     eax, [esi]
301         mov     [next_memblock], eax
303         mov     [esi + MEM_BLOCK.next_block], edi
304         mov     eax, [edi + MEM_BLOCK.prev_block]
305         mov     [esi + MEM_BLOCK.prev_block], eax
306         mov     [edi + MEM_BLOCK.prev_block], esi
307         mov     [esi + MEM_BLOCK.list.next], 0
308         mov     [esi + MEM_BLOCK.list.prev], 0
309         mov     [eax + MEM_BLOCK.next_block], esi
311         mov     ebx, [edi + MEM_BLOCK.base]
312         mov     [esi + MEM_BLOCK.base], ebx
313         mov     edx, [size]
314         mov     [esi + MEM_BLOCK.size], edx
315         add     [edi + MEM_BLOCK.base], edx
316         sub     [edi + MEM_BLOCK.size], edx
318         mov     eax, [edi + MEM_BLOCK.size]
319         calc_index eax
320         cmp     eax, [block_ind]
321         je      .add_used
323         list_del edi
325         mov     ecx, [block_ind]
326         lea     edx, [mem_block_list + ecx*8]
327         cmp     edx, [edx]
328         jnz     @f
329         btr     [mem_block_mask], ecx
331         bts     [mem_block_mask], eax
332         lea     edx, [mem_block_list + eax*8]  ;edx= list head
333         list_add edi, edx
334 .add_used:
336         call    md.add_to_used
338         spin_unlock_irqrestore heap_mutex
339         mov     eax, [esi + MEM_BLOCK.base]
340         pop     edi
341         pop     esi
342         pop     ebx
343         ret
345 .m_eq_size:
346         list_del edi
347         lea     edx, [mem_block_list + ebx*8]
348         cmp     edx, [edx]
349         jnz     @f
350         btr     [mem_block_mask], ebx
352         mov     esi, edi
353         jmp     .add_used
355 .error_unlock:
356         spin_unlock_irqrestore heap_mutex
357 .error:
358         xor     eax, eax
359         pop     edi
360         pop     esi
361         pop     ebx
362         ret
363 endp
365 align 4
366 proc free_kernel_space stdcall uses ebx ecx edx esi edi, base:dword
368         spin_lock_irqsave heap_mutex
370         mov     eax, [base]
372         call    md.del_from_used
373         test    esi, esi
374         jz      .fail
376         mov     eax, [esi + MEM_BLOCK.size]
377         add     [heap_free], eax
379         mov     edi, [esi + MEM_BLOCK.next_block]
380         cmp     [edi + MEM_BLOCK.flags], MEM_BLOCK_FREE
381         jne     .prev
383         list_del edi
385         mov     edx, [edi + MEM_BLOCK.next_block]
386         mov     [esi + MEM_BLOCK.next_block], edx
387         mov     [edx + MEM_BLOCK.prev_block], esi
388         mov     ecx, [edi + MEM_BLOCK.size]
389         add     [esi + MEM_BLOCK.size], ecx
391         calc_index ecx
393         lea     edx, [mem_block_list + ecx*8]
394         cmp     edx, [edx]
395         jne     @F
396         btr     [mem_block_mask], ecx
398         mov     eax, edi
399         call    free_mem_block
400 .prev:
401         mov     edi, [esi + MEM_BLOCK.prev_block]
402         cmp     [edi + MEM_BLOCK.flags], MEM_BLOCK_FREE
403         jne     .insert
405         mov     edx, [esi + MEM_BLOCK.next_block]
406         mov     [edi + MEM_BLOCK.next_block], edx
407         mov     [edx + MEM_BLOCK.prev_block], edi
409         mov     eax, esi
410         call    free_mem_block
412         mov     ecx, [edi + MEM_BLOCK.size]
413         mov     eax, [esi + MEM_BLOCK.size]
414         add     eax, ecx
415         mov     [edi + MEM_BLOCK.size], eax
417         calc_index eax                     ;new index
418         calc_index ecx                     ;old index
419         cmp     eax, ecx
420         je      .m_eq
422         push    ecx
423         list_del edi
424         pop     ecx
426         lea     edx, [mem_block_list + ecx*8]
427         cmp     edx, [edx]
428         jne     .add_block
429         btr     [mem_block_mask], ecx
431 .add_block:
432         bts     [mem_block_mask], eax
433         lea     edx, [mem_block_list + eax*8]
434         list_add edi, edx
435 .m_eq:
436         spin_unlock_irqrestore heap_mutex
437         xor     eax, eax
438         not     eax
439         ret
440 .insert:
441         mov     [esi + MEM_BLOCK.flags], MEM_BLOCK_FREE
442         mov     eax, [esi + MEM_BLOCK.size]
443         calc_index eax
444         mov     edi, esi
445         jmp     .add_block
447 .fail:
448         spin_unlock_irqrestore heap_mutex
449         xor     eax, eax
450         ret
451 endp
453 align 4
454 proc kernel_alloc stdcall, size:dword
455         locals
456           lin_addr    dd ?
457           pages_count dd ?
458         endl
460         push    ebx
461         push    edi
463         mov     eax, [size]
464         add     eax, 4095
465         and     eax, not 4095;
466         mov     [size], eax
467         and     eax, eax
468         jz      .err
469         mov     ebx, eax
470         shr     ebx, 12
471         mov     [pages_count], ebx
473         stdcall alloc_kernel_space, eax
474         mov     [lin_addr], eax
475         mov     ebx, [pages_count]
476         test    eax, eax
477         jz      .err
479         mov     edx, eax
481         shr     ebx, 3
482         jz      .tail
484         shl     ebx, 3
485         stdcall alloc_pages, ebx
486         test    eax, eax
487         jz      .err
489         mov     ecx, ebx
490         or      eax, PG_GLOBAL + PG_SWR
491         mov     ebx, [lin_addr]
492         call    commit_pages
494         mov     edx, ebx                    ; this dirty hack
495 .tail:
496         mov     ebx, [pages_count]
497         and     ebx, 7
498         jz      .end
500         call    alloc_page
501         test    eax, eax
502         jz      .err
504         stdcall map_page, edx, eax, dword (PG_GLOBAL + PG_SWR)
505         add     edx, 0x1000
506         dec     ebx
507         jnz     @B
508 .end:
509         mov     eax, [lin_addr]
510         pop     edi
511         pop     ebx
512         ret
513 .err:
514         xor     eax, eax
515         pop     edi
516         pop     ebx
517         ret
518 endp
520 align 4
521 proc kernel_free stdcall, base:dword
523         push    ebx esi
525         spin_lock_irqsave heap_mutex
527         mov     eax, [base]
528         call    md.find_used
530         cmp     [esi + MEM_BLOCK.flags], MEM_BLOCK_USED
531         jne     .fail
533         spin_unlock_irqrestore heap_mutex
535         mov     eax, [esi + MEM_BLOCK.base]
536         mov     ecx, [esi + MEM_BLOCK.size]
537         shr     ecx, 12
538         call    release_pages   ;eax, ecx
539         stdcall free_kernel_space, [base]
540         pop     esi ebx
541         ret
542 .fail:
543         spin_unlock_irqrestore heap_mutex
544         xor     eax, eax
545         pop     esi ebx
546         ret
547 endp
549 ;;;;;;;;;;;;;;      USER HEAP     ;;;;;;;;;;;;;;;;;
551 HEAP_TOP  = 0x80000000
553 align 4
554 proc init_heap
556         mov     ebx, [current_process]
557         mov     eax, [ebx + PROC.heap_top]
558         test    eax, eax
559         jz      @F
560         sub     eax, [ebx + PROC.heap_base]
561         sub     eax, PAGE_SIZE
562         ret
564         lea     ecx, [ebx + PROC.heap_lock]
565         call    mutex_init
567         mov     esi, [ebx + PROC.mem_used]
568         add     esi, 4095
569         and     esi, not 4095
570         mov     [ebx + PROC.mem_used], esi
571         mov     eax, HEAP_TOP
572         mov     [ebx + PROC.heap_base], esi
573         mov     [ebx + PROC.heap_top], eax
575         sub     eax, esi
576         shr     esi, 10
577         mov     ecx, eax
578         sub     eax, PAGE_SIZE
579         or      ecx, MEM_BLOCK_FREE
580         mov     [page_tabs + esi], ecx
581         ret
582 endp
584 align 4
585 proc user_alloc stdcall, alloc_size:dword
587         push    ebx esi edi
589         mov     ebx, [current_process]
590         lea     ecx, [ebx + PROC.heap_lock]
591         call    mutex_lock
593         mov     ecx, [alloc_size]
594         add     ecx, (4095 + PAGE_SIZE)
595         and     ecx, not 4095
596         mov     esi, [ebx + PROC.heap_base]
597         mov     edi, [ebx + PROC.heap_top]
598   .scan:
599         cmp     esi, edi
600         jae     .m_exit
602         mov     ebx, esi
603         shr     ebx, 12
604         mov     eax, [page_tabs + ebx*4]
605         test    al, MEM_BLOCK_FREE
606         jz      .test_used
607         and     eax, 0xFFFFF000
608         cmp     eax, ecx   ;alloc_size
609         jb      .m_next
610         jz      @f
612         lea     edx, [esi + ecx]
613         sub     eax, ecx
614         or      al, MEM_BLOCK_FREE
615         shr     edx, 12
616         mov     [page_tabs + edx*4], eax
617   @@:
618         or      ecx, MEM_BLOCK_USED
619         mov     [page_tabs + ebx*4], ecx
620         shr     ecx, 12
621         inc     ebx
622         dec     ecx
623         jz      .no
624   @@:
625         mov     dword [page_tabs + ebx*4], MEM_BLOCK_RESERVED
626         inc     ebx
627         dec     ecx
628         jnz     @B
629   .no:
631         mov     edx, [current_process]
632         mov     ebx, [alloc_size]
633         add     ebx, 0xFFF
634         and     ebx, not 0xFFF
635         add     [edx + PROC.mem_used], ebx
637         lea     ecx, [edx + PROC.heap_lock]
638         call    mutex_unlock
640         lea     eax, [esi + 4096]
642         pop     edi
643         pop     esi
644         pop     ebx
645         ret
646 .test_used:
647         test    al, MEM_BLOCK_USED
648         jz      .m_exit
650         and     eax, 0xFFFFF000 ; not PAGESIZE
651 .m_next:
652         add     esi, eax
653         jmp     .scan
654 .m_exit:
655         mov     ecx, [current_process]
656         lea     ecx, [ecx + PROC.heap_lock]
657         call    mutex_unlock
659         xor     eax, eax
660         pop     edi
661         pop     esi
662         pop     ebx
663         ret
664 endp
666 align 4
667 proc user_alloc_at stdcall, address:dword, alloc_size:dword
669         push    ebx
670         push    esi
671         push    edi
673         mov     ebx, [current_process]
674         lea     ecx, [ebx + PROC.heap_lock]
675         call    mutex_lock
677         mov     edx, [address]
678         and     edx, not 0xFFF
679         mov     [address], edx
680         sub     edx, 0x1000
681         jb      .error
682         mov     esi, [ebx + PROC.heap_base]
683         mov     edi, [ebx + PROC.heap_top]
684         cmp     edx, esi
685         jb      .error
686 .scan:
687         cmp     esi, edi
688         jae     .error
689         mov     ebx, esi
690         shr     ebx, 12
691         mov     eax, [page_tabs + ebx*4]
692         mov     ecx, eax
693         and     ecx, 0xFFFFF000
694         add     ecx, esi
695         cmp     edx, ecx
696         jb      .found
697         mov     esi, ecx
698         jmp     .scan
699 .error:
700         mov     ecx, [current_process]
701         lea     ecx, [ecx + PROC.heap_lock]
702         call    mutex_unlock
704         xor     eax, eax
705         pop     edi
706         pop     esi
707         pop     ebx
708         ret
709 .found:
710         test    al, MEM_BLOCK_FREE
711         jz      .error
712         mov     eax, ecx
713         sub     eax, edx
714         sub     eax, 0x1000
715         cmp     eax, [alloc_size]
716         jb      .error
718 ; Here we have 1 big free block which includes requested area.
719 ; In general, 3 other blocks must be created instead:
720 ; free at [esi, edx);
721 ; busy at [edx, edx + 0x1000 + ALIGN_UP(alloc_size,0x1000));
722 ; free at [edx + 0x1000 + ALIGN_UP(alloc_size,0x1000), ecx)
723 ; First or third block (or both) may be absent.
724         mov     eax, edx
725         sub     eax, esi
726         jz      .nofirst
727         or      al, MEM_BLOCK_FREE
728         mov     [page_tabs + ebx*4], eax
729   .nofirst:
730         mov     eax, [alloc_size]
731         add     eax, 0x1FFF
732         and     eax, not 0xFFF
733         mov     ebx, edx
734         add     edx, eax
735         shr     ebx, 12
736         or      al, MEM_BLOCK_USED
737         mov     [page_tabs + ebx*4], eax
738         shr     eax, 12
739         dec     eax
740         jz      .second_nofill
741         inc     ebx
742   .fill:
743         mov     dword [page_tabs + ebx*4], MEM_BLOCK_RESERVED
744         inc     ebx
745         dec     eax
746         jnz     .fill
748   .second_nofill:
749         sub     ecx, edx
750         jz      .nothird
751         or      cl, MEM_BLOCK_FREE
752         mov     [page_tabs + ebx*4], ecx
754   .nothird:
755         mov     edx, [current_process]
756         mov     ebx, [alloc_size]
757         add     ebx, 0xFFF
758         and     ebx, not 0xFFF
759         add     [edx + PROC.mem_used], ebx
761         lea     ecx, [edx + PROC.heap_lock]
762         call    mutex_unlock
764         mov     eax, [address]
766         pop     edi
767         pop     esi
768         pop     ebx
769         ret
770 endp
772 align 4
773 proc user_free stdcall, base:dword
775         push    esi
777         mov     esi, [base]
778         test    esi, esi
779         jz      .fail
781         push    ebx
783         mov     ebx, [current_process]
784         lea     ecx, [ebx + PROC.heap_lock]
785         call    mutex_lock
787         xor     ebx, ebx
788         shr     esi, 12
789         mov     eax, [page_tabs + (esi-1)*4]
790         test    al, MEM_BLOCK_USED
791         jz      .cantfree
792         test    al, MEM_BLOCK_DONT_FREE
793         jnz     .cantfree
795         and     eax, not 4095
796         mov     ecx, eax
797         or      al, MEM_BLOCK_FREE
798         mov     [page_tabs + (esi-1)*4], eax
799         sub     ecx, 4096
800         mov     ebx, ecx
801         shr     ecx, 12
802         jz      .released
803   .release:
804         xor     eax, eax
805         xchg    eax, [page_tabs + esi*4]
806         test    al, 1
807         jz      @F
808         test    eax, PG_SHARED
809         jnz     @F
810         call    free_page
811         mov     eax, esi
812         shl     eax, 12
813         invlpg  [eax]
814   @@:
815         inc     esi
816         dec     ecx
817         jnz     .release
819  .released:
820         push    edi
822         mov     edx, [current_process]
823         lea     ecx, [edx + PROC.heap_lock]
824         mov     esi, dword [edx + PROC.heap_base]
825         mov     edi, dword [edx + PROC.heap_top]
826         sub     ebx, [edx + PROC.mem_used]
827         neg     ebx
828         mov     [edx + PROC.mem_used], ebx
829         call    user_normalize
830         pop     edi
831  .exit:
832         call    mutex_unlock
834         xor     eax, eax
835         inc     eax
836         pop     ebx
837         pop     esi
838         ret
840   .cantfree:
841         mov     ecx, [current_process]
842         lea     ecx, [ecx + PROC.heap_lock]
843         jmp     .exit
844   .fail:
845         xor     eax, eax
846         pop     esi
847         ret
848 endp
851 align 4
852 proc user_unmap stdcall, base:dword, offset:dword, size:dword
854         push    ebx
856         mov     ebx, [base]             ; must be valid pointer
857         test    ebx, ebx
858         jz      .error
860         mov     edx, [offset]           ; check offset
861         add     edx, ebx                ; must be below 2Gb app limit
862         js      .error
864         shr     ebx, 12                 ; chek block attributes
865         lea     ebx, [page_tabs + ebx*4]
866         mov     eax, [ebx - 4]          ; block attributes
867         test    al, MEM_BLOCK_USED
868         jz      .error
869         test    al, MEM_BLOCK_DONT_FREE
870         jnz     .error
872         shr     edx, 12
873         lea     edx, [page_tabs + edx*4]  ; unmap offset
875         mov     ecx, [size]
876         add     ecx, 4095
877         shr     ecx, 12                 ; unmap size in pages
879         shr     eax, 12                 ; block size  +  1 page
880         lea     ebx, [ebx + eax*4-4]      ; block end ptr
881         lea     eax, [edx + ecx*4]        ; unmap end ptr
883         cmp     eax, ebx                ; check for overflow
884         ja      .error
886         mov     ebx, [offset]
887         and     ebx, not 4095           ; is it required ?
888         add     ebx, [base]
890   .unmap:
891         mov     eax, [edx]              ; get page addres
892         test    al, 1                   ; page mapped ?
893         jz      @F
894         test    eax, PG_SHARED          ; page shared ?
895         jnz     @F
896         mov     dword[edx], MEM_BLOCK_RESERVED
897                                         ; mark page as reserved
898         invlpg  [ebx]                   ; when we start using
899         call    free_page               ; empty c-o-w page instead this ?
900   @@:
901         add     ebx, 4096       ; PAGESIZE?
902         add     edx, 4
903         dec     ecx
904         jnz     .unmap
906         pop     ebx
907         or      al, 1                   ; return non zero on success
908         ret
909 .error:
910         pop     ebx
911         xor     eax, eax                ; something wrong
912         ret
913 endp
915 align 4
916 user_normalize:
917 ; in: esi=heap_base, edi=heap_top
918 ; out: eax=0 <=> OK
919 ; destroys: ebx,edx,esi,edi
920         shr     esi, 12
921         shr     edi, 12
923         mov     eax, [page_tabs + esi*4]
924         test    al, MEM_BLOCK_USED
925         jz      .test_free
926         shr     eax, 12
927         add     esi, eax
928         jmp     @B
929 .test_free:
930         test    al, MEM_BLOCK_FREE
931         jz      .err
932         mov     edx, eax
933         shr     edx, 12
934         add     edx, esi
935         cmp     edx, edi
936         jae     .exit
938         mov     ebx, [page_tabs + edx*4]
939         test    bl, MEM_BLOCK_USED
940         jz      .next_free
942         shr     ebx, 12
943         add     edx, ebx
944         mov     esi, edx
945         jmp     @B
946 .next_free:
947         test    bl, MEM_BLOCK_FREE
948         jz      .err
949         and     dword[page_tabs + edx*4], 0
950         add     eax, ebx
951         and     eax, not 4095           ; not (PAGESIZE - 1)    ?
952         or      eax, MEM_BLOCK_FREE
953         mov     [page_tabs + esi*4], eax
954         jmp     @B
955 .exit:
956         xor     eax, eax
957         inc     eax
958         ret
959 .err:
960         xor     eax, eax
961         ret
963 user_realloc:
964 ; in: eax = pointer, ebx = new size
965 ; out: eax = new pointer or NULL
966         test    eax, eax
967         jnz     @f
968 ; realloc(NULL,sz) - same as malloc(sz)
969         push    ebx
970         call    user_alloc
971         ret
973         push    ecx edx
975         push    eax
976         mov     ecx, [current_process]
977         lea     ecx, [ecx + PROC.heap_lock]
978         call    mutex_lock
979         pop     eax
981         lea     ecx, [eax - 0x1000]
982         shr     ecx, 12
983         mov     edx, [page_tabs + ecx*4]
984         test    dl, MEM_BLOCK_USED
985         jnz     @f
986 ; attempt to realloc invalid pointer
987 .ret0:
988         mov     ecx, [current_process]
989         lea     ecx, [ecx + PROC.heap_lock]
990         call    mutex_unlock
992         pop     edx ecx
993         xor     eax, eax
994         ret
996         test    dl, MEM_BLOCK_DONT_FREE
997         jnz     .ret0
998         add     ebx, 0x1FFF
999         shr     edx, 12
1000         shr     ebx, 12
1001 ; edx = allocated size, ebx = new size
1002         add     edx, ecx
1003         add     ebx, ecx
1004         cmp     edx, ebx
1005         jb      .realloc_add
1006 ; release part of allocated memory
1007 .loop:
1008         cmp     edx, ebx
1009         jz      .release_done
1010         dec     edx
1011         xor     eax, eax
1012         xchg    eax, [page_tabs + edx*4]
1013         test    al, 1
1014         jz      .loop
1015         call    free_page
1016         mov     eax, edx
1017         shl     eax, 12
1018         invlpg  [eax]
1019         jmp     .loop
1020 .release_done:
1021         sub     ebx, ecx
1022         cmp     ebx, 1
1023         jnz     .nofreeall
1024         mov     eax, [page_tabs + ecx*4]
1025         and     eax, not 0xFFF
1026         mov     edx, [current_process]
1027         mov     ebx, [edx + PROC.mem_used]
1028         sub     ebx, eax
1029         add     ebx, 0x1000
1030         or      al, MEM_BLOCK_FREE
1031         mov     [page_tabs + ecx*4], eax
1032         push    esi edi
1033         mov     esi, [edx + PROC.heap_base]
1034         mov     edi, [edx + PROC.heap_top]
1035         mov     [edx + PROC.mem_used], ebx
1036         call    user_normalize
1037         pop     edi esi
1038         jmp     .ret0   ; all freed
1039 .nofreeall:
1040         sub     edx, ecx
1041         shl     ebx, 12
1042         or      ebx, MEM_BLOCK_USED
1043         xchg    [page_tabs + ecx*4], ebx
1044         shr     ebx, 12
1045         sub     ebx, edx
1046         push    ebx ecx edx
1047         mov     edx, [current_process]
1048         shl     ebx, 12
1049         sub     ebx, [edx + PROC.mem_used]
1050         neg     ebx
1051         mov     [edx + PROC.mem_used], ebx
1052         pop     edx ecx ebx
1053         lea     eax, [ecx + 1]
1054         shl     eax, 12
1055         push    eax
1056         add     ecx, edx
1057         lea     edx, [ecx + ebx]
1058         shl     ebx, 12
1059         jz      .ret
1060         push    esi
1061         mov     esi, [current_process]
1062         mov     esi, [esi + PROC.heap_top]
1063         shr     esi, 12
1065         cmp     edx, esi
1066         jae     .merge_done
1067         mov     eax, [page_tabs + edx*4]
1068         test    al, MEM_BLOCK_USED
1069         jnz     .merge_done
1070         and     dword [page_tabs + edx*4], 0
1071         shr     eax, 12
1072         add     edx, eax
1073         shl     eax, 12
1074         add     ebx, eax
1075         jmp     @b
1076 .merge_done:
1077         pop     esi
1078         or      ebx, MEM_BLOCK_FREE
1079         mov     [page_tabs + ecx*4], ebx
1080 .ret:
1081         mov     ecx, [current_process]
1082         lea     ecx, [ecx + PROC.heap_lock]
1083         call    mutex_unlock
1084         pop     eax edx ecx
1085         ret
1087 .realloc_add:
1088 ; get some additional memory
1089         mov     eax, [current_process]
1090         mov     eax, [eax + PROC.heap_top]
1091         shr     eax, 12
1092         cmp     edx, eax
1093         jae     .cant_inplace
1094         mov     eax, [page_tabs + edx*4]
1095         test    al, MEM_BLOCK_FREE
1096         jz      .cant_inplace
1097         shr     eax, 12
1098         add     eax, edx
1099         sub     eax, ebx
1100         jb      .cant_inplace
1101         jz      @f
1102         shl     eax, 12
1103         or      al, MEM_BLOCK_FREE
1104         mov     [page_tabs + ebx*4], eax
1106         mov     eax, ebx
1107         sub     eax, ecx
1108         shl     eax, 12
1109         or      al, MEM_BLOCK_USED
1110         mov     [page_tabs + ecx*4], eax
1111         lea     eax, [ecx + 1]
1112         shl     eax, 12
1113         push    eax
1114         push    edi
1115         lea     edi, [page_tabs + edx*4]
1116         mov     eax, 2
1117         sub     ebx, edx
1118         mov     ecx, ebx
1119         cld
1120         rep stosd
1121         pop     edi
1122         mov     edx, [current_process]
1123         shl     ebx, 12
1124         add     [edx + PROC.mem_used], ebx
1126         mov     ecx, [current_process]
1127         lea     ecx, [ecx + PROC.heap_lock]
1128         call    mutex_unlock
1129         pop     eax edx ecx
1130         ret
1132 .cant_inplace:
1133         push    esi edi
1134         mov     eax, [current_process]
1135         mov     esi, [eax + PROC.heap_base]
1136         mov     edi, [eax + PROC.heap_top]
1137         shr     esi, 12
1138         shr     edi, 12
1139         sub     ebx, ecx
1140 .find_place:
1141         cmp     esi, edi
1142         jae     .place_not_found
1143         mov     eax, [page_tabs + esi*4]
1144         test    al, MEM_BLOCK_FREE
1145         jz      .next_place
1146         shr     eax, 12
1147         cmp     eax, ebx
1148         jae     .place_found
1149         add     esi, eax
1150         jmp     .find_place
1151 .next_place:
1152         shr     eax, 12
1153         add     esi, eax
1154         jmp     .find_place
1155 .place_not_found:
1156         pop     edi esi
1157         jmp     .ret0
1158 .place_found:
1159         sub     eax, ebx
1160         jz      @f
1161         push    esi
1162         add     esi, ebx
1163         shl     eax, 12
1164         or      al, MEM_BLOCK_FREE
1165         mov     [page_tabs + esi*4], eax
1166         pop     esi
1168         mov     eax, ebx
1169         shl     eax, 12
1170         or      al, MEM_BLOCK_USED
1171         mov     [page_tabs + esi*4], eax
1172         inc     esi
1173         mov     eax, esi
1174         shl     eax, 12
1175         push    eax
1176         mov     eax, [page_tabs + ecx*4]
1177         and     eax, not 0xFFF
1178         or      al, MEM_BLOCK_FREE
1179         sub     edx, ecx
1180         mov     [page_tabs + ecx*4], eax
1181         inc     ecx
1182         dec     ebx
1183         dec     edx
1184         jz      .no
1186         xor     eax, eax
1187         xchg    eax, [page_tabs + ecx*4]
1188         mov     [page_tabs + esi*4], eax
1189         mov     eax, ecx
1190         shl     eax, 12
1191         invlpg  [eax]
1192         inc     esi
1193         inc     ecx
1194         dec     ebx
1195         dec     edx
1196         jnz     @b
1197 .no:
1198         push    ebx
1199         mov     edx, [current_process]
1200         shl     ebx, 12
1201         add     [edx + PROC.mem_used], ebx
1202         pop     ebx
1204         mov     dword [page_tabs + esi*4], MEM_BLOCK_RESERVED
1205         inc     esi
1206         dec     ebx
1207         jnz     @b
1209         mov     ecx, [current_process]
1210         lea     ecx, [ecx + PROC.heap_lock]
1211         call    mutex_unlock
1212         pop     eax edi esi edx ecx
1213         ret
1217 ;;;;;;;;;;;;;;      SHARED MEMORY     ;;;;;;;;;;;;;;;;;
1220 ; param
1221 ;  eax= shm_map object
1223 align 4
1224 destroy_smap:
1226         pushfd
1227         cli
1229         push    esi
1230         push    edi
1232         mov     edi, eax
1233         mov     esi, [eax + SMAP.parent]
1234         test    esi, esi
1235         jz      .done
1237         lock dec [esi + SMEM.refcount]
1238         jnz     .done
1240         mov     ecx, [esi + SMEM.bk]
1241         mov     edx, [esi + SMEM.fd]
1243         mov     [ecx + SMEM.fd], edx
1244         mov     [edx + SMEM.bk], ecx
1246         stdcall kernel_free, [esi + SMEM.base]
1247         mov     eax, esi
1248         call    free
1249 .done:
1250         mov     eax, edi
1251         call    destroy_kernel_object
1253         pop     edi
1254         pop     esi
1255         popfd
1257         ret
1259 E_NOTFOUND      =  5
1260 E_ACCESS        = 10
1261 E_NOMEM         = 30
1262 E_PARAM         = 33
1264 SHM_READ        = 0
1265 SHM_WRITE       = 1
1267 SHM_ACCESS_MASK = 3
1269 SHM_OPEN        = 0 shl 2
1270 SHM_OPEN_ALWAYS = 1 shl 2
1271 SHM_CREATE      = 2 shl 2
1273 SHM_OPEN_MASK   = 3 shl 2
1275 align 4
1276 proc shmem_open stdcall name:dword, size:dword, access:dword
1277         locals
1278            action         dd ?
1279            owner_access   dd ?
1280            mapped         dd ?
1281         endl
1283         push    ebx
1284         push    esi
1285         push    edi
1287         mov     [mapped], 0
1288         mov     [owner_access], 0
1290         pushfd                         ;mutex required
1291         cli
1293         mov     eax, [access]
1294         and     eax, SHM_OPEN_MASK
1295         mov     [action], eax
1297         mov     ebx, [name]
1298         test    ebx, ebx
1299         mov     edx, E_PARAM
1300         jz      .fail
1302         mov     esi, [shmem_list.fd]
1303 align 4
1305         cmp     esi, shmem_list
1306         je      .not_found
1308         lea     edx, [esi + SMEM.name]; link , base, size
1309         stdcall strncmp, edx, ebx, 32
1310         test    eax, eax
1311         je      .found
1313         mov     esi, [esi + SMEM.fd]
1314         jmp     @B
1316 .not_found:
1317         mov     eax, [action]
1319         cmp     eax, SHM_OPEN
1320         mov     edx, E_NOTFOUND
1321         je      .fail
1323         cmp     eax, SHM_CREATE
1324         mov     edx, E_PARAM
1325         je      .create_shm
1327         cmp     eax, SHM_OPEN_ALWAYS
1328         jne     .fail
1330 .create_shm:
1332         mov     ecx, [size]
1333         test    ecx, ecx
1334         jz      .fail
1336         add     ecx, 4095
1337         and     ecx, -4096
1338         mov     [size], ecx
1340         mov     eax, sizeof.SMEM
1341         call    malloc
1342         test    eax, eax
1343         mov     esi, eax
1344         mov     edx, E_NOMEM
1345         jz      .fail
1347         stdcall kernel_alloc, [size]
1348         test    eax, eax
1349         mov     [mapped], eax
1350         mov     edx, E_NOMEM
1351         jz      .cleanup
1353         mov     ecx, [size]
1354         mov     edx, [access]
1355         and     edx, SHM_ACCESS_MASK
1357         mov     [esi + SMEM.base], eax
1358         mov     [esi + SMEM.size], ecx
1359         mov     [esi + SMEM.access], edx
1360         mov     [esi + SMEM.refcount], 0
1361         mov     [esi + SMEM.name + 28], 0
1363         lea     eax, [esi + SMEM.name]
1364         stdcall strncpy, eax, [name], 31
1366         mov     eax, [shmem_list.fd]
1367         mov     [esi + SMEM.bk], shmem_list
1368         mov     [esi + SMEM.fd], eax
1370         mov     [eax + SMEM.bk], esi
1371         mov     [shmem_list.fd], esi
1373         mov     [action], SHM_OPEN
1374         mov     [owner_access], SHM_WRITE
1376 .found:
1377         mov     eax, [action]
1379         cmp     eax, SHM_CREATE
1380         mov     edx, E_ACCESS
1381         je      .exit
1383         cmp     eax, SHM_OPEN
1384         mov     edx, E_PARAM
1385         je      .create_map
1387         cmp     eax, SHM_OPEN_ALWAYS
1388         jne     .fail
1390 .create_map:
1392         mov     eax, [access]
1393         and     eax, SHM_ACCESS_MASK
1394         cmp     eax, [esi + SMEM.access]
1395         mov     [access], eax
1396         mov     edx, E_ACCESS
1397         ja      .fail
1399         mov     ebx, [current_slot]
1400         mov     ebx, [ebx + APPDATA.tid]
1401         mov     eax, sizeof.SMAP
1403         call    create_kernel_object
1404         test    eax, eax
1405         mov     edi, eax
1406         mov     edx, E_NOMEM
1407         jz      .fail
1409         inc     [esi + SMEM.refcount]
1411         mov     [edi + SMAP.magic], 'SMAP'
1412         mov     [edi + SMAP.destroy], destroy_smap
1413         mov     [edi + SMAP.parent], esi
1414         mov     [edi + SMAP.base], 0
1416         stdcall user_alloc, [esi + SMEM.size]
1417         test    eax, eax
1418         mov     [mapped], eax
1419         mov     edx, E_NOMEM
1420         jz      .cleanup2
1422         mov     [edi + SMAP.base], eax
1424         mov     ecx, [esi + SMEM.size]
1425         mov     [size], ecx
1427         shr     ecx, 12
1428         shr     eax, 10
1430         mov     esi, [esi + SMEM.base]
1431         shr     esi, 10
1432         lea     edi, [page_tabs + eax]
1433         add     esi, page_tabs
1435         mov     edx, [access]
1436         or      edx, [owner_access]
1437         shl     edx, 1
1438         or      edx, PG_SHARED + PG_UR
1440         lodsd
1441         and     eax, 0xFFFFF000
1442         or      eax, edx
1443         stosd
1444         loop    @B
1446         xor     edx, edx
1448         cmp     [owner_access], 0
1449         jne     .fail
1450 .exit:
1451         mov     edx, [size]
1452 .fail:
1453         mov     eax, [mapped]
1455         popfd
1456         pop     edi
1457         pop     esi
1458         pop     ebx
1459         ret
1460 .cleanup:
1461         mov     [size], edx
1462         mov     eax, esi
1463         call    free
1464         jmp     .exit
1466 .cleanup2:
1467         mov     [size], edx
1468         mov     eax, edi
1469         call    destroy_smap
1470         jmp     .exit
1471 endp
1473 align 4
1474 proc shmem_close stdcall, name:dword
1476         mov     eax, [name]
1477         test    eax, eax
1478         jz      .fail
1480         push    ebx ; Added
1481         push    esi
1482         push    edi
1483         pushfd
1484         cli
1486         mov     esi, [current_slot]
1487         add     esi, APP_OBJ_OFFSET
1488         mov     ebx, esi ; Fixed endless loop bug with not existing name (part 1)
1489 .next:
1490         mov     eax, [esi + APPOBJ.fd]
1491         test    eax, eax
1492         jz      @F
1494         cmp     eax, ebx ;esi ; Fixed endless loop bug with not existing name (part 2)
1495         je      @F            ; Small optimization
1496         mov     esi, eax
1497         ;je      @F
1499         cmp     [eax + SMAP.magic], 'SMAP'
1500         jne     .next
1502         mov     edi, [eax + SMAP.parent]
1503         test    edi, edi
1504         jz      .next
1506         lea     edi, [edi + SMEM.name]
1507         stdcall strncmp, [name], edi, 32
1508         test    eax, eax
1509         jne     .next
1511         stdcall user_free, [esi + SMAP.base]
1513         mov     eax, esi
1514         call    [esi + APPOBJ.destroy]
1516         popfd
1517         pop     edi
1518         pop     esi
1519         pop     ebx ; Added
1520 .fail:
1521         ret
1522 endp
1526 proc    user_ring stdcall, size:dword
1528 locals
1529         virt_ptr        dd ?
1530         phys_ptr        dd ?
1531         num_pages       dd ?
1532 endl
1534 ; Size must be an exact multiple of pagesize
1535         mov     eax, [size]
1536         test    eax, PAGE_SIZE-1
1537         jnz     .exit
1539 ; We must have at least one complete page
1540         shr     eax, 12
1541         jz      .exit
1542         mov     [num_pages], eax
1544 ; Allocate double the virtual memory
1545         mov     eax, [size]
1546         shl     eax, 1
1547         jz      .exit
1548         stdcall user_alloc, eax
1549         test    eax, eax
1550         jz      .exit
1551         mov     [virt_ptr], eax
1553 ; Now allocate physical memory
1554         stdcall alloc_pages, [num_pages]
1555         test    eax, eax
1556         jz      .exit_free_virt
1557         mov     [phys_ptr], eax
1559 ; Map first half of virtual memory to physical memory
1560         push    ecx esi edi
1561         mov     ecx, [num_pages]
1562         mov     esi, [virt_ptr]
1563         mov     edi, [phys_ptr]
1564   .loop1:
1565         stdcall map_page, esi, edi, PG_UWR
1566         add     esi, PAGE_SIZE
1567         add     edi, PAGE_SIZE
1568         dec     ecx
1569         jnz     .loop1
1571 ; Map second half of virtual memory to same physical memory
1572         mov     ecx, [num_pages]
1573         mov     edi, [phys_ptr]
1574   .loop2:
1575         stdcall map_page, esi, edi, PG_UWR
1576         add     esi, PAGE_SIZE
1577         add     edi, PAGE_SIZE
1578         dec     ecx
1579         jnz     .loop2
1580         pop     edi esi ecx
1582         mov     eax, [virt_ptr]
1583         ret
1585   .exit_free_virt:
1586         stdcall user_free, [virt_ptr]
1588   .exit:
1589         xor     eax, eax
1590         ret
1592 endp