home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
CP/M
/
CPM_CDROM.iso
/
cpm
/
utils
/
squsq
/
unsq15.lbr
/
UNSQ15.AQM
/
UNSQ15.ASM
Wrap
Assembly Source File
|
1985-02-09
|
20KB
|
1,040 lines
;UNSQ.ASM ver. 1.5 - A Z80 assembly language version of USQ.
;Copyright (C) 1983,1984 by Gail Zacharias, 345 Harvard St.,Apt. 2A,
;Cambridge, MA 02138. Phone (617) 876-3035.
;
;Commands:
; UNSQ inputfile [ outputdrive: ]
; Unsqueezes files created with SQ. Input filename may be ambiguous.
; Any matching non-SQ files will be ignored.
;
; UNSQ inputfile T
; Unsqueezes files and types them out on the console.
; ^S pauses output, ^O toggles output on/off.
;
;In either form, ^C aborts, ^X skips to next file.
;
;Modifications/updates (in reverse order)
;
;06/02/84 - Fixed bug introduced in 1.3 where buffer boundaries used wrong
; UNSQ15 offsets. (GZ for C.Falconer)
;
;04/21/84 - Changed ORG statement to allow assembly for
; UNSQ14 non-standard CP/M systems. (KBP)
;
;03/28/84 - Added option to save alternate registers across
; UNSQ13 system calls. (GZ)
;
;11/07/83 - Renamed from USQ to UNSQ to avoid confusion with
; UNSQ12 other programs of the same name. Released for
; non-commercial use by permission of Gail Zacharias. (KBP)
;
;Originally written in March 1983. Converted to assemble on
;CP/M with MAC and Z80.LIB -- April 1983 by Keith Petersen, W8SDZ
;
MACLIB Z80 ;Macro Library for MAC to know Z80
;
TABEX EQU -1 ;Sofware-expand tabs on TTY output
;Set to 0 if your terminal has hardware tabs.
EXXOS EQU -1 ;Preserve alternate registers across os calls
;Set to 0 if your system doesn't mung them.
;
ID1 EQU 076H ;Low ID byte
ID2 EQU 0FFH ;High ID byte
DLE EQU 090H ;Multiples-collapsing escape
;
;CP/M stuff
;
BASE EQU 0 ;Base address of standard CP/M
;
XBDOS EQU 5 ;System BDOS address
;
IF NOT EXXOS
BDOS EQU 5
ENDIF
;
DFCB EQU 5CH
DFCB2 EQU DFCB+10H
DBUF EQU 80H
;
FCB@EX EQU 0CH
FCB@CR EQU 20H
;
CONIN EQU 1 ;Console Input
CONOUT EQU 2 ;Console Output
PCS EQU 9 ;Print Console String
RCS EQU 10 ;Read Console String
OPENF EQU 15 ;Open File
CLOSF EQU 16 ;Close File
SFF EQU 17 ;Search For First
SFN EQU 18 ;Search For Next
DELF EQU 19 ;Delete File
RSS EQU 20 ;Read Sector Sequential
WSS EQU 21 ;Write Sector Sequential
MAKEF EQU 22 ;Make File
SDMA EQU 26 ;Set DMA
;
CR EQU 'M'-'@'
LF EQU 'J'-'@'
;
;Flags
TTYFLG EQU 7 ;TTY output (not DISK)
FLSFLG EQU 6 ;TTY output temporarily being flushed
EOFFLG EQU 5 ;Past EOF, only reading for checksum (when TTY)
FILFLG EQU 4 ;Have a file (always false for TTY)
;
ORG BASE+100H ;TPA
;
OBUF EQU $ ;Output buffer beginning page
CHKSUM EQU $+1 ;Checksum
;
START: JMP INIT
;
;I/O Transfer subroutine.
; Called with buffer address in DE, FCB address in HL, I/O code in A.
; Returns with NZ set if error, DE=DE+80h, all other registers preserved.
; IOSB gets error status if error. Carry always cleared.
; Gives user a chance to abort.
IOT: PUSH B
PUSH D
PUSH H
PUSH PSW
CALL SETDMA
CALL CONCHK ;Wanna quit?
POP B
POP D
PUSH D
PUSH B
MOV C,B
CALL BDOS
POP B
POP H
XTHL
LXI D,80H
DAD D
XCHG
POP H
ORA A
JRZ IOT1
STA IOSB
;
IOT1: MOV A,B
POP B
RET
;
;Page I/O Transfer.
; Called with A=beginning page, H=end page, BC=FCB, L=I/O code.
; Returns with NZ set if error, C=# pages, HL=beginning address,
; B,DE,A clobbered.
; If A=H, returns with Z set but HL clobbered.
; For input transfer returns with Carry set if had EOF last time.
POT: LDA OBUF
MVI L,WSS
LXI B,OFCB
JR PIOT
;
PIT: MVI A,IBUF
;
PIT1: MOV L,A
LDA IOSB
ORA A
MOV A,L
STC
RNZ
MVI L,RSS
LXI B,IFCB
;
PIOT: PUSH B
MOV D,A
MOV A,H
SUB D
MOV B,A
MOV C,A ;Save it to return
JRZ PIOT2
XRA A ;This sets Z for first time in loop
MOV E,A ;Page number --> address
MOV A,L
POP H
PUSH D ;Save it to return
;
PIOT1: CZ IOT ;Do a page (2 sectors)
CZ IOT
DJNZ PIOT1
;
PIOT2: POP H
RET
;
;Flush output file.
; Called with message pointer in DE.
; Closes and deletes the file. All regs clobbered.
FLUSH: CALL PRINT ;Explain the reason
LDA FLAGS ;Nothing to flush if no file
BIT FILFLG,A
RZ
MVI C,CLOSF ;Close it
CALL OFDOS
INR A
JZ CLSERR
MVI C,DELF
JMP OFDOS ;Delete and return, dont care if fails
;
CLSERR: LXI D,CLSERM
JMP EXIT
;
;Read Huffman encoded character.
; Called with HL'=pointer, B'=bit count, C'=page count.
; Returns with A=char, NZ set if eof, HL',B',C' updated, DE' clobbered.
; If eof then A=0.
GETERM: DB ' ** Bad SQ file: Missing EOF marker **',CR,LF,'$'
;
HUFC: EXX ;Get alternate registers
XRA A ;Init tree offset
;
HUFC0: DJNZ HUFC2
INR L ;New byte
JRNZ HUFC1
INR H ;New page
DCR C
JRNZ HUFC1
PUSH PSW ;New bufferful
CALL PIT
LXI D,GETERM ;Past EOF? (This doesnt catch all past-EOF
JC FABT ;errors, just those which try to go around the
;the buffer a 2nd time. Others will be caught
;by the checksum, presumably)
POP PSW
;
HUFC1: MVI B,8
;
HUFC2: PUSH H ;DE=Tree+4*A (The node address)
MOV L,A
MVI H,0
DAD H
DAD H
LXI D,TREE
DAD D
XCHG
POP H
RRCR M
JRNC HUFC3 ;Want car, ok
INX D ;Else want cdr
INX D
;
HUFC3: INX D ;high
LDAX D
DCX D
ORA A
JRNZ HUFC4 ;Leaf
LDAX D
JR HUFC0
;
HUFC4: INR A ;Set eof flag
LDAX D ;Get actual data
CMA
EXX ;Back to regular regs
RET
;
;Filename Character Check.
; Entered with character in A.
; Returns with NC if illegal, C if legal. In latter case, Z if '.'
; Character gets upcased.
FCCHK: ANI 7FH
CPI ' '+1
CMC
RNC ;space or less
CPI '*'
RZ ;*
CPI ','
RZ ;,
CPI '.'
CMC
RZ ;.
CPI ':'
RC ;Everything else before : is ok
CPI '@'
CMC
RNC ;:;<=>?
CPI '['
RZ ;[
CPI ']' ;]
RZ
CPI 'a'
RC ;@,uppercase letters,\,^,_,` all ok
CPI 'z'+1
JRNC FCCHK1
ADI 'A'-'a' ;upcase setting carry
RET ;cause we accept lowercase letters as ok
;
FCCHK1: CPI 7FH ;Clear carry for rubout
RET ;else {|} are ok.
;
;Fill Output Fcb.
; Called with filename pointer in DE, length in A.
; Returns with everything clobbered, NC if error in filename, otherwise
; OFCB has the name.
OUTFCB: LXI H,OFCB+1 ;Fill with spaces
MVI B,11
;
OUTF0: MVI M,' '
INX H
DJNZ OUTF0
ORA A
RZ ;Too short
CPI 12+1
RNC ;Too long
MOV C,A ;save
MOV B,A
LXI H,OFCB
;
OUTF1: INX D
LDAX D
CALL FCCHK
RNC ;Illegal char
JRNZ OUTF2 ;Not '.', ok
ORA A ;Clear carry
DCR C
RZ ;Too short, or we are in file type already
MVI C,1 ;Mark as being in file type
MOV A,B
CPI 4+1
RNC ;Type too long
LXI H,OFCB+8
JR OUTF3
;
OUTF2: INX H
MOV M,A
;
OUTF3: DJNZ OUTF1
MOV A,C
CPI 8+1
RET ;Illegal if no . and more than 8 long
;
;Word move.
; Called with source in DE, destination in HL, length in B.
; Moves non-space characters. DE & HL advanced, A,B clobbered.
WMOVE: LDAX D
INX D
ANI 7FH
CPI ' '
JRZ WMOVE1
MOV M,A
INX H
;
WMOVE1: DJNZ WMOVE
RET
;
;Filename Type.
; Called with FCB in DE. Everything clobbered.
NAMBUF: DB 15 ;Buffer length
DS 1+15
;
FTYPE: LXI H,NAMBUF+1
LDAX D
INX D
ORA A
JRZ FTYPE1 ;Default drive
ADI 'A'-1
MOV M,A
INX H
MVI M,':'
INX H
;
FTYPE1: MVI B,8
CALL WMOVE
MVI M,'.'
INX H
MVI B,3
CALL WMOVE
LXI D,NAMBUF
STC
DSBC D
MOV A,L
XCHG
;JP ATYPE ;(falls into ATYPE)
;
;Ascii Type.
; Called with length in A, (back)pointer in HL.
; Returns with everything clobbered.
ATYPE: ORA A
RZ
MVI C,CONOUT
MOV B,A
;
ATYPE0: INX H
MOV E,M
PUSH H
PUSH B
CALL BDOS
POP B
POP H
DJNZ ATYPE0
RET
;
; Random little utilities.
CRLFMSG:DB CR,LF,'$'
;
CRLF: LXI D,CRLFMSG
PRINT: MVI C,PCS
JBDOS: IF NOT EXXOS
JMP BDOS
ENDIF
IF EXXOS
BDOS: CALL SAVEXX
CALL XBDOS
RETEXX: CALL RESEXX
RET
;
SAVEXX: EXX
XTHL
PUSH D
PUSH B
PUSH H
XXHL: LXI H,0
XXDE: LXI D,0
XXBC: LXI B,0
EXX
RET
;
RESEXX: EXX
SHLD XXHL+1
SDED XXDE+1
SBCD XXBC+1
POP H
POP B
POP D
XTHL
EXX
RET
;
ENDIF
;
OFDOS: LXI D,OFCB
JR JBDOS
IFDOS: LXI D,IFCB
JR JBDOS
;
SDDMA: LXI D,DBUF
SETDMA: MVI C,SDMA
JR JBDOS
;
;Open Output File.
; Called with original name pointer in HL, length in A.
; Returns with everything clobbered, file open on OFCB.
NEWMSG: DB ' Name to use instead ==> ','$'
DELMSG: DB ' File exists, delete (Y/N)?:','$'
DELERM: DB ' ++ Cannot delete file. ++','$'
MAKERM: DB ' ++ Cannot make file (dir full?) ++','$'
;
OUTFIL: PUSH H
PUSH PSW
CALL ATYPE ;Type original name
CALL CRLF
POP B
POP D
LDA FLAGS ;TTY output?
RAL
RC ;Then no file to get
MOV A,B
;
OUTNAM: CALL OUTFCB ;Good name?
JRC OUTDEL
;
OUTNM1: LXI D,NEWMSG ;Lost, ask him for a new one
CALL PRINT
LXI D,NAMBUF
MVI C,RCS
CALL BDOS
CALL CRLF ;Bdos only echos CR (sigh)
LXI D,NAMBUF+1
LDAX D
JR OUTNAM ;Try again
;
OUTDEL: CALL SDDMA
XRA A
STA OFCB+FCB@CR
STA OFCB+FCB@EX
MVI C,SFF
CALL OFDOS
INR A
JRZ OUTMAK
LXI D,DELMSG
CALL PRINT
MVI C,CONIN
CALL BDOS
PUSH PSW
CALL CRLF
POP PSW
ORI 20H
CPI 'y'
JRNZ OUTNM1
MVI C,DELF
CALL OFDOS
INR A
JRZ DELERR
;
OUTMAK: MVI C,MAKEF
CALL OFDOS
INR A
LXI H,FLAGS
SETB FILFLG,M
RNZ
LXI D,MAKERM
JR JEXIT
;
DELERR: LXI D,DELERM
;
JEXIT: JMP EXIT
;
;Get tree Node.
; Called with input pointer in HL, output in DE
; Returns with HL,DE advanced, A,C clobbered
; NC set if node out of range.
GETNOD: INX H ;Low
MOV A,M
STAX D
INX D
MOV C,A
INX H ;High
MOV A,M
STAX D
INX D
INR A ;Make sure in -257 to 255 range
CPI 2
RC ;High= FF or 00, always in range
INR A
RNZ ;Else high not FE is illegal
INR C
RNZ ;And anything but FEFF is illegal
STC
RET
;
;Unsqueeze a huffman encoded file.
; Called with file open on IFCB, drive field initialized in OFCB, OBuf set up.
ORGMSG: DB ' ==> ','$'
IDERM: DB 'Not a SQ file',CR,LF,'$'
FNMERM: DB '** Original filename way too long!',CR,LF,'$'
NCTERM: DB '** Node count too large',CR,LF,'$'
TREERM: DB '** Tree node not in -257:255 range',CR,LF,'$'
CLSERM: DB ' ++ Cannot close file ++','$'
CHKMSG: DB ' ** Warning: Checksum did not match **',CR,LF,'$'
NOFMSG: DB ' (Empty output file, deleting)',CR,LF,'$'
;
FABMSG: DB CR,LF,' ++++ File aborted ++++',CR,LF,'$'
;
TREERR: LXI D,TREERM
;JP FABT ;(falls into FABT)
;
FABT: CALL FLUSH ;Flush output file if any
;JP NXTF ;(falls into NXTF)
;
NXTF: LXI SP,STACK ;Reset stack
MVI C,CLOSF ;This is probably not needed but..
CALL IFDOS ; close old input file anyhow
LXI H,IFCB+1 ;Reset search context
LXI D,DFCB+1
LXI B,11
LDIR
CALL SDDMA
XRA A
STA DFCB+FCB@CR
STA DFCB+FCB@EX
MVI C,SFF
LXI D,DFCB
CALL BDOS
LXI H,REQNAM ;Put back wildcard name
LXI D,DFCB
LXI B,12
LDIR
;
NXTF0: MVI C,SFN ;Find next file
;
FIRSTF: CALL BDOS ;Enter here for first time around
INR A
JZ FINISH
DCR A ;Get a pointer to filename
RRC
RRC
RRC
MOV L,A
MVI H,0
LXI D,DBUF+1
DAD D
LDA REQNAM ;Get original drive
LXI D,IFCB
STAX D
INX D ;Move found filename to the input FCB
LXI B,11
LDIR
LDA IFCB+10
RAL
JRC NXTF0 ;SYS file, try again
LHLD FCOUNT ;Have file, update count
INX H
SHLD FCOUNT
XRA A
STA IFCB+FCB@CR
STA IFCB+FCB@EX
STA IOSB ;Init IOSB
;
IF TABEX
STA COLUMN ;Current column
ENDIF
;
LXI H,FLAGS ;Reset all but ttyflg (flsflg,filflg,eofflg)
MOV A,M
ANI 1 SHL TTYFLG
MOV M,A
MVI C,OPENF ;Open the file
CALL IFDOS
INR A
LXI D,OPNERM
JZ EXIT
;
; Input file is open, flags, iosb initialized.
;
LXI D,IFCB ;Say 'Filename ==> '
CALL FTYPE
LXI D,ORGMSG
CALL PRINT
LXI H,0FEFFH ;Init tree in case no nodes
SHLD TREE
SHLD TREE+2
MVI H,IBUF+1 ;Read in a page to start with
CALL PIT
MOV A,M ;1st ID byte
CPI ID1
LXI D,IDERM
JRNZ JFABT ;Not a SQ file
INX H ;2nd ID byte
MOV A,M
CPI ID2
;
JFABT: JNZ FABT ;Not a SQ file
;
; File starts with proper SQ header.
;
UNSQF: INX H ;Checksum
MOV E,M
INX H
MOV D,M
SDED CHKSUM
PUSH H ;Save filename pointer
MVI B,250 ;(Can't be more than 250, only read in a page)
MOV C,B
;
FNM: INX H
MOV A,M
ORA A
JRZ FNM1
DJNZ FNM
LXI D,FNMERM
JMP FABT ;Name way to long, give up
;
FNM1: MOV A,C
SUB B ;A=length of name
PUSH PSW ; Save it
PUSH H ;Get more file
MVI A,IBUF+1
MVI H,IBUF+5
CALL PIT1
POP H
INX H ;Number of nodes
MOV B,M ;Low
INX H
MOV A,M ;High
LXI D,TREE
ORA A
JRZ TREE0 ;Less than 100h, ok
DCR A ;Else better be exactly 100h
ORA B
JRZ TREE1
LXI D,NCTERM ;Bad node count
JMP FABT
;
TREE0: ORA B
JRZ BUFS ;Skip loop if exactly 0
;
TREE1: CALL GETNOD ;Car
;
JTREER: JNC TREERR
CALL GETNOD ;Cdr
JRNC JTREER
DJNZ TREE1
;
; Have read in filename, checksum, tree, everything looks ok.
; Filename pointer and length are on stack
BUFS: PUSH H ;Fill rest of buffer
LDA OBUF
MOV H,A
MVI A,IBUF+5
CALL PIT1
POP H
POP PSW ;Get back length
XTHL ;get back start pointer
CALL OUTFIL ;Get us a file
POP H
LDA OBUF ;Init input setup
SUB H
MOV C,A
MVI B,1
ADD H ;Restore to (obuf) for below
EXX ;And put it away
DCR A ;Init output setup
MOV H,A
MVI L,0FFH
LDA XBDOS+2
SUI 8+1 ;2K for ccp
SUB H
MOV D,A
;
; All set up, do it!
;
JR HUFF ;Jump into loop
;
HUFF0: MVI A,DLE
;
HUFF1: MOV C,A ;Save
CALL PUTC
;
HUFF: CALL HUFC
JRNZ FILL ;Eof, done
CPI DLE
JRNZ HUFF1
CALL HUFC
JRNZ HUFF2 ;Got end of file, A=00h but means 100h
ORA A
JRZ HUFF0 ;0 repeat count means real DLE
;
HUFF2: DCR A ;Account for one we already did before DLE
JRZ HUFF ;Hmm...
MOV B,A
;
HUFF3: CALL PUTC
DJNZ HUFF3
JR HUFF
;
FILL: LDA FLAGS
RAL ;TTY output?
JRC CHKCHK ;Nothing to save then
MOV A,L ;Round off sector with ^Zs
CMA
ANI 7FH
JRZ SAVE
;
FILL1: INX H
MVI M,'Z'-'@'
DCR A
JRNZ FILL1
;
SAVE: INX H
LDA OBUF
SUB H
ORA L
PUSH PSW ;Remeber if had no output
JRZ CLOSE ;and skip saving
PUSH H
CALL POT
POP H
JRNZ OUTERR
SLAR L
JRNC CLOSE
LXI D,OFCB ;Output orphan sector
XCHG
MVI A,WSS
CALL IOT
JRNZ OUTERR
;
CLOSE: MVI C,CLOSF ;Close the file
CALL OFDOS
INR A
JZ CLSERR
POP PSW ;Get back data flag in Z
JRNZ CHKCHK ;Had data, ok
LXI D,NOFMSG ;Else tell him
CALL PRINT
MVI C,DELF ;and flush empty file
CALL OFDOS
;
CHKCHK: LHLD CHKSUM ;Check checksum
LXI D,CHKMSG
MOV A,H
ORA L
CNZ PRINT ;Print warning but keep file anyway.
JMP NXTF ;And do it again
;
OUTMSG: DB ' ++ Error writing sector (disk full?) ++','$'
;
OUTERR: LXI D,OUTMSG
;
QUIT: CALL FLUSH
JMP DONE
;
;Put character.
; Called with character in C, pointer in HL, page count in D.
; Returns with HL,D updated, A and E clobbered, BC preserved.
; If TTYFLG is on, HL,D are ignored and clobbered as well.
PUTC: PUSH B
PUSH H
LHLD CHKSUM
XRA A
MOV B,A
DSBC B
SHLD CHKSUM
PUSH D
CALL CONCHK ;Had enough?
POP D
POP H
LDA FLAGS
RAL
JRC TPUTC ;Do TTY output
INR L
JRNZ PUTC1
INR H ;Another page
DCR D
JRNZ PUTC1
CALL POT
JRNZ OUTERR
MOV D,C
;
PUTC1: POP B
MOV M,C
RET
;
TPUTC: RAL ;flsflg?
JRC TPUTCX
RAL ;eofflg?
JRC TPUTCX
MOV A,C
POP B
CPI 'Z'-'@'
JRNZ TPUTCC
LXI H,FLAGS
SETB EOFFLG,M
RET
;
TPUTCC: ANI 7FH
CPI '['-'@'
JRNZ TPUTC1
MVI A,'$'
;
TPUTC1: PUSH B
CPI 'G'-'@'
JRZ BPUTC
CPI 'J'-'@'
JZ BPUTC
;
TPUTC3: IF TABEX
LXI H,COLUMN
ENDIF
;
CPI 'I'-'@'
JRZ TPUTT
CPI 'L'-'@'
JRZ TPUTC0
CPI 'M'-'@'
JRZ TPUTC0
CPI 7FH
JRZ TPUTC2
CPI ' '
JRC TPUTC2
;
IF TABEX
INR M
ENDIF
;
BPUTC: MOV C,A
;
IF EXXOS
CALL SAVEXX
ENDIF
BPUTC1: CALL 0 ;CONOUT through bios
IF EXXOS
CALL RESEXX
ENDIF
;
TPUTCX: POP B
RET
;
TPUTC2: MOV B,A ;Save char
MVI A,'^' ;Output ^
CALL TPUTCC
MOV A,B ;Now output decontrolified char
XRI 40H
JR TPUTC3
;
IF TABEX
TPUTC0: MVI M,0
JR BPUTC
;
TPUTT: MOV A,M ;Print a tab. HL points to column.
CMA
ANI 7
INR A
MOV B,A
;
TPUTT1: MVI A,' '
CALL TPUTCC
DJNZ TPUTT1
JR TPUTCX
ENDIF
;
IF NOT TABEX
TPUTC0 EQU BPUTC
TPUTT EQU BPUTC
ENDIF
;
;Check console for control characters.
;All regs clobbered.
;
ABTMSG: DB ' ++ Aborted ++','$'
;
CONCHK: IF EXXOS
CALL SAVEXX
ENDIF
CONCK1: CALL 0 ;CONST through bios
ORA A
BGETC1: CNZ 0 ;CONIN through bios
LXI H,FLAGS
BIT TTYFLG,M ;Are we outputting to the TTY
JRZ CONCH1 ;If not, dont check for ^S/^O
PUSH H
CPI 'S'-'@' ;^S=pause until character typed
BGETC2: CZ 0 ; CONIN through bios
POP H
CPI 'O'-'@' ;^O=toggle flush flag
JRNZ CONCH1
MOV A,M
XRI 1 SHL FLSFLG
MOV M,A
IF NOT EXXOS
RET
ENDIF
IF EXXOS
JMP RETEXX
ENDIF
;
CONCH1: IF EXXOS
CALL RESEXX
ENDIF
CPI 'C'-'@' ;^C means abort
LXI D,ABTMSG
JZ QUIT
CPI 'X'-'@' ;^X means abort current file
LXI D,FABMSG
JZ FABT
RET
;
OPNERM: DB ' ++ Cannot open file ++','$'
;
FINISH: LHLD FCOUNT
MOV A,H
ORA L
JRNZ DONE
LXI D,NOPERM ;Complain that didn't find any files
;
EXIT: CALL PRINT ;Print reason
;
DONE: LSPD STACK
RET
;
;Storage which doesn't require initialization, don't bother putting
;in COM file...
TREE EQU $ ;The huffman code tree
IOSB EQU TREE+(4*256) ;I/O status byte, saved on error in IOT
;
IF TABEX
COLUMN EQU IOSB+1 ;Current output column, for tab expansion
ENDIF
;
IF NOT TABEX
COLUMN EQU IOSB
ENDIF
;
FLAGS EQU COLUMN+1
FCOUNT EQU FLAGS+1 ;Number of files looked at all together.
OFCB EQU FCOUNT+2 ;Output FCB
IFCB EQU OFCB+33 ;Input FCB
REQNAM EQU IFCB+33 ;Requested name, wildcards and all
TOS EQU REQNAM+12 ;Top of stack area
STACK EQU TOS+(2*25) ;Saved SP
PGMEND EQU STACK+2 ;That's all folks
;
IBUF EQU (PGMEND+0FFH) SHR 8 ;Input buffer page
;
;Initialization code -- should be under 1K so fits under Tree memory
;
NOPERM: DB ' ++ File not found ++','$'
;
HLPMSG: DB 'UNSQ inputfile [ outputdrive: ]',CR,LF
DB 'Unsqueezes files created with SQ. Input '
DB 'filename may be ambiguous.'
DB CR,LF,'Any matching non-SQ files will be ignored.'
DB CR,LF,CR,LF,'UNSQ inputfile T'
DB CR,LF,'Unsqueezes files and types them out on the console.'
DB CR,LF,'^S pauses output, ^O toggles output on/off.'
DB CR,LF,CR,LF,'In either form, ^C aborts, ^X skips to next file'
DB '$'
;
INIT: LXI H,0 ;Establish local stack and save old one
SHLD FCOUNT ; (Init count while have a 0 in hl...)
DAD SP
LXI SP,STACK+2
PUSH H
IF EXXOS
EXX
SHLD XXHL+1 ;Save OS alternate registers
SDED XXDE+1
SBCD XXBC+1
EXX
ENDIF
LHLD BASE+1 ;Init BIOS routines
LXI D,3
DAD D
SHLD CONCK1+1
DAD D
SHLD BGETC1+1
SHLD BGETC2+1
DAD D
SHLD BPUTC1+1
XRA A
LXI H,FLAGS
MOV M,A
LXI D,HLPMSG ;Prepare to give help at the drop of a hat
LDA DFCB+1 ;Anything there?
CPI ' '
JZ EXIT
LDA DFCB2+1 ;Output filename is flags (sigh)
CPI ' '
JRZ INIT1
CPI 'T'
JNZ EXIT
SETB TTYFLG,M ;TTY output:
LDA XBDOS+2 ;Use everything for input buffer...
SUI 8+1
STA OBUF
JR INIT2
;
INIT1: LDA DFCB2 ;Save the output drive
STA OFCB
LDA XBDOS+2 ;Establish buffer boundary
SUI 8+1+IBUF ;with input buffer about 60% of the output
SRLR A
SRLR A
MOV B,A
SRLR A
ADD B
ADI IBUF
STA OBUF
;
INIT2: LXI H,DFCB ;Save the input filename for future searches
LXI D,REQNAM
LXI B,12
LDIR
XRA A ;Find the first input file
STA DFCB+FCB@EX
STA DFCB+FCB@CR
MVI C,SFF
LXI D,DFCB
JMP FIRSTF
;
END