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

📄 dkutil.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
	TITLE	DKUTIL - Disk/Device I/O Utility Routines
	page	56,132
;***
; DKUTIL - Disk/Device I/O Utility Routines
;
;	Copyright <C> 1987, Microsoft Corporation
;
;Purpose:
;	This module contains utility routines and dispatch tables
;	used by both disk and device I/O routines.  It will be
;	present in a user program containing any disk or device
;	I/O statements.
;
;******************************************************************************
	INCLUDE switch.inc
	INCLUDE rmacros.inc

;Code segments:
	useSeg	NH_TEXT 	;near heap
	useSeg	ER_TEXT 	;error handling
	useSeg	CN_TEXT 	;console I/O
	useSeg	DV_TEXT 	;device independent I/O
	useSeg	RT_TEXT 	;runtime core

;Data segments:
	useSeg	_DATA		;initialized variables
	useSeg	_BSS		;uninitialized variable

	INCLUDE seg.inc 	;set up segments
	INCLUDE baslibma.inc
	INCLUDE devdef.inc
	INCLUDE files.inc
	INCLUDE ascii.inc
	INCLUDE idmac.inc
	INCLUDE const.inc
	INCLUDE rtps.inc	;constants shared with QBI

	SUBTTL	local constant definitions
	page

	TTY	EQU	0	;default b$PTRFIL is TTY

	PRSTM	EQU	0	;print statement
	CHANL	EQU	1	;#
	USING	EQU	2	;using
	WRSTM	EQU	4	;write statement
	LPSTM	EQU	8	;lprint statement


	SUBTTL	data definitions
	page

sBegin	_DATA			;initialized variables
	globalW b$pDevTable,DevTable,1 ;pointer to device table
	externB b$PRFG 	;print flag (in PRNVAL.ASM), may be combined
				; from below:
				;0: PRINT stmt
				;1: # (channel)
				;2: USING
				;4: WRITE stmt
				;8: LPRINT stmt
				;e.g. 3 means PRINT # USING

	externB b$IOFLAG	;Misc. IO flags.  Defined in GWINI.ASM
	externB b$BAS_EXT	;defined in FILENAME.ASM

sEnd				;end of _DATA

sBegin	_BSS			;uninitialized variables

	globalW b$RECPTR,,2	;User define type (record) pointer
	staticW DispAddr,,1	;kept the dispatch address


	globalB b$EOL,,1	;set when in B$$WCLF

	externW b$PTRFIL	;defined in global.inc
	externB b$FILMOD	;defined in GWINI.ASM
	externB b$PATHNAM	;defined in GWINI.ASM
	externW b$Buf2		;defined in GWINI.ASM
	PATH_LEN EQU b$Buf2	;save area for pathname length
				;sort of a waste, but convenient

	externB b$LPTFDB
	externB b$Chaining
	externW b$CLOS_FDB
	externW b$CLOS_HANDLE	
sEnd	;_BSS

	SUBTTL	code segments externals
	page

sBegin	NH_TEXT 		;near heap
	externNP	B$LHFDBLOC
	externNP	B$LHNXTFIL
	externNP	B$STDALCTMP	
sEnd

sBegin	ER_TEXT 		;error code component
	externNP B$ERR_BFM
	externNP B$ERR_IFN
	externNP B$ERR_BFN
	externNP B$ERR_FAO
	externNP B$ERR_FC

	externNP B$ERR_RVR	;Record variable required
sEnd

sBegin	CN_TEXT 		;console I/O
	externNP	B$TTY_SINP
	externNP	B$TTY_SOUT
	externNP	B$TTY_GPOS
	externNP	B$TTY_GWID
	externNP	B$TTY_BLKIN
	externNP	B$TTY_BLKOUT
	externNP	B$TYPSTR1
sEnd

sBegin	DV_TEXT 		;device I/O
	externNP	b$dkused	;to pull in dkinit...
	externNP	B$GET_PATHNAME
	externNP	B$GET_DEV_NUM
	externNP	B$ADD_EXT
	externNP	B$STDGET
sEnd

sBegin	RT_TEXT 			;runtime core
	externNP	B$LHDALC_CPCT	;Deallocate FDB and compact
sEnd


assumes cs,DV_TEXT
sBegin	DV_TEXT


;*** 
;DoClose -- perform device close function.
;
;Purpose:
;	Closes a file.  Saves a bit of code by setting close function flag
;	and falling into B$PtrDispatch.
;
;Entry:
;	[SI] =	pointer/handle to FDB
;Exit:
;	None
;Uses:
;	Per convention
;
;Exceptions:
;	Many -- from individual close routines
;
;******************************************************************************
cProc	DoClose,<NEAR>
cBegin
	MOV	AH,DV_CLOSE	; dispatch to close routine
cEnd	<nogen>			; fall into B$PtrDispatch

;***
;B$PtrDispatch -- dispatch according to the device number in the FDB
;B$DevDispatch -- dispatch according to the device number specified
;
;Purpose:
;	Dispatch to the desired I/O routine for devices.
;	B$PtrDispatch first gets device number from file control block, and
;	then does the same thing as B$DevDispatch.
;Entry:
;	[AH] =	function number (minor #)
;
;	if B$PtrDispatch then
;		[SI] =	pointer/handle to FDB
;		BX,CX,DX may contain other parameters needed by dispatched
;		function
;
;	if B$DevDispatch then
;		[AL] =	device number (major #)
;		when B$DevDispatch is called from Open functions:
;			[BX] =	file number
;			[CX] =	record length (0 is default)
;			[DX] =	*sd of file name
;			[b$ACCESS]  =	access right
;			[b$LOCKTYPE] = lock type
;
;	AX,BX,CX,DX & SI are reserved and passed to the dispatched routine.
;	DI contains the address of dispatched routine.
;
;Exit:
;	AX-DX as returned by dispatched routines
;Uses:
;	none
;Exceptions:
;	Many -- by the dispatched routines
;*******************************************************************************

cProc	B$PtrDispatch,<NEAR,PUBLIC>,<DI,SI> 
cBegin
DbAssertRel SI,NE,0,DV_TEXT,<B$PtrDispatch: NULL FDB pointer>	
	FDB_PTR ES,SI,SI	;(ES:)[SI] = *FDB
	PUSH	AX		;save AX (popped later)
	MOV	AL,FileDB.FD_DEVICE ;[AL] = device number (0 for disks)
CommDisp:			;common routine for Ptr/Dev dispatch
	NEG	AL		;since device number is -1 to -n
	CBW			;extend to word (i.e. make AH=0)
	SAL	AX,1		;AX = device table offset (word entries)
	MOV	DI,[b$pDevTable] ;DI = device table address
				; [DI] = byte count of table 
	CMP	AX,CS:[DI]	; is offset within range of device table?
	JB	TableOK		; brif so -- no problem
DbHalt	DV_TEXT,<Uninitialized dispatch table in B$PtrDispatch>	
externNP B$ERR_DNA		
	JMP	B$ERR_DNA	; give device unavailable error
				; NOTE:  THIS SHOULD NEVER HAPPPEN!!!

TableOk:			
	INC	DI		; DI = pointer to device table
	INC	DI		
	XCHG	AX,BX		;use BX for table reference
	MOV	DI,CS:[DI+BX]	;get pointer to dispatch table for device
	XCHG	BX,DI		;DI = offset, BX = pointer to dispatch table
	XCHG	AX,BX		;restore BX to entry value, AX = disp table ptr
	MOV	[DispAddr],AX	;save it in mem-loc

	POP	AX		;[AH] = function number
	PUSH	AX		;save function number & device number
	XCHG	AH,AL		;[AL] = function number
	CBW			;convert to word (make AH=0)
	PUSH	DI		;save DI
	MOV	DI,[DispAddr]	;get addr of device dispatch table
	ADD	DI,AX		;add function code offset to dispatch
	MOV	AX,CS:[DI]	;get the address of routine
	MOV	[DispAddr],AX	;store in [DispAddr]
DbAssertRel	AX,NZ,0,DV_TEXT,<0 value in dispatch table in B$PtrDispatch>
	POP	DI		;get back DI
	POP	AX		;get back AX
	CALL	[DispAddr]	;dispatch & execute routine
				;[AL]=device #, [AH]=function #
				;[DI]=offset to dispatch table
				;if B$PtrDispatch, (ES:)[SI]=*FDB
				;if B$DevDispatch called from B$OPENIT,
				;  [BX]=file number, [CX]=record length,
				;  [DX]=*sd of file name
cEnd				;exit to caller

cProc	B$DevDispatch,<NEAR,PUBLIC>,<DI,SI> ;match to B$PtrDispatch
cBegin
	PUSH	AX			;save AX (popped later)
	JMP	SHORT CommDisp		;jump to common code
cEnd	<nogen> 			;exit via B$PtrDispatch


	SUBTTL	open supporting routines
	page
;***
;B$OPENIT -- common routine for both open interfaces
;
;Purpose:
;	This routine checks the validity of the file name and file number,
;	and also checks whether the channel has already been opened.  If
;	none has problem, it dispatches to the actual device opening routine.
;Entry:
;	AX		= open mode
;	BX		= channel (file number)
;	CX		= record length
;	DX		= *sd of file name
;	[b$ACCESS]	= access right
;	[b$LOCKTYPE]	= locking mode
;
;	Please refer to the procedure head comments of B$OPEN for the detail
;	description of the values for channel, record length, access & lock.
;Exit:
;	b$PTRFIL is reset
;	string decscriptor deallocated
;Uses:
;	per convention
;Exceptions:
;	(1) file name error	-- Bad file name (B$ERR_BFN)
;	(2) access & locking	-- Path/file access error
;				-- Permission denied
;	(3) file number 	-- Illegal file number (B$ERR_IFN)
;	(4) general		-- File already open (B$ERR_FAO)
;				-- File not found (B$ERR_FAO)
;	(5)record number	-- illegal function call (B$ERR_FC)
;*******************************************************************************

cProc	B$OPENIT,<PUBLIC,NEAR>,<SI>	;save SI

cBegin


	MOV	[b$FILMOD],AL	;save mode for further use
	PUSH	CX		;save record length
	cCall	B$CHKNAM	;check valid file name and file number,
				; on return BX = valid file number and
				; AL = device # (major #) for dispatch
				; file name is saved in b$PATHNAM
	CALL	B$LHFDBLOC	;if file found for the given file number (in
				; BX), SI=*FDB and NZ
	JNZ	ERCFAO		;Brif file already open
	POP	CX		;record length in CX
	INC	CX		;test for rec len = -1 (default)
	JZ	DefRec		;go for default converted to 0 value
	DEC	CX		;restore true rec len
	OR	CX,CX		; Overflow flag might have been set by
				; decrement (for 8000 ==> 7FFF).
	JLE	ERCFC		;go if len <= 0 (illegal func call)
DefRec: 			
	MOV	AH,DV_OPEN	;AH = routine # (minor #) for dispatch
	CALL	B$DevDispatch	;dispatch it
	MOV	[b$PTRFIL],TTY	;reset pointer to FDB


cEnd				;pop SI and exit

ERCFC:	JMP	B$ERR_FC	;illegal function call

;***
;B$CHKNAM -- scan file name & file number
;
;Purpose:
;	Check the validity of file name & file number, if both are good,
;	get the device number (major #) for dispatching.
;	If the name is for file 0 (BLOAD/BSAVE) then this routine appends the
;	extention ".BAS" to the filename if it doesn't already have one.
;Entry:
;	BX	= file number
;			-1		internal file
;			1-255		valid file number
;			0,256-65534	invalid file number
;	DX	= *sd of file name
;Exit:
;	AL	= device number (result from B$GET_DEV_NUM)
;	BX	= 0	if used as an internal file (BLOAD/BSAVE ...)
;		= 1-255 valid file number
;	CX	= count of chars (including null) in pathname
;	for disk files, 
;		[b$PATHNAM] = fully-specified, null-terminated pathname
;	for devices,
;		[b$PATHNAM] = null-terminated option string (including "XXXX:")
;Uses:
;	AH
;Exceptions:
;	Bad file name		(B$ERR_BFN)
;	Illegal file number	(B$ERR_IFN)
;*******************************************************************************

cProc	B$CHKNAM,<NEAR>,<SI,DI,ES>

cBegin
	XCHG	DX,BX		;DX = file number, BX = psdFileName
	MOV	DI,OFFSET DGROUP:b$PATHNAM ;destination to store pathname
	PUSH	DS		; set ES=DS
	POP	ES		
	MOV	CX,[BX] 	; get count of chars in string
	JCXZ	ERCIFN		;brif null filename -- Bad file number
				;Yes, this is a stupid message, but its
				;required for compatability reasons.
	CALL	B$GET_DEV_NUM	;check for device, placing device # in AL
				;and device option string in b$PATHNAM
	JZ	NOT_DEVICE	;brif not device -- process name

	MOV	SI,[BX+2]	; get start address
	PUSH	CX		;save count
	REP	MOVSB		;copy the string into b$PATHNAM
	MOV	[DI],CL		;null-terminate the string
	POP	CX		;restore count (doesn't include null)
	INC	DX		;file # = -1 (BLOAD/BSAVE)?
	JZ	ERCFC		;brif so -- devices not valid for BLOAD/BSAVE
	JMP	SHORT CHK_NUMBER

NOT_DEVICE:
	CALL	B$GET_PATHNAME	;scan filename and store pathname in *[DI]
				;AL = return flags
				;CX = len of pathname (including null)
	TEST	AL,FN_WILD	;wildcard in pathname?
				;filename detected?
	JNZ	ERCBFN		;Brif yes, give "Bad file name"

	INC	DX		;-1 is interal use (BSAVE/BLOAD), change to 0
	JNZ	NotFile0	;Brif not for Bload/Bsave
				;BLOAD and BSAVE need to append '.BAS' to
				;pathname if it doesn't have an extention

				;CX and AL preserved from B$GET_PATHNAME
	MOV	SI,OFFSET DGROUP:b$BAS_EXT ;append ".BAS" extention to
	CALL	B$ADD_EXT	;pathname if no extention present.  Also
				;checks for pathname overflow, and updates
				;count in CX
	XOR	AL,AL		;indicate disk device
	JMP	SHORT SCANX	;exit

NotFile0:			;check file number
	XOR	AL,AL		;indicate disk device
CHK_NUMBER:
	DEC	DX		;get back file number, file # = 0?
	JZ	ERCIFN		;Brif so, give "illegal file number"
	OR	DH,DH		;is greater than 255 ?
	JNZ	ERCIFN		;illegal file number
SCANX:
	CALL	B$STDALCTMP	; dealloc string if temp (all regs saved)
	MOV	PATH_LEN,CX	;save count until dispatched to xxxx_OPEN
	XCHG	DX,BX		;return file number in BX
cEnd


ERCFAO: JMP	B$ERR_FAO	;File already open
ERCBFN: JMP	B$ERR_BFN	;Bad file name
ERCIFN: JMP	B$ERR_IFN	;illegal file number

	SUBTTL	close interface -- B$CLOS
	PAGE
;***
;B$CLOS -- close statement
;viod B$CLOS(I2 channel, I2 channel, ..., cParams)
;
;Purpose:
;	This is the interface of CLOSE statement.  In BASCOM 2.0, there are
;	two interfaces, $DCA and $DKC to handle the close.  $DCA closes all
;	files (no parameter given in CLOSE stmt), and $DKC closes the files
;	given.	In BASCOM 3.0, only one interface is used.  Parameters were
;	pushed in stack with the parameter count followed.
;
;	Note: cProc with PLM convention can't handle variable parameters.  In
;	this routine, enter and exit have to be special handled.
;
;	The following is one of the proposed method to handle variable
;	parameters.
;
;cProc	Name,<PUBLIC,FAR>,<DI>	;save DI
;	ParmW	UnknownParam	;potential parameter, NOTE:  MUST use
;				; "cEnd nogen" at the end of the procedure
;				; and handle exit process explicitly
;	ParmW	cParam		;parameter count, last parameter
;
;cBegin 			;use DI as the pointer to walk in the stack
;				;(SI or BX will be another candidate as the
;				; walking register, however if BX is used,
;				; user has to make sure BX won't be changed
;				; within the routine)
;	.
;	.			;save other registers
;	.
;	LEA	DI,UnknownParam ;DI points to one below the parameter count
;	MOV	CX,cParam	;CX has the parameter count
;	JCXZ	NoParm		;no parameter
;ParmLoop:
;	MOV	BX,[DI] 	;get parameter in BX (for example)
;	.
;	.			;do whatever needed for each parameter
;	.
;	ADD	DI,2		;DI points to next parameter
;	LOOP	Parameter_Loop
;NoParm:
;	.
;	.			;do whatever needed for no parameter
;	.
;ExitProc:
;	.			;restore registers if any
;	.
;	MOV	SP,DI		;clean stack
;	MOV	DI,[BP-2]	;get back DI
;	LEA	BX,[BP+2]	;bx=*return addr
;	MOV	BP,[BP] 	;get back BP
;	JMP	DWORD PTR [BX]	;return to caller
;cEnd	nogen			;no code generated
;
;Entry:
;	Parameters were pushed in stack.
;	int	channel
;		.
;		.
;		.
;	int	channel
;	ushort	cParams
;Exit:

⌨️ 快捷键说明

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