;************************************************************************ ;* * ;* CRunch LZH v1.1 * ;* 04 Sept 1989 * ;* - Roger Warren * ;************************************************************************ ; ; With the kind permission of Mr. Steven Greenberg, author of ; CRunch, this program was generated from his CRunch v2.4 code ; dated 15 Sept 1987. Accordingly, the following notifications ; are in order: ; ; Copyright (c) R. Warren 09/04/89 ; Portions Copyright (c) S. Greenberg 09/15/87 ; May be reproduced for non-profit use only ; .Z80 .SALL TITLE 'CRrunch LZH v1.1 04 Sept 1989' EXTRN PARSEU CSEG ;============================================================================== ; MEMPAG EQU 2000H ; <=== set! [see comment near end of program] ; ;============================================================================== ;.............................................................................. ;CRLZH HISTORY: ; v1.1 Official first release. No functional changes from Beta version. ; Merely stepped version for differentiation. ; v1.0 Beta test version ; ;CRunch HISTORY: ; v2.4 Update Note: As explained in the CRUNCH24 general release LBR, ; v2.4 will generate identical files (except embedded revision level ; byte) to CRUNCH v2.3. The great majority of the changes are user ; interface related, and are described in the CRUNCH24 documentation ; files. Some changes were made in the implementation of the "core" of ; the algorithms for both CRUNCH and UNCRunch- in the case of CRUNCH, ; conditionals were removed by splitting into three separate loops. In ; the case of UNCRunch, an unnecessary chase to the end of "virtual ; links" was eliminated by aborting the search as soon as an available ; reassignment slot is found. Other performance improving changes in ; clude less time updating the screen and dynamic I/O buffer sizing. ; Non-time-critical "user-interface" changes (eg the "tag mode" code, ; etc.) were coded in as straightforward a manner as possible, with ; little regard to code space minimization and even less to speed. ; ; While some documentation of the code has been cleaned up in the sev ; eral month interim between the CRUNCH24.LBR release and the release of ; this source code, I have been very careful to avoid any temptation to ; change any of the code itself, thus insuring that this source code can ; be used to create the identical COM files included in the v2.4 release ; of CRUNCH. FALSE EQU 0 ; TRUE EQU NOT FALSE ; CRUNCH EQU TRUE ; True for crunch, false for uncr (for common) REV EQU 11H ; Program revision level SIGREV EQU 10H ; "significant" revision level (compatibility) NOPRED EQU 0FFFFH ; "no predecessor" SCRUPT1 EQU 03H ; Screen update speeds SCRUPT2 EQU 0FH ; ; --- reserved codes --- EOFCOD EQU 100H ; Eof code ;--- Ascii equates --- ; CTRLC EQU 03H ; ^c BELL EQU 07H ; Beep BS EQU 08H ; Backspace LF EQU 0AH ; Linefeed CR EQU 0DH ; Carriage return ;--- CP/M address equates --- ; DFCB EQU 5CH ; Default file control block #1 DFCB2 EQU 6CH ; Default file control block #2 DDMA EQU 80H ; Default dma address BDOS EQU 0005H ; Bdos entrypoint ;--- BDOS function equates --- ; CONIN EQU 1 ; Input a character from the console CONOUT EQU 2 ; Output single char to console PRTSTR EQU 9 ; Print string to console CONST EQU 11 ; Get console status GETVER EQU 12 ; Get cp/m version# SELDSK EQU 14 ; Select disk OPEN EQU 15 ; Open file CLOSE EQU 16 ; Close file SFIRST EQU 17 ; Search for first file SNEXT EQU 18 ; Search for next file ERASE EQU 19 ; Erase file READ EQU 20 ; Read file (sequential) WRITE EQU 21 ; Write file (sequential) MAKE EQU 22 ; Make file GETDSK EQU 25 ; Get currently logged drive SETDMA EQU 26 ; Set dma address SETATR EQU 30 ; Set file attributes GSUSER EQU 32 ; Get/set user code RSTDRV EQU 37 ; Reset disk drive SETMS EQU 44 ; Set multi-sector count (cp/m+ only) ;.............................................................................. ; START: JP STRT ; <--- entry DB 'Z3ENV',01H ; Zcpr3 environment descriptor Z3ED: DB 00H,00H ; ---------------------------------------------- Z3FLG: DB 0 ; Zcpr flag ARCHIV: DB 0 ; Archive bit mode flag INSREV: DB 23H ; Program rev for install purposes QUIFL: DB 0 ; Quiet mode flag NPROFL: DB 0 ; No prompt before overwrite flag TRBOFL: DB 0 ; Defeat multi-sector i/o flag CNFRFL: DB 0 ; Confirm every file flag WRMFLG: DB 0 ; Warm boot flag BIGFLG: DB 0 ; Bigger file prompt flag MAXDRV: DB 0FFH ; Maximum drive allowed by program MAXUSR: DB 0FFH ; Maximum user# allowed by program SPARFL: DB 0FFH ; Spare flag (or value) ;.............................................................................. ; ; File type exclusion list. Must end with zero. ; |<-1->|<-2->|<-3->|<-4->|<-5->| EXTBL: DB 'ARC','ARK','LBR',0,0,0,0,0,0 ; |<-6->|<-7->|<-8->|<-9->|<10->| DB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DB 0 ; Must leave this terminating zero. DB 0 ; Leave this byte. Patch space for compat- ; ability with UNCRLZH ;-=*=-=*=-=*==*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=- CPYRT: DB CR,LF,LF DB 'CRLZH v1.1 Copyright (c) R. Warren 09/04/89',CR,LF DB ' Portions Copyright (c) S. Greenberg 09/15/87',CR,LF DB 'May be used/reproduced for non-profit use only$ 619-270-3148' ;-=*=-=*=-=*==*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=-=*=- STRT: SUB A ; Z-80 test [RAF] JP PO,Z80 ; LD DE,WRNGUP ; "Program requires Z-80 Processor" JP MESS80 ; Special no frills exit w/ message Z80: LD (OLDSTK),SP ; Save os's stack LD SP,TOPSTK ; Set local stack CALL STRTUP ; Does a lot of stuff ;.............................................................................. ; ; ***** Re-enter here for each matching file ***** ; ; General wildcard operation: When the program is first invoked, all ; matching filenames are put end to end in FNBUFF, 12 bytes apeice, in ; alphabetical order. Since a filename is only 11 characters long the ; spare byte, which precedes each filename, is used as a "tag/flag". By ; the time file processing starts (now), a number of routines have already ; run (parts of the STRTUP routine). These routines set the tag-flag ; which indicates to us now in what manner the file should be processed: ; "00" = "skip it", "01" = process it", "02" = "perform a direct copy (if ; possible)", "FF" = "no more files". ; NXTFIL: LD SP,TOPSTK ; Reset SP LD A,(QUIFM) ; OR A ; CALL Z,CRLF ; Extra CR/LF if not in "quiet" mode LD DE,INFCB ; Input file's fcb CALL CLRFCB ; Init it to blanks and zeroes INC DE ; Leave "DE" pointing at "INFCB+1" for below LD HL,(BUFPTR) ; Pntr to name of next file from expansion bfr NXTSEL: LD A,(HL) ; OR A ; If zero, the file is "unselected" JR NZ,ISSEL ; Br if it is selected LD BC,12 ; Else just quietly skip to the next file ADD HL,BC ; LD (BUFPTR),HL ; JR NXTSEL ; ;................................ ; The file is "selected"; prepare to process it ISSEL: CP 0FFH ; (FF means done) JP Z,RETCCP ; Br if that is the case PUSH AF ; Save stat (to see if file is "excluded" blw) INC HL ; Skip to 1st filename char LD BC,11 ; Filename character count LDIR ; Put next file name into input fcb LD (BUFPTR),HL ; Save new pointer for next file CALL INTRAM ; Initialize all ram LD A,01H ; This loc req's diff init for crunch vs uncr LD (CSAVE),A ; Goes there POP AF ; Get file's status byte back again CP 02H ; 02 if file matched the "exclusion" list JR NZ,COPNIN ; If not, definitely attempt to compress it LD A,(WLDFLG) ; If so, see if prgm was invoked w/ wildcards OR A ; JR Z,COPNIN ; If not, go attempt compression LD A,(DIFDU) ; Else see if a direct copy is in order OR A ; (flag set if data flow is to distinct DU:'s) JP Z,NXTFIL ; If not, forget the whole thing ;.............................................................................. ; ; Perform a direct straight copy of the file ; LD DE,DASHES ; "-----" for visual separation CALL MESAG2 ; JP COPY9 ; Performs the copy ;.............................................................................. ; ; Normal Processing; Prepare to compress the input file. First, open the input ; file. A failure here is unusual, since the file existed at the time the ; filename expansion took place. There are "normal" series of events which ; could lead up to this, however. ; COPNIN: LD DE,DASHES ; "-----" for visual separation CALL MESAG2 ; CALL OPNIN ; Attempt to open the next input file "INFCB" JR NC,OPOK ; Br if ok LD DE,ERR1 ; "input file not found" JP SKIP1 ; Skip to next file ; OPOK: CALL GETCHR ; start input machine JR NC,NOTMT ; If carry is set on 1st byte, file is empty LD DE,ERR0 ; "input file empty" JP SKP991 ; NOTMT: CP 76H ; If file starts with "76FE" or "76FF", it is JR NZ,CBL ; - already crunched or squeezed respectively ; "76FD" LZH PUSH AF ; 1st byte was "76H", take advance peek at 2nd EXX ; Carefully check next byte, w/o norm call LD A,(HL) ; EXX ; INC A ; Well? JR Z,ALRDSQ ; Br if already squeezed INC A ; JR Z,ALRDCR ; Br if already crunched INC A ; Check for LZH encoding JR Z,ALRDLZ ; Br if already LZH encoded POP AF ; ;.............................................................................. ; ALRDCR: POP AF ; LD DE,MSGCR ; "already crunched" JP SKP991 ; ALRDSQ: POP AF ; LD DE,MSGSQ ; "already squeezed" JP SKP991 ; ALRDlz: POP AF ; LD DE,MSGLZH ; "already LZH encoded" JP SKP991 ; ;.............................................................................. ; ; So far the input file is open. The output file is not. ; CBL: LD A,' ' ; For aesthetic alignment purposes CALL TYPE ; LD HL,INFCB ; Print input filename to console CALL PRNFIL ; LD DE,OUTFCB ; Now for the output fcb CALL CLRFCB ; Clear it INC DE ; Leave "DE" pointing at filename area CALL CPYNAM ; Copies filename from input fcb to output fcb LD HL,OUTFCB+9 ; Point to 1st letter of ext for analysis LD A,' ' ; See if extension is blank CP (HL) ; JR Z,FORYYY ; If so, force an extension of "YYY" LD A,'Y' ; See if middle letter is "Y" INC HL ; CP (HL) ; JR NZ,NORMY ; Normal condition- simply force 2nd ltr to y ;................................ INC HL ; Point to last char CP (HL) ; is y? JR NZ,NORMY ; Normal condition- simply force 3rd ltr to y DEC HL DEC HL ; Last chance...first char CP (HL) ; is y? JR NZ,NORMY ; Ok... LD DE,ERR7 ; If this happens, user better rename his file JP SKP991 ; But give him a straight copy, anyway ;...............................; ; FORYYY: LD HL,OUTFCB+9 ; Come here if an extension of "YYY" is needed LD A,'Y' ; LD (HL),A ; (A future version will rename "XYZ" files INC HL ; To "XYY" rather than "YYY", a better idea) LD (HL),A ; INC HL ; ;...............................; NORMY: LD (HL),A ; ;.............................................................................. ; ; Now open the output file. "OPNOUT" will check for duplicate filenames, ; and prompt if indicated. If carry is set on return, the file was not ; opened. DE points to an appropriate error message, if any. The routine ; also types an arrow to the screen, followed by a "PRNFIL" call to type ; the DU: and filename to the screen. CALL OPNOUT ; Do all that JP C,SKIP2A ; Skips to next file if so deemed by "OPNOUT" ;.............................................................................. ; ; Now both files are open. Eventually either both will be closed, or the ; input closed and the output deleted. LD A,76H ; Output the "76FD" header CALL OUTB ; Each call to "OUTB" outputs one byte LD A,0FDH ; CALL OUTB ; LD HL,INFCB ; Pointer to original (input) file's name CALL OUTFIL ; Embed it into the output file at bytes 2+ LD HL,STAMP ; Pointer to possible additional "stamp" chars IDOULP: LD A,(HL) ; Possibly get a stamp char INC HL ; Incr bfr pntr CALL OUTB ; (output at least one zero no matter what) OR A ; End of stamp bfr? JR NZ,IDOULP ; Loop till so ;........................................................... ; LD A,(QUIFM) ; Print "heading" if in verbose mode OR A ; JR NZ,QUIET1 ; LD DE,HEADNG ; (the "in / out " stuff) CALL MESAGE ; QUIET1: PAGE ;============================================================================== ; ; *** Main encoding loop *** ; ; LD A,0FFH ; Flag as old to COMMON.LIB LD (OLDFLG),A EXX ; Go back to start of file (already read some) LD HL,IBUF ; EXX ; LD HL,SECNT ; Bugger up the sector count since we just INC (HL) ; - reset the input pointer LD HL,(INCTR) ; [rev 2.1 fix] DEC HL ; Decr "inctr" for same reason LD (INCTR),HL ; LD A,'0' ; [rev 2.1 fix] LD (PROGBF+5),A ; Reset ascii display to zero LD HL,TABLE ; Point to large data area for CRLZH LD A,0 ; Zero (actually xx00xxxx) for ; normal checksum flag to CRLZH CALL CRLZH JP C,INSUFF ; only error is insufficient memory ONBND: LD A,(CHKSUM+0) ; Now output the checksum CALL OUTB ; (lo byte) LD A,(CHKSUM+1) ; CALL OUTB ; (high byte). This completes all output. CALL DONE ; Writes out partial output bfr, thru cur loc CALL CLSOUT ; Close the output file CALL CLSIN ; Close the input file (prevents inadvertent ; Accumulation of open files). ;.............................................................................. ; ; Now we are done with the file. The size of the resulting file will be com- ; pared with the original; if the resulting file is larger, file will be ; erased and the original will be copied in uncompressed format instead. This ; will only be done if the source and destination DU:'s are different ; (obviously a direct copy to the same drive and user is nonsensical). When ; this is the case, the user will be given the option of saving the "crunched" ; file- if he doesn't then it will be erased. ; LD A,(BIGFLG) ; Get size question override flag AND A ; Check if non-0, clear carry at same time JP NZ,NEXT ; Skip if bigger LD DE,(INCTR) ; Size of input file LD HL,(OUTCTR) ; Size of resulting file SBC HL,DE ; Compare JP C,NEXT ; (normally the case) LD A,(DIFDU) ; Dest du: differ from origin? OR A ; JP Z,ASKHIM ; If not, give option of saving larger file LD DE,MSG998 ; "not smaller..." CALL MESAG2 ; CALL ERAOUT ; Erase the output file COPY9: CALL COPY ; Perform a straight copy JP C,NXTFIL ; If the copy did not actually take place JR NEXT ; If it did, count it ;.............................................................................. ; SKP991: CALL MESAG2 ; Type predefined message LD A,(DIFDU) ; Dest du: differ from origin? OR A ; JP Z,NXTFIL ; JR COPY9 ; ;.............................................................................. ; ASKHIM: LD DE,QUES1 ; Result file not smaller than original CALL MESAGE ; Ask the guy if he wants it anyway CALL RSPNSE ; Get his response PUSH AF ; Nec? CALL CRLF ; POP AF ; JR NZ,SKIP4A ; "skip4a" erases output file, goes to next ;.............................................................................. NEXT: LD HL,NFP ; Increment #of files processed INC (HL) ; CALL ARCIT ; Flag input file as archived JP NXTFIL ; Repeat if still more files ;.............................................................................. ;................................ ; Entry if neither input nor output files SKIP1: CALL MESAGE ; - have been open yet SKIP1A: JP NXTFIL ; (entry here if no error text desired) ;................................ ; Entry here if input file open only SKIP2: CALL MESAGE ; SKIP2A: CALL CLSIN ; (entry here for no message) JP NXTFIL ; ;................................ ; Entry here if both input and output SKIP3: CALL MESAGE ; - files need to be closed SKIP3A: CALL CLSIN ; CALL CLSOUT ; JP NXTFIL ; ;................................ ; Entry here to erase output & close input file SKIP4: CALL MESAGE ; SKIP4A: CALL CLSOUT ; (entry here for no message) LD DE,OUTFCB ; Close, then erase output file LD C,ERASE ; CALL BDOSAV ; CALL CLSIN ; Close input file as well JP NXTFIL ; ;...............................; ; File I/O PLZHEN: JP OUTB ; continue at outb extrn CRLZH PUBLIC plzhen PUBLIC glzhen GLZHEN: ; fall thru to GETC ;============================================================================== ; ; Subr gets a char from the input stream & adds its value to running checksum. ; GETC: CALL GETCHR ; Get a char into a RET C ; Don't add in the garbage char recv'd on eof CALL CKSUM ; Add it in AND A ; Guarantee clear carry when no eof RET ; That's it ;------------------------------------------------------------------------------ ; ; Like "prnfil", but send chars to the output stream instead of typing. ; This routine WILL explicitly output blanks in the filename extension. ; OUTFIL: LD BC,0C20H ; B = loop counter, c = blank character CHARL2: INC HL ; Pre-incr pointer LD A,(HL) ; Get a char CP C ; Blank? JR Z,SKPTY2 ; Suppress them (but not in the .ext) TYPEI2: CALL OUTB ; Send char to the output stream SKPTY2: DEC B ; Loop counter RET Z ; Rtn when done LD A,B ; Check loop counter CP 4 ; At this point, type a "." JR NZ,CHARL2 ; LD A,"." ; This is also a convenient char to set "C" to LD C,A ; A "." cannot be found in an fcb filename JR TYPEI2 ; Type the ".". do no incr hl. ;============================================================================== ; ; "Stamp" processing. ; PRCSTM: PUSH DE ; Called w/ "HL" pointing to text of "stamp" LD DE,STAMP ; Buffer for holding the date stamp or text LD B,7FH ; Put a limit on its length STMPLP: LD A,(HL) ; Get a char LD (DE),A ; Put it in the buffer INC DE ; OR A ; Zero denotes end of cmnd tail, ending stamp JR Z,PRCDN1 ; INC HL ; SUB ']' ; The "proper" way the stamp should end JR Z,PRCDN2 ; DJNZ STMPLP ; Get more chars ERR8: LD DE,PRSER8 ; Stamp overflow, probably impossible JP FATALU ; PRCDN1: POP DE ; Come here if null terminated the stamp RET ; Return with the null in "A" & z set PRCDN2: LD (DE),A ; Make sure a null (a has one now) gets here NBLP: LD A,(HL) ; Advance to first non-blank after stamp CP ' ' ; JR NZ,NBC ; Br if we have one INC HL ; Else advance DJNZ NBLP ; And continue JR ERR8 ; Overflow error NBC: POP DE ; Rtn with "HL" pointing to 1st non-blank char OR A ; (rtn z stat if that char is null) RET ; ;.............................................................................. ; EXCLUD: ; Flag files matching the "exclusion list" LD BC,12 ; Leave 12 in bc for incrementing ix LD IX,FNBUFF ; Points to beg of filenames OUTLP: LD A,(IX+0) ; Get flag byte for this entry CP 0FFH ; Final [non-] entry? RET Z ; (return if so) OR A ; Is it an untagged filename? JR Z,NXTFN ; If so, leave it that way & move to next LD HL,EXTBL-3 ; Beg of "exclusion" list ; INRLP0: INC HL ; INRLP1: INC HL ; (if hl already incr'd once) INRLP2: INC HL ; ( " " twice) LD A,(HL) ; Get a char from list OR A ; End of list? JR Z,NXTFN ; If so, move on to next filename in "fnbuff" CP '?' ; Wildcard? JR Z,AUTOM1 ; Yes, automatically matches CP (IX+9) ; Else see if it matches first ft char JR NZ,INRLP0 ; No match, forget it and move to next filename AUTOM1: INC HL ; LD A,(HL) ; Repeat twice more for other 2 chars CP '?' ; JR Z,AUTOM2 ; CP (IX+10) ; JR NZ,INRLP1 ; AUTOM2: INC HL ; LD A,(HL) ; As above CP '?' ; JR Z,AUTOM3 ; CP (IX+11) ; JR NZ,INRLP2 ; AUTOM3: LD A,02H ; File type matches; flag file as "excluded" LD (IX+0),A ; NXTFN: ADD IX,BC ; Move to next filename in "fnbuff" JR OUTLP ; ;============================================================================== ; ; All ASCII centralized here as a service to disassembly hobbyists. ; VUNITS EQU (REV/16)+'0' ; Version, units dig, in ascii VTNTHS EQU (REV AND 0FH)+'0' ; Version, tenths dig, in ascii INTRO: DB 'LZH Cruncher v',VUNITS,'.',VTNTHS,CR,LF,'$' ERR7: DB ' [ Can''t crunch .YYY files ]$' MSGCR: DB ' [ Already crunched ] $' MSGSQ: DB ' [ Already squeezed ] $' MSGLZH: DB ' [ Already LZH encoded ] $' MSG998: DB CR,LF,' [ Result not smaller ] $' QUES1: DB 'Result not smaller. Save anyway? : ',BELL,'$' USAGE: DB CR,LF,LF,'Usage:',CR,LF,LF DB ' Filename Date, etc. Option letters',CR,LF DB ' / / /',CR,LF DB 'CRLZH {du:} {du:} { [id] } { / }',CR,LF DB ' \ \ |',CR,LF DB ' Source Destination (space)' DB CR,LF,LF DB ' is up to 4 letters immediately following a " /".',CR,LF DB ' "Q" = Quiet mode "C" = Confirm (tag) mode',CR,LF DB ' "O" = Overwrite mode "A" = Archive bit mode',CR,LF DB ' Option letters toggle (reverse) the corresponding default setup.',CR,LF DB CR,LF DB ' Both "du:" are of form DU:, UD:, D:, or U:',CR,LF DB ' "[id]" is date or any text enclosed in "[ ]".',CR,LF DB CR,LF DB ' Everything is optional except filename.',CR,LF,'$' ;============================================================================== ; ; ** Include file begins here ** INCLUDE COMMON.LIB ; ** Include file ends here ** ; ;============================================================================== ; Additional misc ram locs which need not be initialized, or are init- ; ialized by the routines which use them. CSAVE: DS 1 ;................................ ; SAFETY: DS 16 ; Safety region beyond stack limit check ENDPRG EQU $ ; (approx bottom of stack) ;______________________________________________________________________________ ; STKSZ EQU 8 ; Minimum stack size (pages) IBUFSZ EQU 8 ; Input buffer size (pages) ;============================================================================== ; ; ===> All tables will begin at "MEMPAG", defined at the top of the pro- ; gram. This should be set to a page aligned value (ie address that ends in ; "00") which is ABOVE the end all program and data segments. You may have ; to do one test link to determine the proper value (changing "MEMPAG" will ; not change the length of the segments on the subsequent link). ; ; "MEMPAG" is defined at the beginning of this program to remind you to set ; it properly. If you set it higher than necessary, there will be no negative ; effect other than an increase in the TPA req'd to run the program. If you ; set it too low, you will be in big trouble. The value must be set manually ; because most linkers cannot resolve an "and", "shift", or "hi" byte ; extraction at link time to determine the page boundary. ; ;============================================================================== ; "MAXFLS" is buffer size (in files) for wildcard expansions. Room for ; this many files will be allocated. MAXFLS EQU 256 TOPSTK EQU MEMPAG+(STKSZ*256) ; Top of stack IBUF EQU TOPSTK ; (= beg of input buffer) EIBUF EQU IBUF+(IBUFSZ*256) ; End of input buffer TABLE EQU EIBUF ; (= beg of table) EOTBL EQU TABLE+(5*20*256) ; End of table FNBUFF EQU EOTBL ; (= beg of wildcard expansion buffer) ENDFNB EQU FNBUFF+(12*MAXFLS) ; End of expansion buffer STAMP EQU ENDFNB ; File "stamp" buffer ** size temp *** ENDALL EQU STAMP+100H ; End of everything, except output buffer OBUF EQU ENDALL ; Beg of dynamically sized output buffer ;------------------------------------------------------------------------------ IBUFHI EQU HIGH IBUF ; Input bfr addr, hi byte (lo byte = 0) EIBFHI EQU HIGH EIBUF ; End of input bfr addr, hi byte, likewise TABLHI EQU HIGH TABLE ; Beg of table, hi byte, likewise ETBLHI EQU HIGH EOTBL ; End of table, hi byte, likewise EFNBHI EQU HIGH ENDFNB ; End of expansion buffer, likewise ENDHI EQU HIGH ENDALL ; OBUFHI EQU HIGH OBUF ; Output bfr addr, hi byte likewise END