; FLOPPY DISK TEST FOR Z-80 CP/M SYSTEMS - DR. DOBB's: April 1981 ; ; This program reads from the disk, saves that information, writes its ; own pattern, reads that, then restores the original data if requested. ; This gives far better diagnostics than using "FBAD" or "FINDBAD" which ; only read the information already on the disk and make no attempt to ; write anything, thus is a minimal check, compared with far more robust ; checks such as this program. ; ; ; NOTE: Since it does so very much more than FBAD or ; FINDBAD, it also takes a lot longer, typically ; 11 seconds per track on a 8" floppy with 52 ; records/track. This is about 28 minutes on ; a DSDD diskette with a total of 154 tracks. ; ; ; SPCL NOTE: THIS PROGRM DOES NOT MAKE A DISK FILE OF ; BAD AREAS FOUND. ; ; ; 12/12/85 Reformatted, added progress reporting, other changes ; v2 - Irv Hoff ; ; BDOS EQU 0005H WBOOT EQU 0000H ; ; ; BDOS calls ; CONOUT EQU 2 ; Display character on console LIST EQU 5 ; List output to printer DIRCON EQU 6 ; Direct console I/O PRINT EQU 9 ; Pring string CPMVER EQU 12 ; CP/M version ; ; ; General equates ; CR EQU 0DH ; ASCII characters LF EQU 0AH FF EQU 0CH TAB EQU 09H ; ; ; Parameters for disk (supplied as single density, soft sector) ; DRVF EQU 'A'-65 ; First drive to allow testing 0=A 1=B DRVL EQU 'P'-65 ; Last drive to allow test TRKFST EQU 0 ; First track TRKLST EQU 154 ; Last track (77 one side, 154 both) RECFST EQU 1 ; First record RECLST EQU 52 ; Last record (26 SD, 52 DD) BPR EQU 128 ; Bytes per record BPT EQU BPR*RECLST ; Bytes per record DIG EQU 2 ; Number of digits to accept ; In track and record assign. ; (Should be set larger for ; Devices having track/ ; Record numbers >99 ; VER EQU 1 ; Program version REV EQU 0 ; Revision ; ; ORG 100H ; ; START: JP DTST ; Enter from CP/M ; ; ; Global variables for use by all routines ; PASS: DEFW 0 ; Current pass ERRORS: DEFW 0 ; Error count for pass ; ; ; The following variables are used by RDBUF and WRTBUF to address the ; disk, and display failing disk addresses. ; DRV: DEFB 0 ; Drive to test TRK: DEFW 0 ; Current track REC: DEFW 0 ; Current record BUFFER: DEFW 0 ; Current memory address IOLEN: DEFW 0 ; Bytes last transferred ; ; ; The following variables define the area to be tested on the selected ; drive. ; TRKF: DEFW 0 ; First track to test TRKL: DEFW 0 ; Last track to test RECF: DEFW 0 ; First record to test RECL: DEFW 0 ; Last record to test ; ; ; The following variables define the test mode ; BYPASS: DEFB 0 ; 0=do not bypass error item. ; 1=bypass error itemization, ; Print total errors per pass. SKEW: DEFB 0 ; 0=no record skew ; 1=use record skew for speed LISDEV: DEFB 0 ; 0=print errors on terminal ; 1=print errors on list dev. LOCKIO: DEFB 0 ; 0=no lock ; 1=lock on read ; 2=lock on write RESTOR: DEFB 0 ; 0=do not restore original ; Data, 1=restore original ; Data on disk LOCKPT: DEFB 0 ; 0=use variable test data ; Pattern, 1=lock on user ; Supplied data pattern. PATTRN: DEFB 0 ; Contains user supplied ; 8 bit data pattern. PASSL: DEFW 0 ; Last pass to do on this test DIGITS: DEFB DIG ; Max. number of digits to be ; Accepted during hex. or dec. ; Numeric input. XTRAN: DEFW RECTRB ; Address of record translate table ; ; ; Disk test --- main control -- entry from CP/M ; DTST: LD DE,DTSTA ; Print program title LD C,PRINT CALL BDOS LD HL,(BDOS+1) LD DE,BUFFEND OR A ; Make sure enough user SBC HL,DE ; Memory to execute test JR NC,DTST01 LD DE,DTSTS ; Not enough memory LD C,PRINT ; Print warning and exit CALL BDOS JP WBOOT ; DTST01: LD C,CPMVER ; Check CP/M version CALL BDOS LD A,L ; Make sure 2.x AND 0F0H CP 20H JR Z,DTST02 LD DE,DTSTZ ; Not CP/M 2.x, print LD C,PRINT ; Error message and quit CALL BDOS JP WBOOT ; DTST02: XOR A ; Initialize variables LD (BYPASS),A LD (SKEW),A LD (LISDEV),A LD (LOCKIO),A LD (RESTOR),A LD (LOCKPT),A LD (PASS),A LD (PASS+1),A LD (ERRORS),A LD (ERRORS+1),A LD DE,DTSTB ; Now set up test configuration CALL GETYN ; Itemize errors? CP 'Y' JR Z,DTST03 ; Yes LD A,1 ; No LD (BYPASS),A JR DTST04 ; Skip query for output device ; DTST03: LD DE,DTSTC ; Audit errors on console or printer CALL GETL CP 'C' JR Z,DTST04 ; C=use console CP 'P' CALL NZ,QUERY JR NZ,DTST03 ; No match, try again LD A,1 ; P=use line printer LD (LISDEV),A ; DTST04: LD DE,DTSTD ; Lock on read or write? CALL GETL CP 'N' ; N=no locks JR Z,DTST06 CP 'R' ; R=lock on read JR NZ,DTST05 LD A,1 LD (LOCKIO),A JR DTST12 ; Bypass queries about restore ; Mode and data pattern, since ; We are locked in read mode ; DTST05: CP 'W' ; W=lock on write CALL NZ,QUERY JR NZ,DTST04 ; No match, try again LD A,2 LD (LOCKIO),A JR DTST08 ; Bypass restore question ; Since we are locked in ; Write mode ; DTST06: LD DE,DTSTE ; Restore user data? CALL GETYN CP 'Y' ; Y=restore JR NZ,DTST08 LD A,1 ; N=do not restore LD (RESTOR),A ; DTST08: LD DE,DTSTF ; Lock on data pattern? CALL GETYN CP 'N' JR Z,DTST12 ; N=use variable pattern LD A,1 ; Y=lock on pattern LD (LOCKPT),A ; Supplied by operator LD DE,DTSTG ; Accept data pattern CALL GETH ; From keyboard LD (PATTRN),A ; DTST12: LD DE,DTSTH ; Select drive to be tested CALL GETL SUB 'A' ; Convert to logical number CP DRVF ; Make sure its legal CALL C,QUERY JR C,DTST12 ; Too small, try again CP DRVL+1 CALL NC,QUERY JR NC,DTST12 ; Too large, try again LD (DRV),A ; Save drive assignment ADD A,'A' ; Also format for output LD (DTSTI1),A LD DE,DTSTI ; Confirm selected drive? CALL GETYN CP 'N' JR Z,DTST12 ; Not confirmed, try again LD HL,TRKFST ; Initialize track limits LD (TRKF),HL LD HL,TRKLST LD (TRKL),HL ; DTST15: LD DE,DTSTJ ; Test all tracks? CALL GETYN CP 'Y' ; Y=use all of them JR Z,DTST20 ; N=user wants to specify ; DTST17: LD DE,DTSTK ; Enter first track to test CALL GETN LD (TRKF),HL ; Save it LD DE,DTSTL ; Enter last track to test CALL GETN LD (TRKL),HL ; Save it LD DE,(TRKF) ; Make sure first OR A ; Track<=last track SBC HL,DE CALL C,QUERY ; Wrong, start again JR C,DTST17 ; DTST20: LD HL,RECFST ; Initialize record limits LD (RECF),HL LD HL,RECLST LD (RECL),HL ; DTST22: LD DE,DTSTM ; Use all records of each track CALL GETYN CP 'Y' ; Y=use all records JR Z,DTST26 ; N=user wants to specify ; DTST24: LD DE,DTSTN ; Enter first record to test CALL GETN LD (RECF),HL ; Save it LD DE,DTSTO ; Enter last record to test CALL GETN LD (RECL),HL ; Save it LD DE,(RECF) ; Make sure first OR A ; Record<=last record SBC HL,DE CALL C,QUERY JR C,DTST24 ; Error, start again ; DTST26: LD DE,DTSTP ; How many test passes CALL GETN ; Should be made? LD (PASSL),HL ; Save # of passes LD DE,DTSTT ; Print advisory message LD C,PRINT ; As test begins CALL BDOS LD DE,DTSTU ; Remind user whether he is LD A,(RESTOR) ; Using restore mode OR A JR Z,DTST32 LD DE,DTSTV ; DTST32: LD C,PRINT CALL BDOS ; DTST40: LD HL,(TRKF) ; Begin a pass LD (TRK),HL ; Initialize current track ; DTST42: LD E,'*' LD C,CONOUT CALL BDOS LD A,(STAR) INC A LD (STAR),A CP 77 JP DTST43 XOR A LD (STAR),A LD DE,DTSTR3 LD C,PRINT CALL BDOS ; DTST43: LD E,0FFH LD C,DIRCON ; Check for interruption CALL BDOS ; From console OR A JP NZ,DTST94 ; Break detected, quit LD A,(RESTOR) OR A ; Is this restore mode? JR Z,DTST45 ; No jump LD HL,BUFF3 ; Yes, save current disk LD DE,MERR1 ; Contents CALL RDBUF ; DTST45: LD A,(LOCKIO) CP 1 ; Is this lock on read? JR Z,DTST47 ; Yes jump LD HL,BUFF1 ; Set up test pattern LD DE,BPT CALL BUFPAT LD HL,BUFF1 ; Write test pattern LD DE,MERR2 CALL WTBUF ; DTST47: LD A,(LOCKIO) CP 2 ; Is this lock on write? JR Z,DTST70 ; Yes, jump LD HL,BUFF2 ; Read back test pattern ; (or just read existing data ; If locked on read) LD DE,MERR3 CALL RDBUF ; DTST50: LD A,(LOCKIO) OR A ; Is this lock on read or write JR NZ,DTST70 ; Yes, jump ; No, compare test data LD HL,BUFF1 ; Written, to data read LD DE,BUFF2 ; Back from disk. If LD BC,MERR4 ; Difference found, CALL BUFCMP ; Print error message ; DTST70: LD A,(RESTOR) OR A ; Using restore mode? JR Z,DTST80 ; No, jump ; Yes, write back user's data LD HL,BUFF3 LD DE,MERR6 CALL WTBUF LD HL,BUFF1 ; Verify that LD DE,MERR7 ; It was rewritten OK CALL RDBUF LD HL,BUFF1 LD DE,BUFF3 LD BC,MERR5 ; Check restored data CALL BUFCMP ; If difference found, print ; 'data cannot be restored' ; DTST80: LD DE,(TRK) ; Advance current track INC DE LD (TRK),DE LD HL,(TRKL) OR A ; Done with all tracks? SBC HL,DE JP NC,DTST42 ; No, process another ; DTST90: LD BC,(PASS) ; End of pass INC BC ; Count passes LD (PASS),BC LD HL,DTSTR1 CALL CONV ; Convert pass # LD BC,(ERRORS) LD HL,DTSTR2 CALL CONV ; Convert error count LD DE,DTSTR ; Print pass and errors LD C,PRINT ; On console CALL BDOS LD A,(LISDEV) ; Also using printer? OR A JR Z,DTST92 ; No, jump ; Yes, also send pass and error ; Count to printer LD HL,DTSTR CALL PERR9 ; DTST92: XOR A ; Reset error count LD (ERRORS),A LD (ERRORS+1),A LD HL,(PASS) LD DE,(PASSL) OR A ; Are enough passes done? SBC HL,DE JP C,DTST40 ; Not yet, loop done with all passes ; DTST94: LD DE,DTSTW ; Ask whether to exit CALL GETL ; Or to continue test CP 'Y' ; C=continue JP Z,DTST CP 'N' ; E=exit JR NZ,DTST94 ; If no match, try again LD DE,DTSTX ; Print goodbye LD C,PRINT CALL BDOS ; And return control JP WBOOT ; To CP/M ;..... ; ; ; Routines to read and write up to one track - read current track from ; RECF to RECL. Call HL=buffer base address, DE=error message address ; RDBUF: LD (RDBUFA),DE ; Save message address LD (BUFFER),HL ; Save buffer address LD HL,0 ; Initialize transfer byte LD (IOLEN),HL ; Count CALL SELDSK ; Select disk LD HL,(RECF) LD (REC),HL ; Initialize current record ; RDBUF1: CALL SETIO ; Setup track, record, memory CALL READ ; Now request transfer OR A ; Was I/O successful? JR Z,RDBUF2 ; No error, jump LD DE,(RDBUFA) CALL PERR ; I/O error, audit it ; RDBUF2: CALL RWADV ; Advance record address JR NC,RDBUF1 ; Not done, read another RET ; Back to caller ;..... ; ; RDBUFA: DEFW 0 ; Address of error message ; ; Write current track from RECF to RECL. Call DE=error message address ; HL=buffer base address. ; WTBUF: LD (WTBUFA),DE ; Save message address LD (BUFFER),HL ; Save memory address LD HL,0 ; Initialize transfer LD (IOLEN),HL ; Byte count CALL SELDSK ; Select disk drive LD HL,(RECF) LD (REC),HL ; Initialize current record ; WTBUF1: CALL SETIO ; Set track, record, memory CALL WRITE ; Request disk write OR A ; Any I/O errors? JR Z,WTBUF2 ; No, jump LD DE,(WTBUFA) CALL PERR ; Error, audit it ; WTBUF2: CALL RWADV ; Advance record address JR NC,WTBUF1 ; Not done, write another RET ; Back to caller ;..... ; ; WTBUFA EQU RDBUFA ; Save address of error message ; ; Advance record and memory addr RWADV: LD DE,BPR ; De<--bytes per record LD HL,(BUFFER) ADD HL,DE ; Update buffer address LD (BUFFER),HL LD HL,(IOLEN) ADD HL,DE ; Count bytes transferred LD (IOLEN),HL LD DE,(REC) ; Advance current record INC DE LD (REC),DE LD HL,(RECL) OR A ; Done with all records? SBC HL,DE ; Exit with carry set if done RET ;..... ; ; ; Set up buffer with test pattern ; ; Call hl=buffer base address ; De=byte length to set up BUFPAT: LD A,(LOCKPT) OR A ; Are we locked on user specified ; Data pattern? JR NZ,BUFPA2 ; Yes, jump ; BUFPA1: LD A,R ; Read refresh register XOR H ADD A,L ; Make data a function of memory ; Address LD (HL),A ; And store it INC HL ; Advance buffer address DEC DE ; Count bytes stored LD A,D ; Done yet? OR E JR NZ,BUFPA1 ; No, loop RET ;..... ; ; BUFPA2: LD A,(PATTRN) ; User specified parrern LD (HL),A ; Store one byte INC HL ; Advance buffer pointer DEC DE ; Count bytes stored LD A,D ; Done yet? OR E JR NZ,BUFPA2 ; Not done, loop RET ; Exit ;..... ; ; ;Compare specified buffer and print error message if difference found ; ; Call BC=error message address ; DE=1st buffer addr ; Hl=2nd buffer addr BUFCMP: LD (BUFCMA),BC ; Save message addr LD (BUFCMB),HL ; Save base of buffer LD BC,(IOLEN) ; Length to compare ; BUFCM1: LD A,(DE) ; Fetch byte from 1st buffer CP (HL) ; Compare it to 2nd buffer JR NZ,BUFCM3 ; Difference found, jump ; BUFCM2: INC HL ; Advance buffer addresses INC DE DEC BC ; Count bytes LD A,B ; Done yet? OR C JR NZ,BUFCM1 ; No, loop RET ; Back to caller ;..... ; ; ; Difference found, print ; Error audit trail BUFCM3: PUSH BC ; First save registers PUSH DE PUSH HL LD DE,(BUFCMB) OR A SBC HL,DE ; Find a buffer offset PUSH HL ; Now divide by bytes per POP BC ; Record to find relative LD DE,BPR ; Record number CALL DIV LD HL,(RECF) ADD HL,BC ; Add relative record to first ; Record to find actual ; Address for use by PERR LD (REC),HL LD DE,(BUFCMA) CALL PERR ; Now audit error POP HL ; Restore registers POP DE POP BC ; Advance memory address out of this ; Record where an error was found ; BUFCM4: INC HL ; Bump buffer addresses INC DE DEC BC ; Done with all data area? LD A,B OR C RET Z ; Yes, exit compare routine LD A,L ; Check if on new record AND BPR-1 ; Boundary JR Z,BUFCM1 ; Found it, go compare more data JR BUFCM4 ; Keep adv until record boundary ; BUFCMA: DEFW 0 ; Address of error message BUFCMB: DEFW 0 ; Base buffer addresses ;..... ; ; ; Error printing routine, prints pass, drive, track, record and message ; specified by caller on the console device. ; ; Call DE=error message address PERR: LD A,(BYPASS) OR A ; Is error itemization bypass set JR NZ,PERR2 ; Yes, skip printing and go count LD (PERRA),DE ; Save message address LD BC,(PASS) INC BC LD HL,PERRC ; Convert current pass CALL CONV LD A,(DRV) ; Form drive name ADD A,'A' LD (PERRD),A LD BC,(TRK) ; Convert current track LD HL,PERRE CALL CONV LD BC,(REC) ; Convert current record LD A,(SKEW) ; Is skew in effect? OR A JR Z,PERR0 ; No CALL RECTRAN ; Yes, translate record ; PERR0: LD HL,PERRF CALL CONV LD A,(LISDEV) ; Should output be on OR A ; Console or printer? JR NZ,PERR3 ; Jump, use printer, fall thru LD HL,(ERRORS) ; Use console LD A,H ; Is this the first error? OR L JR NZ,PERR1 ; No, jump LD DE,DTSTQ ; Print title for errors LD C,PRINT CALL BDOS ; PERR1: LD DE,PERRB ; Print disk address LD C,PRINT CALL BDOS LD DE,(PERRA) ; Print error type LD C,PRINT CALL BDOS ; PERR2: LD HL,(ERRORS) ; Count errors INC HL LD (ERRORS),HL RET ; Back to caller ;..... ; ; PERR3: LD HL,(ERRORS) ; Errors to printer LD A,H ; Is this 1st error to be OR L ; Printed this pass? JR NZ,PERR4 ; No, jump LD HL,DTSTQ ; Yes, print title CALL PERR9 ; PERR4: LD HL,PERRB ; Print disk address CALL PERR9 LD HL,(PERRA) CALL PERR9 ; Print error type JR PERR2 ; Go count errors ; Send a string terminated by ; '$' to list device ; PERR9: LD A,(HL) ; Fetch next character CP '$' ; Is it terminator? RET Z ; Yes, exit PUSH HL ; Save string address LD E,A ; Send this character LD C,LIST CALL BDOS POP HL ; Restore string address INC HL ; And increment it JR PERR9 ; Check next character ; PERRA: DEFW 0 ; Addrs of msg describing error PERRB: DEFB CR,LF PERRC: DEFB 'nnnn ' ; Pass # PERRD: DEFB 'n ' ; Drive PERRE: DEFB 'nnnn ' ; Track PERRF: DEFB 'nnnn $' ; Record ; ; ; Disk interface to CP/M BIOS ; SELDSK: LD A,(DRV) ; Select disk drive LD C,A LD DE,24 ; ; This routine links to the JPBIOS: LD HL,(WBOOT+1) ; Desired routine through ADD HL,DE ; The standard CP/M JP (HL) ; BIOS jump table ; SETTRK: LD BC,(TRK) ; Select track LD DE,27 JR JPBIOS ; SETREC: LD BC,(REC) ; Select record LD DE,30 LD A,(SKEW) ; Use record skew? OR A JR Z,JPBIOS ; No CALL RECTRAN ; Translate record addr JR JPBIOS ; SETDMA: LD BC,(BUFFER) ; Set memory addr LD DE,33 JR JPBIOS ; SETIO: CALL SETTRK ; Set up track, record, CALL SETREC ; And memory address CALL SETDMA ; For subsequent read RET ; Or write ;..... ; ; READ: LD DE,36 ; Read one disk record JR JPBIOS ; WRITE: LD DE,39 ; Write one disk record JR JPBIOS ; Translate logical to physical ; Call BC=logical record ; HL=physical record ; RECTRAN:PUSH HL LD HL,RECTRB-1 ADD HL,BC LD C,(HL) POP HL RET ;..... ; ; ; Utility and console input routines ; ; Get Y or N response from operator ; Call DE= address of cue ; A=Y or N GETYN: PUSH DE ; Save cue address LD C,PRINT ; Print cue message CALL BDOS LD DE,GETYNA ; Print possible answers LD C,PRINT CALL BDOS CALL GETCHR ; Get a character from console POP DE ; Restore cue address ; In case needed again CP 'Y' ; Make sure response is OK RET Z ; Exit if yes CP 'N' RET Z ; Exit if no ; PUSH DE CALL QUERY ; Print '?' if not POP DE ; Y or N, try again JR GETYN ; GETYNA: DEFB '(Y/N) ',TAB,'> $' ; ; Get any response from operator ; Call DE=cue address ; A=ASCII character GETL: LD C,PRINT ; Print cue message CALL BDOS LD DE,GETLA ; Tab and print LD C,PRINT ; Cue mark CALL BDOS CALL GETCHR ; Read console RET ;..... ; ; GETLA: DEFB TAB,'> $' ; ; Get a decimal # from the console ; Call DE=cue address ; Return HL=number GETN: PUSH DE ; Save cue message address LD C,PRINT CALL BDOS ; Print cue message LD DE,GETNA ; Print tab and cue mark LD C,PRINT CALL BDOS LD HL,0 ; Initialize forming answer LD A,(DIGITS) LD B,A ; Total chars allowed to be input ; GETN1: PUSH HL ; Save answer PUSH BC ; Save character count CALL GETCHR ; Read console POP BC ; Restore char count POP HL ; Restore forming answer CP CR ; Is this return? JR Z,GETN9 ; Yes, exit with answer CP '0' ; Is this legal character? JR C,GETN3 ; No, jump CP '9'+1 ; Is this legal character? JR NC,GETN3 ; No, jump AND 0FH ; Isolate bottom 4 bits PUSH HL ; Previous data * 10 POP DE ADD HL,HL ; *2 ADD HL,HL ; *4 ADD HL,DE ; *5 ADD HL,HL ; *10 LD E,A ; Now add in this digit LD D,0 ADD HL,DE DJNZ GETN1 ; Count characters accepted JR GETN9 ; Enough accepted, exit ; Illegal character detected GETN3: CALL QUERY ; Print '?' and POP DE ; Restart input JR GETN ; Input complete, clean GETN9: POP DE ; Stack and exit with RET ; Answer in (HL) ;..... ; ; GETNA: DEFB TAB,'> $' GETNB: DEFB '?$' ; ; Get $dig hex digits from kbd ; Call DE=cue address ; Return a=lower 8 bits of # ; HL=entire 16 bit # GETH: PUSH DE ; Save cue address LD C,PRINT CALL BDOS ; Print cue message LD DE,GETHA ; Print tab and cue mark LD C,PRINT CALL BDOS LD HL,0 ; Initialize forming answer LD A,(DIGITS) LD B,A ; Max digits to accept ; GETH1: PUSH BC ; Save registers PUSH HL CALL GETCHR ; Read console POP HL POP BC ; Restore registers CP CR ; If exit JR Z,GETH25 CP '0' ; Make sure its legal JR C,GETH3 ; No, jump CP '9'+1 ; If alpha fold to JR C,GETH15 ; Lowercase ; GETH15: CP 'F'+1 ; Make sure its legal JR NC,GETH3 ; No, jump CP 'A' ; Check if alpha JR C,GETH2 ; Jump if 0-9 ADD A,9 ; Add correction ; GETH2: AND 0FH ADD HL,HL ; Previous data *16 ADD HL,HL ; (Left shift 4 bits) ADD HL,HL ADD HL,HL ADD A,L ; Add this char to it LD L,A ; Forming result DJNZ GETH1 ; Keep reading console ; GETH25: POP DE ; Clean up stack LD A,L ; Put lower 8 bits of answer RET ; In 'A'. (incase exit by ) ;..... ; ; GETH3: CALL QUERY ; Print '?' POP DE ; Then restart input JR GETH ; GETHA: DEFB TAB,'> $' ; QUERY: PUSH AF ; Save flags LD DE,QUERYA LD C,PRINT ; Print '?' CALL BDOS POP AF ; Restore flags RET ;..... ; ; QUERYA: DEFB ' ?$' ; ; Get 1 character from console via ; Raw input mode, do not echo GETCHR: LD E,0FFH LD C,DIRCON CALL BDOS ; Read console OR A ; Anything there? JR Z,GETCHR ; No, try again CP 'C'-40H ; CTL-C to abort? JP Z,CTLC CP CR ; Is it ? RET Z ; Yes, finished ; CP 97 JR C,GETCH1 CP 123 JR NC,GETCH1 AND 5FH ; Put character in upper-case if needed ; GETCH1: PUSH AF ; No, echo it LD E,A LD C,DIRCON ; Display character just received CALL BDOS POP AF ; Restore 'A' and exit RET ;..... ; ; CTLC: POP HL LD DE,QUERYA LD C,PRINT CALL BDOS JP WBOOT ; ABRT: DEFB CR,LF,CR,LF,'++ ABORTING ++',CR,LF,CR,LF,'$' ;..... ; ; ; Convert binary to decimal ASCII ; Call BC=binary, in range 0000-9999 ; HL=first byte addr to store CONV: LD DE,1000 CALL DIV CALL CONV9 ; Thousands digit LD DE,100 CALL DIV CALL CONV9 ; Hundreds digit LD DE,10 CALL DIV CALL CONV9 ; Tens digit CALL CONV9 ; Units RET ; Back to caller ;..... ; ; CONV9: LD A,C ; Turn quotient into ADD A,'0' ; ASCII char and LD (HL),A ; Store it INC HL ; Bump output pointer PUSH DE ; Bc<--remainder POP BC RET ;..... ; ; ; Single precision divide ; Call bC=numerator ; DE=divisor ; Return BC=quotient ; DE=remainder DIV: PUSH HL LD HL,0 OR A SBC HL,DE EX DE,HL LD HL,0 LD A,17 ; DIV0: PUSH HL ADD HL,DE JR NC,DIV1 EX (SP),HL ; DIV1: POP HL PUSH AF RL C RL B RL L RL H POP AF DEC A JR NZ,DIV0 OR A RR H RR L EX DE,HL POP HL RET ;..... ; ; ; Data area ; RECTRB: DEFB 1,7,13,19,25 ; Table built DEFB 5,11,17,23 ; With skew DEFB 3,9,15,21 ; Factor = 6 DEFB 2,8,14,20,26 ; 128 byte record DEFB 6,12,18,24 DEFB 4,10,16,22 STAR: DEFB 0 ; ; ; Messages for test initialization and error printing ; DTSTA: DEFB CR,LF,LF,'Z-80 Floppy Disk Test version ' DEFB VER+'0','.',REV+'0',CR,LF,'$' DTSTB: DEFB CR,LF,'Itemize errors? ','$' DTSTC: DEFB CR,LF,'Use console or printer? (C/P) ','$' DTSTD: DEFB CR,LF,'Lock on read or write? (N/R/W) ','$' DTSTE: DEFB CR,LF,'Restore original data? ','$' DTSTF: DEFB CR,LF,'Lock on data pattern? ','$' DTSTG: DEFB CR,LF,'Enter data pattern, hex 00-FF','$' DTSTH: DEFB CR,LF,'Drive to be tested ' DEFB '(',DRVF+'A','-',DRVL+'A',') ','$' DTSTI: DEFB CR,LF,'Confirm: test drive ' DTSTI1: DEFB 'X ? $' DTSTJ: DEFB CR,LF,'Test all tracks? ','$' DTSTK: DEFB CR,LF,'First track to test ','$' DTSTL: DEFB CR,LF,'Last track to test ','$' DTSTM: DEFB CR,LF,'Test all records? ','$' DTSTN: DEFB CR,LF,'First record to test ','$' DTSTO: DEFB CR,LF,'Last record to test ','$' DTSTP: DEFB CR,LF,'How many test passes? ','$' DTSTQ: DEFB CR,LF,LF,'Pass Drive Track Sector ' DEFB 'Error-type',CR,LF,'$' DTSTR: DEFB CR,LF,LF,'Pass ' DTSTR1: DEFB 'nnnn complete, ' DTSTR2: DEFB 'nnnn errors.' DTSTR3: DEFB CR,LF,'$' DTSTS: DEFB CR,LF,'Not enough memory to execute.',CR,LF,'$' DTSTT: DEFB CR,LF,LF,'Beginning disk test - push any key ' DEFB 'to abort program. ',CR,LF,'$' DTSTU: DEFB 'WARNING: user data will not be restored. ' DEFB CR,LF,'$' DTSTV: DEFB 'User data will be restored. ',CR,LF,'$' DTSTW: DEFB CR,LF,'Continue test (Y/N)','$' DTSTX: DEFB CR,LF,LF,'Goodbye. ',CR,LF,'$' DTSTY: DEFB CR,LF,'Use record skew? $' DTSTZ: DEFB CR,LF,'Need CP/M 2.x to execute. ',CR,LF,'$' MERR1: DEFB 'read error - original data','$' MERR2: DEFB 'write error - test pattern','$' MERR3: DEFB 'read error - test pattern','$' MERR4: DEFB 'compare error - test pattern','$' MERR5: DEFB 'original data cannot be restored','$' MERR6: DEFB 'write error - restore phase','$' MERR7: DEFB 'read error - restore phase','$' ; ; BUFF1 EQU 1000H ; Disk buffers BUFF2 EQU BPT*2+BUFF1 BUFF3 EQU BPT*2+BUFF2 BUFFEND EQU BPT*2+BUFF3 ;..... ; ; END