]> pd.if.org Git - mmurtl/blob - ossource/memcode.asm
autocommit for file dated 2003-12-29 17:36:54
[mmurtl] / ossource / memcode.asm
1 ;=============================================================================\r
2 ;  MMURTL Operating System Source Code\r
3 ;  Copyright 1991,1992,1993,1994 Richard A. Burgess\r
4 ;  ALL RIGHTS RESERVED     Version 1.0\r
5 ;\r
6 .DATA\r
7 \r
8 .INCLUDE MOSEDF.INC\r
9 .INCLUDE TSS.INC\r
10 .INCLUDE JOB.INC\r
11 .ALIGN DWORD\r
12 ;\r
13 ;=============================================================================\r
14 ; Memory Management Data\r
15 ;=============================================================================\r
16 \r
17 PUBLIC _nPagesFree              DD 0                    ;Number of free physical pages left\r
18 PUBLIC _oMemMax                 DD 000FFFFFh    ;Default to 1 MB\r
19                                                                         ;Page Allocation Map\r
20 PUBLIC rgPAM    DB 2048 DUP (0)         ;1 bit/4Kbytes - 2048 bytes = 64Mb\r
21 PUBLIC sPAM             DD 32                           ;Deafult is 32 (1Mb)\r
22 sPAMmax                 EQU 2048                        ;Max is 2048 (64Mb)\r
23 \r
24 MemExch                 DD 00000000h            ;Semaphore exchange for Mem Mgmt\r
25 pNextPT                 DD 00000000h            ;We alloc the "next" page table\r
26                                                                         ;in advance (MANDATORY)\r
27 ;Some equates (MASKS) for PT Management\r
28 \r
29 ;             20 Bit Address      AVL00DA00UWP\r
30 MEMALIAS EQU  00000000000000000000100000000111b ;User Writable\r
31 MEMUSERD EQU  00000000000000000000000000000111b ;User Writable (Data)\r
32 MEMUSERC EQU  00000000000000000000000000000101b ;User Readable (Code)\r
33 MEMSYS   EQU  00000000000000000000000000000101b ;System Read/Write\r
34 ALIASBIT EQU  00000000000000000000100000000000b\r
35 PRSNTBIT EQU  00000000000000000000000000000001b\r
36 ;\r
37 ;=============================================================================\r
38 ; Memory Management Code\r
39 ;=============================================================================\r
40 \r
41 .CODE\r
42 \r
43 ;\r
44 ; MEMORY Management Code\r
45 ; OS Internal support calls (near) are at top of this file.\r
46 ; OS PUBLIC calls are at the bottom\r
47 ;\r
48 ; The following internals deal with PHYSICAL memory and the Page\r
49 ; Allocation Map (PAM).\r
50 ;\r
51 ;   InitMemMgmt  - Called to set up all OS memory management functions\r
52 ;\r
53 ;   FindHiPage   - Finds first available physical page from top of memory\r
54 ;                                  down and sets it     allocated then returns the\r
55 ;                                  Physical address of the page.\r
56 ;       FindLoPage   - Finds first available physical page from BOTTOM of memory\r
57 ;                                  and sets it allocated then returns the\r
58 ;                                  Physical address of the page. This is for DMA.\r
59 ;       MarkPage         - Given a physical page address, this SETS the PAM bit\r
60 ;                                  to allocate it.\r
61 ;       UnMarkPage   - Given the physical page address, this RESETS the PAM bit\r
62 ;                                  to deallocate it.\r
63 ;\r
64 ; The following internals deal with LINEAR memory and PTs.\r
65 ;\r
66 ;       LinToPhy    - Converts a linear to a physical address (OS or APP).\r
67 ;                 Also provides lin address to PTE in question.\r
68 ;                                 IN:   EBX is Linear address\r
69 ;                                       EAX is Job Number (for PD)\r
70 ;                                 OUT:  EAX is Physical address\r
71 ;                                               ESI is Linear address of PTE for EBX Lin Add\r
72 ;       FindRun     - Finds a run of FREE contiguous PTEs\r
73 ;                                 IN:   EAX = 0 for OS run, or 256 for User run\r
74 ;                                               EBX = nPages\r
75 ;                                 OUT:  EAX = Linear Address of run (0 if can't find)\r
76 ;                                               EBX = nPages (same as in)\r
77 ;       AddRun      - Creates one or more PTEs (first owner)\r
78 ;                                 IN:   EAX = Linear address of page(s) to add.\r
79 ;                                               EBX = count of pages\r
80 ;                                 OUT:  EAX = 0 if OK, else Error\r
81 ;                                               EBX = count of pages (same as in)\r
82 ;       AddDMARun   - Creates one or more PTEs (first owner)\r
83 ;                                       (Same as AddRUn except adds LO pages)\r
84 ;                                 IN:   EAX = Linear address of page(s) to add.\r
85 ;                                               EBX = count of pages\r
86 ;                                 OUT:  EAX = 0 if OK, else Error\r
87 ;                                               EBX = count of pages (same as in)\r
88 ;\r
89 ;       AliasRun    - Creates one or more ALIAS PTEs\r
90 ;\r
91 ;       AddUserPT   - Allocates physical memory and adds new PT to user PD\r
92 ;\r
93 ;       AddOSPT     - Allocates physical memory and adds new PT to ALL PDs\r
94 ;\r
95 ;========================================================================\r
96 \r
97 ;IN:   Nothing\r
98 ;OUT:  Nothing (except that you can use memory management routines now!)\r
99 ;USED: ALL REGISTERS ARE USED.\r
100 ;\r
101 ; This section finds out how much memory we have (in MBs) by writing\r
102 ; to the highest DWord in each meg until it fails a readback test.\r
103 ; It sets nPages Free after finding out just how much we have.\r
104 ; We assume 1MB to start (which means we start at 2Mb (1FFFFC).\r
105 ; It places the highest addressable offset in GLOBAL oMemMax.\r
106 ; We also calculate the number of pages of physical memory this\r
107 ; is and store it in the GLOBAL nPagesFree.\r
108 \r
109 PUBLIC InitMemMgmt:\r
110                 MOV _nPagesFree, 256    ;1 Mb of pages = 256\r
111                 MOV EAX,1FFFFCh         ;top of 2 megs (for DWORD)\r
112                 XOR EBX,EBX                             ;\r
113                 MOV ECX,06D72746CH      ;'mrtl' test string value for memory\r
114 MEMLoop:\r
115                 MOV DWORD PTR [EAX],0h  ;Set it to zero intially\r
116                 MOV DWORD PTR [EAX],ECX ;Move in test string\r
117                 MOV EBX,DWORD PTR [EAX] ;Read test string into EBX\r
118                 CMP EBX,ECX                             ;See if we got it back OK\r
119                 JNE MemLoopEnd                  ;NO!\r
120                 ADD EAX,3                               ;Yes, oMemMax must be last byte\r
121                 MOV _oMemMax,EAX                ;Set oMemMax\r
122                 SUB EAX,3                               ;Make it the last DWord again\r
123                 ADD EAX,100000h                 ;Next Meg\r
124                 ADD _nPagesFree, 256    ;Another megs worth of pages\r
125                 ADD sPAM, 32                    ;Increase PAM by another meg\r
126                 CMP EAX,3FFFFFCh        ;Are we above 64 megs\r
127                 JAE MemLoopEnd                  ;Yes!\r
128                 XOR EBX,EBX                             ;Zero out for next meg test\r
129                 JMP MemLoop\r
130 MemLoopEnd:\r
131 \r
132 ; Page Allocation Map is now sized and ZEROed\r
133 ; Now we must fill in bits used by OS which was just loaded and\r
134 ; the Video RAM and Boot ROM (neither of which we consider free).\r
135 ; This also fills out each of the Page Table Entries (PTEs) for the\r
136 ; initial OS code and data.  Note that linear address match physical\r
137 ; address for the initial OS data and code (its the law!)\r
138 \r
139 ; This first part MARKS the OS code and data pages as used\r
140 ; and makes PTEs.\r
141 ;\r
142                 MOV EDX, OFFSET pTbl1           ;EDX points to OS Page Table 1\r
143                 XOR EAX, EAX                            ;Point to 1st physical/linear page (0)\r
144 IMM001:\r
145                 MOV [EDX], EAX                          ;Make Page Table Entry\r
146                 AND DWORD PTR [EDX], 0FFFFF000h         ;Leave upper 20 Bits\r
147                 OR      DWORD PTR [EDX], 0001h                  ;Supervisor, Present\r
148                 MOV EBX, EAX\r
149                 CALL MarkPage                           ;Marks page in PAM\r
150                 ADD EDX, 4                                      ;Next table entry\r
151                 ADD EAX, 4096\r
152                 CMP EAX, 30000h                         ;Reserve 192K for OS (for now)\r
153                 JAE SHORT IMM002\r
154                 JMP SHORT IMM001                        ;Go for more\r
155 \r
156 ; Now we fill in PAM and PTEs for Video and ROM slots.\r
157 ; This covers A0000 thru 0FFFFFh (upper 384K of first Meg).\r
158 ; Right now we just mark everything from A0000 to FFFFF as used.\r
159 ; This routine could be expanded to search through the ROM pages of\r
160 ; ISA memory (C0000 -FFFFF) finding the unaccessable ones and marking\r
161 ; them as allocated in the PAM. Several chip sets on the market allow\r
162 ; you to set ROM areas as useable RAM (such as the 82C30 C&T).  But we\r
163 ; can't be sure everyone can do it, nor can we provide instructions\r
164 ; to everyone.\r
165 \r
166 IMM002:\r
167                 MOV EAX, 0A0000h                        ;Points to 128K Video & 256K ROM area\r
168                 MOV EBX, EAX                            ;\r
169                 SHR EBX, 10                                     ;Make it index (SHR 12, SHL 2)\r
170                 MOV EDX, OFFSET pTbl1           ;EDX pts to Page Table\r
171                 ADD EDX, EBX\r
172 IMM003:\r
173                 MOV [EDX], EAX                                  ;Make Page Table Entry\r
174                 AND DWORD PTR [EDX], 0FFFFF000h ;Leave upper 20 Bits\r
175                 OR      DWORD PTR [EDX], 0101b          ;Mark it "User" "ReadOnly" & "Present"\r
176                 MOV EBX, EAX                            ;Setup for MarkPage call\r
177                 CALL MarkPage                           ;Mark it used in the PAM\r
178                 ADD EDX, 4                                      ;Next PTE entry\r
179                 ADD EAX, 4096                           ;Next page please\r
180                 CMP EAX, 100000h                        ;1Mb yet?\r
181                 JAE IMM004                                      ;Yes\r
182                 JMP SHORT IMM003                        ;No, go back for more\r
183 \r
184 ; Initial Page Directory and the Page Table are static.\r
185 ; Now we can go into PAGED Memory mode.  This is done by loading\r
186 ; CR3 with the physcial address of the Page Directory, then reading\r
187 ; CR0, ANDing it with 8000000h and then writing it again.\r
188 ; After the MOV CR0 we must JMP to clear the prefetch queue of\r
189 ; any bogus physical addresses.\r
190 \r
191 IMM004:\r
192                 MOV EAX, OFFSET PDir1  ;Physical address of OS page directory\r
193                 MOV CR3, EAX            ;Store in Control Reg 3\r
194                 MOV EAX, CR0            ;Get Control Reg 0\r
195                 OR  EAX, 80000000h      ;Set paging bit ON\r
196                 MOV CR0, EAX            ;Store Control Reg 0\r
197                 JMP IM0005                      ;Clear prefetch queue\r
198 IM0005:\r
199 ;\r
200 ; Now we allocate an Exchange that the OS uses for a semaphore\r
201 ; use to prevent reentrant use of the any of the critical\r
202 ; memory managment functions.\r
203 ;\r
204                 LEA EAX, MemExch                ;Alloc Semaphore Exch for Memory calls\r
205                 PUSH EAX\r
206                 CALL FWORD PTR _AllocExch\r
207 \r
208                 PUSH MemExch                            ;Send a dummy message to pick up\r
209                 PUSH 0FFFFFFF1h\r
210                 PUSH 0FFFFFFF1h\r
211                 CALL FWORD PTR _SendMsg\r
212 \r
213 \r
214                 ;We must allocate a Page Table to be used when one\r
215                 ;must be added to a PD (User or OS).  This must be\r
216                 ;done in advance of finding out we need one because\r
217                 ;we may not have a linear address to access it in\r
218                 ;if the current PTs are all used up!  A tad complicated\r
219                 ;I'm afraid...\r
220 \r
221                 PUSH 1                                          ; 1 page for Next Page Table\r
222                 MOV EAX, OFFSET pNextPT         ;\r
223                 PUSH EAX\r
224                 CALL FWORD PTR _AllocOSPage     ; Get 'em!\r
225 \r
226                 RETN                            ;Done initializing memory managment\r
227 ;\r
228 \r
229 ;========================================================================\r
230 FindHiPage:\r
231 ; This finds the first unused physical page in memory from the TOP down\r
232 ; and returns the physical address of it to the caller.\r
233 ; It also MARKS the page as used (assuming that we will allocate it).\r
234 ; Of course this means if we call FindHiPage and don't use it we\r
235 ; must call UnMarkPage to release it.\r
236 ; This reduces nPagesFree by one.\r
237 ;\r
238 ;IN  :  Nothing\r
239 ;OUT :  EBX is the physical address of the new page, or 0 if error\r
240 ;USED:  EBX, Flags\r
241 \r
242                 PUSH EAX\r
243                 PUSH ECX\r
244                 PUSH EDX\r
245                 MOV ECX, OFFSET rgPAM           ;Page Allocation Map\r
246                 MOV EAX, sPAM                           ;Where we are in PAM\r
247                 DEC EAX                                         ;EAX+ECX will be offset into PAM\r
248 FHP1:\r
249                 CMP BYTE PTR [ECX+EAX],0FFh             ;All 8 pages used?\r
250                 JNE FHP2                                        ;No\r
251                 CMP EAX, 0                                      ;Are we at Bottom of PAM?\r
252                 JE  FHPn                                        ;no memory left...\r
253                 DEC EAX                                         ;Another Byte lower\r
254                 JMP SHORT FHP1                          ;Back for next byte\r
255 FHP2:\r
256                 MOV EBX, 7                                      ;\r
257                 XOR EDX, EDX\r
258                 MOV DL, BYTE PTR [ECX+EAX]      ;Get the byte with a whole in it...\r
259 FHP3:\r
260                 BT  EDX, EBX                            ;Test bits\r
261                 JNC FHPf                                        ;FOUND ONE! (goto found)\r
262                 CMP EBX, 0                                      ;At the bottom of the Byte?\r
263                 JE  FHPn                                        ;Error (BAD CPU???)\r
264                 DEC EBX                                         ;Next bit\r
265                 JMP FHP3\r
266 FHPf:\r
267                 BTS EDX, EBX                            ;Set the bit indexed by EBX\r
268                 MOV BYTE PTR [ECX+EAX], DL      ;Set page in use\r
269                 SHL EAX, 3                                      ;Multiply time 8 (page number base in byte)\r
270                 ADD EBX, EAX                            ;Add page number in byte\r
271                 SHL EBX, 12                                     ;Now EBX = Physical Page Addr (EBX*4096)\r
272                 DEC _nPagesFree                         ;One less available\r
273                 POP EDX\r
274                 POP ECX\r
275                 POP EAX\r
276                 RETN\r
277 FHPn:\r
278                 XOR EBX, EBX                            ;Set to zero for error\r
279                 POP EDX\r
280                 POP ECX\r
281                 POP EAX\r
282                 RETN\r
283 ;========================================================================\r
284 FindLoPage:\r
285 ; This finds the first unused physical page in memory from the BOTTOM up.\r
286 ; It also MARKS the page as used (assuming that we will allocate it).\r
287 ; Of course this means if we call FindLoPage and don't use it we\r
288 ; must call UnMarkPage to release it.\r
289 ; This reduces nPagesFree by one.\r
290 ;\r
291 ;IN  :  Nothing\r
292 ;OUT :  EBX is the physical address of the new page, or 0 if error\r
293 ;USED:  EBX, Flags\r
294 \r
295                 PUSH EAX\r
296                 PUSH ECX\r
297                 PUSH EDX\r
298                 MOV ECX, OFFSET rgPAM           ;Page Allocation Map\r
299                 XOR EAX, EAX                            ;Start at first byte in PAM\r
300 FLP1:\r
301                 CMP BYTE PTR [ECX+EAX],0FFh             ;All 8 pages used?\r
302                 JNE FLP2                                        ;No\r
303                 INC EAX                                         ;Another Byte higher\r
304                 CMP EAX, sPAM                           ;Are we past at TOP of PAM?\r
305                 JAE FLPn                                        ;no memory left...\r
306                 JMP SHORT FLP1                          ;Back for next byte\r
307 FLP2:\r
308                 XOR EBX, EBX                            ;\r
309                 XOR EDX, EDX\r
310                 MOV DL, BYTE PTR [ECX+EAX]      ;Get the byte with a whole in it...\r
311 FLP3:\r
312                 BT  EDX, EBX                            ;Test bits\r
313                 JNC FLPf                                        ;FOUND ONE! (goto found)\r
314                 INC EBX                                         ;Next bit\r
315                 CMP EBX, 8                                      ;End of the Byte?\r
316                 JAE FLPn                                        ;Error (BAD CPU???)\r
317                 JMP FLP3\r
318 FLPf:\r
319                 BTS EDX, EBX                            ;Set the bit indexed by EBX\r
320                 MOV BYTE PTR [ECX+EAX], DL      ;Set page in use\r
321 \r
322                 SHL EAX, 3                                      ;Multiply time 8 (page number base in byte)\r
323                 ADD EBX, EAX                            ;Add page number in byte\r
324                 SHL EBX, 12                                     ;Now EBX = Physical Page Addr (EBX*4096)\r
325                 DEC _nPagesFree                         ;One less available\r
326                 POP EDX\r
327                 POP ECX\r
328                 POP EAX\r
329                 RETN\r
330 FLPn:\r
331                 XOR EBX, EBX                            ;Set to zero for error\r
332                 POP EDX\r
333                 POP ECX\r
334                 POP EAX\r
335                 RETN\r
336 \r
337 ;========================================================================\r
338 MarkPage:\r
339 ; Given a physical memory address, this finds the bit in the PAM associated\r
340 ; with it and SETS it to show the physical page in use.  This is used\r
341 ; with the routines that initialize all memory mgmt function.\r
342 ; This reduces nPagesFree by one.\r
343 ;\r
344 ;IN  :  EBX is the physical address of the page to mark\r
345 ;OUT :  Nothing\r
346 ;USED:  EBX, Flags\r
347 \r
348                 PUSH EAX\r
349                 PUSH ECX\r
350                 PUSH EDX\r
351                 MOV EAX, OFFSET rgPAM           ;Page Allocation Map\r
352                 AND EBX, 0FFFFF000h                     ;Round down to page modulo 4096\r
353                 MOV ECX, EBX\r
354                 SHR ECX, 15                                     ;ECX is now byte offset into PAM\r
355                 SHR EBX, 12                                     ;Get Bit offset into PAM\r
356                 AND EBX, 07h                            ;EBX is now bit offset into byte of PAM\r
357                 MOV DL, [EAX+ECX]                       ;Get the byte into DL\r
358                 BTS EDX, EBX                            ;BitSet nstruction with Bit Offset\r
359                 MOV [EAX+ECX], DL                       ;Save the new PAM byte\r
360                 DEC _nPagesFree                         ;One less available\r
361                 POP EDX\r
362                 POP ECX\r
363                 POP EAX\r
364                 RETN\r
365 ;========================================================================\r
366 UnMarkPage:\r
367 ; Given a physical memory address, this finds the bit in the PAM associated\r
368 ; with it and RESETS it to show the physical page available again.\r
369 ; This increases nPagesFree by one.\r
370 ;\r
371 ;IN  :  EBX is the physical address of the page to UNmark\r
372 ;OUT :  Nothing\r
373 ;USED:  EBX, Flags\r
374 \r
375                 PUSH EAX\r
376                 PUSH ECX\r
377                 PUSH EDX\r
378                 MOV EAX, OFFSET rgPAM           ;Page Allocation Map\r
379                 AND EBX, 0FFFFF000h                     ;Round down to page modulo\r
380                 MOV ECX, EBX\r
381                 SHR ECX, 15                                     ;ECX is now byte offset into PAM\r
382                 SHR EBX, 12                                     ;\r
383                 AND EBX, 07h                            ;EBX is now bit offset into byte of PAM\r
384                 ADD EAX, ECX\r
385                 MOV DL, [EAX]\r
386                 BTR EDX, EBX                            ;BitReset instruction\r
387                 MOV [EAX], DL\r
388                 INC _nPagesFree                         ;One more available\r
389                 POP EDX\r
390                 POP ECX\r
391                 POP EAX\r
392                 RETN\r
393 \r
394 ;============================================================\r
395 ;\r
396 ; LinToPhy\r
397 ; Looks Up the Physical address of a 32 bit linear address passed in.\r
398 ; The JCB is used to identify who's page tables we are translating.\r
399 ; The linear address is used to look up the Page Table entry which is\r
400 ; used to get the physical address.  This call is used for things like\r
401 ; aliasing for messages, DMA operations, etc.\r
402 ; This also leave the Linear Address of the PTE itself in ESI\r
403 ; for callers that need it.\r
404 ;\r
405 ; INPUT:        EAX -- Job Number that owns memory we are aliasing\r
406 ;                       EBX -- Linear address\r
407 ;\r
408 ; OUTPUT:       EAX -- Physical Address\r
409 ;           ESI -- Linear Address of PTE for this linear address\r
410 ;\r
411 ; USED:         EAX, EBX, ESI, EFlags\r
412 ;\r
413 PUBLIC LinToPhy:\r
414                 PUSH EBX                                ;Save Linear\r
415                 CALL GetpJCB                    ;Leaves pJCB in EAX\r
416                 MOV EAX, [EAX+JcbPD]    ;EAX now has ptr to PD!\r
417                 ADD EAX, 2048                   ;Move to shadow addresses in PD\r
418                 SHR EBX, 22                             ;Shift out lower 22 bits leaving 10 bit offset\r
419                 SHL EBX, 2                              ;*4 to make it a byte offset into PD shadow\r
420                 ADD EBX, EAX                    ;EBX/EAX now points to shadow\r
421                 MOV EAX, [EBX]                  ;EAX now has Linear of Page Table\r
422                 POP EBX                                 ;Get original linear back in EBX\r
423                 PUSH EBX                                ;Save it again\r
424                 AND EBX, 003FFFFFh              ;Get rid of upper 10 bits\r
425                 SHR EBX, 12                             ;get rid of lower 12 to make it an index\r
426                 SHL EBX, 2                              ;*4 makes it byte offset in PT\r
427                 ADD     EBX, EAX                        ;EBX now points to Page Table entry!\r
428                 MOV ESI, EBX                    ;Save this address for caller\r
429                 MOV EAX, [EBX]                  ;Physical base of page is in EAX\r
430                 AND EAX, 0FFFFF000h             ;mask off lower 12\r
431                 POP EBX                                 ;Get original linear\r
432                 AND EBX, 00000FFFh              ;Cut off upper 22 bits of linear\r
433                 OR EAX, EBX                             ;EAX now has REAL PHYSICAL ADDRESS!\r
434                 RETN\r
435 \r
436 ;=============================================================================\r
437 ; FindRun\r
438 ; This finds a linear run of FREE LINEAR memory in one of the USER or OS PTs.\r
439 ; This is either at address base 0 (for OS) or 1Gb (for user).\r
440 ; EAX = 0 if we are looking for OS memory, else\r
441 ; EAX = 256 if we are looking for USER memory.\r
442 ; The linear address of the run is returned in EAX unless no\r
443 ; run that large exists, in which case we return 0.\r
444 ; The linear run may span page tables (if they already exist).\r
445 ; This is an interesting routine because it uses two nested loops\r
446 ; to walk thru the page directory and page tables while using the\r
447 ; SIB (Scale Index Base) addressing of the 386 for indexing.\r
448 ;\r
449 ; IN :  EAX  PD Shadow Base Offset for memory (0 for OS, 256 for user)\r
450 ;               EBX  Number of Pages for run\r
451 ;\r
452 ; OUT:  EAX  Linear address or 0 if no run is large enough\r
453 ;               EBX  still has count of pages\r
454 ; USED: EAX, EBX, EFlags  (all other registers saved & restored)\r
455 ;\r
456 ;\r
457 FindRun:\r
458                 PUSH EBX                                ;Holds count of pages (saved for caller)\r
459                 PUSH ECX                                ;Keeps count of how many free found so far\r
460                 PUSH EDX                                ;Index into PD for PT we are working on\r
461                 PUSH ESI                                ;Address of PD saved here\r
462                 PUSH EDI                                ;\r
463 \r
464                 MOV ECX, EBX                    ;Copy number of pages to ECX. Save in EBX\r
465                 MOV EDX, EAX                    ;Index into shadow addresses from EAX\r
466 \r
467                 CALL GetpCrntJCB                ;Leaves pCrntJCB in EAX\r
468                 MOV ESI, [EAX+JcbPD]    ;ESI now has ptr to PD\r
469                 ADD ESI, 2048                   ;Move to shadow addresses\r
470 \r
471 FR0:\r
472                 MOV EDI, [ESI+EDX*4]    ;Linear address of next page table into EDI\r
473                 OR EDI, EDI                             ;Is the address NON-ZERO (valid)?\r
474                 JNZ FR1                                 ;Yes, go for it\r
475                 XOR EAX, EAX                    ;Return 0 cause we didn't find it!\r
476                 JMP SHORT FREXIT                ;\r
477 FR1:\r
478                 XOR EAX, EAX                    ;EAX indexes into PT (to compare PTEs)\r
479 FR2:\r
480                 CMP EAX, 1024                   ;Are we past last PTE of this PT?\r
481                 JB  FR3                                 ;No, keep testing\r
482                 INC EDX                                 ;Next PT!\r
483                 JMP SHORT FR0                   ;\r
484 FR3:\r
485                 CMP DWORD PTR [EDI+EAX*4], 0    ;Zero means it's empty (available)\r
486                 JNE     FR4                                                     ;In use\r
487                 DEC ECX                                 ;One more empty one!\r
488                 JZ  FROK                                ;We found enough entries goto OK\r
489                 INC EAX                                 ;Not done yet, Next PTE Please.\r
490                 JMP SHORT FR2                   ;\r
491 FR4:\r
492                 ;If we got here we must reset ECX for full count and\r
493                 ;go back and start looking again\r
494                 INC EAX                                 ;Not empty, next PTE please\r
495                 MOV ECX, EBX                    ;We kept original count in EBX\r
496                 JMP FR2\r
497 FROK:\r
498                 ;If we got here it means that ECX has made it to zero and\r
499                 ;we have a linear run large enough to satisy the request.\r
500                 ;The starting linear address is equal to number of the last\r
501                 ;PTE we found minus ((npages -1) * 4096)\r
502                 ;EDX was index into PD, while EAX was index into PT.\r
503                 ;EBX still has count of pages.\r
504 \r
505                 SHL EDX, 22                     ;EDX is 10 MSBs of Linear Address\r
506                 SHL EAX, 12                     ;EAX is next 10 bits of LA\r
507                 OR EAX, EDX                     ;This is the linear address we ended at\r
508                 DEC EBX                         ;One less page (0 offset)\r
509                 SHL EBX, 12                     ;Times size of page (* 4096)\r
510                 SUB EAX, EBX            ;From current linear address in tables\r
511 \r
512 FREXIT:\r
513                 POP EDI                         ;\r
514                 POP ESI                         ;\r
515                 POP EDX                         ;\r
516                 POP ECX                         ;\r
517                 POP EBX                         ;\r
518                 RETN\r
519 ;=============================================================================\r
520 ; AddRun\r
521 ; This adds one or more PTEs to a page table (or tables if the run\r
522 ; spans two or more tables).\r
523 ; The address determines the protection level of the PTE's we add.\r
524 ; If it is less than 1GB it means OS memory which we will set to SYSTEM.\r
525 ; Above 1Gb is user which we will set to user level protection.\r
526 ; The linear address of the run should be in EAX, and the count of\r
527 ; pages should be in EBX (this is the way FindRun left them).\r
528 ;\r
529 ; IN :  EAX  Linear address of first page\r
530 ;               EBX  Number of Pages to add\r
531 ; OUT:  Nothing\r
532 ; USED: EAX, EFlags\r
533 ;\r
534 AddRun:\r
535                 PUSH EBX                                ;(save for caller)\r
536                 PUSH ECX                                ;\r
537                 PUSH EDX                                ;\r
538                 PUSH ESI                                ;\r
539                 PUSH EDI                                ;\r
540 \r
541                 MOV ECX, EBX                    ;Copy number of pages to ECX (EBX free to use).\r
542                 MOV EDX, EAX                    ;LinAdd to EDX\r
543                 SHR EDX, 22                             ;Get index into PD for first PT\r
544                 SHL EDX, 2                              ;Make it index to DWORDS\r
545 \r
546                 PUSH EAX                                ;Save EAX thru GetpCrntJCB call\r
547                 CALL GetpCrntJCB                ;Leaves pCrntJCB in EAX\r
548                 MOV ESI, [EAX+JcbPD]    ;ESI now has ptr to PD!\r
549                 POP EAX                                 ;Restore linear address\r
550 \r
551                 ADD ESI, 2048                   ;Offset to shadow address of PD\r
552                 ADD ESI, EDX                    ;ESI now points to initial PT (EDX now free)\r
553 \r
554                 MOV EDX, EAX                    ;LinAdd into EDX again\r
555                 AND EDX, 003FF000h              ;get rid of upper 10 bits & lower 12\r
556                 SHR EDX, 10                     ;Index into PD for PT (10 vice 12 -> DWORDS)\r
557 AR0:\r
558                 MOV EDI, [ESI]                  ;Linear address of next page table into EDI\r
559 \r
560                 ;At this point, EDI is pointing the next PT.\r
561                 ;SO EDI+EDX will point to the next PTE to do.\r
562                 ;Now we must call FindPage to get a physical address into EBX,\r
563                 ;then check the original linear address to see if SYSTEM or USER\r
564                 ;and OR in the appropriate control bits, THEN store it in PT.\r
565 \r
566 AR1:\r
567                 CALL FindHiPage                 ;EBX has Phys Pg (only EBX affected)\r
568                 OR EBX, MEMSYS                  ;Set PTE to present, User ReadOnly\r
569                 CMP EAX, 40000000h              ;See if it's a user page\r
570                 JB  AR2\r
571                 OR EBX, MEMUSERD                ;Sets User/Writable bits of PTE\r
572 \r
573 AR2:\r
574                 MOV DWORD PTR [EDI+EDX], EBX    ;EDX is index to exact entry\r
575                 DEC ECX                                                 ;Are we done??\r
576                 JZ ARDone\r
577                 ADD EDX, 4                              ;Next PTE please.\r
578                 CMP EDX, 4096                   ;Are we past last PTE of this PT?\r
579                 JB AR1                                  ;No, go do next PTE\r
580                 ADD ESI, 4                              ;Yes, next PDE (to get next PT)\r
581                 XOR EDX,EDX                             ;Start at the entry 0 of next PT\r
582                 JMP SHORT AR0                   ;\r
583 ARDone:\r
584                 POP EDI                         ;\r
585                 POP ESI                         ;\r
586                 POP EDX                         ;\r
587                 POP ECX                         ;\r
588                 POP EBX                         ;\r
589                 RETN\r
590 \r
591 ;=============================================================================\r
592 ; AddDMARun\r
593 ; This adds one or more PTEs to a page table (or tables if the run\r
594 ; spans two or more tables).\r
595 ; The address determines the protection level of the PTE's we add.\r
596 ; If it is less than 1GB it means OS memory which we will set to SYSTEM.\r
597 ; Above 1Gb is user which we will set to user level protection.\r
598 ; The linear address of the run should be in EAX, and the count of\r
599 ; pages should be in EBX (this is the way FindRun left them).\r
600 ;\r
601 ; IN :  EAX  Linear address of first page\r
602 ;               EBX  Number of Pages to add\r
603 ; OUT:  Nothing\r
604 ; USED: EAX, EFlags\r
605 ;\r
606 AddDMARun:\r
607                 PUSH EBX                                ;(save for caller)\r
608                 PUSH ECX                                ;\r
609                 PUSH EDX                                ;\r
610                 PUSH ESI                                ;\r
611                 PUSH EDI                                ;\r
612 \r
613                 MOV ECX, EBX                    ;Copy number of pages to ECX (EBX free to use).\r
614                 MOV EDX, EAX                    ;LinAdd to EDX\r
615                 SHR EDX, 22                             ;Get index into PD for first PT\r
616                 SHL EDX, 2                              ;Make it index to DWORDS\r
617 \r
618                 PUSH EAX                                ;Save EAX thru GetpCrntJCB call\r
619                 CALL GetpCrntJCB                ;Leaves pCrntJCB in EAX\r
620                 MOV ESI, [EAX+JcbPD]    ;ESI now has ptr to PD!\r
621                 POP EAX                                 ;Restore linear address\r
622 \r
623                 ADD ESI, 2048                   ;Offset to shadow address of PD\r
624                 ADD ESI, EDX                    ;ESI now points to initial PT (EDX now free)\r
625 \r
626                 MOV EDX, EAX                    ;LinAdd into EDX again\r
627                 AND EDX, 003FF000h              ;get rid of upper 10 bits & lower 12\r
628                 SHR EDX, 10                     ;Index into PD for PT (10 vice 12 -> DWORDS)\r
629 ARD0:\r
630                 MOV EDI, [ESI]                  ;Linear address of next page table into EDI\r
631 \r
632                 ;At this point, EDI is pointing the next PT.\r
633                 ;SO EDI+EDX will point to the next PTE to do.\r
634                 ;Now we must call FindPage to get a physical address into EBX,\r
635                 ;then check the original linear address to see if SYSTEM or USER\r
636                 ;and OR in the appropriate control bits, THEN store it in PT.\r
637 \r
638 ARD1:\r
639                 CALL FindLoPage                 ;EBX has Phys Pg (only EBX affected)\r
640                 OR EBX, MEMSYS                  ;Set PTE to present, User ReadOnly\r
641                 MOV DWORD PTR [EDI+EDX], EBX    ;EDX is index to exact entry\r
642                 DEC ECX                                                 ;Are we done??\r
643                 JZ ARDDone\r
644                 ADD EDX, 4                              ;Next PTE please.\r
645                 CMP EDX, 4096                   ;Are we past last PTE of this PT?\r
646                 JB ARD1                                 ;No, go do next PTE\r
647                 ADD ESI, 4                              ;Yes, next PDE (to get next PT)\r
648                 XOR EDX,EDX                             ;Start at the entry 0 of next PT\r
649                 JMP SHORT ARD0                  ;\r
650 ARDDone:\r
651                 POP EDI                         ;\r
652                 POP ESI                         ;\r
653                 POP EDX                         ;\r
654                 POP ECX                         ;\r
655                 POP EBX                         ;\r
656                 RETN\r
657 \r
658 ;=============================================================================\r
659 ; AddAliasRun\r
660 ; This adds one or more PTEs to a page table (or tables if the run\r
661 ; spans two or more tables) adding PTEs from another job's PTs marking\r
662 ; them as ALIAS entries.\r
663 ; Aliased runs are ALWAYS at USER protection levels even if in the\r
664 ; OS address span!\r
665 ;\r
666 ; The NEW linear address of the run should be in EAX, and the count of\r
667 ; pages should be in EBX (this is the way FindRun left them).\r
668 ; ESI has the linear address we are aliasing and EDX has the Job#\r
669 ;\r
670 ; IN :  EAX  Linear address of first page of new alias entries\r
671 ;            (from find run)\r
672 ;               EBX  Number of Pages to alias\r
673 ;       ESI  Linear Address of pages to Alias (from other job)\r
674 ;       EDX  Job Number of Job we are aliasing\r
675 ;\r
676 ; OUT:  Nothing\r
677 ; USED: EAX, EFlags\r
678 ;\r
679 AliasLin    EQU DWORD PTR [EBP-4]\r
680 AliasJob    EQU DWORD PTR [EBP-8]\r
681 \r
682 AddAliasRun:\r
683                 PUSH EBP                ;\r
684                 MOV EBP,ESP             ;\r
685                 SUB ESP, 8\r
686 \r
687                 MOV AliasLin, ESI\r
688                 MOV AliasJob, EDX\r
689 \r
690                 PUSH EBX                                ;(save for caller)\r
691                 PUSH ECX                                ;\r
692                 PUSH EDX                                ;\r
693                 PUSH ESI                                ;\r
694                 PUSH EDI                                ;\r
695 \r
696                 ;This first section sets to make [ESI] point to first PT that\r
697                 ;we have to move the other guy's physical pages into\r
698 \r
699                 MOV ECX, EBX                    ;Copy number of pages to ECX (EBX free to use).\r
700                 MOV EDX, EAX                    ;LinAdd to EDX\r
701                 SHR EDX, 22                             ;Get index into PD for first PT\r
702                 SHL EDX, 2                              ;Make it index to DWORDS\r
703 \r
704                 PUSH EAX                                ;Save EAX thru GetpCrntJCB call\r
705                 CALL GetpCrntJCB                ;Leaves pCrntJCB in EAX\r
706                 MOV ESI, [EAX+JcbPD]    ;ESI now has linear address of PD\r
707                 POP EAX                                 ;Restore linear address\r
708 \r
709                 ADD ESI, 2048                   ;Offset to shadow addresses in PD\r
710                 ADD ESI, EDX                    ;ESI now points to first PT of interest\r
711 \r
712                 MOV EDX, EAX                    ;LinAdd into EDX again\r
713                 AND EDX, 003FF000h              ;get rid of upper 10 bits & lower 12\r
714                 SHR EDX, 10                     ;Index into PD for PT (10 vice 12 -> DWORDS)\r
715 ALR0:\r
716                 MOV EDI, [ESI]                  ;Linear address of crnt page table into EDI\r
717 \r
718                 ;At this point, EDI is pointing to the PT we are in.\r
719                 ;SO then EDI+EDX will point to the next PTE to do.\r
720                 ;Now we must call LinToPhy with Linear Add & JobNum\r
721                 ; to get a physical address into EAX.\r
722                 ;This is the Physical address to store in the new PTE.  We must\r
723                 ;mark it MEMALIAS before adding it to PT.\r
724 ALR1:\r
725                 PUSH ESI                                ;Save for next loop (used by LinToPhy)\r
726 \r
727                 MOV EAX, AliasJob               ;Job we are aliasing\r
728                 MOV EBX, AliasLin               ;Address we are aliasing\r
729                 ADD AliasLin, 4096              ;Set up for next loop (post increment)\r
730                 CALL LinToPhy                   ;\r
731 \r
732                 ;EAX now has physical address for this page\r
733                 ;\r
734 \r
735                 AND EAX, 0FFFFF000h             ;cut off system bits of PTE\r
736                 OR EAX, MEMALIAS                ;Set system bits as ALIAS\r
737 \r
738                 POP     ESI                                     ;Restore ESI (LinToPhy used it)\r
739 \r
740                 ;Now store it in new PTE\r
741 \r
742                 MOV DWORD PTR [EDI+EDX], EAX    ;EDX is index to exact entry\r
743 \r
744                 DEC ECX                                 ;Are we done??\r
745                 JZ ALRDone\r
746                 ADD EDX, 4                              ;Next PTE please.\r
747                 CMP EDX, 4096                   ;Are we past last PTE of this PT?\r
748                 JB ALR1                                 ;No, go do next PTE\r
749                 ADD ESI, 4                              ;Yes, next PDE (to get next PT)\r
750                 XOR EDX,EDX                             ;Start at the entry 0 of next PT\r
751                 JMP SHORT ALR0                  ;\r
752 ALRDone:\r
753                 POP EDI                         ;\r
754                 POP ESI                         ;\r
755                 POP EDX                         ;\r
756                 POP ECX                         ;\r
757                 POP EBX                         ;\r
758 \r
759                 MOV ESP,EBP             ;\r
760                 POP EBP                 ;\r
761                 RETN\r
762 \r
763 ;=============================================================================\r
764 ; AddUserPT\r
765 ; This creates a new User Page Table, initializes it and sticks it\r
766 ; in the Users's PD (in User Address space above 1GB).\r
767 ; This is easier than AddOSPT because there is no need to update\r
768 ; anyone else's PDs!  This sets the protection on the PT to user\r
769 ; Read & Write.  Individual PTEs will be set read only for code.\r
770 ;\r
771 ; IN :  Nothing\r
772 ; OUT:  0 if OK or Error (ErcNoMem - no free phy pages!)\r
773 ; USED: EAX, EFlags\r
774 ;\r
775 AddUserPT:\r
776                 PUSH EBX                                ;(save for caller)\r
777                 PUSH ECX                                ;\r
778                 PUSH EDX                                ;\r
779                 PUSH ESI                                ;\r
780                 PUSH EDI                                ;\r
781 \r
782                 MOV EAX, _nPagesFree    ;See if have enuf physical memory\r
783                 OR EAX, EAX\r
784                 JNZ AUPT01\r
785                 MOV EAX, ErcNoMem               ;Sorry, out of physical mem\r
786                 JMP AUPTDone\r
787 AUPT01:\r
788                 CALL GetCrntJobNum              ;Leaves job num in EAX (for LinToPhy)\r
789                 MOV EBX, pNextPT                ;Pre allocated Page (Linear Address)\r
790                 CALL LinToPhy                   ;EAX will have Physical address\r
791 \r
792                 ; Put it in the User PD (and linear in shadow).\r
793                 ; Find first empty slot\r
794 \r
795                 CALL GetpCrntJCB                ;pJCB in EAX\r
796                 MOV EDI, JcbPD                  ;Offset to PcbPD in JCB\r
797                 ADD EDI, EAX                    ;EDI points to UserPD Address\r
798                 MOV ESI, [EDI]                  ;ESI now points to PD\r
799                 ADD ESI, 2048                   ;ESI now points to upper 1 GB in PD\r
800                 MOV ECX, 511                    ;Number of entries (at least 1 is already gone)\r
801 AUPT02:\r
802                 ADD ESI, 4                              ; Next possible empty entry\r
803                 MOV     EBX, [ESI]\r
804                 OR EBX, EBX                     ; Is it empty?\r
805                 LOOPNZ AUPT02                   ; No! (Try again)\r
806 \r
807                 ; ESI now points to empty Slot\r
808                 ; Physical Address of new table is still in EAX\r
809                 ; Get Linear address back into EBX\r
810                 ; and put them into PD\r
811 \r
812                 OR  EAX, MEMUSERD               ;Set user bits (Read/Write)\r
813                 MOV [ESI], EAX                  ;Physical address in lower half\r
814                 ADD ESI, 2048                   ;Move to shadow\r
815                 MOV EBX, pNextPT                ;Linear add back into EBX\r
816                 MOV [ESI], EBX                  ;Put in Linear address of PT (upper half)\r
817 \r
818                 ;Now we now need another PreAllocated Page Table for\r
819                 ;next time. Get a run of 1 for next new page table\r
820 \r
821                 MOV EBX, 1                              ;size of request\r
822                 XOR EAX, EAX                    ;PD shadow offset needed by FindRun (0)\r
823                 CALL FindRun\r
824                 OR EAX, EAX                             ;was there an error (0 means no mem)\r
825                 JNZ AUPT05\r
826                 MOV EAX, ErcNoMem               ;\r
827                 JMP SHORT AUPTDone\r
828 AUPT05:\r
829                 MOV pNextPT, EAX                ;save pNextPT (the linear address)\r
830                 CALL AddRun                             ;AddRun will return NON-ZERO on error\r
831 AUPTDone:\r
832                 POP EDI                         ;\r
833                 POP ESI                         ;\r
834                 POP EDX                         ;\r
835                 POP ECX                         ;\r
836                 POP EBX                         ;\r
837                 RETN\r
838 \r
839 ;=============================================================================\r
840 ; AddOSPT\r
841 ; This creates a new OS Page Table, initializes it and sticks it\r
842 ; in the OS's PD (in OS address space below 1GB).\r
843 ; This also updates ALL PDs for ALL jobs.  We must do this\r
844 ; to ensure the OS code can reach its memory no matter what JOB/TASK\r
845 ; it is running in.\r
846 ;\r
847 ; IN :  Nothing\r
848 ; OUT:  0 if OK or Error (ErcNoMem - no free phy pages!)\r
849 ; USED: EAX, EFlags\r
850 ;\r
851 AddOSPT:\r
852                 PUSH EBX                                ;(save for caller)\r
853                 PUSH ECX                                ;\r
854                 PUSH EDX                                ;\r
855                 PUSH ESI                                ;\r
856                 PUSH EDI                                ;\r
857 \r
858                 MOV EAX, _nPagesFree    ;See if have enuf physical memory\r
859                 OR EAX, EAX\r
860                 JNZ AOPT01\r
861                 MOV EAX, ErcNoMem               ;Sorry, out of physical mem\r
862                 JMP AOPTDone\r
863 AOPT01:\r
864                 MOV EAX, 1                              ;OS Job Number (Monitor)\r
865                 MOV EBX, pNextPT                ;Pre allocated Page (Linear Address)\r
866                 CALL LinToPhy                   ;EAX will have Physical address\r
867 \r
868                 ; Put it in the OS PD (and linear in shadow).\r
869                 ; Find first empty slot\r
870 \r
871                 MOV ESI, OFFSET PDir1   ; ESI points to OS Pdir\r
872                 MOV ECX, 511                    ; Count of PDEs to check\r
873 AOPT02:\r
874                 ADD ESI, 4                              ; Next possible empty entry\r
875                 MOV EBX, [ESI]\r
876                 OR EBX, EBX                             ; Is it empty?\r
877                 LOOPNZ AOPT02                   ; No! (Try again)\r
878 \r
879                 ; ESI now points to empty PDir Slot\r
880                 ; EAX still has Physical Address of new table\r
881                 ; Get Physical Address back into EBX\r
882                 ; and put them into PDir\r
883 \r
884                 OR EAX, PRSNTBIT                ;Set present bit\r
885                 MOV [ESI], EAX                  ;Physical address in lower half\r
886                 ADD ESI, 2048                   ;Move to shadow\r
887                 MOV EBX, pNextPT                ;Linear add back into EBX\r
888                 MOV [ESI], EBX                  ;Put in Linear address of PT (upper half)\r
889 \r
890                 ; Update ALL PDs from PDir1 !!\r
891                 ; This doesn't happen often if it happens at all.\r
892                 ; The OS will usually not take 4 MBs even with ALL\r
893                 ; of its dynamic structures (except on\r
894                 ; a 32 Mb system or larger and when fully loaded)\r
895 \r
896                 MOV EDX, nJCBs                  ; # of dynamic JCBs\r
897 AOPT03:\r
898                 MOV EAX, EDX                    ;Next JCB\r
899                 CALL GetpJCB                    ;EAX now has pointer to a job's PD\r
900                 MOV ECX, [EAX+JcbPD]    ;See if PD id zero (Inactive JCB)\r
901                 OR ECX, ECX                             ;Is it a valid Job? (0 if not)\r
902                 JZ AOPT04                               ;No, Not a valid JCB (unused)\r
903 \r
904                 ADD EAX, JcbPD                  ;EAX NOW points to PD of JCB\r
905                 MOV EBX, OFFSET PDir1   ;Source of Copy\r
906 \r
907                 PUSH EDX                                ;Save nJCB we are on\r
908 \r
909                 PUSH EAX                                ;Save values on stack\r
910                 PUSH EBX\r
911 \r
912                 PUSH EBX                                ;Source\r
913                 PUSH EAX                                ;Destination\r
914                 PUSH 1024                               ;Lower half of PD (Physical Adds)\r
915                 CALL FWORD PTR _CopyData\r
916 \r
917                 POP  EBX                                ;Get values from stack\r
918                 POP  EAX\r
919 \r
920                 ADD EBX, 2048                   ;Move to shadow\r
921                 PUSH EBX\r
922                 ADD EAX, 2048                   ;Move to shadow\r
923                 PUSH EAX\r
924                 PUSH 1024                               ;Upper half of PD (Linear Adds)\r
925                 CALL FWORD PTR _CopyData\r
926 \r
927                 POP EDX                                 ; Get back JCB number\r
928 \r
929 AOPT04:\r
930                 DEC EDX\r
931                 CMP EDX, 2\r
932                 JA AOPT03                               ;Jobs 1 & 2 use PDir1 (Mon & Debugger)\r
933 \r
934                 ;At this point the new table is valid to ALL jobs!\r
935                 ;We now need another PreAllocated Page Table for\r
936                 ;next time. Get a run of 1 for next new page table\r
937 \r
938                 MOV EBX, 1                              ;size of request\r
939                 XOR EAX, EAX                    ;PD shadow offset needed by FindRun (0)\r
940                 CALL FindRun\r
941                 OR EAX, EAX                             ;was there an error (0 means no mem)\r
942                 JNZ AOPT05\r
943                 MOV EAX, ErcNoMem               ;\r
944                 JMP SHORT AOPTDone\r
945 AOPT05:\r
946                 MOV pNextPT, EAX                ;save pNextPT (the linear address)\r
947                 CALL AddRun                             ;AddRun\r
948                 XOR EAX, EAX                    ;Set ErcOK (0)\r
949 AOPTDone:\r
950                 POP EDI                         ;\r
951                 POP ESI                         ;\r
952                 POP EDX                         ;\r
953                 POP ECX                         ;\r
954                 POP EBX                         ;\r
955                 RETN\r
956 \r
957 ;=============================================================================\r
958 ; GetGDTDesc\r
959 ; You supply the GDT selector in BX and this puts entry in EAX,EDX.\r
960 ; EAX, EBX and EDX are used.\r
961 ; This assumes that the PUBLIC Variable GDTbase has been filled in by\r
962 ; the OS using SGDT after it went PMode.\r
963 ; Used by the Debugger among other things.\r
964 ;\r
965 GetGDTDesc:\r
966                 AND EBX,0000FFF8h       ;Mask any left overs (hi word)\r
967                 ADD EBX,GDTBase         ;Add to GDT base\r
968                 MOV EAX,[EBX]\r
969                 MOV EDX,[EBX+4]\r
970                 RETN\r
971 \r
972 ;=============================================================================\r
973 ;=============================================================================\r
974 ;  BEGIN PUBLIC CALL DEFINITION FOR MEMORY MANAGEMENT\r
975 ;=============================================================================\r
976 ;=============================================================================\r
977 ; PUBLIC calls (far through call gates)\r
978 ; AddCallGate   - Adds a public CallGate to the GDT\r
979 ; AddIDTGate    - Adds an Interrupt Vector to the IDT\r
980 ; AllocPage     - Returns a ptr to allocated linear memory pages (Hi Phys)\r
981 ; AllocOSPage   - Returns a ptr to allocated linear memory pages (Hi Phys)\r
982 ; AllocDMAPage  - Returns a ptr with physical and linear memory pages\r
983 ; AliasMem              - Aliases a memory address from one Job to another\r
984 ; DeAllocPage   - Provided with ptr, deallocates memory pages\r
985 ; QueryMemPages - Tells you how many pages are left free\r
986 ; GetPhyAdd             - Returns the Physical Address for a Linear Address\r
987 ;=============================================================================\r
988 ; AddGDTCallGate will build and add a GDT entry for a call gate allowing\r
989 ; access to OS procedures. This call doesn't check to see if the GDT\r
990 ; descriptor for the call is already defined. It assumes you know what you\r
991 ; are doing and overwrites one if already defined.  The Selector number is\r
992 ; checked to make sure you're in range (40h thru max call gate num).\r
993 ;\r
994 ; IN: AX - Word with Call Gate ID type as follows:\r
995 ;\r
996 ;                       DPL entry of 3 EC0x   (most likely)\r
997 ;                       DPL entry of 2 CC0x   (Not used in MMURTL)\r
998 ;                       DPL entry of 1 AC0x   (Not used in MMURTL)\r
999 ;                       DPL entry of 0 8C0x   (OS call ONLY)\r
1000 ;                       (x = count of DWord params 0-F)\r
1001 ;\r
1002 ;     CX    Selector number for call gate in GDT (constants!)\r
1003 ;         ESI   Offset of entry point in segment of code to execute\r
1004 ;\r
1005 ; OUT:  EAX     Returns Errors, else 0 if all's well\r
1006 ;\r
1007 ; USES: EAX, EBX, ECX, ESI, EFLAGS\r
1008 \r
1009 PUBLIC __AddCallGate:\r
1010                 CMP CX, 40h             ;Is number within range of callgates?\r
1011                 JAE AddCG01                     ;not too low.\r
1012                 MOV EAX, ercBadGateNum\r
1013                 RETF\r
1014 AddCG01:\r
1015                 MOVZX EBX, CX\r
1016                 SUB EBX, 40                     ;sub call gate base selector\r
1017                 SHR EBX, 3                      ;make index vice selector\r
1018                 CMP EBX, nCallGates     ;see if too high!\r
1019                 JBE AddCG02                     ;No.\r
1020                 MOV EAX, ercBadGateNum  ;Yes.\r
1021                 RETF\r
1022 AddCG02:\r
1023                 MOVZX EBX, CX           ;Extend selector into EBX\r
1024                 ADD EBX, GDTBase        ;NOW a true offset in GDT\r
1025                 MOV WORD PTR [EBX+02], 8        ;Put Code Seg selector into Call gate\r
1026                 MOV [EBX], SI           ;0:15 of call offset\r
1027                 SHR ESI, 16                     ;move upper 16 of offset into SI\r
1028                 MOV [EBX+06], SI        ;16:31 of call offset\r
1029                 MOV [EBX+04], AX        ;call DPL & ndParams\r
1030                 XOR EAX, EAX            ;0 = No Error\r
1031                 RETF\r
1032 \r
1033 ;=============================================================================\r
1034 ; AddIDTGate will build and add an IDT Trap, Interrupt, or Task Gate.\r
1035 ; The Selector of the call is Always 8 for Int or Trap, and is the\r
1036 ; TSS of the task for a Task gate.\r
1037 ;\r
1038 ; IN:   AX      - Word with Gate ID type as follows:\r
1039 ;                               Trap Gate with DPL of 3       8F00\r
1040 ;                               Interrupt Gate with DPL of 3  8E00\r
1041 ;                               Task Gate with DPL of 3       8500\r
1042 ;\r
1043 ;               BX      - Selector of gate (08 or TSS selector for task gates)\r
1044 ;\r
1045 ;               CX      - Word with Interrupt Number (00-FF)\r
1046 ;\r
1047 ;               ESI - Offset of entry point in OS code to execute\r
1048 ;                         (THIS MUST BE 0 FOR TASK GATES)\r
1049 ;\r
1050 ; USES: EAX, EBX, ECX, EDX, ESI, EFLAGS\r
1051 \r
1052 PUBLIC __AddIDTGate:\r
1053                 MOVZX EDX, CX                           ;Extend INT Num into EDX\r
1054                 SHL EDX, 3                                      ;Gates are 8 bytes each (times 8)\r
1055                 ADD EDX, OFFSET IDT                     ;EDX now points to gate\r
1056                 MOV WORD PTR [EDX+4], AX        ;Put Gate ID into gate\r
1057                 MOV EAX, ESI\r
1058                 MOV WORD PTR [EDX], AX          ;Put Offset 15:00 into gate\r
1059                 SHR EAX, 16\r
1060                 MOV WORD PTR [EDX+6], AX        ;Put Offset 31:16 into gate\r
1061                 MOV WORD PTR [EDX+2], BX        ;Put in the selector\r
1062                 RETF\r
1063 ;\r
1064 ;\r
1065 ;=============================================================================\r
1066 ; AllocOSPage --\r
1067 ; This allocates one or more pages of physical memory and returns a\r
1068 ; linear pointer to one or more pages of contiguous memory in the OS space.\r
1069 ; A result code is returned in the EAX register.\r
1070 ; STEPS:\r
1071 ; 1) See if we have enough physical memory (check nPagesFree)\r
1072 ; 2) Find a contiguous run of linear pages to allocate (PTEs)\r
1073 ; 3) Allocate each physical page placing it in the run of PTEs\r
1074 ;\r
1075 ; We search thru the page tables for the current job and find enough\r
1076 ; contiguous PTEs to satisfy the request.  If the current PT doesn't have\r
1077 ; enough contiguous entries, we add another page table to the OS PD\r
1078 ; and get them from the new one and the old one (i.e., the run may\r
1079 ; span page tables).\r
1080 ;\r
1081 ; Procedureal Interface :\r
1082 ;\r
1083 ;   AllocOSPage(dn4KPages,ppMemRet): dError\r
1084 ;\r
1085 ;   dn4KPages is a DWORD (4 BYTES). This is the number of contigous pages\r
1086 ;       to be allocated.\r
1087 ;\r
1088 ;   ppMemRet points to the pointer where the address of the\r
1089 ;                       new linear memory is returned.\r
1090 ;\r
1091 n4KPages        EQU [EBP+10h]           ;These equates are also used by AllocPage\r
1092 ppMemRet        EQU [EBP+0Ch]           ;\r
1093 \r
1094 PUBLIC __AllocOSPage:           ;\r
1095                 PUSH EBP                ;\r
1096                 MOV EBP,ESP             ;\r
1097                 PUSH MemExch                    ;Wait at the MemExch for Msg\r
1098                 MOV EAX, pRunTSS                ;Put Msg in callers TSS Message Area\r
1099                 ADD EAX, TSS_Msg\r
1100                 PUSH EAX\r
1101                 CALL FWORD PTR _WaitMsg\r
1102                 CMP EAX,0h                              ;Kernel Error??\r
1103                 JNE SHORT ALOSPExit     ;Yes! Serious problem.\r
1104 \r
1105                 MOV EAX,n4KPages                ;size of request\r
1106                 OR  EAX,EAX                             ;More than 0?\r
1107                 JNZ ALOSP00                             ;Yes\r
1108                 MOV EAX,ercBadMemReq    ;Can't be zero!\r
1109                 JMP ALOSPExit           ;\r
1110 ALOSP00:\r
1111                 CMP EAX, _nPagesFree    ;See if have enuf physical memory\r
1112                 JBE ALOSP01                             ;Yes\r
1113                 MOV EAX, ErcNoMem               ;Sorry boss, we're maxed out\r
1114                 JMP SHORT ALOSPExit\r
1115 ALOSP01:\r
1116                 MOV EBX,n4KPages                ;size of request\r
1117                 XOR EAX, EAX                    ;PD shadow offset needed by FindRun (0)\r
1118                 CALL FindRun\r
1119                 OR EAX, EAX                             ;(0 = No Runs big enuf)\r
1120                 JNZ SHORT ALOSP02               ;No Error!\r
1121 \r
1122                 ;If we didn't find a run big enuf we add a page table\r
1123 \r
1124                 CALL AddOSPT                    ;Add a new page table (we need it!)\r
1125                 OR EAX, EAX                             ;See if it's 0 (0 = NO Error)\r
1126                 JZ SHORT ALOSP01                ;Go back & try again\r
1127                 JMP SHORT ALOSPExit             ;ERROR!!\r
1128 ALOSP02:\r
1129                                                                 ;EAX now has linear address\r
1130                                                                 ;EBX still has count of pages\r
1131                 CALL AddRun                             ;Does not return error\r
1132                                                                 ;EAX still has new linear address\r
1133                 MOV EBX, ppMemRet               ;Get address of caller's pointer\r
1134                 MOV [EBX], EAX                  ;Give em new LinAdd\r
1135                 XOR EAX, EAX                    ;No error\r
1136 ALOSPExit:                                  ;\r
1137                 PUSH EAX                                ;Save last error\r
1138                 PUSH MemExch                    ;Send a Semaphore msg (so next guy can get in)\r
1139                 PUSH 0FFFFFFF1h                 ;\r
1140                 PUSH 0FFFFFFF1h                 ;\r
1141                 CALL FWORD PTR _SendMsg ;\r
1142                 POP EAX                                 ;Get original error back (ignore kernel erc)\r
1143                 MOV ESP,EBP                             ;\r
1144                 POP EBP                 ;\r
1145                 RETF 8                  ;\r
1146 \r
1147 ;=============================================================================\r
1148 ; AllocPage --\r
1149 ; This is identical to AllocOSPage except it's call gate is set to USER\r
1150 ; level and the PD base value is set to 3072.  See the call description\r
1151 ; for AllocOSPage\r
1152 \r
1153 PUBLIC __AllocPage:             ;\r
1154                 PUSH EBP                ;\r
1155                 MOV EBP,ESP             ;\r
1156                 PUSH MemExch                    ;Wait at the MemExch for Msg\r
1157                 MOV EAX, pRunTSS                ;Put Msg in callers TSS Message Area\r
1158                 ADD EAX, TSS_Msg\r
1159                 PUSH EAX\r
1160                 CALL FWORD PTR _WaitMsg\r
1161                 CMP EAX,0h                              ;Kernel Error??\r
1162                 JNE SHORT ALPExit       ;Yes! Serious problem.\r
1163                 MOV EAX,n4KPages                ;size of request\r
1164                 OR  EAX,EAX                             ;More than 0?\r
1165                 JNZ ALP00                               ;Yes\r
1166                 MOV EAX,ercBadMemReq    ;Can't be zero!\r
1167                 JMP ALPExit                             ;\r
1168 ALP00:\r
1169                 MOV EAX,n4KPages                ;size of request\r
1170                 CMP EAX, _nPagesFree    ;See if have enuf physical memory\r
1171                 JBE ALP01                               ;Yes\r
1172                 MOV EAX, ErcNoMem               ;Sorry boss, we're maxed out\r
1173                 JMP SHORT ALPExit\r
1174 ALP01:\r
1175                 MOV EBX, EAX                    ;nPages\r
1176                 MOV EAX, 256                    ;PD base for USER mem (needed by FindRun)\r
1177                 CALL FindRun\r
1178                 OR EAX, EAX                             ;(0 = No Runs big enuf)\r
1179                 JNZ SHORT ALP02                 ;No Error!\r
1180 \r
1181                 CALL AddUserPT                  ;Add a new page table (we need it!)\r
1182                 OR EAX, EAX                             ; 0 = NO Error\r
1183                 JZ SHORT ALP01                  ; Go back & try again\r
1184                 JMP SHORT ALPExit               ; ERROR!!\r
1185 \r
1186 ALP02:\r
1187                 CALL AddRun                             ;Does not return error\r
1188                 MOV EBX, ppMemRet               ;Get address of caller's pointer\r
1189                 MOV [EBX], EAX                  ;Give em new LinAdd\r
1190                 XOR EAX, EAX                    ;No error\r
1191 ALPExit:                                    ;\r
1192                 PUSH EAX                                ;Save last error\r
1193                 PUSH MemExch                    ;Send a Semaphore msg (so next guy can get in)\r
1194                 PUSH 0FFFFFFF1h                 ;\r
1195                 PUSH 0FFFFFFF1h                 ;\r
1196                 CALL FWORD PTR _SendMsg ;\r
1197                 POP EAX                                 ;Get original error back (ignore kernel erc)\r
1198                 MOV ESP,EBP                             ;\r
1199                 POP EBP                 ;\r
1200                 RETF 8                  ;\r
1201 \r
1202 ;=============================================================================\r
1203 ; AllocDMAPage --\r
1204 ; This allocates one or more pages of physical memory and returns a\r
1205 ; linear pointer to one or more pages of contiguous memory in the OS space.\r
1206 ; This is for DMA, and thusly allocates the physical memory\r
1207 ; from the low end!!!!\r
1208 ; The caller is responsible to ensure the physical addresses do\r
1209 ; not cross 64K boundaries for 8 bit channel use,\r
1210 ; or 128K boundaries for 16 bit use. The caller should also check\r
1211 ; to ensure the physical pages are contiguous. He can allocate\r
1212 ; until they are then deallocate what he doesn't use.\r
1213 ;\r
1214 ; A result code is returned in the EAX register.\r
1215 ; STEPS:\r
1216 ; 1) See if we have enough physical memory (check nPagesFree)\r
1217 ; 2) Find a contiguous run of linear pages to allocate (PTEs)\r
1218 ; 3) Allocate each physical page placing it in the run of PTEs\r
1219 ;    from the bottom up!!!\r
1220 ;\r
1221 ; We search thru the page tables for the OS and find enough\r
1222 ; contiguous PTEs to satisfy the request.  If the current PT doesn't have\r
1223 ; enough contiguous entries, we add another page table to the OS PD\r
1224 ; and get them from the new one and the old one (i.e., the run may\r
1225 ; span page tables).\r
1226 ;\r
1227 ; Procedureal Interface :\r
1228 ;\r
1229 ;   AllocDMAPage(dn4KPages,ppMemRet,pdPhyMemRet): dError\r
1230 ;\r
1231 ;   dn4KPages is a DWORD (4 BYTES). This is the number of contigous pages\r
1232 ;       to be allocated.\r
1233 ;\r
1234 ;   ppMemRet points to the pointer where the address of the\r
1235 ;                       new linear memory is returned.\r
1236 \r
1237 ;   pdPhyMemRet points to DWord where the physical address of the memory\r
1238 ;               is returned.\r
1239 ;\r
1240 n4KDMAPages     EQU [EBP+20]            ;\r
1241 ppDMAMemRet     EQU [EBP+16]            ;\r
1242 pdDMAPhyMemRet  EQU [EBP+12]            ;\r
1243 \r
1244 EXTRN GetCrntJobNum NEAR\r
1245 \r
1246 PUBLIC __AllocDMAPage:           ;\r
1247                 PUSH EBP                 ;\r
1248                 MOV EBP,ESP             ;\r
1249                 PUSH MemExch                    ;Wait at the MemExch for Msg\r
1250                 MOV EAX, pRunTSS                ;Put Msg in callers TSS Message Area\r
1251                 ADD EAX, TSS_Msg\r
1252                 PUSH EAX\r
1253                 CALL FWORD PTR _WaitMsg\r
1254                 CMP EAX,0h                              ;Kernel Error??\r
1255                 JNE SHORT ALDMAPExit    ;Yes! Serious problem.\r
1256 \r
1257                 MOV EAX,n4KDMAPages             ;size of request\r
1258                 OR  EAX,EAX                             ;More than 0?\r
1259                 JNZ ALDMAP00                    ;Yes\r
1260                 MOV EAX,ercBadMemReq    ;Can't be zero!\r
1261                 JMP ALDMAPExit          ;\r
1262 ALDMAP00:\r
1263                 CMP EAX, _nPagesFree    ;See if have enuf physical memory\r
1264                 JBE ALDMAP01                    ;Yes\r
1265                 MOV EAX, ErcNoMem               ;Sorry boss, we're maxed out\r
1266                 JMP SHORT ALDMAPExit\r
1267 ALDMAP01:\r
1268                 MOV EBX, EAX                    ;size of request\r
1269                 XOR EAX, EAX                    ;PD shadow offset needed by FindRun (0)\r
1270                 CALL FindRun\r
1271                 OR EAX, EAX                             ;(0 = No Runs big enuf)\r
1272                 JNZ SHORT ALDMAP02              ;No Error!\r
1273 \r
1274                 ;If we didn't find a run big enuf we add a page table\r
1275 \r
1276                 CALL AddOSPT                    ;Add a new page table (we need it!)\r
1277                 OR EAX, EAX                             ;See if it's 0 (0 = NO Error)\r
1278                 JZ SHORT ALDMAP01               ;Go back & try again\r
1279                 JMP SHORT ALDMAPExit            ;ERROR!!\r
1280 ALDMAP02:\r
1281                                                                 ;EAX now has linear address\r
1282                                                                 ;EBX still has count of pages\r
1283                 CALL AddDMARun                  ;Does not return error\r
1284                                                                 ;EAX still has new linear address\r
1285                 MOV EBX, ppDMAMemRet            ;Get address of caller's pointer\r
1286                 MOV [EBX], EAX                  ;Give em new LinAdd\r
1287 \r
1288                 ;Set up to get the physical address of the linear we just gave 'em\r
1289 \r
1290                 MOV EBX, EAX                    ;Linear to EBX\r
1291                 CALL GetCrntJobNum              ;Leaves job num in EAX\r
1292                 CALL LinToPhy                   ;Leave Phy in EAX\r
1293                 MOV EBX,pdDMAPhyMemRet  ;Give them the physical address\r
1294                 MOV [EBX], EAX\r
1295 \r
1296                 XOR EAX, EAX                    ;No error\r
1297 \r
1298 ALDMAPExit:                                 ;\r
1299                 PUSH EAX                                ;Save last error\r
1300                 PUSH MemExch                    ;Send a Semaphore msg (so next guy can get in)\r
1301                 PUSH 0FFFFFFF1h                 ;\r
1302                 PUSH 0FFFFFFF1h                 ;\r
1303                 CALL FWORD PTR _SendMsg ;\r
1304                 POP EAX                                 ;Get original error back (ignore kernel erc)\r
1305                 MOV ESP,EBP                             ;\r
1306                 POP EBP                 ;\r
1307                 RETF 12                 ;\r
1308 \r
1309 ;=============================================================================\r
1310 ; AliasMem --\r
1311 ; This creates alias pages in the current job's PD/PTs if the current\r
1312 ; PD is different than the PD for the job specified.  This allows\r
1313 ; system services to access a caller memory for messaging WITHOUT having\r
1314 ; to move data around.  The pages are create at USER protection level\r
1315 ; even if they are in OS memory space (a service installed in OS memory).\r
1316 ; Even if the address is only two bytes, if it crosses page boundries,\r
1317 ; we need two pages.\r
1318 ;\r
1319 ; STEPS:\r
1320 ; 1) See if the current PD = Specified Job PD. If so, Exit. (No alias needed).\r
1321 ; 2) Calculate how many entries (pages) will be needed.\r
1322 ; 3) See if they are available.\r
1323 ; 3) Make PTE entries and return alias address to caller.\r
1324 ;\r
1325 ; Procedureal Interface :\r
1326 ;\r
1327 ;   AliasMem(pMem, dcbMem, dJobNum, ppAliasRet): dError\r
1328 ;\r
1329 ;   pMem   is the address to alias.\r
1330 ;       dcbMem is the number of bytes needed for alias access.\r
1331 ;       JobNum is the job number that pMem belongs to.\r
1332 ;       ppAliasRet is the address to return the alias address to.\r
1333 ;\r
1334 ;\r
1335 ;pMem           EQU [EBP+24]            ;\r
1336 ;dcbMem         EQU [EBP+20]            ;\r
1337 ;JobNum         EQU [EBP+16]            ;\r
1338 ;ppAliasRet EQU [EBP+12]                ;\r
1339 \r
1340 PUBLIC __AliasMem               ;\r
1341                 PUSH EBP                ;\r
1342                 MOV EBP,ESP             ;\r
1343                 CALL GetCrntJobNum              ;Puts Current Job Num in EAX\r
1344                 MOV EBX, [EBP+16]               ;Get Job number for pMem\r
1345                 CMP EAX, EBX                    ;Are they the same Page Directory??\r
1346                 JNE ALSPBegin                   ;No, alias it\r
1347                 XOR EAX, EAX                    ;Yes, No Error\r
1348                 JMP ALSPDone                    ;Exit, we're done\r
1349 \r
1350 ALSPBegin:\r
1351                 ;Now wait our turn with memory management\r
1352 \r
1353 ;               PUSH MemExch                    ;Wait at the MemExch for Msg\r
1354 ;               MOV EAX, pRunTSS                ;Put Msg in callers TSS Message Area\r
1355 ;               ADD EAX, TSS_Msg\r
1356 ;               PUSH EAX\r
1357 ;               CALL FWORD PTR _WaitMsg\r
1358 ;               CMP EAX,0h                              ;Kernel Error??\r
1359 ;               JNE ALSPDone                    ;Yes! Serious problem.\r
1360 \r
1361                 ; We're IN!\r
1362 \r
1363 ALSP00:\r
1364                 MOV EBX, [EBP+24]                       ;pMem into EAX\r
1365                 AND EBX, 0FFFh                          ;MODULO 4096  (remainder)\r
1366                 MOV EAX, [EBP+20]                       ;dcbMem\r
1367                 ADD EAX, EBX                            ;Add the remainder of address\r
1368                 SHR EAX, 12                                 ;EAX is nPages-1\r
1369                 INC EAX                                         ;EAX is now nPages we need!\r
1370                 MOV ECX, EAX                            ;Save nPages in ECX\r
1371 \r
1372                 ;Now we find out whos memory we are in to make alias\r
1373                 ;EAX is 256 for user space, 0 for OS\r
1374                 ;EBX is number of pages for run\r
1375 \r
1376                 CALL GetCrntJobNum                      ;See if it is OS based service\r
1377                 CMP EAX, 1                                      ;OS Job?\r
1378                 JE SHORT ALSP011                        ;Yes\r
1379                 MOV EAX, 256                            ;No, User memory\r
1380                 JMP SHORT ALSP01\r
1381 ALSP011:\r
1382                 XOR EAX, EAX                            ;Set up for OS memory space\r
1383 ALSP01:\r
1384                 MOV EBX, ECX                            ;Number of pages we need into EBX\r
1385                 CALL FindRun                            ;EAX has 0 or 256\r
1386 \r
1387                 ;EAX is now linear address or 0 if no run is large enough\r
1388                 ;EBX  still has count of pages\r
1389 \r
1390                 OR EAX, EAX                                     ;Was there enough PTEs?\r
1391                 JNZ ALSP04                                      ;Yes\r
1392 \r
1393                 CALL GetCrntJobNum                      ;See if it is OS based service\r
1394                 CMP EAX, 1                                      ;OS Job?\r
1395                 JE SHORT ALSP02                         ;Yes (RAB)\r
1396 \r
1397                 CALL AddUserPT                          ;No!  Add a new USER page table\r
1398                 JMP SHORT ALSP03\r
1399 ALSP02:\r
1400                 CALL AddOSPT                            ;No!  Add a new OS page table\r
1401 ALSP03:\r
1402                 OR EAX, EAX                                     ;0 = NO Error\r
1403                 JZ SHORT ALSP00                         ;Go back & try again\r
1404                 JMP SHORT ALSPExit                      ;ERROR!!\r
1405 \r
1406 ALSP04:\r
1407                 ;EAX has linear address (from find run) Sve in EDI\r
1408                 ;EBX still has number of pages to alias\r
1409                 ;Set ESI to linear address of pages to alias (from other job)\r
1410                 ;Set EDX job number of job we are aliasing\r
1411 \r
1412                 MOV EDI, EAX                            ;Save alias page address base\r
1413                 MOV ESI, [EBP+24]                       ;Address to alias\r
1414                 MOV EDX, [EBP+16]                       ;Job number\r
1415                 CALL AddAliasRun\r
1416 \r
1417                 ;Now, take new alias mem and add trailing bits to address\r
1418                 ;and return to caller so he knows address (EDI is lin add)\r
1419 \r
1420                 MOV EAX, [EBP+24]                       ;original pMem\r
1421                 AND EAX, 0FFFh                          ;Get remaining bits\r
1422                 ADD EDI, EAX\r
1423                 MOV ESI, [EBP+12]                       ;pAliasRet\r
1424                 MOV [ESI], EDI                          ;Returned address to caller!\r
1425 \r
1426                 XOR EAX, EAX                            ;Set to 0 (no error)\r
1427 \r
1428                 ;We are done\r
1429 ALSPExit:                                   ;\r
1430 ;               PUSH EAX                                ;Save last error\r
1431 ;               PUSH MemExch                    ;Send a Semaphore msg (so next guy can get in)\r
1432 ;               PUSH 0FFFFFFF1h                         ;\r
1433 ;               PUSH 0FFFFFFF1h                         ;\r
1434 ;               CALL FWORD PTR _SendMsg ;\r
1435 ;               POP EAX                                 ;Get original error back (ignore kernel erc)\r
1436 ALSPDone:\r
1437                 MOV ESP,EBP                             ;\r
1438                 POP EBP                 ;\r
1439                 RETF 16                 ;\r
1440 \r
1441 ;=============================================================================\r
1442 ; DeAliasMem --\r
1443 ;\r
1444 ; Procedureal Interface :\r
1445 ;\r
1446 ;               DeAliasMem(pAliasMem, dcbAliasBytes, JobNum):ercType\r
1447 ;\r
1448 ;   pAliasMem is the address which was given to you from the AliasMem call.\r
1449 ;   This zeros out the page entries that were made during the AliasMem\r
1450 ;   call. We do not need to go through the OS MEM semaphore exchange\r
1451 ;       because we are only zeroing out PTE's one at a time. This\r
1452 ;       WOULD NOT interfere with any memory allocation routines.\r
1453 ;\r
1454 ;       pAliasMem is the address to DeAlias\r
1455 ;       dcbAliasBytes is the size of the original memory aliased\r
1456 ;\r
1457 ;pAliasMem              EQU [EBP+20]\r
1458 ;dcbAliasBytes  EQU [EBP+16]\r
1459 ;AliasJobNum    EQU [EBP+12]\r
1460 \r
1461 PUBLIC __DeAliasMem             ;\r
1462                 PUSH EBP                ;\r
1463                 MOV EBP,ESP             ;\r
1464 \r
1465                 MOV EBX, [EBP+20]                       ;pMem into EBX\r
1466                 AND EBX, 0FFFh                          ;MODULO 4096  (Get remainder)\r
1467                 MOV EAX, [EBP+16]                       ;dcbMem\r
1468                 ADD EAX, EBX                            ;Add the remainder of address\r
1469                 SHR EAX, 12                                 ;EAX is nPages-1\r
1470                 INC EAX                                         ;EAX is now nPages we to dealias!\r
1471                 MOV ECX, EAX                            ;Number of pages into EDI & ECX\r
1472                 MOV EDI,ECX                                     ;Save also in EDI (for compare)\r
1473                 MOV EDX, [EBP+20]                       ;Linear Mem to DeAlias\r
1474 \r
1475 DALM01:\r
1476                 MOV EBX, EDX                    ;Address of next page to deallocate\r
1477                 MOV EAX, [EBP+12]               ;Job num into EAX for LinToPhy\r
1478                 CALL LinToPhy                   ;Call this to get address of PTE into ESI\r
1479 \r
1480                 ;Now we have Physical Address in EAX (we don't really need it)\r
1481                 ;and pointer to PTE in ESI (We NEEDED THIS).\r
1482                 ;See if PTE is an alias, if so just ZERO PTE.\r
1483                 ;DO NOT deallocate the physical page\r
1484 \r
1485                 MOV EBX, [ESI]                  ;Get PTE into EBX\r
1486                 TEST EBX, PRSNTBIT              ;Is page present (valid)???\r
1487                 JNZ DALM02                              ;Yes, it's page is present\r
1488 \r
1489                 CMP ECX, EDI                    ;NO! (did we do any at all)\r
1490                 JNE DALM011                             ;We did some.\r
1491                 MOV EAX, ErcBadLinAdd   ;None at all!\r
1492                 JMP SHORT DALMExit\r
1493 \r
1494 DALM011:\r
1495                 MOV EAX, ErcBadAlias    ;We dealiased what we could,\r
1496                 JMP SHORT DALMExit              ;but less than you asked for!\r
1497 \r
1498 DALM02:\r
1499                 TEST EBX, ALIASBIT              ;Is page an ALIAS?\r
1500                 JZ DALM03                               ;NO - DO not zero it!\r
1501 \r
1502                 ;If we got here the page is presnt and IS an alias\r
1503                 ;so we zero out the page.\r
1504 \r
1505                 XOR EAX, EAX                    ;\r
1506                 MOV [ESI], EAX                  ;ZERO PTE entry\r
1507 DALM03:\r
1508 \r
1509                 ADD EDX, 4096                   ;Next linear page\r
1510                 LOOP DALM01\r
1511                                                                 ;If we fall out EAX = ErcOK already\r
1512 DALMExit:\r
1513                 MOV ESP,EBP             ;\r
1514                 POP EBP                 ;\r
1515                 RETF 12                 ;\r
1516 \r
1517 \r
1518 ;=============================================================================\r
1519 ; DeAllocPage --\r
1520 ;\r
1521 ; Procedureal Interface :\r
1522 ;\r
1523 ;               DeAllocPage(pOrigMem, n4KPages):ercType\r
1524 ;\r
1525 ;   pOrigMem is a POINTER which should be point to memory page(s) to be\r
1526 ;   deallocate.  The lower 12 bits of the pointer is actually ignored\r
1527 ;   because we deallocate 4K pages.  This will free physical pages unless\r
1528 ;   the page is marked as an alias. It will always free linear memory\r
1529 ;   providing it is valid.  Even if you specify more pages than are valid\r
1530 ;   this will deallocate or dealias as much as it can before reaching\r
1531 ;   an invalid page.\r
1532 ;\r
1533 ;       n4KPages is the number of 4K pages to deallocate\r
1534 ;\r
1535 pOrigMem        EQU [EBP+10h]\r
1536 n4KPagesD       EQU [EBP+0Ch]           ;\r
1537 \r
1538 PUBLIC __DeAllocPage:           ;\r
1539                 PUSH EBP                ;\r
1540                 MOV EBP,ESP             ;\r
1541 \r
1542                 PUSH MemExch                    ;Wait at the MemExch for Msg\r
1543                 MOV EAX, pRunTSS                ;Put Msg in callers TSS Message Area\r
1544                 ADD EAX, TSS_Msg\r
1545                 PUSH EAX\r
1546                 CALL FWORD PTR _WaitMsg\r
1547                 CMP EAX,0h                              ;Error??\r
1548                 JNE DAMExit             ;Yes!\r
1549 \r
1550                 MOV EDX, pOrigMem               ;Linear Mem to deallocate\r
1551                 AND EDX, 0FFFFF000h             ;Drop odd bits from address (MOD 4096)\r
1552                 MOV ECX, n4KPagesD              ;Number of pages to deallocate\r
1553 \r
1554 DAP01:\r
1555                 MOV EBX, EDX                    ;Address of next page to deallocate\r
1556                 CALL GetCrntJobNum              ;Leave Job# in EAX for LinToPhy\r
1557                 CALL LinToPhy                   ;\r
1558 \r
1559                 ;Now we have Physical Address in EAX\r
1560                 ;and pointer to PTE in ESI.\r
1561                 ;See if PTE is an alias, if so just ZERO PTE,\r
1562                 ;else deallocate physical page THEN zero PTE\r
1563 \r
1564                 MOV EBX, [ESI]                  ;Get PTE into EBX\r
1565                 TEST EBX, PRSNTBIT              ;Is page present (valid)???\r
1566                 JNZ DAP02                               ;Yes, it's page is present\r
1567 \r
1568                 CMP ECX, n4KPagesD              ;NO! (did we do any at all)\r
1569                 JNE DAP011                              ;We did some..\r
1570                 MOV EAX, ErcBadLinAdd   ;None at all!\r
1571                 JMP SHORT DAMExit\r
1572 \r
1573 DAP011:\r
1574                 MOV EAX, ErcShortMem    ;We deallocated what we could,\r
1575                 JMP SHORT DAMExit               ;but less than you asked for!\r
1576 \r
1577 DAP02:\r
1578                 TEST EBX, ALIASBIT              ;Is page an ALIAS?\r
1579                 JNZ DAP03                               ;Yes, it's an Alias\r
1580 \r
1581                 ;If we got here the page is presnt and NOT an alias\r
1582                 ;so we must unmark (release) the physical page.\r
1583 \r
1584                 AND EBX, 0FFFFF000h             ;get rid of OS bits\r
1585                 CALL UnMarkPage                 ;\r
1586 \r
1587 DAP03:\r
1588                 XOR EAX, EAX                    ;\r
1589                 MOV [ESI], EAX                  ;ZERO PTE entry\r
1590 \r
1591                 ADD EDX, 4096                   ;Next linear page\r
1592                 LOOP DAP01\r
1593                                                                 ;If we fall out EAX = ErcOK already\r
1594 DAMExit:\r
1595                 PUSH EAX                                ;save Memory error\r
1596 \r
1597                 PUSH MemExch                    ;Send a dummy message to pick up\r
1598                 PUSH 0FFFFFFF1h                 ; so next guy can get in\r
1599                 PUSH 0FFFFFFF1h\r
1600                 CALL FWORD PTR _SendMsg ;\r
1601                 CMP EAX, 0                              ;Kernel error has priority\r
1602                 JNE DAMExit1                    ; over memory error\r
1603 \r
1604                 POP EAX                                 ;get Memory error back\r
1605 \r
1606 DAMExit1:\r
1607                 MOV ESP,EBP             ;\r
1608                 POP EBP                 ;\r
1609                 RETF 8                  ;\r
1610 \r
1611 ;=============================================================================\r
1612 ; QueryMemPages --\r
1613 ;\r
1614 ; Procedureal Interface :\r
1615 ;\r
1616 ;               QueryMemPages(pdnPagesRet):ercType\r
1617 ;\r
1618 ;       pdnPagesRet is a pointer where you want the count of pages\r
1619 ;   left available returned\r
1620 ;\r
1621 pMemleft        EQU [EBP+0Ch]\r
1622 \r
1623 PUBLIC __QueryPages:            ;\r
1624                 PUSH EBP                ;\r
1625                 MOV EBP,ESP             ;\r
1626 \r
1627                 MOV ESI, pMemLeft\r
1628                 MOV EAX,  _nPagesFree\r
1629                 MOV [ESI], EAX\r
1630                 XOR EAX, EAX                    ;No Error\r
1631 \r
1632                 MOV ESP,EBP             ;\r
1633                 POP EBP                 ;\r
1634                 RETF 4                  ;\r
1635 \r
1636 ;==============================================================================\r
1637 ;\r
1638 ; GetPhyAdd -- This returns the phyical address for a linear address\r
1639 ;\r
1640 ;\r
1641 ; Procedureal Interface :\r
1642 ;\r
1643 ;               GetPhyAdd(JobNum, LinAdd, pPhyRet):ercType\r
1644 ;\r
1645 ;       LinAdd is the Linear address you want the physical address for\r
1646 ;       pPhyRet points to the unsigned long where Phyadd is returned\r
1647 ;\r
1648 ;\r
1649 ;JobNum  EQU [EBP+20]\r
1650 ;LinAdd  EQU [EBP+16]\r
1651 ;pPhyRet EQU [EBP+12]\r
1652 ;\r
1653 \r
1654 PUBLIC __GetPhyAdd:                     ;\r
1655                 PUSH EBP                ;\r
1656                 MOV EBP,ESP             ;\r
1657                 MOV EBX, [EBP+16]               ; Linear Address\r
1658                 MOV EAX, [EBP+20]               ; Job Number\r
1659                 CALL LinToPhy\r
1660                 MOV ESI, [EBP+12]               ; pPhyRet\r
1661                 MOV [ESI], EAX                  ;\r
1662                 XOR EAX, EAX                    ; No Error\r
1663                 MOV ESP,EBP             ;\r
1664                 POP EBP                 ;\r
1665                 RETF 12                 ;\r
1666 \r
1667 \r
1668 ;====== End Of Module =====================\r