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

📄 dkopen.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
appfi2:				; [DX|CX] = last position
	CALL	B$SeekFromStart ; back up over CTRL Z ([DX|AX] = result)
	XCHG	AX,CX		; [DX|CX] = current position

EmptyApp:
	MOV	FileDB.FD_BUFCNT,0 ; nothing in buffer
				; No need to clear FD_INBUFCNT, since it
				; will never be referenced again.
; commented out this code and associated code in DISK_LOC because LOC
; could return negative values if we SEEK to before where we started.
;	MOV	FileDB.FD_LOGREC,CX ; save starting position for append files
;	MOV	FileDB.FD_HIGHLR,DX 
OpenExit: 			; done
cEnd

ERCIOE: 				
	CALL	B$LHDALC	; deallocate FDB
	JMP	B$ERR_IOE	; device I/O error

;*** 
; DO_CLOSE -- close a file.
;
;Purpose:
;	Closes a file whose handle is in BX.  Added with [15] to save code.
;	Closes file but does not dealocate FDB upon INT 24 error.
;Entry:
;	BX = file handle
;Exit:
;	None
;Uses:
;	None
;Preserves:
;
;Exceptions:
;	None
;
;******************************************************************************

cProc	DO_CLOSE,<NEAR>
cBegin
	MOV	b$CLOS_HANDLE,BX ; close file, no FDB dealloc on INT24 error
	CALL	B$CLOSE		; close the file
	MOV	b$CLOS_HANDLE,0	; finished with critical section
cEnd


;*** 
; DiskOpenHelper -- open a file.
;
;Purpose:
;	Actually open a file whose pathname is in b$PATHNAM.
;
;Entry:
;	b$PATHNAM = pathname of file to open.
;	BX	=  mode of open
;	CX	= special open flag if OS/2
;
;Exit:
;	AX	= error code if error, 0 otherwise
;	BX	= file descriptor (if no error)
;	IF	NOT OM_DOS5
;		Carry set if error; clear otherwise.
;Uses:
;	DX
;Preserves:
;	None
;Exceptions:
;	None
;
;******************************************************************************

cProc	DiskOpenHelper,<NEAR>
cBegin

	MOV	DX,OFFSET DGROUP:b$PATHNAM ; address of pathname
	OR	BL,[b$LOCKTYPE];add access code for DOS 3.0

	CALLOS	OPEN,,,,DX,BX
	JC	OpenRet		; brif error
	XCHG	BX,AX		; BX = file descriptor
	XOR	AX,AX		; AX = 0 (no error -- clears carry)
OpenRet:
cEnd

	PAGE
;***
;B$CHKFOPEN -- check if file already open.
;
;Purpose:
;	Re-written as part of [11].
;
;	Checks for file already open by searching all FDBs, and comparing
;	their pathname fields, if they exist.
;
;Entry:
;	DI = pointer to standard processed pathname (from B$GET_PATHNAME)
;	ES = DS (only for NOT FV_FARFDB case)
;
;Exit:
;	None
;Uses:
;	AX,BX
;Exceptions:
;	B$ERR_FAO -- file already open
;****

cProc	B$CHKFOPEN,<NEAR,PUBLIC>,<SI>
cBegin
	XOR	SI,SI		;prepare to get first FDB

CHKFO_LOOP:
	CALL	B$LHNXTFIL	; point to next FDB in SI
	JZ	CHKFO_DONE	;if no more, then jump to exit
	FDB_PTR ES,SI,SI	; (ES:)SI = *FDB

;check pathname field of FDB pointed to by [SI] for match with pathname in [DI]
	CMP	FileDB.FD_DEVICE,0 ;does this FDB have a pathname field?
	JNE	CHKFO_LOOP	;brif not -- pathnames don't match
	LEA	BX,FileDB.FD_BUFFER ;BX = pathname2 address
	ADD	BX,FileDB.FD_VRECL  

	XCHG	BX,SI		;SI = pathname2 address
	PUSH	DI		;save pathname1 address

CMP_LOOP:			;compare the two pathname strings for equality
	LODSB			;load byte from filename2 into AL
	SCASB			;compare bytes
	JNZ	NEXT_FDB	;brif not equal -- try next FDB
	OR	AL,AL		;last byte?
	JNZ	CMP_LOOP	;brif not -- check another character
	JMP	B$ERR_FAO	; names matched. File already open error

NEXT_FDB:			;ZF if match, NZ if not a match
	POP	DI		;restore pathname1 address
	XCHG	BX,SI		;restore SI to FDB pointer
	JMP	SHORT CHKFO_LOOP ;try next FDB

CHKFO_DONE:
cEnd				;End of B$CHKFOPEN

;*** 
; B$OPEN_DEV and B$DEVOPN -- Special device open common routines.
;	 Re-wrote as part of [32].
;
;Purpose:
;	Allocates an FDB for a device.
;	B$DEVOPN is called when a buffer is to be allocated (if a non-zero
;	buffer size is specified), while B$OPEN_DEV is called when no buffer
;	is to be allocated (sets CX to 0)
;
;Entry:
;	[AL] = file device
;	[AH] = valid file modes
;	[CX] = size of buffer(s) (not including basic FDB size)
;	[DL] = file width
;	[BX] = file number
;
;Exit:
;	[SI] = pointer/handle to allocated FDB.
;	FD_DEVICE, FD_WIDTH, and FD_MODE fields of FDB initialized.
;
;Uses:
;
;Preserves:
;	AX,BX,DX (B$DEVOPN preserves CX)
;
;Exceptions:
;	B$ERR_BFM -- Bad file mode
;
;******************************************************************************


cProc	B$OPEN_DEV,<PUBLIC,NEAR> 
cBegin				
	XOR	CX,CX		; specify no buffer to be allocated
cEnd	nogen			; fall through into B$DEVOPN

cProc	B$DEVOPN,<PUBLIC,NEAR>,<CX> 
cBegin				

	TEST	[b$FILMOD],AH	;Check for valid file mode
	JZ	ercbfm1 	;  Bad file mode

	JCXZ	NO_BUFFER	;brif buffer not requested
	ADD	CX,FDB_EXTRA	;add in space for extra FDB fields
NO_BUFFER:
	XCHG	BX,CX		;put length in BX, file number in CX
	ADD	BX,FDB_SIZE	;set size of data block needed
	PUSH	DX		; save file width
	MOV	DL,LH_FILE	;set type of entry to allocate
	CALL	B$LHALC_CPCT	; compact local heap, and allocate FDB
	POP	DX		;restore file width
	XCHG	BX,CX		;[BX] = file number
	MOV	CL,b$FILMOD	;get file mode of open
	MOV	FileDB.FD_MODE,CL ;and save it in the FDB

	MOV	FileDB.FD_DEVICE,AL ;set file device
	MOV	FileDB.FD_WIDTH,DL  ;set file width
cEnd				


ercbfm1: JMP	B$ERR_BFM	;Bad file mode

	SUBTTL	open interface -- B$OPEN & B$OOPN
	page
;***
;B$OPEN -- open a disk file using new syntax
;void B$OPEN(sd *psdName,I2 channel,I2 cbRecord,U2 ModeAccessLock)
;
;Purpose:
;	This interface is for opening a file using the syntax as follows:
;
;	OPEN "filespec" [FOR mode] [ACCESS access] [locking] AS [#] filenum
;								    [LEN=recl]
;	where	mode	={INPUT, OUTPUT, APPEND, RANDOM},
;		access	={READ, WRITE, READ WRITE}
;		locking ={SHARED, LOCK {READ | WRITE | READ WRITE} }.
;	If FOR clause is omitted, the default file mode is random.
;
;	In BASCOM 2.0, multi-interfaces are used.  The usage is as follows:
;
;	OPEN "filespec" [FOR mode] [sharing] AS [#]filenum [LEN=record len]
;		|	    |		|	    |		|
;		|	  $DKO	      $DKA	    |		|   $DKM
;		|___________________________________|___________|_____|
;
;	Where $DKO & $DKA set flags and do some checks, and $DKM dispatchs
;	to the open routine.
;
;	In BASCOM 3.0, a single interface is used, B$OPEN, which has all
;	opening information in the stack when entering.  The order of
;	parameters are different from the one above.  The correct order is
;	defined in "Entry" section.
;
;	When entering from the compiler, the value of access is different
;	from the actual needs, so that the modification is necessary.  The
;	reason for making the value different is to detect more easily the
;	legal use of access & locking clauses (network features).
;
;	sdName/*psdName	sd for file name
;
;	channel 	1-255		valid
;			0,256-65535	illegal function call
;
;	cbRecord	0		illegal function call
;			1-32767 	valid
;			32767-65534	illegal function call
;			65535		default (-1)
;
;	* Note: LEN=0 in the statement now gives 'illegal function call'
;
;	ModeAccessLock (the following input values are adjusted to
;		    correspond to those used in the runtime)
;
;	    mode	MD_SQI		=1h	input
;			MD_SQO		=2h	output
;			MD_RND		=4h	random
;			MD_DEFAULT	=4h	default (to random)
;			MD_APP		=8h	append
;			MD_BIN		=20h	binary		[29]
;
;	    access	ACCESS_DEFAULT	=  0h	no access clause
;			ACCESS_READ	=100h	access read
;			ACCESS_WRITE	=200h	access write
;			ACCESS_BOTH	=300h	access read write
;
;	* the actual access value needed by DOS func. call for opening are
;	  0, 1 & 2 for access read, access write and access read write
;	  respectively.
;
;	    lock
;			LOCK_COMPATIBLE =0000h	compatible mode
;			LOCK_DEFAULT	=0000h	no lock clause
;			LOCK_BOTH	=1000h	lock read write
;			LOCK_WRITE	=2000h	lock write
;			LOCK_READ	=3000h	lock read
;			LOCK_SHARED	=4000h	shared (lock none)
;
;	Symbols listed above will be available in a runtime include file
;	called "runtime.inc".
;
;	Algorithm -- Pseudo C code
;
;	B$OPEN(file_name,file_num,record_length,ModeAccessLock)
;	sd	*file_name
;	int	file_num,record_length
;	ushort	ModeAccessLock
;	{
;	    b$ACCESS = ModeAccessLock >> 8 & 0x0F;	/* save access */
;	    b$LOCKTYPE = ModeAccessLock >> 8 & 0xF0;	/* save lock */
;	    if (access || lock) 	/* has access or locking clause ? */
;		if DOSVER < 3.0 	/* dos version has to be above 3.0 */
;		    error("illegal function call")
;	    openit(AX_open_mode,BX_file_num,CX_rec_length,DX_sd_filename)
;	}
;Entry:
;	Parameters were pushed in the stack.
;	sd	sdName		(file name)
;	int	Channel 	(file number)
;	int	cbRecord	(record length)
;	ushort	ModeAccessLock	(file mode, access right, locking status)
;Exit:
;	b$PTRFIL is reset
;Uses:
;	none
;Exceptions:
;	(1) file name error	-- Bad file name (B$ERR_BFN)
;	(2) access & locking	-- Illegal function call (B$ERR_AFE)
;				-- Path/file access error
;				-- Permission denied
;	(3) file number 	-- illegal file number (B$ERR_INF)
;	(4) general		-- File already open (B$ERR_FAO)
;				-- File not found (B$ERR_FAO)
;*******************************************************************************

cProc	B$OPEN,<PUBLIC,FAR>
	ParmSD	sdName		; sd to filename
	ParmW	Channel 	;I2, file #
	ParmW	cbRecord	;I2, record len
	ParmW	ModeAccessLock	;U2, file mode, access method, sharing status
cBegin
	MOV	AX,ModeAccessLock	; get lock/access/mode info
	MOV	BL,AH		;get the lock type
	AND	BL,0F0H 	;isolate lock from access
	AND	AH,0FH		;isolate access from lock
	MOV	[b$ACCESS],AH	;save access
	MOV	[b$LOCKTYPE],BL	; save it
	OR	AH,BL		;has access clause or locking clause ?
	JZ	DISPATCH	;Brif not, go dispatch
	cCall	B$DOS3CHECK	;must be 3.0 or above
	JB	ERCAFE		;Brif not, give advanced feature call
DISPATCH:
	XOR	AH,AH		;isolate mode from lock/access
	MOV	BX,Channel	;file number in BX
	MOV	CX,cbRecord	;record length in CX
	GetpSD	DX,sdName	; [DX] = psdName
	cCall	B$OPENIT	;dispatch to actual open routine
cEnd				;end of B$OPEN

ERCAFE: JMP	B$ERR_AFE	;give advanced feature error

	page
;***
;B$OOPN -- old open form
;void B$OOPN(U2 mode, I2 channel, SD sdName, I2 cbRecord)
;
;Purpose:
;	Simular to B$OPEN, B$OOPN is the single interface for old open form.
;	(refer to the procedure head comments of B$OPEN for detail)
;
;	In BASCOM 2.0, the mode passed in is a *sd to the mode string, whereas
;	in BASCOM 3.0, the mode passed in is an U2, which is simular to B$OPEN.
;
;	Algorithm -- pseudo C code
;
;	B$OOPN(psdMode, channel, sdName, cbRecord)
;	ushort	mode
;	int	channel,cbRecord
;	SD	sdName
;	{
;	    b$ACCESS=b$LOCKTYPE=0;	/* no access or locking clause */
;
;	    substitute mode of "I" into MD_SQI
;	    substitute mode of "O" into MD_SQO
;	    substitute mode of "R" into MD_RND
;	    substitute mode of "A" into MD_APP
;	    substitute mode of "B" into MD_BIN;		[29]
;
;	    openit(AX_open_mode,BX_file_num,CX_cbRecord,DX_sd_filename)
;	}
;Entry:
;	Parameters were pushed in stack.
;	SD	sdMode		(file mode)
;	int	Channel 	(file number)
;	SD	sdName		(file name)
;	int	cbRecord	(record length)
;Exit:
;	b$PTRFIL is reset
;Uses:
;	per convention
;Exceptions:
;	(1) file name error	-- Bad file name (B$ERR_BFN)
;	(2) access & locking	-- Illegal function call (B$ERR_AFE)
;				-- Path/file access error
;				-- Permission denied
;	(3) file number 	-- illegal file number (B$ERR_INF)
;	(4) general		-- File already open (B$ERR_FAO)
;				-- File not found (B$ERR_FAO)
;*******************************************************************************

cProc	B$OOPN,<PUBLIC,FAR>

	ParmSD	sdMode		:[33] sd, file mode
	ParmW	Channel 	;I2, file number
	ParmSD	sdName		:sd, file name
	ParmW	cbRecord	;I2, record length
cBegin
	MOV	[b$ACCESS],ACCESS_DEFAULT	;default compatible mode
	MOV	[b$LOCKTYPE],LOCK_DEFAULT	; default no locking clause
	GetpSD	BX,sdMode	; DX = *sd of file mode
	MOV	CX,[BX] 	;get the length
	JCXZ	ERCBFM1 	;Brif length = 0 -- "bad file mode"
	PUSH	BX		;save sd
	MOV	BX,2[BX]	;get the pointer to the first character
	MOV	BL,BYTE PTR [BX];BL has the character
	AND	BL,0DFH 	;convert lower case to upper case
	MOV	AX,MD_SQI	; MD_SQI = 1
	CMP	BL,"I"		;is input ?
	JZ	ModeSet 	;Brif yes
	INC	AX		; MD_SQO = 2
	CMP	BL,"O"		;is output ?
	JZ	ModeSet 	;Brif yes
	MOV	AL,MD_RND	; MD_RND = 4
	CMP	BL,"R"		;is random ?
	JZ	ModeSet 	;Brif yes
	MOV	AL,MD_APP	; MD_APP = 8
	CMP	BL,"A"		;is append ?
	JZ	ModeSet 	; Brif yes
	CMP	BL,"B"		; is binary ?
	JNZ	ERCBFM1 	;Brif not, give "Bad file mode"
	MOV	AL,MD_BIN	; MD_BIN = 20H
ModeSet:
	POP	BX		;recover sd
	cCall	B$STDALCTMP	;dealloc if temp sd
	MOV	BX,Channel	;file number in BX
	MOV	CX,cbRecord	;record length in CX
	GetpSD	DX,sdName	; DX = *sd of file name
	cCall	B$OPENIT	;dispatch to actual open routine
cEnd				;end of B$OOPN

sEnd	RT_TEXT

end

⌨️ 快捷键说明

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