PAGE 60 TITLE MP/M Front End BIOS module ; ; ---------------------------------------- ; | XX XX DDDDDD SSSSSS KK KK | ; | XX XX DD DD SS SS KK KK | ; | XX XX DD DD SS KK KK | ; | XXX DD DD SSSSSS KKKK | ; | XX XX DD DD SS KK KK | ; | XX XX DD DD SS SS KK KK | ; | XX XX DDDDDD SSSSSS KK KK | ; ---------------------------------------- ; ; Created 80Nov11 by: John E. Lauber ; Copyright 1980, Measurement Systems and Controls, Inc. ; Edit history: ; 80Dec05-jel Created from FBIOS ; 81Jan28-jel Sector field increased to 16-bit ; 81Jun06-jel Added return of DMA option flag from SETDMA call. ; 81Jul16-jel Added support for NEW low-level driver link. ; This source is written for MACRO-80 (Microsoft's Z-80 macro assembler) .Z80 ; for ZILOG SUBTTL Equates and Definitions PAGE CR EQU 0DH ; define return LF EQU 0AH ; define line feed ; Global entry points for XIOS jump table. GLOBAL HOME GLOBAL SELDSK GLOBAL SETTRK GLOBAL SETSEC GLOBAL SETDMA GLOBAL READ GLOBAL WRITE GLOBAL SECTRN ; External XIOS entry points for disk error routines EXTRN COLDSTART EXTRN CHRIN EXTRN CHROUT ; External Physical disk driver entry points. EXTRN SECBUF ; base of sector buffer ; Headers defined in low-level drivers for 16 devices. IRPC DN, EXTRN DPH.&DN ENDM ; XDSK globals GLOBAL DVRTBL ; drive descriptor block GLOBAL DIRBUF ; base of directory buffer GLOBAL OPFLGS ; driver option flags GLOBAL PNTMSG ; print message utility GLOBAL INIDVR ; driver initialization SUBTTL Logical Device Routines PAGE ; Select Disk routine. On entry, the caller passes the new drive number ; in the C register (range 0-15). Bit-0 in the E register is set to 0 ; if this is the first time this device is being accessed and therefore ; the format type of the diskette must be found. ; SELDSK: LD B,0 ; prep drive number for double add LD A,C ; get drive number CP 16 ; check 0-15 limit LD HL,0 RET NC ; error if greater than 15 ; BIT 0,E ; is this first select? JR Z,NEWDSK ; yes, branch to lookup type ; LD A,C LD (USRDSK),A ; set user selected disk ; LD HL,DPHTBL ; base of header table ADD HL,BC ADD HL,BC ; point to selected disk entry LD E,(HL) INC HL LD D,(HL) ; load DPH addr PUSH DE ; save on stack LD HL,10 ; offset to disk parameter block ADD HL,DE ; point to DPB address LD E,(HL) INC HL LD D,(HL) ; load DPB addr LD (USRDPB),DE ; store DPB addr ; LD HL,FTBL ; point to base of format table ADD HL,BC ; point to entry LD A,(HL) ; get format type LD (FMTFL),A ; set as current type ; POP HL ; restore DPH addr RET ; done ; This begins the first time access to a drive. ; NEWDSK: CALL STKSAVE ; save the stack for this ; PUSH BC ; save selected drive number CALL WRSTAT ; check write status POP BC ; LD HL,DPHTBL ADD HL,BC ADD HL,BC LD A,(HL) INC HL LD H,(HL) LD L,A OR H JR Z,NEWD.E ; PUSH HL ; save DPH address PUSH BC ; and drive number LD HL,DVRTBL+DSK LD (HL),C ; set selected drive for driver LD B,4 CLRTBL: INC HL LD (HL),0 ; clear driver table DJNZ CLRTBL ; CALL DFMT ; find the format POP BC LD A,L OR H ; test for valid DPB JR NZ,NEWD.1 ; branch if DPB present POP HL ; and DPH address JR NEWD.E ; select error ; NEWD.1: EX DE,HL ; save DPB pointer in DE ; LD A,C LD (USRDSK),A ; set as user selected disk ; LD HL,FTBL ; get base of format table ADD HL,BC ; point to entry LD A,(DE) ; get format type from DPB LD (HL),A ; set drive format in table LD (FMTFL),A ; set format type as current ; POP HL PUSH HL ; restore DPH addr in reg ; INC DE ; point to translate table address LD A,(DE) LD (HL),A INC HL INC DE LD A,(DE) LD (HL),A ; patch translate table into DPB header INC DE ; point to DPB LD (USRDPB),DE ; store it away LD BC,9 ADD HL,BC ; point to DPB in DPH LD (HL),E INC HL LD (HL),D ; store in DPH ; POP HL ; restore DPH address RET ; done ; New disk select routine branches here if error is selecting drive. ; NEWD.E: LD HL,0 RET ; and exit routine ; Home routine. ; Position R/W head on track zero ; HOME: LD BC,0 ; prep for SETTRK ; ; Set Track routine. ; New track number in reg C ; SETTRK: LD (USRTRK),BC ; update storage RET ; done ; Set Sector routine. ; New sector number in reg C ; SETSEC: LD (LACSEC),BC ; set varible RET ; done ; Sector Translation routine. ; Logical CP/M sector in BC, DE->translate table ; If (SPT) greater than 256, then 16-bit translate table is referenced ; If (SPT) less than 256, 8-bit translate table is referenced ; with register H set to 0. ; if DE=0 then no translation will take place (sector adjusted by 1). ; Return with physical sector in reg HL. SECTRN: LD (USRSEC),BC ; set unlace user sector LD H,B LD L,C ; move sector to HL LD A,E OR D ; check DE for zero JR Z,NOTRN ; yes, no translation PUSH HL ; save sector LD HL,(USRDPB) INC HL ; point to SPT high order byte LD A,(HL) ; get the byte POP HL ; restore sector OR A JR NZ,SECT16 ; branch if 16-bit sector field ADD HL,DE ; point to entry LD L,(HL) ; get 8-bit sector LD H,0 ; mask to 8-bit sector RET ; done SECT16: ADD HL,HL ; sector number times 2 ADD HL,DE ; point to 16-bit entry LD A,(HL) ; get low order byte INC HL LD H,(HL) ; get high order byte LD L,A ; join with low order RET ; done NOTRN: INC HL ; adjust 0-x to 1-x+1 RET ; done ; Set DMA address routine. ; New DMA address in regs BC ; SETDMA: LD (DMAADD),BC ; set it LD A,(OPFLGS) ; get driver option flags RET ; and return with them ; CP/M read record entry. ; READ: LD HL,MODFL ; point to mode flags RES WRT,M ; set for reading LD C,0 ; force write type 0 JR RDWR ; CP/M write record entry. ; WRITE: LD HL,MODFL ; point to mode flags SET WRT,M ; set for writing ; ; Copy the user selected sector table to the unallocated sector ; sector table if the write type is equal to "2" (new unallocated block). ; RDWR: ; CALL STKSAVE ; switch to local stack LD A,C ; get write type LD (WRTYP),A ; store write type CP 2 ; write type 2? JR NZ,CHKUNA ; no, branch LD HL,USRTBL LD DE,UNATBL LD BC,5 LDIR ; update UNA followers LD HL,(USRDPB) ; get selected DPB INC HL INC HL INC HL ; point to BLM LD A,(HL) INC A LD (UNACNT),A ; store as UNA counter ; ; Check the unallocated sector counter and branch to set ; pre-reading if count is equal to zero. ; CHKUNA: LD HL,UNACNT ; point to counter LD A,(HL) ; get it OR A ; set flags JR Z,SETPRD ; if zero, set pre-read DEC (HL) ; UNACNT = UNACNT-1 ; ; Compare the selected sector with the next unallocated sector, ; and branch to set pre-reading if the sectors do not match. ; LD HL,UNATBL ; point HL to UNA table LD DE,USRDSK ; point DE to user select table LD B,5 ; compare five bytes CHKU1: LD A,(DE) ; get user value CP (HL) ; compare with UNA value JR NZ,SETPRD ; set pre-read if bad match INC HL INC DE ; bump pointers DJNZ CHKU1 ; loop four times ; ; Increment the unallocated sector table to the next sector. ; Check the overflow to the next track. ; LD HL,(USRDPB) LD E,(HL) INC HL LD D,(HL) ; put SPT in DE LD HL,(UNASEC) ; get current UNA sector INC HL LD (UNASEC),HL ; store next number OR A SBC HL,DE ; compare to SPT JR C,RESPRD ; if no track overflow LD HL,0 LD (UNASEC),HL ; reset UNA sector LD HL,(UNATRK) ; get current UNA track INC HL ; bump it once LD (UNATRK),HL ; RESPRD: LD HL,MODFL RES PRD,M ; reset pre-read flag JR BLKUP ; SETPRD: LD HL,MODFL SET PRD,M ; set pre-read flag XOR A ; zero ACC LD (UNACNT),A ; and reset UNA counter ; ; This point begins the proccedure for blocking the logical ; CP/M sector up to the physical sector. ; BLKUP: LD HL,(LACSEC) ; get lace sector DEC HL ; adjust relative 0 LD A,(FMTFL) ; get format flags PUSH AF AND 7FH ; pre-select side 0 LD B,A ; store it in B POP AF BIT SD2,A ; test for double-sided device JR Z,BLKSEC ; skip side select if single-sided ; ; Select side 0 or side 1 of device by subtracting 1/2 the ; SPT value to select side and new sector on side 1. ; PUSH HL ; save logical sector LD HL,(USRDPB) ; get user DPB INC HL LD D,(HL) SRL D DEC HL LD E,(HL) RR E ; 1/2 SPT in DE POP HL ; restore logical sector PUSH HL OR A SBC HL,DE ; sector - 1/2 SPT POP HL JR C,BLKSEC ; CY set if side 0 SBC HL,DE SET SD2,B ; ; Now block up to the physical sector and create ; a sector mask byte for future use. ; BLKSEC: LD A,B ; get FMT value LD (USRFMT),A ; set in block AND 3 ; mask sector size LD B,A ; and place in B XOR A BLKS1: DEC B ; decrement sector size JP M,BLKS2 ; if done SRL H RR L ; divide sector by 2 SCF RLA ; extend sector mask JR BLKS1 ; and loop BLKS2: LD (RECMSK),A ; store record mask INC HL ; adjust relative 1 LD (USRSEC),HL ; store physical sector ; ; Compare the selected physical sector with the ; current physical sector and skip reading if buffer current. ; LD HL,DVRTBL ; point to disk I/O table LD DE,USRTBL ; point to user select table LD B,6 CHKSEC: LD A,(DE) CP (HL) JR NZ,NEWSEC ; if bad match, select new sector INC HL INC DE ; bump pointers DJNZ CHKSEC JR SAMSEC ; must be same sector NEWSEC: ; ; Check if the current buffer needs updating on disk ; and copy the new sector into physical I/O table. ; CALL WRSTAT ; check write buffer LD HL,USRTBL LD DE,DVRTBL LD BC,6 LDIR ; update current disk table LD HL,MODFL ; get mode flags BIT PRD,M ; test pre-read RES PWR,M ; set for physical read CALL NZ,DVRIO ; call physical driver I/O ; ; Deblock the buffer contents and send the caller ; his 128 bytes of data. ; SAMSEC: LD A,(LACSEC) ; get laced sector low order byte DEC A ; adjust for logical record (0-x) LD HL,RECMSK AND (HL) ; deblock sector RRA LD D,A ; muliply by 128 and LD A,0 ; place in DE RRA LD E,A ; relative offset in buffer LD HL,SECBUF ADD HL,DE ; HL=absolute address LD DE,(DMAADD) ; get CP/M DMA address LD BC,128 LD A,(MODFL) ; get mode flags BIT WRT,A ; are we writing? JR Z,MOVREC ; no, regs are OK EX DE,HL ; switch source&destination for writing SET BUF,A ; flag buffer dirty LD (MODFL),A ; restore it MOVREC: LDIR ; move the record ; ; Unconditionally update the contents of the buffer if ; the write type is equal to "1" (directory sector). ; LD A,(WRTYP) ; get write type CP 1 ; directory write? CALL Z,WRSTAT ; yes, flush buffer XOR A ; zero ACC RET ; done ; Check write buffer status and flush if dirty. ; Reset the dirty flag. ; WRSTAT: LD HL,MODFL BIT BUF,M ; test dirty flag RES BUF,M ; reset it RET Z ; done if not set SET PWR,M ; set for physical write ; Physical disk I/O: ; The physical disk read write routines are called from this routine, ; and disk error recovery handled also. The user has the option of typing ; a CNTR-C to abort error and returning to CP/M with device A selected, ; or typing CNTR-I to ignore error and return to BDOS without error ; indication or typing any other key for a retry. ; DVRIO: XOR A LD (DVRTBL+RESULT),A ; reset result byte LD A,(MODFL) BIT PWR,A ; test for write or read JR NZ,DVRWRT ; if writing CALL DREAD ; if reading JR DVRIO1 DVRWRT: CALL DWRITE DVRIO1: LD A,(DVRTBL+RESULT) ; check for errors OR A ; set flags RET Z ; if no errors LD DE,WRTMSG LD A,(MODFL) ; get mode flags BIT PWR,A ; writing? JR NZ,$+5 ; yes, print it LD DE,RDMSG CALL PNTMSG LD DE,ERRMSG CALL PNTMSG ; print error and device string LD A,(DVRTBL+DSK) ; get device ADD A,"A" CALL CHROUT ; print device letter LD A,(DVRTBL+RESULT) AND 0F0H ; test for sector type errors JR Z,DVRER1 ; if not LD DE,ERRTRK CALL PNTMSG ; print track string LD HL,(DVRTBL+TRK) CALL HEX16 ; and track LD A,(FMTFL) ; get format type BIT 7,A ; double sided disk? JR Z,DVRER2 ; no, skip side number LD DE,ERRSID CALL PNTMSG ; print side string LD A,(DVRTBL+FMT) RLCA ; shift bit-7 to bit-0 AND 1 ; mask it ADD A,"0" CALL CHROUT ; print side number DVRER2: LD DE,ERRSEC CALL PNTMSG ; print sector sting LD HL,(DVRTBL+SEC) CALL HEX16 ; and sector DVRER1: LD DE,ERRTYP CALL PNTMSG ; print error type string LD A,(DVRTBL+RESULT) CALL HEXOUT ; print error byte LD DE,ERROPT CALL PNTMSG ; print prompt CALL CHRIN ; get a character PUSH AF ; save it CALL CRLF POP AF ; restore it CP "I"-40H ; ignore? RET Z ; yes, done CP "C"-40H ; abort? JP NZ,DVRIO ; no, must be a retry JP COLDSTART ; and re-boot ; Message strings WRTMSG: DB CR,LF,"WRITE$" RDMSG: DB CR,LF,"READ$" ERRMSG: DB " ERROR: Device-$" ERRTRK: DB " Track-$" ERRSID: DB " Side-$" ERRSEC: DB " Sector-$" ERRTYP: DB " Type-$" ERROPT: DB CR,LF,"(RETURN=retry, CNTL-C=abort, CNTL-I=ignore)? $" CRLFM: DB CR,LF,"$" SUBTTL Utility Subroutines PAGE ; Find and execute DFMT routine of current DVRTBL drive number. ; DFMT: LD BC,18 ; offset for DFMT routine address JR EXCDVR ; execute routine ; Find and execute DREAD routine of current DVRTBL drive number. ; DREAD: LD BC,20 ; offset for DREAD routine addr JR EXCDVR ; execute routine ; Find and execute DWRITE routine of current DVRTBL drive number. ; DWRITE: LD BC,22 ; offset for DWRITE routine addr ; ; Common code for executing low-level driver routine. ; EXCDVR: LD DE,(DVRTBL+DSK) ; get drive number from table LD D,0 ; prep for double add LD HL,DPHTBL ; base of header table ADD HL,DE ADD HL,DE ; index relative to drive # LD A,(HL) INC HL LD H,(HL) LD L,A ; DPH addr loaded LD (DVRTBL+DPH),HL ; store in driver table ; ADD HL,BC ; point to routine addr LD A,(HL) INC HL LD H,(HL) LD L,A ; load address JP (HL) ; and execute ; Find and execute any existing low-level initialization rouitine. ; INIDVR: LD HL,DPHTBL ; base of header table LD B,16 ; max number of DPH addr entrys INID.1: LD E,(HL) INC HL LD D,(HL) ; DPH addr loaded INC HL LD A,E OR D ; test for presence PUSH HL ; save table pointer PUSH BC ; and count CALL NZ,INID.2 ; if DPH entry is present POP BC POP HL DJNZ INID.1 ; count down RET ; all done ; Low-level driver initialization only if routine address is non-zero ; INID.2: LD HL,16 ; offset for INIT routine addr ADD HL,DE ; point to addr LD A,(HL) INC HL LD H,(HL) LD L,A ; load routine addr OR H ; test for zero RET Z ; if routine not present JP (HL) ; execute it ; Stack saver routine for disk routines. ; STKSAVE is called from entry point, stack is swapped and the inverse ; stack restore routine, STKREST is placed first on new stack so disk ; routines may simply return. ; STKSAVE: POP HL ; get back return address LD (OLDSP),SP ; save old stack LD SP,INTSTK ; load internal stack PUSH HL LD HL,STKREST EX (SP),HL ; stack restore first on stack JP (HL) ; return to caller ; STKREST: LD SP,(OLDSP) ; restore original stack RET ; done ; OLDSP: DW 0 ; old stack pointer storage DS 32 ; internal stack area INTSTK: ; top of internal stack ; ; Print a CR and LF conbination: CRLF: LD DE,CRLFM ; ; Print message on console: PNTMSG: LD A,(DE) ; get char INC DE ; bump pointer CP "$" ; string terminator? RET Z ; yes, done PUSH DE CALL CHROUT ; print it POP DE JR PNTMSG ; and loop HEX16: LD A,H ; get MSB PUSH HL CALL HEXOUT ; and print it POP HL LD A,L ; get MSB ; ; Print the ACC in hex on the console: HEXOUT: PUSH AF ; save byte RRCA RRCA RRCA RRCA ; shift MSN to LSN CALL OUTCHR ; print hex digit POP AF OUTCHR: AND 0FH ; mask LSN ADD A,90H ; add offset DAA ; pack BCD ADC A,40H ; add offset DAA ; pack again and fall into CHROUT JP CHROUT ; send char SUBTTL Data and Variable Area PAGE ; user selected table referencing a logical sector. USRTBL EQU $ ; user select table USRDSK: DB 0 ; user selected disk USRTRK: DW 0 ; track USRSEC: DW 0 ; sector USRFMT: DB 0 ; format DMAADD: DW 0 ; CP/M DMA address WRTYP: DB 0 ; write type CP/M USRDPB: DW 0 ; selected DPB LACSEC: DW 0 ; CP/M laced sector RECMSK: DB 0 ; record mask UNACNT: DB 0 ; unallocated record counter ; Unallocated record table to follow CP/M blocks. UNATBL EQU $ UNADSK: DB 0 ; unallocated follower disk UNATRK: DW 0 ; track UNASEC: DW 0 ; sector ; Mode flag with bit assignments. MODFL: DB 0 ; driver mode flags WRT EQU 0 ; CP/M write flag PRD EQU 1 ; pre-read sector flag BUF EQU 2 ; buffer dirty flag PWR EQU 3 ; physical write flag ; Device format type byte with bits defined as follows. FMTFL: DB 0 ; Bits 0 & 1 - sector size field ; 00 = 128 bytes ; 01 = 256 bytes ; 10 = 512 bytes ; 11 = 1024 bytes SD2 EQU 7 ; double-sided type OPFLGS: DB 0 ; driver option flags ; Device format table FTBL: DB 0,0,0,0,0,0,0,0 ; 16 devices DB 0,0,0,0,0,0,0,0 ; Device header table (storage for 16 disk parameter header addresses) DPHTBL: IRPC DN, DW DPH.&DN ENDM ; Physical Driver Descriptor Block. DVRTBL EQU $ DB 0 DW 0 DW 0 DB 0 DW SECBUF DW 0 DB 0 ; Drive Descriptor Block layout. DSK EQU 0 ; disk (0-15) TRK EQU 1 ; track (0-65535) SEC EQU 3 ; sector (0-65535) FMT EQU 5 ; format type (sector size/side select) DMA EQU 6 ; DMA address DPH EQU 8 ; DPH address RESULT EQU 10 ; operation results ; directory buffer DIRBUF: DS 128 ; end of variables END