;Program: LBREXT ;Version: 2.0 ;Author: Bob Peddicord ;Date: 09/04/87 ver equ 34 ; September 27, 1991 ;This program is something like Richard Conn's LGET. The main ;differance is that this program will extract "CRUNCHED" and ;"SQUEEZED" files. It has a brief help display, invoked by ;typing // after the name. ex:lbrext // ;The only option is "U" to unsqueeze or uncrunch a file, ;otherwise the program will just extract whatever you ;specify. ;Wildcard filename(s) may be specified Don't forget to put a ;"," between filenames if specifying more then one filename. ;Example: LBREXT dir:lbrname dir:filename.typ,dir:filename.typ... o ;See file LBREXT.HST FOR REVISION HISTORY eof equ 1ah bdos equ 5 bell equ 7 bs equ 8 cr equ 0dh lf equ 0ah tbuff equ 0080h lentsz equ 17 ; Size of dir entry: ; 11 - for FN.FT ; 2 - for Index ; 2 - for Length ; 2 - for CRC ;DSLIB routines extrn timini,rclock,pstamp,bin2bcd ;Extra labels in modified LUOPEN (SLUOPEN.REL) routine extrn ludate,lumdate,lutime,lumtime ;From Z33LIB for more authentic parsing extrn z33chk,z33fname ;Z3LIB routines extrn z3init,zprsfn,z3log,getefcb,gzmtop,whrenv ;ZSLIB routines extrn jul2bin,prdat3 ;SYSLIB routines extrn putud,getud,logud,retud extrn eprint,epstr,cout,crlf extrn pfn3,initfcb,caps,getmtop extrn f$delete,f$close,f$write,f$make,setdma extrn luinit,luread,luopen,r$read,luclose extrn capine,condin,f$exist,pafdc,@afncmp extrn crc3init,crc3clr,crc3upd,crc3done extrn codend ; ****** needed for unsqueezing/uncrunching ****** extrn usqrel,unlzh,uncrel ; Entry points for usqrel, unlzh and uncrel public getbyt,out,glzhun,plzhun ;We begin.... jp start db 'Z3ENV' db 1 z3eadr: dw 0fe00h ; Options odflt: db 0 ; Overwrite existing file (default no) udflt: db 0 ; Uncopress files (default no) db 'LBREXT' ; Config file name for ZCNFG db (ver/10)+'0',(ver mod 10)+'0' idflt: db 0 ; Inspect mode (default no) start: ld (savstk),sp ld sp,stack ld hl,(z3eadr) call whrenv ; Get real environment address ld (z3eadr),hl ld (zflag),a call z3init ld hl,(odflt) ; Store user-patchable options ld (oflag),hl ; ..in working storage ld a,(idflt) ld (iflag),a call putud call codend call crc3init ; Init crc table inc h inc h ld (cmdline),hl ld l,80h ; Pseudo-add for cmdline length ld (filebuf),hl ld de,3400+0ffh add hl,de ld a,h ld (fbufhi),a ; Ptr to absolute end of file buffer ld hl,tbuff+1 ld de,(cmdline) ld bc,128 ldir ld hl,(cmdline) ld de,argtable ld a,3 ; Init. table in DSEG for 3 args ld (de),a ld a,0ffh call argv ld a,(argcnt) ; Check count cp 2 jp nc,nohelp help: call eprint db 'LbrExtract, Version ',[ver/10]+'0','.',[ver mod 10]+'0' db cr,lf db ' Syntax: ',0 call getefcb jr z,noefcb ld b,8 comnlp: inc hl ld a,(hl) and 7fh cp ' ' call nz,cout djnz comnlp jr cmnend noefcb: call eprint db 'LBREXT',0 cmnend: call eprint db ' dir:library' db ' dir:afn1,dir:afn2,... o' db cr,lf db 'Options:' db cr,lf db ' U - ',0 ld a,(uflag) call prdont call eprint db 'Uncompress squeezed/crunched/LZH-encoded files' db cr,lf db ' O - ',0 ld a,(oflag) call prdont call eprint db 'Overwrite existing files' db cr,lf db ' I - ',0 ld a,(iflag) call prdont call eprint db 'Inspect (confirm files before extracting)' db cr,lf,0 jp badarg ; Print the word "don't" if the flag passed in A is non-zero prdont: or a ret z call eprint db 'Don''t ',0 ret nohelp: cp 3 jr c,noarg ld hl,(opptr) caseloop: ld a,(hl) or a jr z,noarg cp '/' jr z,help1 cp ' ' jr z,help1 cp 'U' jr z,unsq cp 'O' jr z,ovrwrt cp 'I' jr z,insp errrtn: call eprint db ' Invalid Option:' db ' ' db 0 call cout call crlf jp help ovrwrt: ld de,oflag jr togopt insp: ld de,iflag jr togopt unsq: ld de,uflag togopt: ; Toggle option and store ld a,(de) ; Get option flag cpl ; Flip it ld (de),a ; Store in memory help1: inc hl jr caseloop noarg: ld hl,(lbrnptr) ; Pt to lbr name ld de,ludfcb call zpars ; Parse it in call z3log ; Do z3 log call retud ; Get lbr DU ld (lbrdu),bc ; And save it ld de,lbrtyp ld a,(de) ; Get first char cp 20h jr nz,noarg1 ; If not blank, leave type alone ld hl,deflbr ; Set default type ld bc,3 ldir noarg1: ld de,lud call luinit ; Init it for later jr z,lbrfnd ; Go process file call eprint db 'Library File ',0 ld de,lbrname call ntfnd badarg: call getud ld sp,(savstk) ret lbrfnd: xor a ld (filcnt),a ; Make sure counter is zero ld (comflg),a ; Ditto comma flag ld hl,(fileptr) ; Pt to file name wanted ; this is the main loop for getting file names mloop: ld a,(hl) or a ; If 0 were at end of buffer jr z,badarg call getud ld de,lfcb ; Parse in file wanted call zpars ld a,(hl) cp ',' ; See if more than 1 name jr nz,nosep ld (comflg),a ; Set comma found flag inc hl ld (fileptr),hl ; Save ptr for later nosep:: call z3log ; Log into parsed DU call retud ld (outdrv),bc ld bc,(lbrdu) ; Log into lbr du call logud inc de ; Point to filename ld a,(de) cp ' ' ; Is first char of name a space? jr nz,mloop2 ; No, skip this ; Filename is blank. Fill with "?" making it wild. ld h,d ld l,e ; In hl ld bc,11*256+8 ; Init two counters in b & c mloop1: ld (hl),'?' inc hl dec c ; End of name portion? jr nz,mloop1a ; No, continue filling cp (hl) ; Is type also blank? jr nz,mloop2 ; No, quit now MLOOP1A: DJNZ MLOOP1 mloop2: EX DE,HL ld de,lud ; Pt to lbr buffers ld bc,(filebuf) ; Get filebuf location call ldbuf ; Load buffer jp nz,ovrflow ; No good we overflowed buffer ld a,(filcnt) ; Get file count or a ; Test it jp z,nofile ; No files found ld b,a ; File count to B ld hl,(filebuf) ; Pt to file buffer ; files were found filfnd: ld a,(iflag) ; Inspect mode requested? or a jr z,filfnd1 ; (no) ; Inspect option. Enter with file count in B and pointer to file ; buffer in HL. push hl ; save buffer pointer call eprint db 'Inspect -- Yes, No (def), Skip rest',cr,lf,0 xor a ld (skpflg),a ; Init skipping flag INSPLP: LD A,(SKPFLG) ; In skip mode or a jr nz,noext ; Yes, just flag file for no extract call eprint db ' Extract ',0 ld d,h ld e,l ; Filename pointer to DE call pfn3 ; Print name call eprint db '? ',0 call capine ; Get response call crlf cp 3 jp z,badarg ; Exit program if ctrl-c entered cp 'Y' jr z,inspend ; If yes just bump to next file cp 'S' jr nz,noext ld (skpflg),a ; Set skip flag if so requested noext: ld (hl),0 ; Indicate no extract for this file inspend: ld de,lentsz add hl,de ; Point to next entry in buffer djnz insplp ; ..and loop till done pop hl ; Point to beginning of buffer filfnd1: ld (filptr),hl ; Save buffer ptr call openit ; Try and open file ; Return here after successful file extraction ld hl,filcnt ; Get file count dec (hl) ; Decrease by 1 jr z,chkcom ; If zero, check for comma flag ld hl,(filptr) ; Get buffer ptr back ld de,lentsz ; Pt to next file, all files 17 bytes long add hl,de jr filfnd1 ;----------------------------------------------------------------------------- nofile: call eprint db cr,lf db ' No Files Found for ',0 ld de,lfcb+1 call pfn3 ; Print the file name chkcom: ld a,(comflg) ; Get comma flag or a ; Check it jp z,badarg ; If not set no more files wanted jp lbrfnd ; Process other file(s) ;----------------------------------------------------------------------------- ovrflow: call eprint db cr,lf db ' Buffer Overflow',0 jp badarg ;----------------------------------------------------------------------------- openit: ld a,(hl) ; Get first character of member filename or a ; Zero means don't extract ret z ld bc,(lbrdu) call logud ld de,lud call luopen ; Open file jr z,fopen ex de,hl ; DE pts to file name ntfnd: call pfn3 ; Print file name call eprint db ' Not Found',cr,lf,0 ret fopen: ld de,lfcb+1 ; Move to local fcb ld bc,11 ldir ld hl,usrdat ; Prepare to zero fill current t/d ld b,15+6 ; ..and file stamp buffer push hl fildt: ld (hl),a ; Zero fill; a=0 from above inc hl djnz fildt pop de ; DE pts to usrdat ld hl,(ludate) ; Julian date from lbr in hl call dcvt ; Convert and store in usrdat ld de,usrdat+10 ; And again for modify date ld hl,(lumdate) call dcvt ld hl,(lutime) ; MSDOS-format create time from LBR LD DE,USRDAT+3 ; Place to store time call tcvt ; Convert and store ld hl,(lumtime) ; And again for modify time ld de,usrdat+13 call tcvt ; Display input file name and date if available call eprint db ' File: ',0 ; Display file name ld de,lfcb+1 call pfn3 ld hl,usrdat+11 ; Pt to modify month ld a,(hl) or a jr z,nodate ; No date if month=0 dec hl ; Pt back to year call eprint db ' (',0 call prdat3 ld a,')' call cout nodate: call eprint db ' ---> ',0 call proutdu ; Print output file's du ld hl,(buffer) ; Point to end of member list ld de,0ffh add hl,de ; Adjust to page boundary xor a ld l,a ld (inbuf),hl ; Input buffer starts here ld (typflg),a ; Assume member file not compressed inc a ld (bufsiz),a ; Input buffer is one page for now call crc3clr ; Clear crc accumulator call reload ; read in first 2 records ld hl,secnt ; Point to sector count ld b,(hl) ; put in B inc (hl) ; bump sector count (for 1st call to getbyt) ld a,(uflag) ; get uncompress flag and b ; And with unbumped sector count jr z,openout ; Skip this if 0-length file or not uncunching ld hl,(inbuf) ; Pt to beginning of 1st record ld a,(hl) cp 76h ; Test for compression signature jr nz,openout inc hl ld a,(hl) inc hl cp 0fdh jr c,openout ; Not a compressed file ld (typflg),a ; Store copression type cp 0ffh jr nz,crnchd ; Crunched file, go get name ld (hl),a ; Squeezed files have 2 extra bytes in header inc hl ; ..which must be forced non-zero ld (hl),a ; ..because of a bug in the unsqueeze module inc hl crnchd: call pname ; print original file name and store in LFCB ; If member is crunched, pick up possible date info and print out comment ; field ld a,(typflg) ; Determine type of compression inc a jr z,openout ld a,(hl) ; Get char or a ; Could be terminated by zero jr z,openout cp 1 ; DateStamper prefix? jr nz,cklfbr inc hl ld b,15 ; Have DS prefix ld de,usrdat ; Move 15 bytes of DS data todslp: ld a,(hl) cp 0ffh ; If 0ffh, flip to 00 jr nz,todsbf cpl todsbf: ld (de),a inc hl inc de djnz todslp ld a,(hl) or a jr z,openout cklfbr: cp '[' ; Could have comment stamp jr nz,openout call eprint db ' ',0 ; 3 spaces call epstr ; Print up to null terminator openout: ld bc,(outdrv) call logud ; Log into output du ld de,lfcb call initfcb call chkfile ; See if file exists ret z ; Return to call if zero flag set call f$make ; Make output file inc a ; Check return jr nz,setup call eprint db bell,'Directory full!',0 jp badarg ; Allocate input and output buffers ; Input buffer begins at page following last member entry in FILBUF. ; The buffers use all available memory from this point up less the ; amount required by the tables for the decompression algorithm used ; for this member. setup: ld a,(typflg) inc a ld c,16 ; Unsqueeze requires 16 page table jr z,setup1 inc a ld c,96 ; Uncrunch requires 96 page table jr z,setup1 inc a ld c,32 ; UNLZH requires 32 page table jr z,setup1 ld c,0 ; No compression, no table setup1: call getmtop ; Determine top of memory the CP/M way ld a,(zflag) ; Is this a Z-System? or a call nz,gzmtop ; Get top of memory the Z way if so ld a,h ld hl,(inbuf) ; Get beginning of input buffer sub h ; Deduct pages of memory used. sub c ; ..and memory to be used for tables jr c,nomem jr z,nomem srl a ; Divide in half. jr nz,setup2 nomem: call eprint db bell,'Not enough memory',0 jr errexit setup2: ld b,a ; Stash in B. ld (bufsiz),a ; And in storage for later. push hl add a,h ld h,a ld (outbuf),hl ; Ptr to output buffer push hl add a,b ld (obufhi),a ; Ptr to end of buffer ld h,a exx pop de ; Output buffer address in de' pop hl ; Input buffer address in hl' exx ; Extract file with appropriate decompression ld a,(typflg) inc a jr z,usq inc a jr z,uncr inc a jr z,unlz ; Fall through to straight extract inloop: call getbyt ; Get byte jp c,done ; We're done if carry flag set call out ; Output byte jr inloop ; Otherwise loop usq: call usqrel jr expend ; Jump to common code unlz: call unlzh jr expend uncr: call uncrel ; Common code executed after member has been expanded expend: jp nc,done ; Success: tidy up and return call eprint db bell,'File expansion error',0 errexit: call eprint db ', deleting partial output file ',0 call proutdu ; Print output file's du call logud ; log into DU ld de,lfcb+1 call pfn3 dec de call f$close call f$delete ; Delete bad file jp badarg ;----------------------------------------------------------------------------- ; "a" <-- next byte from ("physical") input stream. ; returns with carry set on eof. glzhun: getbyt: exx ; Switch to i/o regs ld a,l ; Pointer to next avail char and 7fh ; See if 00h or 80h and clear carry call z,posrld ; "possibly reload" the buffer if 00 or 80h ld a,(hl) ; Get byte to return (garbage if eof) inc hl ; Advance input pointer exx ; Back to normal regs & rtn ret ; ;................................ ; posrld: ; "possibly reload" the input buffer ; I/o regs are active call condin ; Check for user abort xor 3 jp z,abtrtn ld a,(secnt) ; Decr sector count (for this buffer) dec a ; ld (secnt),a ; ret nz ; Return if buffer not empty ;.............................................................................. ; ; reload the input buffer, & reset hl" to point to the beginning of it. as- ; sumes input bfr starts page boundary and is of page multiple length. the ; i/o registers are active. ; ld a,(eoflag) or a jr nz,zeread reload: push de ; ld bc,(lbrdu) call logud ; Log to the input file user area ld a,(bufsiz) ld b,a ; loop counter, buffer length in pages ld hl,(inbuf) ; Beg of buffer push hl ; Save for later ld c,0 ; Will count sectors actually read ld de,lud rldlp: ld l,0 ; Lo byte of current dma call rdsec ; Read in 128 bytes (1/2 page) jr nz,rldrtn ; (return if eof enecountered) inc c ; Incr "sectors read" count ld l,80h ; To read in the next half page call rdsec ; Do that jr nz,rldrtn ; As above inc c ; inc h ; Next page djnz rldlp ; Loop till done rldrtn: ld (eoflag),a ld a,c ; Put count of sectors read into "secnt" ld (secnt),a ; pop hl ; Reset input pointer to beg of input buffer pop de ; Restore regs and a ; Return w/ clr carry jr z,zeread ; Compute CRC on what we've read. C contains sector count. ; push hl crclp: ld b,128 ; 128 bytes/sector crcsec: ld a,(hl) ; Get a character call crc3upd inc hl ; Point to next djnz crcsec dec c ; Count down sectors jp nz,crclp pop hl ret ; Carry is clear zeread: scf ; Set flg indicating no sectors were read (eof) ret ; ;.............................................................................. ; ; subr for [ non multi-] reload, reads 128 bytes to memory starting at de ; rdsec: call setdma ; jp luread ; Read a record ;______________________________________________________________________________ ; ; output char in 'A' to the output buffer. ; plzhun: out: exx ; Switch to i/o regs ld (de),a ; Put byte into the next avail position inc e ; Increment pointer jr nz,rtout1 ; Return if not on a 256 byte boundary push af ; Save caller"s char inc d ; Incr pointer high byte ld a,(obufhi) ; Limit cp d ; Check jr nz,retout ; Ret if limit not reached ; If so, write the output buffer to disk ld a,(bufsiz) ; Number of 128 byte records to write add a,a ld b,a call wrtout ; Writes out 'b' 128 byte records ld de,(outbuf) ; Reset pointer to beginning of bfr & rtn. retout: pop af ; Restore caller's char, flip regs & rtn rtout1: exx ; ret ; ;______________________________________________________________________________ ; ; write partial or full output buffer to disk. ; the #of records to be written is specified in "b". ; wrtout: push bc ld bc,(outdrv) call logud ; Log to the output file user area pop bc ld a,b ; See if zero sectors spec"d or a ; ret z ; Simply return if so push hl ; Save input buffer ptr ld hl,(outbuf) ; Init dma addr to beg of output bfr ld de,lfcb ; Spec the output file wrtlp: call wrsec ; Write 128 bytes dec b ; jr z,endwrt ; Return if done ld l,80h ; Else incr by 1/2 page call wrsec ; inc h ; Inc hi-byte, 0 the lo to effect ld l,0 ; Another 80h incr djnz wrtlp ; Loop till done endwrt: pop hl ; ret ; ;.............................................................................. ; ; aux subr for above. writes 128 bytes from current val of de. ; wrsec: call setdma ; call f$write ; Do it ret z ; Rtn, assuming no error call eprint ; "disk full." db 'Disk or directory full',0 jp errexit ; ;______________________________________________________________________________ ; ; output the partial output buffer thru the current pointer (de"). if not on ; a sector boundary, fill the remainder with "1a""s. close files & see if ; there are any more of them. ; done: exx ; Determine where nearest record boundary is ld a,e ; Get low byte of output pointer exx ; neg ; Compute how far to next page boundary and 7fh ; Convert to distance to next half-page bndry jr z,onbndy ; If there already (should be the case on uncr) ld b,a ; Else set up to fill rest of sector w/ eof's ld a,1ah ; fillp: call out ; Do that djnz fillp ; onbndy: exx ; Compute #of sectors to write to disk ex de,hl ; Put output pointer in hl ld bc,(outbuf) ; (ok to clobber bc" now, uncr is done w/ it) and a ; (clr carry) sbc hl,bc ; How far into the buffer we are add hl,hl ; Effectively divide difference by 128 ld b,h ; "b" now has #of recs to be written call wrtout ; Do that exx ld hl,(filptr) ; Point to lbr dir entry ld de,lentsz-2 ; Offset to crc add hl,de ld e,(hl) ; Put crc in de inc hl ld d,(hl) call crc3done ; Computed crc to hl sbc hl,de ; Compare (carry cleared by add above) jr z,closfl call eprint db bell,'CRC Error',cr,lf,0 closfl: ld de,lfcb ; Close output file call f$close call timini ; Determine type of date stamping jr z,noclok ; Branch ahead if none ld hl,usrdat+1 ; Point to create month in date buffer ld a,(usrdat+11) ; Get modify month or (hl) jr z,noclok ; If both 0 then no date ld hl,curdt ; Get current date and time push hl call rclock pop hl ld de,usrdat+5 ; ..and stuff it into access date field ld bc,5 ldir ld de,lfcb ; Point to output FCB ld hl,usrdat ; ..and to date buffer call pstamp ; Hl is pointing to usrdat noclok: ld bc,(lbrdu) call logud ld de,lud call luclose ret ;----------------------------------------------------------------------------- ; PNAME - print squeezed/crunched name pname: ld de,lfcb+1 ld b,9 ; 8 chars for filename + 1 for period call dsp1 ld b,3 ; 3 chars for type dsp1: ld a,(hl) ; Get char or a ; Check for end of filetype jr z,dsp2 ; (Squeeze doesn't space fill) call caps call cout ; Display char inc hl cp '.' ; Separator? jr z,dsp3 ld (de),a ; Put it inc de djnz dsp1 ret dsp2: inc b ; Adjust counter (null doesn't print) dsp3: ld a,20h dsp4: dec b ; test counter ret z ; No fill if zero ld (de),a ; Space fill inc de jr dsp4 ;----------------------------------------------------------------------------- proutdu: ; Print output file's du: ld bc,(outdrv) ld a,b add a,'A' call cout ld a,c call pafdc ld a,':' jp cout ; Display colon and return ;----------------------------------------------------------------------------- chkfile: ld hl,tbuff call setdma ld a,(oflag) inc a jr z,chkf1 call f$exist ; See if file is there jr z,chkf1 ; File not there call eprint db cr,lf,bell db 'File exists, overwrite (y/n)?',bs,0 call capine ; Get response cp 3 jp z,badarg cp 'Y' jr nz,chkf2 chkf1: call crlf or 0ffh ret chkf2: call crlf xor a ret ;----------------------------------------------------------------------------- ; LDBUF - load lbr directory to memory buffer ; Return nz if overflow. ldbuf: ld (file),hl ; Save ptr to file name ld (buffer),bc ; Save ptr to memory buffer ld hl,tbuff call setdma ld hl,ludfcb ; Pointer to FCB ex de,hl ; DE = FCB ld c,(hl) ; Get length of directory inc hl ld b,(hl) ld hl,0 ; Read directory in (record 0) loop: call r$read ; Random read ret nz ; File not found if error push hl ; Save key regs push de push bc call scan ; Scan for file name match and build buffer pop bc ; Restore key regs pop de pop hl ret nz ; Buffer overflow inc hl ; Pt to next record dec bc ; Count down length of dir ld a,b ; Done? or c jr nz,loop ret ; ; Scan TBUFF for file names ; If memory overflow, A is non-zero and Zero Flag clear ; If OK, A=0 and zero flag set ; scan: ld hl,tbuff ; Pt to buffer ld b,4 ; 4 entries possible scan1: ld a,(hl) ; Check for active entry inc hl ; Pt to name or a ; 0=active entry jr nz,scanxt push bc ; Save count push hl ld a,(hl) cp 20h ; Check for blank (directory entry) jr z,scanlp2 ex de,hl ld hl,(file) ; Pt to file name ld b,11 ; 11 bytes scanlp: call @afncmp ; Compare file names jr nz,scanlp2 pop hl ; We have a match - pt to entry with HL push hl ld de,(buffer) ; Get address of next buffer entry ld bc,lentsz ; Entry size ldir ld a,(fbufhi) ; Check for overflow cp d jr z,scanerr ; Buffer overflow ld (buffer),de ; Save ptr for next copy ld hl,filcnt ; Point to file count inc (hl) ; And add 1 to it scanlp2: pop hl ; Pt to current pop bc ; Get count scanxt: ld de,31 ; Pt to next add hl,de djnz scan1 xor a ; Set no error ret scanerr: or a ; Return nz for error pop hl ; Fix stack pop bc ret ; abort routine for cancled output ; abtrtn: exx ; Return to normal registers call eprint db bell,'Abort requested',0 jp errexit ; SYSLIB Module Name: SARGV ; Author: Richard Conn ; SYSLIB Version Number: 3.6 ; Module Version Number: 1.1 ; public argv ; ARGV is a UNIX-style ARGC/ARGV string parser. It is passed ; a null-terminated string in HL and the address of a token pointer ; table in DE as follows: ; LXI H,STRING ; LXI D,ARGV$TABLE ; MVI A,0 ; do not mark token end ; CALL ARGV ; JNZ TOKEN$OVFL ; indicates more tokens than allowed ; ... ; ARGV$TABLE: ; DB MAX$ENT ; max number of entries permitted ; DS 1 ; number of entries stored by ARGV ; DS 2 ; pointer to token 1 ; DS 2 ; pointer to token 2 ; ... ; DS 2 ; pointer to token MAX$ENT ; Tokens are delimited by spaces and tabs. ; As well as '='. 27 Feb 86 jww ; On input, if A=0, the end of each token is not marked with a null. ; If A<>0, a null is placed after the last byte of each token. ; If all went well, return with A=0 and Zero Flag set. If there ; are possibly more tokens than pointers, return with A=0FFH and NZ. argv: push bc ; Save regs push de push hl ld c,a ; Save mark flag ex de,hl ld b,(hl) ; Get max entry count push hl ; Save address of max entry count inc hl ; Pt to token count inc hl ; Pt to first pointer ; On each loop, DE = address of next char in string and HL = address of ; next pointer buffer; B = number of pointer buffers remaining and C = ; mark flag (0 = no mark) argloop: call skspc ; Skip spaces and tabs in string pted to by DE or a ; End of string? jr z,argdone ld (hl),e ; Store low inc hl ld (hl),d ; Store high inc hl dec b ; Count down jr z,loop2 call sknspc ; Skip until end of token or a ; Done? jr z,argdone ld a,c ; Get mark flag or a ; 0=no mark jr z,loop1 xor a ; Mark with null ld (de),a ; Store null inc de ; Pt to next char loop1: ld a,b ; Check count or a jr nz,argloop ; Continue on loop2: call sknspc ; Skip over token call skspc ; Any tokens left? or a jr z,argdone ; None if EOL or 0ffh ; Make A = 0FFH to indicate more to come argdone: pop hl ; Get address of max token count push af ; Save return flags ld a,(hl) ; Get max token count sub b ; Subtract counter inc hl ; Pt to return count ld (hl),a ; Set return count pop af ; Get return flag pop hl ; Restore regs pop de pop bc ret ; Skip over space or tab characters skspc: ld a,(de) ; Get char and 7fh ; Mask inc de ; Pt to next cp ' ' ; Continue if space jr z,skspc cp 9 ; Continue if tab jr z,skspc dec de ; Pt to character ret ; Skip over non-space and non-tab characters ; Added '=' so that A:=B: construct yields two arguments. v1.1 jww sknspc: ld a,(de) ; Get char and 7fh ; Mask ret z ; Done if null cp ' ' ret z ; Done if space cp 9 ret z ; Done if tab cp '=' ret z ; New delimiter inc de ; Pt to next jr sknspc ; end ; End of argv inclusion ; Test for ZCPR 3.3, branch to the appropriate ; parsing code and return to caller zpars: ld a,(zflag) ; Check for Z-System running or a jr z,zpars1 ; ZCPR 3.0 parse if not Z-System call z33chk jp z,z33fname ; Let CCP do it if Z33 resident zpars1: xor a ; DIR:-first makes sense here jp zprsfn ; Let Z3LIB do it if BGii or Z30 ; Convert time from lbr into DateStamper format. Enter with MSDOS-format ; time in hl and pointer to storage buffer in DE. tcvt: ld b,3 ; Loop counter for shifting tcvtlp: srl h ; Shift H right, LSB to carry rr l ; Shift L right, carry to MSB djnz tcvtlp ; 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 bin2bcd ; Convert to BCD ld (de),a ; Store in buffer inc de ; Advance pointer ld a,l ; Now do minutes call bin2bcd ld (de),a ret ; Convert date from lbr into DateStamper format. Enter with DRI-format ; date in hl and pointer to storage buffer in DE. dcvt: 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 bin2bcd ld (de),a ; Store inc de ld a,b ; Month call bin2bcd ld (de),a inc de ld a,l ; Day call bin2bcd ld (de),a ret ; Buffers ;----------------------------------------------------------------------------- deflbr: db 'LBR' ;----------------------------------------------------------------------------- dseg ; B/m September 10, 1987 eoflag: ds 1 ; EOF flag oflag: ds 1 ; Overwrite option flag uflag: ds 1 ; Flag for uncompressing iflag: ds 1 ; Inspect mode flag typflg: ds 1 ; Type of compression zflag: ds 1 ; Z-System running flag empty: ds 1 ; Zero-length member file flag skpflg: ds 1 ; Skipping flag (for inspect option) filcnt: ds 1 ; Number of files processed comflg: ds 1 ; Comma flag lbrdu: ds 2 ; Lbr directory outdrv: ds 2 ; Output directory filebuf: ds 2 ; Ptr to file buffer filptr: ds 2 ; Ptr to file within buffer fbufhi: ds 1 ; Hi byte of file buffer obufhi: ds 1 ; Hi byte of output buffer outbuf: ds 2 ; Ptr to output buffer inbuf: ds 2 ; Ptr to input buffer cmdline: ds 2 ; Ptr to command line bufsiz: ds 1 ; Buffer length in pages. b/m September 10, 1987 file: ds 2 ; Pointer to FN.FT buffer: ds 2 ; Pointer to memory buffer ; argtable: ds 1 argcnt: ds 1 lbrnptr: ds 2 fileptr: ds 2 opptr: ds 2 ;*************** routines used for library processing ************** lud: ds 17 ludfcb: ds 1 lbrname: ds 8 lbrtyp: ds 27 ;******************************************************************* usrdat: ds 15 ; BCD times & dates go here curdt: ds 6 ; Current time and date lfcb: ds 36 ; Main fcb used savstk: ds 2 ; Save old stack secnt: ds 2 ; Counter for number of bytes in ds 128 ; B/m September 10, 1987 stack: ds 0 ; B/m September 10, 1987 end