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

📄 utils.fdo

📁 一个dos操作系统DRDOS的源码
💻 FDO
📖 第 1 页 / 共 5 页
字号:
	mov	cx,8			; remainder of up to 7 characters
	lea	si,DNAME[bx]		; SI -> directory name
	call	unparse_field		; copy name, strip trailing blanks
	mov	al,'.'
	stosb				; add the dot for start of extension
	push	di			; remember where extention starts
	mov	cx,3			; copy 3-char extension
	lea	si,DNAME+8[bx]		; SI -> directory extention
	call	unparse_field		; copy extension, strip trailing blanks
	pop	ax			; recover start of extension
	cmp	ax,di			; did we generate extension?
	 jne	unparse1		; skip if we did
	dec	di			; else eat the '.'
unparse1:
	xor	ax,ax
	stosb				; NUL-terminate the name
	pop	bx			; ES:BX -> base of name
	cmp	es:byte ptr [bx],05h
	 jne	unparse2		; if not mapped E5 (deleted entry/Kanji)
	mov	es:byte ptr [bx],0E5h	; else map back to E5 for Kanji support
unparse2:
	ret

unparse_field:
;-------------
;	entry:	DS:SI -> disk buffer
;		ES:DI -> ASCIIZ name to build
;		CX = field length
;	On Exit:
;		ES:DI -> end of name
;		BX preserved

	push	si			; save start of field
	add	si,cx			; SI -> end of field
	inc	cx			; one extra for LOOPE dec
unprsf10:
	dec	si			; lets look at the previous char
	cmp	ds:byte ptr [si],' '	; trailing space ?
	loope	unprsf10
	pop	si			; SI = start of field
	rep	movsb
	ret


path_error:
	jmp	fdos_ED_PATH		; return "invalid path" error

mkspace_parent:
;--------------
; save_area contains the parental name, DX bytes long. We wish to insert it
; into an ASCIIZ string so make DX bytes of space at ES:DI.
; On Entry:
;	ES:DI -> ASCIIZ, DX = byte count
; On Exit:
;	DS:SI -> parents name, CX = length of parent (DX on entry)
;
	mov	al,0			; find end of name
	mov	cx,128			; max. path length
	repne	scasb			; scan for end of path
	neg	cx
	add	cx,128			; CX = string length including NUL
	mov	ax,cx
	add	ax,dx
	cmp	ax,64
	 ja	path_error
	dec	di			; ES:DI -> '\0'
	mov	si,di			; SI -> source of copy
	add	di,dx			; point to beyond insertion
	push	ds
	push	es ! pop ds		; move string backwards to make space
	std ! rep movsb ! cld		; for directory name
	pop	ds
	mov	cx,dx			; CX = length of new directory name
	mov	si,offset save_area	; SI -> unparsed name
	ret

;	find parent directory starting with cluster AX
;	entry:	AX = cluster of parent to find
;	exit:	ZF = 1 if not found (shouldn't happen)
;			-or-
;		ZF = 0 if found, BX=DIRP -> dir entry

find_parent:
	mov	blk,ax			; save the block number
	push ds ! pop es
	mov	di,offset info_fcb+1
	mov	ax,'..' ! stosw		; file name is '..'
	mov	al,' '			; pad with spaces
	mov	cx,9 ! rep stosb
	call	finddfcbf		; find pointer to parent
	 jz	fndpar2			; shouldn't happen...
	call	open_dir		; go up one level
	 jc	fndpar3			; screwed up by security...
	call	setenddir		; search from beginning
fndpar1:
	sub	cx,cx
	call	getdir			; find next directory entry
	 jz	fndpar2			; end of directory
	mov	al,DNAME[bx]		; check if deleted file
	cmp	al,0E5h
	 je	fndpar1			; skip empty slots
	cmp	al,0
	 je	fndpar2			; end of directory
	test	DATTS[bx],DA_DIR	; try to find directory
	 jz	fndpar1			; skip plain files
	mov	ax,DBLOCK1[bx]		; get starting cluster
	cmp	ax,blk
	 jne	fndpar1
fndpar3:
	or	ax,0FFFFh		; force non-zero condition
fndpar2:
	ret				; ZF = 0 if found

eject
path_prep_chk:
;-------------
;	Run down the path and parse final name
;	exit:	ds:dx -> info_fcb parsed at path end

	call	path_prep		; prepare the path
	call	chk_no_dev		; devices not allowed
chk_no_dot_or_wild:
;------------------
	call	chk_no_dot		; no subdirs entries either
;	jmp	chk_no_wild		; wild cards not allowed

eject
chk_no_wild:		; make sure path doesn't contain wild cards
;-----------		;  (or is all spaces)
	call	check_no_wild		; error if any wildcards
	 jne	check_no_wild_ret	;  or if all spaces
	jmp	fdos_ED_FILE		; return "invalid filename"

check_no_wild:		; make sure path doesn't contain wild cards
;-------------		;  (or is all spaces) ZF set on problem
	push	es
	push	ds ! pop es		; ES -> SYSDAT
	mov	di,offset info_fcb+1
	mov	cx,11
	mov	al,'?'			; scan for wild cards
	repne	scasb
	 je	check_no_wild_exit	; skip if wild cards found
	mov	di,offset info_fcb+1
	mov	cx,11
	mov	al,' '			; scan for all spaces
	repe	scasb			; ZF set if a problem
check_no_wild_exit:
	pop	es
check_no_wild_ret:
	ret


chk_for_root:
;------------
; On Entry:
;	info_fcb -> name of failed search
;	fdos_hds -> dir we searched in
; On Exit:
;	ZF set if a search for root (or '.' in root)
;
	cmp	fdos_hds_blk,0		; are we in the root ?
	 jne	chk_for_root10		; no, no further checks required
	push ds ! pop es
	mov	di,offset info_fcb+1
	mov	al,'.'			;  check for root
	scasb				; is it a '.' entry ?
	 jne	chk_for_root10
	mov	cx,8+3-1
	mov	al,' '
	repe	scasb			; is it all spaces ?
chk_for_root10:
	ret


;	Parse a pathname into an info_fcb
;	entry:	es:si -> asciiz string
;		AX = drive code
;	exit:	es:si -> next asciiz name in path
;		dx -> fcb
;		CY clear, AL = 0 if end of string
;		CY set, AX = error code

parse_path:
;----------
	push	ds ! push  es
	pop	ds ! pop   es

	call	clear_info_fcb		; initialise to blanks and drive AL

	mov	dx,offset info_fcb	; use a scratch fcb
	mov	di,dx			; dx saves initial di
	inc	di

	mov	ax,[si]			; check first two chars
	cmp	al,'.'			; special case:  if name = '.'
	 jne	parse_path20		;   then we parse it differently
	movsb				; copy the '.'
	cmp	ah,'.'			; special case:  if name = '..'
	 jne	parse_path10		;   then we parse it differently
	movsb				; copy '..'
parse_path10:
	lodsb				; get next char
	cmp	al,' '			; skip all spaces
	 je	parse_path10
	jmps	parse_path30		; now exit as normal

parse_path20:
	call	check_delim		; if first char = delimeter
	 je	parse_path30		;   then only allow '\'

;	filename begins with a legal char, parse it normally

	mov	di,dx
	inc	di			; di -> fcb name field
	mov	cx,8			; length of name field
	call	parse_one		; parse just the name
	mov	di,dx			; DI -> FCB
	cmp	es:byte ptr 1[di],0E5h	; is first character E5?
	 jne	parse_path30		; skip if not
	mov	es:byte ptr 1[di],05h	; else make it internal synonym
parse_path30:
	cmp	al,'.'
	 jne	parse_path40		; skip if no extension
	add	di,9			; di -> fcb ext field
	mov	cx,3			; length of ext field
	call	parse_one		; parse just extension
parse_path40:
if PASSWORD
	cmp	al,';'			; check if password specified
	 jne	parse_path50		; skip if no password
	mov	di,offset password_buffer
	mov	cx,8			; length of password field
	call	parse_one		; parse just password
	push	ax
	push ds ! push si
	push ss ! pop ds		; DS:SI -> ASCII password
	mov	si,offset password_buffer
	call	hash_pwd		; AX = encrypted password
	mov	local_password,ax	; remember it in case we need it
	pop si ! pop ds
	pop	ax
endif
parse_path50:
	test	al,al			; a NUL is OK
	 jz	parse_path90
	call	check_slash		; if terminator != '\' or '/',
	stc				; assume an error
	 jne	parse_path80		; report it if so
parse_path60:
	lodsb				; get next character
	call	check_delim		; we expect a normal character
	 jne	parse_path80		;  here - exit if we've got one
	call	check_slash		; swallow '\'s at this point and leave
	 je	parse_path60		;  other delimiters for next time
	cmp	al,'.'			; trailing '\.' ?
	 jne	parse_path75
	mov	cx,si			; remember position of '.'
parse_path70:
	lodsb				; now discard trailing spaces
	cmp	al,' '
	 je	parse_path70		; keep going until we lose all spaces
	test	al,al			; stop at a NUL
	 jz	parse_path50
	call	check_slash		; if it's a '\' try again
	 je	parse_path50
	mov	si,cx			; retract to the '.'
parse_path75:
	mov	al,'\'			; return '\' as the delimiter
	clc				;  and exit with no problems
parse_path80:
	dec	si			; retract a byte (CY unaffected)
parse_path90:
	push  ds  !  push  es
	pop   ds  !  pop   es
	ret



	Public	parse_one
	
;	Parse a single name or extension
; On Entry:
;	DS:SI -> asciiz name
;	ES:DI -> start of fcb field
;	CX = field size
; On Exit:
;	AL = last char parsed
;
; nb. make no assumptions about DS and ES
;

parse_one:
	lodsb				; grab asciiz char
	cmp	al,'*'			; if char = *, then fill
	 jz	parse_one_wild		;   rest of field with '?'
	call	check_delim		; if char is not delimiter,
	 jnz	parse_one_char		;   then move it to fcb
	ret				; if delimiter, return

parse_one_wild:
	mov	al,'?'
	rep	stosb			; after filling
	jmps	parse_one_ignore	; skip until a delimiter

parse_one_char:
if KANJI
	call	dbcs_lead		; is it 1st byte of Kanji pair?
	 jnz	parse_one_skip		; skip if straight 8-bit
	inc	si			; assume both chars discarded
	dec	cx			; we will copy 2 bytes
	 jcxz	parse_one_ignore	; ignore both if only room for one
	stosb				; thats the first byte
	dec	si			; point at 2nd again
	lodsb				; get the 2nd byte
parse_one_skip:
endif
	stosb				; send char to fcb
	loop	parse_one		; get another character from ASCIIZ string
parse_one_ignore:
	lodsb
	call	check_delim		; ignore up to next delimiter
	 jnz	parse_one_ignore
	ret

;
;
;	Check for a path name delimiter
;	entry:	AL = ASCIIZ char
;	exit:	all registers preserved
;		ZF = 1 if char is a delimeter
;		ZF = 0 if char is legal in file names

	Public	check_delim

check_delim:
;-----------
	cmp	al,' '			; if any printable char,
	 jae	check_delim_char	;   then skip
	cmp	al,al			; set zf
	ret

check_delim_char:
if KANJI
	call	dbcs_lead		; if it's 1st of kanji pair
	 jne	check_delim10		; DON'T upper case it
	test	al,al			; clear zf
	ret				; (should really check the 2nd byte)
check_delim10:
endif
	call	toupper			; make it upper case
	push es ! push di ! push cx
	push cs ! pop es
	lea	di,delim_string		; es:di -> delimeters
	mov	cx,length delim_string
	cld
	repnz	scasb			; match al against the list
	pop cx ! pop di ! pop es
	clc				; never return cf set
	ret				; with zf set by scasb

delim_string	db  ':.;,=+\<>|/"[]'	; DOS delimeters


;	Check AX for '\\'

	Public	check_dslash

check_dslash:
	xchg	al,ah
	call	check_slash
	xchg	al,ah
	 jne	check_slash_done
;	jmp	check_slash

;	Check delimeter character for '\' or '/'
;	entry:	al = char
;	exit:	zf = 1 if either slash

check_slash:
	cmp	al,'\'			; if first char is a backslash
	 jz	check_slash_done	;   or a frontslash, then
	cmp	al,'/'			;   return with zf set
check_slash_done:
	clc				; never return cf set
	ret

;	Convert character to upper case
;	WARNING - may be called with DS <> SYSDAT

toupper:
;-------
	test	al,al
	 js	toupper_intl
	cmp	al,'a'
	 jb	isupper
	cmp	al,'z'
	 ja	isupper
	sub	al,'a'-'A'
isupper:
	ret

toupper_intl:
	callf	ss:intl_xlat		; call international upper case vector
	ret

eject
kill_file:	; release clusters for file/dir and delete entry
;---------
	mov	bx,dirp			; get pointer to directory entry
if DELWATCH
	call	hdsblk			; AX = directory root cluster
	xchg	ax,dx			; DX = dir cluster
	mov	cx,dcnt			; CX = directory index for entry
	mov	ah,DELW_DELETE		; we are about to delete this dir
	mov	al,physical_drv		;  directory entry so give delwatch
	callf	ss:fdos_stub		;  a chance to make it pending delete
	 jnc	kill_file10		; delwatch took it - just update dir
endif
	mov	al,0E5h			; deleted file mark
	xchg	al,DNAME[bx]		; delete the directory entry
	mov	DUNDEL[bx],al		; save 1st letter for UNDEL command
	mov	ax,DBLOCK1[bx]		; get starting block #
	call	delfat			; release all clusters
kill_file10:
	jmp	flush_dirbuf		; update the directory
					; done it! (DIR/FAT still dirty)
eject

mustbe_nolbl:
;------------
; On Entry:
;	None
; On Exit:
;	Only returns if no label exists
;	forces us to root of drive
;
	push	ds ! pop es		; ES = DS for string ops
	mov	si,offset info_fcb+1
	mov	di,offset save_area	; SI->search name, DI->save area
	mov	cx,11
	push	di			; save save_area
	push	si			; save info_fcb+1
	push	cx			; save length
	rep	movsb			; copy search name into save area
	pop	cx			; CX = length (11)
	pop	di			; DI = info_fcb+1
	push	di
	push	cx
	mov	al,'?'			; now fill info_fcb with wildcards
	rep	stosb
	call	find_labelf		; look for a volume label
	pop	cx			; CX = length (11)
	pop	di			; DI = info_fcb+1
	pop	si			; SI = save_area
	push	ds ! pop es		; ES = DS for string ops
	rep	movsb			; restore info_fcb
	 jnz	mustbe_nolbl10		; if we found a label bail out
	ret
mustbe_nolbl10:
	jmp	fdos_ED_ACCESS		; return access denied

find_labelf:				; find label only
;-----------				; forces us to root
; On Entry:
;	None
; On Exit:
;	ZF clear if volume label found
;	dirp/dcnt tell where label is
;
	call	setenddir		; start from beginning
;	jmp	find_label

⌨️ 快捷键说明

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