home *** CD-ROM | disk | FTP | other *** search
- TITLE DISK -- A Multiple Disk Driver
- SUBTTL Header and global definitions
- PAGE 64D,132D ; make line length 132
- ; .286
- .radix 16
- OK186 EQU (@Cpu and 02)
-
- ;DISK_NO EQU 1 ; should get this from makefile
- RQ STRUC ; Standard Request Header
- RQ_LEN DB ? ; number of bytes passed -- first field
- RQ_UCD DB ? ; unit code
- RQ_CCD DB ? ; command code
- RQ_STAT DW ? ; status (return code)
- RQ_RES DB 8 DUP(?) ; reserved area
- RQ ENDS
- ; Status field bit equates
- STAT_ERR EQU 8000 ; There was an error. See low byte.
- STAT_BUSY EQU 200 ; Busy. Used in build BPB call.
- STAT_DONE EQU 100 ; Operation complete.
- ; low byte error return codes.
- STAT_GEN_FAIL EQU 0E ; general failure
- STAT_READ_FAULT EQU 0BH ; read fault
- STAT_WRITE_FAULT EQU 0A ; write fault
- STAT_NOT_FOUND EQU 8 ; sector not found
- STAT_UNK_CMD EQU 3 ; unknown command
- STAT_UNK_UNIT EQU 1 ; unknown unit
- ;
- CSEG SEGMENT
- ; start driver. first section is data
- ; (though it is in the code segment)
- ASSUME CS:CSEG,DS:NOTHING,ES:NOTHING
- ; special device header
- ; This MUST be at ORG 0 (i.e. the first code).
- START EQU $
- NEXT_DEV DD -1 ; ptr to next device
- ATTRIBUTE DW 4800 ; block device, supports 3.x, ioctl
- STRATEGY DW DEV_STRAT ; ptr to device strategy
- INTERRUPT DW DEV_INT ; ptr to dev interrupt handler
- DEV_COUNT DB 0 ; number of units
- DEV_NAME DB 'SEGdsk','0'+DISK_NO ; 7 bytes of filler
- DRVTBL LABEL WORD
- DW INIT
- DW MEDIA_CHK
- ; according to DOS tech manual, BUILD_BPB should never get called, as long as
- ; MEDIA_CHK always returns "media unchanged" [sic]. However, this is not true.
- ; DOS's "reserved" functions 1F and 32 call it, anyway.
- DW BUILD_BPB
- DW EXIT ; would be IOCTL_IN
- DW DOTRANS
- DW CMDERR
- DW CMDERR
- DW CMDERR
- DW DOTRANS
- DW DOTRANS
- DW CMDERR
- DW CMDERR
- DW IOCTL_OUT
- DW EXIT
- DW EXIT
- DW REMOVE
- DW CMDERR
- PTRSAV DD ? ; for DEVSTRAT
- SUBTTL Small Routines (interrupt, entry, exit, error, media check)
- PAGE
- STRATP PROC FAR ; device strategy
- DEV_STRAT:
- MOV WORD PTR CS:[PTRSAV],BX
- MOV WORD PTR CS:[PTRSAV+2],ES
- RET
- STRATP ENDP
-
- DEV_INT: ; device interrupt handler
- IF OK186
- PUSHA
- ELSE
- PUSH AX
- PUSH BX
- PUSH CX
- PUSH DX
- PUSH SI
- PUSH DI
- PUSH BP
- ENDIF
- PUSH DS
- PUSH ES
- ASSUME DS:CSEG
- MOV AX,CS ; get normal data addressability (DS=CS)
- MOV DS,AX
- LES BP,[PTRSAV]
- MOV AL,ES:[BP].RQ_CCD ; Command code
- CMP AL,10
- JA CMDERR ; Bad command
- CBW ; = xor ah,ah
- SHL AX,1 ; 2 times command = word table index
- MOV SI,AX
- JMP WORD PTR [SI].DRVTBL ; Index into table
- ;
- STD_BPB STRUC ; a bios parameter block
- B_PER_S DW ?
- SEC_PER_AU DB ?
- RES_SECTS DW ?
- NFATS DB ?
- NDIRENTS DW ?
- NSECTS DW ?
- MEDIA_DES DB ?
- NFATSECTS DW ? ; last word of standard portion
- STD_BPB ENDS
-
- STD_BPB_LEN EQU TYPE STD_BPB
-
- BPB STRUC
- DB STD_BPB_LEN DUP (?)
- RELSEC DD ? ; add-on: see part_rec.rel_sect
- PARTNO DB ? ; save partition number of this drive
- BPB ENDS
- ;
- BPB_NDX DW OFFSET BPB_SPACE
- DW (OFFSET BPB_SPACE)+(TYPE BPB)
- DW (OFFSET BPB_SPACE)+2*(TYPE BPB)
- DW (OFFSET BPB_SPACE)+3*(TYPE BPB)
- ;
- BBPBDATA STRUC ; build bpb data struct
- BP_RQ DB (TYPE RQ) DUP(?) ; standard part
- BP_MDES DB ? ; media descriptor (input)
- BP_TRANS DD DWORD PTR ? ; transfer address
- BP_RET1 DW ?
- BP_RET2 DW ?
- BBPBDATA ENDS
- ;
- BUILD_BPB:
- MOV AL,ES:[BP].RQ_UCD
- CBW
- MOV SI,AX
- SHL SI,1
- MOV SI,[SI].BPB_NDX
- MOV ES:[BP].BP_RET1,SI
- MOV ES:[BP].BP_RET2,CS
- JMP SHORT EXIT
- ;
- MCDATA STRUC ; media check data struct
- MC_RQ DB (TYPE RQ) DUP(?) ; standard part
- MC_MDES DB ? ; media descriptor (input)
- MC_RET DB ? ; returned byte: 1 if media unchanged
- MCDATA ENDS
- ;
- MEDIA_CHK: ; Winchesters never change
- MOV ES:[BP].MC_RET,1
- JMP SHORT EXIT
- REMOVE:
- MOV AX,STAT_DONE+STAT_BUSY ; "busy" bit = non-removable medium
- JMP SHORT ERR1
- CMDERR:
- MOV AX,STAT_ERR+STAT_UNK_CMD+STAT_DONE ; unknown command error
- JMP SHORT ERR1
-
- IOCTL_OUT: ; only valid return is a copy of the extended BPB
- MOV AL,ES:[BP].RQ_UCD
- CBW ; promote AL to AX with sign extension
- SHL AX,1 ; make device number into table offset
- MOV SI,AX
- MOV AX,ES
- LES DI,DWORD PTR ES:[BP].RW_TRANS
- MOV SI,[SI].BPB_NDX ; now SI points to the correct BPB
- MOV CX,TYPE BPB ; get length of data to transfer
- REP MOVSB
- MOV ES,AX
- MOV ES:[BP].RW_COUNT,TYPE BPB ; set length of data transferred
- JMP SHORT EXIT
-
- EXITP PROC FAR ; EXIT - All routines return through this path
- EXIT: MOV AX,STAT_DONE ; "done" (no error)
- ERR1: MOV ES:[BP].RQ_STAT,AX ; mark operation complete
- POP ES
- POP DS
- IF OK186
- POPA
- ELSE
- POP BP
- POP DI
- POP SI
- POP DX
- POP CX
- POP BX
- POP AX
- ENDIF
- RET ; restore regs and return
- EXITP ENDP
- SUBTTL Read and Write sectors
- PAGE
-
- RWDATA STRUC
- RW_RQ DB (TYPE RQ) DUP(?) ; standard part
- RW_MEDIA DB ? ; media descriptor
- RW_TRANS DD DWORD PTR ? ; transfer address
- RW_COUNT DW ? ; # of sectors to transfer
- RW_START DW ? ; first block to transfer
- RWDATA ENDS
- ;
- ; local variables:
- DISK_ADDR EQU 7F+DISK_NO ; 0x80 = disk #1, 0x81 = disk 2.
- NSECS DB ? ; number of sectors per track
- SHPROD DW ? ; NHEADS*NSECS
- ;
- DOTRANS:
- MOV AL,ES:[BP].RQ_UCD
- CBW ; promote AL to AX with sign extension
- MOV SI,AX
- INC AX ; (adjust for 1-based)
- CMP AL,[DEV_COUNT]
- JLE OK_COUNT
- MOV AX,STAT_ERR+STAT_DONE+STAT_UNK_UNIT
- JMP SHORT ERR1
- OK_COUNT:
- SHL SI,1 ; make device number into table offset
- MOV SI,[SI].BPB_NDX ; now SI points to the correct BPB
- MOV BX,ES:[BP].RW_START ; starting sector of request
- MOV DI,BX ; start_sec+sec_trans>num_secs =>error
- MOV AX,ES:[BP].RW_COUNT
- ADD BX,AX
- CMP BX,[SI].NSECTS
- JBE OK_COUNT2
- MOV AX,STAT_ERR+STAT_DONE+STAT_NOT_FOUND
- JMP SHORT ERR1
- OK_COUNT2:
- MOV BX,AX ; save
- MOV AX,WORD PTR [SI].RELSEC
- MOV DX,WORD PTR [SI+2].RELSEC
- ADD AX,DI ; add starting relative sector word to request
- ADC DX,0 ; add carry, if any, to high word
- DIV [SHPROD] ; AX=DX:AX div CX (CX=nsects*nheads), DX=DX:AX mod CX
- IF OK186
- SHL AH,6
- ELSE
- MOV CL,6 ; Need to put into screwy BIOS format
- SHL AH,CL
- ENDIF
- XCHG AL,AH
- MOV CX,AX
- MOV AX,DX ; now get head and sector number
- DIV [NSECS] ; now AH=sector number, AL=head number
- MOV DH,AL
- OR CL,AH
- INC CX ; sector number is 1 based, not 0 based (from MOD)
- MOV DL,DISK_ADDR ; drive code
- MOV AX,BX ; get original RW_COUNT back
- CMP AX,80
- JLE BIOS_OK1
- BIOS_BAD1:
- MOV AX,STAT_ERR+STAT_DONE+STAT_GEN_FAIL
- JMP SHORT ERR1
- BIOS_OK1:
- MOV BX,WORD PTR ES:[BP].RW_TRANS
- PUSH CX
- PUSH DX
- MOV DI,AX
- IF OK186
- SHL AX,9
- ELSE
- MOV CL,9
- SHL AX,CL
- ENDIF
- MOV DX,AX
- ADD AX,BX
- JNC BIOS_OK2
- SUB DX,AX
- MOV AX,DX
- IF OK186
- SHR AX,9
- ELSE
- SHR AX,CL
- ENDIF
- MOV ES:[BP].RW_COUNT,AX
- JMP SHORT SKIP_OK2 ; skip restore of original AX
- BIOS_OK2:
- MOV AX,DI ; original sector count was good
- SKIP_OK2:
- ; following depends on fact that BIOS read fcn is 2, write is 3
- MOV AH,2 ; AL has number of sectors; AH gets op code
- CMP ES:[BP].RQ_CCD,4 ; 4=read
- JE DO_OP
- INC AH
- DO_OP:
- POP DX
- POP CX
- PUSH ES
- MOV ES,WORD PTR ES:[BP+2].RW_TRANS
- INT 13
- POP ES
- JNC OK_TRANS ; Carry bit unaffected by POP
- CMP AH,11 ; CRC error -- ignore
- JNE BIOS_BAD1
- OK_TRANS:
- JMP EXIT
- ;
- ; the BPB table should be the LAST thing declared before initialization code,
- ; as we throw away whatever we don't need of it.
- BPB_SPACE BPB 4 DUP(<>) ; space for whatever BPB's we need
- ;
- SUBTTL Initialization code
- PAGE
- ; Equates
- CR EQU 0DH
- LF EQU 0AH
- BOOT_BPB EQU 0BH ; offset of main BPB in boot sector
- BOOT_PARTTAB EQU 1BE ; offset of partition table in boot sector
- SIGNATURE EQU 06
- ; Local Structs
- PART_REC STRUC
- BOOT_IND DB ?
- S_HEAD DB ?
- S_SEC_CYL DW ?
- SYS_IND DB ?
- E_HEAD DB ?
- E_SEC_CYL DW ?
- REL_SECT DD ?
- NUM_SECT DD ?
- PART_REC ENDS
- ;
- INITDATA STRUC
- INI_RQ DB (TYPE RQ) DUP(?) ; standard part
- INI_NUNITS DB ? ; number of units in driver
- INI_END_OFF DW ? ; ending address offset
- INI_END_SEG DW ? ; ending address segment
- INI_BPB_OFF DW ? ; BPB array offset
- INI_BPB_SEG DW ? ; BPB array segment
- INI_BLOCKDEV DB ?
- INITDATA ENDS
- ; Data
- PREFIX DB "Pdisk",'0'+DISK_NO,": $"
- COPYRIGHT DB "(c) 1986, 1988 S. E. Garfinkle. All Rights Reserved.$"
- NO_VOLS DB "No volumes found.$"
- NO_DRIVE DB "No valid drive connected.$"
- DRV_INST DB "0 Drive(s) installed.$"
- BOOT_SEC DB 200 DUP(?)
- SEC_BUF_2 DB 200 DUP(?)
- ; Initialization code
- INIT:
- PUSH ES ; save ES until end of initialization
- MOV AX,DS ; ES=DS
- MOV ES,AX
- MOV DX,OFFSET COPYRIGHT
- CALL PR_MSG
- MOV AH,8 ; set up for "determine drive characteristics" call
- MOV DL,DISK_ADDR
- INT 13
- CMP DL,DISK_NO
- JAE GOT_DISKS
- MOV DX,OFFSET NO_DRIVE
- CALL PR_MSG
- XOR DX,DX
- JMP END_INIT
- GOT_DISKS:
- AND CL,3F ; max # of sectors. rest of CL is cylinder high bits
- MOV [NSECS],CL
- MOV AL,DH ; max # of heads.
- INC AL ; was zero-based.
- MUL CL
- MOV [SHPROD],AX ; saves a lot of time later
- MOV AX,201 ; need to read master boot record: AH=read, AL=1 sector
- MOV BX,OFFSET BOOT_SEC
- MOV CX,1 ; cylinder 1, sector 0
- MOV DX,DISK_ADDR ; head 0, current disk
- INT 13
- CLD
- MOV SI,OFFSET BOOT_SEC+BOOT_PARTTAB
- ; DI does double duty here: it serves as the ptr to the BPBs being filled and
- ; also as the pointer to the end of retainable code.
- MOV DI,OFFSET BPB_SPACE
- MOV BX,OFFSET SEC_BUF_2
- MOV CX,4 ; max number of partitions
- MOV DX,((DISK_NO - 1) SHL 0C) ; volume count=0 (DL), partno=DISK_NO << 4
- LOOP1A:
- CMP [SI].SYS_IND,SIGNATURE
- JNE E_LOOP1A
- PUSH CX
- PUSH DX
- PUSH SI
- MOV CX,[SI].S_SEC_CYL
- MOV DH,[SI].S_HEAD
- MOV DL,DISK_ADDR
- MOV AX,201
- INT 13
- MOV SI,OFFSET SEC_BUF_2+BOOT_BPB
- MOV CX,STD_BPB_LEN
- REP MOVSB
- POP SI ; SI once again points to PARTTAB
- MOV AX,WORD PTR [SI].REL_SECT
- STOSW
- MOV AX,WORD PTR [SI+2].REL_SECT
- STOSW
- POP DX
- MOV AL,DH ; low 4 bits are partition number
- STOSB
- POP CX
- INC DL
- E_LOOP1A:
- INC DH
- ADD SI,TYPE PART_REC
- LOOP LOOP1A
- MOV AX,STAT_DONE
- OR DL,DL
- JNZ END_INIT
- NONE:
- MOV DX,OFFSET NO_VOLS
- CALL PR_MSG
- MOV AX,STAT_DONE+STAT_ERR+STAT_GEN_FAIL
- XOR DL,DL
- XOR DI,DI
- END_INIT:
- POP ES ; restore addressability to DOS request header
- MOV [DEV_COUNT],DL ; "not necessary," according to manual
- MOV ES:[BP].INI_NUNITS,DL
- MOV ES:[BP].INI_END_OFF,DI
- MOV ES:[BP].INI_BPB_OFF,OFFSET BPB_NDX
- MOV ES:[BP].INI_END_SEG,CS
- MOV ES:[BP].INI_BPB_SEG,CS
- MOV DI,OFFSET DRV_INST
- ADD BYTE PTR [DI],DL
- MOV DX,DI
- CALL PR_MSG
- JMP ERR1
-
- CRLF DB CR,LF,"$"
-
- PR_MSG PROC NEAR
- MOV AH,9
- PUSH DX
- MOV DX,OFFSET PREFIX
- INT 21
- POP DX
- INT 21
- MOV DX,OFFSET CRLF
- INT 21
- RET
- PR_MSG ENDP
-
- CSEG ENDS
- END
-