;************************************************************************ ;* * ;* TYPELZH v11 * ;* 08 Sep 1989 * ;* * ;************************************************************************ ; ;_______________________________________________________________________ ; ; 09/08/89 Updated for release. No functional changes. ; v11 - R. Warren ; Elephant's Graveyard ; (619)270-3148 ; ; 08/15/89 Beta release of TYPELZH. This program is based on TYPELZ. ; v10 - R. Warren ; Elephant's Graveyard ; (619)270-3148 ;----------------------TYPELZ notes follow:------------------------ ; ; 10/30/87 Added equate for BYE5 to use maximum disk and user bytes. ; v22 Modified and corrected screen output. Corrected printer out- ; put. - Ernest F. Barnhard, N8DVE ; AB17 RCP/M ; ; 12/22/86 Modified to also accept '$', in addition to '/' as a valid ; v21 switch in the command trail and changed MSG16 and MSG16A to ; show the '$' switch. Added 'PRINT2:' subroutine for messages ; with an embedded '$' character. These messages must termi- ; nate with a null. Eliminated the printing of the ending line ; by remarking-out the call to that routine in 'EXIT:' Added a ; final form feed, when printing, in the routine 'EXIT:'. Also ; changed CP 0 statements to OR A and changed LD A,0 statments ; to XOR A, saving one byte and three cycles each. Added in- ; structions for assembly and linking with M80 and L80. ; - Don Brown ; Metroplex RCP/M Dallas ; ; 08/31/86 All file decompression done by two simple calls to external ; v20 routines. Supports new v20 crunched files as well as v1x. ; See .DOC file for previous history. ; - Steven Greenberg ; ;_______________________________________________________________________ ; .Z80 ; CSEG ; EXTRN UNL,USQREL,UNCREL,ENDU PUBLIC GETBYT,OUT,GLZHUN,PLZHUN ; ;_______________________________________________________________________ ; ; This program needs to be linked to the unsqeeezer and uncruncher files ; UNLZH.REL, USQREL.REL and UNCREL.REL respectively. An assumption that ; UNCREL will be "on top" is made - if a different linking scheme is used ; change the value to which HL is loaded to (near beg of prog) to an appro- ; priate block of available memory (see UNCREL.DOC for more details). The ; version distributed was linked w/ DRI's LINK simply by the line: ; ; B>LINK TLZH11,USQREL,UNLZH,UNCREL ; ;_______________________________________________________________________ ; ; Sample Session Using M80 and L80 ; ; B>M80 =TLZH11.Z80/M ; ; No Fatal error(S) ; ; B>L80 /P:100,/D:2000,TLZH11,UNLZH,USQREL,UNCREL,/M ; ; Link-80 3.43 14-Apr-81 Copyright (c) Microsoft ; ; Data 2000 2121 < 289> ; Program 0100 1A25 < 6437> ; ; ENDU 2121 ENDUSQ 2100 GETBYT 06CE ; GLZHUN 0571 OUT 0798 PLZHUN 056E ; TOP_OF 1A71 UNCREL 155B UNL 10C6 ; UNLZH 10CD USQREL 13CD ; ; 29972 Bytes Free ; */R ; */P:100,/D:1A25,TLZH11,UNLZH,USQREL,UNCREL,/M ; Data 1A25 1B46 < 289> ; Program 0100 1A25 < 6437> ; ; ENDU 1B46 ENDUSQ 1B25 GETBYT 06CE ; GLZHUN 0571 OUT 0798 PLZHUN 056E ; TOP_OF 1A71 UNCREL 155B UNL 10C6 ; UNLZH 10CD USQREL 13CD ; ; 29972 Bytes Free ; ; *TLZH11/N,/E ; ; Data 1A25 1B46 < 289> ; Program 0100 1A25 < 6437> ; ; 29972 Bytes Free ; [0000 1B46 27] ;_______________________________________________________________________ ; NO EQU 0 YES EQU NOT NO ; REV EQU 22H VREV EQU 11H ; VERSION REV LSIGREV EQU 10h ; LZH stuff significant revision level IBUFSZ EQU 4 ; Input buffer size, pages ; ; --- ASCII equates --- ; CTRLC EQU 03H TAB EQU 09H LF EQU 0AH CRTLK EQU 0BH FEED EQU 0CH ; Formfeed CR EQU 0DH CTRLS EQU 13H CTRLX EQU 18H ; ; --- CP/M address equates --- ; WHLADR EQU 03EH ; Wheel address DDMA EQU 80H ; Default DMA address BDOS EQU 0005H ; BDOS entrypoint ; ;--- BDOS function equates --- ; CONIN EQU 1 ; Console input CONOUT EQU 2 ; Single character to console output LSTOUT EQU 5 ; Single character to list device DIRCON EQU 6 ; Direct console I/O (to check for keystroke) PRTSTR EQU 9 ; String to console output CONST EQU 11 ; Get console status OPEN EQU 15 ; Open file CLOSE EQU 16 ; Close file READ EQU 20 ; Read file (sequential) SETDMA EQU 26 ; Set DMA address SGUSER EQU 32 ; Set / get user number READR EQU 33 ; Read file (random) ;_______________________________________________________________________ ; BEGIN: JP START ; BYE5 EQU NO ; If BYE5 bytes for MAXDRV & MAXUSR ; IF BYE5 MAXDRV EQU 03DH MAXUSR EQU 03FH ENDIF ; BYE5 ; IF NOT BYE5 DEFB '[MAXDRV-1>' ; MAXDRV: DEFB 'C'-40H-1 ; Highest accessible drive - 1 (A=0) DEFB '[MAXUSR+1>' ; MAXUSR: DEFB 7+1 ; Highest accessible user + 1 ENDIF ; NOT BYE5 ; DEFB '[MAXLINES>' ; MAXLIN: DEFB 0 ; Number of lines to print max (0=all) DEFB '[CRTLINES>' ; LPS: DEFB 23 ; Max lines per screen -1 (0= no page) DEFB '[COLUMNS>' ; CPS: DEFB 80 ; Max screen cols for displaying chars DEFB '[PRTCOLS>' ; PRTCOL: DEFB 80 ; Number of printer columns DEFB '[NEXTLN>' ; LACHRS: DEFB 'L' DEFB 'l' DEFB ' ' DEFB 0 DEFB '[EJECTPG>' ; PAPER: DEFB 60 ; Lines per page of list output DEFB '[WHLTEST>' ; RCPM: DEFB 0FFH ; Non-zero means test for wheel ; ;_______________________________________________________________________ ; ; This table lists all filetypes that will NOT be typed by program. ; Ambiguous types are allowed, such as '?RL'. Typing is allowed when in ; wheel mode. ; ; Each entry MUST be 3 characters long ; DEFB '[NOTYPE>' ; NOTYP: DEFB 'COM' DEFB 'OBJ' ; Renamed COM DEFB 'LBR' ; Library (without member designated) DEFB 'OV?' ; OVR,OVL,OV1,OV2 etc DEFB 'ARC' ; Archive file DEFB 'BAD' ; Locked out bad spot DEFB 'SYS' ; System file DEFB '??#' ; Specially marked file (USERS.TX# etc) DEFB 'LOG' ; Log file DEFB 'INT' ; Intermediate file (CBASIC etc) DEFB 'REL' ; Relocatable object file DEFB '?RL' ; PRL, CRL, IRL DEFB 'EXE' ; Executable MSDOS file, renamed COMs DEFB 0 ; Table must end with a NULL DEFB ' "ENDU" is a global var which is the top of "UNCREL.REL". The ; statements below assume UNCREL will be linked on "top" (see ; UNCREL.DOC for more info). ; LD HL,ENDU ; First available memory after program LD DE,0FFH ; Convert to the 1st page boundary after prog ADD HL,DE LD L,0 ; HL now contains that boundary LD (IBUFP),HL ; Define this as pointer to input buffer LD A,H ADD A,IBUFSZ ; Add input buffer size, in pages LD H,A ; LD (TABLES),HL ; This area will be available for tables LD DE,6000H+900H ; Max table & stack mem needed by uncrr.rel ADD HL,DE ; 6000H for tables; 800h for CCP; 100H gd. luck LD A,(BDOS+2) ; Size up the TPA SUB H JR NC,ENOUGH LD DE,MSG3 ; "not enough memory..." JP FATAL0 ; (fatal error) ; ;=*=-=*==*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=- ; ENOUGH: LD A,(RCPM) ; See if we're testing for security OR A ; 0 means not testing JR NZ,WHLCHK ; Non-zero means test LD A,0FFH LD (INTWHL),A ; Otherwise set internal wheel flag TRUE JR FORMAT ; And go on ; WHLCHK: LD A,(WHLADR) ; Check system wheel byte OR A JR Z,FORMAT ; Zero, leave internal wheel flag false LD A,0FFH ; Non-zero, set internal wheel flag TRUE LD (INTWHL),A ; FORMAT: LD HL,DDMA ; Point at DMA LD A,(HL) OR A ; Anything on command line? JR Z,ENUF0 ; SWCHK: INC HL ; Bump up HL LD A,(HL) ; Get byte OR A ; Null indicates end of dma buffer JR NZ,SWCHK ; Not there, advance DEC HL ; Back up 3 bytes DEC HL DEC HL LD A,(HL) ; Make sure we have valid switch CP ' ' JR NZ,ENUF0 INC HL LD A,(HL) CP '$' ; Is there this kind of switch?... JR Z,SWCK1 ; ..Yes, so go process the switch character CP '/' ; Is there this kind of switch?... JR NZ,ENUF0 ; ..No, not one of those either ; SWCK1: INC HL LD A,(HL) CP 'N' ; $N or /N is no paging JR Z,GOODN CP 'L' ; $L or /L is list output JR NZ,ENUF0 ; Not N or L then not a switch / try to parse LD A,(INTWHL) ; Check if wheel OR A JR Z,ENUF0 ; Not a wheel, ignore /L switch LD A,0FFH LD (LDEV),A ; Set the list device flag LD A,(PAPER) LD (PAPLIN),A ; Initialize the line counter ; GOODN: XOR A ; Now cover up switch with nulls LD (HL),A ; For later parsing DEC HL LD (HL),A DEC HL LD (HL),A LD (LPS),A ; Finally stick a null in LPS counter ; (no console paging for EITHER /L or /N) LD A,(DDMA) ; And adjust the DDMA counter to new length SUB 3 LD (DDMA),A ; ENUF0: LD A,(INTWHL) ; Check if wheel OR A JR Z,ENUF1 ; Not a wheel XOR A LD (MAXLIN),A ; If wheel, make lines unlimited ; ENUF1: LD DE,MSG1 ; Version#, etc. CALL PRINT LD C,SGUSER ; Get current user# LD E,0FFH ; Specifies "get" as opposed to "set" CALL BDOSAV LD (USERNO),A ; Save it for later restoration ; PARSE: LD DE,FCB1 ; Init the fcb to blanks & zeroes CALL CLRFCB LD HL,DDMA ; Pointer to beginning of command tail LD B,0 LD C,(HL) ; # of chars in command tail now in BC LD A,C OR A ; Check for no command tail at all JR NZ,NUSAGE ; ;_______________________________________________________________________ ; USAGE: LD HL,MSG16 ; Guy needs help! CALL PRINT2 LD A,(INTWHL) ; Check if wheel OR A JP Z,FATAL2 ; Not a wheel, don't show /L info LD HL,MSG16A ; more usage instructions...only sysop CALL PRINT2 JP FATAL2 ; USAGE1: LD DE,MSG17 ; Bad user code detected CALL MESAGE JP FATAL2 ; Give instructions and exit ; USAGE2: LD DE,MSG18 ; Bad drive# detected CALL MESAGE JP FATAL2 ; USAGE3: LD DE,MSG19 ; Bad filename detected CALL MESAGE JP FATAL2 ; ;_______________________________________________________________________ ; NUSAGE: LD HL,DDMA+1 ; For offset calculation below PUSH HL ; ADD HL,BC ; Make sure byte past last one typed is blank LD (HL),' ' ; (simplifies parsing of the command line) POP HL LD B,C ; Length of command tail, 1 byte version CALL FNB ; Find 1st non-blank char (hl now points to it) JR Z,USAGE ; Blank command tail- guy needs help LD (FLNAM1),HL ; Temp save pntr to first non-blank char here CALL FB ; Find out right now if there is a 2nd filespec JR NZ,NOLIB ; If no additional delimiter found, guess not CALL FNB ; Find first non-blank after delimiter JR Z,NOLIB ; If nothing after delimiter, guess not either LD DE,MEMNAM ; If so, parse the lbr file name first CALL PRSNAM ; Goes into memnam+1 thru memnam+11 ; ;_______________________________________________________________________ ; NOLIB: LD HL,(FLNAM1) ; Start all over again with the first filename DEC HL ; Set def val for pntr to beg of filename -1 LD (FLNAM1),HL ; Goes here LD A,':' ; Looking for this INC HL ; Back to first char INC HL ; To 2nd char CP (HL) ; Is it a ":"? JR Z,DRONLY ; If so, drive [only] has probably been spec'd INC HL CP (HL) ; As above JR Z,DU1 ; A colon here is indicatative of a "du" spec INC HL CP (HL) ; Colon here means "du" spec where u >= "10" JP NZ,PLAIN ; Else just parse chars as a "plain" filename ; ;----------------------------------------------------------------------- ; ; Parse a "DU" specification where U >= 10 ; DU10: LD (FLNAM1),HL ; Save pointer to filename itself (-1) DEC HL ; Back to the units dig DEC HL ; Back to the tens dig LD A,'1' CP (HL) ; Check its validity JP NZ,USAGE1 ; Must be the char "1" or else... ; INC HL ; Move up to the units digit CALL CUNIT ; Convert the units dig to val in "a" ADD A,10 ; Add 10 CALL SETUSR ; Set user# DEC HL ; Back to the tens digit JP DRVSPC ; Go interpret drive spec (hl --> drvspec+1) ;_______________________________________________________________________ ; ; Parse a "DU" specification where U < 10 ; DU1: LD (FLNAM1),HL ; Save pointer to filename itself (-1) DEC HL ; Now points to the user# spec CALL CUNIT ; Convert to # in "a" CALL SETUSR JP DRVSPC ; Go interpret drive spec (hl --> drvspec+1) ; ;_______________________________________________________________________ ; ; Subroutine converts character pointed to by HL to # in "A" ; CUNIT: LD A,(HL) SUB '0' ; Cnvrt from ascii and perf validity chec JP C, USAGE1 ; Invalid user area char (stack gets fixed) CP 10 JP NC,USAGE1 RET ; ;_______________________________________________________________________ ; DRONLY: LD (FLNAM1),HL ; Save pointer to filename itself (-1) ; DRVSPC: DEC HL ; Entry here to interpret the spec'd drive LD A,(HL) ; Get it CALL UCASE ; "upcase" it if necessary SUB 'A' ; Convert it to a number (A=0, B=1, etc) JP C,USAGE2 ; Must be >= 0 ;; JP Z,USAGE2 ; Result must be >= '1' LD HL,MAXDRV CP (HL) ; *** temp *** JR Z,DRVOK ; If = then drive ok JP NC,USAGE2 ; DRVOK: INC A ; Restore drive # for FCB LD (FCB1+0),A ; Put drive# in drive# area of fcb ; PLAIN: LD HL,(FLNAM1) ; Get pointer to beg of filename -1 INC HL ; Now points to beg of filename LD DE,FCB1 ; Point to fcb to be defined CALL PRSNAM ; Parse the file name JP SPECD ; Continue!!! ; ;----------------------------------------------------------------------- ; PRSNAM: INC DE ; HL points to characters to be parsed, ; DE points to FCB LD B,8 ; Char counter for pre-extension chars PUSH DE ; Save fcb pointer PRSLP: LD A,(HL) ; Get a char CP '.' ; Check for'.' JR Z,SKIPP ; If encountered, skip to extension area of fcb CP ' ' ; A blank indicates we are done JR Z,PRSDN1 ; Br if that is the case CALL UCASE ; Else upcase the char if necessary LD (DE),A ; Put it into the fcb INC HL ; Incr both pointers INC DE ; DJNZ PRSLP ; And loop up to 8 times LD A,(HL) ; 9th char had better be a blank or a dot CP ' ' JR Z,PRSDN1 CP '.' JR NZ,PRSBAD ; Else complain ; SKIPP: POP DE ; Points to beginning of fcb again EX DE,HL LD BC,8 ; Add 8 to that to get pointer to ext area of fcb ADD HL,BC EX DE,HL INC HL ; Should now point to 1st char of ext PUSH HL POP HL LD B,3 ; Loop counter for extension chars ; PRS2LP: LD A,(HL) ; Get a character CP ' ' JR Z,PRSDUN ; Blank indicates done CALL UCASE ; Else upcase the letter LD (DE),A ; And put it into the FCB INC HL ; Increment both pointers INC DE ; DJNZ PRS2LP ; And continue RET ; PRSBAD: POP DE JP USAGE3 ; PRSDN1: POP DE ; (exit here if DE wasn't popped yet) PRSDUN: RET ; ;----------------------------------------------------------------------- ; ; Check file type at against table PSW, HL munched, ret only if ok ; TYPCK: PUSH BC ; TYPCK1: PUSH DE PUSH HL LD DE,NOTYP ; Point to no-type table ; TCK1: POP HL PUSH HL LD B,3 ; 3 chars to compare ; TCK2: LD A,(DE) OR A ; If end of table... JP Z,TYPOK ; Then return CP '?' ; Ambiguous? JP Z,TCK3 ; Yes, skip CP (HL) ; If no match... JP NZ,TCK4 ; Then skip to next table entry INC HL INC DE DEC B JP NZ,TCK2 ; Loop until all 3 match POP HL POP DE POP BC JP TCKNO ; Not ok to type ; ; Skip next character in table and filetype ; TCK3: INC HL INC DE DEC B JP NZ,TCK2 JP TCK1 ; ; Skip to next table entry ; TCK4: INC DE DEC B JP NZ,TCK4 JP TCK1 ; ; Restore registers and return (ok to type) ; TYPOK: POP HL POP DE POP BC RET ; ; Complain and abort (type found in table) ; TCKNO: LD DE,MSG22 ; Say "can't type a " CALL MESAGE LD B,3 ; TCL: LD A,(HL) INC HL PUSH BC ;; PUSH HL LD C,CONOUT ; Type the char in "a" to the console LD E,A ; (clobbers c & e) CALL BDOSAV ;; POP HL POP BC DEC B JP NZ,TCL LD DE,MSG23 ; Finish the message CALL PRINT JP FATAL2 ; ;----------------------------------------------------------------------- ; FNB: LD A,' ' ; Find first non-blank char, ret nz stat when found ; FNBLP: CP (HL) RET NZ INC HL DJNZ FNBLP RET ; Ret zero stat if fails after "b" chars ; ;----------------------------------------------------------------------- ; FB: LD A,' ' ; Find blank char, ret zero stat when found ; FBLP: CP (HL) RET Z INC HL DJNZ FBLP ; OR A RET ; Ret non-zero stat if fails after "b" chars ; ;----------------------------------------------------------------------- ; ; Clear and FCB pointed to by DE ; CLRFCB: EX DE,HL LD (HL),0 ; Zero the drive byte INC HL LD B,11 ; Next 11 bytes get blanks ; BLP: LD (HL),' ' INC HL DJNZ BLP ; LD B,24 ; Last 24 bytes get 0 again ZERLP: LD (HL),0 INC HL DJNZ ZERLP ; EX DE,HL ; Restore FCB pointer RET ; ;----------------------------------------------------------------------- ; UCASE: CP 'a' ; "Upcase" the char in "A" if necessary RET C CP ('z'+1) RET NC SUB 20H RET ; ;----------------------------------------------------------------------- ; SETUSR: PUSH HL LD HL,MAXUSR CP (HL) POP HL JP NC,USAGE1 ; LD E,A ; Set the current user to the value in "A" LD C,SGUSER CALL BDOSAV RET ; ;----------------------------------------------------------------------- ; SPECD: LD A,(LPS) SUB 2 LD (LFCNTR),A LD A,(MEMNAM+1) ; 2nd file spec'd? CP ' ' JP NZ,PRCLBR ; Go attempt to process as a library LD A,(INTWHL) ; See if wheel user OR A JR NZ,SPECD1 ; If wheel, bypass NOTYP table check PUSH HL LD HL,FCB1+9 CALL TYPCK ; See if filetype is listed in NOTYP table POP HL ; SPECD1: LD DE,FCB1 ; Point to spec'd file LD C,OPEN CALL BDOSAV INC A JR NZ,INOK ; Br if successful LD DE,MSG2 ; Else, "Input file not found" JP FATAL ; INOK: LD A,(INTWHL) ; See if wheel user OR A JR NZ,INOK1 ; If wheel, skip next check ; CKRES: LD A,(FCB1+2) ; Check if restricted file (high bit of F2 set) AND 80H LD DE,MSG20 ; Say: "Cannot type that file." JP NZ,FATAL ; CKSYS: LD A,(FCB1+10) ; Check if system bit set (high bit of T2 set) AND 80H LD DE,MSG2 ; Say: "Input file not found" JP NZ,FATAL ; INOK1: LD A,'(' CALL CONO LD HL,FCB1+1 CALL PRNFIL LD A,(FCB1+10) ; Check middle letter letter of extension CP 'Q' ; Squeezed file? JP Z,USQZIT ; Yes, go attempt to unsqueeze it CP 'Y' ; LZH encoded file JP Z,UNCRLIT ; Yes, go attempt to UNLZH it CP 'Z' ; Crunched? JP NZ,NORMAL ; If not, treat it as "normal" ; ;----------------------------------------------------------------------- ; --- Ucruncher --- ;----------------------------------------------------------------------- ; ; UNCREL.REL performs all validity checking, version #, etc. itself. We ; cannot just call it immediately in this case however because we want ; to extract & display the filename to the console. ; UNCRIT: LD DE,MSG5 ; Print " ---> " CALL PRINT EXX ; Init input pointer to beg of input bfr LD HL,(IBUFP) EXX CALL GETNXT ; Get 1st byte (should be 76H) JP C,EMPTY ; (If file has zero length) CALL GETNXT ; Prob a 0FEH ; ;----------------------------------------------------------------------- ; LD B,12 ; Loop limiter (11 char filename + ".") ; EATLP: CALL GETNXT ; Get next char OR A ; A zero byte indicates end of filename JR Z,ATEIT ; Br when that is encountered AND 7FH ; Force valid as-5diASCII (should be already) CALL CONO ; Type to console CP '.' ; Check for name / ext division character JR Z,ISDOT ; Br when encountered DJNZ EATLP ; Continue, but not past end of filename JR IGNORE ; If no 0 detected, ignore following info ; ISDOT: LD B,3 ; Update loop limiter counter JR EATLP ; And continue ; ;................................ ; IGNORE: LD B,0FFH ; Some kind of limit to prevent poss hangup IGLP: DJNZ OK1 JR BADHED ; Bad header ; OK1: CALL GETBYT ; Loop absorbs extraneous header info OR A ; Wait for the terminating zero JR Z,ATEIT ; If terminating zero is reached CP '[' ; Else check for date stamp BOF char JR NZ,IGLP ; Other chars are extraneous at this point LD DE,SPACE3 ; Offset the text 3 spaces CALL PRINT LD A,'[' ; Print the bracket, too ; TYPLP: DJNZ OK2 JR BADHED ; OK2: CALL CONO ; Type it CALL GETBYT ; Get next byte OR A ; Zero? JR Z,DUNTYP ; Br out if so CP ']' ; End of stamp? JR NZ,TYPLP ; If not, just loop ; DUNTYP: LD A,']' ; If we branched out of loop & it was missing CALL CONO ; If so, just type that one more char JR ATEIT ; ;................................ ; BADHED: ; Ie bad header NCRNCH: LD DE,MSG8 ; Entry here for all invalid crunched files JP FATAL ; "not a crunched file" ; TOONEW: LD DE,MSG9 ; "Can't uncrunch that file. Newer revision JP FATAL ; Of this program needed" or some such ; ;................................ ; ATEIT: CALL SELDEV ; Direct future output to proper source EXX LD HL,(IBUFP) ; Reset to beg again, expected by "UNCREL" EXX LD A,(SECNT) ; Above reset will cause an extraneous decr INC A ; Of this counter. Pre-adjust for that. LD (SECNT),A LD HL,(LSCNT) ; Likewise this thing, if its being used INC HL LD (LSCNT),HL LD HL,(TABLES) ; Spec table area for UNCREL CALL UNCREL ; Uncrunch the whole file! JP NC,EXIT ; Perf a normal exit (really should have ; Hit a "1A' bef this, already intercepted). CP 1 ; Carry set, analyze error code return JR Z,TOONEW ; "1" means need newer program revision JP NCRNCH ; Generic error message for all other errors ;----------------------------------------------------------------------- ; --- Un LZH --- ;----------------------------------------------------------------------- ; ; Extract & display the filename to the console. ; UNCRLIT: LD DE,MSG5 ; Print " ---> " CALL PRINT EXX ; Init input pointer to beg of input bfr LD HL,(IBUFP) EXX CALL GETNXT ; Get 1st byte (should be 76H) JP C,EMPTY ; (If file has zero length) CP 076h ; JR NZ,NLZH ; Invalid if not LZH CALL GETNXT ; Prob a 0FDH CP 0FDh ; JR NZ,NLZH ; Invalid if not LZH ; ;----------------------------------------------------------------------- ; LD B,12 ; Loop limiter (11 char filename + ".") ; LEATLP: CALL GETNXT ; Get next char OR A ; A zero byte indicates end of filename JR Z,ATEITL ; Br when that is encountered AND 7FH ; Force valid as-5diASCII (should be already) CALL CONO ; Type to console CP '.' ; Check for name / ext division character JR Z,LISDOT ; Br when encountered DJNZ LEATLP ; Continue, but not past end of filename JR LIGNORE ; If no 0 detected, ignore following info ; LISDOT: LD B,3 ; Update loop limiter counter JR LEATLP ; And continue ; ;................................ ; LIGNORE: LD B,0FFH ; Some kind of limit to prevent poss hangup LIGLP: DJNZ LOK1 JR BADLHED ; Bad header ; LOK1: CALL GETBYT ; Loop absorbs extraneous header info OR A ; Wait for the terminating zero JR Z,ATEITL ; If terminating zero is reached CP '[' ; Else check for date stamp BOF char JR NZ,LIGLP ; Other chars are extraneous at this point LD DE,SPACE3 ; Offset the text 3 spaces CALL PRINT LD A,'[' ; Print the bracket, too ; LTYPLP: DJNZ LOK2 JR BADLHED ; LOK2: CALL CONO ; Type it CALL GETBYT ; Get next byte OR A ; Zero? JR Z,LDUNTYP ; Br out if so CP ']' ; End of stamp? JR NZ,LTYPLP ; If not, just loop ; LDUNTYP: LD A,']' ; If we branched out of loop & it was missing CALL CONO ; If so, just type that one more char RVW1: CALL GETBYT ; Loop till termiating zero found JR C,BADLHED ; Oops! Bumped into EOF OR A ; Terminator? JR NZ,RVW1 ; No... ; ;============================================================================== ; LZH stuff ; ATEITL: CALL SELDEV ; Direct future output to proper source LD HL,(TABLES) ; Spec table area for UNCREL CALL UNL ; process from there on JP NC,EXIT ; Perf a normal exit (really should have ; Hit a "1A' bef this, already intercepted). CP 1 ; Carry set, analyze error code return JP Z,TOONEW ; "1" means need newer program revision BADLHED: NLZH: LD DE,MSG24 ; JP FATAL ;...............................; PLZHUN: JP OUT ; complete there GLZHUN: JP GETBYT ; complete there ; ;----------------------------------------------------------------------- ; --- Unsqueezer --- ;----------------------------------------------------------------------- ; USQZIT: EXX ; Very similar to "uncruncher", above LD HL,(IBUFP) ; Init input pntr to beg of input buffer EXX CALL GETNXT ; 76H, hopefully JP C,EMPTY ; If file empty CALL GETNXT ; Presumably "FF" (all checked by USQR call) CALL GETNXT ; (chksum low) ignore CALL GETNXT ; (chksum high) ignore LD DE,MSG5 ; " --->" CALL PRINT ; Ok, print an arrow LD B,32 ; Realistic (?!?) limit for filename length ; EATLP2: PUSH BC CALL GETNXT ; Eat up the file name OR A ; A zero byte indicates end of filename JR Z,ATEIT2 ; Br when that is encountered CALL CONO ; Print a filename char to the console POP BC JR EATLP2 ; Continue ; INVSQ: LD DE,MSG12 ; Invalid squeezed file JP FATAL ; ATEIT2: POP BC ; The POP we missed from the loop above CALL SELDEV ; Direct output properly EXX ; RE-init pointer to beg again LD HL,(IBUFP) ; (UNCREL expects all bytes from the start) EXX LD A,(SECNT) ; Adj count (see uncruncher for explanation) INC A LD (SECNT),A LD A,(LSCNT) ; LIkewise this count INC A LD (LSCNT),A LD HL,(TABLES) ; Spec pointer to avail mem for UNCR call CALL USQREL ; Unsqueeze entire file JP NC,EXIT ; (prob should have hot an EOF bef this) JR INVSQ ; Generic error msg for invalid sqz'd files ; ;----------------------------------------------------------------------- ; --- "Normal" ASCII --- ;----------------------------------------------------------------------- ; NORMAL: CALL SELDEV ; Check for request for :lst output EXX LD HL,(IBUFP) ; Init pntr to beg of output buffer EXX CALL GETNXT ; Get 1st char "manually" JP C,EMPTY ; So we can chk for empty file CALL CONO ; Ok, output that char ; NORMLP: CALL GETNXT JP C,EXIT ; } Output the rest of the file CALL CONO JR NORMLP ; EMPTY: LD DE,MSG14 ; If physical EOF hit bef logical EOF JP FATAL ; ;----------------------------------------------------------------------- ; --- General Library Processing --- ;----------------------------------------------------------------------- ; PRCLBR: LD A,(INTWHL) ; See if wheel user OR A JR NZ,PRCLB1 ; If wheel, bypass NOTYP table check LD HL,MEMNAM+9 ; Point at filetype of requested member CALL TYPCK ; See if filetype is listed in NOTYP table ; PRCLB1: LD HL,'BL' ; Force ".LBR" extension LD (FCB1+9),HL LD A,'R' LD (FCB1+11),A LD DE,FCB1 ; Point to spec'd file LD C,OPEN CALL BDOSAV INC A JR NZ,INOK2 ; Branch if successful LD DE,MSG2 ; Else, "Input file not found" JP FATAL ; INOK2: LD HL,(IBUFP) ; Init to beg of input buffer CALL GTNEXT ; Get 1 char, forcing a buffer fill JP C,EMPTY DEC L ; (but re-adjust to beg of sector again) CALL CPBLNK ; Lib dir itself- must be active & named 8 blanks JR Z,LBROK ; Branch if ok ; BADLBR: LD DE,MSG13 ; "Library file invalid" JP FATAL ; LBROK: LD L,12 ; Further check- lbr's index should be 0000 XOR A CP (HL) JR NZ,BADLBR INC L CP (HL) JR NZ,BADLBR ; INC L ; Now get .LBR's length LD B,(HL) LD L,32 ; First "real" entry JR SKIP1 ; (first sector only has 3 real entries, not 4) ; SRCHLP: CALL CPNAME ; Check 4 entries sector JR Z,FOUND ; SKIP1: CALL CPNAME JR Z,FOUND CALL CPNAME JR Z,FOUND CALL CPNAME JR Z,FOUND ; DEC B ; Decrement record count JR Z,NOTFND ; CALL GTNEXT ; Guarantee reload of buffer if necessary JR C,NOTFND DEC L ; But force pointer back by one JR SRCHLP ; Continue checking ; NOTFND: LD DE,MSG15 ; ".LBR member file not found" JP FATAL ; FOUND: LD DE,DDMA ; Misc. area for a phony sector read LD C,SETDMA CALL BDOSAV LD DE,12 ADD HL,DE ; Offset to index LD E,(HL) INC HL LD D,(HL) ; Get index into DE INC HL LD C,(HL) ; Get length in records INC HL LD B,(HL) INC BC ; Init limit counter to # of records +1 LD (LSCNT),BC LD (FCB1+33),DE ; Set random record number XOR A LD (FCB1+35),A LD C,READR LD DE,FCB1 CALL BDOSAV ; Perf a random read ; BREAK: XOR A ; (Re-)zero the EOF flag LD (EOFLAG),A ; (Short libraries may hit EOF twice) INC A ; "1" LD (LBRFLG),A ; Flag fact that we are typing from a lbr file LD (SECNT),A ; So 1st call to gtnext/getnxt will load "IBUF" LD A,'(' ; Want to type member name, not .LBR filename CALL CONO ; Start w/ this LD HL,MEMNAM+1 ; Point to name of member file being typed CALL PRNFIL ; Type it LD A,(MEMNAM+10) CP 'Q' ; Squeezed? JP Z,USQZIT ; Go unsqueeze it CP 'Y' ; LZH encoded file JP Z,UNCRLIT ; Yes, go attempt to UNLZH it CP 'Z' ; Crunched? JP Z,UNCRIT ; Go uncrunch it JP NORMAL ; Else just go type it ; ;----------------------------------------------------------------------- ; ; Searches .LBR directory for a match ; CPNAME: LD DE,MEMNAM+1 ; Pointer to what we're trying to match ; CPN: PUSH BC PUSH HL ; Save pointer to beg of entry XOR A CP (HL) ; Make sure entry is active JR NZ,NFG ; Else immediate failure ; LD B,11 ; #of chars to compare ; CPLP: LD A,(DE) ; Get a char INC DE INC HL ; *** l only *** CP (HL) ; Compare JR NZ,NFG ; Br if no match DJNZ CPLP ; Else continue checking POP HL POP BC RET ; Ret w/ zero stat (do not advance hl) ; NFG: POP HL LD DE,32 ; Advance hl to point to next entry ADD HL,DE POP BC RET ; Return with non-zero stat, indicating no match ; ;................................ ; CPBLNK: LD DE,BLANKS ; (bunch of blanks to match) JR CPN ; Rest is like normal match routine ; ;----------------------------------------------------------------------- ; File Input Utilities ;----------------------------------------------------------------------- ; ;=*=-=*==*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=- ; GETBYT: ; <<--- Entrypoint for all external ; ; requests for data bytes ; (called by both compression utilities) ; [same as "GETNXT"] ; ;=*=-=*==*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=- ; GETNXT: EXX ; Like "GTNEXT" but uses HL' CALL GTNEXT EXX RET NC JP EXIT ; (Hardware EOF before 1A exit) ; ;....................................................................... ; ; "A" <-- next byte from ("physical") input stream. "get12" produces a ; logical input stream of 12-bit values from this. ; GTNEXT: LD A,L ; Pointer to next avail char SLA A ; See if 00h or 80h OR A ; (init carry flag [rtn stat] to clear) CALL Z,MAYRLD ; "maybe reload" the buffer if 00 or 80H RET C ; Return immed w/ carry set on end-of-file ; LD A,(HL) ; Get next byte itself to return INC HL ; Advance input pointer RET ; ;................................ ; MAYRLD: LD A,(LBRFLG) ; "library" mode? OR A JR Z,SKPCNT ; PUSH HL LD HL,(LSCNT) ; Prevents possibly reading beyond the DEC HL ; .LBR member in question LD (LSCNT),HL LD A,L OR H POP HL JR NZ,SKPCNT ; SCF RET ; (really should hit a "1A" before this) ; SKPCNT: LD A,(SECNT) DEC A LD (SECNT),A CALL Z,RELOAD RET ; ;----------------------------------------------------------------------- ; ; Reload the input buffer, & reset HL to point to the beginning of it. ; Assumes input bfr starts page boundry and is of page multiple length. ; This routine is called by "getnxt". ; RELOAD: PUSH BC PUSH DE LD B,IBUFSZ ; Loop counter, buffer length in pages LD A,(IBUFP+1) ; Pointer to input buffer, hi byte LD D,A LD L,0 ; Count of sectors actually read ; RLDLP: LD E,0 ; Low byte of current DMA CALL RDSEC ; Read in 128 bytes (1/2 page) JR NZ,RLDRTN ; (return if eof enecountered) INC L LD E,80H ; To read in the next half page CALL RDSEC ; Do that JR NZ,RLDRTN ; As above INC L INC D ; Next page DJNZ RLDLP ; Loop till done ; RLDRTN: LD A,L LD (SECNT),A POP DE ; Restore regs POP BC LD HL,(IBUFP) ; Reset input pointer AND A RET NZ ; And return SCF RET ; ;----------------------------------------------------------------------- ; ; Subr for "reload"; reads 128 bytes to memory starting at HL ; RDSEC: PUSH DE ; Save DMA before clobbering it with FCB LD C,SETDMA ; Set DMA function CALL BDOSAV LD DE,FCB1 ; Input FCB LD C,READ CALL BDOSAV ; Read a record POP DE ; Restore DMA to original DMA address OR A ; Set stat non-zero if EOF encountered RET Z ; LD A,(EOFLAG) ; Abnormal termination if 2 EOF's are hit OR A JP NZ,EXIT INC A ; 1st EOF- set flag LD (EOFLAG),A RET ; ;----------------------------------------------------------------------- ; ; Print name of output file. HL should point to the FCB plus 1. ; PRNFIL: LD B,12 ; Loop cntr (max #of chars plus ".") ; CHARLP: LD A,(HL) ; Get a char CP " " ; Blank? JR Z,SKPTYP ; Supress them ; TYPEIT: CALL CONO ; Type char in a to console ; SKPTYP: DEC B ; Loop counter RET Z ; Rtn when done ; LD A,B ; Check loop counter CP 4 ; At this point, type a "." JR NZ,NOT4 LD A,"." JR TYPEIT ; Type it. do not incr hl or reload a. ; NOT4: INC HL ; Advance pointer JR CHARLP ; Repeat till done ; ;----------------------------------------------------------------------- ; ; BDOS call BC, DE, HL, & HL' saved ; ; *** temp IX & IY *** ; BDOSAV: PUSH BC PUSH DE PUSH HL EXX PUSH HL EXX CALL BDOS EXX POP HL EXX POP HL POP DE POP BC RET ; ;----------------------------------------------------------------------- ; Console / Printer Related Utilities ;----------------------------------------------------------------------- ; ; Print message string pointed to by DE ; MESAGE: CALL CRLF ; Precede all messages with CR,LF ; PRINT: PUSH BC ; (entry here for no CR,LF) LD C,PRTSTR ; Print string CALL BDOSAV POP BC RET ; ;----------------------------------------------------------------------- ; PRINT2: LD A,(HL) ; Get the next character OR A ; Is it a null?... RET Z ; ..Yes, so exit PUSH HL ; ..No, so save the string pointer CALL SCRNOT ; Go print the character using BDOS function 2 POP HL ; Restore the address of the string INC HL ; Point to the next character JR PRINT2 ; Continue looping till complete ; ;----------------------------------------------------------------------- ; MESS80: LD C,PRTSTR ; Non-Z80 fatal error special exit CALL BDOS ; Can't use "BDOSAV" RET ; Got here from jump; returns to CCP ; ;----------------------------------------------------------------------- ; CRLF: LD A,CR ; Print a CR,LF sequence CALL CONO LD A,LF CALL CONO RET ; ;=*=-=*==*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=- ; OUT: ; <<--- External entrypoint for character output (same as "cono") ; (called by all 3 data compression utilities) ; ;=*=-=*==*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=- ; ; Routine to branch output to console or to LST: Output the character ; in "A" to the console. ; CONO: AND 7FH ; Strip high bit of char CP 1AH ; First check for EOF JP Z,EXIT ; And exit if so PUSH BC ; Then save all other regs PUSH DE PUSH HL PUSH AF ; Save character LD A,(LSTART) ; See if we're sending to list device OR A JP NZ,SNDLST ; Branch to list output routine or fall through ; To console output routine at SCREEN: ; ;----------------------------------------------------------------------- ; ; This segment handles console output ; SCREEN: POP AF ; Get char back PUSH AF ; Keep it saved CP TAB ; Check if tab expansion is necessary JR Z,MAKTAB ; Handle tab expansion CALL SCRNOT ; Print any other char POP AF PUSH AF CP LF ; Is it a LF JP NZ,NTANLF ; No, skip length counting ; ; All linefeed tests start here ; MAXCNT: LD A,(MAXLIN) ; Are we counting max lines? OR A ; 0 indicates not counting JR Z,NOCNT ; So skip test DEC A ; Otherwise deduct 1 LD (MAXLIN),A ; And put it back OR A ; Then check if zero JR NZ,NOCNT ; Not zero, don't bail out LD DE,MSG21 ; Otherwise say: all thru/ download it CALL MESAGE JP POPEXIT ; Print msg and exit ; NOCNT: LD A,(LPS) ; Are we paginating OR A ; 0 means no JP Z,CONRTN ; So we go back ; ; Here we count the linefeed for pagination ; ANLF: LD HL,LFCNTR DEC (HL) JP NZ,CONRTN LD DE,MSG6 ; "[more]" CALL PRINT ; ; Now wait for any key ; WAIT: LD C,DIRCON ; Console input LD E,0FFH CALL BDOSAV OR A JR Z,WAIT ; Hold for a character AND 1FH CP CTRLC ; Check for ^C JP Z,POPEXIT ; If so, terminate CP CRTLK JP Z,POPEXIT CP CTRLX ; Likewise JP Z,POPEXIT LD HL,LACHRS ; Now check if it matches our line advance CP (HL) ; Check table 1 line advance (3 chars in table) JR Z,L1 INC HL ; (second character) CP (HL) JR Z,L1 INC HL ; (third character) CP (HL) JR Z,L1 LD A,(LPS) ; Lines / Screen DEC A JR WIPE ; L1: LD A,1 ; WIPE: LD (LFCNTR),A ; Reset the counter LD DE,MSG7 ; Wipe out the prompt CALL PRINT JP CONRTN ; MAKTAB: LD A,' ' ; Loop to expand tabs to appropiat #of blanks CALL SCRNOT ; Always expand to at least one blank LD A,(COLCTR) ; New cursor position AND 07H ; See if it is a multiple of eight JR Z,NTANLF ; Loop until it is LD A,(COLCTR) ; Otherwise bump up col ctr and keep going INC A LD (COLCTR),A LD HL,COLCTR ; Point to column counter LD A,(CPS) ; Get max col allowed CP (HL) ; Compare to next char pos JR NC,MAKTAB ; Loop to expand TAB LD (HL),1 ; Point to begining of new line JR ANLF ; Start new line, skip remaining spaces ;; JR MAKTAB ; SCRNOT: PUSH BC PUSH DE LD C,CONOUT ; Type the char in "a" to the console LD E,A ; (clobbers c & e) CALL BDOSAV POP DE POP BC RET ; ; Handle column counting ; NTANLF: LD A,(CPS) LD B,A LD HL,COLCTR ; Pointer to current column# POP AF ; Get char back PUSH AF ; Save it CP CR ; Reset column counter when cr encountered JR NZ,NRSTCC ; LD (HL),0 ; CR resets col# to zero ; NRSTCC: LD A,(HL) ; Normal column increment INC A LD (HL),A ; New position CP B ; Check if at terminal width limit JP Z,CONRTN ; Next col = max col JP C,CONRTN ; Next col < max col ;; LD (HL),0 ; Perform a phantom CR LD (HL),1 ; Point to 1st column JP ANLF ; Perform a phantom LF ; ;----------------------------------------------------------------------- ; ; This segment handles list out ; SNDLST: LD HL,COLCTR ; Get column pointer POP AF ; Character to send in A PUSH AF ; Save it CP TAB ; First check if tab (special handling) JR Z,LTAB CALL LCOUT ; Send any other character to printer CP CR ; Now check if CR / reset the column counter JR Z,LRSTCOL CP LF ; Check if LF. If not, skip line counter ;; JR NZ,CONRTN JR Z,FRMCNT INC (HL) ; Point to next column LD A,(PRTCOL) ; Get max col CP (HL) ; Compare to next column JP NC,CONRTN ; If >= then return LD (HL),1 ; Point to 1st column ; FRMCNT: LD A,(PAPLIN) ; Are we counting paper length? OR A ; 0 indicates not counting JR Z,CONRTN ; So skip test DEC A ; Otherwise deduct 1 LD (PAPLIN),A ; And put it back OR A ; Then check if zero JR Z,EJECT ; Zero, send a formfeed LD A,(MAXLIN) ; Are we counting output lines? OR A ; 0 indicates not counting JR Z,CONRTN ; So skip test DEC A ; Otherwise deduct 1 LD (MAXLIN),A ; And put it back OR A ; Then check if zero JR NZ,CONRTN ; Not zero, don't bail out LD DE,MSG21 ; Otherwise say: all thru/ download it CALL MESAGE JP POPEXIT ; Print msg and exit ; NOFORM: INC (HL) JP CONRTN ; Use existing return routine EJECT: ;; LD E,FEED LD A,FEED ; Get ;; LD C,LSTOUT ; Send a formfeed char to printer ;; CALL BDOSAV CALL LCOUT LD A,CR CALL LCOUT LD A,(PAPER) LD (PAPLIN),A ;; JP CONRTN ; Return via console check ; LRSTCOL: ;; PUSH HL ;; LD HL,COLCTR ; Pointer to current column# LD (HL),1 ; CR resets col to # 1 ;; POP HL JP CONRTN ; LTAB: LD A,' ' ; Loop to expand tabs to appropriate # of blanks CALL LCOUT ; Always expand to at least one blank ;; LD A,(COLCTR) ; New cursor position ;; AND 07H ; See if it is a multiple of eight LD A,07H AND (HL) ; See if multiple of 8 JR Z,NOFORM ; Return if finished INC (HL) ; Point to next column LD A,(PRTCOL) ; Get printer max col CP (HL) ; Compare to next col JR NC,LTAB ; If >= then expand TAB LD (HL),1 ; Point to 1st column JR FRMCNT ; Count line skipping remaining blanks ;; JR NZ,LTAB ; Loop until it is ;; JP CONRTN ; ; Sends a character to LST: device ; LCOUT: LD C,LSTOUT ; Type the char in "a" to the PRINTER LD E,A ; (clobbers c & e) PUSH AF PUSH HL CALL BDOSAV POP HL ;; LD A,(COLCTR) ; Bump the column counter ;; INC A ;; LD (COLCTR),A POP AF RET ; ;----------------------------------------------------------------------- ; ; This segment handles return from either column or list out ; CONRTN: LD C,DIRCON ; Check for console character LD E,0FFH CALL BDOSAV AND 31 ; Mask so ^C,C,c or ^S,S,s or ^X,X,x all work CP CTRLC ; Check for ^C JP Z,POPEXIT ; If so, terminate CP CTRLX ; Likewise on ^X JP Z,POPEXIT CP CTRLS ; Check for ^S CALL Z,PAUSE ; Pause if so POP AF POP HL POP DE POP BC RET ; ; Wait for any key from console ; PAUSE: LD C,DIRCON LD E,0FFH CALL BDOS ; Registers already saved OR A JR Z,PAUSE RET ; ;----------------------------------------------------------------------- ; ; Sets output flags and sends appropriate message ; SELDEV: PUSH AF ; Check for request for :lst output LD A,(LDEV) ; 0 = no :lst, 0ffh = :lst out OR A JR Z,SELCON ; SELLST: LD DE,MSG11A ; Send "printer" message to console CALL PRINT LD A,(LDEV) ; Now get back printer flag LD (LSTART),A ; Move flag to ACTUAL flag used after header JR SELDUN ; SELCON: LD DE,MSG11 CALL PRINT ; SELDUN: POP AF RET ; ;----------------------------------------------------------------------- ; FATAL0: CALL MESAGE ; Emergency exit- no frills LD SP,(OLDSTK) ; (Not enough memory or wrong uP) RET ; ;----------------------------------------------------------------------- ; ; Print fatal error messages. Jump to this routine- not a call! ; FATAL: CALL MESAGE ; One final message, then exit FATAL2: JR EXIT ; ;----------------------------------------------------------------------- ; ; Get junk off stack before exit ; POPEXIT:POP AF POP HL POP DE POP BC ; ; *** Common exit *** ; EXIT: CALL CRLF ; For neatness LD A,(LSTART) ; Load the printing flag OR A ; Are we sending to the printer?... JR Z,EXIT2 ; ..No, so exit LD A,FEED ; ..Yes, so load a formfeed and.. CALL LCOUT ; ...print a ford feed ; EXIT2: LD A,(USERNO) ; Restore user number saved at entry time LD E,A LD C,SGUSER CALL BDOSAV LD SP,(OLDSTK) ; Restore to system stack RET ; And return to system CCP ; ;______________________________________________________________________ ; ; Messages ; VUNITS EQU (VREV/16)+'0' ; Version, units dig, in ASCII VTNTHS EQU (VREV AND 0FH)+'0' ; Version, tenths dig, in ASCII MSG1: DEFB LF,' TYPELZH v',VUNITS,VTNTHS,' $' MSG2: DEFB LF,'Input file not found.$' MSG3: DEFB LF,'Not enough memory.$' MSG4: DEFB LF,'Program requires Z-80.$' MSG5: DEFB ' ---> $' MSG6: DEFB '[more] ','$' MSG7: DEFB CR ; Continues on next line BLANKS: DEFB ' ',CR,'$' MSG8: DEFB LF,'Invalid Crunched File.$' MSG9: DEFB LF,'File needs newer program revision.$' MSG11: DEFB ')',CR,LF DEFB ' [ ^X = abort = next line ' DEFB ' = next page ]',CR,LF,'$' MSG11A: DEFB ')',CR,LF,LF,' ==>> Sending file to printer',CR,LF,'$' MSG12: DEFB LF,'Invalid Squeezed File.$' MSG13: DEFB LF,'Invalid Library File.$' MSG14: DEFB LF,'File empty.$' MSG15: DEFB LF,'Member not found in Library.$' MSG16: DEFB CR,LF,LF,' Usage: TYPE [D [U]:] ' DEFB '[ ] [/O]' DEFB CR,LF,' [/O] is optional /N ' DEFB 'for no page breaks.',0 MSG16A: DEFB CR,LF,' or optional /L ' DEFB 'for printer output.',0 MSG17: DEFB LF,'Invalid user code.$' MSG18: DEFB LF,'Invalid drive specification.$' MSG19: DEFB LF,'Invalid filename.$' MSG20: DEFB LF,'File is restricted - sorry.$' MSG21: DEFB LF,'Line count limit exceeded. ' DEFB 'Please download the file.$' MSG22: DEFB LF,'Can''t type a .$' MSG23: DEFB ' file.$' MSG24: DEFB LF,'Invalid LZH encoded file.$' SPACE3: DEFB ' $' ; ;----------------------------------------------------------------------- ; INTWHL: DEFB 0 ; Internal wheel flag LBRFLG: DEFB 0 ; Init to 0 (non-lbr status) MEMNAM: DEFB 0,' ' ; *** temp *** Zero plus 11 blanks SECNT: DEFB 1 ; Count sectors read from input file COLCTR: DEFB 1 ; Current column position EOFLAG: DEFB 0 ; Zero after 1st EOF is encountered ; ;----------------------------------------------------------------------- ; DSEG ; ; Additional miscellaneous RAM locations which need not be initialized ; or are initialized by the routines which use them. ; OLDSTK: DS 2 ; CCP's stack value saved here on entry LSCNT: DS 2 LFCNTR: DS 1 ; Counts linefeeds (decr'd) LDEV: DS 1 ; List device flag - non-zero = LST: requested LSTART: DS 1 ; Actual list flag / enabled AFTER header done PAPLIN: DS 1 ; Counts linefeeds when LST: outputting FLNAM1: DS 2 ; Temp storage to a pointer to a filename -1 USERNO: DS 1 ; Storage for a user area number IBUFP: DS 2 ; Pointer to the input buffer TABLES: DS 2 ; Pointer to beg of avail ram after the bfr FCB1: DS 36 ; The input file FCB STACK: DS 64 ; Local stack- USQR & UNCRR allocate their own DS 128 ; Plus a tad more... ; TOPSTK EQU $ ; END