TITLE "Z-System CD-ROM Support Utility" ;****************************************************************** ; CDZSWP ; ACCESS CD-ROM FILES FROM A Z-SYSTEM (CP/M) ; Adapted from CD Sweep (c), V1.3, 1996 by Duncan Elvin ; (with permission, 19 Sept 1997) ; Harold F. Bower ; ; This program was manually converted from the original C program ; (Hi-Tec) into Z80 Assembly and adapted for Z-System operation with ; screen attributes and other user features. ; ; CDZSWP allows you to: ; Display CD-ROM directory information ; Copy a File from CD-ROM to another supported drive ; List a file to the Console ; Load/Unload Disc (if overlay and drive both support it) ; ; The program is written for assembly with ZMAC or compatible assembly ; tools. See the DOC file for additional details on assembly, linkage, ; and options for selecting drivers. ; ; Harold F. Bower ; ; 1.0 - 15 Oct 97 - Fixed error in last file limit on screen. HFB ; 0.6 - 13 Oct 97 - Cleanup, Initial Release. HFB ; 0.0 - 31 Aug 97 - Initial version HFB ;****************************************************************** VER EQU 10 DATE MACRO DEFB '15 Oct 97' ENDM EXTRN PA2HC, PAFDC, PHLDC, PHLFDC, INLINE, CIN, PFN2 ; from SYSLIB EXTRN CODEND, CRLF, COUT, CAPIN, RETUD, LOGUD, SETDMA EXTRN F$EXIST, F$DELETE, F$MAKE, F$WRITE, F$CLOSE EXTRN F$OPEN, F$READ, CAPSTR EXTRN WHRENV, GETQUIET, GETNAME, PRTNAME, ZPRSFN ; from Z3LIB EXTRN Z3LOG, WAIT1S EXTRN Z3VINIT, VPRINT, VPSTR, GXYMSG, GotoXY, EREOL ; from VLIB EXTRN CLS, CLREOS, TINIT, DINIT, STNDOUT, STNDEND EXTRN TIMINI, PSTAMP ; from DSLIB BELL EQU 07H BS EQU 08H TAB EQU 09H LF EQU 0AH CR EQU 0DH CTRLC EQU 'C'-'@' ; Next Screen CTRLE EQU 'E'-'@' ; Prev Line CTRLF EQU 'F'-'@' ; Find Filespec CTRLL EQU 'L'-'@' ; Find Next Filespec CTRLR EQU 'R'-'@' ; Prev Screen CTRLX EQU 'X'-'@' ; Next Line BDOS EQU 5 FCB EQU 005CH ; Default CP/M File Control Block TBUFF EQU 0080H ; --- Constants for CD-ROM access --- CD_SECS EQU 60 ; Seconds per Minute (MSF addressing) CD_FRAMES EQU 75 ; Frames per Second (MSF addressing) CD_BLKOFF EQU 150 ; Offset of first logical frame (MSF addressing) PVD_LBA EQU 16 ; Primary Volume Description (2048-byte blks) ROOT_OFS EQU 156 ; Offset of Root Directory in PVD DIR_FLG EQU 00000010B ; Byte/Bit value of Directory entry ; Structure of iso9660 Directory entry on CD-ROM (offsets of entries) LEN_DIR EQU 0 ; Byte - Length of this dir entry XAR_LEN EQU 1 ; Byte - ? START EQU 2 ; DWord- Starting Block # (based on 2k Blks) STARTM EQU 6 ; DWord- (same but Big-Endian) LENGTH EQU 10 ; DWord- Length of target in bytes LENGTHM EQU 14 ; DWord- (same but Big-Endian) YR EQU 18 ; Byte - Year (0..99 in binary) MN EQU 19 ; Byte - Month (1..12 in binary) DY EQU 20 ; Byte - Day (1..31 in binary) HR EQU 21 ; Byte - Hour (0..23 in binary) MIN EQU 22 ; Byte - Minute (0..59 in binary) SEC EQU 23 ; Byte - Second (0..59 in binary) OSET EQU 24 ; Byte - ? (High-Sierra Flags?) FLAGS EQU 25 ; Byte - x x x x x x x x ; | | | | | | | +- 1=Sub Directory ; | | | | | | +--- 1=Dir entry ILSIZE EQU 26 ; Byte - ? ILSKIP EQU 27 ; Byte - ? VSSNI EQU 28 ; Word - ? VSSNM EQU 30 ; Word - ? LEN_NAM EQU 32 ; Byte - Length of following name NAME EQU 33 ; Array[32]- Name, variable length. First char ; has special significance as: ; 0b = This Directory (".") ; 1b = Parent Directory ("..") ; Entries are catenated and range from 31 (21H) to 65 (41H) bytes in length ; Portions of these entries are used in a memory-resident array as: ; ; start offset 0 ; DWord ; length offset 4 ; DWord ; yr offset 8 ; Byte ; mn offset 9 ; Byte ; dy offset 10 ; Byte ; hr offset 11 ; Byte ; min offset 12 ; Byte ; flags offset 13 ; Byte ; name offset 14 ; Array[13] - Null-terminated string E_SIZE EQU 27 ; Size of each Directory Entry E_LEN EQU 4 ; Offset to Length field E_YR EQU 8 ; Offset to Year field E_DY EQU 10 ; Offset to Day field E_FLAG EQU 13 ; Offset to flags byte E_NAME EQU 14 ; Offset to name string MAX_NAM EQU 13 ; Constant for name length checks ; Constants for VLIB Screen Display. ; Line 1 (top) = Banner, Line 2 = Current Path, Lines 3/4 = Blank ROWOFF EQU 4 ; Offset of Row # to first File ; Last Line - 1 = Blank (used for String prompts) ; Last Line = Brief command Line Help/prompt ;================ P r o g r a m S t a r t s H e r e ================== Enter: JP Begin DEFB 'Z3ENV' DEFB 1 envadr: DEFW 0 ; Address of z3 environment DEFW Enter ; (Type 4 filler) DEFB 'CDZSWP ',0 ; Configuration Overlay name usEur: DEFB 0FFH ; US (0FFH) or European (0) Date Display Form drvDU: DEFB 1 ; Default .DRV User DEFB 'A'-'A' ; Default .DRV Drive drvNam: DEFB 'CDZSWP DRV' ; Default Driver name.typ Begin: LD HL,(BDOS) ; Get Base of BDOS (or RSX) CALL WHRENV ; ..and locate any Z3 Environment LD (envadr),HL ; Save in the header CALL Z3VINIT ; Initialize the library routines CALL TINIT ; then Terminal CALL TIMINI ; and Date/Time Stamping routines CALL GETNAME ; Retrieve name by which invoked CALL RETUD ; Get Entry Drive/User LD (entrDU),BC ; (save) CALL GETQUIET JR NZ,Begin1 ; Skip print if quiet CALL Banner Begin1: LD (stack),SP ; Set up a local stack LD SP,stack LD HL,(envadr) ; Pt to ENV LD DE,31H ; Offset to Screen Geometry ADD HL,DE LD A,(HL) ; Get # Columns LD (ncols),A ; store INC HL LD A,(HL) ; # Lines LD (nrows),A ; store CALL CODEND ; Get beginning of Unused RAM LD (datPtr),HL ; save for local use JP Begin0 ; ..continue initializing after the Overlay HDRSIZ EQU $-Enter DEFS 80H-HDRSIZ ; Pad up to 180H where Overlay starts ;====================================================================== ; Overlay Section. The raw CD-ROM Driver is read into this location ; (or overlayed directly) to provide a "generic" method of accomodating ; different physical drive interfaces. A set of dummy hooks begin the ; code which are overwritten if a driver is loaded. ;---------------------------------------------------------------------- oStart: DW 0 ; Size (in Bytes) of installed Overlay ; (0 = No Overlay Installed) DB 0 ; Overlay Version # OvlStr: JP RetID ; Return Overlay ID String Addr OvlIni: JP RetID ; Initialize Subsystem/Drive OvlRd: JP RetID ; Read a 2k Block from CD to Buffer OvlEj: JP RetID ; Spin-down disc and Eject Tray/Caddy OvlLod: JP RetID ; Load Tray/Caddy and Spin Up Disc JP $-$ ; JP $-$ ; JP $-$ ; idStr: DEFB 'CDZSWP.OVL',0 ; <<-- Mandatory Validation String -->> RetID: LD HL,DummID ; Pt to Dummy ID String SCF ; signal Error RET ; exit DummID: DEFB BELL,CR,LF,'--- No Overlay Installed ---',CR,LF,0 OLEN EQU $-oStart ; Get actual length of Overlay DEFS 2048-OLEN ; reserve space up to 2k limit ;=================== End of Reserved Overlay Space ==================== ; Continue with initialization, insuring an overlay is installed Begin0: LD A,(FCB+1) ; Get first char of first FCB CP '/' ; Is help requested? JP Z,Help ; ..jump to print help and exit if so CALL LdOvly ; Check for Overlay presence, load if needed JR C,BeginX ; ..print Error message and exit if Bad CALL VPRINT DEFB ' Using >>> ',0 CALL ovlStr ; Get Identifying string from the overlay CALL VPSTR ; display it CALL CRLF ; move to new line LD HL,bufr ; Get Buffer address for Overlay CALL OvlIni ; Initialize System/Drive/Subsystem JR C,BegnEr ; ..jump to error exit if bad CALL VPRINT DEFB ' Drive = ',0 CALL VPSTR ; Else print drive type CALL CRLF JR Main ; ..continue w/Main BegnEr: CALL VPSTR ; print returned Error CALL VPRINT ; Else Say why on new line DB CR,LF,'++ Initialization Error ',0 BeginX: CALL VPRINT DEFB '..aborting..',CR,LF,0 JP Finis ; and Quit ;---------------------------------------------------------------------; ;--- Main routine from CD Sweep (c) D.Elvin, Assembly by H.F.Bower ---; ;---------------------------------------------------------------------; ;void main() ;{ ; strcpy(path, ""); /* initial path */ Main: CALL VPSTR XOR A ; Clear initial path LD (path),A ; if(!read_cd(PVD_LBA, buff)) { /* read PVD */ ; puts("Error reading CD drive"); ; exit(-1); ; } LD BC,0000 ; Primary Vol Descriptor has fixed LBA # LD DE,PVD_LBA ; load up as needed for Read CALL OvlRd ; Try to Read into Buffer JR NC,Main0 ; ..jump if Ok CALL VPSTR ; Else Print returned Error Message FinErr: CALL VPRINT DEFB '..aborting..',0 ;..fall thru to GP Exit code.. Finis: CALL CRLF CALL DINIT ; De-Initialize Display LD BC,(entrDU) CALL LOGUD ; log back into entry Drive/User LD SP,(stack) ; Restore Entry Stack Pointer RET ; ..and back to Command Processor ; if(strncmp("CD001", (char *)&buff[1], 5)) { /* check valid PVD */ ; puts("Invalid format CD"); ; exit(-1); ; } pvdID: DEFB 'CD001' LENPVD EQU $-pvdID Main0: LD HL,bufr+1 ; Set up for string comparison LD DE,pvdID LD B,LENPVD Main0L: LD A,(DE) ; Get a char CP (HL) ; Match? INC HL ; (bump ptrs) INC DE JR NZ,Main0X ; ..quit if Not DJNZ Main0L ; ..else loop til finished Main0X: JR Z,Main1 ; Continue if ID String matches CALL VPRINT DEFB CR,LF,'Invalid format CD',0 JR Finis ; e = (iso9660 *)(buff + ROOT_OFS); /* find root dir entry */ ; iso_media = (e->flags) & DIR_FLG; /* detect iso9660 media */ ; printf("Media type: %s\n", iso_media ? "ISO9660" : "High Sierra"); Main1: LD DE,bufr+ROOT_OFS ; Use DE for ptr to e LD HL,FLAGS ADD HL,DE ; offset to e->flags LD A,(HL) ; fetch AND DIR_FLG ; mask LD (iso_md),A ; save PUSH AF CALL VPRINT DEFB ' Media type: ',0 POP AF JR NZ,Main1A ; ..jump if ISO CALL VPRINT DEFB 'High Sierra',CR,LF,0 JR Main1B Main1A: CALL VPRINT DEFB 'ISO9660',CR,LF,0 ; entry[0].start = e->start; /* copy strt/len */ ; entry[0].length = e->length; Main1B: PUSH DE ; Save ptr to e.ofs CALL CODEND ; Get ptr to entry array LD (entry),HL ; (save in global ptr) POP DE EX DE,HL ; Set so DE -> entry[0], HL -> e.OFS INC HL INC HL ; advance e to pt to e->start LD BC,4 LDIR ; copy start address LD BC,4 ADD HL,BC ; skip startm LDIR ; copy len ; read_file(entry, NULL, MEM); /* read root dir */ ; n = 0; /* start with first entry */ LD HL,(entry) ; Pt to first entry in array CALL Rd_Fil JR NC,Main1C ; ..jump if No Errors CALL CRLF ; Else move to next line CALL VPSTR ; Print Message JP FinErr ; ..and Exit with Error message Main1C: CALL WAIT1S ; Pause a couple of seconds CALL WAIT1S ; to see messages LD A,(nrows) SUB 6 LD (shown),A ; Save number of entries we can see at once ; /* main loop */ ; do { ; if(!n) /* disp path & # entrys if top of dir */ ; printf("\nCurrent Path=%s : %d Files\n", ; strlen(path) ? path : "\\", entrys+1); ;---- Main Loop when new directory is logged in ---- Main00: LD HL,1 ; Start here, skip "This Dir" (entry 0) ;--- Main Loop entry when Re-Loading additional Page during Page Fwd/Back --- MLoopR: LD (firstn),HL ; First Entry is 0 LD (nn),HL ; Current entry is 0 XOR A LD (current),A ; Current relative Display is 0 MRstor: CALL Banner ; Clear Screen, Home Cursor and Print Banner CALL VPRINT DEFB ' Current Path = ',0 LD HL,path LD A,(HL) OR A ; Null string for path? JR NZ,Main01 ; ..jump if Not LD HL,rtDir ; Else point to Root Dir String Main01: CALL STNDOUT CALL VPSTR CALL STNDEND CALL VPRINT DEFB ' : ',0 LD HL,(entrys) ; Get # Entries (omit entry 0) CALL PHLFDC ; print in decimal CALL VPRINT DEFB ' Files',0 ; Compute Total number of (remaining) entries in Dir LD DE,(firstn) ; Get first entry # LD HL,(entrys) ; #Entries-1 LD A,H OR L ; Any files to display? JR Z,MLoop ; ..jump if No INC HL ; (make = #Entries) OR A SBC HL,DE LD A,(shown) LD C,A LD B,0 ; Set # we can display at once INC H DEC H ; > 255 entries? JR NZ,Mn00A ; ..jump if Yes to use "shown" incr CP L ; Remaining > "shown"? JR NC,Mn00B ; ..jump if No to use remaining incr Mn00A: LD H,B ; Else Move "shown" LD L,C ; in position to offset start# Mn00B: LD B,L ; Get # entries to display (for counting) PUSH AF ; (save for later) ADD HL,DE ; Add # Entries to display to starting entry# LD (lastn),HL ; save last displayed entry LD HL,ROWOFF*256+4 ; Start at Row Offset, Col 4 Mn0L: PUSH BC PUSH DE PUSH HL CALL GotoXY CALL GEnt_N ; compute entry[n] in HL (preserve DE) CALL Pr_Ent ; and print it POP HL INC H ; move down a line CALL GotoXY POP DE INC DE POP BC DJNZ Mn0L ; ..loop til all displayed CALL CLREOS ; then clear rest of Screen CALL Select ; Visually mark the Current File ; switch(c = getch()) { MLoop: CALL P_LinX ; Position Cursor at next-to-last line CALL VPRINT ; LF goes to last line DEFB LF,'Up=^E, Dn=^X, NxtPg=^C, PrvPg=^R, Exit=X, Help=? : ',0 CALL EREOL CALL CAPIN ; Get Char from console, no echo ; Command dispatcher. All Command Functions Jump to respective return points. ; I know this is ugly, but the different functions have different needs, and ; this aggregation of spaghetti does it efficiently. CP CR JR Z,CmdL ; Log (Open) Directory CP 'H' JP Z,CmdH ; Make Home location (first entry) current CP CTRLF JP Z,Cmd_F ; Find First file in current Directory CP CTRLL JP Z,Cmd_L ; Find Next file in current Directory CP 'C' JP Z,CmdC ; Copy file from CD-ROM to CP/M File CP CTRLX JP Z,Cmd_X ; Move Cursor down to next entry (w/wrap) CP CTRLE JP Z,Cmd_E ; Move Cursor Up to previous entry (w/wrap) CP CTRLR JP Z,Cmd_R ; Display previous Screen of names (Page Back) CP CTRLC JP Z,Cmd_C ; Display next Screen of names (Page Forward) CP 'V' JP Z,CmdV ; View (Type) a Text File on the Screen CP '+' JP Z,CmdLod ; Load Tray/Caddy and Spinup CP '-' JP Z,CmdUnL ; Spindown and Eject Tray/Caddy CP '.' JR Z,CmdPer ; Log into Parent Directory CP '?' JP Z,CmdQ ; Display more detailed Help of commands CP 'X' ; Exit Command? JP Z,Finis ; ..exit if Yes LD A,BELL CALL COUT ; Else bad command, so beep JP MLoop ; ..and do nothing rtDir: DEFB '\\',0 ; Root Directory string ;================================================================= ; C O M M A N D F U N C T I O N S ;================================================================= ; Log into (Open) Parent directory of Current CmdPer: LD HL,1 ; Set Index to Parent LD (nn),HL ;..fall thru to Log In.. ;--------------- ; Log into (Open) a Directory and make it current on the screen CmdL: XOR A LD (srchBf),A ; Clear any previous search Buffer LD DE,(nn) ; Get Index CALL GEnt_N ; compute Entry address EX DE,HL ; put in DE LD HL,E_FLAG ADD HL,DE ; Pt to flags BIT 1,(HL) ; Directory? JR NZ,CmdL0 ; ..jump if Yes LD A,BELL CALL COUT ; Else Beep JP MLoop ; ..and back to prompt ; if(entry[n].name[1] == '.') { /* if going up a level.. */ CmdL0: LD HL,E_NAME+1 ADD HL,DE ; Pt to name[1] LD A,(HL) CP '.' ; Going up a level? JR NZ,CmdL4 ; if((s = strrchr(path, '\\')) != 0 /* strip dir from path */ ; s[0] = '\0'; ; } LD HL,path LD B,0 ; Init cc Fend: LD A,(HL) ; find end of string OR A ; End? JR Z,CmdL1 ; ..exit if Yes INC B INC HL JR Fend ; Else loop CmdL1: DEC HL ; else back up FendS: LD A,(HL) ; Get a char CP '\' JR Z,CmdL2 ; ..reached Root DEC HL DJNZ FendS ; loop til there, or base CmdL2: LD A,B CP 2 ; At Root? JR NZ,CmdL3 ; ..jump if No to delete Sep INC HL CmdL3: LD (HL),0 JR CmdL6 ; else { /* if going down a level.. */ ; sprintf(nam, "%s\\%s", path, entry[n].name); ; strcpy(path, nam); /* add dir to path */ ; } CmdL4: LD HL,path ; Pt to path Fend1: LD A,(HL) OR A ; EOS? JR Z,CmdL5 ; ..jump if Yes INC HL JR Fend1 ; else back CmdL5: LD (HL),'\' ; Add backslash between Dir names INC HL LD C,L ; Copy adr LD B,H LD HL,E_NAME ; Offset to entry[n].name ADD HL,DE FendA0: LD A,(HL) LD (BC),A ; append INC HL INC BC OR A JR NZ,FendA0 ; ..loop til done ; Read file at current Dir Entry, display from start CmdL6: EX DE,HL ; Place entry[n] in HL for call CALL Rd_Fil JR NC,CmdH ; ..jump if Ok Read of Directory PUSH HL ; Else save returned Message LD HL,2*256+1 ; Start at Path Line Offset, Col 1 CALL GotoXY ; position Cursor CALL CLREOS ; clear screen CALL VPRINT DEFB CR,LF,'++ Problem Reading Directory : ',0 POP HL CALL VPSTR LD HL,0 ; Insure we have No Entries loaded LD (entrys),HL LD A,L LD (path),A ; clear Path JP MLoop ; ..Show prompt for User ;--------------- ; "Home" the current Screen such that the parent directory is the first shown ; ; case 'h': /* Home to start of dir */ ; case 'H': ; n = 0; ; break; CmdH: LD HL,1 ; Skip "This Dir" Entry (0), start @ Parent LD (nn),HL JP Main00 ; break ;--------------- ; Find Next occurance of Specified Search pattern Cmd_L: LD HL,srchBf LD A,(HL) OR A ; Anything to search for? JP Z,CmdFEr ; ..exit w/Beep if Not PUSH HL CALL P_LinX CALL VPRINT ; Else show for what we search DEFB 'Searching for : ',0 POP HL CALL VPStr JR SrchN ; ..continue below ;--------------- ; Find a specified file and position current pointer to that location. ; Ambiguous file specifications are supported with "*" and "?" per CP/M ; ; case 'f': /* find file */ ; case 'F': ; printf("Find which file:"); /* get name to be matched */ ; gets(nam); Cmd_F: CALL P_LinX ; Cursor on Next-to-Last Line CALL VPRINT DEFB 'Search For : ',0 CALL EREOL ; Clear rest of Line LD HL,srchBf ; Place the String here CALL GetLn0 ; Get any user input CALL CAPSTR ; insure in Caps JP Z,CmdFEr ; ..Error if Nothing entered LD HL,2-1 ; Else start searches from second file (-1) LD (srchFn),HL ; accomodating pre-inc ; Set up for Search. Search Next enters here. SrchN: LD BC,(srchFn) ; Get File index ptr INC BC ; Bump LD (srchFn),BC ; resave LD HL,(entrys) LD A,L SUB C LD A,H SBC A,B ; Any (more) files to locate? JP C,CmdFEr ; ..beep and quit if Not LD E,C LD D,B ; Move to locate CALL GEnt_N ; obtain address LD DE,E_NAME ADD HL,DE ; offset to Name field LD DE,srchBf ; and load source ptr CmdF0: LD A,(DE) CP '*' ; Match All? JR Z,CmdF4 CP '?' ; Match This char? JR Z,CmdF3 CP (HL) ; Exact match? JR NZ,SrchN ; ..jump if Not OR A ; End? JR Z,CmdFnd ; ..Found! Set up & Exit CmdF1: INC HL ; Advance target CmdF2: INC DE ; advance Source (srch str) JR CmdF0 ; ..loop til done CmdF3: LD A,(HL) ; Get char from Target CP '.' ; Delim? JR Z,SrchN ; ..no match if Yes OR A ; EOL? JR Z,SrchN ; ..no match if Yes JR CmdF1 ; Else consider it a match CmdF4: LD A,(HL) CP '.' ; Delim? JR Z,CmdF2 ; ..bump source & check if Yes OR A ; EOL? JR Z,CmdF2 ; ..bump source & check if Yes INC HL ; Else bump target JR CmdF0 ; ..and check next ; Match was found. See if it is currently displayed CmdFnd: CALL DSelec ; Deselect Current LD (nn),BC ; Save matched index as current LD HL,(lastn) LD A,L SUB C LD A,H SBC A,B ; > last on screen? JR C,CmdFRe ; ..jump and re-draw if Yes LD HL,(firstn) LD A,C SUB L LD A,B SBC A,H ; < first on screen? JR C,CmdFRe ; ..jump and re-draw if Yes EX DE,HL LD L,C ; Move our index LD H,B OR A SBC HL,DE LD A,L LD (current),A ; Save current index CALL Select ; Mark as selected JP CmdFX ; ..clear Status & back to loop ; We need to re-draw the screen, compute indices CmdFRe: LD L,C LD H,B ; Move our index to HL LD DE,5 LD A,E ; proposed current to A OR A SBC HL,DE ; Space to Back up five? JR NC,CmdFr1 ; ..jump if Yes LD HL,0 ; Else start at Zero LD A,C ; use real index as current CmdFR1: LD (firstn),HL ; Save the first file on new screen LD (current),A ; set one to select CALL ClPrmp ; Clear Prompt Line JP MRstor ; ..refresh display CmdFEr: LD A,BELL CALL COUT CmdFX: CALL ClPrmp ; Clear Prompt Line JP MLoop ; ..continue ;---------------- ; Copy File from CD-ROM to another drive (Z-System Format) CmdC: CALL P_LinX ; Cursor on Next-to-Last Line LD DE,(nn) ; Get Index CALL GEnt_N ; compute Entry address LD DE,E_FLAG ADD HL,DE ; offset to flags byte LD A,(HL) AND 03H ; Can we copy it (Not Dir or SubDir)? JR Z,CmdC0 ; ..jump if Yes CALL VPRINT DB BELL,'Can''t Copy Directory!',0 CALL AnyKey JP MLoop ; ..abort CmdC0: CALL VPRINT DEFB 'Copy to (default = ',0 CALL RETUD LD A,B ADD A,'A' CALL COUT LD A,C CALL PAFDC LD A,':' CALL COUT LD DE,(nn) ; Get Index CALL GEnt_N ; compute Entry address LD DE,E_NAME ADD HL,DE PUSH HL CALL VPSTR CALL VPRINT DEFB ') : ',0 CALL EREOL ; Clear rest of Line POP HL CALL GetFN ; Get any user input PUSH AF ; (save status) CALL EREOL ; Clear Status Line for results POP AF JR NC,CmdC1 ; ..jump if Ok CALL VPRINT DEFB BELL,'++ Can''t copy to ambiguous destination!',0 JP CmdCEv ; ..exit clearing status line after Anykey CmdC1: LD DE,FCB CALL Z3LOG ; Log into Drive/User of Destination CALL F$EXIST ; Does it already Exist? JR Z,CmdC2 ; ..jump if Not CALL VPRINT ; Else DEFB BELL,'File Exists! Erase ([Y]/N)? : ',0 CALL CAPIN ; Get response CP 'N' ; Explicit "N"o? JR Z,CIsN ; ..jump if it an N LD A,'Y' ; Else assume "Y"es CIsN: CALL COUT ; Echo selection JP Z,CmdCX ; ..simply quit if No Overwrite LD A,CR CALL COUT ; Move to left edge CALL EREOL ; clear line CALL VPRINT DEFB 'Erasing..',0 CALL F$DELETE ; Delete the file (DE still -> FCB) JR Z,CmdC2 ; ..jump if Ok CALL VPRINT ; Else Err DEFB BELL,'Can''t Erase (W/P?)!!',0 JR CmdCEv ; ..back to Menu after Anykey pause CmdC2: LD A,CR CALL COUT ; Move to left edge CALL EREOL ; clear line CALL VPRINT DEFB 'Creating..',0 LD DE,FCB CALL F$MAKE ; Create the File (as Open) INC A JR NZ,CmdC3 ; ..jump if Ok CALL VPRINT DEFB BELL,'Can''t Create (No Dir Space?)!!',0 CmdCEv: CALL AnyKey ; Wait JP CmdCX ; ..back to Menu CmdC3: CALL VPRINT DEFB ' Copying to -> ',0 LD DE,FCB ; Pt to FCB LD A,(DE) ; Get Drive ADD A,'@' ; make letter ("@" is Current) CALL COUT ; print LD A,(FCB+13) ; Get User from Z3 space AND 7FH ; (strip MSB) CALL PAFDC ; print in decimal LD A,':' CALL COUT ; separate INC DE ; Advance to 1st char of Name CALL PFN2 ; print FN.FT LD A,' ' CALL COUT ; Add space LD DE,(nn) ; Get Index CALL GEnt_N ; compute Entry address PUSH HL ; (save for later) LD DE,E_LEN ADD HL,DE ; Pt to Len LD DE,jj ; Move length to char count variable LD B,3 LD A,(HL) ADD A,A ; Double LSB, shift B7 to Carry PUSH AF ; (save Rem) CmdCC: INC HL LD A,(HL) RLA ; C <- B7..B0 <- C LD (DE),A INC DE DJNZ CmdCC ; ..loop til all Count moved LD HL,jj POP AF SRL A ; Correct byte to Remainder count LD (remndr),A ; save OR A PUSH HL CALL NZ,IncDW ; Increment Sector Count if partial Sector POP HL LD B,3 LD A,(HL) ; Check for Zero Length CmdCC1: INC HL OR (HL) ; add bytes DJNZ CmdCC1 ; ..til all done POP HL ; (restore Addr of Dir entry) JP Z,CmdCQ ; ..close and exit if Null File CALL GetLBA ; Get the LBA # from (HL) CmdC4: PUSH BC ; Save LBA for repeats PUSH DE CALL OvlRd ; Read per Overlay routine JR NC,CmdCOk ; ..jump if Ok CALL VPSTR ; Else print Error Message JR CmdC5B ; ..exit, closing file CmdCOk: LD B,16 ; Set 16 CP/M Sectors per CD-ROM Block LD HL,bufr ; data in bufr OR A ; Ok? JR Z,CmdC4A ; ..jump if Yes POP DE ; Else clear stack POP BC CALL VPSTR ; print returned error message JR CmdCEx ; ..exit closing file after AnyKey prompt CmdC4A: PUSH HL CALL SETDMA ; Copy From Here LD HL,jj CALL DecDW ; Any More Sectors? JR Z,CmdC5 ; ..jump if No to write Final Sector LD DE,FCB CALL F$WRITE ; Write a Sector POP DE ; Restore DMA Address JR NZ,CmdCEr ; ..exit if Error LD HL,0080H ; Else ADD HL,DE ; compute possible next sector addr DJNZ CmdC4A ; ..loop if More in this block POP DE ; Restore Block # POP BC INC E ; Increment Block # (LSB) JR NZ,CmdC4 ; .loop if no inter-digit carry INC D JR NZ,CmdC4 ; propagate INC C ; thru all JR NZ,CmdC4 INC B JR CmdC4 ; ..loop to Read next CmdC5: LD A,(remndr) OR A ; Partial Sector? JR Z,CmdC5B ; ..jump if Not to write final Sector LD E,A LD D,0 POP HL ; Clear stack of DMA Addr ADD HL,DE ; offset into Sector CmdC5A: LD (HL),1AH ; Fill w/CtrlZ INC DE ; Advance Rel Index INC HL ; and Addr BIT 7,E ; Done w/Fill? JR Z,CmdC5A ; ..loop if Not ;..else fall thru to Write CmdC5B: LD DE,FCB CALL F$WRITE ; Write final Sector JR Z,CmdCQ ; .closing if Ok ;..else fall thru to Error CmdCEr: CALL VPRINT DEFB BELL,'++ Write Error! exiting.',0 CmdCEx: CALL AnyKey LD DE,FCB CALL F$CLOSE ; Close file to be nice JR CmdCX ; ..and exit CmdCQ: LD DE,FCB CALL F$CLOSE ; Close the file LD DE,(nn) ; Get Index CALL GEnt_N ; compute Entry address LD DE,E_YR ADD HL,DE ; offset to Year field LD DE,timBuf ; Pt to Time Stamp Buffer PUSH DE CALL GSData ; Copy Stamp data to ZsDos form (Create/Mod) LD DE,FCB POP HL ; restore ptr to T&D buffer CALL PSTAMP ; add stamp to file JR Z,CmdCX ; ..jump to ignore errors CALL VPRINT ; Else day it is dated DEFB ' (Dated)',0 ; then exit CmdCX: LD BC,(entrDU) CALL LOGUD ; restore Entry Drive/User in case altered CALL ClPrmp ; Clear the line we messed up JP MLoop ; back to menu ;--------------- ; Move Current Pointer Forward to Next Entry in displayed Directory Cmd_X: CALL DSelec ; Deselect Current Marked entry LD DE,(nn) INC DE ; assume next is current LD HL,(lastn) DEC HL ; (insure wrap if past last file) LD A,(current) INC A ; also assume next screen index OR A SBC HL,DE ; Legal index on screen? JR NC,Cmd2v ; ..jump if Yes LD DE,(firstn) ; Else wrap to first XOR A ; set to display first Cmd2v: LD (nn),DE ; save file index LD (current),A ; and screen index CALL Select ; Select it JP MLoop ; ..and back to Top level ;--------------- ; Move Current Pointer Backward to Previous Entry in Displayed Directory Cmd_E: CALL DSelec ; Deselect entry LD DE,(nn) DEC DE ; assume Prev is current LD A,(current) DEC A ; also assume next screen index JP P,Cmd2v ; ..finish up above since ok LD HL,(lastn) DEC HL ; (insure accurate calcs) LD DE,(firstn) OR A SBC HL,DE ; Compute last file index LD A,L ADD HL,DE ; (undo subtract) EX DE,HL JR Cmd2v ; ..finish up above ;--------------- ; Page Screen Back (toward beginning of file) Cmd_R: LD HL,(firstn) ; Get first file number LD A,L DEC A ; (correct for skipping "This Dir") OR H ; At beginning already? JP Z,MLoop ; ..do nothing if Yes LD A,(shown) LD E,A LD D,0 SBC HL,DE ; Else subtract possible # of Entries JP NC,MLoopR ; ..show if we are still shy of beginning LD HL,0 ; Else start at beginning JP MLoopR ;--------------- ; Page Screen Forward (toward End of file) Cmd_C: LD DE,(firstn) ; Get first line # LD A,(shown) LD L,A LD H,0 ADD HL,DE ; Assume we have more to go LD BC,(entrys) LD A,C SUB L LD A,B SBC A,H ; Are we already at end (first+shown > entrys)? JP C,MLoop ; ..do nothing if Yes JP MLoopR ; ..else display next screen of files ;--------------- ; View (Type) a text file on the screen with pagination and line truncation. CmdV: LD DE,(nn) CALL GEnt_N ; Pt to Dir entry EX DE,HL LD HL,E_FLAG ADD HL,DE ; offset to flags byte LD A,(HL) AND 03H ; Can we view it (Not Dir or SubDir)? JP NZ,MRstor ; ..abort if Not LD HL,E_LEN ADD HL,DE ; Pt to Len PUSH DE ; (save ptr) LD DE,jj ; Move length to char count variable LD BC,4 LDIR POP HL ; Position Addr of Dir entry OR 0FFH LD (first),A ; Don't Re-read first sector CALL GetLBA ; Load LBA from HL pointer LD (lbaSav),DE ; (save for use by GByte) LD (lbaSav+2),BC CALL OvlRd ; Read Block from Overlay JR NC,CmdV1 ; ..jump if Ok CALL VPSTR ; Else Print returned Error message JP MLoop ; ..return to menu CmdV1: LD BC,0 ; Relative Ptr at start LD E,C ; No chars on line (0) LD HL,bufr ; pt to buffer LD A,(nrows) SUB 2 ; allow overlap LD (lcnt),A ; Line cntr to avail lines CALL CLS ; Start w/clear screen CmdV2: CALL GByte ; Get a byte from file CP CR JR Z,CmdV5 ; ..forget about CRs CP 1AH JR Z,CmdVX ; ..jump if CP/M EOF to End CP LF JR NZ,CmdV4 ; ..jump if Not to print Char LD A,(lcnt) DEC A JR NZ,CmdV3 ; ..jump if more on this screen CALL VPRINT DEFB CR,LF,'[more]',0 CALL CIN CP CTRLC ; Abort? JP Z,MRstor ; ..quit if Yes, restoring screen CALL VPRINT DEFB BS,BS,BS,BS,BS,BS,0 LD A,(nrows) SUB 3 LD (lcnt),A JR CmdV5 CmdV3: LD (lcnt),A ; (save cnt) CALL CRLF ; Move to New line LD E,0 ; Clear Ch cntr JR CmdV5 CmdV4: CP TAB JR NZ,CmdV4B ; ..jump if Not Tab CmdV4A: LD A,' ' ; Else pad tab to spaces CALL COUT ; Print INC E ; bump count LD A,E AND 07H ; At Tab Stop? JR Z,CmdV5 ; ..jump if Yes LD A,(ncols) DEC A DEC A CP E ; At/past last position? JR NC,CmdV4A ; .loop if Not for more pad JR CmdV5 ; ..else continue CmdV4B: LD D,A ; Stash char to print LD A,(ncols) DEC A DEC A CP E ; At/past last position? LD A,D ; (restore char) CALL NC,COUT ; ..print if No INC E ; bump chars printed CmdV5: PUSH HL LD HL,jj CALL DecDW ; done w/file? POP HL JR NZ,CmdV2 ; ..loop if Not CmdVX: CALL VPRINT DEFB CR,LF,' [any key for Dir]',0 CALL CIN JP MRstor ; Exit by restoring screen ;--------------- ;(-) Spin down and eject Tray/Caddy CmdUnl: CALL GXYMsg DEFB 2,1 ; Pos'n Cursor DEFB ' -- Disc Unloaded --',0 CALL EREOL ; Blank rest of line LD HL,0 LD (entrys),HL ; Clear number of entries CALL P_3Clr ; Position on Line 3, Clear rest of Screen CALL OvlEj ; Execute Overlay routine JP NC,MLoop ; ..wait for another command if Ok CALL VPSTR ; Else print returned message JP FinErr ; exit by saying Abort ;--------------- ;(+) Load Tray/Caddy, Spinup disc and log in to Root Directory CmdLod: CALL P_3Clr ; Position on Line 3, Clear rest of Screen CALL OvlLod ; Execute Overlay routine JP NC,Main ; ..Load Directory and display if Ok CALL VPSTR ; Else print returned message JP MLoop ; and wait for next command ;--------------- ;(?) Display Built-In Help CmdQ: CALL P_3Clr ; Position on Line 3, Clear rest of Screen CALL VPRINT DEFB 'Driver : ',0 CALL OvlStr ; Get Overlay String CALL VPSTR ; print CALL VPRINT DEFB CR,LF,LF DEFB ' CD Sweep - Help Screen',CR,LF DEFB ' ----------------------',CR,LF DEFB '^X - Forward One File.',CR,LF DEFB '^C - Forward One Screen.',CR,LF DEFB '^E - Back One File.',CR,LF DEFB '^R - Back One Screen.',CR,LF DEFB '- Log into Directory (aka RETurn/Enter).',CR,LF DEFB '. - Log into Parent Directory.',CR,LF DEFB 'H - Move to Start of Directory.',CR,LF DEFB '^F - Find First Entry Occurrance.',CR,LF DEFB '^N - Find Next Entry Occurrance.',CR,LF DEFB 'C - Copy File to another Drive.',CR,LF DEFB 'V - View Text File.',CR,LF DEFB '- - Open Tray/Eject Caddy.',CR,LF DEFB '+ - Close Tray/Load Caddy.',CR,LF DEFB 'X - Exit to Command Prompt.',CR,LF DEFB '? - Display Help (this screen).',CR,LF,LF,0 CALL AnyKey ; wait til any key pressed JP MRstor ; Continue restoring screen ;=======================================================================; ;--- Z-System Command Processor / Screen Attribute Handling Routines ---; ;=======================================================================; ; Mark Current File Display Select: PUSH DE ; Save regs PUSH HL CALL P_LinC ; Position Cursor to Current Entry CALL VPRINT DEFB '-->',0 LD A,L ADD A,11 ; Offset to 1st char in Name LD L,A CALL GotoXY LD DE,(nn) ; Get Current file index in Array CALL GEnt_N ; Offset to current entry EX DE,HL LD HL,E_NAME ADD HL,DE ; and Name CALL STNDOUT ; Highlight ON Selec0: CALL VPSTR ; Print Name CALL STNDEND ; Highlight OFF POP HL POP DE RET ;..... ; Un-Mark Current File Display DSelec: PUSH DE ; Save regs PUSH HL CALL P_LinC ; Position Cursor to Current Entry CALL VPRINT DEFB ' ',0 LD A,L ADD A,11 ; Offset to 1st char in Name LD L,A CALL GotoXY LD DE,(nn) ; Get Current file index in Array CALL GEnt_N ; Offset to current entry EX DE,HL LD HL,E_NAME ADD HL,DE ; and Name JR Selec0 ; ..finish off above ;========================================================================== INCLUDE CDZSWP1.INC ; Add routines from D.Elvin's CDSWEEP ; Small routine to read from a sector with sector read if crossing boundaries ; Local routine only used here. ; Enter: HL -> within bufr ; BC = Low 16 bits of Big Count/Index ; Exit : HL -> byte 0 of bufr if read performed ; A = byte at specified address ; Uses : AF,HL,B' (misc decremented Cntr) GByte: LD A,C ; Get low addr OR A ; 0 ? JR NZ,GByte1 ; ..jump if Not time to read LD A,B AND 07H ; Hi-byte indicate time to Read? JR NZ,GByte1 ; ..jump if Not to get from buffer LD A,(first) OR A ; First Block? LD A,0 LD (first),A ; (clear flag in any event) JR NZ,GByte1 ; ..jump if 1st to prevent re-read PUSH DE ; Else save Regs PUSH BC LD HL,lbaSav CALL IncDW ; Advance LBA count LD DE,(lbaSav) ; Load incremented LBA into Regs LD BC,(lbaSav+2) CALL OvlRd ; Read via Overlay routine POP BC POP DE JR NC,GByte0 ; ..jump if Good Read CALL VPSTR ; Else display Error Message RET ; exit GByte0: LD HL,bufr GByte1: LD A,(HL) ; Get Char INC HL ; advance to next source position INC BC ; and bump ptr/cntr EXX ; Go to Alt Regs DEC B ; count down EXX ; to Prim Regs RET ;..... ; Compute "entry[n]" Address ; Enter: DE = "n" index (base 0) ; entry obtained from global name space ; Exit : HL -> entry[n] ; Uses : HL,AF GEnt_N: PUSH BC ; Save Regs PUSH DE LD HL,(entry) ; pt to current entry LD BC,E_SIZE ; Add length of entries til we get offset GEnt_0: LD A,D OR E ; Arrived? JR Z,GEnt_X ; ..exit if Yes ADD HL,BC ; Else offset to next DEC DE ; count down JR GEnt_0 ; ..and offset more GEnt_X: POP DE ; Restore Regs POP BC RET INCLUDE CDZSWP0.INC ; Add Misc, B/P Bios, Z-System & Support code ;--------------------- DATA ------------------------- ; These are all unitialized storage locations so that they do not ; add to the storage requirements of the final executable program DSEG ; Globals needed for CD Sweep port entrys: DEFS 2 ; int entrys; Number of Entrys in array path: DEFS 100 ; char path[100]; Null-term String for Path iso_med: DEFS 1 ; byte iso_media; 0=High Sierra, 1=ISO9660 entry: DEFS 2 ; (global Word) Ptr to current entry in DirAry entent: DEFS 2 ; Temp Storage for entry[entrys] ptr len: DEFS 4 ; (global DWord) Length of Logged Dir (bytes) jj: DEFS 4 ; (local DWord in MakIdx) Length of Dir so far nn: DEFS 2 ; GP Word for counting entrys while printing round: DEFS 1 ; 0 = No rounding of size values, FF = round up iso_md: DEFS 1 ; (global bool) 0=High Sierra, Non-0=iso-media tempB: DEFS 1 ; Temporary byte of storage first: DEFS 1 ; Boolean flag to prevent re-read in MakIdx lbaSav: DEFS 4 ; Storage for LBA (in GByte) ;=== Values for Z-System / B/P Bios support === remndr: DEFS 1 ; Possible CP/M partial sector count entrDU: DEFS 2 ; Entry Drive/User location ncols: DEFS 1 ; Number of Columns from ENV nrows: DEFS 1 ; Number of Rows from ENV shown: DEFS 1 ; Number of entries we display at once firstn: DEFS 2 ; Number of first displayed entry lastn: DEFS 2 ; Number of last displayed entry current: DEFS 1 ; Selected entry on screen (0..shown-1) lcnt: DEFS 1 ; counter of displayed lines (for View) datPtr: DEFS 2 ; Ptr for Data IO to/from SCSI drive timBuf: DEFS 15 ; Buffer for ZsDos Time/Date Stamp entry srchBf: DEFS 50 ; Search String (Null-term) for names srchFn: DEFS 2 ; File Number for String (name) Searches linBuf: DEFS 50 ; Buffer for FileSpec entry DEFS 256 ; Space for a local stack stack: DEFS 2 ; Storage for entry Stack Pointer bufr: DEFS 2048 ; (global Buffer) Used to Read from CD-ROM END