home *** CD-ROM | disk | FTP | other *** search
-
- page 66,132
- title '96 TPI DISK DRIVER'
- ; as of 7-4-1986
-
- ; Much of this code is from the Zenith MS-DOS 2.11
- ; BIOS, copyright Zenith Data Systems, 1983-4.
- ; It has been extensively hacked on, but seems to work.
- ;
- ; Features and limitations:
- ;
- ; 1) Device driver for 96 tpi drive support
- ; 2) Sets disk parameter by BPB head, so should read
- ; any 96tpi format with a valid BPB. I have used with
- ; the Tandy format ( as put by FORMAT96 ) and the
- ; DOS 3.2 format for 720k disks.
- ; 3) Does not double step for 48 tpi drives
- ; 4) Has not been tested with single sided drives
- ; 5) DOS considerations limit the reconfigurability to
- ; disks with 512 byte sectors. PCDOS requires a
- ; patch to use large sectors. For smaller sectors,
- ; the routine to read sector 0 would have to include
- ; trying different sector sizes, since the ROM bios
- ; routine used returns error if wrong sector size is
- ; used;
- ; 6) A timeout of 6 secs is used to determined if disk has
- ; been changed. Six seconds was the fastest I could change
- ; disk, so it seemed like a safe value.
- ; 7) Does not support single density diskettes
- ; 8) the assembly code is hardwired for 2 external 96 track
- ; drives and two internal 48 tpi drives. Changes would
- ; require adjusting the offset added to unit number to obtain
- ; physical floppy number, as well as changing the number of
- ; drives returned to DOS upon initialization.
- ;
-
- BPBTEST equ 1
- DEBUG equ 0 ; 1 to use debug lines
- BEGINBPB equ 11; offset in sector 0 to start of BPB
-
- ; INTERRUPT LOCATIONS AND PARAMETERS
-
- TIME_OF_DAY_INTR EQU 1AH
- TOD_GET EQU 0
-
- DISK_IO_INTR EQU 13H
- DIO_READ EQU 2
- DIO_WRITE EQU 3
- DIO_VERIFY EQU 4
- DIO_RESET EQU 0 ; 1 WAS TO REREAD DISK STATUS
-
- ; MISC. CONSTANTS
-
- SEC_SIZE EQU 512
- NUM_RETRY EQU 5
- TIME_OUT EQU 80H
-
-
- ;
- IF1
- %OUT PASS 1 STARTED
- ELSE
- %OUT PASS 2 STARTED
- ENDIF
-
- D_2SEC = 1 ; Assemble with 4 sec timeout for disk media check
-
- ; media check.
- DSK_MAXVAL = 6*18 ; 6 sec delay on disk changes
- TOD_LIM = 2*60*18 ; 2 min between stamp updates
- MIN_SEC = 9 ; Highest sector to update date/time on
-
- ; The Static Request header
-
- SRH_STRUC STRUC
- SRH_LEN DB ?; Length of command request structure
- SRH_UNIT DB ?; Sub unit number
- SRH_CMD DB ?; Command code(see below)
- SRH_STAT DW ?; Status code(see below))
- SRH_RES DB 8 DUP(?); Reserved for two sets of links
- SRH_STRUC ENDS
-
-
- ; Status codes (in upper half of SRH_STAT)
-
- SRHS_ERR EQU 80H; 1=error; 0=no error
- SRHS_RES1 EQU 7CH; reserved
- SRHS_BUI EQU 02H; 1=busy; 0=not busy
- SRHS_DON EQU 01H; 1=done; 0=not done
-
- ; Error codes (in lower half of SRH_STAT)
-
- SRHS_EWPR EQU 0 ; Write protect violation
- SRHS_EUKU EQU 1 ; Unknown unit
- SRHS_EDNR EQU 2 ; Drive not ready
- SRHS_EUKC EQU 3 ; Unknown command
- SRHS_ECRC EQU 4 ; CRC error
- SRHS_ELEN EQU 5 ; Bad request structure length
- SRHS_ESEEK EQU 6 ; Seek error
- SRHS_EUKM EQU 7 ; Unknown media
- SRHS_ESNF EQU 8 ; Sector not found
- SRHS_ENPP EQU 9 ; Printer out of paper
- SRHS_EWRF EQU 10 ; Write fault
- SRHS_ERDF EQU 11 ; Read fault
- SRHS_EGNF EQU 12 ; General failure
- SRHS_EMAX EQU 12 ; Max error code
-
-
- ; Read/Write Request packet
-
- CRW_STRUC STRUC
- CRW_SRH DB SIZE SRH_STRUC DUP(?) ; A static request header
- CRW_MBYTE DB ? ; Media descriptor
- CRW_TADDR DD ? ; Transfer addr
- CRW_CNT DW ? ; Byte/sector count
- CRW_START DW ? ; Starting sector number
- CRW_STRUC ENDS
-
-
- ; Non-destructive read(no wait) packet
-
- CIC_STRUC STRUC
- CIC_SRH DB SIZE SRH_STRUC DUP(?) ; A static request header
- CIC_CHAR DB ? ; Character from device
- CIC_STRUC ENDS
-
-
- ; Media check packet
-
- CMC_STRUC STRUC
- CMC_SRH DB SIZE SRH_STRUC DUP(?) ; A static request header
- CMC_MBYTE DB ? ; Media descriptor
- CMC_STAT DB ? ; Media status (see below)
- CMC_STRUC ENDS
-
- CMCS_CHG EQU -1 ; Media has been changed
- CMCS_DKN EQU 0 ; Don't know if media changed
- CMCS_NOC EQU +1 ; Media not changed
-
-
- ; Build BPB packet
-
- CBPB_STRUC STRUC
- CBPB_SRH DB SIZE SRH_STRUC DUP(?) ; A static request header
- CBPB_MBYTE DB ? ; Media descriptor
- CBPB_TADDR DD ? ; Transfer addr
- CBPB_BADDR DD ? ; BPB addr
- CBPB_STRUC ENDS
-
-
- ; Init packet
-
- CIN_STRUC STRUC
- CIN_SRH DB SIZE SRH_STRUC DUP(?) ; A static request header
- CIN_UNITS DB ? ; Number of units
- CIN_KADDR DD ? ; Break addr
- CIN_BADDR DD ? ; BPB array addr
- CIN_PADDR DD ? ; Init parameters
- CIN_STRUC ENDS
-
-
- ; A BPB (BIOS parameter block)
-
- BPB_STRUC STRUC
- BPB_SECSZ DW ? ; Sector size
- BPB_SPAU DB ? ; Sectors per allocation unit
- BPB_RES DW ? ; Reserved sectors
- BPB_NFATS DB ? ; Number of FAT's (file alloc tables)
- BPB_DIRENTS DW ? ; Number of director entries
- BPB_SECS DW ? ; Number of sectors
- BPB_MBYTE DB ? ; Media byte
- BPB_FATSECS DW ? ; Number of sectors occupied by a FAT
- BPB_SPT DW ? ; Number of sectors per track
- BPB_HEADS DW ? ; Number of heads
- BPB_HIDDEN DW ? ; Number of hidden sectors
- BPB_UNIT DB ? ; Unit number
- BPB_STRUC ENDS
-
- org 0 ;
- CODE segment byte ;
- ASSUME CS:CODE , DS:CODE,ES:CODE,SS:CODE
-
- mydisk_start label near
- DW -1 ; next device offset
- DW -1 ; segment of next driver
- DW 2000H ; 2000H = 0010 0000 0000 0000B ; attributes for non-ibm
- ;block device, ibm type=0
- DW OFFSET DISK_STRAT
- DW OFFSET DISK_INT
- db 2,'96TKDRV'
-
-
- ; Subroutine dispatch table for the disk driver
-
- DISK_TABLE LABEL near
-
- DW offset DISK_INIT ; Init
- DW offset MEDIA_CHECK ; Media check
- DW offset BUILD_BPB ; Build BPB
- DW offset UNKNOWN ; IOCTL INPUT
- DW offset DISK_READ ; Disk read
- DW offset BUSY ; Non destructive read
- DW offset NO_OP ; Status
- DW offset NO_OP ; Flush
- DW offset DISK_WRITE ; Write
- DW offset DISK_WRITE_VERIFY ; Write and verify
- DW offset NO_OP ; Output status
- DW offset NO_OP ; Output flush
- DW offset UNKNOWN ; IOCTL OUTPUT
-
- ; Floppy disk BPB's. These are the floppy disk BPB's used
- ; by the disk I/O code.
-
- FLOPPY_BPBS LABEL word
- ; note these are maximal bpb's so DOS can set up its buffers
- ; have declared here a longer fat than needed 4 sectors for each
- ; because going down to 1k allocation units would need more length
- ;
- ; DOS 3.1 does not seem to play by the rules. It interprets the
- ; BPB by a combination of the startup BPB and the BPB submitted
- ; by BUILD_BPB later
- ; example, disk BPB said 1 FAT, 112 entry directory
- ; DOS gave 2 fats, and 256 entry directory
- ; to get DOS to believe the 2 sectors per allocation block
- ; for this size disk, had to make it that way in the startup
- ; bpb
-
-
- BPBDISK0 BPB_STRUC <512,4,1,2,112,1440,0edh,2,9,2,0,0>
- BPBDISK1 BPB_STRUC <512,4,1,2,112,1440,0edh,2,9,2,0,0>
-
- floppy_start label word ; send these to DOS on startup
- ; this is for testing the effects of startup bph versus
- ; those read on the trk 0 sector 1
- ;
-
- BPB0 BPB_STRUC <512,4,1,2,112,1440,0edh,2,9,2,0,0>
- BPB1 BPB_STRUC <512,4,1,2,112,1440,0edh,2,9,2,0,0>
-
- BPB_VECTOR LABEL NEAR
- DW OFFSET BPB0
- DW OFFSET BPB1
-
- ; maximum format to be reported to DOS
-
- BPBDRIVE db 0 ;stores drive number for new bpb routine
-
- newbpbptr dw offset bpbdisk0 ;
-
- IF BPBTEST ; DEBUG ; caution these output routines seem to crash system
- ; if used too extensively
-
-
- hexdigit db '0123456789ABCDEF'
-
- ; uses dos calls.. should be ok if not redirected
-
- crlf proc near
- push ax
- push bx
- push cx
- push dx
- mov dl,0dh
- call stdtout
- mov dl,0ah
- call stdtout
- pop dx
- pop cx
- pop bx
- pop ax
- ret
- crlf endp
-
- putnibble proc near
- ; take nibble in al, send as hex to screen
- ; uses dos call
- and al,0fh ; make sure it's a nibble
- ; convert to ascii digit or A..F
- xor ah,ah
- mov bx,offset hexdigit
- add bx,ax ; point to digit
- mov dl,cs:[bx]
- call stdtout
- ret
- putnibble endp
-
- putbyte proc near
- ; print byte in al, high nibble first
- push ax
- push bx
- push dx
- push cx
- mov cl,4 ; rotate 4
- push ax
- ror al,cl
- call putnibble
- pop ax
- call putnibble
- pop cx
- pop dx
- pop bx
- pop ax
- ret
- putbyte endp
-
- putword proc near
- ; print in hex the word in ax, in high byte first order
- push ax
- mov al,ah
- call putbyte
- pop ax
- call putbyte
- ret
- putword endp
-
- printword proc near ; print word pointed to by ds:bx
- mov ax,[bx]
- call putword
- call crlf
- inc bx
- inc bx
- ret
- printword endp
-
- printbyte proc near ; print byte pointed to by ds:bx
- mov ax,[bx]
- call putbyte
- call crlf
- inc bx
- ret
- printbyte endp
-
- prtbpb0 proc near ; kills ax,bx,ds
- mov ax,cs
- mov ds,ax
- mov bx,offset bpbdisk0
- prtbpb0 endp
-
- printbpb proc near ; print to console the bpb pointed to by ds:bx
- push ax
- push bx
- push cx
- push dx
- push ds
- push es
- ;
- call printword ;0-1
- call printbyte ;2
- call printword ;3-4
- call printbyte ;5
- call printword ;6-7
- call printword ;8-9
- call printbyte ;10
- call printword ;11-12
- call printword ;13-14
- call printword ;15-16
- call printword ;17-18
- ;
- pop es
- pop ds
- pop dx
- pop cx
- pop bx
- pop ax
- ;
- ret
- printbpb endp
-
- ENDIF ; debug
-
-
-
- ; my floppy disk parameter table ,pointed to by
- ; $1Eh during ROM disk routines
- ; might want to use a macro to define this in case
- ; wanted more than one
-
- myparameters LABEL near
-
- DB 0EFH ; mode byte 1 used by SPECIFY command of 765
- ; top nibble is step rate, second is head unload time
- mode2 DB 002H ; mode byte 2 top 7 bits are head load time,
- ; last bit is is non-DMA mode flag
- DB 025h ; 025H ; delay on motor turnoff in 18.2 clicks/sec
- DB 002H ; bytes per sector 2 = 512 bytes
- DB 009H ; sectors per track
- DB 02AH ; gap length
- DB 0FFH ; data length 80h for 128, ff otherwise
- DB 050H ; gap while formating
- DB 0F6H ; formatting fill byte
- HDSET DB 0DH ; head settling time
- DB 02H ; was 4 motor start time in .25 sec increments
-
-
- ; Floppy disk timeout tables. These are used to store the current
- ; timer values to determine when the drive was last accessed.
-
- DSK_TIMOUT LABEL BYTE
- DD 0 ; 4 bytes
- DD 0 ; 4 bytes
-
-
- ;**************************************
- ; Variables used by the disk I/O code *
- ;**************************************
-
- RETRY_COUNT DB ? ; Location to keep retry count
- DRIVE DB ? ; Drive number for ROM
-
- TIM_PTR DW ? ; Pointer to timeout table of last access
-
- NUM_FLOPPY DB 2 ; Number of floppy drives in the system
- DOP_TYPE DB ? ; Disk operation type (ROM error code)
- DOP_VERIFY DB ? ; Verify flag (1 = verify, 0 = no verify)
-
-
- SEC_CNT DW ? ; Sector count
- OLD_SP1 DW ? ; Old stack pointer for error exit
- OLD_SP2 DW ? ; Old stack pointer for error exit
-
- ; Error codes returned by the ROM
-
- T_ERR DB 80H, 40H, 20H, 10H, 09H, 08H, 04H, 03H, 02H, 01H
- L_ERR = OFFSET $ - OFFSET T_ERR
-
- ; Error codes to return to MS-DOS (1 to 1 map to the table above)
-
- DB 02H, 06H, 0CH, 04H, 0CH, 04H, 08H, 00H, 0CH, 0CH
-
- ; messages, mostly for debugging
-
-
- IF DEBUG
- BUILDBPBMSG DB 0DH,0AH,'Call to Build_BPB in 96TPI.',0dh,0ah, '$'
- MEDIAmsg DB 0DH,0AH,'Call to MEDIA_CHECK in 96TPI.',0dh,0ah, '$'
- notchanged db 0dh,0ah,'Media not changed by timeout.',0dh,0ah,'$'
- timeoutmsg db 0dh,0ah,'In time out routine of media_chk.',0dh,0ah,'$'
- ENDIF; { debug }
-
-
- ; Packet pointer for the DOS packet
-
- PACKET DD ?
- SS_SAVE DW ? ; Storage for saving the DOS stack
- SP_SAVE DW ?
-
- ; MYDISK local stack
-
- DW 128 DUP(?)
-
- STACK_TOP LABEL WORD
-
- ; Disk driver initialization - Return the address of a BPB table
- ; number of units
- ;
- ; has to return the number of units,
- ; end of code
- ; address of array of pointers to BPB's for the units
-
-
-
- ;
- STRATEGY PROC FAR
-
- ; just store the packet address away
-
- DISK_STRAT:
- MOV WORD PTR CS:PACKET,BX
- MOV WORD PTR CS:PACKET+2,ES
- RET
- STRATEGY ENDP
-
-
- ;** DISK_INT - This routine passes the address of a jump
- ; table to the common interrupt routine
- ;
-
- DISK_INT proc FAR
-
- PUSH AX
- CLI
-
- ; turn off interrupts to switch stacks
-
- MOV CS:SS_SAVE,SS ; save previous stack
- MOV CS:SP_SAVE,SP
- MOV AX,CS
- MOV SS,AX ; make local stack
- MOV SP,OFFSET STACK_TOP
-
- ; turn interrupts back on
- ; save most registers, except ds:dx
-
- STI
- PUSH BX
- PUSH CX
- PUSH ES
- PUSH SI
- PUSH DI
- PUSHF
-
- ; ax still has cs
-
- mov ds,ax ; get right data segment
- LES BX,CS:PACKET ; ES:BX = request packet
- MOV SI,offset cs:DISK_TABLE ; Command table
- MOV CL,ES:SRH_CMD[BX] ; CL = requested command
- XOR CH,CH
- SHL CX,1 ; Make into word offset
- ADD SI,CX ; SI = pointer to routine
- JMP [SI] ; Go to it
-
- ; so when it gets to a command, ES:BX points to paket, ds to data segment
-
-
- ; Now exit from the request
- ; TWO POSSIBLE EXITS.. SUCCESS OR ERROR
-
- SUCESS: ; set ah to show no error
- XOR ax,ax
- OR ah,srhs_don ; ????? is srhs_don = 0
- JMP SHORT TRK96_EXIT
-
- ERROR: ; al will contain an error code, and ah is set to indicate
- ; existence of an error
-
- MOV AH,SRHS_ERR ; Flag error
- ; AL has the description of error
- TRK96_EXIT:
-
- LES BX,CS:PACKET ; ES:BX = packet
- MOV ES:SRH_STAT[BX],AX ; Save the status
-
- ; do a little cleanup
- call oldparms ; restore old pointer to disk parameter block
- mov cs:HDSET,0dh ; and make sure our private one is right
- mov cs:mode2,2 ; head load ; since adjusted on fly for read-write
-
- ; now set for return
-
- POPF
- POP DI
- POP SI
- POP ES
- POP CX
- POP BX
- ; get old stack
- CLI
- MOV SS,CS:SS_SAVE
- MOV SP,CS:SP_SAVE
- STI
- POP AX
- RET ; far return
-
- DISK_INT ENDP
-
- ;** Set the busy status flag to show input queue empty
- BUSY PROC NEAR
- MOV AH,SRHS_BUI
- JMP TRK96_EXIT
- BUSY ENDP
-
- ; Unknown command requested
-
- UNKNOWN proc near
- MOV AL,SRHS_EUKC ; Unknown command code
- JMP ERROR ; Flag error
- unknown endp
-
-
- ; Correct the transfer count and flag error, used only for
- ; R/W packets with CX=Number of blocks/chars left untransferred
-
- ERRORC PROC NEAR
- LES BX,CS:PACKET
- SUB ES:CRW_CNT[BX],CX
- JMP SHORT NO_OP
- ERRORC ENDP
-
- ; No operation
- NO_OP proc near
- JMP TRK96_EXIT
- no_op endp
-
-
- ;* MEDIA_CHECK - return the disk change status
- ; If a floppy
- ; Check if drive has been accessed within last
- ; 2 secs, if so, return no change, else return
- ; don't know.
- ;
- ; ENTRY: ES:BX - Pointer to DOS packet
- ; DS = CS
- ;
- ; EXIT: Packet status = Disk change status (-1 disk has changed,
- ; 0 don't know,
- ; 1 disk has not changed)
- ;
- MEDIA_CHECK PROC NEAR
-
- MOV ES:CMC_STAT[BX],CMCS_DKN ; Don't know if disk changed
- MOV AL,ES:SRH_UNIT[BX] ; get unit number
- IF D_2SEC ; Assemble if 2 sec delay chosen
- if debug
- ; push es
- ; push dx
- ; call putbyte
- ; mov dx, offset timeoutmsg
- ; call prtstring
- ; pop dx
- ; pop es
- endif;
- ; See when floppy was last accessed
-
- CBW ; make ax = al
- MOV CL,2 ; multiply by 4
- SHL AX,CL ; Make unit into dword pointer
- MOV DI,AX ; store ax in di for indexing later
- MOV CS:WORD PTR TIM_PTR,AX ; Store pointer for later use
- MOV AH,TOD_GET
- ; Get time from system
- push bx
- INT TIME_OF_DAY_INTR
- pop bx
-
- if debug
- ; push ax
- ; mov ax,cx
- ; call putword
- ; mov ax,dx
- ; call putword
- ; call crlf
- ; mov ax,cs:word ptr dsk_timout[DI+2]
- ; call putword
-
- ; mov ax,cs:word ptr dsk_timout[di]
- ; call putword
- ; pop ax
- endif; { debug }
- ;
- CMP AL,0 ; Same day?
- JNZ MC0 ; No
- SUB DX,CS:WORD PTR DSK_TIMOUT[DI] ; Get number of elapsed ticks
- SBB CX,CS:WORD PTR DSK_TIMOUT[DI+2]
- JNZ MC0 ; Jump if too many ticks
- CMP DX,DSK_MAXVAL ; More than DSK_MAXVAL ticks?
- JG MC0 ; Yes
- mov al,1
- mov ES:BYTE PTR CMC_STAT[BX],al ; Flag as not changed
- ; increments from 0 to 1
- if debug
- ; push es
- ; push dx
- ; mov dx, offset notchanged
- ; call prtstring
- ; pop dx
- ; pop es
- endif; { debug }
-
- MC0:
- ENDIF ; time_out check
- JMP TIM_RESET ; Reset timer and exit
-
- MEDIA_CHECK ENDP
-
-
- SUBTTL Build BPB for disk
- PAGE
- ;** BUILD_BPB
- ; Return the address of a BPB that describes
- ; the requested unit.
- ; The new method is to to read the first sector of the
- ; disk into a buffer, and move the bpb part into the bpb
- ; storage spot. This is not completely adaptable, since the
- ; implicit assumption is that sectors are 512 bytes long
- ;
- ;
- ; ENTRY: ES:BX - packet
- ; DS - MYDISK segment
- ;
- ; EXIT: Packet has pointer to new BPB
- ;
-
- oldbx dw 0
- oldes dw 0
-
- BUILD_BPB PROC NEAR
-
- ; Get BPB for floppy disk
- ;
- ife bpbtest ; quick and dirty bpb
- MOV AX, OFFSET cs:BPBDISK0
- MOV WORD PTR ES:CBPB_BADDR[BX],AX ; Return offset and segment
- MOV WORD PTR ES:CBPB_BADDR[BX+2],cs
- JMP SUCESS
- endif
-
- if bpbtest
- mov word ptr cs:oldbx,bx
- mov word ptr cs:oldes,es
- MOV AL,ES:SRH_UNIT[BX] ; get unit number
- and al,1 ; 0 or 1 only possible values
- mov cs:bpbdrive,al ; store it
- call newparms ; set disk parameters correctly
- call fetchfirst ; read first sector of disk
- jc fetcherror ; carry set if error
-
- getbpbsector:
- mov al,cs:bpbdrive ; decide which table to use
- or al,al
- jz set0 ;
- set1:
- mov ax, offset bpbdisk1 ; in case drive 1
- jmp movebpb
- set0:
- MOV AX,OFFSET BPBDISK0 ;
-
- MOVEBPB:
- mov word ptr cs:newbpbptr,ax ; store the bpb-address again
- ; get disk bpb for validity
- mov ax,word ptr cs:disk_buf[beginbpb] ; get number of bytes
- cmp ax,0200h ; minor test for validity of result
- jz FINISHUP ; jz takes 8 bit displacement
- jmp UNKNOWN ; can't handle this disk
-
- FINISHUP: ; haven't gotten here if unless new bpb is plausible
- MOV AX,offset disk_buf ; BX SET FROM FETCHBPB CALL
- add AX,BEGINbpb ;11 = offset to beginning of bpb in dos buffer
- mov si,ax ; move ds:si to es:di
- mov ax,cs
- mov ds,ax ; set ds:si = cs:offset disk_buf + 11
- mov es,ax
- mov di,word ptr cs:newbpbptr ;ax
- mov cx,type BPBDISK0 ; should give right length
- cld ; clear direction flag for loop
- move18:
- MOVSB
- loop move18
-
- ; now set pointers
- mov ax,word ptr cs:newbpbptr
- mov bx,word ptr cs:oldbx
- mov es,word ptr cs:oldes
- MOV WORD PTR ES:CBPB_BADDR[BX],AX ; Return offset and segment
- MOV WORD PTR ES:CBPB_BADDR[BX+2],CS
- JMP SUCESS
- endif; if bpbtest
- BUILD_BPB ENDP
-
- if bpbtest
- fetchfirst proc near
- ; set up presently only to control outboard drives 2..3 out of 0..3
- add al,2 ; outboard drives
- mov dl,al ; drive number set up int 13h read call
- ; use int 13h to read sector 1 of track 0 side 0
- ; need dl=drive, es:bx =dta, ah= diskop, al = sectors to read
- mov BX,offset disk_buf ; GET THE TRANSFER ADDRESS
- mov ax,cs
- mov es,ax
- mov ah, DIO_READ
- mov al,1 ; read one sector
- mov dh,0 ; side 0
- mov ch,0 ; track 0
- mov cl,1 ; sector 1 of track 0
- int DISK_IO_INTR
- ret
- fetchfirst endp
-
- fetcherror proc near
- ; error code in ah if carry flag was set
- ; get ready to do error analysis
- ; decode error return from ROM routine
- PUSH CS ; Set up addressing
- POP ES
- MOV AL,AH ; Code in AL for scan
- MOV CX,L_ERR ; Length of table
- MOV DI,OFFSET T_ERR
- CLD
- REPNZ SCASB
- MOV AL,[DI+(L_ERR-1)] ; Get the mapped error code
- jmp error ; could not read bpb sector
- fetcherror endp
-
- endif; if bpbtest
-
- prtstring proc near
- ; takes string in ds:dx and prints until find '$'
- push ax
- push bx
- push cx
- push dx
- beginhere:
- mov bx,dx
- mov al,[bx]
- cmp al,'$'
- jz allover
- push dx
- mov dl,al
- call stdtout
- pop dx
- inc dx
- jmp beginhere
- allover:
- pop dx
- pop cx
- pop bx
- pop ax
- ret
- prtstring endp
-
- stdtout proc near
- ; takes byte in dl and outputs to the console
- ; don't use DOS calls to avoid re-entrant problem
- ;
- push ax
- push bx
- push cx
- push dx
- mov ah,14
- mov al,dl
- mov bh,0
- mov bl,0 ; should not matter
- int 10h
- ; mov ah,0 ; send to printer for now
- ; mov al,dl
- ; mov dx,0
- ; int 17h
- pop dx
- pop cx
- pop bx
- pop ax
- ret
- stdtout endp
-
-
- oldparmofs dw 1 dup(?)
- oldparmseg dw 1 dup(?)
-
-
-
-
- ; Set up SI to point to disk BPB table
-
- ;** DISK I/O - This routine will handle all disk I/O calls
- ;
- ; ENTRY: ES:BX - pointer to DOS packet
- ; DS = CS
- ;
- ; EXIT: None
- ;
-
- DISK_READ PROC NEAR
-
- MOV DOP_TYPE,DIO_READ ; Read operation
- mov cs:HDSET, 0 ;
- mov cs:mode2,0 ; head load time
- call newparms
- JMP SHORT DOP1
-
- DISK_READ ENDP
-
- DISK_WRITE_VERIFY PROC NEAR
- mov cs:HDSET,0dh
- mov cs:mode2,2
- call newparms
- MOV DOP_VERIFY,1 ; Write with verify
- JMP SHORT DOP0
- DISK_WRITE_VERIFY ENDP
-
- DISK_WRITE PROC NEAR
- mov cs:HDSET,0dh
- mov cs:mode2,2
- call newparms
- MOV DOP_VERIFY,0 ; Write no verify
- DOP0:
- MOV DOP_TYPE,DIO_WRITE ; Write operation
- DOP1:
- MOV CX,ES:CRW_CNT[BX] ; Count of sectors
- CMP CX,0 ; If count = 0 then done
- JNZ DOP2
- JMP SUCESS
-
- ; Set up SI to point to disk BPB table
-
- DOP2:
- MOV SEC_CNT,CX ; Save sector count
- MOV OLD_SP1,SP ; Save stack for error exit
- MOV AL,ES:SRH_UNIT[BX] ; Get unit and save
- and al,1
- MOV DRIVE,AL
-
-
- ; Address disk parameter table
- ; how would the media byte know what it was?
-
- MOV AL,drive ; Get the drive number
- MOV AH,TYPE BPB_STRUC
- MUL AH
- ADD AX,OFFSET BPBDISK0
- MOV SI,AX ; Get pointer to BPB table
- mov ax,cs
- mov ds,ax
- MOV AL, BYTE PTR BPB_SPT[SI]
-
- ASSUME DS:code
-
- DOP5:
- MOV CX,SEC_CNT ; Set up sector count in case of error
-
- ; Check if last requested sector lies on this disk
-
- MOV DX,ES:CRW_START[BX]
-
- MOV DI,DX ; Start sector
- ADD DI,CX ; # of sectors
-
- JC DOP7 ; Bad parms, no such sector
-
- DOP6:
- CMP DI,BPB_SECS[SI] ; compare to last sector on disk
- JBE DOP8 ; Request OK
-
- DOP7:
- MOV AL,SRHS_ESNF ; Sector not found error
- JMP DISK_ERROR1
-
- DOP8:
- ADD DX,BPB_HIDDEN[SI] ; Add in hidden sectors
-
-
- ASSUME DS:code
-
-
-
- ; Calculate track, sector number and head
-
- DOP10:
- CALL DECODE ; Set necessary regs for call to DOP18
- MOV DL,DRIVE ; Move drive to DL for ROM
-
- add dl,2 ; map it to floppies 2,3
- ; instead of 0,1
-
- ; Check if transfer lies within this 64K boundry for DMA
-
- LES BX,ES:CRW_TADDR[BX] ; Get transfer address
- DOP11:
- MOV AX,ES ; Get 16 bits of transfer address
- PUSH CX
- MOV CL,4
- SHL AX,CL
- MOV CL,9 ; Prepare for next shift operation
- ADD AX,BX
- NEG AX ; Find remainder of this 64K
- JNZ DOP12
- MOV AH,80H ; Special case, full 64K available
- DEC CL ; Correct shift count
- DOP12:
- SHR AX,CL ; this 64K
- POP CX
- JZ DOP14 ; If none left in this 64K, get 1 sector
- CMP AX,SEC_CNT ; Can request be honored?
- ; AX < SEC_CNT Can't service
- ; AX >= SEC_CNT Can service
- JB DOP13
- MOV AX,SEC_CNT
-
- ; R/W the requested number of sectors
-
- DOP13:
- CALL DOP18 ; R/W the sectors
- JC DISK_ERRORL
- CMP SEC_CNT,0 ; Update sector count
- JNZ DOP14 ; R/W across 64kb boundry
-
- DISK_EXIT:
-
- TIM_RESET:
- IF D_2SEC
-
- MOV DI,CS:WORD PTR TIM_PTR ;
- ; was set by media_check??? Get offset into timout table
- MOV CS:WORD PTR TIM_PTR,0FFFH ; Make pointer invalid
- MOV AL,NUM_FLOPPY ; Get total number of floppies
- CBW
- MOV CL,2 ; Make an offset
- SHL AX,CL ; multiply by 4
- CMP DI,AX ; Is it a floppy?
- JGE DISK_EXIT1 ; No
- MOV AH,TOD_GET ; Get time from ROM
- INT TIME_OF_DAY_INTR
- MOV CS:WORD PTR DSK_TIMOUT[DI],DX ; Store low word
- MOV CS:WORD PTR DSK_TIMOUT[DI+2],CX ; Store high word
-
- DISK_EXIT1:
- ENDIF
-
-
-
-
- JMP SUCESS ; All done!
-
- ; Need to R/W 1 sector to cross 64Kb boundry
-
- DOP14:
- CLD ; Clear direction for later use
- PUSH ES ; Save user buffer area
- PUSH BX
-
- CMP DOP_TYPE,DIO_READ
- JZ DOP15 ; Read one sector
-
- ; Copy user data to internal buffer and write it
-
- PUSH ES ; Set up segments for source and dest.
- PUSH CS
- POP ES
- POP DS
- PUSH SI ; Save disk table pointer
- MOV SI,BX ; Set up source offset
- MOV DI,OFFSET DISK_BUF ; Set up dest. offset
- MOV BX,DI ; Set up X-fer offset for disk write
-
- PUSH CX ; Save CX
- MOV CX,SEC_SIZE/2 ; Move 1 sector (512b) of data
- REP MOVSW
- POP CX ; Restore CX
- POP SI ; Restore disk table pointer
- PUSH CS ; Restore data segment
- POP DS
-
- CALL DOP17 ; Write 1 sector
- JC DISK_ERRORL
- POP BX ; Restore user buffer
- POP ES
- ADD BH,SEC_SIZE SHR 8
- JMP SHORT DOP16
-
- DISK_ERRORL:
- JMP DISK_ERROR
-
- ; Read 1 sector, transfer it to the users area and continue
-
- DOP15:
- PUSH CS ; Set up MYDISK transfer address
- POP ES
- MOV BX,OFFSET DISK_BUF
- CALL DOP17
- JC DISK_ERRORL
- POP DI ; restore user transfer address
- POP ES
-
- PUSH SI ; Save disk pointer table
- MOV SI,OFFSET DISK_BUF
- PUSH CX ; Save CX
- MOV CX,SEC_SIZE/2 ; Move 1 sector of data to user
- REP MOVSW
- POP CX ; restore CX
- POP SI ; Restore disk table pointer
-
- MOV BX,DI ; Update user address
- DOP16:
- CMP SEC_CNT,0 ; All done?
- JZ DISK_EXITL
- JMP DOP11
- DISK_EXITL:
- JMP DISK_EXIT
-
- ;* Read/Write sectors
- ;
- ; Entry:
- ; AX - count of sectors to R/W (1 if entering at DOP17)
- ; CH - Track number
- ; CL - Sector number
- ; DL - Drive
- ; DH - Head number
- ; ES:BX - transfer address
- ; DS:SI - BPB of disk
- ; DOP_TYPE - Code to pass the ROM for read or write
- ;
- ; Exit:
- ; 'C' set, a disk error has occured
- ; 'C' clear, operation sucessful
- ; AX,
- ; BX (updated load address),
- ; CX (updated track and sector),
- ; DH (updated head number),
- ; DI.
- ;
- DOP17:
- MOV AX,1 ; R/W 1 Sector
- DOP18:
- MOV OLD_SP2,SP ; Save old stack for quick error exit
- MOV RETRY_COUNT,NUM_RETRY
- PUSH AX ; Save count
- MOV AL,BYTE PTR BPB_SPT[SI] ; Get sectors per track
- PUSH CX
- AND CL,3FH
- SUB AL,CL ; How many sectors left on this track?
- POP CX
- INC AL
- CBW ; Clear high byte
- POP DI ; Restore count
- CMP DI,AX ; See if request will fit in this track
- JAE DOP19 ; Yes, fulfill request
- MOV AX,DI ; No, get remainder of this track
-
- ; Do the actual disk read/write
-
- DOP19:
- PUSH AX ; Save count
- MOV AH,DOP_TYPE ; Pass operation type
- INT DISK_IO_INTR ; Call ROM
- JC RETRY ; Retry on error
- POP AX ; Restore count
-
- ; Check for verify
-
- CMP WORD PTR DOP_TYPE,1 SHL 8 + DIO_WRITE ; Check for verify-write
- JNZ DOP20
- PUSH AX
- MOV AH,DOP_VERIFY ; Verify sectors
- INT DISK_IO_INTR
- JC RETRY
- POP AX
-
- DOP20:
- SUB SEC_CNT,AX ; Update sector count
-
- MOV AH,AL ; Copy sector count to AH
- SHL AH,1 ; Turn into 512 byte sectors
- ADD BH,AH ; Update load address
- SUB AH,AH ; Fix up sector count
-
- SUB DI,AX ; Update count
-
- ; Update head, track and sector
-
- DOP21:
- PUSH BX ; Free up a register
- MOV BH,0 ; cl get Cylinder in BX
- ;ROL BH,1
- ;ROL BH,1
- ;AND BH,0 ; assume cylinder < 256
- MOV BL,CH
-
- AND CL,3FH ; Isolate sector bits
- ADD CL,AL ; Get new sector to start at
- CMP CL,BYTE PTR BPB_SPT[SI] ; Check if beyond end of track
- JBE DOP22 ; No, skip
- MOV CL,1 ; Past end, now at sector 1
- INC DH
-
- CMP DH,BYTE PTR BPB_HEADS[SI]
- JB DOP22
- SUB DH,DH ; Back to head zero
- INC BX ; Next track
- DOP22:
- ;
- ; ROR BH,1 ; Set up track and sector registers
- ; ROR BH,1
- OR CL,BH
- MOV CH,BL
- POP BX ; Restore transfer address
-
- CMP DI,0 ; Operation done?
- JNZ DOP23
- CLC
- RET
- DOP23:
- MOV AX,DI ; Update remaining sector count
- JMP DOP18 ; Continue
-
- RETRY:
- PUSH AX ; Save return code
- MOV AH,DIO_RESET ; Reset disk system
- INT DISK_IO_INTR
- POP AX ; Restore return
- CMP AH,TIME_OUT ; Test for disk time out
- JZ RETRY1
- DEC RETRY_COUNT
- JZ RETRY1
- POP AX ; Restore count and
- JMP DOP19 ; try again
- RETRY1:
- MOV SP,OLD_SP2 ; Restore stack to entry conditions
- STC ; Show error
- RET
-
- ; Retry error has occured. Get the ROM error code and map to
- ; an MS-DOS error code.
-
- DISK_ERROR:
- PUSH CS ; Set up addressing
- POP ES
- MOV AL,AH ; Code in AL for scan
- MOV CX,L_ERR ; Length of table
- MOV DI,OFFSET T_ERR
- CLD
- REPNZ SCASB
- MOV AL,[DI+(L_ERR-1)] ; Get the mapped error code
-
- ;* Disk error
- ;
- ; Entry: AL - Error code
- ; SEC_CNT - Count of sectors not yet done
- ;
- DISK_ERROR1:
- MOV CX,SEC_CNT ; Return the number of sectors left to transfer
- MOV SP,OLD_SP1 ; Pop the stack to entry conditions
- JMP ERRORC
-
- DISK_WRITE ENDP
-
- NEWPARMS proc near ; can't use dos call to reset pointer
- ;ret ; for testing
- cli
- push ax
- push bx
- PUSH DX
- PUSH DS
- SUB DX,DX
- MOV DS,DX ; look in segment 0
-
- ASSUME DS:NOTHING
- ; have a pointer to current disk parameter table at 1eh
- mov bx,001eh shl 2 ; 1eh double words
- mov ax, offset cs:myparameters
- mov [bx],ax
- inc bx
- inc bx
- mov ax,cs
- mov [bx],ax
- ;
- POP DS
- POP DX
- pop bx
- pop ax
- sti
- ret
- NEWPARMS ENDP
-
- assume ds:code
-
- oldparms proc near
- ;ret ; for testing
- cli
- push ax
- push bx
- PUSH DX
- PUSH DS
- xor ax,ax
- MOV DS,ax ; look in segment 0
- ASSUME DS:NOTHING
- ; have a pointer to current disk parameter table at 1eh
- mov bx,001eh shl 2 ; point to current ROM parameters
- mov ax,cs:oldparmofs ; get value there
- mov [bx],ax
- mov ax,cs:oldparmseg ; get value there
- inc bx
- inc bx
- mov [bx],ax
- POP DS
- POP DX
- pop bx
- pop ax
- sti
- ret
- oldparms endp
-
-
- assume ds:code
-
- ; DECODE - This routine will take a MS-DOS logical sector number
- ; and decode it into head sector and cylinder for the
- ; given disk.
- ; add adjustment to double step 96 tpi drive if using 48 tpi media
- ; ; this not working yet
- ;
- ; ENTRY: DX - Logical sector number
- ; DS:SI - Pointer to BPB for this disk
- ;
- ; EXIT: CH - Cylinder number
- ; CL - Sector number
- ; DH - Head
- ;
- ; USES: AX
- ;
- DECODE PROC NEAR
-
- PUSH BX
- MOV BX,DX
- SUB AX,AX
- XCHG AX,DX ; AX = Start sector
- ; divide dx:ax by sectors per track
- ; get quotient in ax, remainder in dx
-
- DIV WORD PTR BPB_SPT[SI] ; divide by sectors per track
- ; run sectors 1 .. spt
- INC DL ; DL = Sector #, AX = track
- MOV CL,DL ; Move sector into CL for ROM
- SUB DX,DX
-
- ; decide on tracks
- ; track in ax, head in dl
-
- DIV WORD PTR BPB_HEADS[SI]
- MOV DH,DL ; Put head into DH for ROM
-
- ; max cylinder is 8 bits = 1024
-
- AND AH,0 ; Ensure no high bits for cyl.
- OR CL,AH ; Set sector and cyl. high bits
- MOV CH,AL ; Low part of cyl. for ROM
-
- around: MOV DL,BL ; Restore DL
- POP BX
- RET
-
- DECODE ENDP
-
- DISK_BUF LABEL BYTE ; Disk buffer after initialization complete
- db 512 dup(?) ; 512 dup(?)
-
-
- MYDISK_END LABEL NEAR
-
- DISK_INIT PROC NEAR
- ; put at end so can discard after initialization
- ; DISK_INIT fills in ES:BX with address of Request header
- ; returns break address in ds:dx
- ; so don't save old ds:dx on stack
-
- ; the device driver init is slightly different from the
- ; bios init, in that ds:dx contains information
- ; hence have to
- ; change disk_int
- ; disk_exit
- ; use mdisk as a template for these changes
-
-
- push ax
- push bx
- push es
- mov ax,cs
- mov ds,ax
- mov ah,19h ; get current drive number
- int 21h
- mov dl,al ; set up call to find out number of drives
- mov ah,0eh ; log current disk again and get number of drives
- int 21h
- add al,'A' ; make it alpha
- mov drive0,al ; put into signon message
- inc al
- mov drive1,al
- mov dx, offset hereiam
- call prtstring
- pop es
- pop bx
- pop ax
-
-
- ;have told world what we do
-
- ; remember standard disk parameters from DOS
- cli
- push ax
- push bx
- push ds
- xor ax,ax
- mov ds,ax
- mov bx,001eh shl 2 ; 1eh double words
- mov ax,[bx] ; get offset
- mov cs:oldparmofs,ax
- inc bx
- inc bx
- mov ax,[bx]
- mov cs:oldparmseg,ax
- pop ds
- pop bx
- pop ax
- sti
-
- ; return number of units
-
- mov al,2 ; NUM_DISKS
- MOV ES:[CIN_UNITS + BX],al ; two units
-
- ; return end of this driver code
- ; normalize it to largest possible segment
-
- mov ax,cs
- mov ds,ax
- mov dx, offset mydisk_end + 17; { add a little room }
- mov cx,4
- shr dx,cl ; make it a paragraph boundary
- add ax,dx ; ax had cs from before
- xor dx,dx ; round it off
-
- ; must also return break address in DS:DX, according to manual
-
- mov ds,ax ; segment
- MOV ES:word ptr CIN_KADDR[BX], DX ; Break address
- MOV ES:word ptr CIN_KADDR[BX+2],AX ; dword
- MOV ES:word ptr CIN_BADDR[BX], OFFSET BPB_VECTOR
- MOV ES:word ptr CIN_BADDR[BX+2],CS
-
- ; what about status word, and media byte??
-
- JMP SUCESS
-
- DISK_INIT ENDP
-
- HEREIAM DB 0dh,0ah,'96 TPI Driver installed for two external drives, '
- drive0 db 43h,': and '
- drive1 db 44h,':'
- if d_2sec
- DB 0dh,0ah,'Version 1.3 using media change timeout of 6 seconds.'
- endif;
- if bpbtest
- db 0dh,0ah,'Reads track 0, side 0, sector 1 BPB'
- db ' for disk information.'
- endif;
- if debug
- db 0dh,0ah,'Debugging test version.'
- endif;
- db 0dh,0ah,'Copyright by Clarence Wilkerson 6-11-1986.'
- db 0dh,0ah,'$'
-
- MYDISK_LENGTH = OFFSET MYDISK_END - OFFSET MYDISK_START
-
- CODE ENDS
- END mydisk_start