;================================================================ ; CDZSWP Overlay. ; Version : B/P Bios using SCSI Hard Disk Subsystem. ; Revision: 1.0 ; Author : Harold F. Bower ; Date : 10 October 1997 ; Desc: This file uses the generic direct device driver features of ; the Banked and Portable (B/P) Bios to access a CD-ROM drive ; connected to the SCSI Bus. The drive block size is re- ; defined to 512 bytes to avoid overwriting the B/P default ; buffer, and four reads are employed to fill the host 2048- ; byte buffer for each block request. ; Requirements: ; - B/P Bios with SCSI Interface ; - SCSI CD-ROM drive such as: Sony CDU-55S/56S double-speed ; Chinon CDS-535 single-speed. ; The drive SCSI address must match one of the three physical ; device descriptor blocks in the Bios. Parameters for the ; drive are ignored. Only the Dev/LUN byte is used. ; ; NOTE: Early releases of B/P Bios did not contain adequate ; checks on Buffer reuse (for HSTBUF). Contact the author ; for fixes to prevent corruption of files copied from the ; CD-ROM. ;---------------------------------------------------------------- ; Assemble this file with ZMAC (or SLR Assemblers) to a .HEX file ; and form into an overlay file as: ; ; ZMAC CD-BPS.SRC /H ; MYLOAD CDZSWP.DVR=CD-BPS.HEX <-- output renamed to default ; ; NOTE: the file must be self-contained with no external ; declarations to library routines. ;================================================================ REV EQU 10 ; Revision (Maj/Min) in Decimal BELL EQU 07H ; Ascii Char values LF EQU 0AH CR EQU 0DH envAdr EQU 0109H ; Address of ENV Address in Z3 Program Header RETBIO EQU 30*3 ; Jump offset for Return BIOS pointers ORG 180H ; <<<--- Overlay Starts Here! <--- ;!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*! ;*!*!*!*!*!*!* DO NOT ALTER SEQUENCES IN THIS TABLE !*!*!*!*!*!*!*!*!* ;!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*!*! Begin: DEFW LENGTH ; This word for checking available space DEFB REV ; Revision # (decimal) of this version ; Standard Entry Points. JP RetID ;+3 Return Pointer to Overlay Text ID String JP DrInit ;+6 Validate System Configuration, Init Params JP RdBlok ;+9 Read a 2048-byte block of Data from CD-ROM JP Eject ;+12 Spin down Disc and Eject Tray/Caddy JP Load ;+15 Load Tray/Caddy and Spin up Disc JP 0 ;+18 JP 0 ;+21 JP 0 ;+24 DEFB 'CDZSWP-OVL',0 ;+27 <<-- Mandatory Validation String -->> ;---------------------------------------------------------------- ; Return Pointer to a Null-Terminated Overlay Identification String ; Enter: None ; Exit : HL -> String ; Uses : HL ;---------------------------------------------------------------- RetID: LD HL,idStr RET idStr: DEFB 'Generic B/P Bios SCSI Driver, Rev ' DEFB REV / 10 + '0','.',REV MOD 10 + '0',', (512-byte Blocks)',0 ;---------------------------------------------------------------- ; Initialize Drive Sub-System. Steps to be accomplished here are: ; 1) Store address of Buffer for later use by all routines ; 2) Validate System Configuration (H/W, S/W, OS and/or Configuration ; 3) Perform any System-specific Initializations needed. ; Enter: HL -> 2048-byte buffer for CD-ROM "Block" ; Exit : HL -> Null String if Ok, Null-terminated error string if Error ; Carry Set (C) if Errors occured (e.g. No Drive) or System incompatible ; Carry Clear (NC) if system compatible and initializations performed ; Uses : All Registers ; NOTE: Access to pre-defined Static Z-System items is permitted, ; such as the z3eadr pointer at location 0103H ;---------------------------------------------------------------- DrInit: LD (bufAdr),HL ; Save the Buffer Address locally CALL ChkBP ; Insure that we are operating under B/P Bios RET NZ ; ..quit w/Message Ptr if Not (use Z for test) ; We have B/P Bios, Get timer location for accurate timeout measurements LD HL,(bioBas) ; Get Bios Addr LD L,26*3 ; offset to Time Entry LD DE,idBufr ; set dummy buffer for Time LD C,0 ; Set to Read CALL JPHL ; ..Get Time/Pointer LD (cntrAd),BC ; save for later use ; Check for adequate Disk Controller and Scan for active SCSI CD-ROM LD HL,(bioBas) ; Get Bios Address (only Page used) LD L,0BAH ; Offset to Controller type LD A,(HL) ; fetch it BIT 7,A ; Is it GIDE (IDE/ATA)? JR NZ,BadCon ; ..jump to Error exit if Yes CP 3 ; Is it Seagate SCSI? JR Z,ContOk ; ..jump if So CP 5 ; Is it a "SCSI-2" variant? JR NC,ContOk ; ..jump if So, Else fall thru to Error BadCon: LD HL,badCtl ; Pt to Error Message SCF ; set Error Flag RET ; exit badCtl: DEFB CR,LF,BELL,'+++ Can''t handle this Controller Type! +++' DEFB CR,LF,0 ContOk: LD L,31*3 ; Offset to Direct Disk IO vector LD (SCSI+1),HL ; and store in SCSI vector ; Set Hard Disk Data Transfer Area, get CDB Size LD DE,(bufAdr) ; Get Start of User RAM Data Buffer LD BC,2*256+0 ; Hard Disk Function 0 for params CALL SCSI CP 6 ; Is the Command Block >6 bytes long? JR NC,BlklOk ; ..jump if Ok LD HL,lenErr ; Else Pt to Message SCF ; set Error Flag RET ; exit lenErr: DEFB CR,LF,BELL,'**** SCSI Block Length Error !',0 ; Scan all three allowable Hard drives and identify types BlklOk: XOR A ; Clear CD-ROM detected flag LD (havecd),A ; Initialize flag LD (devSav),A ; and device variables LD HL,(bioBas) ; Get the Base of BIOS LD L,0BBH-9 ; Offset to (first Hard drive)-(entry size) LD B,3 ; examine all three units DvLoop: PUSH BC LD DE,9 ; Offset to an entry ADD HL,DE PUSH HL LD A,(HL) ; Get Device/LUN byte LD (devLUN),A ; saving in case it's Ok AND 00011000B ; Is it valid? JR NZ,DvSet ; ..jump if so XOR A ; Set flags to fall thru DvSet: CALL NZ,Inquir ; Do SCSI Fcn 12H if valid, else fall thru POP HL POP BC DJNZ DvLoop ; ..loop til all three checked LD A,(devSav) ; Get any saved device byte LD (devLUN),A LD A,(havecd) ; Did we find a CD-ROM? OR A JR Z,NoCD ; ..exit w/Error Ptr if Not CALL Load ; Else Command to Load just in case.. RET C ; returning Error if none LD HL,idBufr ; Return w/ID String RET ; Error Flag Clear if Ok NoCD: LD HL,noCDR ; Else Pt to error Message SCF ; set Error Flag RET ; exit noCDR: DEFB CR,LF,BELL,'++ No CD-ROM Detected..',CR,LF,0 ;---------------------------------------------------------------- ; Read a Specified Block of 2048 bytes from the CD-ROM into the Buffer. ; Enter: BCDE = 32-bit Logical Block Address (2048-byte blocks) to Read ; (MSB in B..LSB in E) ; Exit : Carry Set (C) if Errors occured, Clear (NC) if Ok ; HL - Points to Null String if Ok ; - Points to a (possibly Null) Null-terminated string if Errors ; A contains Non-Zero Error Code: ; (currently undefined except for:) ; 1FH = Excessively Large Block Number ; Uses : All Registers ;---------------------------------------------------------------- ; This routine only uses up to 19-bits of addressing for 2048-byte ; Block addresses (expanding to 21 when multiplied by 4 for 512- ; byte blocks) in order to use 6-byte SCSI Read Command. Return ; Error if block size exceeds what can be handled. RdBlok: LD A,B ; Get Block MSB OR A ; Too large? JR NZ,RdBlk0 ; ..jump to Error if Yes LD A,C ; Else get next byte AND 0F8H ; Too Large JR Z,RdBlk1 ; ..jump to continue if No RdBlk0: LD A,1FH ; LBA Address too large. Return Error LD HL,bigLBA ; return String SCF RET bigLBA: DEFB CR,LF,BELL,'Address too Large!',0 RdBlk1: LD HL,cmdBlk ; Point to the Command Block LD (HL),08H ; Read Block Command (6-byte) INC HL LD A,(devLUN) ; Get Device code AND 0E0H ; strip all but LUN SLA E ; Multiply CDE by 2 RL D RL C SLA E ; again for * 4 RL D RL C OR C ; Add LUN to MSB of result (size alreacy Ok) LD (HL),A ; stuff LBA [2] INC HL LD (HL),D ; LBA [1] INC HL LD (HL),E ; and LBA [0] (LSB) INC HL ; Advance to # of Blocks LD (HL),1 ; read only 1 INC HL LD (HL),0 ; with no control bits LD HL,(bufAdr) ; Set current blk ptr LD (bufPtr),HL ; for start of transfer LD B,4 ; Four 512-byte blocks in a 2048-byte bufr RdBlk2: PUSH BC ; Save Loop Counter LD DE,(bufPtr) ; Get Data Buffer address LD BC,2*256+0 ; Set in Driver (Func 0, set params) CALL SCSI LD A,(devLUN) ; Get the Drive/LUN byte from storage LD BC,2*256+1 ; Select Hard Drive unit CALL SCSI XOR A ; Say we don't have any Write Data LD DE,cmdBlk ; pt to CDB LD BC,2*256+2 ; Driver 02 (Hard), Function 2 (Direct SCSI) CALL SCSI ; execute POP BC ; (restore Loop counter) OR A ; Ok? JP NZ,SnsErr ; ..take Error Return if Bad ; Advance to next block LD HL,cmdBlk+3 ; Pt to LSB byte of CDB LBA INC (HL) ; Increment LSB JR NZ,NoOvfl ; ..jump if no overflow DEC HL ; else back up INC (HL) ; bump middle one JR NZ,NoOvfl ; ..jump if no overflow DEC HL ; Back up LD A,(HL) ; fetch LUN/LBA MSB AND 0E0H ; keep only LUN LD C,A ; (save) INC (HL) ; Bump LBA MSB LD A,(HL) ; fetch AND 1FH ; kill possibly altered LUN OR C ; add LUN LD (HL),A ; put back NoOvfl: LD HL,(bufPtr) LD DE,512 ADD HL,DE ; Advance to next block area LD (bufPtr),HL DJNZ RdBlk2 ; ..loop til all four blocks read ; This is Ok Exit from several points OkExit: LD HL,nulStr XOR A RET ; then back to Caller w/Ok Status ;---------------------------------------------------------------- ; Spin Down any installed Disc and Eject Tray/Caddy ; Enter: None ; Exit : Carry Set (C) if Errors occured, Clear (NC) if Ok ; HL - Points to a Null String if Ok, ; - Points to a Null-terminated string if Error and A ; contains non-Zero Error Code. ; Uses : All Registers ;---------------------------------------------------------------- Eject: LD HL,cmdBlk ; Point to the Command Block LD (HL),1BH ; Start/Stop Unit Command (6-byte) INC HL LD A,(devLUN) ; Get Device code AND 0E0H ; strip all but LUN LD (HL),A ; Save (w/Immediate Bit = 0) INC HL LD (HL),0 ; (reserved) INC HL LD (HL),0 ; (reserved) INC HL LD (HL),00000010B ; Spin Down, Open Tray INC HL LD (HL),0 ; No Control Byte LD DE,(bufAdr) ; Get Data Buffer address LD BC,2*256+0 ; Set in Driver (Func 0, set params) CALL SCSI LD A,(devLUN) ; Get the Drive/LUN byte from storage LD BC,2*256+1 ; Select Hard Drive unit CALL SCSI XOR A ; Say we don't have any Write Data LD DE,cmdBlk ; pt to CDB LD BC,2*256+2 ; Driver 02 (Hard), Function 2 (Direct SCSI) CALL SCSI ; execute OR A ; Ok? JP Z,OkExit ; .Exit thru here if Yes JP SnsErr ; ..Else Determine Error and return it ;---------------------------------------------------------------- ; Load Tray/Caddy and Spin Up Disc ; Enter: None ; Exit : Carry Set (C) if Errors occured, Clear (NC) if Ok ; HL - Points to a Null String if Ok, ; - Points to a Null-terminated string if Error and A ; contains non-Zero Error Code. ; Uses : All Registers ;---------------------------------------------------------------- Load: LD HL,cmdBlk ; Point to the Command Block LD (HL),1BH ; Start/Stop Unit Command (6-byte) INC HL LD A,(devLUN) ; Get Device code AND 0E0H ; strip all but LUN LD (HL),A ; Save (w/Immediate Bit=0) INC HL LD (HL),0 ; (reserved) INC HL LD (HL),0 ; (reserved) INC HL LD (HL),00000011B ; Close Tray and Spin Up Disc INC HL LD (HL),0 ; No Control Byte LD DE,(bufAdr) ; Get Data Buffer address LD BC,2*256+0 ; Set in Driver (Func 0, set params) CALL SCSI LD A,(devLUN) ; Get the Drive/LUN byte from storage LD BC,2*256+1 ; Select Hard Drive unit CALL SCSI XOR A ; Say we don't have any Write Data LD DE,cmdBlk ; pt to CDB LD BC,2*256+2 ; Driver 02 (Hard), Function 2 (Direct SCSI) CALL SCSI ; execute OR A ; Ok? CALL NZ,SnsErr ; Check Sense if Not LD HL,cntrAd ; Else wait for Ready LD (HL),150 ; (Set for 15 Sec timeout) LoadW: LD HL,cmdBlk PUSH HL XOR A ; Get 0 LD (HL),A ; Test Unit Ready Code INC HL LD A,(devLUN) ; Get Device code AND 0E0H ; strip all but LUN LD (HL),A ; Save INC HL LD (HL),A ; (reserved) INC HL LD (HL),A ; (reserved) INC HL LD (HL),A ; (reserved) INC HL LD (HL),A ; No Control Byte POP DE ; (restore CDB ptr) LD BC,2*256+2 ; Driver 02 (Hard), Function 2 (Direct SCSI) CALL SCSI ; execute OR A ; Ok? JP Z,OkExit ; ..Exit thru here if Yes CALL SnsErr ; Else Clear Error Sense Status LD A,(cntrAd) ; Get remaining timer count OR A ; Expired? JR NZ,LoadW ; ..loop if Not LD HL,timout ; Else send appropriate message SCF ; and return Error RET timout: DEFB CR,LF,BELL,'..Timeout waiting for Ready! ',0 ;===================== Support Routines ========================= ;..... ; Execute a SCSI Inquire (12H) command on the specified drive. First ; Select the drive with Hard Driver Function 1, then fill the Command ; Descriptor Block with Command 12H (Read Mode) parameters and execute. ; If a valid return, determine whether or not the drive is a CD-ROM. ; Return Either a Null Ptr (0000) or Pointer to the Vendor and Product ; ID Strings and Product Revision Level within the User Buffer. ; When the first CD-ROM is encountered, Set a flag and save the ; associated devLUN byte for use in later accesses. Inquir: LD A,(haveCD) AND 01H ; Have we already found one? RET NZ ; ..return if Yes LD A,(devLUN) ; Get the Drive/LUN byte from storage LD BC,2*256+1 ; Select Hard Drive unit CALL SCSI LD HL,cmdBlk ; Address our local Command Block Image PUSH HL ; (save) LD (HL),12H ; Stuff Command INC HL LD A,(devLUN) ; Get Device code AND 0E0H ; strip all but LUN LD (HL),A ; stuff INC HL LD (HL),0 INC HL LD (HL),0 INC HL LD (HL),0FFH ; Set Maximum space for return params INC HL LD (HL),0 ; No Codes POP DE ; Get Command Block Address back XOR A ; ..and say we don't have any Write Data LD BC,2*256+2 ; Driver 02 (Hard), Function 2 (Direct SCSI) CALL SCSI ; ..and execute OR A ; Did it execute Ok? JP NZ,ERROR ; ..jump if Errors LD HL,(bufAdr) ; Else pt to Data Area LD A,(HL) ; Get first byte of Data LD DE,8 ADD HL,DE ; (offset to text) AND 1FH ; mask CP 00101B ; CD-ROM? RET NZ ; ..return if Not ; Else copy ID String to local Buffer LD DE,idBufr LD BC,28 ; Store entire string LDIR XOR A LD (DE),A ; and Null-terminate it OR 0FFH LD (havecd),A ; Say that we found a drive LD A,(devLUN) LD (devSav),A ; and save device byte for later accesses LD HL,cmdBlk ; Pt to Command Block PUSH HL LD (HL),1AH ; Mode Sense Command INC HL LD A,(devLUN) ; Get Device code AND 0E0H ; strip all but LUN LD (HL),A ; stuff INC HL LD (HL),00001101B ; Set Page 0DH, Current Values INC HL LD (HL),0 INC HL LD (HL),0FFH ; Set Maximum space for return params INC HL LD (HL),0 ; No Codes POP DE ; Get Command Block Address back XOR A ; say we don't have any Write Data LD BC,2*256+2 ; Driver 02 (Hard), Function 2 (Direct SCSI) CALL SCSI ; execute OR A ; Ok? CALL NZ,SnsErr ; ..call if Errors to see if they are real ; (only returns if Not Real) LD HL,(bufAdr) ; Else pt to Data Area LD DE,10 ADD HL,DE ; offset to lower 2 bytes of Block Size LD A,(HL) ; fetch Hi-byte (of lower 2) CP 2 ; Is it already set to 512 byte Blocks? JR Z,StSizX ; ..jump if Yes LD HL,(bufAdr) ; Pt to Data area LD (HL),0 ; Initialize Header INC HL ; (4 bytes) LD (HL),0 INC HL LD (HL),0 INC HL LD (HL),8 ; end with Block Descriptor Length INC HL PUSH BC LD B,6 StSizL: LD (HL),0 ; Set Density Code, # Blks, rsvd, MSB of Len INC HL DJNZ StSizL POP BC LD (HL),2 ; to 512 bytes INC HL LD (HL),0 LD HL,cmdBlk PUSH HL LD (HL),15H ; Mode Select Command INC HL LD A,(devLUN) AND 0E0H LD (HL),A INC HL LD (HL),0 INC HL LD (HL),0 INC HL LD (HL),0CH ; set parm length (no pages) INC HL LD (HL),0 POP DE OR 0FFH ; Say we DO have Data to Write LD BC,2*256+2 ; Driver 02 (Hard), Function 2 (Direct SCSI) CALL SCSI ; execute OR A ; Ok? CALL NZ,SnsErr ; ..call if Errors to see if they are Real StSizX: XOR A ; Return Ok RET ERROR: LD HL,nulStr SCF RET ;..... ; Execute a Request Sense SCSI command to see if a Real error was detected. ; Return if only a warning, else delete the return address and return SnsErr: LD HL,cmdBlk ; Pt to Comnd Block PUSH HL LD (HL),03H ; Request Sense INC HL INC HL ; (skip, LUN already set) LD (HL),0 INC HL LD (HL),0 INC HL LD (HL),0FFH ; allow up to 255 bytes INC HL LD (HL),0 ; no control codes POP DE XOR A ; Say we don't have any Write Data PUSH BC LD BC,2*256+2 ; Driver 02 (Hard), Function 2 (Direct SCSI) CALL SCSI ; execute POP BC OR A ; Did it execute Ok? JR Z,SnsEr0 ; ..jump if Yes NulErX: LD HL,InvSns ; Else Pt to Message SCF ; Set Err Flag RET InvSns: DEFB CR,LF,BELL,'--Invalid Sense - ',0 SnsEr0: LD HL,(bufAdr) ; Pt to data area LD A,(HL) ; Get Valid/Error Code byte OR A JP Z,ERROR ; ..exit w/No Message if no Code SnsEr1: INC HL INC HL ; Advance to Sense Key LD A,(HL) AND 0FH JP Z,ERROR ; ..exit w/No Message if no more specific info ; Else we may have more specific data to return as a string. LD L,A ; Move resultant Key LD H,0 ; as 16-bits ADD HL,HL ; double for word index LD DE,keyPtr ADD HL,DE ; offset to entry in ptr table LD E,(HL) INC HL LD D,(HL) ; fetch EX DE,HL ; position SCF RET keyPtr: DEFW erStr1, erStr2, erStr3 DEFW erStr4, erStr5, erStr6 DEFW nulStr, erStr8, nulStr DEFW nulStr, erStrB, nulStr DEFW nulStr, nulStr, nulStr erStr1: DEFB '-- Recovered Error',BELL,0 erStr2: DEFB '-- Not Ready',BELL,0 erStr3: DEFB '-- Medium Error',BELL,0 erStr4: DEFB '-- Hardware Error',BELL,0 erStr5: DEFB '-- Illegal Request',BELL,0 erStr6: DEFB '-- Unit Attention',BELL,0 erStr8: DEFB '-- Blank Check',BELL,0 erStrB: DEFB '-- Aborted Command' nulStr: DEFB BELL,0 ; dual-use of ending bytes ;..... ; Insure that we are operating under B/P Bios, and Set address of the ; "Real" Bios Jump table if validated. ; Enter: Address of the Env must have been set ; Exit : biosJT set to base of Jump Table, Zero Set (Z) if found (Carry ?) ; else error message returned, Carry Set (C), Zero Reset (NZ) ChkBP: LD HL,(envAdr) ; Get the ENV Address from Header LD DE,8 ADD HL,DE ; Offset to Extended flag BIT 7,(HL) ; Is it extended? LD DE,(0001) ; .(Get BIOS Warm Boot Entry in case Not) JR Z,NoXtnd ; ..jump if Not extended LD DE,45H-8 ; It is Extended, Add additional offset ADD HL,DE ; .to BIOS Base address LD E,(HL) ; ..and fetch INC HL LD D,(HL) NoXtnd: EX DE,HL LD (bioBas),HL ; Save BIOS Base or WB Vector (Page used) LD L,RETBIO ; ..offset to Return BIOS Information entry LD A,(HL) ; Get the char CP 0C3H ; Is it a Jump? JR NZ,NotBP ; ..Not B/P Bios if not CALL JPHL ; Call it if it appears Ok LD (biosJT),BC ; ..saving potential "real" BIOS WB Jump Addr LD HL,-6 ; "B/P" must be first 3 chars at -6 from Config ADD HL,DE LD A,(HL) ; Get first CP 'B' ; Ok? JR NZ,NotBP ; ..error if not INC HL LD A,(HL) ; Get second CP '/' ; Ok? JR NZ,NotBP ; ..error if not INC HL LD A,(HL) ; Finally third CP 'P' ; Ok? RET Z ; Return Zero Set if Ok NotBP: LD HL,noBPstr ; Point to Error String SCF ; Set Error Flag RET ; ..back to Caller noBPstr: DEFB CR,LF,BELL,'+++ Not B/P Bios +++',CR,LF,0 ;..... ; Routines to directly access B/P Bios entry points SCSI: JP 0000 ; Jump to Direct Disk IO routine BDvTbl: LD A,22*3 ; Return Table of DPH Vectors JPBios: LD HL,(0001) ; Get Bios Warm Boot Vector LD L,A ; ..and place Page offset to make address JPHL: JP (HL) ;..... ; Data Storage maintained here in the Code Segment idBufr: DEFS 29 ; Buffer for CD-ROM "Inquire" Identity String haveCD: DEFS 1 ; Flag for CD-ROM Drive Presence biosJT: DEFS 2 ; Base Address of "Real" Bios Jump Table bioBas: DEFS 2 ; Base Address running BIOS (Page used) cntrAd: DEFS 2 ; B/P Bios 100mS counter Byte Address devLUN: DEFS 1 ; B/P Device/LUN Byte for Drive devSav: DEFS 1 ; Device/LUN Byte temp buffer bufAdr: DEFS 2 ; Pointer to 2048-byte Buffer in Main Pgm bufPtr: DEFS 2 ; secondary ptr for four 512-byte reads cmdBlk: DEFS 12 ; Adequate space for Command Descr. Blk. LENGTH EQU $-Begin END