📄 bdevio.a86
字号:
; FDRWCNT = extra bytes requested
; On Exit:
; FDRWCNT adjusted if read past EOF
; CY set if problem extending file
;
les bx,current_dhndl
mov ax,es:DHNDL_SIZELO[bx] ; are we past the end of file
mov dx,es:DHNDL_SIZEHI[bx] ; if so we may wish to extend on write
sub ax,byteoff ; AX,DX = current offset
sbb dx,byteoff+WORD ; are we already beyond EOF ?
jb fdrw_s40
sub ax,fdrwcnt ; will we be going beyond EOF ?
sbb dx,0
jnb fdrw_s10 ; no, whole xfer is OK
test fdrwflg,1 ; check if we're reading
jz fdrw_s50 ; if we are just adjust the
add fdrwcnt,ax ; amount we can xfer
fdrw_s10:
; We call share concerning the XFER to check if any of the proposed
; file region is locked.
; les bx,current_dhndl ; check for locked regions
mov cx,net_retry
fdrw_s15:
push cx
mov cx,fdrwcnt ; in the file
callf share_stub+S_FDOSRW
pop cx
jnc fdrw_s20 ; CY set on error
dec cx
jz fdrw_s30
call share_delay
jmps fdrw_s15
fdrw_s20:
ret
fdrw_s30:
jmp fdos_error ; CY clear, AX = error code
fdrw_s40:
; We are going beyond EOF - if it is a read we fail it, if a write
; try to extend the file
test fdrwflg,1 ; check if we're reading
stc ; assume failure
jnz fdrw_s20 ; reads fail now, writes extend file
fdrw_s50:
call fdrw_s10 ; make sure SHARE doesn't object
; jmp fdwrite_extend ; if not try to extend the file
fdwrite_extend:
;--------------
; Try to extend to file to the required size before we write to it
; On Entry:
; ES:BX -> DHNDL_
; BYTEOFF = current position in file
; FDRWCNT = extra requested
; On Exit:
; CY clear if cluster chain now big enough for desired file size
;
mov ax,byteoff ; AX,DX = current offset
mov dx,byteoff+2
add ax,fdrwcnt ; AX,DX = offset after r/w if success
adc dx,0 ; add offset from lower 16 bits
div clsize ; AX whole blocks required
test dx,dx ; any remainder ?
jz fdw_e05 ; yes, we have a partial block
inc ax ; round up blocks required
fdw_e05:
xchg ax,cx ; CX blocks are required
mov ax,es:DHNDL_BLK1[bx] ; assume we need to follow from start
test ax,ax
jz fdw_e30 ; if no starting block do the lot
dec cx ; else count # extra blocks required
mov dx,es:DHNDL_BLK[bx] ; do we have a current block ?
test dx,dx ; if not we have to start
jz fdw_e10 ; with the first block
mov ax,dx ; new starting block as this must
sub cx,es:DHNDL_IDX[bx] ; be less than extended size
fdw_e10:
jcxz fdw_e20 ; bail out of we have enough
fdw_e15:
push ax ; save current block
push cx ; save # required
call getnblk ; AX = next block in chain
pop cx ; restore # required
pop bx ; recover previous block
cmp ax,lastcl ; end of chain yet ?
ja fdw_e40
loop fdw_e15 ; try another one
fdw_e20:
clc ; chain is already long enough
ret
fdw_e30:
; We have no initial block, so allocate them all
; xor ax,ax ; no preconceptions over where we
call alloc_chain ; allocate chain of CX clusters
jc fdw_e35
les bx,current_dhndl
mov es:DHNDL_BLK1[bx],ax ; remember initial block
clc
fdw_e35:
ret
fdw_e40:
; We have a partial chain, ending at cluster BX
push bx ; save current end of chain
xchg ax,bx ; start allocating from cluster AX a
call alloc_chain ; a chain of CX clusters
pop bx
jc fdw_e45
xchg ax,bx ; AX = previous cluster, link cluster
call fixfat ; BX to end of the chain
clc
fdw_e45:
ret
fdrw_seek:
;---------
; On Entry:
; BYTEOFF = offset within file
; On Exit:
; BLK = cluster containing current filepos
; BLKOFFSET = offset within cluster
; BLKIDX = cluster index within file
; PBLOCK = sector containing current filepos
; POFFSET = offset within sector (reflected in ZF)
;
mov ax,byteoff ; where are we now ?
mov dx,byteoff+WORD
div clsize
mov blkidx,ax ; save cluster
mov blkoffset,dx ; and offset within it
les bx,current_dhndl
cmp ax,es:DHNDL_IDX[bx] ; do we know this block ?
jb fdrw_seek10 ; we can't go backwards, use 1st block
mov cx,es:DHNDL_BLK[bx] ; get last index block
jcxz fdrw_seek10 ; use 1st block if it isn't valid
sub ax,es:DHNDL_IDX[bx] ; skip this many
jmps fdrw_seek20
fdrw_seek10:
mov cx,es:DHNDL_BLK1[bx] ; start with 1st block
fdrw_seek20:
xchg ax,cx ; AX = starting cluster
jcxz fdrw_seek40 ; CX = clusters to skip
fdrw_seek30:
push cx
call getnblk ; get next block
pop cx
cmp ax,lastcl ; stop on premature end of chain
ja fdrw_seek_error ; (file size must be wrong..)
loop fdrw_seek30
fdrw_seek40:
les bx,current_dhndl
mov dx,blkidx
mov es:DHNDL_IDX[bx],dx ; remember this position for next time
mov es:DHNDL_BLK[bx],ax
mov blk,ax ; save the block for coniguous checks
mov bx,blkoffset
call clus2sec ; convert to sector/offset
mov word ptr fdrwsec,ax ; remember this block
mov word ptr fdrwsec+WORD,dx
mov fdrwsecoff,bx ; and offset within it
test bx,bx ; set ZF
; clc ; no problems
ret
fdrw_seek_error:
stc ; we hit unexpected end of chain
ret ; (shouldn't happen)
; Read/write partial sector via deblocking code
; On Entry:
; FDRWSEC = sector address on disk
; FDRWSECOFF = offset within sector
; FDRWCNT = byte count for read/write
; On Exit:
; AX = # of bytes transferred
deblock_rw:
;----------
mov cx,0FF00h+BF_ISDAT ; CH = preread, buffer is data
mov dx,word ptr fdrwsec ; set sector to xfer from
mov ah,byte ptr fdrwsec+WORD
call locate_buffer ; ES:SI -> buffer
mov bx,fdrwsecoff ; BX = offset within sector
mov ax,psecsiz
mov dx,ax ; DX = physical sector size
sub ax,bx ; AX = bytes left in sector
cmp ax,fdrwcnt ; more than we want to transfer?
jb deblkrw10 ; yes, only do up to end of sector
mov ax,fdrwcnt ; else do up to end of request
deblkrw10:
mov cx,ax ; AX, CX = byte count
; (AX for return, CX for MOVSW)
push ds
test fdrwflg,1 ; check if reading or writing
jz dblkrw30 ; skip if writing
push es
les di,fdrwptr ; destination is user memory
pop ds ; source segment is data buffer
lea si,BCB_DATA[si+bx] ; DS:SI -> data
jmps dblkrw40 ; copy the data
dblkrw30: ; we're writing
or es:BCB_FLAGS[si],BF_DIRTY; mark buffer as dirty
lea di,BCB_DATA[si+bx] ; ES:DI -> data
lds si,fdrwptr ; source is user memory
dblkrw40:
shr cx,1 ; make it a word count
rep movsw ; move the words
jnc dblkrw50 ; skip if even # of bytes
movsb ; else move last byte
dblkrw50:
pop ds ; restore registers
ret
; entry: BYTEOFF = 32-bit offset into file
; BLKOFFSET = byte offset within cluster
; PRVBLK = block in which transfer starts
; FDRWREQ = requested transfer length
;---------
direct_rw:
;---------
sub dx,dx ; assume no extra blocks required
mov ax,fdrwreq ; total byte count
mov cx,clsize ; get number of bytes
sub cx,blkoffset ; CX = bytes remaining in this block
sub ax,cx ; if wholly containined within block
jbe direct_rw10 ; then leave it alone
div clsize ; else get # of extra clusters
xchg ax,dx ; DX = clusters, AX = remainder
or ax,ax ; round up if any remainder
jz direct_rw10 ; skip if even number
inc dx ; else one more cluster
direct_rw10: ; DX = # of contiguous clusters req'd
call check_cont ; check how many contiguous blocks
mov ax,clsize ; space = cnt * dpbptr->clsize;
mul cx ; AX:DX = # of bytes transferrable
sub ax,blkoffset ; BX = skipped bytes in 1st cluster
sbb dx,0
; AX:DX = max # of bytes transferrable
; from current position
test dx,dx
jnz direct_rw20 ; if > 64 K, use up request
cmp ax,fdrwreq ; if less than we requested
jb direct_rw30 ; then lets do it
direct_rw20:
xor dx,dx
mov ax,fdrwreq ; else use requested count
direct_rw30:
div psecsiz ; AX = # complete sectors
mov fdrwdircnt,ax ; save direct sector count
mov mult_sec,ax ; set multi sector count
mul psecsiz ; AX = bytes to xfer
push ax ; save for later
mov ax,fdrwoff ; FDRWPTR = disk transfer address
mov cur_dma,ax
mov ax,fdrwseg
mov cur_dma_seg,ax
mov ax,word ptr fdrwsec ; set sector to xfer from
mov word ptr pblock,ax
mov ax,word ptr fdrwsec+WORD
mov word ptr pblock+WORD,ax
mov rwmode,0000$0110b ;data read/write
mov cl,fdrwflg
and cl,1 ; CL = read/write flag
jz direct_rw40
xor cx,cx ; indicate no retries
call read_block ; read in the data
jmps direct_rw50
direct_rw40:
call write_block ; write out the data
direct_rw50:
call SynchroniseBuffers ; synchronize BCBs with direct transfer
pop ax ; recover bytes xfered
push ds ! pop es ; restore ES = SYSDAT
ret
check_cont: ; check for adjacent blocks or space
;----------
; entry: DX = # of extra contiguous blocks req'd
; exit: CX = # of contiguous blocks available
; We first check all adjacent allocated clusters.
; If we'd like more and we find the end of file
; and we are writing and the adjacent blocks aren't
; allocated, then we count them as well and link
; them into the file.
mov ax,blk ; current block number
xor cx,cx ; contiguous blocks found = 0
test dx,dx ; any extra required ?
jz check_cont20
check_cont10: ; get link of current block
push ax ; save current block
push cx ; save extra blocks so far
push dx ; save extra blocks we'd like
call getnblk ; get the link
pop dx
pop cx
pop bx
inc bx ; BX = current block + 1
cmp ax,bx ; check if next block is contiguous
jne check_cont20 ; and try for another
inc cx ; extra contiguous cluster
dec dx ; one less block to check
jnz check_cont10 ; try again if we still want more
check_cont20: ; we can do CX extra clusters
inc cx ; include 1st cluster too..
ret
;------------------
SynchroniseBuffers: ; synchronize BCBs after multi sector transfer
;------------------
; On Entry:
; FDRWSEG:FDRWOFF = transfer address for IO_READ/IO_WRITE
; FDRWDIRCNT = physical sector count for direct transfer
; FDRWSEC = sector address for transfer
; FDWRFLG = even for write, odd for read
; On Exit:
; direct transfer buffer or BCB updated if BCB overlap
;
; If any data buffer is found, that falls into the region affected
; by the direct sector transfer, the following action is performed:
; If the operation was a read and the sector buffer is clean,
; no action is required. If it was dirty, the buffer contents is
; copied to the corresponding location in the DTA buffer.
; If the operation was a write, the sector buffer is discarded.
;
;
mov dx,word ptr fdrwsec
mov ah,byte ptr fdrwsec+WORD
mov al,adrive ; get our drive number
lds bx,bcb_root ; DS:BX -> 1st buffer
SynchroniseBuffers10:
test ds:BCB_FLAGS[bx],BF_ISDAT; is this a data buffer?
jz SynchroniseBuffers30 ; skip if directory or FAT
cmp al,ds:BCB_DRV[bx] ; does the drive match?
jne SynchroniseBuffers30 ; skip if different
mov si,ds:BCB_REC[bx] ; compute bcb->rec - prec
sub si,dx ; result in SI,CL (lsb..msb)
mov cl,ds:BCB_REC2[bx]
sbb cl,ah ; get bits 16-23 of result
jne SynchroniseBuffers30 ; skip if bcb->rec < prec
cmp si,ss:fdrwdircnt ; else check against transfer length
jae SynchroniseBuffers30 ; skip if beyond transfer length
test ss:fdrwflg,1 ; test direction: read or write
jz SynchroniseBuffers20 ; skip if disk write
test ds:BCB_FLAGS[bx],BF_DIRTY; if buffer dirty, did read old data
jz SynchroniseBuffers30 ; else data read was valid
push ax ! push dx ; save record address
mov ax,ss:psecsiz ; # of bytes in sector buffer
mov cx,ax
shr cx,1 ; CX = words per sector
mul si ; AX = byte offset from start buffer
add ax,ss:fdrwoff ; AX = offset
xchg ax,di ; DI = offset
mov es,ss:fdrwseg ; ES:DI -> data to be replaced
lea si,BCB_DATA[bx]
rep movsw ; move CX words (one physical sector)
pop dx ! pop ax ; restore record address
jmps SynchroniseBuffers30
SynchroniseBuffers20: ; multi sector write
mov ds:BCB_DRV[bx],0FFh ; discard this sector
SynchroniseBuffers30:
if DOS5
mov bx,ds:BCB_NEXT[bx]
cmp bx,ss:word ptr bcb_root
else
lds bx,ds:BCB_NEXT[bx] ; get next buffer address
cmp bx,0ffffh
endif
jne SynchroniseBuffers10 ; if so stop
push ss ! pop ds ; restore DS
ret
eject
Public blockif, ddioif
;======= ================================
blockif: ; disk read/write bios interface
;======= ================================
; entry: AL = BIOS Request function number
; ADRIVE = block device to xfer to/from
; RWMODE = read/write mode
; CUR_DMA_SEG:CUR_DMA -> xfer address
; PBLOCK = starting block of xfer
; MULT_CNT = # blocks to xfer
; exit: AX = BX = output
mov req_cmd,al
mov al,rwmode ; copy rwmode to where the device
mov req_rwmode,al ; driver can get the hint
mov ax,cur_dma ; get DMA offset
push ax ; (save it)
and ax,000Fh ; get offset within paragraph
mov req4_buffer,ax ; set transfer offset
pop ax ; (restore offset)
mov cl,4
shr ax,cl ; convert to paragraphs
add ax,cur_dma_seg ; add in the segment
mov req4_buffer+2,ax ; set transfer segment
mov ax,mult_sec ; get requested sector count
mov req4_count,ax ; set requested sector count
;------
ddioif:
;------
push es
mov al,adrive ; get selected drive
call get_ddsc ; ES:BX -> DDSC
mov ax,word ptr pblock
mov dx,word ptr pblock+WORD ; DX:AX = starting block
push es
les si,es:DDSC_DEVHEAD[bx] ; ES:SI -> device driver
if DOS5
; DOS 4 support
mov word ptr req4_bigsector,ax
mov word ptr req4_bigsector+2,dx
mov req_len,RH4_LEN ; set length of request header
test es:DH_ATTRIB[si],DA_BIGDRV ; large sector number support?
jz blockif10 ; no, normal request header
mov ax,-1 ; indicate we use 32-bit sector number
blockif10:
mov req4_sector,ax ; set requested sector address
else
mov word ptr req4_bigsector,ax
mov word ptr req4_bigsector+2,dx
mov req4_sector,ax ; set requested sector address
mov req4_sector+2,dx ; (support large DOS drives)
mov req_len,RH4_LEN ; assume 22 bytes in request header
test es:DH_ATTRIB[si],DA_BIGDRV ; large sector number support?
jz blockif10 ; no, normal request header
mov req_len,RH4_LEN+2 ; else indicate long request
blockif10:
endif
pop es
call block_device_driver ; make call to device driver
js blockif20
xor ax,ax ; no error
blockif20:
mov mult_sec,1 ; reset sector count
mov bx,ax ; AX, BX = return code
pop es
ret
block_device_driver:
;------------------
; entry: ES:BX -> DDSC, req_hdr partly filled in
; exit: AX = status after function
; SF = 1 if error occurred
; note: BX preserved
mov al,es:DDSC_MEDIA[bx]
mov req_media,al ; set current media byte
mov al,es:DDSC_RUNIT[bx] ; get relative unit #
mov req_unit,al ; set the unit
push ds
push es
push bx
push ds
lds si,es:DDSC_DEVHEAD[bx]
pop es
mov bx,offset req_hdr ; ES:BX -> request packet
call device_driver ; do operation
pop bx
pop es
pop ds
ret
; On Entry:
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -