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

📄 buffers.a86

📁 一个dos操作系统DRDOS的源码
💻 A86
📖 第 1 页 / 共 3 页
字号:
title 'BUFFERS - buffer handling routines'
;    File              : $BUFFERS.A86$
;
;    Description       :
;
;    Original Author   : DIGITAL RESEARCH
;
;    Last Edited By    : $CALDERA$
;
;-----------------------------------------------------------------------;
;    Copyright Work of Caldera, Inc. All Rights Reserved.
;      
;    THIS WORK IS A COPYRIGHT WORK AND CONTAINS CONFIDENTIAL,
;    PROPRIETARY AND TRADE SECRET INFORMATION OF CALDERA, INC.
;    ACCESS TO THIS WORK IS RESTRICTED TO (I) CALDERA, INC. EMPLOYEES
;    WHO HAVE A NEED TO KNOW TO PERFORM TASKS WITHIN THE SCOPE OF
;    THEIR ASSIGNMENTS AND (II) ENTITIES OTHER THAN CALDERA, INC. WHO
;    HAVE ACCEPTED THE CALDERA OPENDOS SOURCE LICENSE OR OTHER CALDERA LICENSE
;    AGREEMENTS. EXCEPT UNDER THE EXPRESS TERMS OF THE CALDERA LICENSE
;    AGREEMENT NO PART OF THIS WORK MAY BE USED, PRACTICED, PERFORMED,
;    COPIED, DISTRIBUTED, REVISED, MODIFIED, TRANSLATED, ABRIDGED,
;    CONDENSED, EXPANDED, COLLECTED, COMPILED, LINKED, RECAST,
;    TRANSFORMED OR ADAPTED WITHOUT THE PRIOR WRITTEN CONSENT OF
;    CALDERA, INC. ANY USE OR EXPLOITATION OF THIS WORK WITHOUT
;    AUTHORIZATION COULD SUBJECT THE PERPETRATOR TO CRIMINAL AND
;    CIVIL LIABILITY.
;-----------------------------------------------------------------------;
;
;    *** Current Edit History ***
;    *** End of Current Edit History ***
;
;    $Log$
;
;    BUFFERS.A86 1.13 94/11/30 16:26:08 
;    added support for using multiple FAT copies on reads if one fails    
;    BUFFERS.A86 1.12 93/08/06 16:19:11
;    make geblk public    
;    BUFFERS.A86 1.8 93/07/07 21:06:25
;    Smirnoff'd
;    BUFFERS.A86 1.6 93/03/16 22:30:29
;    UNDELETE support changes
;    BUFFERS.A86 1.5 93/03/05 18:00:26
;    Fix bug clearing cluster of new sub directory
;    ENDLOG

;	Date	   Who	Modification
;	---------  ---	---------------------------------------
;    9 Sep 91 Initial version created for VLADIVAR
;    3 mar 93 correct zeroblk bug

	NOLIST
	eject ! include i:fdos.equ
	eject ! include bdos.equ
	eject ! include i:doshndl.def
	eject
	LIST

eject
PCMODE_DATA	dseg

	extrn	current_ddsc:dword
if DELWATCH
	extrn	fdos_stub:dword
endif

BDOS_DATA	dseg	word

fatrec		rw	1		; current FAT record

fatbytl		rb	1		; low byte of split FAT entry
fatbyth		rb	1		; high byte of split FAT entry
split_fat	rb	1		; 0/FFh to indicate split entry

eject
	extrn	adrive:byte
	EXTRN	chdblk:WORD
	EXTRN	clsize:WORD
	EXTRN	cur_dma:WORD
	EXTRN	cur_dma_seg:WORD
	extrn	dosfat:WORD
	EXTRN	fatadd:WORD
	extrn	lastcl:word
	EXTRN	mult_sec:WORD
	EXTRN	nfatrecs:WORD
	EXTRN	nfats:WORD
	extrn	pblock:dword
	extrn	physical_drv:byte
	extrn	psecsiz:word
	extrn	rwmode:byte		; data/directory/FAT, read/write
	extrn	secperclu:word
	extrn	bcb_root:dword		; PCMODE disk buffer root
	extrn	deblock_seg:word

BDOS_CODE	cseg

	extrn	clus2sec:near
	extrn	discard_dirbuf:near
	extrn	fdos_error:near
	extrn	flush_dirbuf:near
	extrn	hshdscrd:near
	extrn	read_block:near
	extrn	select_adrive:near	; select drive AL
	extrn	write_block:near

	public	alloc_cluster		; allocate data block
	public	alloc_chain		; allocate a chain
	public	buffers_check		; check if buffers exist for this drive
	PUBLIC	delfat			; release data blocks
	PUBLIC	discard_all		; discard all buffers on ADRIVE
	public	discard_dir		; discard directory buffers on ADRIVE
	public	discard_dirty		; discard directory buffers on ADRIVE
	PUBLIC	fixfat			; set value of FAT entry
	public	flush_drive		; flush buffers to disk
	public	locate_buffer		; locate a buffer
	PUBLIC	update_dat		; flush write pending buffers
	public	update_ddsc_free	; count free blocks on drive
	PUBLIC	update_dir		; update directory entry
	PUBLIC	update_fat		; write out modified FAT records
	public	zeroblk			; zero cluster (MKDIR)
if DELWATCH
	public	allocate_cluster	; allocate free cluster on adrive
	public	change_fat_entry	; write a new value into the FAT
endif




update_ddsc_free:
;----------------
; make sure DDSC_FREE is up to date
; a by-product of this is to checksum the FAT, so we can spot changes
; of removable media
	push	es
	les	bx,ss:current_ddsc
	mov	cx,es:DDSC_FREE[bx]	; get current free space
	 jcxz	update_ddsc_free30	; if none recount to make sure
	inc	cx			; is count uninitialised ? (=FFFF)
	 jz	update_ddsc_free30	; if so better count the free space
update_ddsc_free10:
	pop	es
	ret

update_ddsc_free30:
; rebuild our free space count
	xor	ax,ax			; assume no free space yet
	lea	di,DDSC_BLOCK[bx]	; ES:DI -> DDSC_BLOCK
	stosw				; DDSC_BLOCK = 0
	stosw				; DDSC_FREE = 0
	inc	ax			; skip reserved block #'s 0 and 1
update_ddsc_free40:
	inc	ax			; move to next data block #
	cmp	ax,lastcl		; are we beyond end of disk
	 ja	update_ddsc_free10	; stop if all free blocks counted
	push	ax			; save current index
	call	getblk			; get contents of FAT entry, update ZF
	pop	ax			; restore current FAT index
	 jnz	update_ddsc_free40	; try next block if not free
	inc	es:DDSC_FREE[bx]	; one more free block
	jmps	update_ddsc_free40	; try next block



discard_dirty:
;-------------
;	This gets called after a write-protect error is returned

	mov	ah,BF_DIRTY		; discard dirty FAT, dir & data
	jmps	discard_buffers

discard_all:
;-----------
	mov	ah,BF_ISFAT+BF_ISDIR+BF_ISDAT
	jmps	discard_buffers		; discard all the buffers

discard_dir:
;-----------
	mov	ah,BF_ISDIR		; dir only, leave data and FAT
;	jmps	discard_buffers	

discard_buffers:
;---------------
;	entry:	adrive = drive to discard
;		AH = flags for type to discard i.e. BF_ISFAT, etc.

	mov	al,adrive		; get the work drive
	call	discard_dirbuf		; discard 32-byte directory buffer
	call	hshdscrd		; discard hashing info for drive
	les	si,bcb_root		; get first buffer
discard_buffers10:
	cmp	al,es:BCB_DRV[si]	; does the drive match?
	 jne	discard_buffers20	; try next one if not
	test	ah,es:BCB_FLAGS[si]	; does the type match?
	 jz	discard_buffers20	; try next one if not
	mov	es:BCB_DRV[si],0FFh	; else discard the buffer
	mov	es:BCB_FLAGS[si],0
discard_buffers20:
if DOS5
	mov	si,es:BCB_NEXT[si]	; get next buffer address
	cmp	si,word ptr bcb_root
else
	les	si,es:BCB_NEXT[si]	; get next buffer address
	cmp	si,0ffffh
endif
	 jne	discard_buffers10	; and repeat until all done
discard_buffers30:
	push	ds ! pop es		; restore ES and return
	ret


;-------------
buffers_check:
;-------------
;	entry:	AL = drive to check (preserved)
;		AH = flags
;	exit:	ZF = 1 if all buffers clean on this drive

	push	ds			; we use DS here cause it's quicker...
	lds	si,ss:bcb_root		; start with most recently used
buffers_check10:
	cmp	al,BCB_DRV[si]		; check if for different drive
	 jne	buffers_check20		;   skip if not our problem
	test	ah,BCB_FLAGS[si]	; test if its one we are looking for
	 jnz	buffers_check30		;   return with non-zero condition
buffers_check20:
if DOS5
	mov	si,BCB_NEXT[si]		; get next buffer address
	cmp	si,ss:word ptr bcb_root
else
	lds	si,BCB_NEXT[si]		; get next buffer address
	cmp	si,0ffffh
endif
	 jne	buffers_check10		; loop back if more to do
	xor	dx,dx			; set ZF = 1
buffers_check30:
	pop	ds			; restore DS after BCBs done
	ret


eject

;	entry:	AX = first block to release
;	exit:	AX and following released

delfat:			; release chain of clusters
;------
	cmp	ax,2			; is block number too small?
	 jb	delfat10		; yes, then stop it
	cmp	ax,lastcl		; is block number too large?
	 ja	delfat10		; yes, then stop it
	push	ax			; else save the number
	call	getblk			; get the next link
	xchg	ax,cx			; CX = link
	pop	ax			; AX = this block
	sub	bx,bx			; set it to 0000
	push	cx			; save the link for next pass
	call	fixfat			; release the block
	pop	ax			; AX = next block or end
	jmps	delfat			; try again until all released
delfat10:				; all blocks in chain freed
	ret


; On Entry:
;	AX = block to read
; On Exit:
;	AX = next FAT block index
;
	Public	getnblk

getnblk:				;UWORD getnblk(blk);
;-------
;
	push	ax
	call	getblk			; get current setting
	pop	bx
	 jz	getnblk10		; return if something there
	ret
getnblk10:
	mov	ax,dosfat		; if unallocated then allocate it
	push	ax
	xchg	ax,bx			; AX = blk, BX = i
	call	fixfat
	pop	ax
	mov	dx,ax			; DX = end of chain
	xor	cx,cx			; no blocks follow this one
	ret

; On Entry:
;	AX = block to read
; On Exit:
;	AX = contents
;	ZF = 1 if AX == 0000h (disk full)

	Public	getblk

;------
getblk:
;------
	push	es ! push bx
	call	fatptr			; get address of block AX in buffer
	mov	ax,es:[bx]		; get the word from FAT
	 jnz	getblk10		; skip if on odd address (must be 12 bit)
	cmp	dosfat,FAT12		; else check if 16 or 12 bit
	 je	getblk20		; skip if even 12 bit
	pop	bx ! pop es
	test	ax,ax			; update ZF
	ret

getblk10:
	shr	ax,1			; shift top 12 bits down
	shr	ax,1
	shr	ax,1
	shr	ax,1
getblk20:
	and	ax,0FFFh		; leave bottom 12 bits only
	pop	bx ! pop es
	ret



alloc_cluster:
;-------------
; On Entry:
;	AX = previous cluster (hint for desired start)
; On Exit:
;	AX = start of chain
;	CY set on failure
;
	mov	cx,1
;	jmp	alloc_chain

alloc_chain:
;-----------
; On Entry:
;	AX = previous cluster (hint for desired start)
;	CX = # clusters wanted
; On Exit:
;	AX = start of chain, 0 on failure
;	CY set on failure
;
; We want to allocate a chain of CX clusters, AX was previous cluster
; We return with CY clear and AX = 1st cluster in chain on success,
; CY set on failure
;
; When allocating a new chain we first ask SSTOR how much physical space is
; present on the disk. Until SSTOR reports at least 2 clusters free we
; repeatedly call DELWATCH to purge files and recover space. If DELWATCH is
; unable to free space we return "disk full".
;
; When allocating a block we normally are normally given a target block to
; start searching from. We allow DELWATCH to alter this value when it frees
; space to optimise the search.
;
	push ax ! push cx		; save entry parameters
	call	update_ddsc_free	; make sure DDSC_FREE is correct
if DELWATCH
alloc_chain10:
	pop dx ! push dx		; DX = clusters wanted
	les	bx,ss:current_ddsc
	mov	cx,es:DDSC_FREE[bx]	; CX = clusters available
	mov	al,adrive		; AL = current drive
	cmp	cx,dx			; do we have enough room in the FAT ?
	 jb	alloc_chain20		; if not ask DELWATCH to purge
	mov	ah,SSTOR_SPACE		; does Superstore have room for data?
	callf	ss:fdos_stub		; call stub routine
	test	cx,cx			; are we out of space ?
	 jnz	alloc_chain40		; no, go ahead and allocate the chain
	mov	es:DDSC_FREE[bx],cx	; SSTOR says there's none, lets agree
	call	update_fat		; flush FAT to bring SSTOR up to date
	jmps	alloc_chain10		; go round again and ask DELWATCH to
					;  free up some more space
					; we loop until either SSTOR says OK
					;  or DELWATCH frees all it can
alloc_chain20:
	mov	ah,DELW_FREECLU		; ask DELWATCH to purge a file
	callf	ss:fdos_stub		; call stub routine
	cmp	cx,es:DDSC_FREE[bx]	; can DELWATCH free up any space ?
	 jne	alloc_chain10		; yes, go and try again
alloc_chain30:
	pop cx ! pop ax			; failure, restore stack
	jmps	alloc_chain80		;  and exit in failure

alloc_chain40:
endif
	pop cx ! pop ax			; restore entry parameters
	push	cx			; save # required
	call	allocate_cluster	; try to allocate 1st cluster
	pop	cx			; recover # required
	test	ax,ax			; could we ?
	 jz	alloc_chain80
	dec	cx			; one less to allocate

	push	ax			; save head of chain
	 jcxz	alloc_chain60
alloc_chain50:
	push	cx

	push	ax			; save current end of chain
	call	allocate_cluster	; allocate another cluster
	pop	bx			; BX = end of chain

	test	ax,ax			; could we allocate anything ?
	 jz	alloc_chain70		; no, bail out and free partial chain

	xchg	ax,bx			; AX = previous cluster, link cluster
	push	bx			;  BX to end of the chain
	call	fixfat
	pop	ax			; AX = new end of chain

	pop	cx
	loop	alloc_chain50
alloc_chain60:
	pop	ax			; return the start of the chain as it's
	clc				;  long enough now...
	ret

alloc_chain70:
; We haven't enough free clusters - lets free what we allocated so far
	pop	cx			; discard count
	pop	ax			; AX = start of chain
	call	delfat			; release the chain
alloc_chain80:
	xor	ax,ax
	stc				; we couldn't manage it
	ret

allocate_cluster:
;----------------
; On Entry:
;	AX = cluster to start from (AX = none known)
; On Exit:
;	AX = cluster allocated
;
	test	ax,ax			; previous block known?

⌨️ 快捷键说明

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