;************************************************************************* ; ZLUX by J. POPLETT ;************************************************************************* ; vers equ 27 ; version number vext equ ' ' ; version extension z3env defl 0fe00h ; No big deal, Z3INS will fix it anyway ; copr macro defb 'Copyright (C) 1986 by John H. Poplett. All Rights Reserved.' endm ;---------------------- ; Version 2.7 04/21/90 ; Now ZLUX will attach itself to .LZH and .ZIP files. However, there ; doesn't exist a CP/M program to type members of a .ZIP file. So, ZLUX ; will not allow it (at this time). Also added the use of VLIB routines ; to display text in both regular and standout mode, as well as clear ; the screen between commands. Unfortunately, the program exceeds the ; 4k guidline (weighing in at around 5000 bytes, without the ; internal directory). If you want to save code, disable the VLB equate. ; ; - Mark Motley, Downey RCP/M & PBBS (213)806-2226 ;______________________ ; Version 2.6 04/25/88 ; No longer needs to be reassembled in order to rename from ZLUX: ; now uses ZCPR External FCB to determine name by which it was invoked. ; Also added code to handle .ARK type files like .ARC files. ; -L. Sonderling ; Compuserve: 73577,53 ; Bix: lsonderling ;---------------------- ; Version 2.5 12/4/86 ; Fixed a bug in the inline routine that has been plagueing ; ZLUX since V2.2. The original inline routine expanded tabs with ; spaces but placed a single tab character in the line buffer. ; Attempts to backspace after a tab would hang the system. ; NEW with 2.5 is an optional internal directory function. ; Although an internal directory runs slightly counter to the ; original intention of ZLUX, i.e. to make maximum use of external ; utilities, the internal directory is a great deal faster than, ; say, SDXX, and therefore, warranted. Purists can of course stick ; to the original and use an external program for display of ; library directories. Importantly, Bruce Morgen's fix to the ; SYSLIB SLUDIR module, SLUDIR11.Z80 was/is used for assembling ; ZLUX25 w/the internal directory option. ; Joubert Berger contributed an improvement to the CTRL-E ; function; Harris Edelman helped again w/beta testing; thanks also ; to Norman Beeler, Al Hawley, Steve Kitahata and Bruce Morgen. ; -J. Poplett, the PPR MBBS (213) 382-2213 ; ;------------------------- ; Version 2.4 5/24/86 ; Incorporated .ARC file capability into ZLUX, using UNARC utility ; for DIR and TYPE commands. Fully automatic determination of LBR/ARC ; file presence. No syntax differences in the commands. No KMD/XMODEM ; transfer at present time (although its being worked). ; Shortened and re-worded internal ascii statements to keep code less ; than 4k. This is an "OFFICIAL" release, approved by J. Poplett. ; Just install, (compile if changing options), rename LUX.COM, and ; locate LUX.COM and UNARC.COM on A0: ; ; -Norman Beeler ; ZeeMachine Z-Node #35 ; (408)735-0176/(408)245-1420 ; Multi-user/RAS ;------------------------ ; ; define TRUE and FALSE ; false equ 0 true equ not false ; ; ASCII characters and constants ; cmdlen equ 60 cr equ 0dh ; Carriage return lf equ 0ah ; Line feed del equ 7fh ; Delete null equ 0 ; NULL bel equ 7 ; BELL bs equ 8 ; BACKSPACE tab equ 9 ; TAB ctrlc equ 'C'-40h ; CTRL-C ctrle equ 'E'-40h ; CTRL-E ctrlr equ 'R'-40h ; CTRL-R ctrlu equ 'U'-40h ; CTRL-U ctrlx equ 'X'-40h ; CTRL-X ; ; ; Base page address equates ; fcb equ 5ch ; CCP file control block dmaadr equ 80h ; Default DMA buffer address (DBUF) parm equ dmaadr+2 ; Location of parameter in DMA ; ; Conditional assembly equates ; ; The comment equate allows one to opt for either the semicolon as a comment ; delimiter or to have an instant help key (the '?'). The option is given ; because otherwise a '?' on a comment line would give a help screen. Set ; to true if semicolon delimiter is desired; set to false if instant help ; key desired. (NOTE- an initial '?' will still give a help screen with the ; comment option enabled.) ; comment equ true ; TRUE, if recognize semicolon as comment kmdm equ false ; TRUE, if KMD in use; FALSE, if XMODEM passcmd equ true ; TRUE, if non-LUX commands passed to CCP byeclr equ TRUE ; TRUE, if BYE clears Z3 shell stack exthlp equ false ; TRUE, if ZLUX.HLP help file on-line ; The equate below will determine whether the video routines from VLIB ; will be included or not. If VLB is true, ZLUX will clear the screen ; between commands, and display things in both regular and standout ; mode. If your BBS doesn't set up the TCAP for each user, set it FALSE ; and save some code. vlb equ true ; TRUE, include VLIB stuff ; ; the following equate adds a library directory function that is internal ; to ZLUX. Although this option increases the programs code size, overall ; operation is speedier. ; intdir equ true ; TRUE, if use internal directory code ; ; Z3LIB & SYSLIB external references ; ; if intdir extrn caps,codend,condin,luinit,ludir extrn fname,pfn3,phldc,phl4hc endif ; if passcmd extrn putcst endif ; extrn z3vinit,z3log,clrcl,putcl extrn getsh1,dirtdu,zprsfn,parser extrn getmdisk,getmuser,getduok,getmsg extrn qshell,shfull,shpush,shpop extrn cout,cin,vprint,crlf,sknsp extrn capstr,vpstr,retud,f$exist if vlb extrn vidinit,cls,stndout,stndend,tinit,dinit endif .request syslib,vlib,z3lib ; jp begin ; Jump Z3 header db 'Z3ENV' ; Z3 program type db 1 ; External environment descriptor z3eadr: dw z3env ; Arbitrary environment address, ; Z3INS will fix it later ; set up stack, Z80-style ; begin: ld (stack),sp ; Save Z3's stack pointer ld sp,stack ; Set new stack pointer ; ; initialize Z3 environment ; ld hl,(z3eadr) ; Get env ptr call z3vinit ; Inform Z3LIB if vlb call tinit ; Initialize terminal endif ; ; begin by clearing Z3 CL buffer and setting pointer to LBR's name ; call clrcl ; Check for & clear Z3 command line buffer jp z,err3 ; Might as well quit now if no buffer ld de,lbrnam-shname; Offset to LBR name from our shell name call getsh1 ; Shell Stack address in HL (DE preserved) jp z,sherr ; Oops, no Shell Stack add hl,de ; Add in the offset ld (lfname),hl ; Store for later use ld de,15 ; Z3msg offset for Shell scratch byte call getmsg ; Z3MSG address in HL jp z,err2 ; NO Z3MSG space add hl,de ; Add the offset ld (arcflg),hl ; Store for later use ; ; get name by which we were invoked from external fcb ; and move it to 'shname' for future re-invocation ; ld hl,(z3eadr) ; environment address ld de,24h ; offset to address of EFCB in environment add hl,de ; point to EFCB address ld e,(hl) ; and load inc hl ; it into ld d,(hl) ; DE ex de,hl ; HL now has address of EFCB inc hl ; point to second byte of EFCB (filename) ld de,shname ; destination of move ld bc,08 ; length to move ldir ; move program name to 'shname' ; ; are we already a shell? ; reshel: call qshell ; Test the command status byte jp z,getcmd ; Don't reinvoke if we're a shell ; ; check for filename parameter and append to shell name if found ; rstrt: ld a,(dmaadr) ; 1st byte of DMA contains length of parameter or a ; Is it null? if so, no parameter specified jp z,err1 ; Exit with error msg if null dec a ; Or just a space? jp z,err1 ; Exit with error msg if one-byte tail ld hl,parm ld a,(hl) ; What's the first character? cp '/' ; These are trapped on restarts jp z,z3hlp ; Branch if it's a Z3 help query call getmdisk ; Max disk in A ld d,a ; To D inc d ; Bump it for CP/JP NC call getmuser ; Max user in A ld e,a ; To E inc e ; Bump it for CP/JP NC call getduok ; Will we accept DU: form? jr nz,duisok ; Good, skip a CALL call dirtdu ; See if a valid NDR entry jr z,curdir ; If not, try current directory only duisok: ld a,(fcb) ; FCB drive byte into A or a ; Current disk? jr nz,gotdrv ; Otherwise A has it curdir: call retud ; Get current DU: from SYSLIB ld a,b ; Disk into A inc a ; Bump it to 1=A, etc. gotdrv: cp d ; Compare to max drive + 1 jp nc,direrr ; A register must be smaller add a,'A'-1 ; ASCII the drive ld hl,lbrnam ; Point at our shell tail ld (hl),a ; Plant it ld a,(fcb+13) ; Get user number from FCB cp e ; Compare to max user + 1 jp nc,direrr ; A register must be smaller inc hl ; Bump to user spot in our buffer ; ; Convert hexadecimal user area number to 1- or 2-digit ASCII ; ld b,'0'-1 ; Preset for two-digit calculation later cp 10 ; See if single digit jr nc,twodig ; If not, print two digits add a,'0' ; Else convert to ASCII ld (hl),a ; And plant it jr putcln ; Then do colon twodig: inc b ; Count tens digit in B sub 10 ; Keep subtracting 10 until carry is set jr nc,twodig add a,10 ; Get remainder (units digit) back ld c,a ; Save it in C ld a,b ld (hl),a inc hl ld a,c add a,'0' ld (hl),a ; putcln: inc hl ld (hl),':' inc hl ; putnam: ld de,fcb+1 ; DE points to FCB filename ld b,8 ; Maximum filename length nloop: ld a,(de) ; Get character from FCB cp ' ' ; End of filename? jr z,clapnd ; Go append .LBR ld (hl),a ; Character to LBRNAM inc hl ; Bump HL inc de ; And DE djnz nloop ; Count down clapnd: push hl ; Save for possible ARC/ARK/LZH/ZIP call apnd ; ; make `LBR' the FCB filetype and see if the file exists ; ld hl,fcb+9 ; Point at FCB filetype call apnd1 ; Plug in L and B and R ld de,fcb ; Point at FCB for the LIBs call z3log ; Log in via Z3LIB call f$exist ; Check via SYSLIB jp nz,chsh ; Lbr file, so go pop hl ; Take off stack push hl ; Put back on (for possible ARC/ZIP) call apnd4 ; Plug in .LZH ld hl,fcb+9 ; Here too, call apnd5 ; plug in .LZH call z3log ; Log in call f$exist ; Check for existance jp nz,chsh ; Lzh file, so go pop hl ; Get again push hl ; Push again call apnd6 ; Setup zip file ld hl,fcb+9 ; Plug in zip call apnd7 call z3log ; Log in call f$exist ; Exist? jp nz,chsh ; Zip file, so go pop hl ; Retrieve again push hl ; save for next try call apnd2 ; Try again ld hl,fcb+9 ; Do it again for .ARC call apnd3 ; Plug in A and R and C ld de,fcb ; Point at FCB for the ARCS call z3log ; Log in call f$exist ; Exist? jp nz,chsh ; ARC file,so go pop hl ; Get filename push hl ; Back on stack inc hl ; inc hl ; Increment to last char in type inc hl ; ld (hl),'K' ; try for .ARK file ld hl,fcb+11 ; In the FCB ld (hl),'K' ; just change last char ld de,fcb call z3log ; Log in call f$exist ; Exist? jp z,err4 ; No file, no ZLUX jr chsh1 ; ; check for shell stack full, become a shell if there's room ; chsh: pop hl ; Just to be sure chsh1: call shfull ; All clear? jp z,sherr ; Let's not play if not ld hl,shname ; Time to play ball call shpush ; Install us on shell stack ; ; Insures that internal directory code will display a full directory on ; restarts. ; if vlb call cls ; Clear the screen endif call vprint ; Print header if vlb db 1 endif db 'ZLUX v' db (vers/10)+'0','.',(vers mod 10)+'0',vext if vlb db 2 endif db cr,lf,lf,0 if intdir ld hl,afnstr ; point to wild-card str (*.*) in HL ld de,cmdln+4 ; point to command line buffer call strcp ; copy it endif ; jp dir ; Give our directory and exit, and ; Z3 will get back to us (trust me) ; ;========================================================================= ; subroutines start here ;========================================================================= ; z3hlp: call vprint ; Polite, Z3-style help db cr,lf if vlb db 1 endif db 'ZLUX V' db (vers/10)+'0','.',(vers mod 10)+'0',vext if vlb db 2 endif db cr,lf,lf db 'Syntax:' db cr,lf db 0 jr errz ; To syntax message ; err1: call vprint db cr,lf db 'No file specified',cr,lf,lf db 'Syntax:' db cr,lf db 0 ; errz: call vprint db tab,'ZLUX [DIR: or DU:]ufn[.lbr/arc/ark/lzh/zip]',cr,lf db tab,'(DIR: & DU: is system-dependent)' db 0 jp exit1 ; err2: call vprint db cr,lf db 'No Z3MSG Buffer' db 0 jp exit1 ; err3: call vprint db cr,lf db 'No Z3CL Buffer' db 0 jp exit1 ; sherr: call vprint db cr,lf db 'Shell Stack full or not supported' db 0 jp exit1 ; direrr: call vprint db cr,lf db 'Directory not available' db 0 jp exit1 ; tpaerr: call vprint db cr,lf db 'Insufficient memory for library directory.' db 0 jp exit1 ; err4: call vprint db cr,lf,lf db 'LBR/ARC/ARK/LZH/ZIP file not found, check directory.' db cr,lf,0 jp exit1 ; err5: call vprint db cr,lf,lf db 'ARC file transfer not available' db cr,lf,0 ret ; err6: call vprint db cr,lf,lf db 'TYPEing of ZIP members not supported' db cr,lf,0 ret exit1: call crlf exit: ld hl,(stack) ; Get old Z3 stack ld sp,hl ; Restore it if vlb ; If using VLIB stuff call dinit ; Deinitialize terminal endif ret ; Return to CPR ; ; print ZLUX shell prompt and get user command ; getcmd: ; ; print command line prompt ; prompt: call vprint db cr,lf if vlb db 1 endif db '[ in ZLUX, ^C to quit, ? for help ]' if vlb db 2 endif db cr,lf,lf,0 hlfprt: ld hl,(lfname) call vpstr ld a,'>' call cout ; ; Command Line Editor (like ZRDOS's, but no ctrl chars printed) ; ------------------------------------------------------------- ; MAIN INLINE (MODIFIED FROM SYSLIB) ENTRY POINT ; original author: Richard Conn inline: ; ; INLINE RESTART LOOP ; ; Added code here so that the CMDLIN buffer is cleared on each restart. ; This is critical (not to mention safer) because a comment line or use ; of the one-key, instant ? help can leave the buffer full of schmutz ; JHP 04/26/86 ; inl0: ld hl,cmdln ; GET START OF STRING ld b,cmdlen ; length of command line in B xor a ; null in accumulator clrllp: ld (hl),a ; put null in command line byte inc hl ; increment pointer djnz clrllp ; loop til command line initialized (nulled) ld hl,cmdln ; start of command line in HL ld c,a ; SET CHAR COUNT ; MAIN LOOP inl1: call cin ; GET INPUT CHAR cp null ; DO NOT PERMIT jr z,inl1 cp ctrlc jp z,ccabrt cp bs ; BACKSPACE? jp z,inbs cp del ; DELETE? jp z,inbs cp tab ; TABULATE? jp z,intab cp cr ; CARRIAGE RETURN? jp z,incr cp lf ; LINE FEED? jp z,incr cp ctrlr ; CTRL-R jr z,prnlin cp ctrlu ; CTRL-U? jr z,restrt cp ctrlx ; CTRL-X? jr z,rexstrt cp ctrle ; CTRL-E? jr z,newline cp ' ' jr c,inl1 ld (hl),a ; STORE CHAR inc hl ; PT TO NEXT call cout if not comment ; moved check for help to after the call to cp '?' ; COUT so user can see character. jp z,help ; JHP 04/26/86 endif inc c ; INCR CHAR CNT ld a,cmdlen ; MAX CHAR CNT cp c ; COMPARE jr nc,inl1 ; NO OVERRUN, LOOP ld a,bel ; load ASCII bell into A call cout ; sound bell jr inbs ; print backspace & loop ; ; ; ** INLINE MODULES ** ; ; ; NEWLINE -- ECHO AND CONTINUE ; ; improvement of CTRL-E function provided by Joubert Berger ; newline: ld a,c ; count into A or a ; NULL test jr z,newln2 ; if NULL skip backup routine ld b,c ; count into b reg ld a,bs ; ASCII backspace char in acc newln: call cout ; backup for count in b reg djnz newln ; loop til b = 0 newln2: ld a,lf ; ASCII linefeed in acc call cout ; print LF ld c,0 ; 0 in cursor position counter ld hl,cmdln ; hl points to working cmd line buffer jr inl1 ; return to main edit loop ; TAB -- TABULATE TO NEXT TAB STOP ; ; lowercase code modifies tab expansion to allow backspacing. A backspace ; following a tab was causing some remote systems to freeze up (mine included) ; jhp 06/31/86 ; intab: ld a,c ; get count into a ld b,8 ; 8 into B add a,b ; add 8 to accumulator cp cmdlen ; compare against max length jr nc,inl1 ; return, if a + 8 > max len ld c,a ; get new "expanded" count in c ld a,' ' tablp: call cout ld (hl),a inc hl djnz tablp jr inl1 ; ; PRNLIN -- PRINT HASH, AND LINE BUFFER prnlin: call hash ld b,c ld a,bs prnlp: call cout djnz prnlp push hl ld hl,cmdln call vpstr pop hl jp inl1 ; ; CTRL-U -- ERASE LINE AND RESTART restrt: call hash ; PRINT HASH CHAR ; FALL THRU ; START UP AGAIN VIA REXSTRT ; CTRL-X -- ERASE (AND BACKSPACE) LINE AND RESTART rexstrt: call eralin ; ERASE LINE jp inl0 ; STARTOVER ; eralin: ld a,c ; CHECK FOR EMPTY LINE or a ; 0 CHARS? ret z call exbs ; jr eralin ; ; BACKSPACE -- DELETE PREVIOUS CHAR AND BACK UP CURSOR inbs: call exbs ; EXECUTE jp inl1 ; BACKSPACE ROUTINE exbs: call bol ; BEGINNING OF LINE? ret z ; CONTINUE IF SO dec c ; DECR COUNT dec hl ; BACK UP ld (hl),0 ; null character in buffer for ^R JHP 5/86 ld a,bs ; PRINT call cout ld a,' ' ; call cout ld a,bs ; jp cout ; CARRIAGE RETURN -- DONE; STORE ENDING ZERO incr: call crlf call bol jp z,getcmd ld (hl),0 ; STORE ENDING ZERO jr gotcmd ; ; ** SUPPORT ROUTINES ** ; BOL -- RETURNS W/ZERO FLAG SET IF USER AT BEGINNING OF LINE bol: ex de,hl ; DE=HL ld hl,cmdln ; GET START ADR ex de,hl ; HL RESTORED ld a,d ; CHECK FOR MATCH cp h ; MATCH? ret nz ; NO MATCH ld a,e ; CHECK FOR COMPLETE MATCH cp l ret ; ; ; HASH -- PRINT HASH MARK FOLLOWED BY & hash: ld a,'#' ; PRINT HASH CHAR call cout ld a,lf call cout ld a,bs jp cout ; ccabrt: call eralin ; ERASE LINE jp cabort ; PRINT CONTROL-C ABORT MESSAGE & QUIT ; ; Capitalize and parse line editor buffer, call scanner ; gotcmd: ld hl,cmdln if comment ld a,(hl) ; get first byte into A cp ';' ; is it a comment line? jp z,hlfprt ; yez, go back fo mo cp '?' ; a request for help? jp z,help ; if help char, go get help endif call capstr ld de,fcb call zprsfn call cmdser ; ; if command not recognized print error ; message & return to ZLUX cmdln prompt ; OR pass command to CCP ; jr nz,notcmd if vlb call cls ; Clear the screen first endif jp (hl) ; Jump to routine from scanner ; notcmd: if not passcmd call vprint db cr,lf,lf db 'Invalid command. Use ? or HELP' db cr,lf,0 jp getcmd else ; ; PUTCST insures that the shell will recover if a bad command spec is ; given ; xor a ; 0 in A call putcst ; tell ZCPR3 next is a normal command ld hl,cmdln ; addr of non-ZLUX command in HL call putcl ; setup Z3 command buffer jp exit ; give it a shot endif ; ; table of valid ZLUX command keys (only the CMDTBL: ; label is really needed) for programmer's convenience ; cmdtbl: hkey: db 'HELP ' dw help ; if (not passcmd) or (not byeclr) bkey: db 'BYE ' dw bye endif ; catkey: db 'CAT ' dw cat ; if not passcmd chtkey: db 'CHAT ' dw chat endif ; dkey: db 'DIR ' dw dir fkey: db 'FILES ' dw files lkey: db 'LUX ' dw lux zlkey: db 'ZLUX ' dw lux skey: db 'SEND ' dw send skkey: db 'SENDK ' dw sendk tkey: db 'TYPE ' dw type xkey: db 'XMODEM' dw xmodem kkey: db 'KMD ' dw kmd ; if not passcmd pkey: db 'PWD ' dw pwd endif ; db 0 ; Marks end of table ; if (not passcmd) or (not byeclr) bye: call shpop ld hl,cstr1 call putcl jp exit endif ; cat: ld hl,cstr2 call arctst jr nz,cat1a ld hl,cstr2a jr cat1 cat1a: call lzhtst jr nz,cat1b ld hl,cstr2b jr cat1 cat1b: call ziptst jr nz,cat1 ld hl,cstr2c cat1: call putcl jp exit ; if not passcmd chat: ld hl,cstr3 call putcl jp exit endif ; dir: if not intdir ld hl,cstr4 ; DIR (SDxxx) call arctst jr nz,dir1a ld hl,cstr4a ; UNARC (UNARCxx) jr dir2 dir1a: call lzhtst jr nz,dir1b ld hl,cstr4b ; LHARC (LHRDxx) jr dir2 dir1b: call ziptst jr nz,dir2 ld hl,cstr4c ; ZIP (ZIPDIRxx) else ld hl,cstr4a call arctst jp nz,dir2 call codend ; get codend for library buffers ld (lubuff),hl ; stash it ld hl,(lfname) ; address of token into HL ld de,ludfcb ; address of LUD FCB in DE call fname ; parse token into FCB ld de,lud ; point at syslib library structure call luinit ; init w/SYSLIB routine ld hl,cmdln+4 ; address of dir spec, if any ld de,lmbrn ; call fname ld hl,lmbrn+1 ld bc,(lubuff) ; start address in heap for dir buffers ld de,lud ; address of LU descriptor call ludir ; get directory (array of 17 byte elements) jp nz,tpaerr ; jump on error call vprint defb cr,lf,'ZLUX directory for ',0 ld hl,(lfname) call vpstr call crlf call crlf ld b,2 ldhdr: call vprint defb 'Filename Recs Size CRC ',0 djnz ldhdr call crlf xor a ld (lbrflg),a ld hl,(lubuff) ; get start address of array prlibm: call condin ; see if user typed anything jr z,prlbm1 ; no, continue cp ctrlc ; yes, was it control-C? jp z,ldone ; if Z, quit prlbm1: ld a,(hl) ; get first byte into A or a ; check for end of array delimiter (null) jp z,ldone ; if null, quit printing loop cp ' ' ; is it the first element in the library? jr nz,n1stel ; no, go print ld de,17 ; yes, offset in DE add hl,de ; add offset to ptr jr prlibm ; go get next array element n1stel: push hl ; else, save HL on stack ex de,hl ; put filename ptr into DE for call to PFN3 call pfn3 ; print the name of the library member ld a,' ' ; ASCII space into accumulator call cout ; print it pop hl ; restore address of array ld de,13 ; offset to rec size in DE add hl,de ; add it ex de,hl ; put address of lib member rec size in DE call getwd ; get word pointed to by DE into HL push de ; save ptr call phldc ; print rec size ld a,' ' ; print space call cout ld de,8 ; div by 8 to get size in Kbytes call divhd ; HL = HL / DE jr z,nrmndr ; check for remainder inc hl ; if remainder, bump up a Kbyte nrmndr: ld a,l ; put LSB into accumulator or h ; OR it with MSB jr nz,nozero ; is it zero? inc hl ; yes, increment nozero: call phldc ; print result ld a,'K' ; K into accumulator call cout ; print it ld a,' ' ; space into acc call cout ; print it call cout ; print it again pop de ; restore ptr into array element call getwd ; get word pointed to by DE into HL push de ; save ptr call phl4hc ; print CRC value in hex ld a,'H' call cout ld a,(lbrflg) or a jr nz,nxtlin call vprint defb ' | ',0 ld a,0ffh jr uniret nxtlin: call crlf xor a uniret: ld (lbrflg),a pop hl jp prlibm ; getwd: ld a,(de) ; get LSB of rec size ld l,a ; put it in L inc de ; increment pointer into array element ld a,(de) ; get MSB ld h,a ; put it in H inc de ; increment ptr into array element ret ; ; DIVHD -> HL = HL / DE. On entry, HL = dividend, DE = divisor; on return, ; result in HL, remainder in DE. Zero flag reset if remainder ; divhd: ld a,d ; put LSB of divisor in A or e ; or w/MSB ret z ; return if null ld a,h ; get dividend in AC ld c,l call div16 ; divide ex de,hl ; put remainder in DE ld h,a ; put quotient in HL ld l,c ; ld a,d ; reset flag if remainder or e ret div16: ld hl,0 ld b,16 loop16: rl c rla adc hl,hl sbc hl,de jr nc,$+3 add hl,de ccf djnz loop16 rl c rla ret ; ldone: call crlf jp getcmd endif dir2: ld de,mcmdln ; Command line scratch push de ; Save it for PUTCL call strcp ; Move HL to DE ld hl,(lfname) ; Our LBR's full name call lzhtst ; Is it a LZH file? call z,skipdu ; Yes, then skip the 'DU:' call strcp ; Move it call arctst jp z,tailt3 ; Skip the "L" if ARC file call lzhtst jp z,tailt3 ; Skip the "L" if LZH file call ziptst jp z,tailt3 ; Skip the "L" if ZIP file ld hl,cstr5 ; "$L" jp tailt2 ; Share some code ; files: ld hl,cstr4 ; DIR again ld de,mcmdln ; Scratch push de ; Save it call strcp ; Move ld hl,(lfname) ; get library name address into HL filelp: ld a,(hl) ; get first byte of DU: into A ld (de),a ; put it into MCMDLN inc de ; increment ptrs inc hl cp ':' ; have we reached the delimiter yet? jr nz,filelp ; no, loop ld hl,cstr6 ; *.LBR call arctst ; Is it an ARC file? jr nz,flel2a ; Zero = yes ld hl,cstr6a ; ARC file, so change string jr filel2 ; Process flel2a: call lzhtst ; Is it an LZH file? jr nz,flel2b ; Zero = nope ld hl,cstr6b ; LZH file, so change string flel2b: call ziptst ; Is it a ZIP file? jr nz,filel2 ; Zero = Nope ld hl,cstr6c ; ZIP file, so change string filel2: jr tailt2 ; Exit via shared code ; lux: ld a,(cmdln+4) ; Check for Z3 help query cp '/' jp z,help ; Give internal menu, else ld hl,(lfname) ; old LFNAME addr in HL ld de,fcb ; FCB in DE call zprsfn ; parse it for auld lang syne call z3log ; log into old lib's DU: ld hl,cmdln ; Point to buffer call parser ; Parse ala' Z3 call shpop ; Deshell us jp rstrt ; Restart LUX ; send: call lzhtst ; Is it an LZH file? jr nz,send1a ; Yes, print error call ziptst ; Is it a ZIP file? jr z,send1 ; Nope, so process command send1a: call err5 ; Can't send ZIP/LZH members yet jp getcmd ; Go get new command send1: ld hl,cstr7 ; Gets us XMODEM S or KMD S tailit: ld de,mcmdln ; Our scratchpad buffer push de ; Save that for PUTCL call strcp ; Move HL to DE ld hl,(lfname) ; The LBR's full name call lzhtst ; Is it a LZH file? call z,skipdu ; If so, then skip the 'DU:' call strcp ; Move that ld hl,cmdln ; INLINE's buffer tailt1: call sknsp ; SHOULD put us at the right 20H tailt2: call strcp ; And trailing parm w/null tailt3: pop hl ; Get back MCMDLN call putcl ; Give it to Z3 jp exit ; And boogie ; sendk: call lzhtst ; Is it an LZH file? jr nz,sndk1a ; Yes, print error call ziptst ; Is it a ZIP file? jr z,sendk1 ; Nope, so send sndk1a: call err5 ; Can't send ARC members yet jp getcmd ; Go try again sendk1: ld hl,cstr8 ; XMODEM/KMD SK jr tailit ; Same stuff follows ; type: ld hl,cstr9 ; TYPE (Sigi's TYPEL3x) call arctst jr nz,type1a ld hl,cstr9a jr type1 type1a: call lzhtst ; Is it LZH file? jr nz,type1b ; Nope ld hl,cstr9b ; Yes, load LHVW jr type1 ; Process type1b: call ziptst ; Is it ZIP file (not supported!) jr nz,type1 ; No call err6 ; Yes, display zip error msg jp getcmd ; Get next command type1: jr tailit ; Same old stuff ; kmd: ld hl,cmdln+4 ; KMD's parm #1 jr kmdin ; Skip to parm tests xmodem: ld hl,cmdln+7 ; XMODEM's parm #1 kmdin: ld a,(hl) ; Get first parm char cp 'S' ; Only S is kosher jp nz,notcmd ; Or it's not a command inc hl ; Next char ld a,(hl) ; Into A cp 'K' ; Packet send? jr z,xmdmk ; Branch and do that ld hl,cstr7 ; XMODEM S or KMD S jr xmdm ; Skip and do that xmdmk: ld hl,cstr8 ; (whatever...) SK xmdm: ld de,mcmdln ; Our scratchpad buffer push de ; Save that for PUTCL call strcp ; Move HL to DE ld hl,(lfname) ; The LBR's full name call strcp ; Move that ld hl,cmdln ; INLINE's buffer call sknsp ; SHOULD put us at first 20H inc hl ; Set up next SKNSP call jr tailt1 ; Go to some shared code ; if not passcmd pwd: ld hl,cstr0 call putcl jp exit endif ; ; Here are the type test routines. Please notice that they have changed ; from previous versions in that they set the zero flag if the attached ; file is the type tested for. For example, if the attached file is ; FOO.ARC, a call to "arctst" will return zero flag set. Previous versions ; would return zero flag clear. arctst: push hl ld hl,(arcflg) ; Point to ARC flag ld a,(hl) ; Get contents cp 01h ; Is it an ARC file? pop hl ret ; lzhtst: push hl ld hl,(arcflg) ; Point to ARC flag ld a,(hl) ; Get contents cp 02h ; Is it an LZH file? pop hl ret ziptst: push hl ld hl,(arcflg) ; Point to ARC flag ld a,(hl) ; Get contents cp 03h ; Is it a ZIP file? pop hl ret if (not passcmd) or (not byeclr) cstr1: db 'BYE',0 endif ; cstr2: db 'DIR *.LBR $AD',0 cstr2a: db 'DIR *.AR? $AD',0 cstr2b: db 'DIR *.LZH $AD',0 cstr2c: db 'DIR *.ZIP $AD',0 ; if not passcmd cstr3: db 'CHAT',0 endif ; cstr4: db 'DIR ',0 cstr4a: db 'UNARC ',0 cstr4b: db 'LHVW ',0 cstr4c: db 'ZIPDIR ',0 cstr5: db ' $L',0 cstr6: db '*.LBR',0 cstr6a: db '*.AR?',0 cstr6b: db '*.LZH',0 cstr6c: db '*.ZIP',0 ; if kmdm cstr7: db 'KMD A ',0 cstr8: db 'KMD AK ',0 else cstr7: db 'XMODEM L ',0 cstr8: db 'XMODEM LK ',0 endif ;KMDM ; cstr9: db 'TYPE ',0 cstr9a: db 'UNARC ',0 cstr9b: db 'LHVW ',0 ; if not passcmd cstr0: db 'PWD',0 endif if exthlp cstr10: db 'TYPE A0:ZLUX.HLP',0 endif ; ; ; CMDTBL (COMMAND TABLE) SCANNER (adapted from ZCPR3.Z80) ; ON RETURN, HL CONTAINS ADDRESS OF COMMAND, IF FOUND ; ON RETURN, ZERO FLAG SET MEANS VALID COMMAND ; original author: Richard Conn ; cmdser: ld hl,cmdtbl ; Pt to command table ; cmdscan: ld b,6 ; Get size of command text cms1: ld a,(hl) ; Check for end of table or a jr z,cms5 ld de,fcb+1 ; Pt to stored command FCB push bc ; Save size of command text cms2: ld a,(de) ; Compare stored against table entry cp (hl) jr nz,cms3 ; No match inc de ; Pt to next char inc hl djnz cms2 ; Count down ld a,(de) ; Next char in input command must be cp ' ' jr nz,cms4 pop bc ; Clear stack ld a,(hl) ; Get address from table into hl inc hl ld h,(hl) ld l,a ; Hl contains address xor a ; Zero flag set for command found ret ; Command is resident (zero flag set) cms3: inc hl ; Skip to next command table entry djnz cms3 cms4: pop bc ; Get size of command text inc hl ; Skip address inc hl jr cms1 cms5: xor a ; Set nz dec a ; Command not found if nz ret ; ; print help message ; help: if vlb call cls ; Clear the screen endif if exthlp ld hl,cstr10 call putcl jp exit ; else ; ld hl,hlpmsg call vpstr ; Print help message jp getcmd endif ; cabort: call vprint ; Print exit message db ' [^C] Returning to ZCPR3.',0 ; ; pop ZLUX from shell stack/restore stack/return to CPR ; call shpop jp exit1 ; ; Append LBR extension to HL-pointed command string ; apnd: ld (hl),'.' inc hl apnd1: ld (hl),'L' inc hl ld (hl),'B' inc hl ld (hl),'R' inc hl ld (hl),0 ; 'cause we might be changing LBRs push hl ld a,0 ld hl,(arcflg) ; Point to Arc flag ld (hl),a ; Set it false pop hl ret ; ; Append ARC extension to HL-pointed command string ; apnd2: ld (hl),'.' inc hl apnd3: ld (hl),'A' inc hl ld (hl),'R' inc hl ld (hl),'C' inc hl ld (hl),0 ; 'cause we might be changing LBRs push hl ld a,01h ld hl,(arcflg) ; Point to Arc flag ld (hl),a ; Set ARC flag true pop hl ret ; ; Append LZH extension to HL-pointed command string ; apnd4: ld (hl),'.' inc hl apnd5: ld (hl),'L' inc hl ld (hl),'Z' inc hl ld (hl),'H' inc hl ld (hl),0 ; 'cause we might be changing LBRs push hl ld a,02h ld hl,(arcflg) ; Point to Arc flag ld (hl),a ; Set ARC flag true pop hl ret ; ; Append ZIP extension to HL-pointed command string ; apnd6: ld (hl),'.' inc hl apnd7: ld (hl),'Z' inc hl ld (hl),'I' inc hl ld (hl),'P' inc hl ld (hl),0 ; 'cause we might be changing LBRs push hl ld a,03h ld hl,(arcflg) ; Point to Arc flag ld (hl),a ; Set ARC flag true pop hl ret ; ; COPY HL TO DE up to null terminator ; strcp: ld a,(hl) or a ; have we copied null terminator jr z,stcprt ; yes, return ldi ; (HL) -> (DE), ++HL, ++DE jr strcp ; loop til null terminator copied stcprt: ld (de),a ; put null (terminate str) ret ; return ; ; Skip over the DU: pointed to by HL ; The current LHVW (version 1.1 I believe) chokes when it receives ; a DU: specification. ; skipdu: ld a,(hl) ; Get byte inc hl ; Increment HL cp ':' ; Is it a colon? ret z ; If so, then return jr skipdu ; Else, loop ; if not exthlp hlpmsg: if vlb db tab,tab,' Available ZLUX commands' db cr,lf,lf,lf db tab,1,'BYE',2,' logoff computer' db cr,lf db tab,1,'CAT',2,' display all lbr/arc/ark files on system' db cr,lf db tab,1,'CHAT',2,' page system operator' db cr,lf db tab,1,'DIR',2,' display members of current lbr/arc/ark file' db cr,lf db tab,1,'FILES',2,' display lbr/arc/ark files on default drive/user' db cr,lf db tab,1,'HELP',2,' display this message' db cr,lf db tab,1,'LUX',2,' attach to another lbr/arc/ark/lzh/zip file' db cr,lf db tab,1,'ZLUX',2,' attach to another lbr/arc/ark/lzh/zip file' db cr,lf db tab,1,'SEND',2,' send a library member' db cr,lf db tab,1,'SENDK',2,' send a library member in 1K packets' db cr,lf db tab,1,'TYPE',2,' type an ASCII (text) lbr/arc/ark member' db cr,lf db tab,1,'PWD',2,' list available named directories' db cr,lf,lf db tab,' Exit ZLUX with ',1,'Control-C',2 db cr,lf,lf db ' ZLUX V' db (vers/10)+'0','.',(vers mod 10)+'0',vext,' ' copr db cr,lf db 0 endif ;vlb if not vlb db tab,tab,' Available ZLUX commands' db cr,lf,lf,lf db tab,'BYE logoff computer' db cr,lf db tab,'CAT display all lbr/arc/ark files on system' db cr,lf db tab,'CHAT page system operator' db cr,lf db tab,'DIR display members of current lbr/arc/ark file' db cr,lf db tab,'FILES display lbr/arc/ark files on default drive/user' db cr,lf db tab,'HELP display this message' db cr,lf db tab,'LUX attach to another lbr/arc/ark/lzh/zip file' db cr,lf db tab,'ZLUX attach to another lbr/arc/ark/lzh/zip file' db cr,lf db tab,'SEND send a library member' db cr,lf db tab,'SENDK send a library member in 1K packets' db cr,lf db tab,'TYPE type an ASCII (text) lbr/arc/ark member' db cr,lf db tab,'PWD list available named directories' db cr,lf,lf db tab,' Exit ZLUX with Control-C' db cr,lf,lf db ' ZLUX V' db (vers/10)+'0','.',(vers mod 10)+'0',vext,' ' copr db cr,lf db 0 endif ;not vlb endif ;not exthlp ; if intdir ; allocate necessary variables for INTDIR afnstr: defb '*.*',0 ; use to insure full display of library dir lbrflg: db 0 lubuff: dw 0000h lmbrn: ds 36 db 0 lud: ds 6 ; data for LU troutines ds 11 ; name of current file ludfcb: ds 36 ; FCB of library file endif ; lfname: dw 0000h ; Pointer to lib/arc fname string ; (in Z3 Shell Stack) arcflg: dw 0000h ; Pointer to Arcflg byte in Z3MSG ; ; ZLUX installs SHNAME in ZCPR3's shell stack with LBRNAM as tail ; shname: db 'ZLUX ' lbrnam: ds 32-(lbrnam-shname) db 0 ; Lots of room in case SHNAME is ; patched to include DIR: form ; mcmdln: ds 48 ; Scratch buffer for Z3 command lines db 0 ; cmdln: ds cmdlen+2 ; Buffer for command line editor db 0 ; ds 64 ; Room for 32 level stack stack: dw 0000h ; Old system stack saved here ; end xyz{|}~€