⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 kernel.inc

📁 MMURTL(tm) Computer Operating System Ver x0.8, source code.
💻 INC
📖 第 1 页 / 共 4 页
字号:
;   MMURTL Operating System Source Code
;   Copyright 1991,1992,1993, Richard A. Burgess
;   ALL RIGHTS RESERVED
;   Version x0.8

;This file contains all the internal kernel functions plus
;the PUBLIC kernel functions SendMsg, ISendMsg, WaitMsg, CheckMsg,
;Request, Respond, MoveMsg, NewTask and SpawnTask.
;Exchange management functions such as AllocExch and DeAllocExch are
;also included here.
;
; NOTE on interrupts and the kernel primitives:
; Because certain kernel functions may be called from ISRs,
; and because portions of other kernel functions may be
; interrupted by a task change that happens because of an action
; that an ISR takes, we must ensure that interrupts are
; DISABLED prior to the allocation or deallocation
; of most kernel resources. This especially applies when
; a message is "in transit."  For example: taken from an exchange
; but not yet linked to a TSS and placed on the ready queue.
;
; NOTE on Exchanges, Messages, and Tasks (TSSs)
; In MMURTL, an exchange is a place where either Messages or
; Tasks wait.  There can never be tasks AND messages at an
; exchange at the same time (unless the kernel is BROKEN!).
; For this reason we share the HEAD and TAIL link pointers
; for tasks and messages in an exchange.
;
;=============================================================================

enQueueMsg:
;
; INPUT : ESI,EAX
; OUTPUT : NONE
; REGISTERS : EAX,EDX,ESI,FLAGS
; MODIFIES : EDX
;
; This routine will place the link block pointed to by EAX onto the exchange
; pointed to by the ESI register. If EAX is NIL then the routine returns.
;
		CMP EAX,NIL             ; if pLBin = NIL THEN Return;
		JE eqMsgDone            ;
		MOV [EAX.NextLB],NIL    ; pLBin^.Next <= NIL;
		XCHG ESI,EAX            ; pExch => EAX, pLBin => ESI
		CMP [EAX.EHead],NIL     ; if ..MsgHead = NIL
		JNE eqMNotNIL           ; then
		MOV [EAX.EHead],ESI     ;  ..MsgHead <= pLBin;
		MOV [EAX.ETail],ESI     ;  ..MsgTail <= pLBin;
		MOV [EAX.fEMsg], 1		; Flag it as a Msg (vice a task)
		XCHG EAX,ESI            ; Put pExch Back in ESI
		RETN                    ; else
eqMNotNIL:
	    MOV EDX,[EAX.ETail]     ;  ..MsgTail^.NextLB <= pLBin;
		MOV [EDX.NextLB],ESI    ;
		MOV [EAX.ETail],ESI     ;  ..MsgTail <= pLBin;
		MOV [EAX.fEMsg], 1		; Flag it as a Msg (vice a task)
		XCHG EAX,ESI            ; Put pExch Back in ESI
eqMsgDone:
	    RETN                    ;

;=============================================================================

deQueueMsg:
;
; INPUT : ESI
; OUTPUT : EAX
; REGISTERS : EAX,EBX,ESI,FLAGS
; MODIFIES : *prgExch[ESI].msg.head and EBX
;
; This routine will dequeue a link block on the exchange pointed to by the
; ESI register and place the pointer to the link block dequeued into EAX.
;
		MOV EAX,[ESI.fEMsg]     ; Get Msg Flag
		OR EAX, EAX				; Is it a Msg?
		JZ deMsgDone			; No! (return 0)
		MOV EAX,[ESI.EHead]     ; pLBout <= ..MsgHead;
		OR EAX, EAX             ; if pLBout = NIL then Return;
		JZ deMsgDone            ;
		MOV EBX,[EAX.NextLB]    ; ..MsgHead <= ..MsgHead^.Next;
		MOV [ESI.EHead],EBX     ;
deMsgDone:
	    RETN                    ;

;=============================================================================

deQueueTSS:
;
; INPUT : ESI
; OUTPUT : EAX
; REGISTERS : EAX,EBX,ESI,FLAGS
; MODIFIES : EAX,EBX
;
; This routine will dequeue a TSS on the exchange pointed to by the ESI
; register and place the pointer to the TSS dequeued into EAX.
; EAX return NIL if no TSS is waiting at Exch ESI
;
		XOR EAX,EAX				; Set up to return nothing
		MOV EBX,[ESI.fEMsg]		; Msg flag (is it a Msg)
		OR EBX, EBX
		JNZ deTSSDone			; It's a Msg (return leaving EAX 0)
		MOV EAX,[ESI.EHead] 	; pTSSout <= ..TSSHead;
		OR EAX, EAX           	; if pTSSout = NIL then Return;
		JZ deTSSDone           	;
		MOV EBX,[EAX.NextTSS]  	; ..TSSHead <= ..TSSHead^.Next;
		MOV [ESI.EHead],EBX  	;
deTSSDone:
	    RETN                    	;

;=============================================================================

enQueueRdy:
;
; INPUT : EAX
; OUTPUT : NONE
; REGISTERS : EAX,EBX,EDX,FLAGS
; MODIFIES : EAX,EBX,EDX
;
; This routine will place a TSS pointed to by EAX onto the ReadyQueue. This
; algorithm chooses the proper priority queue based on the TSS priority.
; The Rdy Queue is an array of QUEUES (2 pointers, head & tail per QUEUE).
; This links the TSS to rgQueue[nPRI].
;
		CMP EAX,NIL             ; if pTSS = NIL then return;
		JE eqRdyDone            ;
		MOV [EAX.NextTSS],NIL   ; pTSSin^.Next <= NIL;
		XOR EBX,EBX             ; get the priority
		MOV BL,[EAX.Priority]   ; in EBX
		XCHG EAX,EBX            ; Priority => EAX, pTSSin => EBX
		SHL EAX, 3              ; Times 8 (size of QUEUE)
		LEA EDX,RdyQ            ; Add offset of RdyQ => EAX
		ADD EAX,EDX             ; EAX pts to proper Rdy Queue
		CMP [EAX.Head],NIL      ; if Head = NIL
		JNE eqRNotNIL           ; then
		MOV [EAX.Head],EBX      ;  ..Head <= pTSSin;
		MOV [EAX.Tail],EBX      ;  ..Tail <= pTSSin;
		RETN                    ; else
eqRNotNIL:
	    MOV EDX,[EAX.Tail]      ;  ..Tail^.NextTSS <= pTSSin;
		MOV [EDX.NextTSS],EBX   ;
		MOV [EAX.Tail],EBX      ;  ..Tail <= pTSSin;
eqRdyDone:
	    RETN                    ;

;=============================================================================

deQueueRdy:
;
; INPUT : NONE
; OUTPUT : EAX
; REGISTERS : EAX,EBX,ECX,FLAGS
; MODIFIES : RdyQ
;
; This routine will return a pointer in EAX to the highest priority task
; queued on the RdyQ. Then the routine will "pop" the TSS from the RdyQ.
; If there was no high priority process, EAX is returned as NIL.
;
		MOV ECX,nPRI            ; Set up the number of times to loop
		LEA EBX,RdyQ            ; Get base address of RdyQ in EBX
deRdyLoop:
	    MOV EAX,[EBX.Head]      ; Get pTSSout in EAX
		CMP EAX,NIL             ; IF pTSSout is NIL Then go and
		JNE deRdyFound          ; check the next priority
		ADD EBX,sQUEUE          ; Point to the next Priority Queue
		LOOP deRdyLoop          ; DEC ECX and LOOP IF NOT ZERO
deRdyFound:
		CMP EAX,NIL             ; IF pTSSout is NIL Then there are
		JE deRdyDone            ; No TSSs on the RdyQ; RETURN
		MOV ECX,[EAX.NextTSS]   ; Otherwise, deQueue the process
		MOV [EBX.Head],ECX      ; And return with the pointer in EAX
deRdyDone:
	    RETN                    ;

;=============================================================================
;================= BEGIN NEAR KERNEL HELPER ROUTINES =========================
;=============================================================================

; RemoveRdyJob  (NEAR)
;
; This routine searchs all ready queue priorities for tasks belonging
; to pJCB. When one is found it is removed from the queue
; and the TSS is freed up.
;
; Procedureal Interface :
;
;		RemoveRdyJob(char *pJCB):ercType
;
;	pJCB is a pointer to the JCB that the tasks to kill belong to.
;
; pJCB		 	EQU DWORD PTR [EBP+8]
;
; INPUT :  (pJCB on stack)
; OUTPUT : NONE
; REGISTERS : All general registers are trashed
; MODIFIES : RdyQ
;
;
_RemoveRdyJob PROC NEAR
;
		PUSH EBP                ;
		MOV EBP,ESP             ;
		MOV ECX,nPRI            ; Set up the number of times to loop
		LEA EBX,RdyQ            ; Get base address of RdyQ in EBX

		;EBX points to begining of next Priority Queue
RemRdyLoop:
	    MOV EAX,[EBX.Head]      ; Get pTSS in EAX
		MOV EDI, EAX			; EDI points to last TSS by default (or NIL)
		CMP EAX,NIL             ; Is pTSS 0 (none left queued here)
		JNE RemRdy0		        ; Valid pTSS!
RemRdyLoop1:
		MOV [EBX.Tail], EDI		; EDI always points to last TSS or NIL
		ADD EBX,sQUEUE          ; Point to the next Priority Queue
		LOOP RemRdyLoop         ; DEC ECX and LOOP IF NOT ZERO

		XOR EAX, EAX			; No error
		POP EBP
		RETN 4					; All done (clean stack)

		;Go here to dequeue a TSS at head of list
RemRdy0:
		CMP EDX, [EAX.TSS_pJCB]	; Is this from the JCB we want?
		JNE RemRdy2				; No

		MOV EDI, [EAX.NextTSS]  ; Yes, deQueue the TSS
		MOV [EBX.Head], EDI     ; Fix link in Queue list

		PUSH EBX				; Save ptr to RdyQue (crnt priority)

		;Free up the TSS (add it to the free list)
		MOV EBX,pFreeTSS        ; pTSSin^.Next <= pFreeTSS;
		MOV [EAX.NextTSS],EBX   ;
		MOV [EAX.TSS_pJCB], 0	; Make TSS invalid
		MOV pFreeTSS,EAX        ; pFreeTSS <= pTSSin;
		INC _nTSSLeft			;

		POP EBX
		MOV EAX, EDI 		    ; Make EAX point to new head TSS
		OR EAX, EAX				; Is it Zero?
		JZ RemRdyLoop1			; Next Queue please
		JMP RemRdy0				; back to check next at head of list

		;Go here to dequeue a TSS in middle or end of list
RemRdy2:
		MOV EAX, [EDI.NextTSS]	; Get next link in list
		OR EAX, EAX				; Valid pTSS?
		JZ RemRdyLoop1			; No. Next Queue please
		CMP EDX, [EAX.TSS_pJCB]	; Is this from JCB we want?
		JE RemRdy3				; Yes. Trash it.
		MOV	EDI, EAX			; No. Next TSS
		JMP RemRdy2
RemRdy3:
		;EDI points to prev TSS
		;EAX points to crnt TSS
		;Make ESI point to NextTSS

		MOV ESI, [EAX.NextTSS]  ; Yes, deQueue the TSS

		;Now we fix the list (Make Prev point to Next)
		;This extracts EAX from the list

		MOV [EDI.NextTSS], ESI	;Jump the removed link
		PUSH EBX				;Save ptr to RdyQue (crnt priority)

		;Free up the TSS (add it to the free list)
		MOV EBX,pFreeTSS        ; pTSSin^.Next <= pFreeTSS;
		MOV [EAX.NextTSS],EBX   ;
		MOV [EAX.TSS_pJCB], 0	; Make TSS invalid
		MOV pFreeTSS,EAX        ; pFreeTSS <= pTSSin;
		INC _nTSSLeft			;

		POP EBX
		;
		OR  ESI, ESI			;Is EDI the new Tail? (ESI = 0)
		JZ  RemRdyLoop1			;Yes. Next Queue please
		JMP RemRdy2				;back to check next TSS

_RemoveRdyJob ENDP

;=============================================================================
; GetExchOwner  (NEAR)
;
; This routine returns the owner of the exchange specified.
; A pointer to the JCB of the owner is returned.
; ErcNotAlloc is returned if the exchange isn't allocated.
; ErcOutofRange is returned is the exchange number is invalid (too high)
;
; Procedureal Interface :
;
;		GetExchOwner(long Exch, char *pJCBRet): dErrror
;
;	Exch is the exchange number.
;	pJCBRet is a pointer to the JCB that the tasks to kill belong to.
;
; Exch	 	EQU DWORD PTR [EBP+12]
; pJCBRet 	EQU DWORD PTR [EBP+8]

_GetExchOwner PROC NEAR         ;
		PUSH EBP                ;
		MOV EBP,ESP             ;

		MOV EAX, [EBP+12]		; Get Resp Exchange in EDX
		CMP EAX,nExch           ; Is the exchange out of range?
		JB GEO01	            ; No, continue
		MOV EAX,ErcOutOfRange   ; Yes, Error in EAX register
		JMP GEOEnd				;
GEO01:
		MOV EDX,sEXCH           ; Compute offset of Exch in rgExch
		MUL EDX                 ; sExch * Exch number
		MOV EDX,prgExch         ; Add offset of rgExch => EAX
		ADD EDX,EAX             ; EDX -> Exch
		MOV EAX, [EDX.Owner]
		OR EAX, EAX				; Valid Exch (Allocated)
		JNZ GEO02
		MOV EAX, ErcNotAlloc	; No, not allocated
		JMP SHORT GEOEnd
GEO02:
		MOV ESI, [EBP+8]		;Where to return pJCB of Exchange
		MOV [ESI], EAX			;
		XOR EAX, EAX
GEOEnd:
		MOV ESP,EBP             ;
		POP EBP                 ;
		RETN 8                  ;
_GetExchOwner  ENDP

;=============================================================================
; SetExchOwner  (NEAR)
;
; This routine sets the owner of the exchange specified to the
; pJCB specified. This is used by the Job code to set the owner of
; a TSS exchange to a new JCB (even though the exchange was allocated
; by the OS).  No error checking is done as the job code does it upfront!
;
; Procedureal Interface :
;
;		SetExchOwner(long Exch, char *pNewJCB): dErrror
;
;	Exch is the exchange number.
;	pNewJCB is a pointer to the JCB of the new owner.
;
; Exch	 	EQU DWORD PTR [EBP+12]
; pNewJCB 	EQU DWORD PTR [EBP+8]

_SetExchOwner PROC NEAR         ;
		PUSH EBP                ;
		MOV EBP,ESP             ;
		MOV EAX, [EBP+12]		; Exchange Number
		MOV EDX,sEXCH           ; Compute offset of Exch in rgExch
		MUL EDX                 ; sExch * Exch number
		MOV EDX,prgExch         ; Add offset of rgExch => EAX
		ADD EAX,EDX             ; EAX -> oExch + prgExch
		MOV EBX, [EBP+8]
		MOV [EAX.Owner], EBX
		XOR EAX, EAX
		POP EBP                 ;
		RETN 8                  ;
_SetExchOwner  ENDP

;=============================================================================
; SendAbort  (NEAR)
;
; This routine sends one abort message to each valid service
; with the jobnum of the aborting job. If we receive a
; kernel error on Request it may be becuase it is a service
; that is aborting itself. We ignore the kernel errors.
;
; Procedureal Interface :
;
;		SendAbort(long JobNum, ValidExch): dErrror
;
;	JobNum is the job that is aborting
;	ValidExch is any valid exchange so the request will go through
;
; JobNum 	EQU DWORD PTR [EBP+12]
; ValidExch	EQU DWORD PTR [EBP+8]

_SendAbort PROC NEAR            ;
		PUSH EBP                ;
		MOV EBP,ESP             ;

		MOV ESI,OFFSET rgSVC	; Get the address of rgSVC
		MOV ECX,nSVC			; Get the number of Service Descriptors
SAB01:
		CMP DWORD PTR [ESI], 0	; Valid name?
		JE SAB05				; NO, next service

		PUSH ESI				;Save count and pointer to SVC name
		PUSH ECX

		;Push all the params to make the request
		PUSH ESI				;pName
		PUSH 0					;Abort Service Code
		MOV EAX, [EBP+8]		;Exchange
		PUSH EAX
		PUSH OFFSET dJunk		;pHandleRet
		PUSH 0					;npSend
		PUSH 0					;pData0
		PUSH 0					;cbData0
		PUSH 0					;pData1
		PUSH 0					;cbData1
		MOV EAX, [EBP+12]		;JobNum
		PUSH EAX				;dData0
		PUSH 0					;dData1
		PUSH 0					;dData2
		CALL FAR PTR _Request

		POP ECX
		POP ESI
SAB05:
		ADD ESI, sSVC			;Next Service name
		LOOP SAB01
		XOR EAX, EAX
		MOV ESP,EBP             ;
		POP EBP                 ;
		RETN 8                  ;
_SendAbort  ENDP



⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -