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

📄 init.asm

📁 一个dos操作系统DRDOS的源码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
		db	2		; DMA mode
		db	37		; 2*18.2 = 2 second motor off
		db	2		; 512 bytes per sector
parms_spt	db	18		; sectors per track
		db	2Ah		; gap length for read/write
		db	0FFh		; data length (128 byte/sector only)
parms_gpl	db	50h		; data length for format
		db	0F6h		; fill byte for format
		db	15		; head settle time in ms
		db	8		; motor on delay in 1/8s

; The BPB table need not survive config time, so share with layout table

bpbtbl		label	word

	MAX_SPT	equ	40
	
layout_table	label word		; current # of sectors/track

S	= 	1

rept	MAX_SPT
		;	C  H  S  N
		;	-  -  -  -
		db	0, 0, S, 2
S	=	S + 1
endm

	orgabs	600h			; CON: one character look-ahead buffer
; nb. it's at 61B in DOS 4.0

	Public	local_char, local_flag

local_char	db	0		;** fixed location **
local_flag	db	0		;** fixed location **

	public	endbios
endbios		dw	offset CGROUP:RESBIOS	; pointer to last resident byte

CODE	ends

ICODE	segment 'ICODE'			; reusable initialization code

	Assume	CS:CGROUP, DS:CGROUP, ES:CGROUP, SS:Nothing

bpbs		dw	CG:bpb360	; 0: 320/360 Kb 5.25" floppy
		dw	CG:bpb1200	; 1: 1.2 Mb 5.25" floppy
		dw	CG:bpb720	; 2: 720 Kb 3.5" floppy
		dw	CG:bpb360	; 3: (8" single density)
		dw	CG:bpb360	; 4: (8" double density)
		dw	CG:bpb360	; 5: hard disk
		dw	CG:bpb360	; 6: tape drive
		dw	CG:bpb1440	; 7: 1.44 Mb 3.5" floppy
		dw	CG:bpb1440	; 8: Other
		dw	CG:bpb2880	; 9: 2.88 Mb 3.5" floppy

	Public	init0
init0	proc	near
;
; We now uncompress to > (7C00h (ie. boot stack) - 700h (ie. base of code)
; This means our stack collides with our code, very bad news.
; To avoid this we switch stacks into a safer area ie. 0C000h
; The floppy parameters also live at 7C00, so we have to relocate these
; before we expand.

	mov	cs:byte ptr A20Enable,0C3h
					; fixup the RET

	mov	sp, 0C000h		; switch to magic stack

	sti
	cld

	push	cx			; save entry registers
	push	di			; (important in ROM systems)

	xor	si,si
	mov	ds,si
	mov	es,si

	Assume	DS:IVECT, ES:IVECT

	mov	di,522h			; ES:DI -> save area for parameters
	lds	si,i1Eptr		; DS:SI -> FD parameters for ROS

	Assume	DS:Nothing

	mov	i1Eoff,di
	mov	i1Eseg,es		; setup new location
	mov	cx,11
	rep	movsb
	mov	es:byte ptr 0-7[di],36	; enable read/writing of 36 sectors/track

	pop	di
	pop	cx

if COMPRESSED
	mov	si, cs			; preserve entry registers
	mov	ds, si			; other than si, ds and es
	mov	es, si
	xor	si, si
	mov	si, compflg		; Get Compresed BIOS Flag
	or	si, si			; Set to Zero if the BIOS has
	jnz	not_compressed		; been compressed
	mov	si, CG:INITDATA
	push	di			; bios_seg
	push	ax			; bdos_seg
	push	bx			; initial drives
	push	cx			; memory size
	push	dx			; initial flags
	lea	cx, biosinit_end
	sub	cx, si
	inc	cx			; length of compressed part plus one
	mov	di, cx
	neg	di			; furthest offset we can use
	and	di, 0fff0h		; on the next para below
	push	di
	push	si
	shr	cx, 1
	rep movsw			; take a copy
	pop	di			; di is now -> compressed dest
	pop	si			; this is now -> compressed source
bios_r20:
	lodsw				; get control word
	mov	cx,ax			; as a count
	jcxz	bios_r40		; all done
	test	cx,8000h		; negative ?
	jnz	bios_r30		; yes do zeros
	rep	movsb			; else move in data bytes
	jmp short bios_r20		; and to the next

bios_r30:
	and	cx,7fffh		; remove sign
	jcxz	bios_r20		; none to do
	xor	ax,ax
	rep	stosb			; fill with zeros
	jmp short bios_r20
bios_r40:
	pop	dx
	pop	cx
	pop	bx
	pop	ax
	pop	di
not_compressed:
endif
	mov	si,cs
	mov	ds,si			; DS -> local data segment
	cmp	dl,0ffh			; booting from ROM?
	 jz	rom_boot
	cmp	si,1000h		; test if debugging
	 jb	disk_boot		; skip if not

;	When the BIOS is loaded by the DOSLOAD or LOADER utilities under
;	Concurrent for DEBUGGING or in a ROM system then on entry AX
;	contains the current location of the BDOS and CX the memory Size.
;	Bx is the current code segment

	mov	rcode_seg,dx		; rom segment of bios
	mov	current_dos,ax		; current location of the BDOS
	mov	mem_size,cx		; total memory size
	mov	init_drv,bl		; initial drive
	mov	comspec_drv,bh		;
	mov	init_buf,3		; assume default # of buffers
	mov	init_flags,3	
	jmp	bios_exit
	
rom_boot:				; BIOS is copied from ROM:
					; 	DL = 0FFh
					;	AX = segment address of DRBDOS
					;	BH = COMSPEC drive
					;	BL = INIT_DRV
	mov	rcode_seg,di		;	DI = BIOS ROM SEG
	mov	current_dos,ax		; current location of the BDOS
	mov	init_drv,bl		; initial drive C:
	mov	comspec_drv,bh		; commspec drive C:
	mov	init_flags,3		; it is a ROM system, use comspec drive
	jmps	rom_boot10		; common code

disk_boot:
	mov	rcode_seg,cs
	sub	ax,ax
	mov	current_dos,ax		; current BDOS location to disk load
	xchg	ax,dx			; AL = boot drive
	mov	init_runit,al		; save the ROS unit
	test	al,al			; test the boot drive
	 jz	floppy_boot		; skip if floppy boot
	mov	al,2			; it's drive C:
floppy_boot:
	mov	init_drv,al		; set boot drive

rom_boot10:
	pushx	<ds, es>		; save registers
	sub	bx,bx
	mov	ds,bx			; DS:BX -> interrupt vectors

	Assume	DS:IVECT

	push	cs			; we want to save vectors some
	pop	es			;  locally

	lea	di,vecSave
	mov	cx,NUM_SAVED_VECS	; restore this many vectors
SaveVectors:
	xor	ax,ax			; zero AH
	mov	al,es:[di]		; AX = vector to save
	inc	di			; skip to save position
	shl	ax,1
	shl	ax,1			; point at address
	xchg	ax,si			; DS:SI -> location to save
	movsw
	movsw				; save this vector
	loop	SaveVectors		; go and do another

	mov	i0off,CG:Int0Trap
	mov	i0seg,cs		; now grab int0 vector
	mov	i1off,CG:Int1Trap
	mov	i1seg,cs		; now grab int1 vector
	mov	i3off,CG:Int1Trap
	mov	i3seg,cs		; now grab int3 vector
	mov	i4off,CG:Int1Trap
	mov	i4seg,cs		; now grab int4 vector
	mov	i19off,CG:Int19Trap
	mov	i19seg,cs		; now grab int19 vector

	popx	<es, ds>

	Assume	DS:CGROUP, ES:CGROUP

	call	get_boot_options	; look for user keypress
	mov	boot_options,ax		;  return any options

	mov	ah,EXT_MEMORY
	int	SYSTEM_INT		; find out how much extended memory
	 jnc	bios_extmem
	xor	ax,ax			; say we have no memory
bios_extmem:
	mov	ext_mem_size,ax		;  we have and store for reference
	
	mov	init_buf,3		; assume default of 3 buffers
	int	MEMORY_INT		; get amount of conventional memory
	cmp	ax,128
	 jbe	bios_mem
	mov	init_buf,5		; use 5 buffers if > 128K of memory
bios_mem:				; get amount of conventional memory
	mov	cl,6			;    in kilobytes (AX)
	shl	ax,cl			; convert Kb's to paragraphs
	mov	mem_size,ax		; set end of TPA

bios_exit:
; The following code performs the fixups necessary for ROM executable
; internal device drivers.
	mov	ax,cs			; check if we are on a rommed system
	cmp	ax,rcode_seg
	 jne	keep_rcode		; if so no relocation required
	mov	ax,CG:RCODE
	mov	rcode_offset,ax		; fixup variable need
	mov	bx,CG:IDATA
	sub	bx,ax
	mov	icode_len,bx		; during init we need RCODE and ICODE
	mov	bx,CG:RESUMECODE
	sub	bx,ax
	mov	rcode_header,bx
	mov	rcode_len,bx		; afterwards we just need RCODE
keep_rcode:

; If the system ROM BIOS supports RESUME mode then it will call Int 6C
; when returning from sleep mode. We take this over and reset the clock
; based upon the RTC value. To save space we only relocate the code if
; required.
;
	mov	ax,4100h		; does the BIOS support resume mode
	xor	bx,bx
	int	15h			; lets ask it
	 jc	resume_exit
	push	ds
	xor	ax,ax
	mov	ds,ax			; DS = vectors
Assume DS:IVECT
	mov	i6Coff,CG:Resume
	mov	i6Cseg,cs		; point Int 6C at resume code
Assume DS:CGROUP
	pop	ds
	mov	ax,cs			; check if we are on a rommed system
	cmp	ax,rcode_seg
	 jne	resume_exit		; if so nothing extra to keep
	mov	ax,CG:RESBIOS
	sub	ax,CG:RCODE
	mov	rcode_header,ax		; keep Resume code as well...
	mov	rcode_len,ax		; afterwards we just need RCODE
resume_exit:
	mov	ax,CG:ENDCODE		; discard RCODE (we will relocate it)
	mov	endbios,ax
	mov	rcode_fixups,CG:bios_fixup_tbl

	mov	bx,CG:con_drvr		; get first device driver in chain
	mov	word ptr device_root+0,bx
	mov	word ptr device_root+2,ds

init1:
	cmp	word ptr [bx],0FFFFh	; last driver in BIOS?
	 je	init3
	mov	2[bx],ds		; fix up segments in driver chain
	mov	bx,[bx]
	jmps	init1
init3:
	jmp	biosinit		; jump to BIOS code

init0	endp

get_boot_options:
;----------------
; On Entry:
;	None
; On Exit:
;	AX = boot options
	mov	si,offset CGROUP:starting_dos_msg
	lodsb				; get 1st character (never NULL)
get_boot_options10:
	mov	ah,0Eh
	mov	bx,7
	int	VIDEO_INT		; TTY write of character	
	lodsb				; fetch another character
	test	al,al			; end of string ?
	 jnz	get_boot_options10
	call	option_key		; poll keyboard for a while
	 jnz	get_boot_options20	; if key available return that
	mov	ah,2			; else ask ROS for shift state
	int	16h
	and	ax,3			; a SHIFT key is the same as F5KEY
	 jz	get_boot_options20
	mov	ax,F5KEY		; ie. bypass everything
get_boot_options20:
	ret

option_key:
;----------
; On Entry:
;	None
; On Exit:
;	AX = keypress if interesting (F5/F8)
;	ZF clear if we have an interesting key
;
; Poll keyboard looking for a key press. We do so for a maximum of 36 ticks
; (approx 2 seconds).
;
	xor	ax,ax
	int	1Ah			; get ticks in DX
	mov	cx,dx			; save in CX for later
option_key10:
	push	cx		
	mov	ah,1
	int	16h			; check keyboard for key
	pop	cx
	 jnz	option_key30		; stop if key available
	push	cx
	xor	ax,ax
	int	1Ah			; get ticks in DX
	pop	cx
	sub	dx,cx			; work out elapsed time
	cmp	dx,36			; more than 2 secs ?
	 jb	option_key10
option_key20:
	xor	ax,ax			; timeout, set ZF, no key pressed
	ret

option_key30:
	cmp	ax,F5KEY		; if it is a key we want then
	 je	option_key40		;  read it, else just leave
	cmp	ax,F8KEY		;  in the type-ahead buffer
	 jne	option_key20
option_key40:
	xor	ax,ax
	int	16h			; read the key
	test	ax,ax			; clear ZF to indicate we have a key
	ret

ICODE	ends

INITDATA	segment 'INITDATA'

; This is a zero terminated list of locations to be fixed up with the
; segment of the relocated BIOS RCODE


bios_fixup_tbl	dw	CG:MemFixup
		dw	CG:OutputBSFixup
		dw	CG:DriverFunctionFixup
		dw	CG:Int0Fixup
		dw	CG:Int13DeblockFixup
		dw	CG:Int13UnsureFixup
		dw	CG:Int2FFixup
		dw	CG:ResumeFixup
IFDEF EMBEDDED
		dw	CG:RdiskFixup
endif
		dw	0

INITDATA	ends

CODE	segment	'CODE'
IFDEF EMBEDDED
	extrn	RdiskFixup:word
endif
CODE	ends


RCODE_ALIGN	segment public para 'RCODE'
ifndef ROMSYS
	db	1100h dup(0)		; reserve space for command.com
endif
RCODE_ALIGN	ends

RCODE		segment public word 'RCODE'

rcode_header	dw	0

	Public	DataSegment

DataSegment	dw	0070h		; segment address of low data/code

; Called to vector to appropriate sub-function in device driver
; The Function table address immediately follows the near call, so we can index
; into it using the return address. If the offset is in the range 0-6 it's
; actually a device number for the serial/parallel driver
;
;
; On Entry to subfunctions ES:BX -> req_hdr, DX = devno (serial/parallel)
;

FunctionTable	struc
FunctionTableMax	db	?
FunctionTableEntry	dw	?
FunctionTable	ends

	Public	DriverFunction

DriverFunction	proc	far
	cld
	sub	sp,(size P_STRUC)-4	; make space for stack variables
	push	bp			; (BP and RET are included)
	mov	bp,sp			; set up stack frame
	pushx	<ds,es>
	pushx	<ax,bx,cx,dx,si,di>	; save all registers
	mov	ds,cs:DataSegment
	mov	si,(size P_STRUC)-2[bp]	; get return address = command table
	lodsw				; AX = following word
	xchg	ax,dx			; DX = device number (0-6)
	mov	si,offset CGROUP:SerParCommonTable
	cmp	dx,6			; if not a device number it's a table
	 jbe	DriverFunction10
	mov	si,dx			; DS:SI -> table
DriverFunction10:
	les	bx,req_ptr		; ES:BX -> request header
	mov	REQUEST_OFF[bp],bx
	mov	REQUEST_SEG[bp],es
	mov	al,es:RH_CMD[bx]	; check if legal command
	cmp	al,cs:FunctionTableMax[si]
	 ja	cmderr			; skip if out of range
	cbw				; convert to word
	add	ax,ax			;  make it a word offset
	add	si,ax			; add index to function table
	call	cs:FunctionTableEntry[si]
	les	bx,REQUEST[bp]
cmddone:
	or	ax,RHS_DONE		; indicate request is "done"
	mov	es:RH_STATUS[bx],ax	; update the status for BDOS
	popx	<di,si,dx,cx,bx,ax>	; restore all registers
	popx	<es,ds>
	pop	bp
	add	sp,(size P_STRUC)-2	; discard stack variables 
	ret

cmderr:
	mov	ax,RHS_ERROR+3		; "invalid command" error
	jmps	cmddone			; return the error

DriverFunction	endp



OutputBS proc far
;-------
;	pushx	<ax, bx, si, di, bp>	; these are on the stack
	pushx	<cx, dx>
	mov	ah,3			; get cursor address
	mov	bh,0			; on page zero
	int	VIDEO_INT		; BH = page, DH/DL = cursor row/col
	test	dx,dx			; row 0, col 0
	 jz	OutputBS10		; ignore if first line
	dec	dl			; are we in column 0?
	 jns	OutputBS10		; no, normal BS
	dec	dh			; else move up one line
	push	ds
	xor	ax,ax
	mov	ds,ax
	mov	dl,ds:byte ptr [44ah]	; DL = # of columns
	dec	dx			; DL = last column
	pop	ds
	mov	ah,2			; set cursor, DH/DL = cursor, BH = page
	int	VIDEO_INT		; set cursor address
	jmps	OutputBS20

OutputBS10:
	mov	ax,0E08h		; use ROS TTY-like output function
	mov	bx,7			; use the normal attribute
	int	VIDEO_INT		; output the character in AL
OutputBS20:
	popx	<dx, cx>
	popx	<bp, di, si, bx, ax>
	iret

OutputBS endp


Int0Handler proc far
;----------
	cld
	push	cs
	pop	ds
	mov	si,CG:div_by_zero_msg	; DS:SI points at ASCIZ message
	mov	bx,STDERR		; to STDERR - where else ?
	mov	cx,1			; write one at a time
int0_loop:
	mov	dx,si			; DS:DX points at a char
	lodsb				; lets look at it first
	test	al,al			; end of string ?
	 je	int0_exit
	mov	ah,MS_X_WRITE		; write out the error
	int	DOS_INT
	 jnc	int0_loop		; if it went OK do another
int0_exit:
	mov	ax,MS_X_EXIT*256+1	; time to leave - say we got an error
	int	DOS_INT			; go for it!

Int0Handler endp

RCODE		ends

	end	init

⌨️ 快捷键说明

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