home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
ftp.barnyard.co.uk
/
2015.02.ftp.barnyard.co.uk.tar
/
ftp.barnyard.co.uk
/
cpm
/
walnut-creek-CDROM
/
ZSYS
/
SIMTEL20
/
ZSIG
/
UF.LBR
/
UF.ZZ0
/
UF.Z80
Wrap
Text File
|
2000-06-30
|
27KB
|
948 lines
; **********************************************************************
; * *
; * Fast Z80 Unsqueezer *
; * First ZCPR3 Version *
; * 1.0, 7/1/86, by *
; * Bruce Morgen, *
; * derived from *
; * v1.9 2 April 1986 *
; * and v2.0 June 1986 *
; * Original version and algorithm by Steven Greenberg, 1/10/86 *
; * *
; **********************************************************************
; Opcode equates
JPOP EQU 0C3H ; Opcode for "JP" instruction
; ASCII equates
CR EQU 0DH
LF EQU 0AH
; CP/M address equates
DFCB EQU 5CH ; Default file control block
DFCB2 EQU 6CH ; Secondary DFCB
DDMA EQU 80H ; Default DMA address
CPM EQU 0000H ; Warm boot jump address
BDOS EQU 0005H ; BDOS entry point
TPA EQU 0100H ; Transient execution call address
; BDOS function equates
CONOUT EQU 2 ; Print character to console
PRTSTR EQU 9 ; Print string to console
OPEN EQU 15 ; Open file
CLOSE EQU 16 ; Close file
ERASE EQU 19 ; Erase file
READ EQU 20 ; Read file (sequential)
WRITE EQU 21 ; Write file (sequential)
MAKE EQU 22 ; Make file
GCURDK EQU 25 ; Get default disk drive
SETDMA EQU 26 ; Set dma address
GSUSER EQU 32 ; Get/set user area
;-----------------------------------------------------------------------
ORG TPA
ENTRY: JP START
OUTUSR: DB 0
INUSR: DB 0
OLDSTK: DB 'Copyright (c) Steven Greenberg 1/10/86,201-670-8724,'
DB 'reproduce for non-profit only!'
START: LD A,7FH
ADD A,A
JP PE,Z80
LD DE,WRNGUP ; "Program requires Z80 processor"
JP MESS80 ; Non-Z80s: print up and go home
Z80: LD (OLDSTK),SP ; Save OS's stack
LD SP,START ; Set local stack
LD A,(BDOS+2) ; Size up the TPA
SUB EOBFHI+10 ; (includes 2k for the ccp)
JR NC,ENOUGH
LD DE,LAKMEM ; "not enough memory..."
JP FATAL ; (fatal error)
ENOUGH: LD DE,LOGO ; Version#, etc
CALL MESAGE
LD A,(DFCB+1)
CP '/'
JR NZ,NOTHLP
LD DE,HLPMSG
JP FATAL
NOTHLP: LD A,(DFCB2)
LD (OFCB),A
LD A,(DFCB2+13)
LD (OUTUSR),A
LD A,(DFCB+13)
LD (INUSR),A
LD E,A
LD C,GSUSER
CALL BDOS
LD A,'Q' ; Force .?Q?
LD (DFCB+10),A
LD DE,DFCB ; Point to specified file
LD HL,FNBUFF ; And to filename buffer
CALL WILDEX ; Do wildcard expansion
LD (NMBFLS),HL ; Save number of matching files
JR Z,WERR ; Get out if error
LD DE,MAXFLS ; Check if too many matching files
AND A ; Clear carry
SBC HL,DE
JR NC,TOOMNY
LD HL,FNBUFF ; Get name buffer
LD (BUFPTR),HL ; Set up buffer pointer
;-----------------------------------------------------------------------
; Come here for each new file
NXTFIL: XOR A
LD (EOFLAG),A
LD A,(INUSR)
LD E,A
LD C,GSUSER
CALL BDOSAV
LD DE,DFCB+1 ; Clean input FCB
PUSH DE
CALL ZERFCB
LD HL,(BUFPTR)
POP DE
PUSH HL ; Save filepointer
LD BC,11 ; 11 characters
INC HL
LDIR ; Move next filename in place
LD DE,OFCB+1
CALL ZERFCB ; Clean output FCB
POP HL
LD DE,16 ; Offset to next filename
ADD HL,DE
LD (BUFPTR),HL
LD DE,DFCB
LD C,OPEN
CALL BDOSAV
INC A
JR NZ,PRIN ; Branch if successful
WERR: LD DE,ERR1 ; Else, "Input file not found"
JP FATAL
TOOMNY: LD DE,ERR3 ; "Too many matching files"
JP FATAL
PRIN: LD DE,CRLF
CALL PRINT
LD HL,DFCB
LD A,(HL)
DEC A
CP 0FFH
JR NZ,GOTDSK
LD C,GCURDK
CALL BDOSAV
GOTDSK: LD B,A
LD A,(INUSR)
LD C,A
CALL PRNDU
INC HL
CALL PRNFIL
; Before going too much further, take this opportunity to "clone" a
; 16 byte template of code into memory 256 times. This forms the
; skeleton for the compiled block of code "CODTBL". Various specific
; instructions and data will overwrite sections of this template after
; the dictionary info is read.
CLONE: LD HL,TMPLAT ; Xfer one copy to the beg of "CODTBL"
LD DE,CODTBL
LD BC,16
LDIR
LD HL,CODTBL ; Now copy it 255 more times.
LD BC,255*16 ; De already points to "CODTBL+16"
LDIR ; That does it
; Now load up the input buffer. The input buffer, the output buffer,
; and "CODTBL" are all page aligned and of page multiple lengths. There
; are no other criteria for the lengths of the 2 buffers, except that the
; input buffer should have a minimum length of 2K plus 1 more page. This
; guarantees that the entire dictionary (plus miscellaneous header info)
; will be read in on the 1st pass, simplifying the program.
CALL RELOAD ; "reload" leaves HL pointing to
XOR A
LD (EOFLAG),A
LD A,(HL) ; The beginning of "IBUF"
CP 76H ; Check for "Squeezed File Header" 76h,ffh
JR NZ,NTSQZD ; Br if not a squeezed file
INC L ; Note buffer starts on a page boundary
INC (HL) ; Chk for FF [clobber it along the way]
NTSQZD: LD DE,NSQMSG ; Meanwhile , prep for poss err msg
JP NZ,FATAL ; Fatal "not squeezed" condition
LD DE,ARROW ; " --->"
CALL PRINT ; Ok, print an arrow
LD A,(OUTUSR)
LD E,A
PUSH DE
LD C,GSUSER
CALL BDOSAV
LD A,(OFCB)
DEC A
CP 0FFH
JR NZ,GOTDRV
LD C,GCURDK
CALL BDOSAV
GOTDRV: POP BC
LD B,A
CALL PRNDU
LD HL,(IBUF+2) ; Get the 16 bit checksum and save
LD (CHKSUM),HL ; Goes there
LD HL,IBUF+3 ; Init pointer past 76FF and 2 byte
; checksum (-1)
LD DE,OFCB+1 ; Init pointer to filename of output fcb
LD B,11
EATLP: INC L ; Filename << 256 chars
LD A,(HL) ; Eat up the file name
OR A ; A zero byte indicates end of filename
JR Z,ATEIT ; Branch when that is encountered
AND 7FH ; Strip off any "attribits"
CALL UCASE
CP '.' ; Check for name / ext division character
JR Z,ISDOT ; Branch when encountered
LD (DE),A ; Else copy filename char to output FCB
INC DE ; And increment that pointer
DJNZ EATLP ; Continue, but not past filename area of FCB
INC HL ; Once more (position should have a null)
JR ATEIT ; We're really done now
; When "." is encountered, skip to the file extension bytes of the output
; FCB. (Any remaining non-extension bytes were init'd to blank). Do not
; copy the "." to the output FCB.
ISDOT: LD DE,OFCB+9 ; Skip...
LD B,3
JR EATLP ; And continue
ATEIT: PUSH HL
LD HL,OFCB+1
CALL PRNFIL
POP HL
LD DE,OFCB ; Output fcb
LD C,ERASE ; "blind erase" the dest file if it exists
CALL BDOSAV ; (*** implement a prompt here? ***)
LD C,MAKE ; In any case, make the new file
CALL BDOSAV
INC A
JR NZ,MAKTBL ; Err cond check
LD DE,ERR2 ; "file open error"
JP FATAL ; Exit
; Now create "CODTBL" by overwriting certain sections of the
; template created above. The dictionary contains 4 byte nodes-
; these are converted into 16 byte code segments. The maximum
; length of the original dictionary is (257*4) bytes or about 2K
; corresponding to a maximum "CODTBL" length of 8K.
;
; NODE DEFINITION: As mentioned above, a "node" consists of two
; pairs of bytes. The first pair corresponds to a zero bit, the
; latter to a "1". To decode a character, we start at node #0. A
; bit is pulled off the bit stream. We then use the 1st or 2nd byte
; pair depending on the bit value. The byte pair takes on 1 of 2
; forms "nn FF" or "xx 0x". The "nn FF" type is a terminal node,
; it means we have our next output value - that value specifically
; being the 1's complement (makes it more mysterious) of "nn". If
; the node is of the second type, it is a pointer to another node
; (an absolute offset from the beg of the dictionary in terms of
; node#, must be multiplied by 4 for a byte offset. It has a max-
; imum value of 513, and is expressed as a 16-bit #, lo-byte
; first). In this case we go to that node, pull another bit off
; the input stream, and continue the process.
;
; There is actually a 3rd node type, which just comes up once.
; Its form is "FF FE". It's a special end-of-file marker called
; "SPEOF".
;
; HOW THE PROGRAM WORKS: Each node is converted into a 16-byte
; (actually 13 plus 3 nop's) series of instructions. These in-
; structions later perform the unsqueezing operation. The whole
; block of code starts at "CODTBL" (which is also the entrypoint).
; Each 13 byte "node code" consists of a 7 byte header. The header
; shifts out the next bit from reg "b", then conditionally branches
; to the first or second half of the remaining code (3 bytes per
; half; 7+3+3 = 13). The 3 bytes in each half are either the 2
; instructions "LD A,<byte>" followed by "RET" (terminal node) or
; the single instruction "JP <nxtnode>". All calls to "CODTBL"
; eventually hit a terminal node and perform a normal return. The
; only exception is the special end-of-file node which compiles to
; "JP SPEOF"; on this particular return the stack is manually ad-
; justed to compensate for the lack of a "RET" instruction.
;
; THE TEMPLATE: This is the "template" which was "cloned" earlier
;
; The following 3 instructions form the header code for every
; node. They are identical for every node (since the jump is rel-
; ative).
TMPLAT: SRL B ; Shift out next bit
CALL Z,REFILL ; Refill reg when empty
JR C,BITIS1 ; If bit is "1"
; After the header code gets executed, one of 2 halves of the
; remainder of the node gets executed. Which half depends on the
; bit shifted out above ("0" for the first half, "1" for the 2nd).
; Each half-node has two possible forms. The terminal form loads
; an appropriate value and returns. The non-terminal form jumps to
; the header of another node. This 16-byte "node-code template"
; assumes the former case by default, since 2 of 3 bytes in that
; case are fixed (only the value need be in-serted). If it turns
; out to be the latter case, all 3 bytes will be overwritten with a
; "jmp" opcode plus an appropriate address.
BITIS0: LD A,00H ; (00h gets replaced with actual value
RET ; To be returned.)
BITIS1: LD A,00H ; 2nd half of the node, likewise
RET
NOP
NOP ; So the template is exactly 16 bytes
NOP
; Create the "node code" table
MAKTBL: INC L ; Now points one past the filename eof
LD E,(HL) ; Get #of nodes (lo byte)
INC L
LD D,(HL) ; Hi byte of same
INC L
LD A,D
; An additional file validity check: though the #of nodes could in theory
; theory as high as 0201H or so, it should never approach 0300H or higher.
SUB 2;3 ; If this happens, assume it is not a
JP NC,NTSQZD ; Squeezed file.
; HL indexes through source dictionary (already initialized), & HL' is
; current dest pointer (indexes thru "codtbl"). DE is initialized to the
; # of nodes and is decreased to 0.
EXX ; Init some constants
LD DE,10 ; Used for incrementing hl'
LD HL,CODTBL+7 ; Init hl' itself
EXX
; Remember, the whole "header" code and some other instructions are already
; there (from when "template" was duplicated). Only specific details need
; now be filled in.
NODELP: CALL MAKHAF ; Make the first ("0") half-node
CALL MAKHAF ; 2nd ("1") half-node
; Source pointer has already been incremented 4 times, as desired. Dest
; pointer has only been incremented 6 times, however.
EXX
ADD HL,DE ; So take care of that
EXX
DEC DE ; Loop counter
LD A,D
OR E
JR NZ,NODELP ; Continue till done
JR RUN ; Go run, hl is is ready, pointing to
; the first byte of squeezed code
; Create a "half-node"
MAKHAF: LD C,(HL)
INC HL
LD A,(HL) ; Get a byte pair from the dictionary
INC HL
OR A ; If it is negative, it is "terminal"
JP M,TERMOD ; Branch if that is the case.
; Else create code for one half-node of the non-terminal variety.
; Byte pair is in A,C. Multiply it by 16 (bytes/node in "codtbl")
SLA C
RLA
SLA C
RLA
SLA C
RLA
SLA C
RLA
ADD A,CDTBLH ; Add offset to beginning of "CODTBL",
; (page aligned)
LD B,A ; Now bc has the jump address
ALTENT: PUSH BC ; Save it
EXX ; Switch to dest pointers
LD (HL),JPOP ; Insert the "jp" opcode
INC L ; Remember "codtbl" is page aligned
POP BC ; Get addr back
LD (HL),C ; Jump addr, lo
INC L
LD (HL),B ; Jump addr, hi
INC L
EXX ; Back to source pointers
RET ; Thats all
; Create a half-node of the terminal variety
TERMOD: CP 0FEH ; Check for special eof terminal node
JR Z,SPEOF ; Br for that unique case
LD A,C ; Else this byte is the complement of
; The returned value
CPL
EXX ; Switch to dest pointers
INC L ; Just 2nd of 3 bytes need be inserted
LD (HL),A ; Put it in
INC L
INC L ; But make sure hl gets incr'd 3 times
EXX
RET ; That's all
; Special EOF returns to a special address in mainline code, rather
; than using "RET". Stack is adjusted accordingly there.
SPEOF: LD BC,DONE ; The special address
JR ALTENT ; Use convenient code subsection above
; Code to refill register 'B' with the next byte
REFILL: INC L
JR Z,POSRLD ; If l is zero, may be at end of buffer
CONT: LD B,(HL) ; Else get next byte
; Now we pre-shift out the next bit, shifting in a "1" from the left.
; Since the leftmost bit in the reg is a guaranteed "1", testing the
; zero stat of the reg is a necesssary and sufficient condition for
; determining that all the bits in the reg have been used up (see
; header code for "TMPLATE"). The only things to be careful of is that
; the the last bit is NOT used, and that the bit now in the carry flag
; IS used upon return from this subroutine.
SCF ; To shift in the flag bit
RR B ; Shift out real bit as described
RET ; That's it
POSRLD: INC H ; Check if time to reload the input
LD A,EIBFHI ; Buffer with additional data.
CP H
CALL Z,RELOAD ; Reload if necessary (resets hl)
JR CONT
; Main code to perform the unsqueeze. In general, the alternate regs
; are used as output pointers, flags, etc. while the primary registers
; are used for input pointing and general purpose use.
RUN: EXX ; First initialize the alternate regs
LD HL,OBUF ; HL', output pntr, to beg of output bfr
LD BC,0 ; C always has a copy of the previous
EXX ; Char output; b is a "repeat flag".
; Primary register initialization:
DEC HL ; Init hl, the input pntr, to point to
; the first byte of squeezed code -1.
LD DE,0 ; Initialize checksum accumulator to zero
LD B,D ; And initialize 'b' to zero so first
; call will immediately call in the
; actual first byte.
MAINLP: CALL CODTBL ; Unsqueeze a character
CALL SEND ; Output it to the output buffer
JR MAINLP ; And repeat "forever" (see "SPEOF"
; 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.
RELOAD: PUSH AF
PUSH BC
PUSH DE
LD B,IBUFSZ ; Loop counter, buffer length in pages
LD D,IBUFHI ; Beg of buffer (hi)
RLDLP: LD E,0 ; Lo byte of current dma
CALL RDSEC ; Read in 128 bytes (1/2 page)
JR NZ,RLDRTN ; (return if eof enecountered)
LD E,80H ; To read in the next half page
CALL RDSEC ; Do that
JR NZ,RLDRTN ; As above
INC D ; Next page
DJNZ RLDLP ; Loop till done
RLDRTN: POP DE ; Restore regs
POP BC
POP AF
LD HL,IBUF ; Reset input pointer
RET ; And return
; Subr for abover, 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 A,(INUSR)
LD E,A
LD C,GSUSER
CALL BDOSAV
LD DE,DFCB ; Input fcb
LD C,READ
CALL BDOSAV ; Read a record
POP DE ; Restore dma to original dma address
OR A ; Set non-zero status
RET Z
LD A,(EOFLAG)
OR A
JR NZ,HTCHED
CPL
LD (EOFLAG),A
OR A
RET
HTCHED: LD DE,CHOPPD
JP FATAL
;___________________________________________________________________________
;
; When "SPEOF" is encountered, a jump to here is made to exit "CODTBL"
; rather than the normal RET instruction.
DONE: INC SP ; So adjust the stack immediately
INC SP
LD A,(CHKSUM+0) ; Make sure the checksum checks out
CP E ; Lo-byte
JR NZ,NFG ; Br if nfg
LD A,(CHKSUM+1) ; Likewise
CP D
JR Z,CKSMOK ; Ok
; If a checksum error is detected, report the warning. Let the guy
; have his file anyway, for whats its worth.
NFG: LD DE,CHKERR ; "Checksum error detected"
CALL MESAGE
; Switch to alternate regs for output. The total #of bytes generated
; should always be a multiple of 128. This assumption is not made,
; however, as it may not be true if the file was squeezed on non-CP/M
; systems. Compute # of sectors to write- specifically subtract the
; buffer start addr from the current pointer value, add 7FH and divide
; by 128. If the byte count was in fact a multiple of 128, this has
; no effect; otherwise it makes sure the final sector gets written.
CKSMOK: EXX ; Switch to alt regs
AND A ; Clear carry
LD DE,OBUF-7FH ; Take care of adding 7fh in advance
SBC HL,DE ; Subtract
SLA L ; Divide by 128
RL H ; Result now in h
LD B,H ; Use 'b' as the counter
CALL WRTOUT ; Writes 'b' sectors to the output file
EXX ; Back to primary regs
LD DE,OFCB ; Close the output file
LD C,CLOSE
CALL BDOSAV
; Fall through
EXIT: LD HL,(NMBFLS)
DEC HL
LD (NMBFLS),HL
LD A,H
OR L
JP NZ,NXTFIL ; Next file
LD SP,(OLDSTK) ; Restore os stack
RET ; To ccp
; Write 'B' 128 byte sectors to the output file
WRTOUT: LD A,B ; If b=0, don't write any sectors
OR A
RET Z
LD DE,OBUF ; Init dma addr to beg of output bfr
WRTLP: LD C,SETDMA ; Set dma to there
CALL BDOSAV
PUSH DE ; Save that address
LD A,(OUTUSR)
LD E,A
LD C,GSUSER
CALL BDOSAV
LD DE,OFCB ; Specify the output file
LD C,WRITE ; Write a record
CALL BDOSAV
OR A
JR NZ,WRTERR
POP DE ; Address as saved above
DJNZ NEXSEC ; Decrement counter, continue if not done
RET
NEXSEC: LD E,80H ; Else increment by 1/2 page
LD C,SETDMA
CALL BDOSAV
PUSH DE ; Save DMA pointer
LD DE,OFCB ; Output FCB
LD C,WRITE ; Write another record
CALL BDOSAV
OR A ; Need the test here also
JR NZ,WRTERR
POP DE ; Get back orig pointer
INC D ; Inc hi-byte, 0 the lo to effect
LD E,0 ; Another 80h incr
DJNZ WRTLP ; Loop till done
RET
BDOSAV: EXX ; BDOS call with all registers and alts
PUSH BC ; saved except for AF, AF', IX and IY
PUSH DE
PUSH HL
EXX
PUSH BC
PUSH DE
PUSH HL
CALL BDOS
POP HL
POP DE
POP BC
EXX
POP HL
POP DE
POP BC
EXX
RET
WRTERR: LD DE,WRTMSG ; Write error, falls through to "fatal"
; For fatal errors- print the message, restore the OS stack & return.
; This rountine is "jumped to", not called
FATAL: CALL MESAGE
LD SP,(OLDSTK) ; Restore stack pointer Z80-style
RET
MESAGE: EX DE,HL ; Save pntr to message (supplied in DE)
LD DE,CRLF ; First print a CR/LF sequence
LD C,PRTSTR
CALL BDOSAV
EX DE,HL ; Then the message in question
PRINT: LD C,PRTSTR ; Entry here if no CR/LF desired
JP BDOSAV
MESS80: LD C,PRTSTR ; For non-Z80 mesage, don't use "BDOSAV"
JP BDOS
; Send character to the output buffer, plus related processing
SEND: EXX ; Alt regs used for output processing
SRL B ; If reg is "1", repeat flag is set
; (note, clears itself automatically)
JR C,REPEAT ; Go perf the repeat
CP 90H ; Else see if char is the repeat spec
JR Z,SETRPT ; Br if so
LD C,A ; Else nothing special- but always keep
CALL OUT ; Else just output the char;
EXX ; Back to normal regs
RET
; Set repeat flag; count value will come as the next byte. (Note: don't
; clobber C with the "90H"- it still has the prev character, the one to
; be repeated)
SETRPT: INC B ; Set flag
EXX ; Switch to primary regs & return.
RET
; Repeat flag was previously set; current byte in a is a count value.
; A zero count is a special case which means send 90H itself. Otherwise
; use B (was the flag) as a counter. The byte itself goes in A.
REPEAT: OR A ; Check for special case
JR Z,SND90H ; Jump if so
DEC A ; Compute "count-1"
LD B,A ; Juggle registers
LD A,C
AGAIN: CALL OUT ; Repeat b occurrences of byte in 'a'
DJNZ AGAIN ; Leaves b, the rpt flag, 0 as desired
EXX ; Restore regs & rtn
RET
SND90H: LD A,90H ; Special case code to send the byte 90h
CALL OUT ; Itself
EXX ;
RET ; (90H "squeezes" into 2 bytes)
; Output character in 'A' directly to the output buffer
OUT: EXX ; Back to primary regs briefly
LD C,A ; Save a in c
ADD A,E ; De is the running checksum
LD E,A
JR NC,NOCARY
INC D
NOCARY: LD A,C ; Put the char back into a
EXX ; Back to output (alternate) regs
LD (HL),A ; Put byte into the next avail position
INC L ; Increment pointer
RET NZ ; Return if not passing a page boundry
INC H ; Incr pointer high byte, check limit
LD L,A ; Use l, which is 0, for temp storage
LD A,EOBFHI ; Limit
CP H ; Check
LD A,L ; But first restore regs
LD L,0 ;
RET NZ ; Ret if limit not reached
PUSH AF
PUSH BC
LD B,OBUFSZ*2 ; Number of 128 byte records to write
CALL WRTOUT
POP BC
POP AF
LD HL,OBUF
RET
;-----------------------------------------------------------------------
;
; Clean up FCB (DE=FCB_address+1)
ZERFCB: LD B,11 ; Fill filename with blanks
LD A,' '
CALL ZL
LD B,24 ; Then zero remainder
XOR A
ZL: LD (DE),A
INC DE
DJNZ ZL
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 TYPE ; Type the char
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
;-----------------------------------------------------------------------
;
TYPE: ; Type the char in "a" to the console
PUSH AF ;
PUSH BC ;
PUSH DE ;
LD E,A ; Where bdos wants it
LD C,CONOUT ; Bdos "console output" function
CALL BDOSAV ; Do it
POP DE ;
POP BC ;
POP AF ;
RET ;
;______________________________________________________________________________
;
; Print drive/user.
;
; Entry: B = drive number (0 .. 15)
; C = user number (0 .. 31, 32-user environments supported)
;
; Result: all registers except PSW are preserved.
;
PRNDU:
PUSH BC ; save our DU just in case
;
LD A,B ; Get drive in Acc.
ADD A,'A' ; Add character offset so 0 = 'A'
CALL TYPE ; Type it
LD A,C ; Get user in Acc.
;
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
CALL TYPE ; Print to CON:
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
CALL TYPE
LD A,C
ADD A,'0'
CALL TYPE
;
PUTCLN:
;
LD A,':' ; Get a colon
CALL TYPE ; Type that
;
POP BC ; Get back our DU
;
RET ; All done
;______________________________________________________________________________
;
UCASE: ; "Upcase" the letter in "A", if necessary
CP 'a' ;
RET C ; If < "a", forget it
CP 'z'+1 ;
RET NC ; Likewise if > "z"
SUB 20H ; Else convert
RET ;
;-----------------------------------------------------------------------
LOGO: DB 'Fast Unsqueezer, ZCPR3 Version 1.0$'
ERR1: DB 'Input file not found.$'
ERR2: DB 'File open error.$'
ERR3: DB 'Too many matching files.$'
ARROW: DB ' ---> $'
LAKMEM: DB 'Out of memory.$'
NSQMSG: DB 'Not a squeezed file.$'
CHKERR: DB 'Checksum error detected.$'
WRNGUP: DB 'Program requires Z80 uP.$'
WRTMSG: DB 'Output error, program aborted.$'
CHOPPD: DB 'Unexpected EOF encountered.$'
HLPMSG: DB CR,LF
DB 'Syntax:',LF,'UF [du: or dir:]afn [output du: or dir:]'
CRLF: DB CR,LF,'$'
;-----------------------------------------------------------------------
; Wildcard expansion module - This module, for use with SYSLIB, can be
; used to expand a wildcard filename into a table of file names as found
; in current DU:
; ENTRY:
; HL = .buffer
; DE = .afn fcb
; EXIT:
; HL = number of files
; ACC= zero flag set if error
; the buffer contains HL file names of 16 characters each
; Char 0 contains the user number
SFIRST EQU 17
SNEXT EQU 18
WILDEX: LD (BUFPTR),HL
LD HL,0
LD (COUNT),HL
LD C,SFIRST
CALL BDOSAV
CP 0FFH
RET Z ; Nothing found -- error
CALL MOVEN ; Move name
WLOOP: LD C,SNEXT ; Search for next
CALL BDOSAV
CP 0FFH
JR Z,DONEW ; Finished
CALL MOVEN
JR WLOOP
DONEW: OR A
LD HL,(COUNT)
RET
MOVEN: PUSH DE
LD HL,(BUFPTR)
ADD A,A
ADD A,A
ADD A,A
ADD A,A
ADD A,A
ADD A,80H
LD C,A
LD B,0
LD D,16 ; Move 16 characters
MOVLP: LD A,(BC)
LD (HL),A
INC HL
INC BC
DEC D
JR NZ,MOVLP
LD (BUFPTR),HL
POP DE
LD HL,(COUNT)
INC HL
LD (COUNT),HL
RET
BUFPTR: DW 0
COUNT: DW 0
NMBFLS: DW 0
CHKSUM: DS 2 ; Checksum kept here
EOFLAG: DS 1 ; "EOF Flag", set from 0 to FF when EOF is hit
OFCB: DS 36 ; Output fcb
MAXFLS EQU 400 ; Buffer size (in files) for wildcard ex-
; Pansions. room for this many files will
; Will be allocated. (400 should do it.)
FNBUFF: DS [16*MAXFLS] ; Beg off wildcard expansion buffer
ENDFNB EQU $ ; End of buffer
; Compute next page boundary following the end of the above buffer. Do
; this by adding 0FFH and "anding" with 0FF00H. This will become the
; beginning of "CODTBL".
PGBND EQU [ENDFNB+0FFH] AND 0FF00H ; (works with aseg only)
ORG PGBND
; Minimum input buffer size is 9 pages to guarantee that the max possible
; dictionary size (512 bytes plus overhead) will be read in the first pass.
IBUFSZ EQU 16 ; Input buffer size (pages)
; Output buffer can be any page multiple length (note it too is also page
; aligned). Increases beyond 64 pages (16k) may do little to improve perf.
OBUFSZ EQU 64 ; Output buffer size (pages)
PAGE EQU 256 ; Clarity is king....
CODTBL: DS 256*16
IBUF: DS IBUFSZ*PAGE ; Beginning of input buffer
OBUF: DS OBUFSZ*PAGE ; Likewise output buffer
EOBUF EQU $ ; End of output buffer
CDTBLH EQU HIGH CODTBL
IBUFHI EQU HIGH IBUF ; High bytes of the beginning addresses
EIBFHI EQU HIGH OBUF ; of the buffers just defined
EOBFHI EQU HIGH EOBUF
END