PAGE 60 TITLE Floppy Disk Low-level Driver module ; ; SGDVR.MAC ; The Systems Group ; FDC-2800 low-level driver routines. ; ; edit history, ; 80Dec18 jl - Initial debug complete (8" sng & dbl density). ; 81Jan06 jl - Polled operation of FDC added but not debugged. ; 81Jan12 jl - Polled operation debugged for the wire wrap board. ; 81Jan24 jl - Sector number changed to a 16-bit value. ; 81Feb17 jl - Debugged for Production prototype board. (FDC-2800/1) ; 81Jun06 jl - Support added for driver DMA option flag. ; 81Jul16 jl - Driver altered for new FBIOS compatability. ; 81Aug21 jl - Macro added for building disk parameter headers. ; Source is written for MACRO-80 (Microsoft's macro assembler) .Z80 ; for ZILOG opcodes ; CONDITIONAL EQUATES ARE LOCATED IN FOLLOWING FILE INCLUDE SYSTEM.EQU ; Conditional Switch error messages IF1 IF MPMSYS AND NOT DMAOP ; MP/M driver without DMA invalid .PRINTX "*** SWITCH ERROR *** MPMSYS without DMAOP" ENDIF ENDIF ; Console messages IF1 ; if pass 1 IF DMAOP .PRINTX "Systems Group FDC-2800 driver" ELSE .PRINTX "Systems Group FDC-2801 driver" ENDIF IF MPMSYS .PRINTX "MP/M system operation" ENDIF IF LDRSYS .PRINTX "Loader BIOS operation" ENDIF IF MINI .PRINTX "Mini drive operation" IF TPI96 .PRINTX "For 96 TPI drives" ENDIF ENDIF ENDIF SUBTTL Equates and Definitions PAGE ; These entry points are used by the FBIOS driver. GLOBAL SECBUF ; base of sector buffer ; These are the FBIOS driver globals. EXTRN DVRTBL ; drive descriptor block EXTRN DIRBUF ; base of directory buffer EXTRN PNTMSG ; print message utility routine EXTRN OPFLGS ; driver option flags IF MPMSYS ; addition external entry points for flag operations and ISR stack. EXTRN ISRSTK ; XIOS stack saver routine EXTRN FLAGSET ; MP/M set flag routine (ACC=flag) EXTRN FLAGWAIT ; MP/M flag wait routine (ACC=flag) ; Some additional equates for MP/M operation FDCFL EQU 8 ; floppy disk MP/M flag number FDCVEC EQU 16H ; Page 0 vector location ENDIF ; MPMSYS ; Some CPD-2800 equates for 9519 interrupt controller UICD EQU CPUB+12 ; UIC data port UICC EQU CPUB+13 ; UIC status/control port ; Some CPC-2810 equates IVCNTR EQU CPUB+24 ; Int vector/LED control port ; Drive descriptor block layout. DSK EQU 0 ; current disk TRK EQU 1 ; current track SEC EQU 3 ; current sector FMT EQU 5 ; format type DMA EQU 6 ; DMA address DPH EQU 8 ; current DPH address RESULT EQU 10 ; results (returned from driver) ; 765 drive parameter equates. RTRYS EQU 5 ; Number of Retrys IF DMAOP ND EQU 0 ; 0=DMA mode ELSE ND EQU 1 ; 1=non-DMA mode ENDIF IF MINI ; 5" drive parameters SRT EQU 8 ; drive step rate in ms. HUT EQU 480 ; head unload time in ms. HLT EQU 40 ; head load time in ms. SRTHUT EQU (16-SRT/2) SHL 4 + HUT/32 HLTND EQU HLT/4 SHL 1 + ND ELSE ; 8" drive parameters SRT EQU 6 ; drive step rate in ms. HUT EQU 240 ; Head Unload Time in ms. HLT EQU 50 ; Head Load Time in ms. SRTHUT EQU (16-SRT) SHL 4 + HUT/16 HLTND EQU HLT/2 SHL 1 + ND ENDIF ; ; FDC-2800 port assignments. IF MINI DSKB EQU 090H ; base of 5" controller ENDIF IF NOT MINI DSKB EQU 080H ; base of 8" controller ENDIF FDCMSR EQU DSKB+0 ; 765 FDC Main status register DDATA EQU DSKB+1 ; 765 FDC Main data register CONTRL EQU DSKB+2 ; Main board control port ZDMA EQU DSKB+4 ; Z-80 DMA device ; ; NEC 765 intruction set used. SCYCMD EQU 03H ; specify drive parameters SDSCMD EQU 04H ; sense drive status WRCMD EQU 05H ; write sector RDCMD EQU 06H ; read sector RECCMD EQU 07H ; recalibrate SISCMD EQU 08H ; sense interrupt status RIDCMD EQU 0AH ; read sector ID SKCMD EQU 0FH ; seek command ; ; Control Port (CONTRL) bit assigment for output. BTENA EQU 0 ; Boot enable (0=true) SBENA EQU 1 ; Sector buffer enable (1=true) INTEN EQU 2 ; Interrupt enable (1=unmask) ROMEN EQU 3 ; ROM enable (0=true) MOTOR EQU 4 ; Motor control (1=start) PIOEN EQU 5 ; programmed I/O mode (1=true) ; Control Port bit assignment for input. INTRQ EQU 7 ; interrupt request (input) SUBTTL Disk Parameter Headers and Blocks PAGE ; DISK PARAMETER BLOCKS - (18-bytes long) DPBLKS: IF MINI ; 5" disk parameters ; double-density, single-sided, 1024 byte sector size DB 63H ; format type DW 0 ; no translation ; patched DPB IF TPI96 ; for 96 TPI drives DW 40 DB 4,15 ; 2k block size DB 1 DW 194 ; 195 blocks DW 127 DB 0C0H,0 DW 32 DW 2 ELSE ; for 48 TPI drives DW 40 ; 8 per sector times 5 DB 3,7 ; 1k block size DB 0 DW 189 ; 190 blocks DW 63 DB 0C0H,0 DW 16 DW 2 ENDIF ; TPI 5" drives ; double-density, double-sided, 1024 byte sector size DB 0E3H ; format type DW 0 ; no translation ; patched DPB IF TPI96 ; for 96 TPI drives DW 80 DB 4,15 ; 2k block size DB 0 DW 394 ; 395 blocks DW 127 DB 0C0H,0 DW 32 DW 1 ELSE ; 48 TPI drives DW 80 ; 8 per sector times (2 times 5) DB 4,15 ; 2k block size DB 1 DW 194 ; 195 blocks DW 127 DB 0C0H,0 DW 32 DW 1 ENDIF ; TPI 5" drives ELSE ; 8" disk parameter blocks ; Single-density, single-sided, CP/M standard DB 00H ; density format type DW XLTSD0 ; standard translate table ; patched DPB DW 26 ; sectors per track (SPT) DB 3,7 ; block shift and mask (BSH)(BLM) DB 0 ; extent mask (EXM) DW 242 ; disk storage max (DSM) DW 63 ; director max (DRM) DB 0C0H,0 ; dir alloc (AL0)(AL1) DW 16 ; dir check size (CKS) DW 2 ; offset (OFF) ; Double-density, single-sided, SG standard 1k sectors DB 043H ; density format type DW 0 ; no translate table ; patched DPB (see first for details) DW 64 DB 4 DB 15 ; 2k block size DB 0 DW 303 DW 127 DB 0C0H DB 0 DW 32 DW 1 ; Double-density, double-sided, SG standard 1k sectors DB 0C3H ; format type DW 0 ; patched DPB DW 128 DB 5,31 ; 4k block size DB 1 DW 303 DW 255 DB 0C0H,0 DW 64 DW 1 ENDIF IF1 IF ($-DPBLKS) MOD 18 NE 0 .PRINTX "**** WARNING **** INCORRECT DISK PARAMETER LENGTH" ENDIF ENDIF NODPBS EQU ($-DPBLKS)/18 ; count of all DPB's IFF MINI XLTSD0: DB 1,7,13,19,25,5,11,17,23 DB 3,9,15,21,2,8,14,20,26 DB 6,12,18,24,4,10,16,22 ENDIF IF MINI ; 5" buffer sizes IF TPI96 ; 96 TPI drives ALVSIZ EQU 50 ; 50 bytes ELSE ALVSIZ EQU 25 ; 25 bytes ENDIF CSVSIZ EQU 32 ELSE ; 8" buffer sizes ALVSIZ EQU 39 CSVSIZ EQU 64 ENDIF ; Disk Parameter Header macro. ; Used to build the proper headers for up to four drives. ; DN is the only entry parameter which should be set to the Logical OS ; drive letter (A through P). ??? EQU 0 ; unknown, patched by FBIOS NXTB DEFL BUFBASE ; initial next buffer addr DX DEFL 0 ; next physical drive number MAKDPH MACRO DN DPH.&DN:: ;; define GLOBAL header address DW ???,0,0,0,DIRBUF,??? DW NXTB ;; alocation buffer DW NXTB+CSVSIZ ;; check vector buffer NXTB DEFL NXTB+CSVSIZ+ALVSIZ ;; find next buffer address IF DX EQ 0 DW FLINIT ;; driver init routine ELSE DW 0 ;; for only the first header ENDIF DW FLFMT,FLREAD,FLWRITE ;; driver entry points DB DX ;; physical drive number DX DEFL DX+1 ;; inc drive number ENDM ;; done ; DISK PARAMETER HEADERS. MAKDPH A ; build a Logical drive A IFF LDRSYS ; not loader BIOS operation MAKDPH B ; build a Logical drive B MAKDPH C ; Logical drive C MAKDPH D ; Logical drive D ENDIF ; Compute the total size of all alocation and check vector buffers BUFSIZ EQU DX*(ALVSIZ+CSVSIZ) SUBTTL Define disk format PAGE ; Define Drive Format. On entry, HL points to the drive descriptor block. ; On exit, the ACC=Drive format type, or FF in not determined. ; FLFMT: ; ; Validate the drive number requested to be defined ; and a branch to format error (FMTERR) if beyond limit. ; CALL DSKSEL ; select in new LD A,(INIFL) ; get first time init flag OR A ; test it for board presence JR Z,FMTERR ; if board not present ; ; Issue a read ID field in single-density and branch to ; good ID read with the FMT type if successful. ; LD A,1 LD (RECFL),A ; reset the recalibrate flag DFMT1: LD B,RIDCMD ; get Read ID command CALL READID ; issue it LD A,(RWSTBL+6) ; get returned N for FMT sector size JR Z,GDID ; if good read ID ; ; Now try a read ID field in double-density and branch to ; good ID read with the FMT type if successful. ; LD B,RIDCMD+40H ; try double-density next CALL READID ; issue it LD A,(RWSTBL+6) ; get returned N for FMT sector size SET 6,A ; set double-density bit-6 JR Z,GDID ; if good read ID ; ; Check the recalibrate flag, and recalibrate the drive if first pass ; through this routine. set recal flag to show recal done. ; LD HL,RECFL DEC (HL) ; check recal flag JR NZ,FMTERR ; if recal already performed ; CALL RECAL ; do one recalibrate JR DFMT1 ; and try format look-up again ; ; ; The ACC contains the FMT type as far as density and sector size go. ; Now use the sense drive status command to test for a two sided disk. ; GDID: IF MINI SET 5,A ; set bit-5 for mini FMT ENDIF PUSH AF ; save FMT type CALL SDS ; sense drive status POP AF ; restore FMT type LD HL,RWSTBL ; point to ST-3 BIT 3,M ; test two sided bit-3 JR Z,FDPB ; no, FMT correct SET 7,A ; yes, set double-sided bit-7 IF MINI PUSH AF ; save FMT value AND 40H ; mask density bit OR RIDCMD ; add in read ID command LD B,A LD HL,DRIVE ; point to RW table SET 2,M ; set for head 1 CALL READID ; read ID field from head 1 JR NZ,M1S ; disk is single-sided if ID read error LD A,(RWSTBL+4) ; get head byte from read ID field CP 1 ; is it truly head 1? JR NZ,M1S ; no, disk is single-sided POP AF JR FDPB ; with two-sided FMT value M1S: POP AF RES 7,A ; clear two-sided bit ; ENDIF ; MINI ; ; Find proper DPB in list ; FDPB: LD C,A LD B,NODPBS LD HL,DPBLKS ; point to base of blocks FDPB.1: LD A,(HL) CP C RET Z ; done if match found LD DE,18 ADD HL,DE DJNZ FDPB.1 ; ; Branch here if device read errors or format cannot be found ; FMTERR: LD HL,0 RET SUBTTL Disk Reading and Writing PAGE ; Read entry point. On entry, HL points to the drive descriptor block. ; On exit, RESULT in drive descriptor block set to 0 for success or ; error code in the case of read errors. ; FLREAD: LD B,RDCMD ; B= FDC read command XOR A ; RWFL flag value for reading JR DRDWR ; common routines ; Write entry point. On entry, HL points to the drive descriptor block. ; On exit, RESULT byte of drive descriptor block set to 0 for success ; or error code in the case of write errors. ; FLWRITE: LD B,WRCMD ; B= FDC write command LD A,1 ; RWFL flag value for writing ; ; Common routines to both reading and writing. DRDWR: LD (RWFL),A ; set the RWFL flag ; ; Set up the read or write operation for single- or double- ; density as specified by bit-6 of the format type field in ; the drive descriptor block. ; LD A,(DVRTBL+FMT) ; get format type specifier BIT 6,A ; test double-density bit-6 JR Z,RDWRSD ; if reading or writing single-density SET 6,B ; set MFM bit-6 in FDC command RDWRSD: LD A,B LD (FDCOP),A ; store FDC command ; ; Select in drive (SELDSK subroutine used) ; CALL DSKSEL ; use subroutine ; ; Select either head-0 or head-1 from the format type value. ; XOR A LD (HEAD),A ; reset head field LD HL,DVRTBL+FMT ; point to format type value BIT 7,M ; test head-1 select bit-7 JR Z,ONESID ; if head-0 selected LD HL,DRIVE SET 2,M ; set drive number for head-1 INC HL INC HL LD (HL),1 ; set head field for head-1 ONESID: ; ; Set the sector (SECTOR) and end of track (EOT) fields from the ; selected sector in the drive descriptor block. ; LD A,(DVRTBL+SEC) ; get selected sector LD (SECTOR),A ; set sector field LD (EOT),A ; set EOT field ; ; Lookup the values for the N,GPL and DTL fields from the ; RW values table. Table values are picked based on sector size. ; LD A,(DVRTBL+FMT) ; get the format type value AND 3 ; mask the sector size bits 0&1 LD (N),A ; set the N field ADD A,A ADD A,A ; N value times 4 LD C,A LD B,0 ; prep for double add LD HL,RWVALS ; point to beginning of table ADD HL,BC ; point to entry LD A,(HL) ; get GPL entry LD (GPL),A ; and patch it INC HL LD A,(HL) ; get DTL entry LD (DTL),A ; and patch it INC HL LD (SAVHL),HL ; save pointer to TC or transfer code ; ; Reset the recalibrate flag ; LD A,1 LD (RECFL),A ; set recal flag ; ; Seek to the selected track. NOTE: re-seek entry point for errors. ; RESEEK: LD A,(DVRTBL+TRK) ; get selected track LD (TRACK),A ; put in RW table LD BC,SKCMD SHL 8 + 3 ; get seek command and length CALL CMDRDY ; send command CALL DPOLL ; wait for completion ; ; Start of reading and writing. NOTE: retry entry point also. ; LD A,RTRYS ; get initial retry count DRETRY: LD (RTCNT),A ; set retry counter ; ; If we are operating the FDC with the Z80 DMA device, ; Form the Z80 DMA device reading and writing table ; for the current operation (patch WR0,TC, and DMA address). ; Send this table to the Z80 DMA to enable the transfer. ; IF DMAOP LD HL,WR0 ; point to DMA write register 0 RES 2,M ; set direction bit-2 for reading first LD A,(RWFL) ; get read/write flag OR A ; test for reading JR Z,DMAM1 ; if reading, direction is correct SET 2,M ; set direction bit-2 for writing DMAM1: LD HL,(SAVHL) ; restore pointer to Terminal Count value LD E,(HL) INC HL LD D,(HL) ; Terminal Count in DE LD (TC),DE ; set TC of Z80 DMA RW table LD HL,(DVRTBL+DMA) ; get selected DMA address LD (ADDR),HL ; set DMA address of Z80 DMA RW table LD HL,RWDMA ; point to DMA table LD BC,RWDMAL SHL 8 + ZDMA ; port and length OTIR ; send Z80 DMA RW table ELSE ; NOT DMAOP CALL SDS ; get drive status LD HL,RWSTBL BIT 5,M ; test drive ready LD A,2 ; get error code JP Z,RWERRE ; exit if NOT ready LD A,(RWFL) OR A JR Z,PGM1 BIT 6,M ; test write protect line LD A,3 JP NZ,RWERRE PGM1: ENDIF ; NOT DMAOP ; ; ; Now send the 765 RW table to that device to enable ; the current read or write operation. ; LD A,(FDCOP) LD B,A ; FDC command in B LD C,9 ; length of command in C CALL CMDRDY ; issue command ; ; If we are operating the 765 in programmed I/O mode, now ; we must enable Programmed I/O on the controller board and ; set up the registers for the INIR or OTIR loops. ; IFF DMAOP DI ; LD HL,(SAVHL) ; restore pointer for transfer code LD B,(HL) ; initial INIR count in B reg INC HL LD D,(HL) ; number of INIR's in D reg LD HL,(DVRTBL+DMA) ; DMA address in HL LD C,DDATA ; FDC data port in C ; LD A,(LATCH) ; get current control latch SET PIOEN,A ; set the Programmed I/O bit LD (LATCH),A ; update current control latch OUT (CONTRL),A ; send new latch to the board ; ; ; Now branch to the proper Programmed I/O loop ; depending on if we are reading or writing. ; LD A,(RWFL) ; get the RW flag OR A ; test for reading JR Z,PGMRD ; to read loop if reading ; ; This next instruction is performed because the NEC 765 will ; throw away the first byte sent to it when writing. ; OUT (DDATA),A ; ; Z80 Programmed I/O write loop. Register E contains the count ; value for the OTIR instruction and register D contains the ; number of OTIR instructions that need be performed. ; PGMWR: OTIR ; mass output DEC D ; more OTIR's to go? JR NZ,PGMWR ; yes if non-zero JR PGMDN ; done with write loop ; ; Z80 Programmed I/O read loop. Register E contains the count ; value for the INIR instruction and register D contains the ; number of INIR instructions that need be performed. ; PGMRD: INIR ; mass input DEC D ; more INIR's to go? JR NZ,PGMRD ; if non-zero ; PGMDN: ; ; Programmed I/O transfer is now complete. Reset the ; programmed I/O enable bit on the controller board. ; LD A,(LATCH) ; get current latch setting RES PIOEN,A ; reset PIOEN bit LD (LATCH),A ; update current latch OUT (CONTRL),A ; send to controller board ; EI ; ; Now the Programmed I/O timeout bit must be checked in ; case of dead-man timeouts in reading or writing. ; IN A,(CONTRL) BIT 6,A ; test PIOEN time out error JR Z,WTINT ; if not, wait for interrupt ; ; If the Programmed I/O timeout bit was TRUE, we must attempt ; to determine the cause of the error without the help of the ; NEC 765 returned status registers. ; CALL RESYNC ; Re-syncronize with the uPD765 LD B,RIDCMD LD A,(DVRTBL+FMT) ; get format type value BIT 6,A ; test density bit-6 JR Z,PGME1 ; if single-density SET 6,B ; set MFM bit-6 in FDC command PGME1: CALL READID ; read an ID field JR NZ,RWERR1 ; if bad read ID operation LD A,(RWSTBL+3) ; get cylinder LD HL,TRACK ; point current sector CP (HL) ; same? JR NZ,RWERR2 ; no, recal and re-seek JR RWERR3 ; yes, retry disk operation ENDIF ; ; Reading and writing result phase begins here if using DMA ; operation or there was not a deadman time in Programmed I/O mode. ; WTINT: CALL DPOLL ; wait for completion interrupt LD A,(RWSTBL) ; get ST-0 AND 0C0H ; mask error bits JR Z,RWERRE ; if successful operation ; ; If operating in Programmed I/O mode, a 765 end of track ; error is used to break the FDC out of a read or a write operation. ; This code determines if the pending error condition is an EOT error. ; IFF DMAOP CP 40H ; check ST-0 for improper termination JR NZ,RWERR1 ; it not, then no EOT error occured LD HL,RWSTBL+1 ; point to ST-1 BIT 7,M ; test for EOT LD A,0 ; prep for error exit routine JR NZ,RWERRE ; yes, normal non-DMA termination ENDIF ; ; Test for a drive not ready condition and branch ; to the error exit routine with the proper result if true. ; RWERR1: LD A,(RWSTBL) ; get ST-0 result BIT 3,A ; check drive not ready bit LD A,2 ; get result code JR NZ,RWERRE ; and quit if true ; ; Now check the wrong cylinder bit in ST-2. If not true, then branch ; to more error routines. If true, then recalibrate the drive and perform ; a re-seek to the selected track. RWERR2 provided for Programmed I/O mode. ; A recalibration and re-seek combination is allowed only once by the ; recal flag (RECFL). ; LD A,(RWSTBL+2) ; get ST-2 result BIT 4,A ; test wrong cylinder JR Z,RWERR3 ; no, skip recalibrate RWERR2: LD HL,RECFL ; point to recal flag DEC (HL) ; recal done? LD A,10H ; get seek error code JR NZ,RWERRE ; yes, skip it CALL RECAL ; recalibrate the drive JP RESEEK ; and re-seek selected track ; ; Check the retry counter for zero and perform preset number ; of retrys to read or write a sector. Variable updated at DRETRY ; entry point. ; RWERR3: LD A,(RTCNT) ; get retry counter DEC A ; one less retry JP NZ,DRETRY ; if not zero ; ; Attempt to determine the type of error encontered through the ; testing of the 765's status registers. Branch to error exit ; routine with a valid result code. ; LD HL,RWSTBL+1 ; point to ST-1 BIT 1,M ; test write protect bit LD A,3 ; get WP code JR NZ,RWERRE BIT 2,M ; test No Data LD A,12H ; get code JR NZ,RWERRE BIT 4,M ; test over-run LD A,16H ; get code JR NZ,RWERRE BIT 0,M ; test missing AM JR Z,RWERR4 ; no, skip INC HL ; point to ST-2 BIT 0,M ; test missing data AM LD A,14H ; get code JR NZ,RWERRE ; if true LD A,11H ; must be missing ID AM JR RWERRE RWERR4: BIT 5,M ; test CRC error LD A,1 ; get code for unknown JR Z,RWERRE ; if not CRC error INC HL ; point to ST-2 BIT 5,M ; test CRC error in data field LD A,15H ; get code JR NZ,RWERRE LD A,13H ; must be CRC error in ID field ; ; Error exit entry point. The result field in the drive descriptor ; block is set to the value in the ACC and then returns to caller. ; RWERRE: LD (DVRTBL+RESULT),A ; set result field RET ; done SUBTTL Driver Subroutines PAGE ; Drive select subroutine. The new drive number (0-3) should be in ; register B. The new drive is checked against the current drive selected ; on the board and if not the same, the track table is used to store the ; old track number and get the new drives track number, then the new drive ; is selected on the board. ; DSKSEL: IF LDRSYS ; if loader BIOS operation LD A,(DVRTBL+DSK) ; use logical drive number AND 3 ; mask it LD B,A ; and store it in B ELSE LD HL,(DVRTBL+DPH) ; get current header LD DE,24 ; offset for physical drive number ADD HL,DE LD B,(HL) ; store number in B ENDIF ; LDRSYS LD A,(DRIVE) ; get current drive AND 3 ; mask to drive number CP B ; same as new? JR Z,DSKCHK ; yes, skip select LD E,A ; old disk in E LD D,0 ; prep for double add LD HL,TRKTBL ; get base of track table ADD HL,DE ; point to disk rel entry LD A,(TRACK) ; get track from RW table LD (HL),A ; and place in track table LD E,B ; get new disk in E LD HL,TRKTBL ; get base of track table ADD HL,DE ; point to disk rel entry LD A,(HL) ; get entry from track table LD (TRACK),A ; and place in RW table LD A,B ; get back new drive DSKCHK: RRCA RRCA ; shift to bits 6&7 AND 0C0H ; mask off other bits LD E,A ; keep in E LD HL,LATCH ; point to current latch LD A,(HL) ; get it AND 03FH ; clear old drive select OR E ; add new drive LD (HL),A ; restore it OUT (CONTRL),A ; send to controller board LD A,B ; get restore ACC to new drive LD (DRIVE),A ; set drive number in RW table ; LD A,(INIFL) ; check for first select OR A RET NZ ; if init already performed ; IN A,(FDCMSR) ; read 765 main status reg AND 0F0H ; mask high nibble CP 80H ; check for presence RET NZ ; if not in the system IF DMAOP LD HL,IZDMA ; initialization table LD BC,IZDMAL SHL 8 + ZDMA ; length and port OTIR ; program it ENDIF CALL SPECIFY LD A,-1 LD (INIFL),A ; set first time init flag RET ; done ; Recalibrate the current board selected drive. The 765 recalibrate ; command is issued and the track field in the RW table set to 0. ; RECAL: LD BC,RECCMD SHL 8 + 2 ; get recal command and length CALL CMDRDY ; issue command CALL DPOLL ; wait for completion IF MINI AND TPI96 LD BC,RECCMD SHL 8 + 2 CALL CMDRDY CALL DPOLL ENDIF XOR A LD (TRACK),A ; reset track field in RW table RET ; done ; Issue sense drive status command and retreive results. ; SDS: LD BC,SDSCMD SHL 8 + 2 ; get sense drive status command CALL CMDRDY ; issue it CALL CMDRES ; read results LD A,(RWSTBL) ; get ST-3 RET ; with it ; Read sector ID field. The B register contains either a single- ; or a double-density read ID command. The command is issued and ; ST-0 error bits mask. ZERO flag is set if no error occured. ; READID: LD C,2 ; length in C CALL CMDRDY ; issue command CALL DPOLL ; wait for completion LD A,(RWSTBL) ; get status AND 0C0H ; mask error bits RET ; with ZERO set for success ; Send command to NEC 765 subroutine. ; initial command in reg B, additional bytes are sent from the ; beginning of the READ/WRITE table as requested by the 765. ; register C contains the number of bytes that should be transfered. ; CMDRDY: IF MINI ; if 5" system PUSH BC ; save command and length LD BC,SDSCMD SHL 8 + 2 ; get sense drive status command CALL CMDSND ; issue it CALL CMDRES ; read results LD HL,RWSTBL ; point to ST-0 ; LD A,(LATCH) ; turn the motor on SET 4,A ; set motor on bit OUT (CONTRL),A RES 4,A ; reset motor on bit OUT (CONTRL),A ; POP BC ; restore callers command and length BIT 5,M ; test for ready line from drive status JR NZ,CMDSND ; and issue command if ready ; ; Now time out for one second to allow the drives to start-up LD HL,0 WT1SEC: EX (SP),HL EX (SP),HL DEC HL LD A,H OR L JR NZ,WT1SEC ; ENDIF ; for MINI ; CMDSND: IN A,(FDCMSR) ; get main status register BIT 4,A ; mask FDC busy bit-4 JR NZ,CMDSND ; loop if busy LD HL,RWTBL ; point to RW table CMDOUT: IN A,(FDCMSR) ; get main status register BIT 7,A ; test RQM JR Z,CMDOUT ; loop if not ready BIT 6,A ; test DIO for direction RET NZ ; if 765 full LD A,B ; get byte for output OUT (DDATA),A ; send it LD B,(HL) ; get next byte for output in B INC HL ; bump RW table pointer DEC C ; count=count-1 JR NZ,CMDOUT ; loop if more to send RET ; done ; ; Receive NEC 765 result phase subroutine. ; The results of an operation are read out of the 765 as ; requested to be read by the DIO bit-6. The results are loaded ; into the RW status table. CMDRES: LD HL,RWSTBL ; set result table pointer CMDRS1: IN A,(FDCMSR) ; get main status register BIT 7,A ; test RQM JR Z,CMDRS1 ; loop if not ready BIT 6,A ; test DIO RET Z ; if done receiving IN A,(DDATA) ; get result byte LD (HL),A ; store data in table INC HL ; bump table pointer JR CMDRS1 ; and loop for more ; Disk polling subroutine. This is called when waiting on the 765 ; to perform an operation in which it will interrupt when completed. ; NOTE that for MP/M system driver, the flagwait routine is called ; from the XIOS. ; DPOLL: IF MPMSYS LD A,(LATCH) ; get FDC latch SET INTEN,A ; set bit to unmask interrupts LD (LATCH),A ; store latch image OUT (CONTRL),A ; send to FDC board ; LD A,FDCFL ; get FDC flag number JP FLAGWAIT ; wait for interrupt ELSE ; must be CP/M IN A,(CONTRL) ; get control status BIT INTRQ,A ; test interrupt line JR Z,DPOLL ; and loop until received CALL FLINT ; clear 765 INT line JR C,DPOLL ; if invalid interrupt RET ; from DPOLL ENDIF ; MPMSYS ; Now the 765 result phase must be performed for any interrupting ; type of command. If the 765 busy bit is set, the results from a ; read or a write type command must be read. If the 765 busy bit is ; not set, then a sense interrupt status command is sent and the ; results of a seek, recal, or drive ready change interrupt are read out. ; FLINT: IN A,(FDCMSR) ; get main status register BIT 4,A ; busy? (read or write in process) JR NZ,RWDN1 ; yes, read results out LD BC,SISCMD SHL 8 + 2 ; get command and length CALL CMDSND ; issue sense interrupt status command RWDN1: CALL CMDRES ; read the results LD A,(RWSTBL) ; get ST-0 AND 0C0H ; mask error bits CP 0C0H ; drive ready change? JR NZ,RWDN2 ; no, exit valid interrupt IN A,(FDCMSR) AND 0FH ; any drive seeking? SCF RET NZ ; yes, wait for completion RWDN2: ; ; If using the DMA operation mode, the Z80 DMA device is disabled ; and any pending DMA interrupt is reset. ; IF DMAOP LD A,083H OUT (ZDMA),A ; disable DMA device LD A,0A3H OUT (ZDMA),A ; reset INT ENDIF ; XOR A ; clear CY for exit valid RET ; from Polled DPOLL IF MPMSYS ; MP/M floppy disk interrupt service routine ; FDCISR: CALL ISRSTK ; save the stack CALL FLINT ; clear the 765 interrupt RET C ; if invalid interrupt ; LD A,(LATCH) RES INTEN,A LD (LATCH),A OUT (CONTRL),A ; mask interrupt from board ; LD A,FDCFL ; get FDC flag number JP FLAGSET ; set through XIOS routine ENDIF ; MPMSYS IFF DMAOP ; Clear the uPD765 status port. ; This routine is called after an error in a programmed I/O transfer ; with the uPD765. The Main status register is used to clear the device ; of any command or result transfer and re-syncronize with the device. ; RESYNC: XOR A DEC A JR NZ,$-1 ; delay for some time ; IN A,(FDCMSR) ; get main status register BIT 7,A ; test DRQ bit JR Z,RESYNC ; wait for this to go true ; BIT 4,A ; test controller busy bit JP Z,SPECIFY ; and quit if busy bit reset BIT 6,A ; now test DIO for direction JR NZ,SYNC1 ; read data port if bit is set XOR A OUT (DDATA),A ; write null data if bit is reset JR RESYNC ; and retest main status SYNC1: IN A,(DDATA) ; read some data JR RESYNC ; and retest main status ENDIF ; Issue the specify command to the 765 with the pre-defined drive ; parameter equates at the beginning of this source. This sets the ; internal 765 timers. ; SPECIFY: LD HL,(RWTBL) PUSH HL LD HL,RWTBL ; use RWTBL for transfer LD (HL),SRTHUT ; set SRT and HUT INC HL LD (HL),HLTND ; set HLT and ND LD BC,SCYCMD SHL 8 + 3 ; get command and length CALL CMDSND ; issue it POP HL LD (RWTBL),HL ; reset the RW table RET SUBTTL Variables, Tables, and Buffers PAGE ; 765 read/write table RWTBL: DRIVE: DB 0 ; drive number TRACK: DB 0 ; track number HEAD: DB 0 ; head number SECTOR: DB 0 ; sector number N: DB 0 ; bytes/sector code EOT: DB 0 ; end of track GPL: DB 0 ; gap length DTL: DB 0 ; data length RWSTBL: DB 0,0,0,0,0,0,0 ; read/write status table IF DMAOP ; Z80 DMA table: Sent to device for initialization or re-initialization IZDMA: DB 083H ; disable DMA DB 0C3H,0C3H,0C3H DB 0C3H,0C3H,0C3H ; reset device. DB 0A3H ; reset INT DB 014H ; port A=memory, port A increments. DB 028H ; port B=I/O, port B fixed. DB 08AH ; stop end of block, ready active high DB 0D5H ; burst mode, ICB and port B LSB follows DB DSKB+6 ; port B LSB DB 002H ; INT at end of block DB 001H ; Port B equals temp source DB 0CFH ; load Port B fixed address IZDMAL EQU $-IZDMA ; length of transfer ; Z80 DMA table: Sent to device for reading and writing. RWDMA: DB 083H ; disable DMA WR0: DB 079H ; Port A address and block length follows ADDR: DW 0 ; patched port A address TC: DW 0 ; patched terminal count (length) DB 0CFH ; load registers DB 0ABH ; enable INT DB 087H ; enable DMA RWDMAL EQU $-RWDMA ; length of transfer ENDIF ; read/write value tables RWVALS: IF DMAOP DB 07H,080H,07FH,0 ; GPL,DTL,Terminal Count DB 0EH,0FFH,0FFH,0 DB 1BH,0FFH,0FFH,1 DB 35H,0FFH,0FFH,3 ELSE DB 07H,080H,080H,1 ; GPL,DTL,Transfer Code DB 0EH,0FFH,000H,1 DB 1BH,0FFH,000H,2 DB 35H,0FFH,000H,4 ENDIF TRKTBL: DB 0,0,0,0 ; track table (support four drives) RTCNT: DB 0 ; retry counter (set to number of retrys) RECFL: DB 0 ; recal flag (set to number of recals) RWFL: DB 0 ; RW flag (0=reading,1=writing) INIFL: DB 0 ; first time init flag FDCOP: DB 0 ; FDC read or write command SAVHL: DW 0 ; temp HL storage IF DMAOP LATCH: DB 00BH ; board latch for DMA buffering ELSE LATCH: DB 009H ; programmed I/O default setting ENDIF BUFBASE EQU $ ; base of ALC and CSV buffers ; Driver initialization. ; This entry point is called once at system cold boot time and may ; be used to perform any neccessary device initialization. ; ; NOTE: Located in the alocation and check vector buffers to save some space. ; FLINIT: IF MPMSYS LD HL,FDCISR ; get floppy ISR routine LD (FDCVEC),HL ; stor ISR address for mode 2 INT's IF CPD280 LD A,0E4H ; Select IREQ-4 response memory OUT (UICC),A ; for 1 byte mode 2 vector LD A,FDCVEC AND 0FFH OUT (UICD),A ; send low order vector LD A,02CH OUT (UICC),A ; clear IREQ-4 IMR bit ENDIF IF CPC281 LD A,1FH ; select 10H for IVEC High nibble OUT (IVCNTR),A ; send to control port ENDIF ENDIF ; MPMSYS IF DMAOP ; if floppy DMA option LD HL,OPFLGS ; point to option flags SET 0,(HL) ; set for DMA present ENDIF ; Print a driver sign-on message using the print message utility ; subroutine contained in FBIOS. ; IFF MPMSYS LD DE,DVRMSG CALL PNTMSG ; print driver sign-on ENDIF ; RET ; from driver initialization IFF MPMSYS DVRMSG: IF MINI IF DMAOP DB "FDC-2800/5 " ELSE DB "FDC-2801/5 " ENDIF ELSE IF DMAOP DB "FDC-2800/8 " ELSE DB "FDC-2801/8 " ENDIF ENDIF DB DX+"0" ; ascii supported drives DB " drives" DB 0DH,0AH,"$" ENDIF ; Alocate the remaining area for alocation and check vector buffers IF ($-BUFBASE) LT BUFSIZ DS BUFSIZ-($-BUFBASE) ENDIF ; Determine how to allocate the sector buffer IF DMAOP SECBUF EQU 0FC00H ; use DMA buffer for sector buffer ELSE IF LDRSYS AND MPMLDR SECBUF EQU 07C00H ; move PIO buffer outside loader area ELSE SECBUF: DS 1024 ; allocate sector buffer here ENDIF ENDIF END