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

📄 initcode.inc

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

;=============================================================================
;The following code	initializes structures and hardware just after bootup
;THIS CODE MUST BE LAST IN OS CODE SEG. THE MEMORY IT OCCUPIES WILL BE
;DEALLOCATED AFTER INITIALIZATION IF IT IS CONTAINED IN A SEPARATE PAGE.
;=============================================================================
InitFreeLB:
;
; INPUT : ECX,EDX
; OUTPUT : NONE
; REGISTERS : EAX,EBX,ECX,FLAGS
; MODIFIES : pFreeLB,rgLBs
;
; This routine will initialize a free pool of link blocks.
; The data used in this algorithm are an array of ECX link blocks (rgLBs),
; each EDX bytes long and pointer to a list of free link blocks (pFreeLB).
;
; The pFreeLB pointer is set to address the first element in rgLBs. Each
; element of rgLBs is set to point to the next element of rgLBs. The
; last element of rgLBs is set to point to nothing (NIL).
;
		LEA EAX,rgLBs           ; pFreeLB <= ^rgLBs;
		MOV pFreeLB,EAX         ;
LB_Loop:
		MOV EBX,EAX             ; for I = 0 TO ECX
		ADD EAX,EDX             ;   rgLBs[I].Next <=
		MOV [EBX.NextLB],EAX    ;     ^rgLBs[I+1];
		LOOP LB_Loop            ;
		MOV [EBX.NextLB],NIL    ; rgFree[1023].Next <= NIL;
		RETN                    ;
;=============================================================================
; AddTSSDesc
; Builds a descriptor for a task and places it in the GDT.  If you
; check the intel documentation the bits of data that hold this
; information are scattered through the descriptor entry, so
; we have to do some shifting, moving, anding and oring to get
; the descriptor the way the processor expects it.  See the Intel
; docs for a complete description of the placement of the bits.
;
; Note: The granularity bit represents the TSS itself, not the code
; that will run under it!
;
;
; IN:
;	EAX - Size of TSS
;	EBX - Decriptor type (default for OS TSS is 0089h)
;		(0089h - G(0),AV(0),LIM(0000),P(1),DPL(00),(010),B(0),(1))
;	EDX - Address of TSS
;	EDI - Address of Desc in GDT
; OUT:
;	GDT is updated with descriptor
; USED:
;	EFlags  (all other registers are saved)

AddTSSDesc:
		;The following code section builds a descriptor entry for
		;the TSS and places it into the GDT
		PUSH EAX
		PUSH EBX
		PUSH EDX
		PUSH EDI
		DEC EAX                 ; (Limit is size of TSS-1)
	    SHL EBX,16              ; Chinese puzzle rotate
		ROL EDX,16              ; Exchange hi & lo words of Base Addr
		MOV BL,DH               ; Base 31 .. 24
		MOV BH,DL               ; Base 23 .. 16
		ROR EBX,8               ; Rotate to Final Alignment
		MOV DX,AX               ; Limit 15 .. 0 with Base 15 .. 0
		AND EAX,000F0000h       ; Mask Limit 19 .. 16
		OR EBX,EAX              ; OR into high order word
		MOV [EDI],EDX           ; Store lo double word
		MOV [EDI+4],EBX         ; Store hi double word
		POP EDI
		POP EDX
		POP EBX
		POP EAX
		RETN

;=============================================================================
; InitFreeTSS
; INPUT :  EAX, ECX
; OUTPUT : NONE
; USED :   ALL General registers, FLAGS
; MODIFIES : pFreeTSS (and the dynamic array of TSSs)
;
; This routine initializes the free pool of Task State Segments.
; On entry:
;	EAX points to the TSSs to initialize (allocated memory).
;   ECX has the count of TSSs to initialize.
;   The size of the TSS is taken from the constant sTSS.
;
; The pFreeTSS pointer is set to address the first TSS. The NextTSS
; field in each TSS is set to point to the next free TSS. The
; last TSS is set to point to nothing (NIL). The IOBitBase field is
; also set to FFFFh for NULL I/O permissions in each TSS.
; NOTE: The allocated memory area for the TSS MUST BE ZEROED before
; calling this routine.  By deafult, we add the TSS descriptors at OS
; protection level. If we spawn or add a User level TSS we must
; OR the DPL bits with 3!

InitFreeTSS:
		MOV pFreeTSS,EAX        	; First one free to use
		MOV EDI, OFFSET rgTSSDesc	; ptr to TSS descriptors
		ADD EDI, 16					; First two TSSs are Static (Mon & Dbgr)
		MOV EDX, sTSS				; Size of TSS (in bytes) into EDX
		MOV EBX, 3					; Number of first dynamic TSS
TSS_Loop:
		MOV ESI,EAX           		  	; for I = 0 TO ECX
		ADD EAX,EDX             		;   EAX <= rgTSSs[I].Next
		MOV [ESI.NextTSS],EAX   		;     ^rgTSSs[I+1];
		MOV [ESI.TSS_IOBitBase], 0FFFFh	; IOBitBase
		MOV [ESI.TSSNum], BX			; TSS Number
		MOV [ESI.TSS_DS], DataSel		;Set up for Data Selectors
		MOV [ESI.TSS_ES], DataSel
		MOV [ESI.TSS_FS], DataSel
		MOV [ESI.TSS_GS], DataSel
		MOV [ESI.TSS_SS], DataSel
		MOV [ESI.TSS_SS0], DataSel
		PUSH EAX					;Save pTSS
		MOV EAX,EDI            		; Get offset of Curr TssDesc in EAX
		SUB EAX, OFFSET GDT    		; Sub offset of GDT Base to get Sel of TSS
		MOV [ESI.Tid],AX    	    ; Store TSS Selector in TSS (later use)
		PUSH EBX
		PUSH EDX

		MOV EAX,EDX             ; Size of TSS (TSS + SOFTSTATE)
		MOV EDX,ESI             ; Address of TSS
		MOV EBX,0089h           ; G(0),AV(0),LIM(0),P(1),DPL(0),B(0)

		CALL AddTSSDesc

		ADD EDI,8               ; Point to Next GDT Slot (for next one)
		POP EDX
		POP EBX
		POP EAX
		INC EBX					; TSS Number
		LOOP TSS_Loop           ;
		MOV [ESI.NextTSS],NIL   ; rgFree[LastOne].Next <= NIL;
		RETN                    ;

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

InitFreeJCB:
; INPUT : 	EAX - Address of JCBs to be initialized
;			ECX - Count of JCBs
;			EDX - Size of JCBs
; OUTPUT :	NONE
; USED:		EAX,EBX,ECX,EDX,ESI EFLAGS
; MODIFIES: pFreeJCB, pJCBs
;
; This routine will initialize the free pool of Job Control Blocks (JCBs).
; EAX points to the first JCB,
; ECX is count of JCBs,
; EDX is size of each JCB.
;
; The pFreeJCB pointer is set to address the first element in rgJCBs.
; Each element of rgJCBs is set to point to the next element of rgJCBs.
; The last element of rgJCBs is set to point to nothing (NIL).
; The JCBs are also sequentially numbered. We can't use it's position
; in the array because some JCBs are static (Mon and Debugger), while
; others (the ones we are initializing now) are dynamicly allocated.
;
		MOV pFreeJCB,EAX        ;Set up OS pointer to list
		MOV pJCBs, EAX			;Set up global ptr to first JCB
		MOV EBX, 3				;1st number for Dynamic JCBs
JCB_Loop:
	    MOV ESI,EAX             ;EBX has pointer to current one
		ADD EAX,EDX             ;EAX points to next one
		MOV [ESI.NextJCB],EAX   ;Make current point to next
		MOV [ESI.JobNum], EBX	;Number it
		INC EBX
		LOOP JCB_Loop           ;Go back till done
		MOV [ESI.NextJCB],NIL   ;Make last one nil
		RETN                    ;

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

InitFreeRQB:
; INPUT : 	EAX - Address of RQBs to be initialized
;			ECX - Count of JCBs
;			EDX - Size of JCBs
; OUTPUT :	NONE
; USED:		EAX,ECX,EDX,ESI EFLAGS
; MODIFIES: pFreeRQB, pRQBs
;
; This routine will initialize a free pool of Request Blocks (RQBs).
; ECX is count of RQBs to initialize,
; EDX is the size (in bytes), and EAX points to a list of free JCBs (pFreeJCB).
;
; The pFreeRQB pointer is set to address the first element in rgRQBs.
; Each element of rgRQBs is set to point to the next element of rgRQBs.
; The last element of rgRQBs is set to point to nothing (NIL).
; The RqBlk handle used in many calls is its position in the array.
; This can be done because the array of RQBs is allocated dynamically.
;
		MOV pFreeRQB,EAX        ;Set up OS pointer to list
		MOV pRQBs, EAX			;Set up global ptr to first RQB
RQB_Loop:
	    MOV ESI,EAX             ;EBX has pointer to current one
		ADD EAX,EDX             ;EAX points to next one
		MOV [ESI.pNextRQB],EAX  ;Make current point to next
		LOOP RQB_Loop           ;Go back till done
		MOV [ESI.pNextRQB],NIL  ;Make last one nil
		RETN                    ;

;=============================================================================
; This sets IRQ00-0F vectors in the 8259s
; to be Int20 thru 2F.
;
; When the PICUs are initialized, all the hardware interrupts are MASKED.
; Each driver that uses a hardware interrupt(s) is responsible
; for unmasking that particular IRQ.
;
PICU1          EQU 0020h
PICU2          EQU 00A0h

Set8259 PROC NEAR
		MOV AL,00010001b
		OUT PICU1+0,AL          	;ICW1 - MASTER
		jmp $+2
		jmp $+2
		OUT PICU2+0,AL          	;ICW1 - SLAVE
		jmp $+2
		jmp $+2
		MOV AL,20h
		OUT PICU1+1,AL          	;ICW2 - MASTER
		jmp $+2
		jmp $+2
		MOV AL,28h
		OUT PICU2+1,AL          	;ICW2 - SLAVE
		jmp $+2
		jmp $+2
		MOV AL,00000100b
		OUT PICU1+1,AL          	;ICW3 - MASTER
		jmp $+2
		jmp $+2
		MOV AL,00000010b
		OUT PICU2+1,AL          	;ICW3 - SLAVE
		jmp $+2
		jmp $+2
		MOV AL,00000001b
		OUT PICU1+1,AL          	;ICW4 - MASTER
		jmp $+2
		jmp $+2
		OUT PICU2+1,AL          	;ICW4 - SLAVE
		jmp $+2
		jmp $+2
		MOV AL,11111010b			;Masked all but cascade/timer
;		MOV AL,01000000b			;Floppy masked
		OUT PICU1+1,AL          	;MASK - MASTER (0= Ints ON)
		jmp $+2
		jmp $+2
		MOV AL,11111111b
;		MOV AL,00000000b
		OUT PICU2+1,AL          	;MASK - SLAVE
		jmp $+2
		jmp $+2
		RETN
SET8259	ENDP

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

InitMemMgmt:
;IN:   Nothing
;OUT:  Nothing (except that you can use memory management routines now!)
;USED: ALL REGISTERS ARE USED.
;
; This section finds out how much memory we have (in MBs) by writing
; to the highest DWord in each meg until it fails a readback test.
; It sets nPages Free after finding out just how much we have.
; We assume 1MB to start (which means we start at 2Mb (1FFFFC).
; It places the highest addressable offset in GLOBAL oMemMax.
; We also calculate the number of pages of physical memory this
; is and store it in the GLOBAL nPagesFree.

		MOV _nPagesFree, 256	;1 Mb of pages = 256
		MOV EAX,1FFFFCh         ;top of 2 megs (for DWORD)
		XOR EBX,EBX				;
		MOV ECX,06D72746CH      ;'mrtl' test string value for memory
MEMLoop:
		MOV DWORD PTR [EAX],0h	;Set it to zero intially
		MOV DWORD PTR [EAX],ECX	;Move in test string
		MOV EBX,DWORD PTR [EAX]	;Read test string into EBX
		CMP EBX,ECX				;See if we got it back OK
		JNE MemLoopEnd			;NO!
		ADD EAX,3				;Yes, oMemMax must be last byte
		MOV _oMemMax,EAX		;Set oMemMax
		SUB EAX,3				;Make it the last DWord again
		ADD EAX,100000h			;Next Meg
		ADD _nPagesFree, 256	;Another megs worth of pages
		ADD sPAM, 32			;Increase PAM by another meg
		CMP EAX,3FFFFFCh        ;Are we above 64 megs
		JAE MemLoopEnd			;Yes!
		XOR EBX,EBX				;Zero out for next meg test
		JMP MemLoop
MemLoopEnd:

; Page Allocation Map is now sized and ZEROed
; Now we must fill in bits used by OS which was just loaded and
; the Video RAM and Boot ROM (neither of which we consider free).
; This also fills out each of the Page Table Entries (PTEs) for the
; initial OS code and data.  Note that linear address match physical
; address for the initial OS data and code (its the law!)

; This first part MARKS the OS code and data pages as used
; and makes PTEs.
;
		MOV EDX, OFFSET pTbl1		;EDX points to OS Page Table 1
		XOR EAX, EAX				;Point to 1st physical/linear page (0)
IMM001:
		MOV [EDX], EAX				;Make Page Table Entry
		AND DWORD PTR [EDX], 0FFFFF000h 	;Leave upper 20 Bits
		OR	DWORD PTR [EDX], 0001h 			;Supervisor, Present
		MOV EBX, EAX
		CALL MarkPage				;Marks page in PAM
		ADD EDX, 4					;Next table entry
		ADD EAX, 4096
		CMP EAX, 24000h				;Reserve 128K for OS (for now)
		JAE SHORT IMM002
		JMP SHORT IMM001			;Go for more

; Now we fill in PAM and PTEs for Video and ROM slots.
; This covers A0000 thru 0FFFFFh (upper 384K of first Meg).
; Right now we just mark everything from A0000 to FFFFF as used.
; This routine could be expanded to search through the ROM pages of
; ISA memory (C0000 -FFFFF) finding the unaccessable ones and marking
; them as allocated in the PAM. Several chip sets on the market allow
; you to set ROM areas as useable RAM (such as the 82C30 C&T).  But we
; can't be sure everyone can do it, nor can we provide instructions
; to everyone.

IMM002:
		MOV EAX, 0A0000h			;Points to 128K Video & 256K ROM area
		MOV EBX, EAX				;
		SHR EBX, 10					;Make it index (SHR 12, SHL 2)
		MOV EDX, OFFSET pTbl1		;EDX pts to Page Table
		ADD EDX, EBX
IMM003:
		MOV [EDX], EAX					;Make Page Table Entry
		AND DWORD PTR [EDX], 0FFFFF000h ;Leave upper 20 Bits
		OR	DWORD PTR [EDX], 0101b 		;Mark it "User" "ReadOnly" & "Present"
		MOV EBX, EAX				;Setup for MarkPage call
		CALL MarkPage				;Mark it used in the PAM
		ADD EDX, 4					;Next PTE entry
		ADD EAX, 4096				;Next page please
		CMP EAX, 100000h			;1Mb yet?
		JAE IMM004					;Yes
		JMP SHORT IMM003			;No, go back for more

; Initial Page Directory and the Page Table are static.
; Now we can go into PAGED Memory mode.  This is done by loading
; CR3 with the physcial address of the Page Directory, then reading
; CR0, ANDing it with 8000000h and then writing it again.
; After the MOV CR0 we must JMP to clear the prefetch queue of
; any bogus physical addresses.

IMM004:
		MOV EAX, OFFSET PDir1  ;Physical address of OS page directory
		MOV CR3, EAX		;Store in Control Reg 3
		MOV EAX, CR0		;Get Control Reg 0
		OR  EAX, 80000000h	;Set paging bit ON
		MOV CR0, EAX		;Store Control Reg 0
		JMP IM0005			;Clear prefetch queue
IM0005:
;
; Now we allocate an Exchange that the OS uses for a semaphore
; use to prevent reentrant use of the any of the critical
; memory managment functions.
;
		LEA EAX, MemExch		;Alloc Semaphore Exch for Memory calls
		PUSH EAX
		CALL FAR PTR _AllocExch

		PUSH MemExch				;Send a dummy message to pick up
		PUSH 0FFFFFFF1h
		PUSH 0FFFFFFF1h
		CALL FAR PTR _SendMsg

		RETN				;Done initializing memory managment
;
;=============================================================================
; InitCallGates inits the array of call gates with an entry to a generic
; handler that returns ErcNotInstalled when called. This prevents new code
; running on old MMURTLs or systems where special call gates don't exist
; without crashing horribly.
;
; IN: Nothing
; Out : Nothing
; Used : ALL registers and flags
;
InitCallGates:
		MOV ECX, nCallGates		;Number of callgates to init
InitCG01:
		PUSH ECX
		DEC ECX					;make it an index, not the count
		SHL ECX, 3				;
		ADD ECX, 40h			;Now ecx is selector number
		MOV EAX, 0EC00h			;DPL 3, 0 Params
		MOV DX, OSCodeSel
		MOV ESI, OFFSET DummyCall
		CALL FAR PTR _AddCallGate
		POP ECX					;ignore error...
		LOOP InitCG01
		RETN

⌨️ 快捷键说明

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