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

📄 dirs.a86

📁 一个dos操作系统DRDOS的源码
💻 A86
📖 第 1 页 / 共 2 页
字号:
title 'DIRS - dos directory support'
;    File              : $DIRS.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$   
;    DIRS.A86 1.13 94/12/01 13:16:24
;    changed error code if directory entry cannot be allocated;    
;    DIRS.A86 1.12 93/08/27 18:49:04
;    hash code fixup on previously unused entries resets hash count
;    pcformat bug where an extra (zero-length) command.com was left on disk
;    ENDLOG
;
;	Date	   Who	Modification
;	---------  ---	---------------------------------------
;   19 Aug 91 Initial version created for VLADIVAR

eject

include	bdos.equ
include i:mserror.equ
include	i:fdos.equ

eject
PCMODE_DATA	dseg
if DELWATCH
	extrn	fdos_stub:dword		; for calling delwatch TSR
endif

BDOS_DATA	dseg	word
	extrn	adrive:byte
	EXTRN	clsize:WORD
	extrn	diradd:word
	extrn	dirinroot:word
	EXTRN	dirperclu:WORD
	EXTRN	dosfat:WORD
	extrn	hashroot:dword
	extrn	hashmax:word
	EXTRN	info_fcb:BYTE
	extrn 	lastcl:word
	extrn	psecsiz:word

eject

hash		rw	2		; hash code work area

; The dirbcb says what is in the local dirbuf

dirbcb		db	0ffh		; drive of dirbuf entry
dirbcb_cl	dw	0		; cluster of dirbuf entry
dirbcb_dcnt	dw	0		; directory index of dirbuf entry
dirbcb_block	rw	2		; block of dirbuf entry
dirbcb_offset	dw	0		; byte offset in block of dirbuf entry


	public	dirbuf
dirbuf		rb	32		; local directory buffer

	public	dirp
dirp		dw	0		; directory entry pointer

	public	dcnt
dcnt	dw	0			; directory index count

	public	finddfcb_mask
finddfcb_mask	dw	0800h		; hi byte = reject DA_VOLUME attribs
					; lo byte = accept non-0 start clusters
					; 00FF = include labels, but not
					;	pending deletes
					; 0000 = include everything
	public	chdblk
chdblk		dw	0		; current cluster # of directory


BDOS_CODE	cseg
	extrn	alloc_cluster:NEAR
	extrn	clus2sec:near
	extrn	hdsblk:near		; get current directory block
	extrn	fdos_error:NEAR
	extrn	fixfat:NEAR
	extrn	getnblk:NEAR
	extrn	locate_buffer:near
	extrn	update_dir:NEAR
	extrn	update_fat:NEAR
	extrn	zeroblk:near

eject


	public	allocdir
	public	discard_dirbuf
	public	finddfcb
	public	finddfcbf
	public	fill_dirbuf
	public	flush_dirbuf
	public	getdir
	public	hshdscrd
	public	mkhsh
	public	setenddir
eject

;----------
fill_dirbuf:	;get 32 byte directory entry
;----------
; On Entry:
;	AX = cluster to read (0=root)
;	BX = dir within cluster
; On Exit:
;	DI -> dirbuf entry

	call	discard_dirbuf		; invalidate block in case of error
	mov	dirbcb_cl,ax		; remember which cluster
	mov	dirbcb_dcnt,bx		;  and dir entry we want
	test	ax,ax			; are we in the root ?
	 jz	fill_dirbuf10
	mov	cl,FCBSHF
	shl	bx,cl			; BX = byte offset in cluster
	call	clus2sec		; DX:AX -> sector
	jmps	fill_dirbuf20		; BX = offset in sector
fill_dirbuf10:
	mov	ax,FCBLEN
	mul	bx			; DX:AX = byte offset
	div	psecsiz			; AX = sector offset, DX = byte offset
	mov	bx,dx			; BX = byte offset in sector
	xor	dx,dx
	add	ax,diradd		; add in start of root dir
	adc	dx,dx
fill_dirbuf20:
	mov	dirbcb_block,ax		; we want this sector
	mov	dirbcb_block+WORD,dx
	mov	dirbcb_offset,bx
	xchg	ax,dx			; DX = low word of sector
	mov	ah,al			; AH = low byte of high word
	push	bx			; save byte offset in sector
	mov	cx,0FF00h+BF_ISDIR	; locate directory sector
	call	locate_buffer		; ES:SI -> BCB_
	pop	bx			; BX = offset within sector
	push es ! pop ds		; DS:SI -> buffer control block
	lea	si,BCB_DATA[si+bx]	; DS:SI -> data in buffer
	push ss ! pop es
	mov	di,offset dirbuf	; ES:DI -> dir buffer
	push	di
	mov	cx,32/WORD		; copy into local buffer
	rep	movsw
	pop	di			; DI -> dir buffer
	push ss ! pop ds
	mov	al,adrive		; remember where we are
	mov	dirbcb,al		;  so we can write it back
	ret


;------------
flush_dirbuf:
;------------
	mov	al,0FFh
	xchg	al,dirbcb		; do we have anything to flush ?
	cmp	al,adrive
	 jne	flush_dir20		; skip if invalid contents
	mov	si,offset dirbcb_block
	lodsw				; get low word of block
	xchg	ax,dx			; put it in DX where it belongs
	lodsw				; get high word of block
	mov	ah,al			; AH:DX -> block to find
	mov	cx,0FF00h+BF_ISDIR	; look for directory
	call	locate_buffer		; locate physical sector
	or	es:BCB_FLAGS[si],BF_DIRTY; mark this buffer as modified
	mov	bx,dirbcb_offset	; BX = offset within buffer
	lea	di,BCB_DATA[si+bx]	; ES:DI -> offset in buffer

	mov	al,es:[di]		; AL = 1st character of dir entry

	mov	si,offset dirbuf	; get CP/M buffer address
	mov	cx,32/WORD
	rep	movsw			; copy modified entry back

	push	ax
	xor	dh,dh			; we only want HCB_ if it's there
	mov	cx,dirbcb_cl		;  and it's this cluster
	call	find_hcb		; does an HCB_ exist for this entry ?
	pop	ax
	 jc	flush_dir20		; no, skip update
	mov	di,dirbcb_dcnt		; we want this dir entry
	cmp	di,es:HCB_CNT[bx]	; is this within the hashed entries ?
	 jae	flush_dir20		;  no, skip the fixup

	test	al,al			; are we using a never used entry ?
	 jnz	flush_dir10		; if so don't trust subsequent hash
	inc	di			;  codes as they have never been read.
	mov	es:HCB_CNT[bx],di	; Truncate table to force a read of the
	dec	di			;  next dir entry (which will normally
flush_dir10:				;  also be never used)
	shl	di,1			; DI = offset of hashed entry
	lea	di,HCB_DATA[bx+di]
	mov	si,offset dirbuf	; this is the dir entry
	call	mkhsh			; AX = hash code of our entry
	stosw				; update hash code for dir entry
flush_dir20:
	push	ds ! pop es		; ES = local data segment
	ret

;--------------
discard_dirbuf:
;--------------
	mov	dirbcb,0FFh		; invalidate dirbuf
	ret


;--------
rd_pcdir:
;--------
;	Exit:	AX = offset of directory entry
;		   = 0 if end of directory


	mov	bx,dcnt
	inc	bx
	mov	dcnt,bx		; dcnt=dcnt+1
	call	hdsblk		; AX = current directory block
	 jz	rd_pcdir40	; skip if we're at the root

; we we in a subdirectory - lets follow the chain

	xchg	ax,cx		; keep subdir cluster in CX
	mov	ax,FCBLEN	; AX = size of dir entry
	mul	bx		; DX:AX = offset of set entry we want
	div	clsize		; AX = # clusters to skip, DX = offset in cluster
	xchg	ax,dx		; DX = # to skip, AX = offset in cluster
	xchg	ax,cx		; AX = start of chain, CX = offset in cluster
	xchg	bx,cx		; BX = offset in cluster, CX = dcnt
	 jcxz	rd_pcdir20	; 1st subdir entry, we are already there
	mov	cx,chdblk	; do we already know where we are ?
	 jcxz	rd_pcdir10	;  if not trace from start of chain
	xchg	ax,cx		; AX = cluster of last dir entry
	test	bx,bx		; have we moved onto next cluster?
	 jnz	rd_pcdir20	; no, trust me..
	mov	dx,1		; move on to next entry in the chain
rd_pcdir10:
	or	dx,dx		; skip along chain until we arrive
	 jz	rd_pcdir20	;  at the destination cluster
	dec	dx
	push	bx
	push	dx
	call	getnblk		; AX = next cluster in chain
	pop	dx
	pop	bx
	cmp	ax,lastcl	; have we fallen off the end of the chain ?
	 jbe	rd_pcdir10
	jmps	rd_pcdir30	; yes, set end of directory
rd_pcdir20:
	mov	chdblk,ax	; remember this cluster for next time
	mov	cl,FCBSHF	; to divide by fcb size
	shr	bx,cl		; BX = dir offset in cluster
	jmps	rd_pcdir50	;  now go and find the entry

rd_pcdir30:
	call	setenddir	; yes, set dcnt to end of directory
	jmps	rd_pcdir60

rd_pcdir40:
; we are in the root directory
	cmp	bx,dirinroot	; end of the root directory ?
	 jae	rd_pcdir30
rd_pcdir50:
	call	fill_dirbuf	;locate directory entry
	xchg	ax,di		; AX -> dir entry
	cmp	dcnt,ENDDIR
	 jnz	rd_pcdir70
rd_pcdir60:
	xor	ax,ax		; return 0 if endofdir
rd_pcdir70:
	mov	bx,ax
	ret


;---------
setenddir:	;set dcnt to the end of directory (dcnt = 0ffffh)
;---------
	mov	dcnt,ENDDIR
	mov	chdblk,0
	ret


chk_wild:	;check fcb for ? marks
;--------
; On Entry:
;	bx -> FCB
; On Exit:
;	ZF set if ? found
;	BX preserved
	push	ds ! pop es		; ES -> SYSDAT
	lea	di,byte ptr FNAME[bx]	; ES:DI -> name to scan
	mov	cx,11
	mov	al,'?'			; scan for wild cards
	repne	scasb
	ret

eject

eject
;---------
finddfcbf:	; Find matching directory fcb(dfcb) from beginning of directory
;---------
	call	setenddir	; set up for search first

;--------
finddfcb:	; Find matching directory fcb(dfcb)
;--------
	mov	cx,2

;------
getdir:
;------
;	entry:	CH  =	offset info_fcb	(always 0 except from rename)
;		CL  = 	search length
;			0 = return next fcb
;			1 = return empty fcb
;			2 = find match  (Based on info_fcb)
;			3 = find match?  Based on info_fcb
;
;	exit:	AX,BX,DIRP = pointer to dfcb
;			     0 = no match (end of directory)
;			     other = offset of requested directory entry
;		ZF = zero flag is set based on AX
;

;	Note:	The most common call for this function is with CX =
;		2 (match with name, not extent)  with 'dcnt' set to
;		0FFFFh  (search  from  beginning  of the  directory
;		(e.g.   open,  create,   delate,   rename,   etc.).
;		Therefore  we try  to optimize  directory  searches
;		using a dynamic hash table...

					;struct dirfcb *getdir(offset,srchl);

	cmp	dcnt,0FFFFh		;if ((dcnt == 0xffff) &&
	 jne	gtd_next
	mov	hash+2,cx		; Save off calling option
	xor	ax,ax			; hash code 0 for free entry
	cmp	cx,1			; what kind of search?
	 je	gtdo15			; CL=1: find free entry (AX=0)
	 jb	gtd_next		; CL=0: find any entry (unhashed)
	or	ch,ch			; name in INFO_FCB+1?
	 jnz	gtd_next		; no, unhashed search
	mov	bx,offset info_fcb
	call	chk_wild		; wildcards used in search?
	 jz	unhshd1			; yes, can't use hashing
	mov	si,offset info_fcb+1	; else compute hash code
	call	mkhsh			;    for name to find
gtdo15:
	mov	hash,ax			; save it for search
	call	hdsblk			; get directory block
gtdo3:
	push	ax			; save dir block for later
	call	hashsrch		; try and use hashing to find a match
	 jnc	gtdo4			; look closer if we get possible match
	add	dcnt,ax			;  else skip known non-matches
	pop	ax			; recover current dir block
	test	ax,ax			; if we are in the root
	 jz	unhashed		;  we must search the hard way
	xchg	ax,bx
	mov	ax,dcnt			; should we go onto next cluster ?
	inc	ax			; only if next entry is the start
	xor	dx,dx			;  of a cluster
	div	dirperclu
	xchg	ax,bx
	test	dx,dx			; at start of cluster ?
	 jnz	unhashed
	call	getnblk			; onto next cluster until we are
	cmp	ax,lastcl		;  at the end of the chain
	 jbe	gtdo3
	jmps	unhashed		; out of luck
gtdo4:
	add	dcnt,ax			; we have found a match, so start
	pop	ax			;  search here
;	jmps	unhashed
unhashed:				;   /* locate entry */
	mov	chdblk,0
unhshd1:
	mov	cx,hash+2		;}
gtd_next:
;--------
	push	cx
	call	rd_pcdir		; Get Next DFCB
	pop	cx
gtd_exit:
	mov	dirp,ax			; assume this is the one
	mov	bx,ax
	or	ax,ax			; should we exit with not found ?

⌨️ 快捷键说明

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