|
DataMuseum.dkPresents historical artifacts from the history of: RegneCentralen RC850 |
This is an automatic "excavation" of a thematic subset of
See our Wiki for more about RegneCentralen RC850 Excavated with: AutoArchaeologist - Free & Open Source Software. |
top - metrics - download
Length: 28672 (0x7000) Types: TextFile Names: »FDSKDR.ASM«
└─⟦9f46c4107⟧ Bits:30005988 Sources for TurboDOS ver. 1.30 device drivers └─⟦this⟧ »FDSKDR.ASM«
.PAGE 132,72 .TITLE "TURBODOS OPERATING SYSTEM - RC 850 FLOPPY DISK DRIVER" .SBTTL "COPYRIGHT (C) 1982, ASE GMBH 6472 ALTENSTADT, INDUSTRIESTR. 17" ; ; VERSION: 4.2.83 ; ; ; .IDENT FDSKDR ;MODULE ID ; .INSERT DREQUATE ;DRIVER SYMBOLIC EQUATES ; TRUE = 0 ;DEFINE LOGICAL EQUATES FALSE = # TRUE ; MINI = FALSE ; Mini Disk operation TPI96 = FALSE ; 96 TPI Mini Disk operation ; IVECF = 6H ; interrupt vector number for the 765 FDC ; ; ; 765 drive parameter equates. ; RTRYS = 10 ; Number of Retrys ; ND = 0 ; 0 FOR DMA MODE (NOTE: 1 NOT SUPPORTED) ; .IFE MINI , Æ ; 5" drive parameters DSRT = 8 ; drive step rate in ms. HUT = 480 ; head unload time in ms. HLT = 40 ; head load time in ms. HUTVAL = HUT/32 HLTND = ((HLT/4)<1)+ND ;Å .IFN MINI , Æ ; 8" drive parameters DSRT = 3 ; drive step rate in ms. HUT = 240 ; Head Unload Time in ms. HLT = 35 ; Head Load Time in ms. HUTVAL = HUT/16 HLTND = ((HLT/2)<1)+ND ;Å ; ; SYSTEM MASTER port assignments. ; FDCMSR = 004H ; 765 FDC Main status register DDATA = 005H ; 765 FDC Main data register ; ENFITR = 0D7H ; enable floppy interrupt mask ; MOTPOR = 014H ; Motor Control Port ; ZDMA = 0F0H ; DMA device ADR1 = 0F2H ; base addr. register (channel 1) WCT1 = 0F3H ; base word count DMACMD = 0F8H ; command register MASKB = 0FAH ; mask register MODE = 0FBH ; mode register CLIFF = 0FCH ; flip/flop register ; ; DMA equates ; RSTMSB = 01H ; reset mask bit channel 1 SETMSB = 05H ; set mask bit channel 1 MDW1 = 045H ; write channel 1 (to memory from fdc) MDR1 = 049H ; read channel 1 (from memory to fdc) ; ; NEC 765 intruction set used. ; SCYCMD = 03H ; specify drive parameters SDSCMD = 04H ; sense drive status WRCMD = 05H ; write sector RDCMD = 06H ; read sector RECCMD = 07H ; recalibrate SISCMD = 08H ; sense interrupt status RIDCMD = 0AH ; read sector ID FMTCMD = 0DH ; format a track command SKCMD = 0FH ; seek command ; ST3TS = 3 ; ST-3 two-sided ST3TO = 4 ; ST-3 track 0 ST3RDY = 5 ; ST-3 drive ready ST3WP = 6 ; ST-3 write protected ; ; Motor Control Port (MOTPOR) bit assigment for output. ; MOTOR = 4 ; Motor control (0=run) FIVEIN = 3 ; Floppy Disk Size (1=5") ; ; Pre-defined type code bits ; TSD = 2 ;TWO-SIDED DISK BIT (TYPE CODE) DDD = 3 ;DOUBLE DENSITY DISK BIT (TYPE CODE) MFD = 4 ;MINI-FLOPPY DISK BIT (TYPE CODE) ; ; Driver Entry Point ; .LOC .PROG.# ; locate in code segment ; DSKDR%:: LXI H,DMXSPH ; get mutual exclusion semaphore CALL WAIT# ; dispatch if necessary CALL ..DD ; call the disk driver PUSH PSW ; save results LXI H,DMXSPH ; get mutual exclusion semaphore CALL SIGNAL# ; signal process as ready POP PSW ; restore results RET ; done ; ..DD: MOV A,PDRFCN(X) ; get PD request function number ORA A ; function=0? JZ FLREAD ; if so, branch DCR A ; function=1? JZ FLWRITE ; if so, branch DCR A ; function=2? JRZ FLFMT ; if so, branch DCR A ; function=3? JZ RETRDY ; if so, branch DCR A ; function=4? JZ FMTTRK ; if so, branch ORI 0FFH ; force error here RET ; else, done ; ; Driver initialization. ; This entry point is called once at system cold boot time and may ; be used to perform any neccessary device initialization. ; .LOC .INIT.# ; locate in initialization segment ; DSKIN%:: LXI D,FDCISR ; get floppy ISR routine LXI H,FDSVEC# ; point to interrupt vector page MOV M,E ; set ISR address into vector INX H MOV M,D ; ; RC 850 CTC initialization (floppy interrupt) ; MVI A,ENFITR ; enable floppy interrupt OUT 0FH ; MVI A,1 ; OUT 0FH ; ; ..FL: IN FDCMSR ; check if 765 ready to talk BIT 7,A ; test RQM JRZ ..FL ; loop if not ready BIT 6,A ; test DIO to see if direction is right JRZ ..GO ; it is, go initialize the FDC IN DDATA ; flush the status out JMPR ..FL ; and loop until we get good status ; ..GO: LXI H,RWTBL ; use RWTBL for transfer LDA STEPR% ; get floppy disk step rate NEG ; adjust for device ADD A ADD A ADD A ADD A ; shift into bits 4-7 ORI HUTVAL ; add in head unload value MOV M,A ; place in table INX H MVI M,HLTND ; set HLT and ND LXI B,(SCYCMD<8)+3 ; get command and length CALL CMDSND ; issue it LXI H,0 SHLD RWTBL ; restore RW table ..X: RET ; done, return to caller ; ; .LOC .PROG.# ; locate in program segment ; ; DETERMINE THE FORMAT OF A DISK IN A DRIVE ; FLFMT: CALL RETRDY ; select and return ready condition ORA A RZ ; if not ready ; ; Issue a read ID field in single-density and branch to ; good ID read with the FMT type if successful. ; MVI A,1 STA RECFL ; reset the recalibrate flag DFMT1: CALL RECAL ; recalibrate disk MVI A,2 ; seek out to track two CALL SEEK2 MVI B,RIDCMD ; get Read ID command CALL READID ; issue it LDA RWSTBL+6 ; get returned N for FMT sector size JRZ 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. ; MVI B,RIDCMD+40H ; try double-density next CALL READID ; issue it LDA RWSTBL+6 ; get returned N for FMT sector size SET DDD,A ; set double-density type JRZ 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. ; LXI H,RECFL DCR M ; check recal flag JRNZ FMTERR ; if recal already performed ; CALL RECAL ; do one recalibrate JMPR 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: .IFE MINI , Æ SET MFD,A ; set mini type bit if mini drive ;Å PUSH PSW ; save FMT type CALL SDS ; sense drive status POP PSW ; restore FMT type LXI H,RWSTBL ; point to ST-3 BIT ST3TS,M ; test two sided bit JRZ FDPB ; no, FMT correct SET TSD,A ; yes, set two-sided type bit ; .IFE MINI , Æ PUSH PSW ; save FMT value BIT DDD,A ; test double density bit MVI B,RIDCMD ; get read command in reg B JRZ M1D SET 6,B ; set MFM bit in command for DDD M1D: LXI H,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 LDA RWSTBL+4 ; get head byte from read ID field CPI 1 ; is it truly head 1? JRNZ M1S ; no, disk is single-sided POP PSW JMPR FDPB ; with two-sided FMT value M1S: POP PSW RES TSD,A ; clear two-sided bit ;Å ; ; Find proper DPB in list ; FDPB: MOV C,A ; save disk type code LXI D,DSTBLS ; get disk spec tables ..LP: MOV A,C ; get disk type code in ACC LXI H,DTCO ; offset to type code in table DAD D ; calc type code address CMP M ; spec found? JRZ DSTF ; if so, continue XCHG MOV E,M INX H MOV D,M ; load spec table link MOV A,D ORA E ; end of list? JRNZ ..LP ; if not, continue JMPR FMTERR ; format type not found ; DSTF: INX D ; bump to proper DST INX D MOV PDRDST(X),E ; set disk spec table address MOV PDRDST+1(X),D ORI 0FFH ; set return code=FF RET ; done ; ; Branch here if device read errors or format cannot be found ; FMTERR: XRA A RET ; ; Format a track entry point. ; FMTTRK: MVI A,1 ; RWFL flag value for writing STA RWFL ; set the RWFL flag ; MOV L,PDRDMA(X) MOV H,PDRDMA+1(X) ; get PD requested DMA address SHLD CURADR ; store as sector buffer address MOV C,PDRTC(X) MOV B,PDRTC+1(X) ; get PD requested transfer count DCX B ; TC-1 for DMA terminal count SBCD TC ; store in DMA table ; CALL RETRDY ; select drive and return ready ORA A ; set flags CMA ; invert for error return RZ ; if drive not present or ready ; MOV A,PDRTRK(X) ; get requested track number ORA A ; track number = 0? CZ RECAL ; if so, recalibrate drive CALL SEEK ; seek to requested track ; LXI H,FDRV ; point to drive number in format table BIT 7,PDRSEC+1(X) ; head number 1 flag set? JRZ ..S0 ; if not, continue SET 2,M ; select head 1 in drive field ..S0: INX H ; point to bytes/sector field MOV A,PDRSEC(X) ; get req sector value ANI 3 ; extract format sector size MOV M,A ; store in format table INX H ; point to sectors/track field MOV A,PDRSC(X) ; get req sector count MOV M,A ; store in format table INX H ; point to gap field MOV A,PDRSEC+1(X) ; get req sector value ANI 7FH ; extract format gap length MOV M,A ; store in format table ; MVI A,RTRYS ; get number of retrys FRETRY: STA RTCNT ; set retry counter ; PUSH PSW ; save the PSW PUSH B ; PUSH D ; PUSH H ; LDA (RWFL) ; get the RWFL flag CPI 00H ; if read mode? JZ RCALL1 ; yes, go read FDC CALL FLDMAR ; no, call write JMP CONT1 ; continue after write RCALL1: CALL FLDMAW ; read FDC CONT1: POP PSW ; restore the PSW POP B ; POP D ; POP H ; ; LXI B,(FMTCMD<8)+6 ; get command and length BIT 7,PDRSEC(X) ; double density flag set? JRZ ..SD ; if not, continue SET 6,B ; set 765 double density bit ..SD: CALL CMDRDY ; output command to 765 CALL FLWAIT ; wait for completion LDA RWSTBL ; get returned ST-0 ANI 0C0H ; mask error bits RZ ; done if no errors ; LDA RTCNT ; get retry counter DCR A ; another retry? JRNZ FRETRY ; if so, loop ORI 0FFH ; else get error return RET ; done ; ; Read entry point. ; FLREAD: MVI B,RDCMD ; B= FDC read command XRA A ; RWFL flag value for reading JMPR DRDWR ; common routines ; ; Write entry point. ; FLWRITE: MVI B,WRCMD ; B= FDC write command MVI A,1 ; RWFL flag value for writing ; ; Common routines to both reading and writing. ; DRDWR: STA RWFL ; set the RWFL flag ; ; Set up the read or write operation for single- or double- ; density as specified by DDD bit of the format type code in ; the drive specification table. ; CALL GETTCA ; get the type code address BIT DDD,M ; test double-density type bit JRZ RDWRSD ; if reading or writing single-density SET 6,B ; set MFM bit-6 in FDC command RDWRSD: MOV A,B STA FDCOP ; store FDC command ; MOV A,PDRSEC(X) STA CURSEC ; set current sector MOV L,PDRDMA(X) MOV H,PDRDMA+1(X) SHLD CURADR ; set current address MOV A,PDRSC(X) STA CURSC ; set current sector count ; ; Lookup the values for the N,GPL and DTL fields from the ; RW values table. Table values are picked based on sector size. ; MOV A,SECSIZ(X) ; get the sector size value ANI 3 ; mask the sector size bits 0&1 STA N ; set the N field ADD A ADD A ; N value times 4 MOV C,A MVI B,0 ; prep for double add LXI H,RWVALS ; point to beginning of table DAD B ; point to entry MOV A,M ; get GPL entry STA GPL ; and patch it INX H MOV A,M ; get DTL entry STA DTL ; and patch it INX H MOV E,M INX H MOV D,M ; get TC value SDED TC ; set DMA terminal count ; XRA A STA IOERR ; clear I/O error status byte INR A STA RECFL ; set the recal flag ; ; Select in drive through ready test routine (RETRDY) ; RESEEK: CALL RETRDY ; use subroutine ORA A CMA ; set ACC=FF RZ ; if drive not ready CALL SEEK ; seek to proper track ; RWLOOP: ; ; Select either head-0 or head-1 from the format type value. ; LDA CURSEC ; get current sector MOV C,A ; store in C CALL GETXLT ; get translation table address JRZ NOTRAN ; if no translation required MVI B,0 DAD B MOV C,M ; get translated sector NOTRAN: INR C ; set sector base to 1 MOV B,SECTRK(X) ; get sectors per track value CALL GETTCA ; get type code address BIT TSD,M ; test head-1 select bit-7 JRZ SNGSID ; if head-0 selected MOV A,M ; is it DS/DD/256 format? CPI 0DH JRNZ ..NOT ; no, use normal cylinder organization ; MOV A,PDRTRK(X) ; yes, back side follows front side CPI 77 JRC SNGSID ; jump if accessing a front side track LXI H,DRIVE ; point to byte to set the head bit in JMPR SETHD1 ; go select side 1 ; ..NOT: SRLR B ; find number of sectors per side SNGSID: LXI H,DRIVE RES 2,M ; reset head select bit MOV A,B CMP C MVI A,0 JRNC FSID ; if side 0 selected MOV A,C SUB B ; subtract off one side MOV C,A SETHD1: SET 2,M ; set drive number for head 1 MVI A,1 FSID: STA HEAD ; set head number MOV A,C ; get sector number STA SECTOR ; set sector STA EOT ; use as EOT value also ; ; Start of reading and writing. NOTE: retry entry point also. ; MVI A,RTRYS ; get initial retry count DRETRY: STA RTCNT ; set retry counter LDA (RWFL) ; get the RWFL flag CPI 00H ; if read mode? JZ RCALL2 ; yes, go read FDC CALL FLDMAR ; no, call write JMP CONT2 ; continue after write RCALL2: CALL FLDMAW ; read FDC CONT2: ; ; Now send the 765 RW table to that device to enable ; the current read or write operation. ; LDA FDCOP MOV B,A ; FDC command in B MVI C,9 ; length of command in C CALL CMDRDY ; issue command ; ; Reading and writing result phase begins here if using DMA ; operation or there was not a deadman time in Programmed I/O mode. ; CALL FLWAIT ; wait for completion interrupt LDA RWSTBL ; get ST-0 ANI 0C0H ; mask error bits JRZ NXTRW ; if successful operation ; ; Test for a drive not ready condition and branch ; to the error exit routine with the proper result if true. ; ; LDA RWSTBL ; get ST-0 result ; BIT 3,A ; check drive not ready bit ; JRNZ NXTRW ; 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. Also provided for Programmed I/O mode. ; A recalibration and re-seek combination is allowed only once by the ; recal flag (RECFL). ; LDA RWSTBL+2 ; get ST-2 result BIT 4,A ; test wrong cylinder JRZ ..RWE ; no, skip recalibrate LXI H,RECFL ; point to recal flag DCR M ; recal done? JRNZ ..RWE ; yes, skip it CALL RECAL ; recalibrate the drive JMP 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. ; ..RWE: LDA RTCNT ; get retry counter DCR A ; one less retry JNZ DRETRY ; if not zero ; NXTRW: LXI H,IOERR LDA RWSTBL ORA M MOV M,A ; update I/O error flag ; LHLD CURADR ; get current DMA address LBCD TC INX B DAD B ; calc new DMA address SHLD CURADR ; set new DMA address ; LXI H,CURSEC ; point to current sector number INR M ; bump current sector number ; LXI H,CURSC ; point to current sector count DCR M ; check sector count JNZ RWLOOP ; if more to read/write ; LDA IOERR ; get error status ANI 0C0H ; mask error bits RZ ; done if no errors ORI 0FFH ; set results to FF RET ; done ; ; Check drive ready condition ; RETRDY: MOV A,PDRDRV(X) ; get disk number CPI 4 ; test for valid drive number MVI A,0 RNC ; if invalid drive, return not ready ; IN FDCMSR ; read 765 status port INR A ; is it present? RZ ; if not, return not ready status ; CALL DSKSEL ; select in drive CALL SDS ; test drive status BIT ST3RDY,A ; test ready status MVI A,0 RZ ; if drive not ready CMA ; set return code=FF RET ; done ; ; Driver Subroutines ; ; Drive select subroutine. ; 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: MOV B,PDRDRV(X) ; get drive number LDA DRIVE ; get current drive ANI 3 ; mask to drive number CMP B ; same as new? JRZ ..NOS ; yes, skip select STA DRIVE ; no, switch to head 0 first MOV C,A ; save current drive number PUSH B ; both drive numbers to stack ..LP: CALL SDS ; use sense drive status to effect switch BIT 2,A ; are we there yet? JRNZ ..LP ; no, wait for it POP B ; restore drive numbers MOV E,C ; get back old drive number and put in E MVI D,0 ; prep for double add LXI H,TRKTBL ; get base of track table DAD D ; point to disk rel entry LDA TRACK ; get track from RW table MOV M,A ; and place in track table MOV E,B ; get new disk in E LXI H,TRKTBL ; get base of track table DAD D ; point to disk rel entry MOV A,M ; get entry from track table STA TRACK ; and place in RW table MOV A,B ; get back new drive ..NOS: STA DRIVE ; set drive number in RW table STA FDRV ; and drive number in FORMAT table 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: MVI B,4 ; set retry counter ..AGN: PUSH B ; save bc register LXI B,(RECCMD<8)+2 ; get recal command and length CALL CMDRDY ; issue command CALL FLWAIT ; wait for completion ; CALL SDS ; sense drive status POP B ; restore BC, with count in B BIT ST3TO,A ; are we at track zero? JRNZ ..OK ; yes, jump - else has retry count expired? DJNZ ..AGN ; no, do it again ; ..OK: XRA A STA TRACK ; reset track field in RW table RET ; done ; ; Seek to PD requested track number. ; SEEK: CALL GETTCA ; point to disk type code MOV A,M ; is it DS/DD/256 format? CPI 0DH MOV A,PDRTRK(X) ; (get selected track number) JRNZ SEEK2 ; no, seek to specified cylinder CPI 77 ; yes, is it on the front side of the disk? JRC SEEK2 ; yes, seek to specified cylinder SUI 77 ; no, subtract off the front side and seek SEEK2: LXI H,TRACK ; point to current track CMP M ; same? RZ MOV M,A ; put in RW table LXI B,(SKCMD<8)+3 ; get seek command and length CALL CMDRDY ; send command CALL FLWAIT ; wait for completion RET ; ; Issue sense drive status command and retreive results. ; SDS: LXI B,(SDSCMD<8)+2 ; get sense drive status command CALL CMDRDY ; issue it MVI B,1 ; expect one byte of status CALL CMDRES ; read results LDA 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: MVI C,2 ; length in C CALL CMDRDY ; issue command CALL FLWAIT ; wait for completion LDA RWSTBL ; get status ANI 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: .IFE MINI , Æ ; if 5" system PUSH B ; save command and length LXI B,(SDSCMD<8)+2 ; get sense drive status command CALL CMDSND ; issue it MVI B,1 ; expect one byte of status back CALL CMDRES ; read results LXI H,RWSTBL ; point to ST-0 ; MVI A,060H+(1<XXX) ; turn the motor on OUT MOTPOR ; POP B ; restore callers command and length BIT 5,M ; test for ready line from drive status JRNZ CMDSND ; and issue command if ready ; ; Now time out for one second to allow the drives to start-up ; PUSH B ; SAVE COMMAND AND COUNT LXI H,60 ; DELAY 60 TICKS CALL DELAY# POP B ; RESTORE COMMAND AND COUNT ;Å CMDSND: MVI A,0FFh ; set command active flag STA ACTFLG ; CMDOUT: LXI H,RWTBL ; point to RW table MOV A,B ; get 765 command ANI 0FH ; mask command bits CPI FMTCMD ; format command? JRNZ ..CL ; if not, continue LXI H,FMTBL ; point to FORMAT table ..CL: IN FDCMSR ; get main status register BIT 7,A ; test RQM JRZ ..CL ; loop if not ready BIT 6,A ; test DIO for direction MVI A,"C" ; set error code for command phase JRNZ FDCERR ; if 765 full MOV A,B ; get byte for output OUT DDATA ; send it MOV B,M ; get next byte for output in B INX H ; bump RW table pointer DCR C ; count=count-1 JRNZ ..CL ; loop if more to send RET ; done ; ; This routine is entered if the FDC is going in the wrong direction ; when a particular operation is requested. ; FDCERR: CALL RECAL ; recalibrate drive MVI A,0FFH ; set error code to ST-0 STA RWSTBL ; RET ; ; ; 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: LXI H,RWSTBL ; set result table pointer CMDRS1: IN FDCMSR ; get main status register BIT 7,A ; test RQM JRZ CMDRS1 ; loop if not ready BIT 6,A ; test DIO MVI A,"R" ; set error code for result phase JRZ FDCERR ; if done receiving IN DDATA ; get result byte MOV M,A ; store data in table INX H ; bump table pointer DCR B ; decrement byte counter RZ ; return if done JMPR CMDRS1 ; and loop for more ; ; Disk wait subroutine. This is called when waiting on the 765 ; to perform an operation in which it will interrupt when completed. ; FLWAIT: ; LXI H,DWTSPH ; get disk wait semaphore JMP WAIT# ; wait for command completion ; ; 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 FDCMSR ; get main status register BIT 7,A ; test RQM JRZ FLINT ; loop if not ready BIT 6,A ; test DIO JRZ RWDN1 ; jump if not already outputting status MVI B,7 ; normally expect 7 bytes of status CALL CMDRES ; go input the result JMPR RWDN2 ; go complete command processing RWDN1: LXI B,(SISCMD<8)+1 ; get command and length CALL CMDOUT ; issue sense interrupt status command MVI B,2 ; expect two bytes of status back CALL CMDRES ; read the results LDA RWSTBL ; get ST-0 ANI 0C0H ; mask error bits CPI 0C0H ; drive ready change? JRNZ RWDN2 ; no, exit valid interrupt IN FDCMSR ANI 0FH ; any drive seeking? STC RNZ ; yes, wait for completion RWDN2: ; ; If using the DMA operation mode, the DMA device is disabled ; MVI A,RSTMSB ; OUT MASKB ; reset mask it channel 1 ; XRA A ; clear CY for exit valid STA ACTFLG ; clear command active flag, also RET ; done ; ; Floppy disk interrupt service routine ; FCISR:: FDCISR: DI ; SSPD INTSP# ; save interrupt stack pointer LXI SP,INTSTK# ; set up aux stack PUSH PSW PUSH B PUSH D PUSH H ; save regs ; LDA ACTFLG ; is any operation in progress? ORA A JRZ ..NOT ; no, skip semaphore signalling ; CALL FLINT ; perform the result phase JC ..ISR ; exit if invalid interrupt ; LXI H,DWTSPH ; yes, get disk wait semaphore CALL SIGNAL# ; signal command completion JMP ..ISR ; go to standard interrupt exit ; ..NOT: CALL FLINT ; perform the result phase for bad interrupt JMP ..ISR ; go to standard interrupt exit ; ..ISR: POP H ; restor all register POP D ; POP B ; POP PSW ; LSPD INTSP# ; JMP ISRXIT# ; exit through dispacher ; ; ; routine to start DMA controller (intel 8237A or am9517) channel 1 ; with transfer between floppy disk controller and memory. ; write into memory: called by FLDMAW ; read from memory : called by FLDMAR ; ; FLDMAS: OUT MODE ; select mode for channel 1 OUT CLIFF ; clear internal flip flop LDA (CURADR + 0) ; OUT ADR1 ; low start address LDA (CURADR + 1) ; OUT ADR1 ; high start address LDA (TC + 0) ; OUT WCT1 ; out low word count LDA (TC + 1) ; OUT WCT1 ; out high word count MVI A,RSTMSB ; OUT MASKB ; clear channel 1 mask bit EI ; RET ; return ; ; routine to set DMA - mode: write (to memory from FDC) ; FLDMAW: MVI A,SETMSB ; set channel 1 mask DI ; OUT MASKB ; MVI A,MDW1 ; DMA write mode JMP FLDMAS ; ; ; routine to set DMA - mode: read (from memory to FDC) ; FLDMAR: MVI A,SETMSB ; set channel 1 mask DI ; OUT MASKB ; MVI A,MDR1 ; DMA read mode JMP FLDMAS ; ; ; Get translate table address ; GETXLT: CALL GETDST ; get DST address first LXI D,XLTBL ; offset for translation table DAD D ; calc addr MOV E,M INX H MOV D,M ; load translation table address XCHG ; into HL register pair MOV A,H ORA L ; translation required? RET ; done ; ; Return current drive type code address in HL ; GETTCA: CALL GETDST ; get DST address first LXI D,TYPCOD ; offset to disk type code DAD D ; calc disk type code address RET ; done ; ; Get PD request DST address ; GETDST: MOV L,PDRDST(X) MOV H,PDRDST+1(X) ; load into HL register pair RET ; done ; ; Variables, Tables, and Buffers ; DSTBLS: ; ; 1024 BYTE SECTOR, DOUBLE-DENSITY, TWO-SIDED (MAXI) ; .WORD .+DSTL ;DISK SPEC TABLE LINK POINTER .BYTE 4 ;BLOCK SIZE .WORD (77*(16*(1<3)))/(1<4) ;NUMBER OF BLOCKS .BYTE 4 ;NUMBER OF DIRECTORY BLOCKS .BYTE 3 ;PHYSICAL SECTOR SIZE (2^N*128) .WORD 16 ;PHYSICAL SECTORS PER TRACK .WORD 77 ;PHYSICAL TRACKS PER DISK .WORD 0 ;NUMBER OF RESERVED TRACKS .WORD 0 ;TRANSLATION TABLE ADDRESS .BYTE 1<DDD!1<TSD!3 ;DISK TYPE CODE .BYTE 35H ;GAP LENGTH ; ; 512 BYTE SECTOR, DOUBLE-DENSITY, TWO-SIDED ; .WORD .+DSTL ;DISK SPEC TABLE LINK POINTER .BYTE 4 ;BLOCK SIZE .WORD (77*(30*(1<2)))/(1<4) ;NUMBER OF BLOCKS .BYTE 2 ;NUMBER OF DIRECTORY BLOCKS .BYTE 2 ;PHYSICAL SECTOR SIZE (2^N*128) .WORD 30 ;PHYSICAL SECTORS PER TRACK .WORD 77 ;PHYSICAL TRACKS PER DISK .WORD 2 ;RESERVED TRACKS .WORD RCTRAN ;TRANSLATION TABLE ADDRESS for RC diskette .BYTE 1<DDD!1<TSD!2 ;DISK TYPE CODE .BYTE 1BH ;GAP LENGTH ; ; 128 BYTE SECTOR, SINGLE-DENSITY, ONE-SIDED ; DSTA: .WORD 0 ;DISK SPEC TABLE LINK POINTER DSTB: .BYTE 3 ;BLOCK SIZE .WORD (75*(26*(1<0)))/(1<3) ;NUMBER OF BLOCKS .BYTE 2 ;NUMBER OF DIRECTORY BLOCKS .BYTE 0 ;PHYSICAL SECTOR SIZE (2^N*128) .WORD 26 ;PHYSICAL SECTORS PER TRACK .WORD 77 ;PHYSICAL TRACKS PER DISK .WORD 2 ;RESERVED TRACKS ; XLTBL = .-DSTB ;TRANSLATION TABLE ADDRESS OFFSET ; .WORD TRTBL ;TRANSLATION TABLE ADDRESS ; DTCO = .-DSTA ;DISK TYPE CODE OFFSET TYPCOD = .-DSTB ;DISK TYPE CODE OFFSET ; .BYTE 0 ;DISK TYPE CODE ; GAPLEN = .-DSTB ;GAP LENGTH OFFSET ; .BYTE 7 ;GAP LENGTH ; DSTL = .-DSTA ;DISK SPEC TABLE LENGTH ; ; SINGLE-DENSITY/SINGLE-SIDED SECTOR TRANSLATION TABLE ; TRTBL: .BYTE 0,6,12,18,24,4,10,16,22 .BYTE 2,8,14,20,1,7,13,19,25 .BYTE 5,11,17,23,3,9,15,21 ; RCTRAN: .BYTE 0,4,8,12,1,5,9,13,2,6,10,14,3,7,11 .BYTE 15,19,23,27,16,20,24,28,17,21,25,29,18,22,26 ; .LOC .DATA.# ; locate in data segment ; DMXSPH: ; mutual exclusion semaphore .WORD 1 ; semaphore count ..DMXH: .WORD ..DMXH ; semaphore P/D head .WORD ..DMXH ; DWTSPH: ; disk wait semaphore .WORD 0 ; semaphore count ..DWTH: .WORD ..DWTH ; semaphore P/D head .WORD ..DWTH ; ; 765 read/write table ; RWTBL: DRIVE: .BYTE 0 ; drive number TRACK: .BYTE 0 ; track number HEAD: .BYTE 0 ; head number SECTOR: .BYTE 0 ; sector number N: .BYTE 0 ; bytes/sector code EOT: .BYTE 0 ; end of track GPL: .BYTE 0 ; gap length DTL: .BYTE 0 ; data length ; ; 765 format table ; FMTBL: FDRV: .BYTE 0 ; format drive number FN: .BYTE 0 ; format bytes/sector FSC: .BYTE 0 ; format sectors/track FGPL: .BYTE 0 ; format gap length (3) .BYTE 0E5H ; format filler byte ; RWSTBL: ; .BYTE 0,0,0,0,0,0,0 ; read/write status table ; ; DMA table ; CURADR: .WORD 0 ; current DMA buffer address TC: .WORD 0 ; patched terminal count (length) ; ; read/write value tables ; RWVALS: .BYTE 07H,080H,07FH,0 ; GPL,DTL,Terminal Count .BYTE 0EH,0FFH,0FFH,0 .BYTE 1BH,0FFH,0FFH,1 .BYTE 35H,0FFH,0FFH,3 ; TRKTBL: .BYTE 0,0,0,0 ; track table (support four drives) ; IOERR: .BYTE 0 ; I/O error status byte CURSC: .BYTE 0 ; current sector count CURSEC: .BYTE 0 ; current sector number ; RTCNT: .BYTE 0 ; retry counter (set to number of retrys) RECFL: .BYTE 0 ; recal flag (set to number of recals) RWFL: .BYTE 0 ; RW flag (0=reading,1=writing) FDCOP: .BYTE 0 ; FDC read or write command ACTFLG: .BYTE 0 ; command active flag STEPR%::.BYTE DSRT ; drive step rate (patchable) ; .END «eof»