]> pd.if.org Git - mmurtl/blob - ossource/kernel.asm
autocommit for file dated 2003-12-29 17:36:54
[mmurtl] / ossource / kernel.asm
1 ;   MMURTL Operating System Source Code\r
2 ;   Copyright 1991,1992,1993,1994 Richard A. Burgess\r
3 ;   ALL RIGHTS RESERVED\r
4 ;   Version 1.0\r
5 \r
6 .DATA\r
7 .INCLUDE MOSEDF.INC\r
8 .INCLUDE TSS.INC\r
9 .INCLUDE RQB.INC\r
10 .INCLUDE JOB.INC\r
11 \r
12 dJunk   DD 0            ;Used as temp in Service Abort function\r
13 dmsg    DD 2 DUP(0) ;tmp for abort\r
14 \r
15 EXTRN TimerTick  DD\r
16 EXTRN SwitchTick DD\r
17 EXTRN dfHalted   DD\r
18 EXTRN _nSwitches DD\r
19 EXTRN _nHalts    DD\r
20 EXTRN _nReady    DD\r
21 \r
22 .CODE\r
23 \r
24 EXTRN LinToPhy NEAR\r
25 \r
26 ;This file contains all the internal kernel functions plus\r
27 ;the PUBLIC kernel functions SendMsg, ISendMsg, WaitMsg, CheckMsg,\r
28 ;Request, Respond, MoveMsg, NewTask and SpawnTask.\r
29 ;Exchange management functions such as AllocExch and DeAllocExch are\r
30 ;also here.\r
31 ;\r
32 ; Note on interrupts and the kernel primitives:\r
33 ; Because certain kernel functions may be called from ISRs,\r
34 ; and because portions of other kernel functions may be\r
35 ; interrupted by a task change that happens because of an action\r
36 ; that an ISR takes, we must ensure that interrupts are\r
37 ; DISABLED prior to the allocation or deallocation\r
38 ; of ALL kernel data segment resources. This especially applies when\r
39 ; a message is "in transit."  For example: taken from an exchange\r
40 ; but not yet linked to a TSS and placed on the ready queue.\r
41 ; This is important!\r
42 ;\r
43 ; NOTE on Exchanges, Messages, and Tasks (TSSs)\r
44 ; In MMURTL, an exchange is a place where either Messages or\r
45 ; Tasks wait.  There can never be tasks AND messages at an\r
46 ; exchange at the same time (unless the kernel is BROKEN!).\r
47 ; When a message is sent to an exchange, if a task is waiting\r
48 ; there, is it immediately associated with the message\r
49 ; and placed on the readyQ in priority order.\r
50 ; For this reason we share the HEAD and TAIL link pointers\r
51 ; for tasks and messages on an exchange.\r
52 ;\r
53 ;=============================================================================\r
54 \r
55 enQueueMsg:\r
56 ;\r
57 ; INPUT : ESI,EAX\r
58 ; OUTPUT : NONE\r
59 ; REGISTERS : EAX,EDX,ESI,FLAGS\r
60 ; MODIFIES : EDX\r
61 ;\r
62 ; This routine will place the link block pointed to by EAX onto the exchange\r
63 ; pointed to by the ESI register. If EAX is NIL then the routine returns.\r
64 ;\r
65                 OR  EAX,EAX                             ; if pLBin = NIL THEN Return;\r
66                 JZ eqMsgDone            ;\r
67                 MOV DWORD PTR [EAX+NextLB], 0   ; pLBin^.Next <= NIL;\r
68                 XCHG ESI,EAX            ; pExch => EAX, pLBin => ESI\r
69                 CMP DWORD PTR [EAX+EHead], 0    ; if ..MsgHead = NIL\r
70                 JNE eqMNotNIL           ; then\r
71                 MOV [EAX+EHead],ESI     ;  ..MsgHead <= pLBin;\r
72                 MOV [EAX+ETail],ESI     ;  ..MsgTail <= pLBin;\r
73                 MOV DWORD PTR [EAX+fEMsg], 1            ; Flag it as a Msg (vice a task)\r
74                 XCHG EAX,ESI            ; Put pExch Back in ESI\r
75                 RETN                    ; else\r
76 eqMNotNIL:\r
77             MOV EDX,[EAX+ETail]     ;  ..MsgTail^.NextLB <= pLBin;\r
78                 MOV [EDX+NextLB],ESI    ;\r
79                 MOV [EAX+ETail],ESI     ;  ..MsgTail <= pLBin;\r
80                 MOV DWORD PTR [EAX+fEMsg], 1            ; Flag it as a Msg (vice a task)\r
81                 XCHG EAX,ESI            ; Put pExch Back in ESI\r
82 eqMsgDone:\r
83             RETN                    ;\r
84 \r
85 ;=============================================================================\r
86 \r
87 deQueueMsg:\r
88 ;\r
89 ; INPUT : ESI\r
90 ; OUTPUT : EAX\r
91 ; REGISTERS : EAX,EBX,ESI,FLAGS\r
92 ; MODIFIES : *prgExch[ESI].msg.head and EBX\r
93 ;\r
94 ; This routine will dequeue a link block on the exchange pointed to by the\r
95 ; ESI register and place the pointer to the link block dequeued into EAX.\r
96 ;\r
97                 MOV EAX,[ESI+fEMsg]     ; Get Msg Flag\r
98                 OR EAX, EAX                             ; Is it a Msg?\r
99                 JZ deMsgDone                    ; No! (return 0)\r
100                 MOV EAX,[ESI+EHead]     ; pLBout <= ..MsgHead;\r
101                 OR EAX, EAX             ; if pLBout = NIL then Return;\r
102                 JZ deMsgDone            ;\r
103                 MOV EBX,[EAX+NextLB]    ; ..MsgHead <= ..MsgHead^.Next;\r
104                 MOV [ESI+EHead],EBX     ;\r
105 deMsgDone:\r
106             RETN                    ;\r
107 \r
108 ;=============================================================================\r
109 \r
110 deQueueTSS:\r
111 ;\r
112 ; INPUT : ESI\r
113 ; OUTPUT : EAX\r
114 ; REGISTERS : EAX,EBX,ESI,FLAGS\r
115 ; MODIFIES : EAX,EBX\r
116 ;\r
117 ; This routine will dequeue a TSS on the exchange pointed to by the ESI\r
118 ; register and place the pointer to the TSS dequeued into EAX.\r
119 ; EAX return NIL if no TSS is waiting at Exch ESI\r
120 ;\r
121                 XOR EAX,EAX                             ; Set up to return nothing\r
122                 MOV EBX,[ESI+fEMsg]             ; Msg flag (is it a Msg)\r
123                 OR EBX, EBX\r
124                 JNZ deTSSDone                   ; It's a Msg (return leaving EAX 0)\r
125                 MOV EAX,[ESI+EHead]     ; pTSSout <= ..TSSHead;\r
126                 OR EAX, EAX             ; if pTSSout = NIL then Return;\r
127                 JZ deTSSDone            ;\r
128                 MOV EBX,[EAX+NextTSS]   ; ..TSSHead <= ..TSSHead^.Next;\r
129                 MOV [ESI+EHead],EBX     ;\r
130 deTSSDone:\r
131             RETN                        ;\r
132 \r
133 ;=============================================================================\r
134 \r
135 PUBLIC enQueueRdy:\r
136 ;\r
137 ; INPUT : EAX\r
138 ; OUTPUT : NONE\r
139 ; REGISTERS : EAX,EBX,EDX,FLAGS\r
140 ; MODIFIES : EAX,EBX,EDX\r
141 ;\r
142 ; This routine will place a TSS pointed to by EAX onto the ReadyQueue. This\r
143 ; algorithm chooses the proper priority queue based on the TSS priority.\r
144 ; The Rdy Queue is an array of QUEUES (2 pointers, head & tail per QUEUE).\r
145 ; This links the TSS to rgQueue[nPRI].\r
146 ;\r
147                 OR  EAX,EAX             ; if pTSS = NIL then return;\r
148                 JZ eqRdyDone            ;\r
149                 INC _nReady                             ;\r
150                 MOV DWORD PTR [EAX+NextTSS], 0  ; pTSSin^.Next <= NIL;\r
151                 XOR EBX,EBX             ; get the priority\r
152                 MOV BL,[EAX+Priority]   ; in EBX\r
153                 XCHG EAX,EBX            ; Priority => EAX, pTSSin => EBX\r
154                 SHL EAX, 3              ; Times 8 (size of QUEUE)\r
155                 LEA EDX,RdyQ            ; Add offset of RdyQ => EAX\r
156                 ADD EAX,EDX             ; EAX pts to proper Rdy Queue\r
157                 CMP DWORD PTR [EAX+Head], 0      ; if Head = NIL\r
158                 JNE eqRNotNIL           ; then\r
159                 MOV [EAX+Head],EBX      ;  ..Head <= pTSSin;\r
160                 MOV [EAX+Tail],EBX      ;  ..Tail <= pTSSin;\r
161                 RETN                    ; else\r
162 eqRNotNIL:\r
163             MOV EDX,[EAX+Tail]      ;  ..Tail^.NextTSS <= pTSSin;\r
164                 MOV [EDX+NextTSS],EBX   ;\r
165                 MOV [EAX+Tail],EBX      ;  ..Tail <= pTSSin;\r
166 eqRdyDone:\r
167             RETN                    ;\r
168 \r
169 ;=============================================================================\r
170 \r
171 PUBLIC deQueueRdy:\r
172 ;\r
173 ; INPUT : NONE\r
174 ; OUTPUT : EAX\r
175 ; REGISTERS : EAX,EBX,ECX,FLAGS\r
176 ; MODIFIES : RdyQ\r
177 ;\r
178 ; This routine will return a pointer in EAX to the highest priority task\r
179 ; queued on the RdyQ. Then the routine will "pop" the TSS from the RdyQ.\r
180 ; If there was no task queued, EAX is returned as NIL.\r
181 ;\r
182                 MOV ECX,nPRI            ; Set up the number of times to loop\r
183                 LEA EBX,RdyQ            ; Get base address of RdyQ in EBX\r
184 deRdyLoop:\r
185             MOV EAX,[EBX]           ; Get pTSSout in EAX\r
186                 OR  EAX, EAX            ; IF pTSSout is NIL Then go and\r
187                 JNZ deRdyFound          ; check the next priority.\r
188                 ADD EBX,sQUEUE          ; Point to the next Priority Queue\r
189                 LOOP deRdyLoop          ; DEC ECX and LOOP IF NOT ZERO\r
190 deRdyFound:\r
191                 OR  EAX, EAX            ; IF pTSSout is NIL Then there are\r
192                 JZ deRdyDone            ; No TSSs on the RdyQ; RETURN\r
193                 DEC _nReady                             ;\r
194                 MOV ECX,[EAX+NextTSS]   ; Otherwise, deQueue the process\r
195                 MOV [EBX],ECX           ; And return with the pointer in EAX\r
196 deRdyDone:\r
197             RETN                    ;\r
198 \r
199 ;=============================================================================\r
200 \r
201 PUBLIC ChkRdyQ:\r
202 ;\r
203 ; INPUT : NONE\r
204 ; OUTPUT : EAX\r
205 ; REGISTERS : EAX,EBX,ECX,FLAGS\r
206 ; MODIFIES : RdyQ\r
207 ;\r
208 ; This routine will return a pointer to the highest priority TSS that\r
209 ; is queued to run. It WILL NOT remove it from the Queue.\r
210 ; If there was no task queued, EAX is returned as NIL.\r
211 ;\r
212                 MOV ECX,nPRI            ; Set up the number of times to loop\r
213                 LEA EBX,RdyQ            ; Get base address of RdyQ in EBX\r
214 ChkRdyLoop:\r
215             MOV EAX,[EBX]           ; Get pTSSout in EAX\r
216                 OR  EAX, EAX            ; IF pTSSout is NIL Then go and\r
217                 JNZ ChkRdyDone          ; check the next priority.\r
218                 ADD EBX,sQUEUE          ; Point to the next Priority Queue\r
219                 LOOP ChkRdyLoop       ; DEC ECX and LOOP IF NOT ZERO\r
220 ChkRdyDone:\r
221             RETN                    ;\r
222 \r
223 ;=============================================================================\r
224 ;================= BEGIN NEAR KERNEL HELPER ROUTINES =========================\r
225 ;=============================================================================\r
226 \r
227 ; RemoveRdyJob  (NEAR)\r
228 ;\r
229 ; This routine searchs all ready queue priorities for tasks belonging\r
230 ; to pJCB. When one is found it is removed from the queue\r
231 ; and the TSS is freed up.  This is called when we are killing\r
232 ; a job.\r
233 ;\r
234 ; Procedureal Interface :\r
235 ;\r
236 ;               RemoveRdyJob(char *pJCB):ercType\r
237 ;\r
238 ;       pJCB is a pointer to the JCB that the tasks to kill belong to.\r
239 ;\r
240 ; pJCB                  EQU DWORD PTR [EBP+8]\r
241 ;\r
242 ; INPUT :  (pJCB on stack)\r
243 ; OUTPUT : NONE\r
244 ; REGISTERS : All general registers are trashed\r
245 ; MODIFIES : RdyQ\r
246 ;\r
247 ;\r
248 PUBLIC _RemoveRdyJob:\r
249 ;\r
250                 PUSH EBP                ;\r
251                 MOV EBP,ESP             ;\r
252                 MOV ECX,nPRI            ; Set up the number of times to loop\r
253                 LEA EBX,RdyQ            ; Get base address of RdyQ in EBX\r
254             MOV EDX, [EBP+8]            ; EDX holds pJCB for comparison (RAB)\r
255 \r
256                 ;EBX points to begining of next Priority Queue\r
257 RemRdyLoop:\r
258             MOV EAX,[EBX+Head]      ; Get pTSS in EAX\r
259                 MOV EDI, EAX                    ; EDI points to last TSS by default (or NIL)\r
260                 OR  EAX,EAX             ; Is pTSS 0 (none left queued here)\r
261                 JNZ RemRdy0                     ; Valid pTSS!\r
262 RemRdyLoop1:\r
263                 MOV [EBX+Tail], EDI             ; EDI always points to last TSS or NIL\r
264                 ADD EBX,sQUEUE          ; Point to the next Priority Queue\r
265                 LOOP RemRdyLoop         ; DEC ECX and LOOP IF NOT ZERO\r
266 \r
267                 XOR EAX, EAX                    ; No error\r
268                 POP EBP\r
269                 RETN 4                                  ; All done (clean stack)\r
270 \r
271                 ;Go here to dequeue a TSS at head of list\r
272 RemRdy0:\r
273                 CMP EDX, [EAX+TSS_pJCB] ; Is this from the JCB we want?\r
274                 JNE RemRdy2                             ; No\r
275 \r
276                 MOV EDI, [EAX+NextTSS]  ; Yes, deQueue the TSS\r
277                 MOV [EBX+Head], EDI     ; Fix link in Queue list\r
278 \r
279                 PUSH EBX                                ; Save ptr to RdyQue (crnt priority)\r
280 \r
281                 ;Free up the TSS (add it to the free list)\r
282                 MOV EBX,pFreeTSS        ; pTSSin^.Next <= pFreeTSS;\r
283                 MOV [EAX+NextTSS],EBX   ;\r
284                 MOV DWORD PTR [EAX+TSS_pJCB], 0 ; Make TSS invalid\r
285                 MOV pFreeTSS,EAX        ; pFreeTSS <= pTSSin;\r
286                 INC _nTSSLeft                   ;\r
287 \r
288                 POP EBX\r
289                 MOV EAX, EDI                ; Make EAX point to new head TSS\r
290                 OR EAX, EAX                             ; Is it Zero?\r
291                 JZ RemRdyLoop1                  ; Next Queue please\r
292                 JMP RemRdy0                             ; back to check next at head of list\r
293 \r
294                 ;Go here to dequeue a TSS in middle or end of list\r
295 RemRdy2:\r
296                 MOV EAX, [EDI+NextTSS]  ; Get next link in list\r
297                 OR EAX, EAX                             ; Valid pTSS?\r
298                 JZ RemRdyLoop1                  ; No. Next Queue please\r
299                 CMP EDX, [EAX+TSS_pJCB] ; Is this from JCB we want?\r
300                 JE RemRdy3                              ; Yes. Trash it.\r
301                 MOV     EDI, EAX                        ; No. Next TSS\r
302                 JMP RemRdy2\r
303 RemRdy3:\r
304                 ;EDI points to prev TSS\r
305                 ;EAX points to crnt TSS\r
306                 ;Make ESI point to NextTSS\r
307 \r
308                 MOV ESI, [EAX+NextTSS]  ; Yes, deQueue the TSS\r
309 \r
310                 ;Now we fix the list (Make Prev point to Next)\r
311                 ;This extracts EAX from the list\r
312 \r
313                 MOV [EDI+NextTSS], ESI  ;Jump the removed link\r
314                 PUSH EBX                                ;Save ptr to RdyQue (crnt priority)\r
315 \r
316                 ;Free up the TSS (add it to the free list)\r
317                 MOV EBX,pFreeTSS        ; pTSSin^.Next <= pFreeTSS;\r
318                 MOV [EAX+NextTSS],EBX                   ;\r
319                 MOV DWORD PTR [EAX+TSS_pJCB], 0 ; Make TSS invalid\r
320                 MOV pFreeTSS,EAX                ; pFreeTSS <= pTSSin;\r
321                 INC _nTSSLeft                                   ;\r
322 \r
323                 POP EBX\r
324                 ;\r
325                 OR  ESI, ESI                    ;Is EDI the new Tail? (ESI = 0)\r
326                 JZ  RemRdyLoop1                 ;Yes. Next Queue please\r
327                 JMP RemRdy2                             ;back to check next TSS\r
328 \r
329 \r
330 ;=============================================================================\r
331 ; GetExchOwner  (NEAR)\r
332 ;\r
333 ; This routine returns the owner of the exchange specified.\r
334 ; A pointer to the JCB of the owner is returned.\r
335 ; ErcNotAlloc is returned if the exchange isn't allocated.\r
336 ; ErcOutofRange is returned is the exchange number is invalid (too high)\r
337 ;\r
338 ; Procedureal Interface :\r
339 ;\r
340 ;               GetExchOwner(long Exch, char *pJCBRet): dErrror\r
341 ;\r
342 ;       Exch is the exchange number.\r
343 ;       pJCBRet is a pointer to the JCB that the tasks to kill belong to.\r
344 ;\r
345 ; Exch          EQU DWORD PTR [EBP+12]\r
346 ; pJCBRet       EQU DWORD PTR [EBP+8]\r
347 \r
348 PUBLIC _GetExchOwner:           ;\r
349                 PUSH EBP                ;\r
350                 MOV EBP,ESP             ;\r
351 \r
352                 MOV EAX, [EBP+12]               ; Get Resp Exchange in EDX\r
353                 CMP EAX,nExch           ; Is the exchange out of range?\r
354                 JB GEO01                    ; No, continue\r
355                 MOV EAX,ErcOutOfRange   ; Yes, Error in EAX register\r
356                 JMP GEOEnd                              ;\r
357 GEO01:\r
358                 MOV EDX,sEXCH           ; Compute offset of Exch in rgExch\r
359                 MUL EDX                 ; sExch * Exch number\r
360                 MOV EDX,prgExch         ; Add offset of rgExch => EAX\r
361                 ADD EDX,EAX             ; EDX -> Exch\r
362                 MOV EAX, [EDX+Owner]\r
363                 OR EAX, EAX                             ; Valid Exch (Allocated)\r
364                 JNZ GEO02\r
365                 MOV EAX, ErcNotAlloc    ; No, not allocated\r
366                 JMP SHORT GEOEnd\r
367 GEO02:\r
368                 MOV ESI, [EBP+8]                ;Where to return pJCB of Exchange\r
369                 MOV [ESI], EAX                  ;\r
370                 XOR EAX, EAX\r
371 GEOEnd:\r
372                 MOV ESP,EBP             ;\r
373                 POP EBP                 ;\r
374                 RETN 8                  ;\r
375 \r
376 ;=============================================================================\r
377 ; SetExchOwner  (NEAR)\r
378 ;\r
379 ; This routine sets the owner of the exchange specified to the\r
380 ; pJCB specified. This is used by the Job code to set the owner of\r
381 ; a TSS exchange to a new JCB (even though the exchange was allocated\r
382 ; by the OS).  No error checking is done as the job code does it upfront!\r
383 ;\r
384 ; Procedureal Interface :\r
385 ;\r
386 ;               SetExchOwner(long Exch, char *pNewJCB): dErrror\r
387 ;\r
388 ;       Exch is the exchange number.\r
389 ;       pNewJCB is a pointer to the JCB of the new owner.\r
390 ;\r
391 ; Exch          EQU DWORD PTR [EBP+12]\r
392 ; pNewJCB       EQU DWORD PTR [EBP+8]\r
393 \r
394 PUBLIC _SetExchOwner:                   ;\r
395                 PUSH EBP                ;\r
396                 MOV EBP,ESP             ;\r
397                 MOV EAX, [EBP+12]               ; Exchange Number\r
398                 MOV EDX,sEXCH           ; Compute offset of Exch in rgExch\r
399                 MUL EDX                 ; sExch * Exch number\r
400                 MOV EDX,prgExch         ; Add offset of rgExch => EAX\r
401                 ADD EAX,EDX             ; EAX -> oExch + prgExch\r
402                 MOV EBX, [EBP+8]\r
403                 MOV [EAX+Owner], EBX\r
404                 XOR EAX, EAX\r
405                 POP EBP                 ;\r
406                 RETN 8                  ;\r
407 \r
408 ;=============================================================================\r
409 ; SendAbort  (NEAR)\r
410 ;\r
411 ; This routine sends one abort message to each valid service\r
412 ; with the jobnum of the aborting job. If we receive a\r
413 ; kernel error on Request it may be becuase it is a service\r
414 ; that is aborting itself. We ignore the kernel errors.\r
415 ;\r
416 ; Procedureal Interface :\r
417 ;\r
418 ;               SendAbort(long JobNum, ValidExch): dErrror\r
419 ;\r
420 ;       JobNum is the job that is aborting\r
421 ;       ValidExch is any valid exchange so the request will go through\r
422 ;\r
423 ; JobNum        EQU DWORD PTR [EBP+12]\r
424 ; ValidExch     EQU DWORD PTR [EBP+8]\r
425 \r
426 PUBLIC _SendAbort:              ;\r
427                 PUSH EBP                ;\r
428                 MOV EBP,ESP             ;\r
429 \r
430                 MOV ESI,OFFSET rgSVC    ; Get the address of rgSVC\r
431                 MOV ECX,nSVC                    ; Get the number of Service Descriptors\r
432 SAB01:\r
433                 CMP DWORD PTR [ESI], 0  ; Valid name?\r
434                 JE SAB05                                ; NO, next service\r
435 \r
436                 PUSH ESI                                ;Save count and pointer to SVC name\r
437                 PUSH ECX\r
438 \r
439                 ;Push all the params to make the request\r
440                 PUSH ESI                                ;pName\r
441                 PUSH 0                                  ;Abort Service Code\r
442                 MOV EAX, [EBP+8]                ;Exchange\r
443                 PUSH EAX\r
444                 PUSH OFFSET dJunk               ;pHandleRet\r
445                 PUSH 0                                  ;npSend\r
446                 PUSH 0                                  ;pData0\r
447                 PUSH 0                                  ;cbData0\r
448                 PUSH 0                                  ;pData1\r
449                 PUSH 0                                  ;cbData1\r
450                 MOV EAX, [EBP+12]               ;JobNum\r
451                 PUSH EAX                                ;dData0\r
452                 PUSH 0                                  ;dData1\r
453                 PUSH 0                                  ;dData2\r
454                 CALL FWORD PTR _Request\r
455 \r
456 ;RAB\r
457 SAB02:\r
458                 PUSH DWORD PTR [EBP+8]\r
459                 PUSH OFFSET     dmsg\r
460                 CALL FWORD PTR _WaitMsg\r
461                 MOV EAX, dmsg\r
462                 CMP EAX, dJunk          ;see if we got got response back!\r
463                 JNE SAB02                       ;NO - wait again\r
464 ;RAB\r
465 \r
466                 POP ECX\r
467                 POP ESI\r
468 SAB05:\r
469                 ADD ESI, sSVC                   ;Next Service name\r
470                 LOOP SAB01\r
471                 XOR EAX, EAX\r
472                 MOV ESP,EBP             ;\r
473                 POP EBP                 ;\r
474                 RETN 8                  ;\r
475 \r
476 \r
477 \r
478 ;=======================================================================\r
479 ;============== BEGIN PUBLIC KERNEL PRIMITIVES =========================\r
480 ;=======================================================================\r
481 ;\r
482 ; Request - The kernel request primitive sends a message like the Send\r
483 ; primitive except this function requires several more parameters.\r
484 ; A system structure called a request block is allocated and some of these\r
485 ; parameters are placed in it.  A request block is the basic\r
486 ; structure used for Client-Server communications.  The exchange where a\r
487 ; request should be queued is determined by searching the system service\r
488 ; array for a matching request service name specified in the request block.\r
489 ; The procedural interface to Request looks like this:\r
490 ;\r
491 ;    Request(  pSvcName     [EBP+56]\r
492 ;              wSvcCode     [EBP+52]\r
493 ;              dRespExch    [EBP+48]\r
494 ;              pRqHndlRet   [EBP+44]\r
495 ;              dnpSend      [EBP+40]\r
496 ;              pData1       [EBP+36]\r
497 ;              dcbData1     [EBP+32]\r
498 ;              pData2       [EBP+28]\r
499 ;              dcbData2     [EBP+24]\r
500 ;              dData0       [EBP+20]\r
501 ;              dData1       [EBP+16]\r
502 ;              dData2       [EBP+12]  ) : dError\r
503 \r
504 \r
505 PUBLIC __Request:                               ;\r
506                 PUSH EBP                                ; Save the Previous FramePtr\r
507                 MOV EBP,ESP                             ; Set up New FramePtr\r
508 \r
509                 ;Validate service name from registry and get exchange\r
510                 MOV EAX, [EBP+56]               ;pServiceName\r
511                 CALL GetExchange                ;Leaves Service Exch in ESI if no errors\r
512                 OR  EAX,EAX                             ;Any errors?\r
513                 JZ SHORT Req02                  ;No\r
514                 JMP ReqEnd                              ;Yes, return error\r
515 Req02:\r
516                 ;Validate exchange\r
517                 MOV EDX, [EBP+48]               ; Get Resp Exchange in EDX\r
518                 CMP EDX,nExch           ; Is the exchange out of range?\r
519                 JB Req03                    ; No, continue\r
520                 MOV EAX,ercOutOfRange   ; Yes, Error in EAX register\r
521                 JMP ReqEnd                              ;\r
522 Req03:\r
523                 ;Get them a request block\r
524                 CLI\r
525                 CALL NewRQB                             ;EAX has ptr to new RqBlk (or 0 if none)\r
526                 STI\r
527                 OR  EAX, EAX                    ;Did we get one? (NIL (0) means we didn't)\r
528                 JNZ Req04                               ;Yes. EAX ptr to new RqBlk\r
529                 MOV EAX, ErcNoMoreRqBlks ;No, Sorry...\r
530                 JMP ReqEnd                              ;\r
531 Req04:\r
532                 ;ESI still has the exchange for the service\r
533                 ;EDX still has the response exchange\r
534                 ;EAX has pRqBlk (Handle)\r
535 \r
536                 MOV EBX, EAX                            ;EBX now pts to RqBlk\r
537                 MOV [EBX+ServiceExch], ESI      ;Put Svc Exch into RqBlk\r
538                 MOV EAX, [EBP+52]                       ;Get Svc Code\r
539                 MOV [EBX+ServiceCode], AX       ;Put Svc Code into RqBlk\r
540                 MOV [EBX+RespExch], EDX         ;Put Resp Exch into RqBlk\r
541                 CALL GetCrntJobNum                      ;Get crnt JCB (Job Num of owner)\r
542                 MOV [EBX+RqOwnerJob], EAX       ;put in RqBlk\r
543                 MOV EAX, [EBP+20]                       ;Get dData0\r
544                 MOV [EBX+dData0], EAX           ;put in RqBlk\r
545                 MOV EAX, [EBP+16]                       ;Get dData1\r
546                 MOV [EBX+dData1], EAX           ;put in RqBlk\r
547                 MOV EAX, [EBP+20]                       ;Get dData2\r
548                 MOV [EBX+dData2], EAX           ;put in RqBlk\r
549                 MOV EAX, [EBP+36]                       ;Get pData1\r
550                 MOV [EBX+pData1], EAX           ;put in RqBlk\r
551                 MOV EAX, [EBP+32]                       ;Get cbData1\r
552                 MOV [EBX+cbData1], EAX          ;put in RqBlk\r
553                 MOV EAX, [EBP+28]                       ;Get pData2\r
554                 MOV [EBX+pData2], EAX           ;put in RqBlk\r
555                 MOV EAX, [EBP+24]                       ;Get cbData2\r
556                 MOV [EBX+cbData2], EAX          ;put in RqBlk\r
557                 MOV EAX, [EBP+40]                       ;Number of Send PbCbs\r
558                 CMP EAX, 3                                      ;Must be 2 or less\r
559                 JB Req06                                        ;\r
560                 MOV EAX, 2\r
561 Req06:\r
562                 MOV [EBX+npSend], AL            ;Put nSend PbCbs into RqBlk\r
563                 MOV CL, 2                                       ;Caculate nRecv (2-nSend)\r
564                 SUB CL, AL                                      ;Leave in CL\r
565                 MOV [EBX+npRecv], CL            ;Put npRecv in RqBlk\r
566 \r
567                 ;At this point the RqBlk is all filled in.\r
568                 ;Now we will return the RqBlkHandle to the user.\r
569                 ;The handle is actually a ptr to the RqBlk but they can't use\r
570                 ;it as one anyway (so no problem)\r
571 \r
572         MOV EDI, [EBP+44]                       ;Ptr to return handle to\r
573         MOV [EDI], EBX                          ;Give it to them\r
574         MOV EDX, EBX                            ;Save RqBlk in EDX\r
575 \r
576                 CLI                                                     ; No interruptions from here on\r
577                 ;Now we allocate a Link block to use\r
578 \r
579                 MOV EAX,pFreeLB                 ; EAX <= pFreeLB;\r
580                 OR EAX,EAX                      ; Is pFreeLB NIL? (out of LBs)\r
581                 JNZ Req08                       ;\r
582                 CALL DisposeRQB                         ; NO... free up RqBlk\r
583                 MOV EAX,ercNoMoreLBs            ; Move error in the EAX register\r
584                 JMP ReqEnd                                      ; Go home with bad news\r
585 Req08:\r
586                 MOV EBX,[EAX+NextLB]            ; pFreeLB <= pFreeLB^.Next\r
587                 MOV pFreeLB,EBX                 ;\r
588                 DEC _nLBLeft                            ;\r
589 \r
590         MOV DWORD PTR [EAX+LBType],REQLB        ; This is a Request Link Block\r
591                 MOV DWORD PTR [EAX+NextLB], 0           ; pLB^.Next <= NIL;\r
592                 MOV [EAX+DataLo],EDX                            ; RqHandle into Lower 1/2 of Msg\r
593                 MOV DWORD PTR [EAX+DataHi], 0           ; Store zero in upper half of pLB^.Data\r
594                 PUSH EAX                                ; Save pLB on the stack\r
595 \r
596                 ;ESI still has the exchange Number for the service.\r
597                 ;The ptr to the exch is required for deQueueTSS so we get it.\r
598 \r
599         MOV EAX,ESI             ; Exch => EAX\r
600                 MOV EDX, sEXCH          ; Compute offset of Exch in rgExch\r
601                 MUL EDX                 ;\r
602                 MOV EDX,prgExch         ; Add offset of rgExch => EAX\r
603                 ADD EAX,EDX             ;\r
604                 MOV ESI,EAX             ; MAKE ESI <= pExch\r
605 \r
606                 ;ESI now points to the exchange\r
607 \r
608                 CALL deQueueTSS                 ; DeQueue a TSS on that Exch\r
609                 OR  EAX,EAX                     ; Did we get one?\r
610                 JNZ Req10                       ; Yes, give up the message\r
611                 POP EAX                         ; No, Get the pLB just saved\r
612                 CALL enQueueMsg                 ; EnQueue the Message on Exch\r
613                 XOR EAX,EAX                                     ; No Error\r
614                 JMP SHORT ReqEnd                ; And get out!\r
615 Req10:\r
616         POP EBX                         ; Get the pLB just saved into EBX\r
617                 MOV [EAX+pLBRet],EBX        ; and put it in the TSS\r
618                 CALL enQueueRdy                 ; EnQueue the TSS on the RdyQ\r
619                 MOV EAX,pRunTSS                         ; Get the Ptr To the Running TSS\r
620                 CALL enQueueRdy                 ; and put him on the RdyQ\r
621                 CALL deQueueRdy                 ; Get high priority TSS off the RdyQ\r
622                 CMP EAX,pRunTSS                 ; If the high priority TSS is the\r
623                 JNE Req12                       ; same as the Running TSS then return\r
624         XOR EAX,EAX                     ; Return to Caller with erc ok.\r
625                 JMP SHORT ReqEnd\r
626 Req12:\r
627         MOV pRunTSS,EAX         ; Make the TSS in EAX the Running TSS\r
628                 MOV BX,[EAX+Tid]        ; Get the task Id (TR)\r
629                 MOV TSS_Sel,BX          ; Put it in the JumpAddr for Task Swtich\r
630                 INC _nSwitches                  ; Keep track of how many swtiches for stats\r
631                 MOV EAX, TimerTick              ;Save time of this switch for scheduler\r
632                 MOV SwitchTick, EAX             ;\r
633                 JMP FWORD PTR [TSS]     ; JMP TSS (This is the task swtich)\r
634         XOR EAX,EAX             ; Return to Caller with erc ok.\r
635 ReqEnd:\r
636                 STI                     ;\r
637                 MOV ESP,EBP                             ;\r
638                 POP EBP                                 ;\r
639                 RETF 48                                 ; Rtn to Caller & Remove Params from stack\r
640 \r
641 ;=============================================================================\r
642 ; The response primitive is used by system services to respond to a\r
643 ; Request received at their service exchange.  The RqBlk handle must be\r
644 ; supplied along with the error/status code to be returned to the\r
645 ; caller.  This is very similar to Send except is dealiases addresses\r
646 ; in the RqBlk and then deallocates it.  The exchange to respond to\r
647 ; is located inside the RqBlk.\r
648 ; If dStatRet is ErcOwnerAbort, simply return the Reqest Block\r
649 ; to the free pool and return Erc 0 to caller.\r
650 ;     Respond(dRqHndl, dStatRet): dError\r
651 ;\r
652 ;\r
653 dRqHndl  EQU DWORD PTR [EBP+16]\r
654 dStatRet EQU DWORD PTR [EBP+12]\r
655 \r
656 PUBLIC __Respond:                               ;\r
657                 PUSH EBP                                ; Save Callers Frame\r
658                 MOV EBP,ESP                             ; Setup Local Frame\r
659 ;RAB\r
660                 MOV EAX, dRqHndl                ; pRqBlk into EAX\r
661                 MOV EBX, dStatRet\r
662                 CMP EBX, ErcOwnerAbort  ;\r
663                 JNE Resp01\r
664                 CLI                                             ; No interruptions\r
665                 CALL DisposeRQB                 ; Return Aborted RQB to pool.\r
666                 XOR EAX, EAX            ; No Error\r
667                 JMP RespEnd                             ; Get out\r
668 Resp01:\r
669 ;RAB\r
670                 MOV ESI, [EAX+RespExch] ; Response Exchange into ESI\r
671                 CMP ESI,nExch           ; Is the exchange out of range?\r
672                 JNAE Resp02             ; No, continue\r
673                 MOV EAX,ercOutOfRange   ; Error into the EAX register.\r
674                 JMP RespEnd                             ; Get out\r
675 Resp02:\r
676         MOV EAX,ESI             ; Exch => EAX\r
677                 MOV EDX,sEXCH           ; Compute offset of Exch in rgExch\r
678                 MUL EDX                 ;\r
679                 MOV EDX,prgExch         ; Add offset of rgExch => EAX\r
680                 ADD EAX,EDX             ;\r
681                 MOV ESI,EAX             ; MAKE ESI <= pExch\r
682                 CMP DWORD PTR [EAX+Owner], 0    ; If the exchange is not allocated\r
683                 JNE Resp04              ; return to the caller with error\r
684                 MOV EAX,ercNotAlloc     ; in the EAX register.\r
685                 JMP RespEnd                             ;\r
686 Resp04:\r
687                 MOV EAX, dRqHndl        ; Get Request handle into EBX (pRqBlk)\r
688                 MOV EBX, [EAX+RqOwnerJob]\r
689                 CALL GetCrntJobNum\r
690                 CMP EAX, EBX\r
691                 JE Resp06                               ;Same job - no DeAlias needed\r
692 \r
693                 MOV EAX, dRqHndl        ; Get Request handle into EBX (pRqBlk)\r
694                 MOV EBX, [EAX+cbData1]  ;\r
695                 OR EBX, EBX\r
696                 JZ Resp05                               ;No need to dealias (zero bytes)\r
697                 MOV EDX, [EAX+pData1]\r
698                 OR EDX, EDX\r
699                 JZ Resp05                               ;Null pointer!\r
700 \r
701                 PUSH ESI                                ;Save pExch across call\r
702 \r
703                 PUSH EDX                                ;pMem\r
704                 PUSH EBX                                ;cbMem\r
705                 CALL GetCrntJobNum\r
706                 PUSH EAX\r
707                 CALL FWORD PTR _DeAliasMem      ;DO it and ignore errors\r
708                 POP ESI                                 ;get pExch back\r
709 Resp05:\r
710                 MOV EAX, dRqHndl        ; Get Request handle into EBX (pRqBlk)\r
711                 MOV EBX, [EAX+cbData2]  ;\r
712                 OR EBX, EBX\r
713                 JZ Resp06                               ;No need to dealias (zero bytes)\r
714                 MOV EDX, [EAX+pData2]\r
715                 OR EDX, EDX\r
716                 JZ Resp06                               ;Null pointer!\r
717                 PUSH ESI                                ;Save pExch across call\r
718 \r
719                 PUSH EDX                                ;pMem\r
720                 PUSH EBX                                ;cbMem\r
721                 CALL GetCrntJobNum              ;\r
722                 PUSH EAX\r
723                 CALL FWORD PTR _DeAliasMem      ;DO it and ignore errors\r
724                 POP ESI                                 ;get pExch back\r
725 Resp06:\r
726                 MOV EAX, dRqHndl        ; Get Request handle into EBX (pRqBlk)\r
727                 CLI                                             ; No interruptions\r
728                 CALL DisposeRQB                 ; Return Rqb to pool. Not needed anymore\r
729 \r
730                 ; Allocate a link block\r
731                 MOV EAX,pFreeLB         ; NewLB <= pFreeLB;\r
732                 OR EAX,EAX              ; IF pFreeLB=NIL THEN No LBs;\r
733                 JNZ Resp07              ;\r
734                 MOV EAX,ercNoMoreLBs    ; caller with error in the EAX register\r
735                 JMP RespEnd\r
736 Resp07:\r
737                 MOV EBX,[EAX+NextLB]    ; pFreeLB <= pFreeLB^.Next\r
738                 MOV pFreeLB,EBX         ;\r
739                 DEC _nLBLeft                    ;\r
740 \r
741         MOV DWORD PTR [EAX+LBType], RESPLB ; This is a Response Link Block\r
742                 MOV DWORD PTR [EAX+NextLB], 0      ; pLB^.Next <= NIL;\r
743                 MOV EBX, dRqHndl        ; Get Request handle into EBX\r
744                 MOV [EAX+DataLo],EBX    ; Store in lower half of pLB^.Data\r
745                 MOV EBX, dStatRet       ; Get Status/Error into EBX\r
746                 MOV [EAX+DataHi],EBX    ; Store in upper half of pLB^.Data\r
747                 PUSH EAX                ; Save pLB on the stack\r
748                 CALL deQueueTSS         ; DeQueue a TSS on that Exch\r
749                 OR  EAX,EAX             ; Did we get one?\r
750                 JNZ Resp08              ; Yes, give up the message\r
751                 POP EAX                 ; Get the pLB just saved\r
752                 CALL enQueueMsg         ; EnQueue the Message on Exch\r
753                 XOR EAX, EAX                    ; No Error\r
754                 JMP SHORT RespEnd       ; And get out!\r
755 Resp08:\r
756         POP EBX                 ; Get the pLB just saved into EBX\r
757                 MOV [EAX+pLBRet],EBX    ; and put it in the TSS\r
758                 CALL enQueueRdy         ; EnQueue the TSS on the RdyQ\r
759                 MOV EAX,pRunTSS         ; Get the Ptr To the Running TSS\r
760                 CALL enQueueRdy         ; and put him on the RdyQ\r
761                 CALL deQueueRdy         ; Get high priority TSS off the RdyQ\r
762 \r
763                 CMP EAX,pRunTSS         ; If the high priority TSS is the\r
764                 JNE Resp10              ; same as the Running TSS then return\r
765                 XOR EAX,EAX             ; Return to Caller with erc ok.\r
766                 JMP SHORT RespEnd               ;\r
767 Resp10:\r
768         MOV pRunTSS,EAX         ; Make the TSS in EAX the Running TSS\r
769                 MOV BX,[EAX+Tid]        ; Get the task Id (TR)\r
770                 MOV TSS_Sel,BX          ; Put it in the JumpAddr\r
771                 INC _nSwitches\r
772                 MOV EAX, TimerTick              ;Save time of this switch for scheduler\r
773                 MOV SwitchTick, EAX             ;\r
774                 JMP FWORD PTR [TSS]     ; JMP TSS\r
775         XOR EAX,EAX             ; Return to Caller with erc ok.\r
776 RespEnd:\r
777                 STI\r
778                 MOV ESP,EBP                             ;\r
779                 POP EBP                                 ;\r
780                 RETF 8                                  ; Rtn to Caller & Remove Params\r
781 \r
782 ;=============================================================================\r
783 ;\r
784 ; MoveRequest - The kernel Move Request primitive.\r
785 ; This allows a service to move a request to another exchange it owns.\r
786 ; This can not be used to forward a request to another service or Job.\r
787 ; It is very similar to send except it checks to ensure the destination\r
788 ; Exchange is owned by the sender.\r
789 ;\r
790 ; Procedural Interface :\r
791 ;\r
792 ;      MoveRequest(dRqBlkHndl, DestExch):ercType\r
793 ;\r
794 ;           dqMsg is the handle of the RqBlk to forward.\r
795 ;           DestExch the exchange to where the Request should be sent.\r
796 ;\r
797 ;\r
798 ;dRqBlkHndl     EQU [EBP+16]\r
799 ;DestExch               EQU [EBP+12]\r
800 \r
801 PUBLIC __MoveRequest:            ;\r
802                 PUSH EBP                ;\r
803                 MOV EBP,ESP             ;\r
804                 MOV ESI, [EBP+12]       ; Get Exchange Parameter in ESI\r
805                 CMP ESI,nExch           ; Is the exchange is out of range\r
806                 JNAE MReq02             ; No, continue\r
807                 MOV EAX,ercOutOfRange   ; in the EAX register.\r
808                 JMP MReqEnd                             ; Get out\r
809 MReq02:\r
810         MOV EAX,ESI             ; Exch => EAX\r
811                 MOV EDX,sEXCH           ; Compute offset of Exch in rgExch\r
812                 MUL EDX                 ;\r
813                 MOV EDX,prgExch         ; Add offset of rgExch => EAX\r
814                 ADD EAX,EDX             ;\r
815                 MOV ESI,EAX             ; MAKE ESI <= pExch\r
816                 MOV EDX, [EAX+Owner]    ; Put exch owner into EDX (pJCB)\r
817                 CALL GetpCrntJCB                ; Leaves it in EAX (uses only EAX)\r
818                 CMP EDX, EAX                ; If the exchange is not owned by sender\r
819                 JE  MReq04              ; return to the caller with error\r
820                 MOV EAX, ErcNotOwner    ; in the EAX register.\r
821                 JMP MReqEnd                             ; Get out\r
822 MReq04:\r
823                 CLI                                             ; No interruptions from here on\r
824                 ; Allocate a link block\r
825                 MOV EAX,pFreeLB         ; NewLB <= pFreeLB;\r
826                 OR EAX,EAX              ; IF pFreeLB=NIL THEN No LBs;\r
827                 JNZ MReq08              ;\r
828                 MOV EAX,ercNoMoreLBs    ; caller with error in the EAX register\r
829                 JMP MReqEnd                             ; Go home with bad news\r
830 MReq08:\r
831                 MOV EBX,[EAX+NextLB]    ; pFreeLB <= pFreeLB^.Next\r
832                 MOV pFreeLB,EBX         ;\r
833                 DEC _nLBLeft                    ;\r
834 \r
835         MOV DWORD PTR [EAX+LBType], REQLBA      ; Request Link Block (ALIASED! RAB)\r
836                 MOV DWORD PTR [EAX+NextLB], 0           ; pLB^.Next <= NIL;\r
837                 MOV EBX, [EBP+16]                                       ; RqHandle\r
838                 MOV [EAX+DataLo],EBX                            ; RqHandle into Lower 1/2 of Msg\r
839                 MOV DWORD PTR [EAX+DataHi], 0           ; Store zero in upper half of pLB^.Data\r
840                 PUSH EAX                        ; Save pLB on the stack\r
841                 CALL deQueueTSS                 ; DeQueue a TSS on that Exch\r
842                 OR  EAX,EAX                     ; Did we get one?\r
843                 JNZ MReq10                      ; Yes, give up the message\r
844                 POP EAX                         ; Get the pLB just saved\r
845                 CALL enQueueMsg                 ; EnQueue the Message on Exch ESI\r
846                 XOR EAX, EAX\r
847                 JMP SHORT MReqEnd               ; And get out!\r
848 MReq10:\r
849         POP EBX                         ; Get the pLB just saved into EBX\r
850                 MOV [EAX+pLBRet],EBX        ; and put it in the TSS\r
851                 CALL enQueueRdy                 ; EnQueue the TSS on the RdyQ\r
852                 MOV EAX,pRunTSS                         ; Get the Ptr To the Running TSS\r
853                 CALL enQueueRdy                 ; and put him on the RdyQ\r
854                 CALL deQueueRdy                 ; Get high priority TSS off the RdyQ\r
855                 CMP EAX,pRunTSS                 ; If the high priority TSS is the\r
856                 JNE MReq12                      ; same as the Running TSS then return\r
857                 XOR EAX,EAX                             ; Return to Caller with erc ok.\r
858                 JMP SHORT MReqEnd\r
859 MReq12:\r
860         MOV pRunTSS,EAX         ; Make the TSS in EAX the Running TSS\r
861                 MOV BX,[EAX+Tid]        ; Get the task Id (TR)\r
862                 MOV TSS_Sel,BX          ; Put it in the JumpAddr for Task Swtich\r
863                 INC _nSwitches                  ; Keep track of how many swtiches for stats\r
864                 MOV EAX, TimerTick              ;Save time of this switch for scheduler\r
865                 MOV SwitchTick, EAX             ;\r
866                 JMP FWORD PTR [TSS]     ; JMP TSS (This is the task switch)\r
867         XOR EAX,EAX             ; Return to Caller with erc ok.\r
868 MReqEnd:\r
869                 STI                     ;\r
870                 MOV ESP,EBP             ;\r
871                 POP EBP                 ;\r
872                 RETF 8                  ;\r
873 \r
874 ;=============================================================================\r
875 ;\r
876 ; SendMsg - The kernel send primitive. This     sends a non-specific message\r
877 ; from a running task to an exchange. This may cause a task swtich if\r
878 ; a task is waiting at the exchange and it is of equal or higher priority\r
879 ; that the task that sent the message.\r
880 ;\r
881 ; Procedural Interface :\r
882 ;\r
883 ;       SendMsg(exch, dMsg1, dMsg2):ercType\r
884 ;\r
885 ;           exch is a DWORD (4 BYTES) containing the exchange to where the\r
886 ;           message should be sent.\r
887 ;\r
888 ;           dMsg1 & dMsg2 are DWord values defined and understood\r
889 ;                       only by the sending and receiving tasks.\r
890 ;\r
891 SendExchange   EQU [EBP+14h]\r
892 MessageHi      EQU DWORD PTR [EBP+10h]\r
893 MessageLo      EQU DWORD PTR [EBP+0Ch]\r
894 \r
895 PUBLIC __SendMsg:                       ;\r
896                 PUSH EBP                ;\r
897                 MOV EBP,ESP             ;\r
898                 MOV ESI,SendExchange    ; Get Exchange Parameter in ESI\r
899                 CMP ESI,nExch           ; If the exchange is out of range\r
900                 JNAE Send00             ; the return to caller with error\r
901                 MOV EAX,ercOutOfRange   ; in the EAX register.\r
902                 JMP SendEnd\r
903 Send00:\r
904         MOV EAX,ESI             ; Exch => EAX\r
905                 MOV EDX,sEXCH           ; Compute offset of Exch in rgExch\r
906                 MUL EDX                 ;\r
907                 MOV EDX,prgExch         ; Add offset of rgExch => EAX\r
908                 ADD EAX,EDX             ;\r
909                 MOV ESI,EAX             ; MAKE ESI <= pExch\r
910                 CMP DWORD PTR [EAX+Owner], 0    ; If the exchange is not allocated\r
911                 JNE Send01              ; return to the caller with error\r
912                 MOV EAX,ercNotAlloc     ; in the EAX register.\r
913                 JMP SendEnd                             ;\r
914 Send01:\r
915                 CLI                                             ; No interrupts\r
916                 ; Allocate a link block\r
917                 MOV EAX,pFreeLB         ; NewLB <= pFreeLB;\r
918                 OR EAX,EAX              ; IF pFreeLB=NIL THEN No LBs;\r
919                 JNZ SHORT Send02        ;\r
920                 MOV EAX,ercNoMoreLBs    ; caller with error in the EAX register\r
921                 JMP SHORT MReqEnd               ; Go home with bad news\r
922 Send02:\r
923                 MOV EBX,[EAX+NextLB]    ; pFreeLB <= pFreeLB^.Next\r
924                 MOV pFreeLB,EBX         ;\r
925                 DEC _nLBLeft                    ;\r
926 \r
927         MOV DWORD PTR [EAX+LBType], DATALB ; This is a Data Link Block\r
928                 MOV DWORD PTR [EAX+NextLB], 0      ; pLB^.Next <= NIL;\r
929                 MOV EBX,MessageLo       ; Get lower half of Msg in EBX\r
930                 MOV [EAX+DataLo],EBX    ; Store in lower half of pLB^.Data\r
931                 MOV EBX,MessageHi       ; Get upper half of Msg in EBX\r
932                 MOV [EAX+DataHi],EBX    ; Store in upper half of pLB^.Data\r
933 \r
934                 PUSH EAX                ; Save pLB on the stack\r
935 \r
936                 CLI                                             ; No interrupts\r
937                 CALL deQueueTSS         ; DeQueue a TSS on that Exch\r
938                 STI\r
939                 OR  EAX,EAX             ; Did we get one?\r
940                 JNZ Send25              ; Yes, give up the message\r
941                 POP EAX                 ; Get the pLB just saved\r
942                 CLI                                             ; No interrupts\r
943                 CALL enQueueMsg         ; EnQueue the Message on Exch\r
944                 JMP Send04              ; And get out (Erc 0)!\r
945 Send25:\r
946         POP EBX                 ; Get the pLB just saved into EBX\r
947                 CLI                                             ; No interrupts\r
948                 MOV [EAX+pLBRet],EBX    ; and put it in the TSS\r
949                 CALL enQueueRdy         ; EnQueue the TSS on the RdyQ\r
950                 MOV EAX,pRunTSS         ; Get the Ptr To the Running TSS\r
951                 CALL enQueueRdy         ; and put him on the RdyQ\r
952                 CALL deQueueRdy         ; Get high priority TSS off the RdyQ\r
953                 CMP EAX,pRunTSS         ; If the high priority TSS is the\r
954                 JNE Send03              ; same as the Running TSS then return\r
955                 JMP SHORT Send04                ; Return with ErcOk\r
956 \r
957 Send03:\r
958         MOV pRunTSS,EAX         ; Make the TSS in EAX the Running TSS\r
959                 MOV BX,[EAX+Tid]        ; Get the task Id (TR)\r
960                 MOV TSS_Sel,BX          ; Put it in the JumpAddr\r
961                 INC _nSwitches\r
962                 MOV EAX, TimerTick              ;Save time of this switch for scheduler\r
963                 MOV SwitchTick, EAX             ;\r
964                 JMP FWORD PTR [TSS]     ; JMP TSS\r
965 Send04:\r
966         XOR EAX,EAX             ; Return to Caller with erc ok.\r
967 SendEnd:\r
968                 STI                     ;\r
969                 MOV ESP,EBP             ;\r
970                 POP EBP                 ;\r
971                 RETF 12                 ;\r
972 \r
973 ;=============================================================================\r
974 ;\r
975 ; ISendMsg - The OS Interrupt Send primitive.\r
976 ;  This procedure allows an ISR to send a message to an exchange.\r
977 ;  This is the same as SendMsg except NO task switch is\r
978 ;  performed. If a task is waiting at the exchange, the message is\r
979 ;  associated (linked) with it and it is moved to the RdyQ.\r
980 ;  It will get a chance to run the next time the RdyQ is evaluated\r
981 ;  by the Kernel which will probably be by the timer interrupt slicer.\r
982 ;  Interrupt tasks can use ISendMsg to send single or multiple messages\r
983 ;  to exchanges during their execution.\r
984 ;  Interrupts are CLEARED on entry and WILL NOT BE SET on exit!!!\r
985 ;  It is the responsibility of the caller to set them if desired.\r
986 ;  ISendMsg is intended only to be used by ISRs in device drivers\r
987 ;\r
988 ;\r
989 ; Procedural Interface :\r
990 ;\r
991 ;       ISendMsg(exch, dMsg1, dMsg2):ercType\r
992 ;\r
993 ;           exch is a DWORD (4 BYTES) containing the exchange to where the\r
994 ;           message should be sent.\r
995 ;\r
996 ;           dMsg1 and dMsg2 are DWORD messages.\r
997 ;\r
998 ; Parameters on stack are the same as _SendMsg.\r
999 \r
1000 PUBLIC __ISendMsg:                                  ;\r
1001                 CLI                     ;INTS ALWAYS CLEARED AND LEFT THAT WAY!\r
1002                 PUSH EBP                ;\r
1003                 MOV EBP,ESP             ;\r
1004                 MOV ESI,SendExchange    ; Get Exchange Parameter in ESI\r
1005                 CMP ESI,nExch           ; If the exchange is out of range\r
1006                 JNAE ISend00            ; then return to caller with error\r
1007                 MOV EAX,ercOutOfRange   ; in the EAX register.\r
1008                 MOV ESP,EBP             ;\r
1009                 POP EBP                 ;\r
1010                 RETF 12                 ;\r
1011 ISend00:\r
1012         MOV EAX,ESI             ; Exch => EAX\r
1013                 MOV EDX,sEXCH           ; Compute offset of Exch in rgExch\r
1014                 MUL EDX                 ;\r
1015                 MOV EDX,prgExch         ; Add offset of rgExch => EAX\r
1016                 ADD EAX,EDX             ;\r
1017                 MOV ESI,EAX                             ; MAKE ESI <= pExch\r
1018                 CMP DWORD PTR [EAX+Owner], 0    ; If the exchange is not allocated\r
1019                 JNE ISend01                             ; return to the caller with error\r
1020                 MOV EAX,ercNotAlloc     ; in the EAX register.\r
1021                 MOV ESP,EBP             ;\r
1022                 POP EBP                 ;\r
1023                 RETF 12                 ;\r
1024 ISend01:\r
1025                 ; Allocate a link block\r
1026                 MOV EAX,pFreeLB         ; NewLB <= pFreeLB;\r
1027                 OR EAX,EAX              ; IF pFreeLB=NIL THEN No LBs;\r
1028                 JNZ SHORT ISend02        ;\r
1029                 MOV EAX,ercNoMoreLBs    ; caller with error in the EAX register\r
1030                 MOV ESP,EBP             ;\r
1031                 POP EBP                 ;\r
1032                 RETF 12                 ;\r
1033 ISend02:\r
1034                 MOV EBX,[EAX+NextLB]    ; pFreeLB <= pFreeLB^.Next\r
1035                 MOV pFreeLB,EBX         ;\r
1036                 DEC _nLBLeft                    ;\r
1037 \r
1038         MOV DWORD PTR [EAX+LBType], DATALB ; This is a Data Link Block\r
1039                 MOV DWORD PTR [EAX+NextLB],0      ; pLB^.Next <= NIL;\r
1040                 MOV EBX,MessageLo       ; Get lower half of Msg in EBX\r
1041                 MOV [EAX+DataLo],EBX    ; Store in lower half of pLB^.Data\r
1042                 MOV EBX,MessageHi       ; Get upper half of Msg in EBX\r
1043                 MOV [EAX+DataHi],EBX    ; Store in upper half of pLB^.Data\r
1044                 PUSH EAX                ; Save pLB on the stack\r
1045                 CALL deQueueTSS         ; DeQueue a TSS on that Exch\r
1046                 OR  EAX,EAX             ; Did we get one?\r
1047                 JNZ ISend03             ; Yes, give up the message\r
1048                 POP EAX                 ; No, Get the pLB just saved\r
1049                 CALL enQueueMsg         ; EnQueue the Message on Exch\r
1050                 JMP ISend04             ; And get out!\r
1051 ISend03:\r
1052         POP EBX                 ; Get the pLB just saved into EBX\r
1053                 MOV [EAX+pLBRet],EBX    ; and put it in the TSS\r
1054                 CALL enQueueRdy         ; EnQueue the TSS on the RdyQ\r
1055 ISend04:\r
1056         XOR EAX,EAX             ; Return to Caller with erc ok.\r
1057                 MOV ESP,EBP             ;\r
1058                 POP EBP                 ;\r
1059                 RETF 12                 ;\r
1060 \r
1061 ;=============================================================================\r
1062 ;\r
1063 ; Wait - The kernel wait primitive. This procedure allows a task to\r
1064 ;  receive information from another task from an exchange.  If no\r
1065 ;  message is at the exchange, the task is placed on the exchange\r
1066 ;  and the ReadyQ is reevaluated to make the next tast run.\r
1067 ;\r
1068 ; A result code is returned in the EAX register.\r
1069 ;\r
1070 ; Procedural Interface :\r
1071 ;\r
1072 ;       Wait(exch,pdqMsgRet):ercType\r
1073 ;\r
1074 ;           exch is a DWORD (4 BYTES) containing the exchange to where the\r
1075 ;           message should be sent.\r
1076 ;\r
1077 ;           pMessage is a pointer to an 8 byte area where the\r
1078 ;           message is stored.\r
1079 ;\r
1080 WaitExchange    EQU [EBP+10h]\r
1081 pMessage                EQU [EBP+0Ch]\r
1082 ;\r
1083 ;\r
1084 PUBLIC __WaitMsg:                               ;\r
1085                 PUSH EBP                ;\r
1086                 MOV EBP,ESP             ;\r
1087                 MOV ESI,WaitExchange    ; Get Exchange Parameter in ESI\r
1088                 CMP ESI,nExch           ; If the exchange is out of range\r
1089                 JNAE Wait00                     ; the return to caller with error\r
1090                 MOV EAX,ercOutOfRange   ; in the EAX register.\r
1091                 MOV ESP,EBP             ;\r
1092                 POP EBP                 ;\r
1093                 RETF 8                                  ;\r
1094 Wait00:\r
1095                 MOV EAX,ESI             ; ExchId => EAX\r
1096                 MOV EBX,sEXCH           ; Compute offset of ExchId in rgExch\r
1097                 MUL EBX                 ;\r
1098                 MOV EDX,prgExch         ; Add offset of rgExch => EAX\r
1099                 ADD EAX,EDX             ;\r
1100                 MOV ESI,EAX             ; Put Exch in to ESI\r
1101                 CMP DWORD PTR [EAX+Owner], 0   ; If the exchange is not allocated\r
1102                 JNE Wait01              ; return to the caller with error\r
1103                 MOV EAX,ercNotAlloc     ; in the EAX register.\r
1104                 MOV ESP,EBP             ;\r
1105                 POP EBP                 ;\r
1106                 RETF 8                  ;\r
1107 Wait01:\r
1108                 CLI                     ;\r
1109                 CALL deQueueMsg         ; EAX <= pLB from pExch (ESI)\r
1110                 OR  EAX,EAX             ; If no message (pLB = NIL) Then\r
1111                 JZ Wait02               ; Wait for Message Else\r
1112                 JMP Wait05              ; Get Message and Return\r
1113 \r
1114 Wait02:\r
1115                 MOV EAX,pRunTSS         ; Get pRunTSS in EAX to Wait\r
1116 \r
1117                 ;This next section of code Queues up the TSS pointed to\r
1118                 ;by EAX on the exchange pointed to by ESI\r
1119                 ; (i.e., we make the current task "wait")\r
1120 \r
1121                 MOV DWORD PTR [EAX+NextTSS], 0  ; pTSSin^.Next <= NIL;\r
1122                 XCHG ESI,EAX                            ; pExch => EAX, pTSSin => ESI\r
1123                 CMP DWORD PTR [EAX+EHead], 0    ; if ..TSSHead = NIL\r
1124                 JNE Wait025                                             ; then\r
1125                 MOV [EAX+EHead],ESI     ;  ..TSSHead <= pTSSin;\r
1126                 MOV [EAX+ETail],ESI     ;  ..TSSTail <= pTSSin;\r
1127                 MOV DWORD PTR [EAX+fEMsg], 0            ; Flag it as a TSS (vice a Msg)\r
1128                 XCHG ESI,EAX            ; Make ESI <= pExch Again\r
1129                 JMP SHORT Wait03                  ; else\r
1130 Wait025:\r
1131             MOV EDX,[EAX+ETail]     ;  ..TSSTail^.NextTSS <= pTSSin;\r
1132                 MOV [EDX+NextTSS],ESI   ;\r
1133                 MOV [EAX+ETail],ESI     ;  ..TSSTail <= pTSSin;\r
1134                 MOV DWORD PTR [EAX+fEMsg], 0            ; Flag it as a TSS (vice a Msg)\r
1135                 XCHG ESI,EAX            ; Make ESI <= pExch Again\r
1136 \r
1137                 ;We just placed the current TSS on an exchange,\r
1138                 ;now we get the next TSS to run (if there is one)\r
1139 \r
1140 Wait03:\r
1141                 CALL deQueueRdy         ; Get highest priority TSS off the RdyQ\r
1142                 OR EAX, EAX                             ; Anyone ready to run?\r
1143                 JNZ Wait035             ; Yes (jump to check pTSS)\r
1144 \r
1145                 MOV EDI, 1\r
1146                 MOV dfHalted, EDI\r
1147                 INC _nHalts\r
1148                 STI                     ; No, then HLT CPU until ready\r
1149                 HLT                     ; Halt CPU and wait for interrupt\r
1150                 CLI                     ; An interrupt has occured. Clear Interrupts\r
1151                 XOR EDI,EDI\r
1152                 MOV dfHalted, EDI\r
1153                 JMP Wait03              ; Check for a task to switch to\r
1154 \r
1155 Wait035:\r
1156                 CMP EAX,pRunTSS         ; Same one as before???\r
1157                 JE Wait04               ; You bet! NO SWITCH!!!\r
1158 \r
1159                 ;Now we switch tasks by placing the address of the\r
1160                 ;new TSS in pRunTSS and jumping to it.  This forces\r
1161                 ;a 386 task switch.\r
1162 \r
1163                 MOV pRunTSS,EAX                 ; Make high priority TSS Run.\r
1164                 MOV BX,[EAX+Tid]                ;\r
1165                 MOV TSS_Sel,BX                  ;\r
1166                 INC _nSwitches\r
1167                 MOV EAX, TimerTick              ;Save time of this switch for scheduler\r
1168                 MOV SwitchTick, EAX             ;\r
1169                 JMP FWORD PTR [TSS]             ; JUMP TSS (Switch Tasks)\r
1170 \r
1171                 ; A task has just finished "Waiting"\r
1172                 ; We are now in the new task with its memory space\r
1173                 ; (or the same task if he was high pri & had a msg)\r
1174                 ; If this is a system service it may need RqBlk address aliases\r
1175                 ; If it is an OS service we alias in OS memory!\r
1176 \r
1177 Wait04:\r
1178                 MOV EDX,pRunTSS         ; Put the TSS in EAX into EDX\r
1179                 MOV EAX,[EDX+pLBRet]    ; Get the pLB in EAX\r
1180 Wait05:\r
1181                 ; if we got here, we have either switched tasks\r
1182                 ; and we are delivering a message (or Req) to the new task,\r
1183                 ; or the there was a message waiting at the exch of\r
1184                 ; the first caller and we are delivering it.\r
1185                 ; Either way, the message is already deQueued from\r
1186                 ; the exch and the critical part of WaitMsg is over.\r
1187                 ; We can start interrupts again except when we have\r
1188                 ; to return the Link Block to the pool (free it up)\r
1189 \r
1190                 STI                                                                     ; WE CAN RESTART INTERRUPTS HERE\r
1191                 CMP DWORD PTR [EAX+LBType],REQLB        ; Is the link block a Req Link Block?\r
1192                 JNE Wait06                                                      ; No, Treat it as a data link block\r
1193 \r
1194                 ;pLB.DataLo is RqHandle (pRqBlk)\r
1195 \r
1196                 PUSH EAX                                ; Save ptr to Link Block\r
1197                 MOV EBX,[EAX+DataLo]    ; Get pRqBlk into EBX\r
1198 \r
1199                 ;Now we set up to alias the memory for the service\r
1200                 ; (Alias the 2 Pointers in the RqBlk)\r
1201                 ;_AliasMem(pMem, dcbMem, dJobNum, ppAliasRet): dError\r
1202 \r
1203                 MOV ECX, [EBX+cbData1]          ;\r
1204                 OR ECX, ECX                                     ;is cbData1 0?\r
1205                 JZ Wait051                                      ;Yes\r
1206 \r
1207                 MOV EAX, [EBX+pData1]           ;\r
1208                 OR EAX, EAX                                     ;is pData1 NULL?\r
1209                 JZ Wait051                                      ;Yes\r
1210 \r
1211                                                                         ;Set up params for AliasMem\r
1212                 PUSH EAX                                        ;pMem\r
1213                 PUSH ECX                                        ;cbMem\r
1214                 MOV EAX, [EBX+RqOwnerJob]\r
1215                 PUSH EAX                                        ;dJobNum\r
1216                 ADD EBX, pData1                         ;Offset to pData1 in RqBlk\r
1217                 PUSH EBX                                        ;Linear Address of pData1\r
1218                 CALL FWORD PTR _AliasMem\r
1219                 OR EAX, EAX                                     ;Error??\r
1220                 JZ Wait051                                      ;No, continue\r
1221                 POP EBX                                         ;Make stack right\r
1222                 MOV ESP,EBP                     ;Return Error...\r
1223                 POP EBP                         ;\r
1224                 RETF 8                          ;\r
1225 \r
1226 Wait051:                                                        ;Second Pointer (pData2)\r
1227                 POP EAX                                         ;Restore ptr to Link Block\r
1228                 PUSH EAX                                        ;Save again\r
1229                 MOV EBX,[EAX+DataLo]            ; Get pRqBlk into EBX\r
1230 \r
1231                 MOV ECX, [EBX+cbData2]          ;\r
1232                 OR ECX, ECX                                     ;is cbData2 0?\r
1233                 JZ Wait052                                      ;Yes\r
1234 \r
1235                 MOV EAX, [EBX+pData2]           ;\r
1236                 OR EAX, EAX                                     ;is pData2 NULL?\r
1237                 JZ Wait052                                      ;Yes\r
1238                                                                         ;Set up params for AliasMem\r
1239                 PUSH EAX                                        ;pMem\r
1240                 PUSH ECX                                        ;cbMem\r
1241                 MOV EAX, [EBX+RqOwnerJob]\r
1242                 PUSH EAX                                        ;dJobNum\r
1243                 ADD EBX, pData2                         ;Offset to pData2 in RqBlk\r
1244                 PUSH EBX                                        ;Linear Address of PData1\r
1245                 CALL FWORD PTR _AliasMem\r
1246                 OR EAX, EAX                                     ;Error??\r
1247                 JZ Wait052                                      ;No, continue\r
1248                 POP EBX                                         ;Make stack right\r
1249                 MOV ESP,EBP                     ;Return Error...\r
1250                 POP EBP                         ;\r
1251                 RETF 8                          ;\r
1252 \r
1253 Wait052:\r
1254                 POP EAX                                 ;Restore ptr to Link Block\r
1255 Wait06:\r
1256                 MOV EBX,[EAX+DataLo]    ; Get pLB^.Data into ECX:EBX\r
1257                 MOV ECX,[EAX+DataHi]    ;\r
1258                 MOV EDX,pMessage                ; Get Storage Addr in EDX\r
1259                 MOV [EDX],EBX                   ; Put pLB^.Data in specified\r
1260                 MOV [EDX+4],ECX             ; memory space (EDX)\r
1261 \r
1262                 ;Return the LB to the pool\r
1263                 CLI\r
1264                 MOV EBX,pFreeLB         ; pLBin^.Next <= pFreeLB;\r
1265                 MOV [EAX+NextLB],EBX    ;\r
1266                 MOV pFreeLB,EAX         ; pFreeLB <= pLBin;\r
1267                 INC _nLBLeft                    ;\r
1268                 STI                     ;\r
1269                 XOR EAX,EAX             ; ErcOK! (0)\r
1270                 MOV ESP,EBP             ;\r
1271                 POP EBP                 ;\r
1272                 RETF 8                  ;\r
1273 \r
1274 ;\r
1275 ;=============================================================================\r
1276 ;\r
1277 ; CheckMsg - The kernel Check primitive. This procedure provides access\r
1278 ; to the operating system by allowing a task to receive information\r
1279 ; from another process WITHOUT BLOCKING. In other words, if no message is\r
1280 ; available Check returns to the caller. If a message IS available it\r
1281 ; is returned to the caller immediately. The caller is never placed on\r
1282 ; an exchange and the RdyQ is not evaluated.\r
1283 ;\r
1284 ; A result code is returned in the EAX register.\r
1285 ;\r
1286 ; Procedureal Interface :\r
1287 ;\r
1288 ;       CheckMsg(exch,pdqMsg):ercType\r
1289 ;\r
1290 ;           exch is a DWORD (4 BYTES) containing the exchange to where the\r
1291 ;           message should be sent.\r
1292 ;\r
1293 ;           pdqMsg is a pointer to an 8 byte area where the message is stored.\r
1294 ;\r
1295 ChkExchange   EQU [EBP+10h]\r
1296 pCkMessage    EQU [EBP+0Ch]\r
1297 \r
1298 PUBLIC __CheckMsg:               ;\r
1299                 PUSH EBP                ;\r
1300                 MOV EBP,ESP             ;\r
1301                 MOV ESI,ChkExchange     ; Get Exchange Parameter in ESI\r
1302                 CMP ESI,nExch           ; If the exchange is out of range\r
1303                 JNAE Chk01              ; the return to caller with error\r
1304                 MOV EAX,ercOutOfRange   ; in the EAX register.\r
1305                 MOV ESP,EBP             ;\r
1306                 POP EBP                 ;\r
1307                 RETF 8                  ;\r
1308 Chk01:\r
1309                 MOV EAX,ESI             ; Exch => EAX\r
1310                 MOV EBX,sEXCH           ; Compute offset of Exch in rgExch\r
1311                 MUL EBX                 ;\r
1312                 MOV EDX,prgExch         ; Add offset of rgExch => EAX\r
1313                 ADD EAX,EDX             ;\r
1314                 MOV ESI,EAX                             ; Put pExch in to ESI\r
1315                 CMP DWORD PTR [EAX+Owner], 0    ; If the exchange is not allocated\r
1316                 JNE Chk02                               ; return to the caller with error\r
1317 \r
1318                 MOV EAX,ercNotAlloc     ; in the EAX register.\r
1319                 MOV ESP,EBP             ;\r
1320                 POP EBP                 ;\r
1321                 RETF 8                                  ;\r
1322 Chk02:\r
1323                 CLI                     ; Can't be interrupted\r
1324                 CALL deQueueMsg         ; EAX <= pLB from pExch (ESI)\r
1325                 OR  EAX,EAX             ; If pLB = NIL Then\r
1326                 JNZ Chk03               ; Go to get msg and return\r
1327 \r
1328                 STI                     ;\r
1329                 MOV EAX,ercNoMsg        ; return with erc no msg\r
1330                 MOV ESP,EBP             ;\r
1331                 POP EBP                                 ;\r
1332                 RETF 8                                  ;\r
1333 Chk03:\r
1334                 STI                                             ;We can be interrupted again\r
1335 \r
1336                 CMP DWORD PTR [EAX+LBType],REQLB        ; Is the link block a Req Link Block?\r
1337                 JNE Chk04                               ; No, Treat it as a data link block\r
1338 \r
1339                 ;pLB.DataLo is RqHandle (pRqBlk)\r
1340 \r
1341                 PUSH EAX                                ; Save ptr to Link Block\r
1342                 MOV EBX,[EAX+DataLo]    ; Get pRqBlk into EBX\r
1343 \r
1344                 ;Now we set up to alias the memory for the service\r
1345                 ; (Alias the 2 Pointers in the RqBlk)\r
1346                 ;_AliasMem(pMem, dcbMem, dJobNum, ppAliasRet): dError\r
1347 \r
1348                 MOV ECX, [EBX+cbData1]          ;\r
1349                 OR ECX, ECX                                     ;is cbData1 0?\r
1350                 JZ Chk031                                       ;Yes\r
1351 \r
1352                 MOV EAX, [EBX+pData1]           ;\r
1353                 OR EAX, EAX                                     ;is pData1 NULL?\r
1354                 JZ Chk031                                       ;Yes\r
1355                                                                         ;Set up params for AliasMem\r
1356                 PUSH EAX                                        ;pMem\r
1357                 PUSH ECX                                        ;cbMem\r
1358                 MOV EAX, [EBX+RqOwnerJob]\r
1359                 PUSH EAX                                        ;dJobNum\r
1360                 ADD EBX, pData1                         ;Offset to pData1 in RqBlk\r
1361                 PUSH EBX                                        ;Linear Address of pData1\r
1362                 CALL FWORD PTR _AliasMem\r
1363                 OR EAX, EAX                                     ;Error??\r
1364                 JZ Chk031                                       ;No, continue\r
1365                 POP EBX                                         ;Make stack right\r
1366                 MOV ESP,EBP                     ;Return Error...\r
1367                 POP EBP                         ;\r
1368                 RETF 8                          ;\r
1369 \r
1370 Chk031:                                                         ;Second Pointer (pData2)\r
1371                 POP EAX                                         ;Restore ptr to Link Block\r
1372                 PUSH EAX                                        ;Save again\r
1373                 MOV EBX,[EAX+DataLo]            ; Get pRqBlk into EBX\r
1374 \r
1375                 MOV ECX, [EBX+cbData2]          ;\r
1376                 OR ECX, ECX                                     ;is cbData2 0?\r
1377                 JZ Chk032                                       ;Yes\r
1378 \r
1379                 MOV EAX, [EBX+pData2]           ;\r
1380                 OR EAX, EAX                                     ;is pData2 NULL?\r
1381                 JZ Chk032                                       ;Yes\r
1382                                                                         ;Set up params for AliasMem\r
1383                 PUSH EAX                                        ;pMem\r
1384                 PUSH ECX                                        ;cbMem\r
1385                 MOV EAX, [EBX+RqOwnerJob]\r
1386                 PUSH EAX                                        ;dJobNum\r
1387                 ADD EBX, pData2                         ;Offset to pData2 in RqBlk\r
1388                 PUSH EBX                                        ;Linear Address of PData1\r
1389                 CALL FWORD PTR _AliasMem\r
1390                 OR EAX, EAX                                     ;Error??\r
1391                 JZ Chk032                                       ;No, continue\r
1392                 POP EBX                                         ;Make stack right\r
1393                 MOV ESP,EBP                     ;Return Error...\r
1394                 POP EBP                         ;\r
1395                 RETF 8                          ;\r
1396 \r
1397 Chk032:\r
1398                 POP EAX                                         ;Restore Ptr to Link Block\r
1399 \r
1400 Chk04:\r
1401         MOV EBX,[EAX+DataLo]    ; Get pLB^.Data into ECX:EBX\r
1402                 MOV ECX,[EAX+DataHi]    ;\r
1403                 MOV EDX,pCkMessage              ; Get Storage Addr in EDX\r
1404                 MOV [EDX],EBX           ; Put pLB^.Data in specified\r
1405                 MOV [EDX+4],ECX                 ; memory space (EDX)\r
1406 \r
1407                 ;Return the LB to the pool\r
1408                 CLI\r
1409                 MOV EBX,pFreeLB         ; pLBin^.Next <= pFreeLB;\r
1410                 MOV [EAX+NextLB],EBX    ;\r
1411                 MOV pFreeLB,EAX         ; pFreeLB <= pLBin;\r
1412                 INC _nLBLeft                    ;\r
1413                 STI                     ;\r
1414 \r
1415                 XOR EAX,EAX             ;ErcOK! (0)\r
1416                 MOV ESP,EBP             ;\r
1417                 POP EBP                 ;\r
1418                 RETF 8                                  ;\r
1419 \r
1420 ;====================================================================\r
1421 ; NewTask --- OS PUBLIC - Creates a new task and schedules it for execution.\r
1422 ; used primarily to create a task for a job other than the one you are in.\r
1423 ; The OS uses this to create the initial task for a newly loaded job.\r
1424 ;\r
1425 ; The OS stacks are preallocated as part of the TSS.  If this is an OS\r
1426 ; task (CodeSeg = 8) then we load the TSS Stack into TSS_ESP and\r
1427 ; TSS_ESP0, otherwise we take the ESP param and place it into TSS_ESP.\r
1428 ;\r
1429 ;  Procedural interface:\r
1430 ;\r
1431 ;       NewTask(JobNum, CodeSeg, Priority, fDebug, Exch, ESP, EIP): dErcRet\r
1432 ;\r
1433 ;\r
1434 NTS_Job         EQU [EBP+36]            ;Job Num for this task\r
1435 NTS_CS          EQU [EBP+32]            ;8 for OS, 18h for user task\r
1436 NTS_Pri         EQU [EBP+28]            ;Priority of this task\r
1437 NTS_fDbg        EQU [EBP+24]            ;TRUE for DEBUGing\r
1438 NTS_Exch        EQU [EBP+20]            ;Exchange for TSS\r
1439 NTS_ESP         EQU [EBP+16]            ;Initial stack pointer\r
1440 NTS_EIP         EQU [EBP+12]            ;Task start address\r
1441 \r
1442 PUBLIC __NewTask:                    ;\r
1443                 PUSH EBP                    ;\r
1444                 MOV EBP,ESP                 ;\r
1445 \r
1446         MOV EDX, NTS_Pri                        ;\r
1447                 CMP EDX, nPRI-1                         ;Priority OK?\r
1448                 JBE NT0000\r
1449                 MOV EAX,ercBadPriority\r
1450                 JMP NTEnd\r
1451 NT0000:\r
1452                 MOV ECX, NTS_Exch\r
1453         CMP ECX, nExch                          ;Exch in range?\r
1454                 JBE NT0001\r
1455                 MOV EAX,ercOutOfRange\r
1456                 JMP NTEnd\r
1457 NT0001:\r
1458                 CLI                     ;we can't be interrupted\r
1459                 MOV EAX,pFreeTSS        ; NewTSS <= pFreeTSS;\r
1460                 OR EAX,EAX              ; IF pFreeTSS=NIL THEN Return;\r
1461                 JNZ NT0002              ;\r
1462                 MOV EAX,ercNoMoreTSSs       ;No...\r
1463                 JMP NTEnd\r
1464 NT0002:\r
1465                 MOV EBX,[EAX+NextTSS]   ; pFreeTSS <= pFreeTSS^.Next\r
1466                 MOV pFreeTSS,EBX        ;\r
1467                 DEC _nTSSLeft                   ;\r
1468                 STI\r
1469 \r
1470                 ;EAX now has pNewTSS\r
1471 \r
1472                 MOV [EAX+Priority],DL       ;put Priority into TSS\r
1473                 MOV DWORD PTR [EAX+TSS_EFlags],0202h  ;Load the Flags Register\r
1474                 MOV [EAX+TSS_Exch], ECX         ;Put new Exch in TSS (ECX is free)\r
1475                 MOV EBX, NTS_EIP                        ;mov EIP into TSS (Start Address)\r
1476                 MOV [EAX+TSS_EIP],EBX\r
1477                 MOV EBX, NTS_ESP                        ;mov ESP into TSS\r
1478                 MOV [EAX+TSS_ESP],EBX\r
1479                 MOV [EAX+TSS_ESP0],EBX          ;\r
1480                 MOV ECX, NTS_CS                         ;mov CS into TSS\r
1481                 MOV [EAX+TSS_CS],CX\r
1482 \r
1483                 PUSH EAX                                        ;Save pNewTSS\r
1484 \r
1485                 ;Now we get pJCB from JobNum they passed in so we can\r
1486                 ;get the PD from the JCB\r
1487 \r
1488                 MOV EAX, NTS_Job                        ;Set up to call GetpJCB\r
1489                 CALL GetpJCB                            ;EAX now has pJCB\r
1490                 MOV ECX, EAX                            ;ECX now has pJCB\r
1491 \r
1492                 POP EAX                                         ;Restore pNewTSS to EAX\r
1493 \r
1494                 MOV [EAX+TSS_pJCB],ECX          ;Put pJCB into TSS\r
1495                 MOV EBX, [ECX+JcbPD]        ;Set up to call LinToPhy\r
1496 \r
1497                 PUSH EAX                                        ;Save pNewTSS again\r
1498 \r
1499                 MOV EAX, NTS_Job                        ;\r
1500                 CALL LinToPhy                           ;Get Physical Address for PD into EAX\r
1501                 MOV EBX, EAX\r
1502                 POP EAX                                         ;pNewTSS into EAX\r
1503                 MOV [EAX+TSS_CR3],EBX           ;Put Physical Add for PD into TSS_CR3\r
1504                 CMP DWORD PTR NTS_fDbg, 0       ;Debug on entry?\r
1505                 JE NT0004                   ;No\r
1506                 MOV WORD PTR [EAX+TSS_TrapBit], 1    ;Yes\r
1507 NT0004:\r
1508 \r
1509                 MOV EBX, NTS_Pri                        ;Get priority of new task\r
1510 \r
1511                 CLI                         ;We can't be interrupted\r
1512                 MOV EDX,pRunTSS                     ;Get who's running\r
1513                 CMP BYTE PTR [EDX+Priority],BL  ;Who got the highest Pri?\r
1514                 JA NT0005                       ;New guy does (lowest num)\r
1515                 CALL enQueueRdy             ;Just put new guy on the ReadyQue (EAX)\r
1516                 XOR EAX,EAX                 ;ercOk\r
1517                 JMP NTEnd                   ;Return to caller\r
1518 NT0005:\r
1519         XCHG EAX,EDX                ;CrntTSS -> EAX, New TSS -> EDX\r
1520         PUSH EDX                                        ;Save New TSS\r
1521                 CALL enQueueRdy             ;\r
1522                 POP EAX                                         ;New TSS -> EAX\r
1523                 MOV pRunTSS,EAX             ;Move new TSS into pRunTSS\r
1524                 MOV BX,[EAX+Tid]            ;Put Selector/Offset in "TSS"\r
1525                 MOV TSS_Sel,BX              ;\r
1526                 INC _nSwitches\r
1527                 MOV EAX, TimerTick              ;Save time of this switch for scheduler\r
1528                 MOV SwitchTick, EAX             ;\r
1529                 JMP FWORD PTR [TSS]         ;Jump to new TSS\r
1530                 XOR EAX,EAX                 ;ErcOk\r
1531 NTEnd:\r
1532                 STI                         ;\r
1533                 MOV ESP,EBP                 ;\r
1534                 POP EBP                     ;\r
1535                 RETF 28                                         ;\r
1536 \r
1537 ;====================================================================\r
1538 ; SpawnTask --- OS PUBLIC - Creates a new task in the current job\r
1539 ; and schedules it for execution\r
1540 ;\r
1541 ; Procedural Interface:\r
1542 ; SpawnTask(pEntry,     dPriority, fDebug, pStack, fOSCode);\r
1543 ;\r
1544 ;\r
1545 pEntryST        EQU DWORD PTR [EBP+28]\r
1546 dPriST          EQU DWORD PTR [EBP+24]\r
1547 fDebugST        EQU DWORD PTR [EBP+20]\r
1548 pStackST        EQU DWORD PTR [EBP+16]\r
1549 fOSCodeST       EQU DWORD PTR [EBP+12]\r
1550 \r
1551 NewExchST       EQU DWORD PTR [EBP-4]\r
1552 NewTSSST        EQU DWORD PTR [EBP-8]\r
1553 \r
1554 PUBLIC __SpawnTask:                  ;\r
1555                 PUSH EBP                    ;\r
1556                 MOV EBP,ESP                 ;\r
1557                 SUB ESP, 8                                      ;two local DWORD vars\r
1558                 CMP dPriST, nPRI-1                      ;Priority OK?\r
1559                 JBE ST0001\r
1560                 MOV EAX,ercBadPriority\r
1561                 JMP STEnd\r
1562 ST0001:\r
1563                 LEA EAX, NewExchST                      ;Allocate exchange\r
1564                 PUSH EAX\r
1565                 CALL FWORD PTR _AllocExch\r
1566                 OR EAX, EAX                                     ;see if we got an error\r
1567                 JNZ STEnd                                       ;Yup, bad news\r
1568 \r
1569                 ;Allocate a new TSS\r
1570                 CLI                     ;we can't be interrupted\r
1571                 MOV EAX,pFreeTSS        ; NewTSS <= pFreeTSS;\r
1572                 OR EAX,EAX              ; IF pFreeTSS=NIL THEN Return;\r
1573                 JNZ ST0002              ;\r
1574                 STI\r
1575 \r
1576                 ;Dealloc Exch if we didn't get a TSS\r
1577                 PUSH NewExchST\r
1578                 CALL FWORD PTR _DeAllocExch\r
1579                 MOV EAX,ercNoMoreTSSs       ;No...\r
1580                 JMP NTEnd\r
1581 ST0002:\r
1582                 MOV EBX,[EAX+NextTSS]   ; pFreeTSS <= pFreeTSS^.Next\r
1583                 MOV pFreeTSS,EBX        ;\r
1584                 DEC _nTSSLeft                   ;\r
1585                 STI\r
1586 \r
1587                 MOV NewTSSST, EAX                       ;Save new TSS\r
1588         MOV EBX, NewExchST                      ;mov exch into TSS\r
1589                 MOV [EAX+TSS_Exch],EBX\r
1590                 MOV WORD PTR [EAX+TSS_CS], OSCodeSel    ;Defaults to OS code selector\r
1591                 CMP fOSCodeST, 0\r
1592                 JNE ST0003\r
1593                 MOV WORD PTR [EAX+TSS_CS], JobCodeSel   ;Make OS code selector\r
1594 ST0003:\r
1595                 MOV EBX,pEntryST                        ;mov EIP into TSS\r
1596                 MOV [EAX+TSS_EIP],EBX\r
1597                 MOV EBX, pStackST                       ;mov ESP into TSS\r
1598                 MOV [EAX+TSS_ESP],EBX\r
1599                 MOV [EAX+TSS_ESP0],EBX\r
1600                 MOV EBX, pRunTSS\r
1601                 MOV EDX, [EBX+TSS_pJCB]         ;Get pJCB from Crnt Task\r
1602                 MOV [EAX+TSS_pJCB],EDX\r
1603                 MOV EDX, [EBX+TSS_CR3]          ;Get CR3 from crnt task\r
1604                 MOV [EAX+TSS_CR3],EDX           ; move into new TSS\r
1605                 MOV DWORD PTR [EAX+TSS_EFlags],0202h  ;Load the Flags Register\r
1606                 CMP fDebugST, 0                                         ;Debug on entry?\r
1607                 JE ST0004                               ;No\r
1608                 MOV WORD PTR [EAX+TSS_TrapBit], 1   ;Yes\r
1609 ST0004:\r
1610         MOV EBX, dPriST                         ;mov priority into BL\r
1611                 MOV [EAX+Priority],BL       ;put in TSS\r
1612 \r
1613                 CLI                         ;we can't be interrupted\r
1614                 MOV EDX,pRunTSS             ;Get who's running\r
1615                 CMP [EDX+Priority],BL       ;Who got the highest Pri?\r
1616                 JA ST0005                   ;If crnt >, New guy does (lowest num)\r
1617                 CALL enQueueRdy             ;Old guy does, just put new guy on Q.\r
1618                 XOR EAX,EAX                 ;ercOk\r
1619                 JMP STEnd                   ;Return to caller\r
1620 ST0005:\r
1621         XCHG EAX,EDX                ;CrntTSS -> EAX, New TSS -> EDX\r
1622         PUSH EDX                                        ;New TSS -> Stack\r
1623                 CALL enQueueRdy             ;Place crnt TSS on Q\r
1624                 POP EAX                                         ;New TSS -> EAX\r
1625                 MOV pRunTSS,EAX             ;Move new TSS into pRunTSS\r
1626                 MOV BX,[EAX+Tid]            ;Put Selector/Offset in "TSS"\r
1627                 MOV TSS_Sel,BX              ;\r
1628                 INC _nSwitches\r
1629                 MOV EAX, TimerTick              ;Save time of this switch for scheduler\r
1630                 MOV SwitchTick, EAX             ;\r
1631                 JMP FWORD PTR [TSS]         ;Jump to new TSS\r
1632                 XOR EAX,EAX                 ;ErcOk\r
1633 STEnd:\r
1634                 STI                         ;\r
1635                 MOV ESP,EBP                 ;\r
1636                 POP EBP                     ;\r
1637                 RETF 20                                         ;\r
1638 \r
1639 ;=============================================================================\r
1640 ;\r
1641 ; AllocExch - The kernel Allocate Exchange primitive. This procedure\r
1642 ; provides access to the operating system by allowing a TASK to\r
1643 ; allocate a message port for the transmission and reception of messages from\r
1644 ; another process.\r
1645 ;\r
1646 ; Procedural Interface :\r
1647 ;\r
1648 ;       AllocExch(pExchRet):dError\r
1649 ;\r
1650 ;          pExchRet is a pointer to where you want the Exchange Handle\r
1651 ;          returned.  The Exchange Handle is a DWORD (4 BYTES).\r
1652 ;\r
1653 ;=============================================================================\r
1654 \r
1655 PUBLIC __AllocExch:              ;\r
1656                 PUSH EBP                ;\r
1657                 MOV EBP,ESP             ;\r
1658 \r
1659                 XOR ESI,ESI             ; Zero the Exch Index\r
1660                 MOV EBX,prgExch         ; EBX <= ADR rgExch\r
1661                 MOV ECX,nExch           ; Get number of exchanges in ECX\r
1662 AE000:\r
1663                 CLI                                     ;\r
1664                 CMP DWORD PTR [EBX+Owner], 0    ; Is this exchange free to use\r
1665                 JE AE001                                ; If we found a Free Exch, JUMP\r
1666                 ADD EBX,sEXCH           ; Point to the next Exchange\r
1667                 INC ESI                 ; Increment the Exchange Index\r
1668                 LOOP AE000              ; Keep looping until we are done\r
1669                 STI                     ;\r
1670                 MOV EAX,ercNoMoreExch   ; There are no instances of the Exch\r
1671                 MOV ESP,EBP             ;\r
1672                 POP EBP                 ;\r
1673                 RETF 4                  ;\r
1674 \r
1675 AE001:\r
1676                 MOV EDX,[EBP+0CH]       ; Get the pExchRet in EDX\r
1677                 MOV [EDX],ESI                   ; Put Index of Exch at pExchRet\r
1678                 MOV EDX,pRunTSS         ; Get pRunTSS in EDX\r
1679                 MOV EAX,[EDX+TSS_pJCB]  ; Get the pJCB in EAX\r
1680                 MOV [EBX+Owner],EAX     ; Make the Exch owner the Job\r
1681                 STI                     ;\r
1682                 MOV DWORD PTR [EBX+EHead],0     ; Make the msg/TSS queue NIL\r
1683                 MOV DWORD PTR [EBX+ETail],0     ;\r
1684                 DEC _nEXCHLeft                                  ; Stats\r
1685                 XOR EAX,EAX             ;ercOK (0)\r
1686                 MOV ESP,EBP             ;\r
1687                 POP EBP                 ;\r
1688                 RETF 4                  ;\r
1689 \r
1690 ;=============================================================================\r
1691 ;\r
1692 ; DeAllocExch - The kernel DeAllocate Exchange primitive. It allows a TASK\r
1693 ; to deallocate a "message port."  It also deQueues any messages, and frees\r
1694 ; up any Link Blocks, TSSs, and RQBs, attached to the exchange\r
1695 ;\r
1696 ; Procedural Interface :\r
1697 ;\r
1698 ;       DeAllocExch(Exch):ercType\r
1699 ;\r
1700 ;           Exch is the Exchange Handle the process is asking to be released.\r
1701 \r
1702 PUBLIC __DeAllocExch:                 ;\r
1703                 PUSH EBP                ;\r
1704                 MOV EBP,ESP             ;\r
1705 \r
1706                 MOV ESI,[EBP+0CH]       ; Load the Exchange Index in ESI\r
1707                 MOV EAX,ESI             ; Get the Exchange Index in EAX\r
1708                 MOV EDX,sEXCH           ; Compute offset of Exch in rgExch\r
1709                 MUL EDX                 ;\r
1710                 MOV EDX,prgExch         ; Add offset of rgExch => EAX\r
1711                 ADD EAX,EDX             ;\r
1712                 MOV ECX,EAX             ; Make a copy in ECX (ECX = pExch)\r
1713 \r
1714                 MOV EDX,pRunTSS         ; Get the pRunTSS in EDX\r
1715                 MOV EBX,[EDX+TSS_pJCB]  ; Get pJCB in EBX\r
1716                 MOV EDX,[EAX+Owner]     ; Get the Exchange Owner in EDX\r
1717                 CMP EBX,EDX             ; If the CurrProc owns the Exchange,\r
1718                 JE DE000                ; yes\r
1719                 CMP EBX, OFFSET MonJCB  ; if not owner, is this the OS???\r
1720                 JE DE000                ; yes\r
1721                 MOV EAX,ercNotOwner     ;\r
1722                 MOV ESP,EBP             ;\r
1723                 POP EBP                 ;\r
1724                 RETF 4                  ;\r
1725 \r
1726 DE000:\r
1727                 CLI                     ;\r
1728                 CMP DWORD PTR [ECX+fEMsg],0 ; See if a message may be queued\r
1729                 JE DE001                        ; No. Go check for Task (TSS)\r
1730                 MOV ESI, ECX                            ; ESI must point to Exch for deQueue\r
1731                 CALL deQueueMsg         ; Yes, Get the message off of the Exchange\r
1732                 OR EAX, EAX\r
1733                 JZ DE002                                ; Nothing there. Go free the Exch.\r
1734 \r
1735                 ;Return the LB to the pool\r
1736                 MOV EBX,pFreeLB         ; pLBin^.Next <= pFreeLB;\r
1737                 MOV [EAX+NextLB],EBX    ;\r
1738                 MOV pFreeLB,EAX         ; pFreeLB <= pLBin;\r
1739                 INC _nLBLeft                    ;\r
1740                 JMP DE000               ; Go And Check for more.\r
1741 \r
1742                 ; If we find an RqBlk on the exchange we must respond\r
1743                 ;with ErcInvalidExch before we continue! This will\r
1744                 ;only happen if a system service writer doesn't follow\r
1745                 ;instructions or a service crashes!\r
1746                 ;\r
1747 DE001:\r
1748                 CMP DWORD PTR [ECX+EHead], 0    ; Check to See if TSS is queued\r
1749                 JE DE002                ; NIL = Empty, JUMP\r
1750                 MOV ESI, ECX                    ; ESI must point to Exch for deQueue\r
1751                 CALL deQueueTSS         ; Get the TSS off of the Exchange\r
1752 \r
1753                 ;Free up the TSS (add it to the free list)\r
1754                 MOV EBX,pFreeTSS        ; pTSSin^.Next <= pFreeTSS;\r
1755                 MOV [EAX+NextTSS],EBX                   ;\r
1756                 MOV DWORD PTR [EAX+TSS_pJCB], 0 ; Make TSS invalid\r
1757                 MOV pFreeTSS,EAX                        ; pFreeTSS <= pTSSin;\r
1758                 INC _nTSSLeft                   ;\r
1759 \r
1760                 JMP DE001               ; Go And Check for more.\r
1761 DE002:\r
1762                 MOV DWORD PTR [ECX+Owner], 0     ; Free up the exchange.\r
1763                 MOV DWORD PTR [ECX+fEMsg], 0     ; Reset msg Flag.\r
1764                 INC _nEXCHLeft                  ; Stats\r
1765                 STI                     ;\r
1766                 XOR EAX,EAX             ;ercOK (0)\r
1767                 MOV ESP,EBP             ;\r
1768                 POP EBP                 ;\r
1769                 RETF 4                  ;\r
1770 \r
1771 ;=============================================================================\r
1772 ;\r
1773 ; GetTSSExch - This returns the Exchange of the current TSS to the\r
1774 ; caller.  This is primarily provided for System Services that provide\r
1775 ; direct access blocking calls for customers.\r
1776 ;\r
1777 ; Procedural Interface :\r
1778 ;\r
1779 ;       GetTSSExch(pExchRet):dError\r
1780 ;\r
1781 ;          pExchRet is a pointer to where you want the Exchange Handle\r
1782 ;          returned.  The Exchange is a DWORD (4 BYTES).\r
1783 ;\r
1784 PUBLIC __GetTSSExch:            ;\r
1785                 PUSH EBP                ;\r
1786                 MOV EBP,ESP             ;\r
1787                 MOV EAX,pRunTSS                 ; Get the Ptr To the Running TSS\r
1788                 MOV ESI,[EBP+0CH]       ; Get the pExchRet in EDX\r
1789                 MOV EBX, [EAX+TSS_Exch] ; Get Exch in EBX\r
1790                 MOV [ESI],EBX                   ; Put Index of Exch at pExchRet\r
1791                 XOR EAX, EAX            ; ErcOK\r
1792                 POP EBP                 ;\r
1793                 RETF 4                  ;\r
1794 \r
1795 ;=============================================================================\r
1796 ;\r
1797 ; SetPriority - This sets the priority of the task that called it\r
1798 ; to the priority specified in the single parameter.\r
1799 ;\r
1800 ; Procedural Interface :\r
1801 ;\r
1802 ;       SetPriority(bPriority):dError\r
1803 ;\r
1804 ;          bPriority is a byte with the new priority.\r
1805 ;\r
1806 PUBLIC __SetPriority            ;\r
1807                 PUSH EBP                ;\r
1808                 MOV EBP,ESP             ;\r
1809                 MOV EAX,pRunTSS                 ; Get the Ptr To the Running TSS\r
1810                 MOV EBX,[EBP+0CH]       ; Get the new pri into EBX\r
1811                 AND EBX, 01Fh                   ; Nothing higher than 31!\r
1812                 MOV BYTE PTR [EAX+Priority], BL ;Put it in the TSS\r
1813                 XOR EAX, EAX            ; ErcOK - No error.\r
1814                 POP EBP                 ;\r
1815                 RETF 4                  ;\r
1816 \r
1817 ;=============================================================================\r
1818 ;\r
1819 ; GetPriority - This gets the priority of the task that called it\r
1820 ; and passes it to bPriorityRet.\r
1821 ;\r
1822 ; Procedural Interface :\r
1823 ;\r
1824 ;       SetPriority(bPriorityRet):dError\r
1825 ;\r
1826 ;          bPriorityret is a pointer to a byte where you want the\r
1827 ;             priority returned.\r
1828 ;\r
1829 PUBLIC __GetPriority            ;\r
1830                 PUSH EBP                ;\r
1831                 MOV EBP,ESP             ;\r
1832                 MOV EAX,pRunTSS                 ; Get the Ptr To the Running TSS\r
1833                 MOV EBX,[EBP+0CH]       ; Get the return pointer into EBX\r
1834                 MOV DL, BYTE PTR [EAX+Priority]\r
1835                 MOV BYTE PTR [EBX], DL  ;\r
1836                 XOR EAX, EAX            ; ErcOK - No error.\r
1837                 POP EBP                 ;\r
1838                 RETF 4                  ;\r
1839 \r
1840 ;======================== End of Module ======================\r