;-----------------------------------------------------------------------; ;--- CD Sweep Support routines (c) D.Elvin in Assembly by H.F.Bower ---; ;-----------------------------------------------------------------------; ;/* print an iso 9660 directory entry */ ; Enter: HL -> Entry to print ; DE = current entry number + 1 ; Exit : None ; Uses : Directory entry data from formal parameter, ; "nn" global variable (entry number). Pr_Ent: EX DE,HL CALL PHLDC ; print in decimal CALL VPRINT DEFB ' : ',0 LD HL,E_NAME ; Offset to name ADD HL,DE ; in this entry LD B,15+1 ; set field length + extra space Pr_En0: LD A,(HL) OR A ; End? JR Z,Pr_En1 ; ..jump if Yes CALL COUT ; Else print INC HL DJNZ Pr_En0 ; ..back for more INC B DEC B ; B *should* not be Zero, but check JR Z,Pr_EnZ ; ..protect in case Pr_En1: LD A,' ' ; Pad with spaces CALL COUT DJNZ Pr_En1 ; ..looping til field filled Pr_EnZ: LD HL,E_DY-3 ; Offset to Year-1 in entry ADD HL,DE LD B,5 ; Check ymdhm XOR A Pr_E0: INC HL ; bump OR (HL) ; add in any bits DJNZ Pr_E0 ; ..loop til done JR NZ,Pr_EnS ; ..print T&D Stamps if something there CALL VPRINT ; Else DEFB ' ',0 JR Pr_ESz ; ..print size Pr_EnS: LD HL,E_DY ; Offset to Day in entry ADD HL,DE PUSH HL ; (save for Time Display) LD A,(usEur) OR A ; Using US (MM/DD/YY) format for Dates? JR NZ,Pr_EnU ; ..jump if Yes, Else dates in Eur (DD.MM.YY) LD A,(HL) ; fetch CALL PA2DC ; print DEC HL LD A,'.' ; Separator (use European since Day first) CALL COUT LD A,(HL) ; Fetch Month CALL PA2DC ; print DEC HL LD A,'.' CALL COUT JR Pr_EnY ; ..jump to print Year Pr_EnU: DEC HL ; Since US form, back up to Month LD A,(HL) ; Fetch Month CALL PA2DC ; print INC HL ; (advance to Day) LD A,'/' ; US Format Separator CALL COUT LD A,(HL) ; Fetch Day CALL PA2DC ; print DEC HL DEC HL ; (back up to Year) LD A,'/' CALL COUT ; print final separator Pr_EnY: LD A,(HL) ; Fetch Year CP 76+1 ; 20th Century? PUSH HL LD HL,Cen20 ; (prepare for Yes) JR NC,Pr_En2 ; ..jump if Yes LD HL,Cen21 ; Else say it's 21st Century Pr_En2: CALL VPSTR POP HL LD A,(HL) ; Get Year again CALL PA2DC ; print LD A,' ' CALL COUT ; Separator CALL COUT POP HL ; Restore Ptr to Day INC HL ; advance to Hr LD A,(HL) CALL PA2DC ; print Hrs LD A,':' CALL COUT INC HL LD A,(HL) CALL PA2DC ; print Mins Pr_ESz: LD A,' ' CALL COUT ; Separator CALL COUT ; Size in this implementation rounded up to size in kilobytes (1024) LD A,0FFH ; Set flag for rounding up another k LD (round),A LD HL,E_LEN ; Offset to Size LSB ADD HL,DE LD A,(HL) ; Fetch LSB INC HL LD C,(HL) ; next to LSB INC HL LD B,(HL) ; next to MSB INC HL LD H,(HL) ; and MSB (DWord now in HBCA) OR A ; Mod 256 remainder? JR NZ,Pr_EnN ; ..jump if Yes to round up LD A,C AND 03H ; Mod 1024 remainder? JR NZ,Pr_EnN ; ..jump if Yes to round up LD (round),A ; Else even DIV 1024, don't round (save 0) Pr_EnN: SRL H ; Shift DIV 256 Quotient RR B ; right twice RR C ; to get Size DIV 1024 SRL H RR B RR C LD A,H ; Get High byte LD L,C ; transfer 16-bit size in K for print LD H,B OR A ; Size Ok? JR Z,Pr_En3 ; ..jump if Yes CALL VPRINT ; Else print B I G symbol DEFB '>64MB ',0 JR Pr_En5 ; ..and continue Pr_En3: LD A,(round) ; Restore Rounding Flag OR A JR Z,Pr_En4 ; ..jump if No rounding needed INC HL ; Else go to next k Pr_En4: CALL PHLDC ; Print Size LD A,'k' CALL COUT Pr_En5: CALL VPRINT DEFB ' : ',0 LD HL,E_FLAG ; Offset to Flags ADD HL,DE BIT 1,(HL) ; Directory? LD HL,dirStr ; (default to Yes) JR NZ,Pr_En6 ; ..jump if Yes LD HL,ndiStr ; Else say nothing Pr_En6: JP VPSTR ; ..just print and return thru Stack dirStr: DEFB '',0 ndiStr: DEFB '-----',0 Cen20: DEFB '19',0 Cen21: DEFB '20',0 ;..... ;/* read a block of data from cd to .. memory .. */ ;void read_file(cd_entry *e, char *nam, int op) { ;----------------------- ; Enter: HL -> e (ptr to cd_entry) ; A = op (0 = MEM, 1 = FIL) ; Exit : none ;----------------------- ; /* read directory to memory */ ; entrys = 0; Rd_Fil: LD DE,0 LD (entrys),DE ; m = e->start; /* start LBA */ ; for(l = e->length; l > 0; l -= CD_SECTOR) { ; read_cd(m++, buff); /* read data to buffer */ CALL GetLBA ; Load LBA into BCDE LD (lbaSav),DE ; (save for use by GByte) LD (lbaSav+2),BC INC HL ; pt to e->length PUSH BC ; (save LBA) PUSH DE LD DE,len ; Set variable needed in MakIdx LD BC,4 LDIR ; move DWord length POP DE POP BC CALL OvlRd ; Read the first 2k Sector into Buffer JR NC,Rd_Fi0 ; ..jump if Ok CALL VPSTR ; Else Print returned Error message SCF ; insure Error status RET ; and return ; /* update index */ ; make_index((l > CD_SECTOR ? CD_SECTOR : l), buff); Rd_Fi0: CALL MakIdx ; Read CD-ROM directory into name array ; NOTE: MakIdx reads via virtual buffer ; entrys--; /* correct record count */ LD HL,(entrys) DEC HL LD (entrys),HL OR A ; return Ok Status RET ;..... ;/* update index & entry count with len bytes from b */ ;void make_index(dword len, byte *b) ;{ ; int j, n; ; iso9660 *e; ; ; j = 0; ; while (j < len) { MakIdx: LD HL,0 ; Initialize length DWord (use global RAM) LD (jj),HL LD (jj+2),HL LD B,H LD C,L LD HL,bufr ; Set Regs for Buffer Access LD DE,(entry) ; Set Start of Dest Array LD (entent),DE ; to temp ptr LD A,0FFH LD (first),A ; Set flag to prevent re-read of 1st Sector MakId0: PUSH HL PUSH DE LD HL,len LD DE,jj LD A,(DE) SUB (HL) INC DE INC HL LD A,(DE) SBC A,(HL) INC DE INC HL LD A,(DE) SBC A,(HL) INC DE INC HL LD A,(DE) SBC A,(HL) POP DE POP HL RET NC ; ..quit if j >= len ; if(!b[j]) ; j++; /* skip padding bytes */ CALL GByte LD (tempB),A ; (save in case it is Length byte) OR A ; Pad? JR NZ,MakId1 ; ..jump if Not PUSH HL LD HL,jj CALL IncDW ; Else bump DWord jj POP HL JR MakId0 ; ..back to main loop ; else { ; if(entrys == MAX_DIR) { /* if too many entrys.. */ ; puts("Too many files."); ; break; ; } MakId1: EXX ; Use Alt Regs LD B,A ; save length DEC B ; compensate for count just read EXX ; back to Primary Regs LD A,(entrys+1) ; Get number of entrys (Hi-byte) AND 0FCH ; keep only bits indicating > 1023 JR Z,MakId2 ; ..jump if < 1024 to continue CALL VPRINT DEFB BELL,'Too many files.',0 JP AnyKey ; ..Abort to caller after pause ; e = (iso9660 *)(&b[j]); /* ptr to entry in buffer */ ; entry[entrys].start = e->start; /* transfer params */ ; entry[entrys].length = e->length; ; entry[entrys].yr = e->yr; ; entry[entrys].mn = e->mn; ; entry[entrys].dy = e->dy; ; entry[entrys].hr = e->hr; /*hfb*/ ; entry[entrys].min = e->min; /*hfb*/ MakId2: LD DE,(entent) ; Pt to Dest CALL GByte ; Skip a byte (xar_len) CALL Mv4Byt ; Move 4 byte (1 DWord) Start Adr (start) CALL Sk4Byt ; Skip Big-Endian Address (startm) CALL Mv4Byt ; Move 4 Bytes (1 DWord) Lngth (length) CALL Sk4Byt ; Skip Big-Endian Length (lengthm) CALL Mv3Byt ; Move 3 Bytes (yr,mn,dy) CALL Mv2Byt ; Move 2 Bytes (hr,min) CALL GByte ; Skip 3 Bytes (sec) ; entry[entrys].flags = iso_media ? e->flags : e-> oset; LD A,(iso_md) ; Is this ISO or High Sierra media? OR A JR NZ,IsISO ; ..jump if ISO CALL Mv1Byt ; Else move "oset" into flags CALL GByte ; skip real flags JR IsISON ; ..continue IsISO: CALL GByte ; Skip the "oset" byte CALL Mv1Byt ; Move Flags IsISON: CALL Sk6Byt ; Skip 6 (ilsize,ilskip,vssni,vssnm) ; /* build name handling '.' & '..' */ ; switch(e->name[0]) { ; case 0: strcpy(entry[entrys].name, "."); break; ; case 1: strcpy(entry[entrys].name, ".."); break; ; default: ; if(e->len_name > (MAX_NAME-1)) /* limit name length */ ; e->len_name = MAX_NAME-1; ; /* copy name & convert to u/case deleting version no. */ ; for(n=0; n < e->len_name; n++) { ; entry[entrys].name[n] = upper(e->name[n]); ; /* if ver no. delete rest of string */ ; if(entry[entrys].name[n] == ';') ; entry[entrys].name[n] = '\0'; ; } ; entry[entrys].name[e->len_name] = '\0'; /* term with null */ ; } CALL GByte ; Get Name Length CP MAX_NAM ; Length < Max allowed? JR C,MakId3 ; ..jump if Yes LD A,MAX_NAM-1 ; Else set allowed char cnt (one for null) MakId3: EXX LD C,A ; Save Actual Char cnt in C' EXX CALL GByte ; Get Name[0] OR A ; This Dir? JR NZ,MakId4 ; ..jump if No LD A,'.' ; Else Save dummy name "." LD (DE),A INC DE ; bump JR MakId6 ; ..continue MakId4: CP 01H ; Parent Directory? JR NZ,MakIdV ; ..jump if No LD A,'.' ; Else Save dummy name ".." LD (DE),A INC DE LD (DE),A INC DE JR MakId6 ; ..continue MakId5: CALL GByte ; Get a Byte MakIdV: CP ';' ; Version signifier? JR NZ,NotVer ; ..jump if No to continue NotL: EXX DEC C ; Done? EXX JR Z,MakId6 ; ..jump if Yes CALL GByte ; Else read another JR NotL ; ..repeating til done NotVer: CP 'a' ; < "a"? JR C,NotLow ; ..jump if Yes CP 'z'+1 ; > "z"? JR NC,NotLow ; ..jump if Yes AND 5FH ; Else make Uppercase NotLow: LD (DE),A ; save INC DE ; pt to next dest EXX DEC C ; More to go? EXX JR NZ,MakId5 ; ..loop if Yes MakId6: XOR A ; Get a null LD (DE),A ; and terminate string EXX ; Go to Alt Regs ClrIt: LD A,B ; Get Count EXX ; (to Prim Regs in case more) OR A ; Done? JR Z,MakId7 ; ..jump if Yes CALL GByte ; Else read another byte EXX ; (to Alt regs) JR ClrIt ; ..loop to test ; j += e->len_dir; /* pos to the next entry */ ; entrys++; ; } ; } ;} MakId7: PUSH HL ; Save Ptr into Bufr LD HL,(tempB) ; Get len_dir from temp storage LD H,0 ; in 16-bits LD DE,(jj) ; Fetch low Wd of Length ADD HL,DE ; offset LD (jj),HL LD HL,(jj+2) ; Get Hi 16 bits LD DE,0 ADC HL,DE ; correct for any carry LD (jj+2),HL ; save LD HL,(entrys) ; Get # Entries INC HL ; bump LD (entrys),HL ; put back LD HL,(entent) LD DE,E_SIZE ADD HL,DE ; Advance LD (entent),HL ; to next Dir Entry in Array EX DE,HL POP HL ; Restore Ptr into Bufr JP MakId0 ; ..back to top of While Loop ; Read a series of one or more bytes from (HL) using GByte to (DE) for cnt in B Mv4Byt: CALL GByte ; Get a byte (bump HL and BC) LD (DE),A ; store INC DE ; bump dest ptr Mv3Byt: CALL GByte LD (DE),A INC DE Mv2Byt: CALL GByte ; Move 2 if entered here LD (DE),A INC DE Mv1Byt: CALL GByte LD (DE),A INC DE RET ; exit pting to next loc'n ; Skip (dummy read) of bytes Sk6Byt: CALL GByte ; Skip 6 CALL GByte ; 5 Sk4Byt: CALL GByte ; 4 Sk3Byt: CALL GByte ; 3 Sk2Byt: CALL GByte ; 2 JP GByte ; 1, return thru Stack ;----------------------- End of CDZSWP1.INC --------------------------