; LD.Z80 ; ; Extended library directory utility for Z-System. ; Vers equ 11 ; current version SubVers equ ' ' ; modification level ; ; The starting point for this program was LDIR-B Version 2.2, which ; gives an UNARC-type display of library directories. Originally ; written by Steven Greenberg, it is the result of several years of ; continuing development by Bruce Morgen, Michal Carson, Sean Sullivan, ; Howard Goldstein, and Gene Pizzetta. LD will be moving in a slightly ; different direction, hence, the name change. My goal is to keep this ; program under 4K, about twice the size of LDIR-B, and to provide a ; more versatile library directory tool with numerous command line and ; configuration options, and making more extensive use of Z-System ; facilities, while remaining compatible with vanilla CP/M. ; ; Please report any bugs as soon as possible, or make suggestions at ; your leisure: ; ; Gene Pizzetta ; 481 Revere St. ; Revere, MA 02151 ; ; Voice: (617) 284-0891 ; Newton Centre Z-Node: (617) 965-7259 ; Ladera Z-Node Central: (213) 670-9465 ; ; HISTORY: ; ; Version 1.1 -- October 25, 1991 -- Gene Pizzetta ; Many changes. Added alternate display of member names, sizes, ; CRC's, and indexes in two-columns. Changed some options, added ; others. Option S prints only the summary line. Option Q is a ; true quiet mode. Option M stores the number of matching members ; and free library directory entries to message registers. Option ; D checks for embedded dates in crunched files before checking ; library directory for dates. Restored configurable wheel byte ; address for non-ZCPR3 systems. If wheel is off, now shows number ; of matching and active members and suppresses display of M and Q ; (along with L and F) options on usage screen, although M and Q ; will still work. In quiet mode output can be sent to the printer. ; Top of memory calculation is now less conservative for low memory ; applications. Fixed a few bugs, including one that kept LD from ; running under vanilla CP/M. Now invokes error handler for errors ; other than no matching member files. A bouquet to Howard Goldstein ; for his testing and suggestions, which have made this a much better ; utility. ; ; Version 1.0 -- October 7, 1991 -- Gene Pizzetta ; Added command line options (C, Q, P, L, and F). Now checks for ; modify date even if there is no create date. Displays date in ; American or European format. Displays time in military or ; civilian format. Single-line display of the first 18 bytes of ; embedded comments abandoned in favor of always displaying the ; uncrunched or unsqueezed filename. Embedded comments are now ; displayed on a separate line (up to 76 characters) in response ; to a command line option. Relocatable code uses a large number ; of library routines. Wheel security prevents non-wheels from ; using options L and F or from accessing system files. ; ; For the history of the predecessor program, see LDIR22.LBR. ; ; System addresses . . . ; BdosE equ 0005h ; BDOS entry CpmFcb equ 5Ch ; default file control block AltFcb equ 6Ch ; alternate file control block CpmDma equ 80h ; default DMA address ; ; BDOS functions . . . ; FOpen equ 15 ; open file FRead equ 20 ; read sequential SetDma equ 26 ; set DMA address RRead equ 33 ; read random ; ; ASCII . . . ; BEL equ 07h ; bell LF equ 0Ah ; line feed FF equ 0Ch ; form feed CR equ 0Dh ; carriage return ; LinLen equ 76 ; maximum number of "comment" characters ; .request zslib,z3lib,syslib ; ext sdats3,stims2,hvtinit,hvdinit,hvon,hvoff ; ZSLIB ext uncaps,jul2bin,binbcd,gcomnam,comnam,eatspc ext eatnspc,zout ext z3init,z3log,getmsg,getcrt,puter2,gzmtop ; Z3LIB ext inverror ext scrlf,lcrlf,condin,cin,sout,sprint,spstr,retud ; SYSLIB ext sctlfl,cout,lout,bdos,sa2hc,getmtop,codend ; public csout,ccout,clout ; jp Start ; ; ZCPR3 header . . . ; db 'Z3ENV',1 Z3EAdr: dw 0 ; ; Configuration area . . . (Have I forgotten anything?) ; dw 0 ; filler db 'LD' ; for ZCNFG db Vers/10+'0',Vers mod 10+'0',' ' CmtFlg: db 0 ; FFh=print embedded comments by default SumFlg: db 0 ; FFh=summary only PrfFlg: db 0 ; FFh=prefer crunched date PagFlg: db 0FFh ; FFh=screen paging LstFlg: db 0 ; FFh=printer echo FFFlag: db 0 ; FFh=send final form feed if printing XFlag: db 0 ; FFh=CRC, index, and double column QtFlag: db 0 ; FFh=quiet mode MemFlg: db 0 ; FFh=results to message registers (ZCPR only) MemReg: db 18 ; first of 4 message registers to use DatFlg: db 0 ; FFh=European date TimFlg: db 0FFh ; FFh=military time EmbChr: db '~' ; flag character for embedded date stamps MaxLns: db 24 ; screen lines before pause (CP/M only) WhlAdr: dw 0 ; wheel byte address (CP/M only) ; ; Program begins . . . ; Start: ld hl,(Z3EAdr) call z3init ld (Stack),sp ; save stack pointer ld sp,Stack ; ..and set up new stack call codend ; set library directory buffer ld (DirBuf),hl ld hl,DftNam ; point to default name call gcomnam ; get disk name if available ld a,00000001b ; turn printer echo off ld (sctlfl),a call Z3Chk ; get environment address (Z if not ZCPR3) ex de,hl ; environment address to DE ld hl,(WhlAdr) ; get default wheel address jr z,PutWhl ; (if not ZCPR, use default) ; ld hl,41 ; HL = offset to wheel byte address add hl,de ; DE = environment address ld a,(hl) ; now HL = address of wheel byte address inc hl ; ..so move wheel byte address into HL ld h,(hl) ld l,a PutWhl: ld a,(hl) ; get wheel byte ld (WhlByt),a ; ..and store it ld a,(CpmFcb+1) cp ' ' jp z,Usage cp '/' jp z,Usage ; call Z3Chk ; ZCPR3? push af call getmtop ; get top of memory pop af jr z,NotZ3 ; (not ZCPR) call getcrt ; get screen lines inc hl ld a,(hl) ld (MaxLns),a ; .. and store them call gzmtop ; if Z, get top of memory again ; NotZ3: ld a,h ; high byte to A dec a ; ..decrement it for safety ld (OvfTpa),a ; ..and save it for later ld a,(MaxLns) ; get screen lines dec a ; ..make room for heading (1st screen only) dec a dec a ld (LinCtr),a ; ..and initialize counter (decrements to 0) ld hl,'RB' ; last 2 letters of LBR (backwords) ld (CpmFcb+10),hl ; put at fcb+10 and fcb+11 ld a,'L' ld (CpmFcb+9),a ; now we have a forced LBR filetype ld hl,AltFcb+1 ; move possible user wildcard ld de,WldFcb ; ..filespec into storage ld bc,11 ldir call GetOpt ; check for options ld a,(OpQFlg) or a call z,hvtinit ; initialize terminal (unless quiet) call Z3Chk ; Z-System? jr nz,LogZ ; (yep) ; call retud ; for CP/M assume current user ld a,c ld (CpmFcb+13),a ; stuff it into file control block LogZ: ld a,(CpmFcb+15) ; check for invalid directory inc a jp z,DirBad ; (no good) ld de,CpmFcb call z3log ; log into target directory xor a ld (CpmFcb),a ; zero drive ld de,CpmFcb+12 ; clear FCB except filename ld b,24 ZLp2: ld (de),a inc de djnz ZLp2 ; ld hl,NFiles ; initialize data area to zeros ld b,InitSz ZLp3: ld (hl),a inc hl djnz ZLp3 ; ld de,CpmFcb ; open the library file ld c,FOpen call bdos inc a jp z,NoLBR ; (no such file) ; ld a,(CpmFcb+10) ; system file? and 80h jr z,NonSys ; (no, it's OK) ld a,(WhlByt) ; check wheel byte or a jp z,NoLBR ; if zero, pretend the file does not exist ; NonSys: ld c,SetDma ; make sure the default DMA is 80h ld de,CpmDma call bdos ld a,(OpSFlg) ; for summary only, skip library name or a jr nz,SSkip1 call sprint db 'Library: ',0 call retud ; get current directory ld a,b add a,'A' call zout ; print drive ld l,c ld h,0 call PrDec ; print user ld a,':' call zout ld hl,CpmFcb+1 ; point to the LBR's filename call PFName ; ..and print it call PrSpc1 ; print a space SSkip1: call RdSect ; read the library's 1st record ld hl,CpmDma ; point to first byte ld a,(hl) ; check validity- the directory entry for the ; directory itself must be "active" (zero) ; ; There should be eleven space characters next (the filename area of the ; directory entry for the directory itself). This validity check is skipped ; because some MS-DOS library programs insert the library's name here. ; ld l,CpmDma+12 ; more validity checking (H = 0): or (hl) ; the library's "Index" must be zero inc hl ; if Index(lo) > 0, library is corrupt or (hl) jp nz,Corupt ; likewise for Index(hi) inc hl ld a,(hl) ; get length of directory(lo) inc hl ld h,(hl) ; and length of directory(hi) ld l,a ; full directory length in HL or h jp z,Corupt ; (0-length library directory is corrupt) ld (DirLen),hl ; store it ld (TotLen),hl ; ; It must be a library, so display its creation and modification dates and ; times, if they exist. ; ld a,(OpSFlg) ; for summary only, skip library dates or a jr nz,SSkip2 call PrSpc2 ld ix,CpmDma+18 ; get creation date of library call DateX ; print a date if it's good ld hl,CreMsg call nc,PrDate ; display the result of "Date" ld ix,CpmDma+20 ; get modified date of library call DateX ld hl,ModMsg call nc,PrDate call scrlf ; ; Program operation: Read library directory into memory in one shot, avoiding ; having to go back to it later while reading the first record of various ; member files. Only the 25 bytes of interest out of 32 will be saved for ; each entry. Entries flagged as deleted or non-existent will be skipped. ; SSkip2: ld de,(DirBuf) ; data packed to memory starting here jr Skp1st ; (only 3 entries first record) ; MainLp: ld hl,CpmDma+00 ; 1st entry per record call ActivQ ; active? call z,PrcEnt ; copy 25 bytes of this entry ; Skp1st: ld hl,CpmDma+20h ; 3 more times per sector call ActivQ ; active? call z,PrcEnt ld hl,CpmDma+40h call ActivQ ; active? call z,PrcEnt ld hl,CpmDma+60h call ActivQ ; active? call z,PrcEnt ld hl,(DirLen) dec hl ld a,l or h jr z,DunDir ; (done reading directory, go process) ld (DirLen),hl ; store length remaining call RdSect ; ..and read another record jr MainLp ; loop without disturbing DE ; ; DunDir -- Finished reading directory, so start processing from beginning ; DirBuf. ; DunDir: ld hl,(NFiles) ; test for no matching members ld a,l or h jp z,Empty ; (none) ; ld a,(OpSFlg) ; request for summary line only? or a jp nz,Empty ; (yes, we can skip a lot of code here) call DoHedg ; print heading ld hl,(DirBuf) ; point to packed data to be processed ; NamLp: call CkAbrt ; check for screen pause or abort call PFName ; type filename (increase HL by 11) call PrSpc2 ld e,(hl) ; get entry's index for later inc hl ld d,(hl) inc hl ld (Index),de ; store 2 byte index value ld e,(hl) ; get file size in sectors inc hl ld d,(hl) inc hl ld a,e ; test for zero-length file or d ld (ZerFlg),a ; save as a flag for later ; ; The member's file size is the next thing to print. The code below prints ; the length in records (in DE), divides it by eight, prints the length in ; kilobytes, and then prints the remainder as a fractional part in kilobytes. ; push hl ; save pointer and size in records push de ex de,hl ; records to HL call PrSDec ; print with leading spaces ld a,'r' ; type an "r" for "records" call zout pop de ; restore pointer and size pop hl xor a ; accumulate the fractional part in here ld b,3 ; set loop counter DvLoop: srl d ; } rr e ; } divide by 8, shifting remainder into A rra ; } djnz DvLoop rra rra ; A = remainder times 8 push af ; save it while we print the full number of K push hl ; save our pointer too ex de,hl call PrSDec ; print number in HL pop hl pop af ; get everything back ld de,MCRC ; point to member CRC and date storage ld bc,10 ldir ; move CRC, create and modify dates and times ld (HLSave),hl ; save pointer again ld h,b ; B is still 0 ld l,a ; move fraction (still in A) to L sra l ; half L sra l ; quarter L sub l ; now A = remainder times 6 ld l,a ; select the appropriate fraction ld de,Fracts ; ..from the 6-byte wide Fracts table add hl,de call spstr ; print fraction ; ld a,(OpXFlg) ; if alternate display, do it or a ; ..and start line again jp nz,XMode ; ; Read the first record of the file into the default DMA and examine it for ; compression type. It's slower than checking the filetype first and only ; reading the record if the middle letter indicates a crunched file, but ; it's more accurate. ; xor a ld (CrFlag),a ; clear flags ld (SqFlag),a ld (CpmDma),a ; clear 1st byte of DMA buffer (nothing read) ld (Offset),a ; offset to create date is zero ld a,(ZerFlg) ; Zero-length file? or a call nz,RdHdr ; (if not, read the first record) ld hl,CpmDma ; point to first character of record ld a,76h ; is there a Z80 halt instruction? cpi jr nz,CmprNo ; (no, so we don't know the compression) ld a,(hl) ; get the second character of the file ld (SqFlag),a ; save as a flag ld de,SqMsg inc a ; "Squeezed" indicated by 076h 0FFh series jr z,CmprTp ld hl,CrFlag ld de,CrMsg ld (hl),a ; save as a flag inc a ; "Crunched" indicated by 076h 0FEh series jr z,CmprTp ld de,LzhMsg ld (hl),a ; save as a flag inc a ; "LZH" indicated by 076h 0FDh series jr z,CmprTp CmprNo: ld de,StoMsg ; no compression ; CmprTp: ex de,hl ; message pointer to HL call spstr ; whatever it is, type it call PrSpc2 ; ..and 2 spaces ; ; The DateQ routine will, if possible, define Day, Month, Year, Hour, and ; Minit as BCD values in buffer. Returns with carry set if no date found. ; ld ix,CDate ; point to create date call DateQ call c,DatLes jr c,NxtDat call ShoDat ; Display date NxtDat: ld a,10 ld (Offset),a ; Offset to mod date is ten ld ix,MDate ; point to modify date call DateQ call c,DatLes jr c,UncNam call ShoDat ; ; Print "real" name if member file is compressed. ; UncNam: ld a,(SqFlag) inc a ; 0FFh if squeezed jr z,UncNm1 ; Print original name if squeezed ld a,(CrFlag) inc a ; 0FFh if crunched jr nz,DunLin ; If not, we are done. Go to next LBR member. ; UncNm1: call GetNam ; get uncompressed name ld a,(OpCFlg) ; do we do comments? or a jr z,DunLin ; (no) ld a,(CrFlag) inc a jr nz,DunLin ; not crunched, we're through ; ; If file is crunched, attempt to fill in the "comments" column by looking ; for text between "[" and "]" in the file header. ; ld b,7Fh ; look for "[" or zero, whichever comes first ld hl,CpmDma ; SrchLp: ld a,(hl) inc hl or a jr z,DunLin ; zero means done cp '[' jr z,DoCmt ; (we found it) djnz SrchLp ; (limit search to the one record we read) jr DunLin ; thats's all, go on to next LBR entry ; ; XMode -- List two-members per line with CRC and Index. Suppresses ; method, date stamp, real name, and embedded comment. ; XMode: ld hl,(MCRC) ; print CRC ld a,h call sa2hc ld a,l call sa2hc call PrSpc1 ld hl,(Index) ; print index call PrSDec ld a,(EolFlg) ; flip end-of-line flag cpl ld (EolFlg),a or a jr z,DunLin ; (end of line) call sprint ; print middle-of=line divider db ' | ',0 jr DunLnX ; ; DoCmt -- An embedded "comment" has been found, so display it. Comment ; text is nearly always in upper-case because it was entered from the command ; line and converted to caps by the CCP. Make the first character upper-case ; and the rest lower-case. ; DoCmt: call scrlf call CkAbrt ld b,LinLen ; number of characters allowed for comment ld c,0FFh ; (used to flag the first loop) call HiOn call sprint db ' [',0 ; CmtLp: ld a,(hl) ; get a character inc hl or a ; if zero we are done jr z,CmtDun cp ']' ; likewise a "]" character call z,zout jr z,CmtDun CmtLp1: inc c call nz,uncaps ; convert to lower-case if not first loop and 7Fh cp 20h call nc,zout ; ignore non-printable characters djnz CmtLp ; loop only for number of characters allowed CmtDun: call HiOff ; ; Finished with entry (and line unless alternate display), so move to next ; library member, if there is one. DunLnX is re-entry for alternate display ; Empty is re-entry for summary-only display. Both skip many lines of code. ; DunLin: call scrlf DunLnX: ld hl,(NFiles) ; decrement the member count dec hl ; ..to see if we're done ld (NFiles),hl ld a,h or l ld hl,(HLSave) ; before looping, restore HL (pointing to jp nz,NamLp ; ..next packed entry in DirBuf) call CkAbrt call DoEndg ; print final divider call CkAbrt Empty: ld a,CR call zout ld hl,CpmFcb+1 call PFName call sprint db ' members: ',0 ;SSkip3: ld hl,(MemCtr) ; get number of matching members ld a,l or h ; test for none push af ; save result for later call PrDec ; print how many members call sprint db ' matched, ',0 ld hl,(ActCtr) call PrDec call sprint db ' active',0 ld a,(WhlByt) ; check wheel byte or a jr z,Done ; (no summary for non-wheels) call sprint db ', ',0 ld hl,(OpnCtr) call PrDec call sprint db ' free, ',0 ld hl,(DelCtr) call PrDec call sprint db ' deleted, ',0 ld hl,(TotLen) add hl,hl add hl,hl dec hl call PrDec call sprint db ' total',0 ld a,(OpLFlg) ; for printer send a final CRLF or a call nz,lcrlf Done: ld a,(OpMFlg) or a call nz,DoMReg ; ( if M option, load message registers) pop af cpl ; cheap 255 for error flag if zero jp z,ErExit ; (no matching members) ; ; Set or reset ZCPR error flag. Entry at ErExit expects error code in A. ; Finish: xor a ; set error code to 0 (no error) ErExit: ld b,a ; save error code in B call Z3Chk jr z,Exit ; (no ZCPR3) ld a,b ; recover error code call puter2 ; set program error flag dec a ; if error code is not zero cp 0FEh ; ..and not FFh call c,inverror ; ..invoke error handler ; ; Return to CCP or do a warm boot if so configured. ; Exit: ld bc,(OpLFlg) ; BC = OpLFlg and OpFFlg ld a,b and c ; if both options are active ld a,FF ; ..send a form feed call nz,lout ld a,(OpQFlg) or a call z,hvdinit ; de-initialize terminal (unless quiet) ld sp,(Stack) ; ..restore stack ret ; ..and return to CCP ; ; Error routines . . . ; NoLBR: call ConOn ; turn on console output ld a,10 ; error code call sprint db BEL,' Library file not found.',0 jr ErExit ; Corupt: call ConOn ld a,4 ; error code call sprint db CR,LF,BEL,' Library file is corrupt.',0 jr ErExit ; DirBad: call ConOn ld a,2 ; error code call sprint db BEL,' Invalid directory.',0 jp ErExit ; Usage: call sprint ; program ID and version DftNam: db 'LD Version ' db Vers/10+'0','.',Vers mod 10+'0',SubVers,CR,LF db 'Usage:',CR,LF ; syntax db ' ',0 ld hl,comnam ; disk name call spstr call sprint db ' {dir:}lbrname {afn} {{/}options}',CR,LF db 'Options:',CR,LF db ' C ',0 ; option C ld hl,CmtFlg call PrDont call sprint db 'display embedded comments',CR,LF db ' X alternate display: ',0 ld a,(XFlag) ; option X or a ld hl,CrcMsg jr z,Usage0 ld hl,DSMsg Usage0: call spstr call sprint db CR,LF db ' S ',0 ; option S ld hl,SumFlg call PrDont call sprint db 'show summary only',CR,LF db ' D prefer ',0 ld a,(PrfFlg) ; option D ld hl,EmbMsg or a jr z,Usage1 ld hl,DirMsg Usage1: call spstr call sprint db ' date stamp',CR,LF db ' P ',0 ; option P ld hl,PagFlg call PrDont call sprint db 'page screen',0 ld a,(WhlByt) or a jp z,Usage3 ; (don't tell non-wheels about Q, M, L, and F) call sprint db CR,LF db ' Q quiet mode',0 ld a,(QtFlag) ; option Q or a call nz,PrOff call sprint db CR,LF db ' M ',0 ; option M ld hl,MemFlg call PrDont call sprint db 'put matching and free entries in registers ',0 ld hl,(MemReg) ld h,0 push hl ; PrDec destroys HL call PrDec ld a,'-' call zout pop hl inc hl inc hl inc hl call PrDec call sprint db CR,LF db ' L ',0 ; option L ld hl,LstFlg call PrDont call sprint db 'echo to printer',CR,LF db ' F ',0 ; option F ld hl,FFFlag call PrDont call sprint db 'send final form feed',0 Usage3: call sprint db CR,LF db 'Option X ',0 ; exception message ld a,(XFlag) or a ld hl,OvrMsg jr z,Usage4 ld hl,ReqMsg Usage4: call spstr call sprint db ' embedded comment display.',0 jp Finish ; PrDont: ld a,(hl) ; HL points to flag or a ret z ; (flag is zero, do nothing) call sprint db 'don''t ',0 ret ; PrOff: call sprint db ' off',0 ret ; ; Subroutines . . . ; ; PrcEnt -- Moves 25 key bytes from one entry into memory in DirBuf. HL ; points to library directory entry, DE increments through DirBuf. ; PrcEnt: inc hl ; skip flag -- we already know its active ld bc,25 ; bytes to be moved ldir ; (DE is incrementing through DirBuf) ld hl,(NFiles) ; OK to clobber HL now (but not DE) inc hl ; increment member files counter ld (NFiles),hl ld (MemCtr),hl ld a,(OvfTpa) ; make sure "DE" never approaches end of TPA sub d jp c,Corupt ; if so, consider library corrupt ret ; ; RdSect -- Read sequentially next sector to CpmDma. Kills BC. ; RdSect: push de ld de,CpmFcb ld c,FRead call bdos or a jp nz,Corupt ; if unexpected EOF error pop de ret ; ; RdHdr -- Read in 1st 128 bytes of member. Member's index is in Index. ; RdHdr: ld hl,(Index) ; get index of file ld (CpmFcb+33),hl ; put it in the rr field at fcb+33,34 xor a ld (CpmFcb+35),a ; make sure this is zero ld c,RRead ; prepare for random read ld de,CpmFcb call bdos ; read first sector of the file to the CpmDma or a jp nz,Corupt ; (operation failed) ret ; ; GetNam -- Print member's real (uncrunched or unsqueezed) filename. ; GetNam: ld a,'>' call zout ld hl,CpmDma+2 ; Filename area ld a,(SqFlag) ; Check for squeezed file inc a jr nz,GetNm1 ; Skip this if crunched inc hl ; Name field offset two bytes farther inc hl ; ..in squeezed files GetNm1: ld b,12 ; Necessary? ; GtNmLp: ld a,(hl) inc hl cp 10h ; usually 0 terminates. Stop at any of 16 ret c ; ..obviously non-ASCII bytes for future cp '[' ret z and 7Fh ; reset high bit call zout djnz GtNmLp ; (also could stop 3 bytes past ".") ret ; ; CkAbrt -- If paging is acive, check LinCtr and, if it's zero, wait for a ; keypress, reset LinCtr to MaxLns value (if key is space, reset LinCtr to 1). ; In addition, check console for a keypress and respond accordingly: ^C, ^K, ; ^X, C, K, or X mean abort; space sets LinCtr to 1; ^S pauses until another ; key is pressed. ; CkAbrt: push af ; save all registers push bc push de ld a,(OpPFlg) ; check OpPFlg or a jr z,ChkCon ; (skip screen paging) ld a,(EolFlg) ld b,a ld a,(OpXFlg) ; if option X and.. and b ; ..not end of line jr nz,ChkCon ; (skip it) ld a,(LinCtr) ; decrement line counter dec a ld (LinCtr),a jr nz,ChkCon ; (more lines to go) ld a,(MaxLns) ; get screen lines dec a ; decrement it by one ld (LinCtr),a ; ..and reset line counter call sprint db ' [more] ',0 call cin ; wait for key push af ; save character ld a,CR ; ..while we get back to column 1 call zout pop af jr Got1B ; ignore ^S ; ChkCon: call condin ; check for console key jr nz,Got1 ; (got one) ; RetAbt: pop de ; always return via this label pop bc pop af ret ; Got1: cp 'S'-40h ; ^S pauses call z,cin ; (if so, wait for another character) Got1B: cp ' ' ; space sets the line counter to one jr z,Set1 and 1Fh ; ^C, ^K, ^X, C, K, X all abort cp 'C'-40h jr z,Abrt cp 'K'-40h jr z,Abrt cp 'X'-40h jr nz,RetAbt ; ignore other keys ; Abrt: jp Finish ; exit direct ; Set1: ld a,1 ; set line counter to 1 ld (LinCtr),a jr RetAbt ; ; PFName -- Print filename addressed by HL, lower-casing attribute characters. ; PFName: ld b,8 call FnLp ld a,'.' ; inject a "." call zout ld b,3 ; fall through for filetype ; FnLp: ld a,(hl) inc hl bit 7,a ; high bit set? jr nz,FnLp1 ; (yes, handle it) call zout ; no, print as-is jr FnLp3 ; FnLp1: and 07Fh or 020h ; lower-case for attribute set cp 020h jr nz,FnLp2 ld a,'_' ; underline for space with attribute set FnLp2: call HiOn call zout call HiOff FnLp3: djnz FnLp ret ; ; PrDec -- Print a binary number in HL as up to four decimal characters. ; Entry PrSDec prints with leading spaces. Entry PrDec prints number only. ; Entry PrZDec prints with leading zeros. ; ;PrZDec: ld c,0FFh ; mask to print leading zeros ; jr DecOut ; PrDec: ld c,0 ; mask to suppress leading zeros jr DecOut ; PrSDec: ld c,0EFh ; mask to convert leading zeros to spaces ; DecOut: call Div10 ; divide number in HL by 10 ld a,l ; get remainder from L (0-9) push af ; save in reverse order for retrieval later ex de,hl ; old dividend becomes new divisor call Div10 ; repeat 3 times ld a,l push af ex de,hl call Div10 ld a,l push af ex de,hl call Div10 ld a,l push af ex de,hl ld b,3 ; loop counter ld a,c ; check mask or a jr z,NoZr ; (suppress leading zeros) DecLp: pop af ; type the 4 digits, with leading 0 suppression or a ; is it zero? jr z,LvMask ; leave mask set if so DoZrs: ld c,0FFh ; or cancel masking (of zeros to spaces) ; LvMask: add a,'0' ; convert to ASCII and c ; possibly blank a zero call zout ; output the character djnz DecLp ; do the first 3 digits ; Last1: pop af ; last digit is easy--never blank it add a,'0' ; convert to ACSII jp zout ; print it and return ; NoZr: pop af ; loop as long as we have zeros or a jr nz,DoZrs ; start printing djnz NoZr jr Last1 ; always print last digit ; ; Div10 -- Divide 16 bit value in HL by 10. ; Div10: push bc ; save BC ex de,hl ld hl,0 ; zero low byte ld bc,-10 ; skip the negation code ld a,11h ; 17 interations required to get all DE bits jr Um1 Um0: adc hl,hl ; Um1: add hl,bc ; Divide HLDE by -BC jr c,Um2 ; If it fits sbc hl,bc ; Else restore it or a ; Make sure carry is 0 ; Um2: rl e ; Result bit to DE rl d dec a jr nz,Um0 ; Continue pop bc ret ; ; DateQ -- obtains date from library directory or from crunched file ; headers, checking preferred source and, if no stamp is found, the ; second source. ; DateQ: ld a,(OpDFlg) ; option D? or a jr z,DateQ1 ; (no, prefer directory stamps) call ChkDS ; check for embedded stamp ret nc ; (got it) jr DateX ; none, check for directory stamp and return ; DateQ1: call DateX ; check for directory stamp ret nc ; (got it) jr ChkDS ; none, check for embedded stamp and return ; ; DateX -- Converts 2-byte date in DRI format (pointed to by IX) and ; 2-byte time in MS-DOS format (at IX+4) to DateStamper BCD Year, Month, ; Day, Hour, and Minit in buffer for printing. Returns carry set if ; no date is found. ; DateX: ld l,(ix+0) ; get date into HL ld h,(ix+1) ; (days since December 31, 1977) ld a,h ; zero means no date or l jr z,DateX1 ; (none, return carry) call CvtDat jr nz,TimeX ; (date okay) DateX1: scf ; set carry flag if no date ret ; TimeX: ld l,(ix+4) ; get time into HL ld h,(ix+5) call CvtTim xor a ; return with carry clear ld (SrcFlg),a ; set directory date as source ret ; ; ChkDS -- If no library date is found, look for an embedded date in ; header of crunched file (flagged by 01h after filename and before ; null header terminator). ; ChkDS: ld a,(CrFlag) ; If it wasn't crunched, don't even bother inc a ; 0ffh if crunched NotD: scf ; Else just set carry (means no date info) ret nz ; And return ld hl,CpmDma+2 ; Loop to look for DateStamped file ld b,13 ; Loop counter inc a ; Value to look for (1) Loop01: cp (hl) ; Compare, scanning forward inc hl jr z,GotIt ; Bingo! jr nc,NotD ; Must have hit the zero, N/G! djnz Loop01 ret ; Return with carry set ; GotIt: ld a,(Offset) ; offset to date we want add a,l ; on page 0, 8-bit add is OK ld l,a ; maybe advance, maybe not ld (SrcFlg),a ; set embedded date as source ld a,(hl) ; pointing to year call FlipFF ld (Year),a inc hl ld b,(hl) ; month in B inc hl ld a,(hl) ; day in A call FlipFF ld (Day),a ld a,b ; now month call FlipFF ld (Month),a inc hl ld a,(hl) ; get hour call FlipFF ld (Hour),a inc hl ld a,(hl) ; get minute call FlipFF ld (Minit),a ret ; FlipFF: inc a ; if FFh, should be zero ret z dec a ; otherwise, leave it alone ret ; ; CvtTim and CvtDat routines were lifted from Howard Goldstein's LBREXT . . . ; ; CvtTim -- Convert time from library in HL (MS-DOS format) to DateStamper. ; CvtTim: ld b,3 ; loop counter for shifting CvtTLp: srl h ; shift H right, LSB to carry rr l ; shift L right, carry to MSB djnz CvtTLp ; repeat 3 times -- when done, hours in H srl l ; shift L right, carry ignored srl l ; now have minutes in L ld a,h ; get hours call binbcd ; convert to BCD ld (Hour),a ld a,l ; now do minutes call binbcd ld (Minit),a ret ; ; CvtDat -- Convert date from library in HL (DRI format) to DateStamper. ; CvtDat: call jul2bin ; convert to binary, b=mo, c=yr, l=da or a ; test day ret z ; invalid if day=0 ld a,c ; get year call binbcd ld (Year),a ld a,b ; month call binbcd ld (Month),a ld a,l ; day call binbcd ld (Day),a ret ; ; ActivQ -- Checks library directory entry before reading it into DirBuf. ; Returns Z if the entry is OK, NZ if it is to be skipped (wildcard matcher ; adapted and shortened from LDIRZ by Rick Conn). ; ActivQ: ld a,(hl) ; must be an active member or a jr z,Activ inc a jr nz,NotOpn ld hl,(OpnCtr) inc hl ld (OpnCtr),hl dec a ret ; NotOpn: ld hl,(DelCtr) inc hl ld (DelCtr),hl ret ; Activ: push de ; save DE ld de,(ActCtr) inc de ld (ActCtr),de ld de,WldFcb ; point to user's wildcard ld a,(de) sub ' ' ; space? jr z,JustDE ; (yes, return Z) ; push hl ; save HL inc hl ; bump to member filename ld b,11 ; check 11 bytes GtEnt1: ld a,(de) ; ..for match with wildcards cp '?' jr z,GtEnt2 ; (match) cp (hl) jr nz,GtEnt0 ; (return NZ if no match) GtEnt2: inc hl ; point to next character inc de djnz GtEnt1 ; ..loop until Z GtEnt0: pop hl JustDE: pop de ret ; ; DoEndg, DoHedg -- Print heading and divider line to screen. Entry at ; DoEndg prints only divider string before summary line. ; DoEndg: ld a,(OpXFlg) ; X mode? or a jr z,DoEnd1 ; (no) ld hl,EolFlg ; end of line? ld a,(hl) or a jr z,DoEndX ; (yes) xor a ld (hl),a ; no, so reset flag to end-of-line call scrlf ; new line call CkAbrt jp DoEndX ; print ending line ; DoHedg: call PrHNam ld a,(OpXFlg) or a jp nz,DoHedX call sprint db 'Mth Created Modified Real Name',CR,LF,0 DoEnd1: call PrHE1 call PrHE2 jp scrlf ; ; DoHedX -- Printer header line and divider string for X Mode. Entry at ; DoEndX prints only divider string before summary line. ; DoHedX: call PrHCrc call sprint db ' | ',0 call PrHNam call PrHCrc call scrlf DoEndX: call PrHE1 call PrHE3 call sprint db ' | ',0 call PrHE1 call PrHE3 jp scrlf ; print new line and return ; ; PrSpcs -- Prints spaces. B = number to print. ; PrSpc1: ld b,1 ; 1 space jr PrSpcs PrSpc2: ld b,2 ; 2 spaces PrSpcs: ld a,' ' jr PrEqLp ; ; PrEqus -- Prints equal signs. B = number to print. ; PrEquX: ld b,14 PrEqus: ld a,'=' PrEqLp: call zout djnz PrEqLp ret ; ; PrHEn -- Prints part of divider string. ; PrHE1: ld b,12 call PrEqus ; member name ld b,3 call PrSpcs ld b,4 call PrEqus ; size ld a,'-' call zout ld b,7 jp PrEqus ; print equals and return ; PrHE2: call PrSpc1 ld b,3 call PrEqus ; method call PrSpc2 call PrEquX ; created call PrSpc2 call PrEquX ; modified call PrSpc2 ld b,13 jp PrEqus ; uncrunched name ; PrHE3: call PrSpc1 ; for X Mode ld b,4 call PrEqus ; CRC call PrSpc1 ld b,4 ; Index jp PrEqus ; print equals and return ; ; PrHNam -- Prints first part of header labels ; PrHNam: call sprint db 'Member Name Size ',0 ret ; ; PrHCrc -- Prints rest of heading in X Mode. ; PrHCrc: call sprint db 'CRC Index',0 ret ; ; ShoDat -- Prints date and time from 5-byte BCD DateStamper string in ; buffer. If month is zero (an invalid state), assumes no date or time ; exists. ; PrDate: call spstr ; print appropriate date message ShoDat: ld a,(Month) ; is there a date? or a jr z,DatLes ; (nope) ld a,(DatFlg) ld hl,Year call sdats3 ld a,(SrcFlg) or a ld a,(EmbChr) call nz,zout call z,PrSpc1 ld a,(TimFlg) call stims2 jp PrSpc1 ; space and return ; ; DatLes -- Prints if no date is found. ; DatLes: call sprint db '-- -- -- -- -- ',0 ret ; ; GetOpt -- Checks for command line options. If second token begins with ; slash, assumes it is option list and wipes out spec in WldFcb. If ; options are third token, no slash is necessary, but it's okay. ; GetOpt: ld hl,CmtFlg ; move default options ld de,OpCFlg ld bc,9 ; nine of them ldir ld hl,CpmDma+1 call eatspc ; move past first token call eatnspc call eatspc jp z,FixOpt ; (no options) cp '/' ; slash? call z,NoWild ; it's options, not filespec jr z,GotOpt ; (we've got options) call eatnspc ; move past second token call eatspc jp z,FixOpt ; (no options) cp '/' jr nz,GotOp1 ; (we've got options) GotOpt: inc hl ; point to next character GotOp1: ld a,(hl) ; get option or a jr z,FixOpt ; (end of options) cp 'C' ; comments? jr z,OptC cp 'F' ; form feed? jr z,OptF cp 'S' ; summary only? jr z,OptS cp 'L' ; printer? jr z,OptL cp 'P' ; paging? jr z,OptP cp 'X' ; alternate display? jr z,OptX cp 'Q' ; quiet? jr z,OptQ cp 'M' ; message registers? jr z,OptM cp 'D' ; date source? jr z,OptD cp '/' ; obvious error, but we'll allow it jp z,Usage cp ' ' ; skip intervening and trailing spaces jr z,GotOpt ld a,19 ; error code call sprint db BEL,' Invalid option.',0 jp ErExit ; OptC: ld de,OpCFlg ; display embedded comments flag jr DoOpt ; OptF: ld de,OpFFlg ; form feed printer jr DoOpt ; OptS: ld de,OpSFlg ; point to summary option flag jr DoOpt ; OptL: ld de,OpLFlg ; printer output flag jr DoOpt ; OptP: ld de,OpPFlg ; screen paging flag jr DoOpt ; OptM: ld de,OpMFlg ; message register flag jr DoOpt ; OptD: ld de,OpDFlg ; date stamp source jr DoOpt ; OptQ: ld de,OpQFlg ; quiet flag jr DoOpt ; OptX: ld de,OpXFlg ; ; DoOpt: ld a,(de) ; get flag cpl ; flip it ld (de),a ; restore it jr GotOpt ; ; FixOpt -- Fix competing options (Q, P, and L) ; FixOpt: ld a,(OpQFlg) or a ; quiet mode? jr z,FixOp1 ; (nope) cpl ld (OpPFlg),a ; yes, turn paging off ld (sctlfl),a ; ..and turn off output FixOp1: ld a,(WhlByt) ; check wheel byte or a jr nz,FixOp2 ; (it's set) ld (OpLFlg),a ; wheel is off, so cancel printer output FixOp2: ld a,(OpLFlg) or a ret z ; (no printing, so return) cpl ld (OpPFlg),a ; turn off paging ld hl,sctlfl ; point to S control flag ld a,10000000b ; mask for list output or (hl) ld (hl),a ret ; NoWild: ld a,' ' ; loads space character into ld (WldFcb),a ; ..first byte of WldFcb ret ; ; ConOn -- Unconditionally starts console output. ; ConOn: ld hl,sctlfl ; point to S control flag ld a,00000001b or (hl) ld (hl),a ret ; ; Z3Chk -- Checks for ZCPR3 environment by assuming that a non-zero ; descriptor address means one exists. Uses A and HL. ; Z3Chk: ld hl,(Z3EAdr) ld a,h or l ret ; ; DoMReg -- Load four message registers with number of matching files ; (2 bytes) and number of free directory entries (2 bytes). If not ; ZCPR3, does nothing. If ZCPR3, but no message buffer, reports error ; and exits. ; DoMReg: call Z3Chk ret z ; (if not ZCPR3, do nothing) call getmsg ; get message buffer address jp z,NoMsg ; (no message buffer) ld a,(MemReg) ; get first storage register add a,30h ; add offset ld e,a ld d,0 add hl,de ex de,hl ; register address in DE ld hl,MemCtr ; point to needed results ld bc,4 ; bytes to move ldir ret ; NoMsg: call ConOn ; turn on console output ld a,4 ; error code call sprint db CR,LF,BEL,' No message buffer.',0 jp ErExit ; ; HiOn and HiOff -- Turns highlighting on and off unless in quiet mode. ; HiOn: push af ; save AF ld a,(OpQFlg) or a call z,hvon pop af ret ; HiOff: push af ld a,(OpQFlg) or a call z,hvoff pop af ret ; ; We can save some bytes by preventing SPRINT and SPSTR from loading ; these (which we don't need). ; csout: jp zout ccout: jp cout clout: jp lout ; ; Messages and initialized data . . . ; ; Library date labels CreMsg: db 'Created: ',0 ModMsg: db ' Modified: ',0 ; Fractional kilobytes Fracts: db '.00k ',0 ; 0k db '.12k ',0 ; 1/8k db '.25k ',0 ; 1/4k db '.37k ',0 ; 3/8k db '.50k ',0 ; 1/2k db '.62k ',0 ; 5/8k db '.75k ',0 ; 3/4k db '.87k ',0 ; 7/8k ; Compression methods StoMsg: db '---',0 SqMsg: db 'SQ ',0 CrMsg: db 'CR ',0 LzhMsg: db 'LZH',0 ; Usage screen modifiers CrcMsg: db 'CRC''s and indexes',0 DSMsg: db 'date stamps, real names',0 ReqMsg: db 'required for',0 OvrMsg: db 'overrides',0 EmbMsg: db 'embedded',0 DirMsg: db 'directory',0 ; ; Uninitialized data . . . ; DSEG ; ; Following 10 bytes are a structure MCRC: ds 2 ; member CRC CDate: ds 2 ; date in DRI format (number of days MDate: ds 2 ; ..since December 31, 1977) CTime: ds 2 ; time in MS-DOS format MTime: ds 2 ; ; Following 5 bytes are a structure Year: ds 1 ; BCD year } Month: ds 1 ; BCD month } DateStamper Day: ds 1 ; BCD day } format Hour: ds 1 ; BCD hour } Minit: ds 1 ; BCD minute } ; ; Following 9 bytes are a structure OpCFlg: ds 1 ; FFh=print embedded comments, 0=don't OpSFlg: ds 1 ; FFh=summary only, 0=whole thing OpDFlg: ds 1 ; FFh=prefer crunched date, 0=directory date OpPFlg: ds 1 ; FFh=screen paging, 0=no paging OpLFlg: ds 1 ; FFh=echo to printer, 0=don't OpFFlg: ds 1 ; FFh=send form feed, 0=don't OpXFlg: ds 1 ; FFh=CRC, 0=date stamps OpQFlg: ds 1 ; FFh=quiet, 0=verbose OpMFlg: ds 1 ; FFh=results to message registers, 0=don't ; Offset: ds 1 ; offset to date in crunched files DirLen: ds 2 ; directory length, number of records Index: ds 2 ; an RA index value to beginning of member file ZerFlg: ds 1 ; 0 if zero-length member file WhlByt: ds 1 ; 0=wheel off, non-zero=wheel on HLSave: ds 2 ; temporary storage for HL OvfTpa: ds 1 ; page below top of memory LinCtr: ds 1 ; line counter for "[more]" prompt NFiles: ds 2 ; overall loop counter for program operation MemCtr: ds 2 ; matching members counter } 4-byte OpnCtr: ds 2 ; open (free) members counter } structure TotLen: ds 2 ; storage for intial NFiles value ActCtr: ds 2 ; active members counter DelCtr: ds 2 ; deleted (marked) members counter CrFlag: ds 1 ; FFh if crunched, other values undefined SqFlag: ds 1 ; FFh if squeezed, other values undefined EolFlg: ds 1 ; FFh if line not filled (Option X) SrcFlg: ds 1 ; 0=directory date, non-zero=embedded date InitSz equ $-NFiles WldFcb: ds 11 ; safe storage for AltFcb filenametyp DirBuf: ds 2 ; address of directory buffer ; ds 128 ; stack area for program's use ; Stack: ds 2 ; stack pointer storage ; end