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

📄 bdevio.a86

📁 与MS-DOS兼容的DOS操作系统
💻 A86
📖 第 1 页 / 共 3 页
字号:
;		DS:SI		Device Header
;		ES:BX		Current Request Header
;
;	On Exit:
;		AX		Request Header Status
;
device_driver:
;------------
	xor	ax,ax
	mov	es:RH_STATUS[bx],ax	; Initialise return status
	push	es
	push	bx
	push	bp
	callf	ss:lock_bios		; lock access to BIOS
	push	cs
	call	device_driver10		; fake a callf
	callf	ss:unlock_bios		; unlock access to BIOS
	pop	bp
	pop	bx
	pop	es
	sti
	cld				; Restore Flags
	mov	ax,es:RH_STATUS[bx]	; Return the Status to the caller
	test	ax,ax			; set SF=1 if error
	ret

device_driver10:
	push	ds
	push	ds:DH_INTERRUPT[si]	; interrupt routine address on stack
	push	ds
	push	ds:DH_STRATEGY[si]	; strategy routine address on stack
	retf				; retf to strategy, interrupt, us

eject
;	Select drive and check for door open ints
;	Build fdos_hds to refer to the drive

;	Exit:	DL = drive to be selected (0-15)

select_logical_drv:
;------------------
; On Entry:
;	AL = logical drive to select (with change media checks)
; On Exit:
;	ES:BX -> LDT_
;
	cmp	al,last_drv		; is it a legal drive ?
	 jae	select_drv_bad		;  no, reject it now
	mov	logical_drv,al		; save logical drive
	call	get_ldt			; ES:BX -> LDT_ for drive
	 jc	select_physical_drv	; no LDT_ during init, must be physical
	mov	word ptr current_ldt,bx
	mov	word ptr current_ldt+WORD,es
	mov	al,es:byte ptr LDT_FLAGS+1[bx]	; is the drive valid ?
	test	al,(LFLG_NETWRKD+LFLG_JOINED)/100h
	 jnz	select_drv_bad		; reject networked/joined drives
	test	al,LFLG_PHYSICAL/100h
	 jz	select_drv_bad		; reject non-physical drives
	mov	al,es:LDT_NAME[bx]	; get the drive from the ascii name
	and	al,1fh			;  as the drive may require rebuilding
	dec	ax			; make it zero based
	push es ! push bx
	call	select_physical_drv	; select the physical root
	pop bx ! pop es
	cmp	es:LDT_ROOTLEN[bx],2	; if logical and physical roots
	 jbe	select_logical_drv30	;  are the same we are OK now
if JOIN
	mov	al,es:LDT_DRV[bx]	; should we be on a different
	cmp	al,fdos_hds_drv		;  physical drive ?
	 jne	select_logical_drv10	; if so then we'd better rebuild
endif
	cmp	es:LDT_BLK[bx],0FFFFh	; did we have a media change ?
	 jne	select_logical_drv20	; then we'd better rebuild
select_logical_drv10:
	call	rebuild_ldt_root	;  the LDT_ root block
select_logical_drv20:
	mov	ax,es:LDT_ROOT[bx]	; get virtual root from LDT
	mov	fdos_hds_root,ax	; move there
	mov	fdos_hds_blk,ax
if JOIN
	mov	al,es:LDT_DRV[bx]	; same with drive
	mov	fdos_hds_drv,al
endif
select_logical_drv30:
	ret

select_physical_drv:
;-------------------
; On Entry:
;	AL = physical drive to select (with change media checks)
; On Exit:
;	None
;
	xor	dx,dx
	mov	fdos_hds_blk,dx		; put it in the root by default
	mov	fdos_hds_root,dx
	mov	fdos_hds_drv,al		; set physical drive in working HDS
	cmp	al,phys_drv		; should we have a DDSC_ for this drive
	 jae	select_drv_bad		;  no, we can't select it then
	mov	physical_drv,al		; save physical drive number
	call	select_adrive		; no, better select it
	 jc	select_drv_critical_error
	ret

select_drv_bad:
;--------------
; An attempt has been made to select a bad drive,
; return a logical error "invalid drive"
	mov	ax,ED_DRIVE		; ED_DRIVE "invalid drive"
	jmp	fdos_error

select_drv_critical_error:
;-------------------------
; The drive is logically correct, so all error at this point must
; be physical ones - so we want a critical error
	jmp	generate_critical_error

eject
select_adrive:
;-------------
; This entry is called to physically select a drive (eg. when flushing buffers)
; It does not alter the current physical_drv setting, which must be re-selected
; afterwards by the caller.
;
; On Entry:
;	AL = disk to select (range validated)
; On Exit:
;	CY set if a problem selecting the drive

	mov	adrive,al
	mov	err_drv,al		; save error drive
	call	get_ddsc		; ES:BX -> DDSC_ for drive
	mov	al,1			; AL = "Unknown Unit"
	 jc	select_drv_err		;  error if no DDSC_
	mov	ax,es:word ptr DDSC_DEVHEAD[bx]
	mov	word ptr error_dev+0,ax
	mov	ax,es:word ptr DDSC_DEVHEAD+2[bx]
	mov	word ptr error_dev+2,ax
	push	es			; remember driver address for error's
	push	bx			; preserve DDSC_
	call	check_media		; see if media has changed
	pop	bx			; restore DDSC_
	pop	es
	 jc	select_drv_err

;	select the disk drive and fill the drive specific variables
;	entry:	ES:BX -> DDSC_ of disk to select
;		AX <> 0 if drive requires BPB rebuilt
;	exit:	CY flag set on error

	test	ax,ax			; device driver, new select?
	 jz	select_ddsc		; use current DDSC if old select
	call	build_ddsc_from_bpb	; else get BPB and build new DDSC
	 jc	select_drv_err		; carry flag reset
	call	select_ddsc		; use to DDSC for select
if DELWATCH
	mov	ah,DELW_NEWDISK		; we have a new disk so I guess
	mov	al,physical_drv		;  I'd better tell delwatch
	les	bx,current_ddsc		;  about the new disk so it
	callf	fdos_stub		;  knows to update itself
endif
	clc				;select disk function ok
	ret

select_drv_err:
; On Entry:
;	AL = extended error code
;	CY set
;
	mov	ioexerr,al		; save error code
	ret


select_ddsc:
;-----------
; On Entry:
;	ES:BX -> DDSC_ of drive to be selected
	mov	word ptr current_ddsc,bx
	mov	word ptr current_ddsc+WORD,es
	push ds ! push es
	pop ds ! pop es			; swap ES and DS
	lea	si,DDSC_SECSIZE[bx]	; DS:SI -> DDSC_ original
	mov	di,offset local_ddsc	; ES:DI -> DDSC_ copy
	mov	cx,LOCAL_DDSC_LEN
	rep	movsb			; make a local copy of interesting bits
	push es ! pop ds		; DS=ES=local data segment
	mov	ax,psecsiz		; now initialise some other vaiiables
	mov	cl,clshf
	shl	ax,cl			; AX = bytes per cluster
	mov	clsize,ax
	xor	ax,ax
	mov	al,clmsk
	inc	ax			; AX = sectors per cluster
	mov	secperclu,ax
	mov	al,byte_nfats		; AX = number of FATs
	mov	nfats,ax		;  (it's handier as a word
	mov	ax,diradd		; number of FAT records can be
    sub ax,fatadd       ;  bigger than 255 
    xor dx,dx           
    div nfats           
    mov nfatrecs,ax     
	mov	cx,FCBLEN
	mov	ax,clsize		; convert from cluster size
	xor	dx,dx			;  to number of dir entries
	div	cx			;  per cluster - handy for
	mov	dirperclu,ax		;  subdirectories
	mov	ax,FAT12
	cmp	lastcl,MAX12		; is it a 12 bit FAT ?
	 jbe	select_ddsc10
	mov	ax,FAT16		; no, it's 16 bit
select_ddsc10:
	mov	dosfat,ax		; remember which for later
	clc				; drive all selected
	ret




eject

build_ddsc_from_bpb:	; call device driver to build BPB, convert to DDSC_
;-------------------
;	On Entry:
;		ES:BX -> DDSC_ to rebuild
;	On Exit:
;		ES:BX preserved
;		CY set on error
;		AL = error code

	push	es
	push	bx			; save DDSC_ address
	xor	di,di
	mov	ax,deblock_seg
	mov	es,ax			; ES:DI -> deblock seg
	test	ax,ax			; if we are deblocking spare buffer
	 jnz	build_bpb10		;  might be in high memory
	dec	ax			; AX = FFFF
	mov	dx,ax			; compute impossible record #
	mov	cx,BF_ISDIR		; locate directory sector w/o preread
	call	locate_buffer		; this will find the cheapest buffer
	mov	es:BCB_DRV[si],0FFh	; don't really want this...
	lea	di,BCB_DATA[si]		; ES:DI -> disk buffer
build_bpb10:
	mov	req4_buffer,di		; xfer to ES:DI
	mov	req4_buffer+2,es
	pop	bx			; restore DDSC_ address
	pop	es

	push	ds
	lds	si,es:DDSC_DEVHEAD[bx]	; DS:SI -> device header
	mov	ax,ds:DH_ATTRIB[si]	; non-FAT ID driver ("non-IBM") bit
	pop	ds			;   in device header attributes
	test	ax,DA_NONIBM
	 jnz	bldbpb30		; skip if media byte in FAT not used

	mov	req_rwmode,0		; read of system area
	mov	req_len,RH4_LEN		; set length field
	mov	req_cmd,CMD_INPUT	; read first FAT sector off disk
if DOS5
	test	ax,DA_BIGDRV		; large sector numbers ?
endif
	mov	ax,1
	mov	req4_count,ax		; read 1st FAT sector
	cwd				; DS:AX = sector 1
	mov	word ptr req4_bigsector,ax
	mov	word ptr req4_bigsector+2,dx
if DOS5
	 jz	bldbpb20
	dec ax ! dec ax			; AX = 0FFFFh
bldbpb20:
endif
	mov	req4_sector,ax		; set requested sector address
	mov	req4_sector+2,dx	; (support large DOS drives)
	call	block_device_driver	; try to read FAT sector, AX = status
	 js	bldbpb_err		; skip if errors (AX negative)
bldbpb30:
	mov	req_len,RH2_LEN		; length of req
	mov	req_cmd,CMD_BUILD_BPB	; "build bpb"
	call	block_device_driver	; call the device driver
	 js	bldbpb_err		; skip if errors (AX negative)
	push	ds
	push	es
	push	bx
	mov	di,bx			; ES:DI -> DDSC_ to initialise
	lds	si,dword ptr req2_bpb	; DS:SI -> BPB to convert
	call	bpb2ddsc		; rebuild the DDSC_
	pop	bx
	pop	es
	pop	ds
	clc				; success - we have a new DDSC_
	ret


bldbpb_err:
	stc				; we had a problem
	ret


eject

;-----------
check_media:	; check media if DPH media flag set
;-----------
; On Entry:
;	ES:BX -> DDSC_ of physical drive to check
; On Exit:
;	CY set on error, AX = error code
;	else
;	AX <> 0 if disk requires BPB rebuild
;	If definite/possible change then LDT's marked as invalid
;	If possible then buffers/hashing discarded provided they are clean
;	If definite then all buffers/hashing for drive discarded even if dirty
;
	mov	req_len,RH1_LEN		; set length field
	mov	req_cmd,CMD_MEDIA_CHECK	; media check routine
	call	block_device_driver	; call the device driver
	 jns	chkmed10
	stc				; we have a problem, generate
	ret				;  an error
chkmed10:
	mov	al,req_media+1		; else get returned value
	xor	ah,ah			;  watch out for 1st access too..
	xchg	ah,es:DDSC_FIRST[bx]	; treat never accessed as changed
	cmp	al,1			; 1 = no change
	 jne	chkmed20
	dec	ax			; AL=0, build bpb only if DDSC_FIRST
;	clc				; it all went OK
	ret

chkmed20:
	mov	dl,adrive		; media may have/has changed
	call	mark_ldt_unsure		;  so force LDT's to unsure
	
; AL = 00 if maybe changed, FF for definitely changed
	test	al,al
	 jz	chkmed_maybe		; media may have changed

chkmed_changed:				; disk has changed for sure
	call	discard_files		; discard open files
	jmps	chkmed30		; discard buffers, build bpb required

chkmed_maybe:				; disk has possibly changed
	call	discard_dir		; we can always discard dir as they
	mov	ah,BF_DIRTY		;  won't be dirty
	mov	al,adrive
	call	buffers_check		; any dirty buffers on adrive?
	 jnz	chkmed40		; yes, can't discard FAT
chkmed30:
	call	discard_all		; discard buffers for drive
chkmed40:
	or	ax,0FFFFh		; better rebuild bpb
;	clc
	ret


	Public	mark_ldt_unsure

mark_ldt_unsure:
;---------------
; On Entry:
;	DL = physical drive
; On Exit:
;	All corresponding LDT's marked as unsure
;	All reg preserved
;
	push	es
	push	ax
	push	bx
	xor	ax,ax			; start with drive A:
mlu10:
	call	get_ldt_raw		; ES:BX -> LDT_
	 jc	mlu30			; CY = no more LDT's
	test	es:LDT_FLAGS[bx],LFLG_NETWRKD+LFLG_JOINED
	 jnz	mlu20			; if networked leave it alone
	cmp	dl,es:LDT_DRV[bx]	; does the physical drive match ?
	 jne	mlu20
	mov	es:LDT_BLK[bx],0FFFFh	; indicate we shouldn't trust BLK
mlu20:
	inc	ax			; onto next LDT
	jmps	mlu10
mlu30:
	pop	bx
	pop	ax
	pop	es
	ret

;-----------
write_block:
;-----------
;	entry:	RWMODE = write type
;			bit 0:
;			  1 - write, not read
;			bits 2-1 (affected disk area)
;			0 0 - system area
;			0 1 - FAT area
;			1 0 - root or sub directory
;			1 1 - data area

	or	rwmode,1		; mark it as a write
	xor	cx,cx			; indicate no second attempt
	mov	al,CMD_OUTPUT		; assume normal write
	cmp	verify_flag,0		; is verify on ?
	 je	rdwr_block
	mov	al,CMD_OUTPUT_VERIFY	; assume use write w/ verify
	jmps	rdwr_block

;----------
read_block:
;----------
;	entry:	RWMODE = read type
;			bit 0:
;			  0 - read, not write
;			bits 2-1 (affected disk area)
;			0 0 - system area
;			0 1 - FAT area
;			1 0 - root or sub directory
;			1 1 - data area
;		CX <> 0	if FAT retry possible (critical error should then
;			be avoided)
;	exit:	SF = 0 if success
;		SF = 1 if failure (CX was non-zero on call)

	and	rwmode,not 1		;mark it as a read
	mov	al,CMD_INPUT
rdwr_block:
	push	cx
	call	blockif			;current drive, track,....
	pop	cx
	 jns	rdwrb5
	jcxz	rdwrb10			; test if any disk error detected
rdwrb5:
	ret				; skip if yes
rdwrb10:
	mov	ioexerr,al		; save extended error
	test	al,al			; is it write protect error ?
	 jnz	rdwrb20			;  we have dirty buffers we can't write
	call	discard_dirty		;  out, so throw 'em away
rdwrb20:
	mov	al,adrive		; if error on different drive
	cmp	al,physical_drv		;  treat error as media change
	 je	generate_critical_error	; if same drive, report error
	call	discard_all		; discard all buffers on drive
	call	discard_files		;  and flush files
	jmp	fdos_restart		; try to restart the instruction

generate_critical_error:
;-----------------------
; On Entry:
;	err_drv, rwmode, ioexerr set up
; On Exit:
;	None - we don't come back
;
	mov	al,ioexerr		; AL = BIOS error return byte
	cbw				;  make it a word
	cmp	ax,15			; only handle sensible errors
	 jb	gen_crit_err10		;  anything else becomes
	mov	ax,12			;  general failure
gen_crit_err10:
	neg	ax			; convert to our negative errors
	add	ax,ED_PROTECT		;  and start with write protect
	jmp	fdos_error		;  now return with error

eject

clus2sec:		; convert from cluster/offset to sector/offset
;--------
; On Entry:
;	AX = cluster
;	BX = byte offset in cluster
; On Exit:
;	DX:AX = sector
;	BX = byte offset in sector
;
	xchg	ax,cx			; remember cluster in CX
	xor	dx,dx
	xchg	ax,bx			; DX:AX = byte offset
	div	psecsiz			; AX = sector offset, DX = byte offset
	mov	bx,dx			; BX = byte offset in sector
	xchg	ax,cx			; AX = cluster, CX = sector offset
	dec	ax
	dec	ax			; forget about 2 reserved clusters
	mul	secperclu		; DX:AX = offset of cluster
	add	ax,datadd
	adc	dx,0			; DX:AX = offset of start of dir
	add	ax,cx			; DX:AX - add in sector offset
	adc	dx,0
	ret


	end

⌨️ 快捷键说明

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