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

📄 dkutil.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
;	clears b$PTRFIL
;	none
;Uses:
;	none
;Exceptions:
;	list of possible abnormal exit points (i.e. FCERR)
;*******************************************************************************

				;NOTE!: This routine has a manually
				;generated epilogue due to variable number
				;of parameters.  If you change the prologue,
				;here you must also change the epilogue
				;further down.

cProc	B$CLOS,<PUBLIC,FAR>	; don't save any registers here
	ParmW	UnknownParam	;potential parameter
	ParmW	cParam		;parameter count
cBegin				;generate stack frame
	PUSH	SI		;save SI and DI explicitly to avoid confusion
	PUSH	DI		
	LEA	DI,UnknownParam ;DI points to the one below parameter count
	MOV	CX,cParam	;CX=*cParam
	JCXZ	NoParm		;no parameter, close all files
ParmLoop:
	MOV	BX,[DI] 	;file number in BX
	CALL	B$LHFDBLOC	;SI=*FDB (NZ) if file found
	JZ	NextParm	;file not opened, go next one
	CALL	DoClose 	;process the close
NextParm:
	INC	DI		;next parameter
	INC	DI
	LOOP	ParmLoop	;loop until all done
	JMP	SHORT ExitProc	;clear stack and exit
NoParm:
	CALL	B$CLOSF		;close all files (destroys all registers)
ExitProc:
	MOV	BX,DI		; BX = old SP
	POP	DI		; get back DI
	POP	SI		;get back SI
	MOV	AX,[BP+2]	; [DX:AX] = return address
	MOV	DX,[BP+4]	
	MOV	BP,[BP] 	; get back old BP
	MOV	SP,BX		; clean the stack LAST, so that interrupts
				; don't bash stuff below the SP
	MOV	[b$PTRFIL],0	;clear b$PTRFIL
	PUSH	DX		;put return address back on stack
	PUSH	AX
	RET			;return to caller
cEnd	nogen			;no code generated

	SUBTTL	Runtime Internal routines
	page

;_____	File Dispatch Routines	-------------------------------------------

	page
;***
;B$$RCH - Read a byte
;DBCS-callback
;
;Purpose:
;	Reads a byte of data from the device designated by b$PTRFIL.
;	If we are handling KANJI characters, we have to disassemble
;	them as they come from B$STDGET (when b$PTRFIL == 0).  B$STDGET
;	will return the entire 2 byte character, while we only want to
;	return a single byte.
;
;Entry:
;	b$PTRFIL set properly
;
;Exit:
;	AL = character
;	AH = trashed
;	PSW.C set if no char ready
;	PSW.Z set if no char ready and FO_REDIRECT
;		(this will only happen if redirected input completely read)
;Uses:
;	Per Convention
;
;Preserves:
;	BX, CX, DX
;
;Exceptions:
;	None.
;****
cProc	B$$RCH,<NEAR,PUBLIC>
cBegin
	PUSH	SI
	MOV	SI,b$PTRFIL
	OR	SI,SI
	JNZ	getch1

	TEST	b$IOFLAG,RED_INP ;Input redirected ?
	jz	getch0		;brif not
	call	B$STDGET	;AX = value, PSW.Z set = no valid byte
	POP	SI
	ret
getch0:
	CALL	B$TTY_SINP	;Console input
	JMP	SHORT GETCH2

GETCH1:
	MOV	AH,DV_SINP	;file input
	CALL	B$PtrDispatch

GETCH2:
	POP	SI		; restore register
	JC	GETCH3		;branch if PSW.C set
	OR	SP,SP		; Clear PSW.Z
	RET
GETCH3:
	OR	SP,SP		; clear PSW.Z (and PSW.C)
	STC			; but set PSW.C again
cEnd				; return to caller

;***
; B$$WCH - Output character in (AL)
;
;	Inputs:
;		al = character to output
;		b$PTRFIL
;		DV_SOUT
;	Outputs:
;		none
;	Modifies:
;		ah
;	Exceptions
;		exit through B$TTY_SOUT
;		Bad file mode for binary files
;****
cProc	B$$WCH,<NEAR,PUBLIC>
cBegin
	PUSH	SI
	MOV	SI,b$PTRFIL
	OR	SI,SI
	JNZ	putch1

; Redirected output must be done after two byte codes collected. Move check
; for redir out to B$TTY_SOUT.

	POP	SI
	JMP	B$TTY_SOUT	;Console output

PUTCH1:
	FDB_PTR ES,SI,SI		;(ES:)[SI] = *FDB
	TEST	FileDB.FD_MODE,MD_BIN	;binary mode?
	JZ	NotBinary
	JMP	B$ERR_BFM	;brif so -- bad file mode
NotBinary:
	MOV	AH,DV_SOUT

ptrdsp: CALL	B$PtrDispatch	;Call Dispatch |Moved here from
	POP	SI		;Restore SI    |B$$BCH which is
cEnd				;and return    |no longer in existance

	page
;***
; B$$POS - Get current file position
;
;	Inputs:
;		b$PTRFIL
;		DV_GPOS
;	Outputs:
;		ah = file position
;	Exceptions
;		Exit through B$TTY_GPOS or PTRDSP
;****
cProc	B$$POS,<NEAR,PUBLIC>
cBegin
	PUSH	SI
	MOV	SI,[b$PTRFIL]
	OR	SI,SI
	JNZ	getps1

	POP	SI
	JMP	B$TTY_GPOS	;Get TTY position

getps1: MOV	AH,DV_GPOS	;Get position
	JMP	ptrdsp
cEnd	<nogen>

	page
;***
; B$$WID - Get current file width
;
;	Inputs:
;		b$PTRFIL
;		$DV_GWID
;	Outputs:
;		ah = file width
;	Exceptions:
;		Exit though B$TTY_GWID or PTRDSP
;****
cProc	B$$WID,<NEAR,PUBLIC>
cBegin
	PUSH	SI
	MOV	SI,[b$PTRFIL]
	OR	SI,SI
	JNZ	getwd1

	POP	SI
	JMP	B$TTY_GWID

getwd1: MOV	AH,DV_GWID
	JMP	ptrdsp
cEnd	<nogen>

	SUBTTL
	PAGE
;***
;   B$BIN - block input
;							;block transfer support
;	Entry	[bx] =	offset of destination		;for bload, bsave
;		[cx] =	maximum number of bytes to read
;		[dx] =	DS of destination
;	exit	?
;****
cProc	B$BIN,<NEAR,PUBLIC>
cBegin
	PUSH	SI
	MOV	SI,[b$PTRFIL]
	OR	SI,SI
	JNZ	blkin1

	POP	SI
	JMP	B$TTY_BLKIN

blkin1: MOV	AH,DV_blkin
	JMP	ptrdsp
cEnd	<nogen>

;***
;B$BOT - Block output
;							;block transfer support
;	Entry	[bx] =	offset of destination		;for bload, bsave
;		[cx] =	number of bytes to write
;		[dx] =	DS of destination
;****

cProc	B$BOT	<NEAR,PUBLIC>
cBegin
	PUSH	SI
	MOV	SI,[b$PTRFIL]
	OR	SI,SI
	JNZ	blkot1

	POP	SI
	JMP	B$TTY_BLKOUT

blkot1: MOV	AH,DV_blkout
	JMP	ptrdsp
cEnd	<nogen>

	PAGE
CRLF_LEN= 2			;Length of CR/LF sequence on disk


;   Moved here from out.asm

;***
;B$$WCLF - Write new line
;
;	USES	F
;
;****

cProc	B$$WCLF,<NEAR,PUBLIC>,<AX,BX,SI>
cBegin
	MOV	b$EOL,1		; processing end-of-line
	MOV	SI,[b$PTRFIL]
	OR	SI,SI		;Check for keyboard output
	JZ	wcspec		;  Yes - do special CR/LF
	FDB_PTR ES,SI,SI	;(ES:)[SI] = *FDB

	TEST	FileDB.FD_DEVICE,80H	;Test for special device
	JZ	WCLF_NOT_SPEC		;If not, then jump

	MOV	AL,ASCCR	;get carriage-return
	CALL	B$$WCH		;and output it
	CMP	FileDB.FD_DEVICE,DN_SCRN ;Test if SCRN device
	JE	NO_OUTPUT_LF	;If so, do not output Linefeed

	CMP	FileDB.FD_DEVICE,DN_COM1 ;test against first COM
	JG	OUTPUT_LF	;if before, then output LF
	CMP	FileDB.FD_DEVICE,DN_LPT1 ;test against last COM
	JG	NO_OUTPUT_LF	;if within COM, jump
OUTPUT_LF:
	mov	al,asclf	; get line feed
	call	B$$WCH		; and output it
NO_OUTPUT_LF:
NOTSPEC:
	JMP	SHORT WCLXT	;jump to exit
WCLF_NOT_SPEC:

	CMP	FileDB.FD_MODE,MD_RND	;Check for random
	JNE	wcdisk		;  No - do disk CR/LF
	TEST	b$PRFG,WRSTM	;WRITE statement?
	JZ	wcdisk		;brif not -- just do disk CR/LF

	MOV	BX,FileDB.FD_VRECL  ;Get field length
	SUB	BX,FileDB.FD_BUFCNT ;Subtract off bytes already written
	SUB	BX,CRLF_LEN	;    and two more for CR/LF
	MOV	AL,' '		;Write (BX) spaces

;	This is tricky because DISK_SOUT will give FOV error if
;	(BX) is negative.

wspc:	JZ	wcdisk		;(BX) = 0 - done
	CALL	B$$WCH		;Write space
	DEC	BX		;Decrement (BX)
	JMP	wspc		;Keep on looping until (BX) = 0

wcdisk:
	MOV	AL,ASCCR
	CALL	B$$WCH		;Output CR
	MOV	AL,ASCLF
	CALL	B$$WCH		;Output LF
	JMP	SHORT wclxt

wcspec: MOV	AL,ASCCR	;Output CR only
	CALL	B$$WCH

wclxt:
	MOV	b$EOL,0		; reset to FALSE
cEnd

;***
; B$PRTSTR, B$PRT_TYPCNT, B$PRT_OUTCNT - Type string given descriptor
; Inputs:
;	BX = Address of string descriptor
; Outputs:
;	None.
; Modifieis:
;	CX,SI,AX,F destroyed.
;****

cProc	B$PRTSTR,<NEAR,PUBLIC>
cBegin
	MOV	CX,[BX]		; [CX] = string length

labelNP <PUBLIC,B$PRT_TYPCNT>
	MOV	SI,[BX+2]	; DS:SI = data ptr
	JCXZ	RETL
	push	si		
	MOV	SI,b$PTRFIL
	OR	SI,SI		;is there an open file?
	JZ	PRT_STR_SCRN	;brif not - - - print to screen
	FDB_PTR ES,SI,SI	;(ES:)[SI] = *FDB
	CMP	FileDB.FD_DEVICE,DN_SCRN    
	JZ	PRT_STR_SCRN	;brif file is opened to the screen
	pop	si		

labelNP <PUBLIC,B$PRT_OUTCNT>
	LODSB			; AL = char
	CALL	B$$WCH		; output char
	LOOP	B$PRT_OUTCNT
RETL:				
cEnd				

PRT_STR_SCRN:
	pop	si		
	JMP	B$TYPSTR1	;print this to the screen

;*** 
; B$CLOSF - Close all files.
;
;Purpose:
;	Close all open files.
;Entry:
;	None
;Exit:
;	None
;Uses:
;	Per convention
;Exceptions:
;	None
;******************************************************************************
cProc	B$CLOSF,<NEAR,PUBLIC>,<SI>
cBegin
	CMP	b$Chaining,0	; Are we chaining?
	JNZ	CLOSF_EXIT	;scram if so - don't close em
CLOSF_LOOP:
	XOR	SI,SI		; flag to get first file
	CALL	B$LHNXTFIL	; SI = next FDB pointer
	JZ	CLOSF_END	; brif no more files -- exit loop
CLOSF_CLOSE:
	CALL	DoClose		; process the close
	JMP	SHORT CLOSF_LOOP ; do the next one

CLOSF_END:
	MOV	SI,OFFSET DGROUP:b$LPTFDB ; SI = LPRINT FDB
	TEST	FileDB.FD_FLAGS,FL_LPT_OPN  ;LPRINT open?
	JE	CLOSF_EXIT	; brif not -- just exit
	AND	FileDB.FD_FLAGS,NOT FL_LPT_OPN	;clear the open flag
	CALL	DoClose		; do the close (doesn't deallocate b$LPTFDB)
CLOSF_EXIT:
cEnd


;***
;DevTable -- device dispatch table
;
;Purpose:
;	Device dispatch table for disk only, generated by DEVMAC macro,
;	is used to select the individual device dispatch table (which
;	can only be disk in this case).  If devices are brought in as
;	well, this table is replaced (during one-time initialization in
;	dvinit) with a full disk/device table.
;	Note:	DEVMAC redefins DEVMAC in devdef.inc.
;Entry:
;	none
;Exit:
;	DevTable is set up
;Uses:
;	none
;*******************************************************************************

DEVMAC	MACRO	DeviceName
	externW	B$D_&DeviceName
	DW	B$D_&DeviceName	;;each entry is the address of
	ENDM			;; individual device table

labelW	DevTable		;device table
	DW	2		; # of bytes in table (for error checking)
	DEVMAC	DISK		; generate entry for disks


;*** 
;B$TEST_CLOSE.
;
;Purpose:
;
;Entry:
;
;Exit:
;
;Uses:
;
;Preserves:
;	All
;Exceptions:
;	Possible INT 24 error upon close (?)
;
;******************************************************************************
cProc	B$TEST_CLOSE,<NEAR,PUBLIC>,<SI,BX>	
cBegin

	MOV	BX,b$CLOS_HANDLE ; get handle to close
	OR	BX,BX		; coming from the open code?
	JNZ	CloseIt		; brif so
	MOV	SI,b$CLOS_FDB	;get FDB entry if closing file
	OR	SI,SI		;test if truly closing the file
	JZ	TEST_CLS_DONE	;if not, then just return
	FDB_PTR ES,SI,SI	;(ES:)[SI] = *FDB
	MOV	BX,FileDB.FD_HANDLE ;get handle from FDB
CloseIt:
	PUSH	AX		;save register
	CALLOS	close,,BX	;Close the file, like it or not....
	POP	AX		;restore register
	XOR	SI,SI		
	XCHG	SI,b$CLOS_FDB	;get close flag and clear it
	OR	SI,SI		;test flag, dealloc it?
	JZ	NoDealloc	
	CALL	B$LHDALC_CPCT	;deallocate FDB and compact local heap
NoDealloc:			
	MOV	b$CLOS_HANDLE,0	; clear flag
TEST_CLS_DONE:
cEnd

sEnd	;DV_TEXT

	END

⌨️ 快捷键说明

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