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

📄 jobcode.inc

📁 MMURTL(tm) Computer Operating System Ver x0.8, source code.
💻 INC
字号:
;   MMURTL Operating System Source Code
;   Copyright 1991,1992,1993, Richard A. Burgess
;   ALL RIGHTS RESERVED
;   Version x0.8
;=============================================================================
;InitNewJCB is used initially by the OS to fill in the first two
;jobs (Monitor & Debugger)
;
InitNewJCB:
; INPUT :	EAX -- Ptr to JCB that is to be filled in
;			EBX -- Linear Ptr to Page Directory for Job
;			ESI -- pbJobName
;			ECX -- cbJobName
;			EDX -- Pointer to Job Virtual Video Buffer (all jobs have one!)
;
; OUTPUT :	JOB Number in EAX
; USED : 	EAX, EBX, ECX, EDX, EDI, ESI, EFlags
; MODIFIES : JCB pointed to in EBX
;
; This fills in a JCB with new information.  This is used to initilaize
; a new JCB during OS init and when a new Job is loaded and run.
;
		MOV [EAX.JcbPD],EBX	    ;Put Ptr to PD into JCB
		MOV EDI, EAX			;EDI points to JCB
		ADD EDI, sbJobName		;Now to JobName
		MOV BYTE PTR [EDI], CL	;size is filled in
		INC EDI					;first byte of name
		REP MOVSB				;Move it in
		MOV [EAX.pVirtVid], EDX	;Video number is in JCB
		MOV EAX, [EAX.JobNum]
		RETN

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

NewJCB:
; INPUT : NONE
; OUTPUT : EAX
; REGISTERS : EAX,EBX,FLAGS
; MODIFIES : pFreeJCB
;
; This routine will return to the caller a pointer to the next free jcb.
; The data used in this algorithm is the free jcb pointer (pFreeJCB).
; This routine will return in EAX register the address of the next free jcb.
; If none exists, then EAX will contain NIL (0). This routine will also
; update the value of pFreeJCB to point to the next "unused" JCB in
; the free pool.
;
		MOV EAX,pFreeJCB        ;Get OS pointer to JCBs
		CMP EAX,NIL             ;IF pFreeJCB=NIL THEN Return;
		JE NewJCBDone           ;
		MOV EBX,[EAX.NextJCB]   ;Get pointer to next free one
		MOV pFreeJCB,EBX        ;Put it in OS pointer
		DEC _nJCBLeft			;
NewJCBDone:
	    RETN                    ;

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

DisposeJCB:
; INPUT : EAX
; OUTPUT : NONE
; REGISTERS : EBX,FLAGS
; MODIFIES : pFreeJCB
;
; This routine will place the jcb pointed to by EAX back into the free
; pool of JCBs pointed to by (pFreeJCB) if EAX is not NIL.
; This invalidates the JCB by placing 0 in JcbPD.
;
		CMP EAX,NIL             ; If pJCBin = NIL THEN Return;
		JE DispJCBDone          ;
		MOV [EAX.JcbPD], 0		;Invalidate JCB
		MOV EBX,pFreeJCB        ;EBX has OS ptr to free list
		MOV [EAX.NextJCB],EBX   ;Move it into newly freed JCB
		MOV pFreeJCB,EAX        ;Move ptr to newly frred JCB to OS
		INC _nJCBLeft			;
DispJCBDone:
	    RETN                    ;

;============================================================
;
; GetpCrntJCB
; Returns a pointer to the current Job Control Block in EAX.
; This is based on which Task is executing.  All TSSs are
; assigned to a Job.  A Job may have more than one Task.
;
; INPUT:	Nothing
; OUTPUT:	EAX -- Linear Address of current JCB
; USED:		EAX, EFlags
;
GetpCrntJCB:
		MOV EAX, pRunTSS		;Current Task State Segment
		MOV EAX, [EAX.TSS_pJCB]	;Pointer to JCB
		RETN

;============================================================
;
; GetCrntJobNum
; Many OS functions deal with the Job number. The Job number
; is a field in the JCB structure.
; Returns the Job number for the currently executing task.
; This is based on which Task is executing.  All TSSs are
; assigned to a Job!  A Job may have more than one Task.
;
; INPUT:	Nothing
; OUTPUT:	EAX -- Current Job Number
; USED:		EAX, EFlags
;
GetCrntJobNum:
		CALL GetpCrntJCB
		MOV EAX, [EAX.JobNum]			;Current JCB
		RETN

;============================================================
;
; GetpJCB
; Returns a pointer to a Job Control Block identified by number
; in EAX.  All TSSs are assigned to a Job.
;
; INPUT:	EAX -- Job Number of desired pJCB
; OUTPUT:	EAX -- Linear Address of the JCB or 0 for invalid number
; USED:		EAX, EFlags
;
GetpJCB:
		PUSH EDX
		CMP EAX, 1
		JNE GetpJCB1
		MOV EAX, OFFSET	MonJCB
		POP EDX
		RETN
GetpJCB1:
		CMP EAX, 2
		JNE GetpJCB2
		MOV EAX, OFFSET	DbgJCB
		POP EDX
		RETN
GetpJCB2:
		CMP	EAX, nJCBs+2		;Add in two static JCBs
		JLE GetpJCB3			;Within range of JCBs
		XOR EAX, EAX
		POP EDX
		RETN
GetpJCB3:
		SUB EAX, 3				;Take off static JCBs+1 (make it an offset)
		MOV EDX, sJCB
		MUL EDX					;Times size of JCB
		ADD EAX, pJCBs			;Now points to desired JCB
		POP EDX
		RETN					;

;============================================================
;
; GetJobNum
; Many OS functions deal with the Job number. The Job number
; is a field in the JCB structure.
; Returns the Job number for the pJCB in EAX in EAX.
;
; INPUT:	EAX pJCB we want job number from.
; OUTPUT:	EAX -- Current Job Number
; USED:		EAX, EFlags
;
GetJobNum:
		MOV EAX, [EAX.JobNum]			;Current JCB
		RETN

;============================================================
;
; AllocJCB  (NEAR)
; This allocates a new JCB (from the pool).  This is a NEAR
; call to support the public job management calls in high level
; languages.
;
; Procedureal Interface :
;
;		AllocJCB(pdJobNumRet, ppJCBRet):ercType
;
;   pdJobNumRet is the number of the new JCB.
;	pJCBRet is a pointer where you want the pointer to the new JCB is returned.
;
;   ErcNoMoreJCBs will be returned if no more JCBs are avaialble.
;
; pdJobNum		 	EQU [EBP+12]
; pJCBRet		 	EQU [EBP+8]

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

		CALL NewJCB				; Get a new JCB
		OR EAX, EAX				;
		JNZ SHORT AJCB01		; We got one!
		MOV EAX, ErcNoMoreJCBs	; Sorry, out of them!
		MOV ESP,EBP             ;
		POP EBP                 ;
		RETN 8	                ;

AJCB01:
		MOV ESI, [EBP+8]		;pJCBRet
		MOV [ESI], EAX
		MOV ESI, [EBP+12]		;Job Num
		CALL GetJobNum			;
		MOV [ESI], EAX			;
		XOR EAX, EAX			;No error
		MOV ESP,EBP             ;
		POP EBP                 ;
		RETN 8	                ;
_AllocJCB ENDP

;============================================================
;
; DeAllocJCB  (NEAR)
; This Deallocates a JCB (returns it to the pool).  This is a NEAR
; call to support the public job management calls in high level
; languages in the OS code.
;
; Procedureal Interface :
;
;		DeAllocJCB(pJCB):ercType
;
;	pJCB is a pointer the JCB to be deallocated.
;
;   ErcNoMoreJCBs will be returned if no more JCBs are avaialble.
;
; pJCB		 	EQU [EBP+8]

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

		MOV EAX, [EBP+8]		; pJCB
		CALL DisposeJCB			; Get a new JCB
		XOR EAX, EAX			;
		MOV ESP,EBP             ;
		POP EBP                 ;
		RETN 4	                ;
_DeAllocJCB ENDP

;============================================================
;===== BEGIN PUBLIC JOB CALLS ===============================
;============================================================
;
; GetpJCB
; This PUBLIC returns a pointer to the JCB for the JobNum
; you specifiy.
;
; Procedureal Interface :
;
;		GetpJCB(dJobNum, pJCBRet):ercType
;
;   dJobNum is the number of the JCB you want.
;	pJCBRet is a pointer where you want the JCB returned.
;
;   ErcBadJobNum will be returned if dJobNum is out of range
;
;   ErcBadJobNum will be returned if dJobNum is invalid
;   or 0 will be returned with the data.
;
; dJobNum		 	EQU [EBP+16]
; pJCBRet		 	EQU [EBP+12]

_GetpJCB PROC FAR            	;
		PUSH EBP                ;
		MOV EBP,ESP             ;

		MOV EAX, [EBP+16]		;Job Num
		OR EAX, EAX
		JZ GetpJcbBad			;0 is invalid
		CMP EAX, nJCBs + 2;		;Dynamic + 2 static
		JBE GetpJcbOK
GetpJcbBad:
		MOV EAX, ErcBadJobNum	;
		MOV ESP,EBP             ;
		POP EBP                 ;
		RETF 8	                ;
GetpJcbOk:
		CALL GetpJCB			;puts address of JCB in EAX
		MOV ESI, [EBP+12]		;pJCBRet
		MOV [ESI], EAX
		CMP [EAX.JcbPD], 0		;Is this a valid JCB
		JNE GetpJCBOk1
        MOV EAX, ErcInvalidJCB	;JCB we are pointing to is unused
		MOV ESP,EBP             ;
		POP EBP                 ;
		RETF 8	                ;
GetpJcbOk1:
		XOR EAX, EAX
		MOV ESP,EBP             ;
		POP EBP                 ;
		RETF 8	                ;
_GetpJCB ENDP

;============================================================
;
; GetJobNum
; This PUBLIC returns the number for the current Job. This is
; the job that the task that called this belongs to.
;
; Procedureal Interface :
;
;		GetJobNum(pJobNumRet):ercType
;
;	pJCBRet is a pointer where you want the JCB returned.
;
; pJobNumRet	EQU [EBP+12]

_GetJobNum PROC FAR            	;
		PUSH EBP                ;
		MOV EBP,ESP             ;
        CALL GetCrntJobNum		;Leave jobnum in EAX
		MOV ESI, [EBP+12]		;pJobNumRet
		MOV [ESI], EAX			;
		XOR EAX, EAX			;No Error
		POP EBP                 ;
		RETF 4	                ;
_GetJobNum ENDP


;================= MODULE END =================================

⌨️ 快捷键说明

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