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
/
ENTERPRS
/
CPM
/
UTILS
/
F
/
QL41.ARK
/
QL.001
< prev
next >
Wrap
Text File
|
1990-04-13
|
43KB
|
1,852 lines
;.......................
;
; QL v4.1 26 January 1989
;
QLVERS EQU 41 ; <=== version #, keep up to date!
QLDATE MACRO
DB ' 26 January 1989'
ENDM
;==============================================================================
;
; Ascii equates
;
NULL EQU 0
CTRLC EQU 'C'-40H
CTRLK EQU 'K'-40H
CTRLX EQU 'X'-40H
BEL EQU 7
BS EQU 8
TAB EQU 9
LF EQU 10
FF EQU 12
CR EQU 13
EOF EQU 1AH
ESC EQU 1BH
;==============================================================================
;
; BDOS function equates
;
CONOUT EQU 2 ; Console Output
DIRIO EQU 6 ; Direct Console I/O
RDBUFF EQU 10 ; Console Read String
OPEN EQU 15 ; File Open
CLOSE EQU 16 ; File Close
SRCH1ST EQU 17 ; Search 1st
SRCHNXT EQU 18 ; Search Next
ERASE EQU 19 ; File Erase
READSEQ EQU 20 ; File Read [Sequential]
WRITSEQ EQU 21 ; File Write [Sequential]
CREAT EQU 22 ; File Create
GETDSK EQU 25 ; Get Current Disk
SETDMA EQU 26 ; Set Direct Memory Address
SGUSER EQU 32 ; Set/Get User
RANDOM EQU 33 ; File Read [Random]
SETRND EQU 36 ; Set random record
;==============================================================================
;
; Page zero equates
;
BDOSEV EQU 0005 ; BDOS Entry Vector
FCB1 EQU 005CH ; File Control Block 1
FCB1FN EQU FCB1+01 ; FCB1 Filename
FCB1TYP EQU FCB1+09 ; FCB1 Type
FCB1EXT EQU FCB1+12 ; FCB1 Extent
FCB1CR EQU FCB1+20H ; Current rec in extent
FCB1R0 EQU FCB1+21H ; Rec number for sizing & lbr random access
FCB1R2 EQU FCB1+23H ; 0'd before random read
;==============================================================================
;
; Derived Equates
;
IF M80 ; Non-syntax specific implementation of
Z1 EQU FALSE ; - mutual exclusion
ELSE
Z1 EQU TRUE
ENDIF
IF Z1
NLIST S ; No source listing
LIST C ; Gen com file directly
ENDIF
IF Z1
CTRLDUMMY EQU .NOT.(CTRLWORDSTAR.OR.CTRLDIMVID)
ELSE
CTRLDUMMY EQU NOT (CTRLWORDSTAR OR CTRLDIMVID)
ENDIF
;==============================================================================
;
; "assumed equates"
;
; Adjustable screen height and width is only partially implemented in the
; current version, so for now these should remain at 24 and 80 respectively.
;
LINES EQU 24 ; Terminal console lines.
COLUMNS EQU 80 ; Terminal console columns.
;==============================================================================
;
IF ZCPR3
CSEG
ELSE
ASEG
ORG 100H
ENDIF
;.....
;
IF ZCPR3
PUBLIC $MEMRY
EXTRN Z3VINIT,TINIT,DINIT
EXTRN CLS,STNDOUT,STNDEND
EXTRN Z3LOG,GETWHL,GETSPEED,GETCRT,GETVID
EXTRN COUT,GETUD,PUTUD
EXTRN RETUD,LOGUD
ENDIF
; set the number of lines we can display (don't change)
DISPLY EQU LINES-LINEOVERLAP-1 ; Display page size = 23
NL EQU LINES-6
;=====================================================================
; Entry Point
;=====================================================================
QL: JP MAIN ; <=== entry
IF ZCPR3
DB 'Z3ENV',1
Z3EADR: DW 0
ENDIF
;..............................................................................
;
; embedded copyright message simplified & moved near beginning (for dump)
; since it is no longer displayed at runtime
DB 'by Nick Dobrinich and Ross Presser '
DB 'Sections Copyright (c) 1986 '
DB 'Steven Greenberg and C.B. Falconer '
DB 'May be reproduced for non-profit use only.'
SIGNON: CALL MSG
DB 'QL v',QLVERS/10+'0','.'
DB (QLVERS-((QLVERS/10)*10))+'0'
IF ZCPR3 ;
DB ' /Z3' ;
ENDIF ;
QLDATE
DB CR,LF,LF
DB ' --- While viewing --- --- Toggle Commands ---',CR,LF
DB CR,LF
DB '<cr> Forward one page A Display ASCII / HEX: '
ASTATE: DB 'ASCII',CR,LF
DB '<sp> Forward one line T Truncate long lines: '
TSTATE: DB 'YES',CR,LF
DB '<##> Go to any page ## C Case sensitive find: '
CSTATE: DB ' NO',CR,LF
DB ' B Backward one page',CR,LF
DB ' H Home (Top of file)',CR,LF
DB ' E End (Bot of file)',CR,LF,LF
DB ' F Find text or hex byte',CR,LF
DB ' R Repeat find',CR,LF
DB ' X Exit viewing',CR,LF,LF,0
RET
REQCMD: CALL MSG
DB CR,LF,LF,'Command, or <ret> to resume Viewing: ',0
RET
;=====================================================================
; Main Program
;=====================================================================
MAIN:
LD (OLDSP),SP ; Save old sp if no warm boot needed
LD SP,STACK ; Set up local stack
;................................
;
IF ZCPR3 ; ZCPR3 initialization stuff
LD HL,(Z3EADR) ;
CALL Z3VINIT ;
CALL TINIT ;
CALL GETCRT ;
INC HL ;
INC HL ;
LD A,(HL) ; Get #of lines on CRT
LD (NLINES),A ; Keep that there
SUB LINEOVERLAP+1 ;
LD (DISPLAY),A ; # of lines per screen
CALL PUTUD ; Save orig DU for exit
CALL RETUD ; Get orig logged DU
LD (DEFDU),BC ; Save that here
LD DE,FCB1 ; Log to the file spec'd on the cmnd line
CALL Z3LOG ;
CALL RETUD ; Get the filenames DU
LD (LBRDU),BC ; And save that here..
LD HL,($MEMRY) ; Get addr of free memory
;...............................;
;................................
; French vanilla CP/M
ELSE ;
ld A,LINES ;
ld (NLINES),a ; Init screen size
LD A,DISPLY ;
LD (DISPLAY),A ; Init lines/pg-1
LD C,GETDSK ;
CALL BDOSC1 ;
LD (DEFDU+1),A ; Keep default drive here ( 0 = "A")
LD (LBRDU+1),A ; Assume that the spec'd filename is same
LD A,(FCB1+0) ; Get the filename's drive spec
OR A ;
JR Z,ISSAME ; If zero, it is indeed the same
DEC A ; Else reduce the fcb+0 value so "A = 0"
LD (LBRDU+1),A ; And use that
;
ISSAME: LD C,SGUSER ; Now for user area stuff. For the regular
LD E,0FFH ; - CP / M version there is only one user#
CALL BDOSC1 ;
LD (DEFDU+0),A ; So keep default user here (for display)
LD (LBRDU+0),A ; And a copy here as well
LD HL,ENDPROG ; Get addr of free memory
ENDIF ;
;...............................;
;................................
; New dynamic memory allocation.
LD (@PTRTBL),HL ; Assign beg of free memory to 1k "PTRTBL"
LD DE,1024 ;
ADD HL,DE ;
LD (@BUFFER),HL ; And everything above that to "BUFFER"
;...............................;
CALL INI1MEM ; Init all memory from "init1" - "end1init"
CALL INI2MEM ; Init all memory from "init2" - "end2init"
; (also initializes "ptrtbl")
LD A,40 ; Init Console String Buffer
LD (STRMAX),A ;
IF USEBIOSCONOUT ; Using faster BIOS rtn
LD HL,(1) ; BIOS + 3 warm start ep
LD DE,9 ; Bias to BIOS conout jp
ADD HL,DE
LD (BIOSCONOUT),HL ; Save adr for fast putc
ENDIF
LD HL,(@BUFFER) ; **
LD (BUFPTR),HL ; Set buffer ptr
;..............................................................................
;
; Check for existence of BYE5.
; Note that "remote operation" is assumed if BYE is detected.
;
LD C,SGUSER ; BDOS set/get user call
LD E,0FFH ; First get current value
CALL BDOSC1 ;
PUSH AF ; Save current value
;
LD C,SGUSER ; BDOS set/get user call
LD E,241 ; Magic number to see if bye is resident
CALL BDOSC1 ; Look for special result from "set/get" user
CP 77 ; Magic return # if BYE is there
JR NZ,NOBYE ; Nope..
LD HL,-0800H ; Flag "BYE5" as resident by puttin -800h here
LD (BYE5FLAG),HL ; (otherwise is zero from init above)
;
NOBYE: POP AF ; Get orig user # back
LD C,SGUSER ; BDOS set/get user call
LD E,A ; Put user# in E
CALL BDOSC1 ;
;..............................................................................
;
CALL CHKSUMCCP ; Do simple chksum of CCP for quit
LD (CCPCHKSUM),A
; Do all calculations relating to available Memory right here...
LD HL,(BDOSEV+1) ; Get BDOS base
LD DE,(BYE5FLAG) ; (-2k) if CCP to be saved, else zero
ADD HL,DE ; Add, ie subtract, that
LD (BDOSBASE),HL ; Take future requests for (BDOS+1) from here
; open the file if one given
; try open 1st with given name, then as .lbr
;................................
;
LD HL,FCB1FN ; See if command tail is blank
LD A,'/' ; Chk for help invocation
CP (HL) ;
JP Z,USAGE ;
LD A,' ' ;
CP (HL) ;
JR NZ,SOMETH ; Br if something was specified
LD B,11 ; Else convert to *.*
;
QUESLP: LD (HL),'?' ;
INC HL ;
DJNZ QUESLP ;
JR SWPAMBIG ; Go "sweep" all matching filenames
;...............................;
; check if ambig file specified
SOMETH: LD BC,11 ; Length (HL already set)
LD A,'?' ; Find a ?
CPIR ; Search
JR Z,SWPAMBIG ; If ambiguous, sweep 'em
;..............................................................................
;
OPENSOMEFILE: ;
LD HL,FCB1EXT
LD D,H ; DE=HL
LD E,L
INC DE ; +1
LD (HL),B
LD BC,23 ; Zero rest of FCB1
LDIR
LD C,OPEN
CALL BDOSCALL ; Open file
JP P,OPENOK ; Open ok >= 0
; Version 4.1 rewritten
; If file does not open "as-is", AND filetype is not blank,
; we don't fool with it at all. If it IS blank, we try
; .LBR, .ARK, and .ARC in succession.
LD HL,FCB1TYP ; point to typ
CALL ILCMP ; Is it all blank?
DB ' ',0
JR NZ,NONE ; If not, give up
CALL OPENIT ; Try LBR
DB 'LBR',1
CALL OPENIT ; Try ARK
DB 'ARK',2
CALL OPENIT ; Try ARC
DB 'ARC',2
JR NONE ; Give up if all failed
OPENIT: POP HL ; Src
LD DE,FCB1TYP ; Dst
LD BC,3 ; Len
LDIR ; Set filetype to try
LD A,(HL) ; Get 'library type' flag
LD (LIBRARY),A ; Store it
INC HL
LD C,OPEN
CALL BDOSCALL ; Try to open it
JP P,OPENOK ; Go if it succeeded
JP (HL) ; Otherwise return
;..............................................................................
;
; The routines to handle ambigous file specifications follow (ie arrive
; here if at least one ? in filename).
;
; Note: In this case an LBR will always be opened as a library.
; In the less than likely event the user wants to examine the guts
; of an LBR file, he may still do so by typing the full command line, eg.
; "QL FILE.LBR" - but "QL FILE" or "QL *.LBR" or almost anything else
; will treat LBR files as libraries).
; We accumulate filenames at the start of the buffer, resetting BUFPTR
; and ask the user to choose one. After selection, we open the file as
; if it had been fully specified.
; After the user is finished with the file (or entire library if an LBR),
; QLEXIT returns to QFCFIL, so he can examine another one. The filenames
; are protected by the resetting of BUFPTR.
; first preserve ambiguous filename
SWPAMBIG:
LD DE,(BUFPTR) ; Dest for fnames
LD (FILPTR),DE ; Save as start of fname table
LD HL,FCB1FN ; Src
LD BC,11 ; Len
LDIR
PUSH DE ; Save ptr
LD DE,80H ; Set default DMA
LD C,SETDMA
CALL BDOSC1
LD C,SRCH1ST ; Search for first
CALL BDOSCALL
INC A
JR NZ,SWP1 ; Go if a match found
;...............................;
; No files found.
; Last ditch effort - check for core dump
NONE: CALL WHLCHK ; Core dump allowed?
JR Z,NOTCORE ; Nope, don't try
LD HL,FCB1FN ; QL CORE will give a core dump
CALL ILCMP ; Note: check only fn, because
DB 'CORE ',0 ; - ext was prob munched
JP Z,COREDM ; Matched -- do a core dump
NOTCORE:
CALL MSG ; Display error msg
DB CR,LF,'++ No matching files found ++',CR,LF,0
JR USAGE
;..............................................................................
;
SWP1: LD IX,0 ; Matches
POP DE ; Dest for fnames
SWPLP: DEC A ; Un-INC
ADD A,A ; A<<5
ADD A,A
ADD A,A
ADD A,A
ADD A,A
ADD A,81H ; +DMA points to fn
LD L,A ; Move to HL
LD H,0
;................................
CALL WHLCHK ; System security stuff
JR NZ,SWPOK ; If wheel is set, it's ok
PUSH HL ; Save ptr to fn start
LD BC,9 ; Check SYS attr
ADD HL,BC ;
POP BC ; Temp save ptr in BC
BIT 7,(HL) ;
JR NZ,SWPNXT ; If set, pretend it wasn't found
DEC HL ; Next check if online COM file
call ilcmp ; Service routine
db 'COM',0 ;
jr Z,swpnxt ; If matched, pretend it wasn't found
;.....
; ; File is good, use it
PUSH BC ; Move ptr from BC to HL
POP HL ;
SWPOK: LD B,11 ; Chars in filename
LDIRLP: LD A,(HL) ; Move it - strip any hi-bits
AND 7FH ; (can't use LDIR, oh well...)
LD (DE),A ;
INC HL ;
INC DE ;
DJNZ LDIRLP ;
INC IX ; Count it
;.....
; ; File is not authorized, go onto next
SWPNXT: LD C,SRCHNXT ; Search for next
CALL BDOSCALL
INC A
JR NZ,SWPLP ; Go get it if it's there
PUSH IX ; Get count in HL
POP HL
LD A,H ; >255 files?
OR A ; Better be zero!
JP Z,SWP2 ;
CALL MSG ; Display error msg
DB CR,LF,'++ Error: Too many matching files ++',0
USAGE: CALL MSG
DB CR,LF,LF,' Usage: QL <afn>'
DB CR,LF
DB ' where <afn> should not match more than 255 files.',0
CALL WHLCHK ; Core dump allowed?
JP Z,QLEXIT ; Nope, don't let him know
CALL MSG
DB CR,LF,' Or: QL CORE',TAB,'for a core dump.'
DB CR,LF,LF,0
JP QLEXIT ; Exit
SWP2:
LD A,L ; Get file cnt
OR A ; Zero files?
JP Z,NONE ; Err msg & exit
; If there was only one file, don't sweep
CP 1 ; Only 1 file?
JR NZ,QFCSET ; Nope, there's more
LD HL,-11 ; Back up to the fn found
ADD HL,DE
JR OKSEL ; And open the file
; Set up parameters for QFC
QFCSET:
LD A,0FFh ; Yes, we are sweeping
LD (SWEEPING),A
LD (BUFPTR),DE ; Protect filenames
LD IX,FILPARM ; Point to QFC parm block
LD (IX+FNCNT),L ; File count
LD HL,(FILPTR) ; Table of filenames
LD DE,11 ; Table entry length
ADD HL,DE ; Point past ambig fname
LD (IX+FNTBL),L ; Table start
LD (IX+FNTBL+1),H ;
LD (IX+ENTLEN),E ; Entry length
LD (IX+FNOFFS),0 ; Offset to filename
LD (IX+FNPARS),0 ; don't request parsing
LD (IX+FNSORT),255 ; do request sorting
LD (IX+HEDRTN),DFNS-256*(DFNS/256) ; Set header routine
LD (IX+HEDRTN+1),DFNS/256 ;
QFCFIL:
CALL INI2MEM ; Init 2nd mem area on every sweep
LD IX,FILPARM ; Point to QFC parm block
CALL QFC ; Let user select a file
; v4.1: Moved a lot to QFC.LIB (Quick File Choose)
JP Z,QLOUT ; Escape char
JR C,QFCFIL ; Unknown chars
OKSEL: LD DE,FCB1FN ; Move selection to FCB1
LD BC,11
LDIR
ld hl,fcb1typ ; point to fcb1typ
call ilcmp ; Service routine
db 'LBR',0 ; Is it an LBR?
jr Z,dolbr ;
;; call ilcmp ;
;; db 'ARK',0 ; Is it an ARK? [ not yet supported ]
;; jr Z,doarc ;
;; call ilcmp ;
;; db 'ARC',0 ; Is it an ARC? [ditto]
;; jr Z,doarc ;
sub a ; Normal file
dofile: ld (library),a ;
JP opensomefile ;
dolbr: ld a,1 ; lbr file
jr dofile ;
doarc: ld a,2 ; arc file
jr dofile ;
;.....................................
;
; Display 'n files matching DU <afn>'
;
DFNS: CALL CLEARSCREEN ;
CALL CRLF ;
CALL ONHALF
LD L,(IX+FNCNT) ; Get # of files
LD H,0 ;
CALL B2DEC ; Display it
CALL MSG ;
DB ' files matching ',0
CALL PRFDU ; Print appropriate DU:
LD HL,(FILPTR) ; Start of table
CALL PRNFN ; Print ambig filespec
CALL OFFHALF ;
CALL CRLF ;
JP CRLF ; &ret
;=============================================================================
;
; Come here if a "core dump" was requested
;
COREDM: LD A,0FFH ; 0ffh
LD (CORE),A ; Set flag
LD (HIPG),A ;
LD HL,0FFFFH ; Of all of memory
LD (EOFADR),HL
LD (FILELEN),HL
XOR A
LD (PAGE),A ; Set init pg 0
LD (AFLAG),A ; Allow hex/ascii disp only
LD (LIBRARY),A ; Not a library
CALL TOGLA ; (flip from 0 [ascii] to ff [hex])
LD HL,(@PTRTBL) ;
INC HL ;
XOR A ;
LD B,A ; 256 pgs
SETMEMPP:
LD (HL),A
INC A
INC HL
INC HL
DJNZ SETMEMPP
JP PRPG ; Display hex/ascii of pg 0
;=============================================================================
;
; compute simple 1 byte chksum of entire CCP
; ret in a
;
CHKSUMCCP:
LD HL,(6)
LD DE,0-800h-6 ; Size of CCP
ADD HL,DE ; *CCP
LD BC,800h ; Chksum entire CCP
CHK1SUM:
ADD A,(HL)
CPI ; HL++,BC--
RET PO ; Chksum in A
JR CHK1SUM
ILLEGAL:
CALL MSG ; Display error and exit
DB CR,LF,'++ Can''t display that ++',CR,LF,0
QLEXIT:
LD SP,STACK ; Stack may be questionable upon arrival here
LD A,(PUTCABRT) ; Did we abort from PUTC?
OR A
JR NZ,QLOUT ; Yep, don't re-sweep
LD A,(SWEEPING) ; If in sweep mode, return to sweeper
OR A ;
JP NZ,QFCFIL
QLOUT: CALL CRLF
IF ZCPR3 ; For Z3:
CALL GETVID ; Restore video
CALL NZ,DINIT ; (if necessary)
CALL GETUD ; and return to starting DU:
ENDIF
IF ALWAYSBOOT ; Don't check CCP
JP 0
ELSE
CALL CHKSUMCCP
LD B,A ; Ccp chksum now
LD A,(CCPCHKSUM) ; Orig CCP chksum
XOR B
JP NZ,0 ; Warm boot if CCP was overlaid
LD SP,(OLDSP) ; Else just ret to CCP
RET
ENDIF
;-----------------------------------------------------------------------------
;
QUIT:
QUITNOSUM:
LD SP,STACK ; Extracting may foul stack
LD A,(LIBRARY)
OR A ; Ordinary file?
JR Z,QLEXIT ; Yes, so exit
DEC A ; Lbr file?
JR Z,QUITSTAY ; Yes, so stay
;; DEC A ; Arc/ark file? [Not supported yet!]
;; JR Z,QUITSTAY ; Yes, so stay
JR QLEXIT ; Otherwise (type error) exit
; working with some collection: list all members and let user choose next
;
QUITSTAY:
LD HL,0
LD (FCB1R0),HL ; Set lbr rec 0
CALL SEEK ; Position to lbr tof and fall thru
; System security related stuff
;
OPENOK: CALL WHLCHK ; If wheel is set, skip all this
JR NZ,LEGAL ;
LD HL,FCB1TYP+1 ; Else check if file has SYS attribute
BIT 7,(HL) ;
JP NZ,NONE ; If it does, pretend file doesn't exist
;
DEC HL ; More system security: no examing online
; COM files. if they're in a lbr, ok, else
; They should be named OBJ or CZM.
call ilcmp ; Service routine
db 'COM',0 ;
JP Z,ILLEGAL ;
LEGAL: LD A,(LIBRARY) ; Access OK, continue
OR A ; flag==0?
JP Z,CHKIFCOMPRESSED ; Ordinary file
DEC A ; flag==1?
JR Z,OPENLBR ; Lbr file
;; DEC A ; flag==2? [Again, not yet supported]
;; JP Z,OPENARC ; Arc file
; When (if!) more 'types' are supported, jumps to
; the appropriate service routines go here.
;------------------------------------------------
; read 1st lbr directory sector to see how big lbr dir is
OPENLBR:
LD DE,(BUFPTR) ; Set dma to buffer
LD HL,1
LD (NSECTS),HL
CALL READFILE
LD A,(MTFLAG) ; Zero if readfile read nothing
OR A ;
JP Z,LBRERROR ; We'll call an empty LBR file a library error
LD IX,(BUFPTR) ; Point to buffer
LD L,(IX+14) ; Dir sects low
LD H,(IX+15) ; Dir sects high
DEC HL ; We already read the 1st
LD A,H
OR L
JR Z,PAKDIR ; Lbr dir is only 1 sect long
LD (NSECTS),HL
CALL READFILE ; Read the rest of the lbr dir
JP Z,LBRERROR
; v4.1: Remove the deleted members from memory
PAKDIR: EX DE,HL
LD (HL),0FFH ; Add lbr dir eof
SUB A ; Count active members
LD HL,(BUFPTR) ; Start of directory
PUSH HL
POP DE ; DE:=HL
LD (HL),0FEh ; Mark first entry as deleted!
LBRPACK:
PUSH AF ; Save
LBRP0: LD BC,32 ; entry length
LD A,(HL) ; Entry type
INC A ; End of directory?
JR Z,LBRP2 ; yes, we're done - all, exit loop
INC A ; Deleted member?
JR Z,LBRP1 ; yes, remove it
LDIR ; Copy into packed directory
POP AF ; Restore count
INC A ; Count it
JR LBRPACK ; Loop
LBRP1: ADD HL,BC ; Point to next
JR LBRP0
LBRP2: POP AF ; Restore counter
LD IX,LIBPARM ; QFC parameter block
LD (IX+FNCNT),A ; Filename cnt
LD (IX+FNOFFS),1 ; Offset to filename
LD (IX+FNPARS),0 ; Don't parse
LD (IX+FNSORT),255 ; Do sort
LD (IX+ENTLEN),C ; Entry length
LD HL,(BUFPTR) ; Start of table
LD (IX+FNTBL),L ;
LD (IX+FNTBL+1),H ;
LD (IX+HEDRTN),PRMBRDIR-256*(PRMBRDIR/256) ; Set header routine
LD (IX+HEDRTN+1),PRMBRDIR/256
QFCLBR:
LD IX,LIBPARM ; QFC parameter block
CALL QFC
JP Z,QLEXIT ; 'exit' type char pressed
JP NC,SELMEMB ; Selection made
CALL UCASE ; Possibly upcase a character in A
LD B,A ;
CALL WHLCHK ; Nothing else legal if wheel isn't set
LD A,B ;
JR Z,QFCLBR ;
CP 'E' ; Set extract mode?
JR Z,EXTRMODE ;
CP 'V' ; Set view mode?
JR NZ,QFCLBR ; Try again
XOR A ; Flag for view mode
JR MODESET
EXTRMODE: ;
LD A,1 ; Flag for extract mode
MODESET: ;
LD (EXTRACTING),A ; Set the mode
; Fall thru, redisplay w/ new prompt
JR QFCLBR ; Quicker
;
;..................................
;
; Display 'n members in DU:lib.ext'
;
PRMBRDIR: ;
CALL CLEARSCREEN ;
CALL ONHALF ; Display header in dim video
CALL CRLF ;
LD L,(IX+FNCNT) ; Get # of entries
LD H,0 ;
CALL B2DEC ; Print it
CALL MSG ;
DB ' members in ',0;
CALL PRNDFN ; Print DU:<filename>
CALL CRLF ;
;
LD A,(EXTRACTING) ; Check flag
OR A ;
JR Z,VIEWMSG ; View mode
;
CALL MSG ; Extract mode
DB '[Extract to ',0
CALL PRDDU ; Print default DU:
CALL MSG ;
DB ' -- Type V for view mode]',0
CALL OFFHALF ; Turn off dim video
JP CRLF ; &ret
;
VIEWMSG: ;
CALL MSG ;
DB '[View',0 ;
CALL WHLCHK ; Instructions to extract
JR Z,VIEW1MSG ; Only if authorized
CALL MSG
DB ' -- Type E for extract mode',0
VIEW1MSG:
LD A,']' ; Finish msg
CALL PUTC
CALL OFFHALF ; Turn off dimvid
JP CRLF ; &ret
;.....................................
;
; Print filename "C", pointed to by HL
;
PRNUMFN: ;
PUSH BC ;
PUSH DE ;
PUSH HL ;
CALL CKABRT ; Chk for abort 1/filename
; - (fixes stack and exits direct if requested)
PUSH BC ; Save everything ("chktyp" destroys)
PUSH DE ;
PUSH HL ;
LD DE,8 ; Set de to point to the filename typ (hl+8)
ADD HL,DE ;
EX DE,HL ;
CALL OFFHALF ; Force full intensity NOW
CALL CHKTYP ; Check if filename typ is COM, REL, etc.
CALL C,ONHALF ; If so, use half-intensity
POP HL ;
POP DE ;
POP BC ;
PUSH BC ;
PUSH DE ; Save everything("B2DEC" destroys)
PUSH HL ;
LD A,C
CP 100 ;
CALL C,SPACE ;
LD A,C ; ("b2dec" left justifies)
CP 10 ;
CALL C,SPACE ;
LD L,C ; Get member's #, still in C
LD H,0 ; Put it in HL
CALL B2DEC ; Display it
CALL MSG ;
DB '. ',0
POP HL ;
POP DE ; Restore registers
POP BC ;
CALL PRNFN ; Type the file name pointed to by HL
CALL OFFHALF
CALL MSG ; Type the fence
DB ' |',0
POP HL ;
POP DE ;
POP BC ;
RET ; End of PRNUMFN: subr
;...............................;
;................................
; Subr to type filename pointed to by HL
;
PRNFN: LD A,(CORE) ; A core dump never has a filename
OR A ;
RET NZ ; So forget about it
;
LD B,8 ; Display first 8 chars in fn
;
PRNXT: LD A,(HL) ; Get char of member name
INC HL ; *char++
AND 7FH ; (make sure 'dcase' works right)
;
IF LOWERCASE ;
CALL DCASE ; "downcase" the character
ENDIF ; Lowercase
;
CALL PUTC ; Print it
DJNZ PRNXT ; Loop 8 times
;
LD A,'.' ; Now display a "."
CALL PUTC ;
;
LD B,3 ; Same as above 3 more times for typ
;
PRNXT2: LD A,(HL) ;
INC HL ;
AND 7FH ;
;
IF LOWERCASE ;
CALL DCASE ; "downcase" the character
ENDIF ; Lowercase
;
CALL PUTC ;
DJNZ PRNXT2 ; Loop 3 times
RET ;
;...............................;
;................................
;
PRFDU: LD HL,(LBRDU) ; Type the filename's (FCB1's) DU:
JR PDU ;
;
PRDDU: LD HL,(DEFDU) ; Type the originally logged (default) DU
;
PDU: LD A,'A' ;
ADD A,H ; Convert that to ascii
CALL PUTC ; And display it
LD H,0 ; User# already in "L", so just zero H
CALL B2DEC ; Print the user#
LD A,':' ;
CALL PUTC ; Print a colon
RET ;
;...............................;
;................................
; Print DU:<filename> for the FCB1 filename
PRNDFN: CALL PRFDU ; Print DU:
LD HL,FCB1+1 ; Point to filename
CALL PRNFN ; Print it and return
RET ;
;...............................;
;................................
;
CHEXIT: CP CTRLC ; ^C or ^K exit right to CP/M
JP Z,SYSTEM ; (stack gets fixed)
CP CTRLK ;
JP Z,SYSTEM ;
;
CP 'X' ; Other exit chars rtn w/ zero stat
RET Z ;
CP 'Q' ;
RET Z ;
CP ESC ;
RET Z ;
CP CTRLX ;
RET Z ;
CP CR ;
RET ;
;...............................;
;=============================================================================
; Here we prepare to extract (and possibly decompress) to disk.
; Most of the work is done by the routines for ordinary reading, with
; the few differences being invoked by the setting of the EXTRACTING flag.
;
EXTCHK: LD A,(EXTRACTING) ; Return Z flag for EXTRACTING
OR A
RET
EXTRDONE:
; When we get here, all except last (partial) buffer has been written
; *(DE-1) is last addr used.
LD A,127 ; Include last sector
ADD A,E
LD E,A
LD A,D
ADC A,0
LD D,A
CALL OUTFLUSH ; Write the last buffer
LD C,CLOSE ; Close the file
LD DE,FCB3
CALL BDOSC1
IF ZCPR3
LD BC,(LBRDU) ;
CALL LOGUD ;
ENDIF ; ZCPR3
LD HL,(FLSECTS) ;
PUSH HL
CALL MSG
DB CR,LF,'Wrote ',0
CALL B2DEC ; Print # of sectors
CALL MSG
DB ' sectors (',0
POP HL ; = # sectors
XOR A ; Clear carry & byte
LD B,3
ROLP: RR H ; Divide by 8 & keep frac
RR L
RR A
DJNZ ROLP
OR A ; Any fraction?
JR Z,NOFRAC
INC HL ; Yep, count as 1K
NOFRAC: CALL B2DEC ; Print # of K
CALL MSG
DB 'K)',CR,LF,0
logbkd:
CALL DELAY8
logbak:
IF ZCPR3
LD BC,(LBRDU) ; Log back to the input DU
CALL LOGUD ;
ENDIF ; ZCPR3
JP QUITNOSUM ; Display lbr dir again
;...............................;
; v4.1: All filename parsing removed to PARSFN in QFC.LIB
EXTCRFILE:
LD HL,FCB3+17 ; UNCR/UNSQ stufgfed FN here
CALL PARSFN ; Parse it into FCB3+1 AND FBC3+17
JR EXTFIL ; Continue
EXTUCFILE: LD HL,MEMBER ; Point to member fn
LD DE,FCB3+1 ; Point to disk fcb
LD BC,11
LDIR
EXTFIL: LD HL,FCB3+12 ; Gotta zero rest of fcb3
LD DE,FCB3+13
LD (HL),0
LD BC,20
LDIR
LD (FLSECTS),BC ; Reset the sectors-written counter
IF ZCPR3
CALL GETUD ;
ENDIF ; ZCPR3
LD C,OPEN ; Attempt to open file
LD DE,FCB3
CALL BDOSC1
INC A ; Success means it already exists
JR Z,LEXT4
CALL MSG
DB CR,LF,LF,' ==> File exists; purge (y/N)? ',0
CALL GETCHR
AND 1FH ; Y, y, or ^Y OK
CP 19H
PUSH AF ; ***
CALL CRLF
POP AF ; ***
;; JP NZ,QUITNOSUM ; Abort if he said no
jp nz,logbak
LD C,ERASE ; Erase if he said yes
LD DE,FCB3
CALL BDOSC1
LEXT4: LD C,CREAT ; Create the file
LD DE,FCB3
CALL BDOSC1
RET P ; If it succeeded go back to reading-in code
CALL MSG
DB ' ++ Directory full ++ ',CR,LF,0
;;LWAIT0: CALL DELAY8
;; JP QUITNOSUM
jp logbkd
; Buffer flush failed; disk is full.
NOSPACE:
CALL MSG
DB ' ++ Disk Full ++',CR,LF,0
LD C,ERASE ; Erase the file
LD DE,FCB3
CALL BDOSC1
;; JR LWAIT0
jp logbkd
;...............................;
; Library member selected.
SELMEMB:
INC HL ; Point to entry fn (QFC set HL=*entry)
LD DE,MEMBER ; Move member filename to member str
LD BC,11 ; (QFC set HL for us)
LDIR
LD E,(HL) ; HL = *member start
INC HL
LD D,(HL) ; DE = starting sect of member
LD (FCB1R0),DE ; Fill in lbr r0,r1 fld for seek to member
INC HL ; HL = *member len
LD E,(HL)
INC HL
LD D,(HL) ; DE = len in sects to read after seek
LD (NSECTS),DE
; chk for zero len, maybe a lbr date file
LD A,D
OR E
JP Z,MT ; If member is empty (zero-length)
; position to member within lbr at fcb1r0
SEEKMEMBER:
CALL SEEK
JP CHKIFCOMPRESSED
; assumes fcb1r0 is set to rec to seek to
; set fcb1 r2 fld to 0
SEEK: XOR A
LD (FCB1R2),A ; 0 lbr r2 fld
LD C,RANDOM
CALL BDOSCALL
RET Z ; Seek ok
POP HL ; Destroy ret adr
LBRERROR:
CALL MSG
DB 'LBR read error',0
CALL DELAY8
JP QLEXIT
;.....
;
SUMMARY:
CALL ONHALF ; Dim video
CALL MSG ;
DB CR,LF,' File: ',0 ;
CALL PRNDFN ; Print DU:<filename>
CALL CRLF
LD A,(LIBRARY) ; Some kind of collection?
OR A ;
JR Z,NLBR2 ;
CALL MSG ;
DB 'Member: ',0 ;
LD HL,MEMBER ;
CALL PRNFN ;
CALL CRLF ;
NLBR2: LD A,(INCOMPLETE) ; Was read complete?
OR A
JR Z,DOSUMMARY ; If so, we know file size
WARNING:
CALL MSG
DB CR,LF,'( ** Entire file does NOT FIT in Memory ** )',0
CALL OFFHALF
RET
; report file size
DOSUMMARY:
CALL MSG ;
DB ' Size: ',0 ;
LD HL,(FILELEN) ; In bytes
PUSH HL
CALL B2DEC
CALL MSG
DB ' bytes (',0
POP HL ; HL = filelen
SRL H
SRL H ; Shift to kilobytes
INC H ; For overflow lsb
LD L,H
LD H,0
CALL B2DEC
CALL MSG
DB 'k)',CR,LF,0
; skip line count for non-text files
LD A,(AFLAG)
OR A
JR NZ,RETSUM ; &ret, no line summary
CALL MSG
DB 'Approx: ',0
LD A,(HIPG)
DEC A ; Don't count last pg lines yet
LD B,A
LD HL,0
JR Z,ONLY1PG ; Only 1 pg, nothing to add
LD A,(DISPLAY) ; Actual lines per pg
LD E,A
LD D,L
CNTLINES:
ADD HL,DE
DJNZ CNTLINES
ONLY1PG:
LD A,(LASTPGLINES)
LD E,A
LD D,0
ADD HL,DE ; Add in last pg lines
CALL B2DEC
CALL MSG
DB ' lines, ',0
; added word counting code
; words are any seq of chars >= '0' (30h) and < 80h
; handle ws doc by ascii mask
; count space between words
LD HL,(BUFPTR)
LD D,FALSE ; Inword = false
; reg E is temp storage for curr ch
LD IX,0 ; Word count
LD BC,(FILELEN) ; Get actual file len
CNT: LD E,(HL) ; Save ch
INC HL
DEC BC
LD A,B
OR C
JR Z,CNTALLDONE
LD A,E ; Get ch
AND 7FH ; Mask to ascii
CP '0' ; Cy if < '0'
JR C,ISWHITESP
; ch is valid in word
XOR A ; False
OR D ; Inword == false?
JR NZ,CNT ; No
LD D,0FFH ; In a word now
INC IX ; Word count++
JR CNT
ISWHITESP:
LD D,FALSE ; Inword = false
JR CNT
CNTALLDONE:
PUSH IX
POP HL
CALL B2DEC
CALL MSG
DB ' words.',CR,LF,0
RETSUM: CALL OFFHALF
RET ; End summary
;------------------------------------------------------------------------------
;
; may be compressed by squeezing or crunching
;
CHKIFCOMPRESSED:
XOR A
LD (INCOMPLETE),A ; Set read not incomplete yet
LD A,(LIBRARY)
OR A ; Working fr lbr?
LD A,(FCB1TYP+1) ; Chk 2nd letter of file typ
JR Z,ISITQZ ; If not lbr
LD A,(MEMBER+9) ; Else, 2nd letter of member typ
ISITQZ: CP 'Q'
JP Z,SQUEEZED
; chk for crunched file
CP 'Z'
JP Z,CRUNCHED
; else it's a normal uncompressed file
; we also come back here for *.azm files after uncr fails
NORMAL:
CALL CRLF
NORML2: CALL EXTCHK ; If extracting, handle files here
CALL NZ,EXTUCFILE ; (the UnCompressed file routine)
LD DE,(BUFPTR) ; Read into buffer til eof or mem full
LD HL,MEMBER ; Print member filename in msg
LD A,(LIBRARY)
OR A
JR NZ,NRMLBR ; Nsects already set for lbr member
LD HL,512 ; Force read to eof or up to BDOS
LD (NSECTS),HL
LD HL,FCB1FN ; Print main filename in msg
NRMLBR: CALL MSG
DB CR,'Reading: ',0 ; (extra CR in case of overwrite)
CALL PRNFN ; v4.1 say what we're reading
CALL READFILE
JP Z,TOOLARGE ; Set incomplete read flag
LD A,(MTFLAG) ; Else check if ANYTHING was read
OR A ;
JP NZ,FINDEOF ; If so, ok
MT: CALL MSG ; Else complain
DB CR,LF,'===> File Empty.',CR,LF,0
CALL DELAY8 ;
JP QUITNOSUM ;
; rewritten for clarity?
; DE should pt to 1st dma adr on entry
; DE pts to last dma adr used on exit
; seq read of uncompressed file or lbr member or lbr dir into buffer
; reads entire file (up to BDOS) or nsects of a lbr dir or member
; nsects should be set for max sects to read
; NZ if read ok
; Z if too large for mem
READFILE:
XOR A ; If subr returns w/ mtflag=0, nothing was read
LD (MTFLAG),A
REEDFILP:
LD C,SETDMA
CALL BDOSC1
LD C,READSEQ
CALL BDOSCALL
RET NZ ; Read to eof ok
LD A,0FFH ; If at least 1 sec read, set this flag
LD (MTFLAG),A ;
; pt to start of next dma
LD HL,128
ADD HL,DE ; Dma += 128
EX DE,HL ; DE=next dma adr
; chk next dma adr < BDOS
LD A,(BDOSBASE+1) ; [possibly adjusted] BDOS hi adr
DEC A ; 256 byte BDOS safety cushion
CP D ; Curr hi dma adr
JR NZ,OKNEXT ; File about to crash into BDOS
CALL EXTCHK
RET Z ; Nope, give up
LD DE,BDOSBASE ; Pass end-of-buffer addr
CALL OUTFLUSH ; Flush the buffer
; On return, DE points to start of buffer again
; chk if spec # of sects read
OKNEXT: LD HL,(NSECTS)
DEC HL ; Nsects--
LD (NSECTS),HL
LD A,H
OR L ; Spec # of sects read?
JR NZ,REEDFILP ; No
INC A ; Set nz for nsects read ok
RET
; C and DE must both be set for call
; saves & restores BC,DE,HL,IX,IY
; Z set if a = 0, M set if a < 0
BDOSC1: PUSH BC
PUSH DE
PUSH HL
PUSH IX
PUSH IY
JR DEISSET
; C must be set for correct BDOS fn on fcb1
; saves & restores all regs except af which has ret code
; set z if a = 0
BDOSCALL:
PUSH BC
PUSH DE
PUSH HL
PUSH IX
PUSH IY
LD DE,FCB1 ; Set FCB1
DEISSET:
CALL BDOSEV
BDOSRET:
OR A ; Set Z & sign flags
POP IY
POP IX
POP HL
POP DE
POP BC
RET
; unsqueezing code setup
SQUEEZED:
LD HL,(BDOSBASE) ; [possibly adjusted] BDOS addr
LD (WORKAREA),HL ; Workarea is all mem up to BDOS for unsq
LD HL,STACK
LD (SPSAVE),HL ; Set default stk if too large
; set *sq and *unsq
LD HL,100H ; Src ptr for getbyt, forcing read
LD DE,(BUFPTR) ; Dst ptr for out
LD (UNCRSRC),HL
LD (UNCRDST),DE
CALL MSG
DB CR,LF,LF,'Unsqueezing: ',0
CALL GETBYT
CP 76H ; Compressed file marker (halt inst)
JP NZ,NOTCOMPRESSED
CALL GETBYT
CP 0FFH ; Squeezed file marker
JP NZ,NOTCOMPRESSED
CALL GETBYT
CALL GETBYT ; Skip 2 chksum bytes
LD DE,FCB3+17 ; Place to put unsqueezed fn
; print the unsqueezed file name
NXTSQFNCHAR:
CALL GETBYT
LD (DE),A ; Save in find string area
INC DE
OR A ; '\0' $ term?
JR Z,SQFNDONE
CALL PUTC
JR NXTSQFNCHAR
SQFNDONE:
CALL EXTCHK ; If we're extracting, time to open the file
CALL NZ,EXTCRFILE ; (the CompRessed file routine)
CALL GETBYT ; Get # of 4 byte transl pairs
LD L,A
CALL GETBYT
LD H,A
; times 4 for number of bytes in transl tbl
ADD HL,HL
ADD HL,HL
LD B,H
LD C,L
; copy unsq transl tbl over ptrtbl temporarily
LD HL,(@PTRTBL) ;
COPYUNSQTT:
CALL GETBYT
LD (HL),A ; Store into tt
INC HL
DEC BC ; Ctr--
LD A,B
OR C
JR NZ,COPYUNSQTT
LD B,0 ; Init bit ctr
; drive the unsqueezer
UNSQNEXT:
CALL UNSQ ; Unsq 1 char
JR C,UNSQDONE ; Eof
CP 90H ; Repeat count follows
JR Z,REPCHAR ; Don't save 90h repeat ch
LD (LASTUNSQCH),A ; Save in case of repeat count
CALL OUT ; Put unsq char into buffer
JR UNSQNEXT
REPCHAR:
CALL UNSQ ; Get repeat count
JR C,UNSQDONE ; Eof
OR A ; 0 cnt?
JR Z,SEND90H ; Then send real 90h
PUSH BC ; Save bit ctr B
LD B,A ; Repeat ctr
DEC B ; Actual cnt is 1 less
JR Z,UNSQNEXT
LD A,(LASTUNSQCH)
REPLOOP:
PUSH AF
CALL OUT ; Out last ch B times
POP AF
DJNZ REPLOOP
POP BC ; Rst bit ctr B
JR UNSQNEXT
SEND90H:
LD A,90H
CALL OUT
JR UNSQNEXT
UNSQDONE:
CALL OUT ; Save eof marker
LD HL,(UNCRSRC)
LD DE,(UNCRDST)
JP FINDEOF
; B = bitstogo mod 8 ctr
; C = curr sq ch, maybe partially shifted
; DE = curr transl tbl incr
; HL = *sq transl tbl
UNSQ: LD DE,0 ; DE=curr tbl incr
XOR A
OR B ; Chk bits to go = 0
JR NZ,NEWINDEX ; Nz is sq char in progress
; else start with a new sq char
NXTSQCHAR:
CALL GETBYT ; Fetch a sq char
LD C,A ; Save in C
LD B,8 ; 8 bits per char shift ctr
; this code is from lt18 unsqueezer
NEWINDEX:
LD HL,(@PTRTBL) ;
; mult curr incr in DE by 4 by repeated adding
ADD HL,DE
ADD HL,DE
ADD HL,DE
ADD HL,DE
; shift out lsb of sq char & chk it
LD A,C ; Get sq char back
SRL A ; Shift bit 0 into cy
LD C,A ; Save sq ch again
JR NC,NOTSET ; Use odd pair
INC HL ; To even pair if bit was set in sq char
INC HL
NOTSET: LD E,(HL) ; New incr for DE if not transl
INC HL
LD D,(HL) ; > 7fh if valid transl
BIT 7,D ; Bit 7 set if valid
JR Z,NOTTRANSL ; Hi bit not set: E is not a transl
DEC B ; Bit ctr--
LD A,0FEH ; End of transl tbl
CP D ; Set z flag if eof
LD A,1AH ; Get eof marker
SCF ; Mark this as the eof return
RET Z ; Since 1ah could be repeat count
LD A,E ; Else get char transl
CCF ; No carry if not eof
CPL ; Extract char by inversion
RET ; Ret the unsq ch
NOTTRANSL:
DJNZ NEWINDEX
JR NXTSQCHAR
; uncrunching i/o code
CRUNCHED:
CALL MSG
DB CR,LF,LF,'Uncrunching: ',0
LD HL,100H ; Src ptr for getbyt, dummy end of sect
LD DE,(BUFPTR) ; Dst ptr for out
LD (UNCRSRC),HL
LD (UNCRDST),DE
; chk to see if header is correct for crunched file
; we do this here in order to abort gracefully if it's an uncrunched .azm file
CALL GETBYT
CP 76H
JR NZ,NOTCOMPRESSED
CALL GETBYT
CP 0FEH
JR NZ,NOTCOMPRESSED
; crunched header ok
; now output the file name
;
; Do not print data which may be after end of filename, but before the
; zero (system dependent data allowed here; CR23d uses this). We will
; print the chars if they are between "[" and "]", however.
;
LD B,12 ; Loop limit for 11 chars plus "."
LD DE,FCB3+17 ; Place to put uncrunched filename
SAYLP: CALL GETBYT ; Next filename char
LD (DE),A ; Save fn for extracting
INC DE
CP '.' ; Dot?
JR NZ,NOTDOT ; If not
LD B,4 ; If we hit the dot, only 4 (dot+3) chars left
NOTDOT: OR A ; A zero terminates, as always
JR Z,CRHDRDONE ; Yes, done
CALL PUTC ; Output the char
DJNZ SAYLP ; Loop a limited number of times
CALL EXTCHK ; If we're extracting, time to open the file
CALL NZ,EXTCRFILE ; (the CompRessed file routine)
CALL GETBYT ; This part's optional- print "[..]" text
OR A ; End-of-header?
JR Z,CRHDRDONE ; If so..
CP '[' ; Beg of comment?
JR NZ,FNDEOH ; Forget it, skip junk and continue
LD B,A ; Save that "["
LD A,' ' ; Space btwn filename and comment looks better
CALL PUTC ;
LD A,B ; Get that "[" bak again
CMNTLP: CALL PUTC ; Ok, start typing comment
CALL GETBYT ; Next char
OR A ; In case of missing "]"
JR Z,CRHDRDONE ;
CP ']' ; End of comment?
JR NZ,CMNTLP ; Loop for more chars if not
CALL PUTC ; Print closing bracket
; now (finally!) make sure we are at the zero marked eoh
FNDEOH: CALL GETBYT
OR A
JR NZ,FNDEOH
; set workarea 24k below BDOS.
; "UNC", in it's present configuration, checks that the address of free
; memory supplied to it in HL allows FULLY 24k (or more). It does this
; after rounding up the value supplied to the next even page boundary. So
; we have to add in an extra 256 bytes to allow for this rounding process.
CRHDRDONE:
LD HL,(BDOSBASE) ; [possibly adjusted] BDOS addr
LD DE,24*1024+256 ; 24k + one page for "rounding"
XOR A
SBC HL,DE
LD (WORKAREA),HL ; Save for debug only
CALL UNC ; Join uncrel after filename scanned
LD HL,(UNCRSRC)
LD DE,(UNCRDST)
JR C,CHKUNCRERRS
; file was successfully uncrunched
PUSH DE ; DE pts to last out+1
EX DE,HL ; HL now pts to last out+1
LD DE,(BUFPTR) ; Start of uncr text
XOR A
SBC HL,DE ; Len of uncr text
LD (FILELEN),HL
POP DE ; Last out+1 for findeof
JP FINDEOF ; Treat like all others
CHKUNCRERRS:
CP 2 ; Error 2 is file not crunched
JR NZ,CHK1ERROR
; we can handle this error:
; force top of file again, then treat as normal text
NOTCOMPRESSED:
LD HL,0
LD (FCB1R0),HL
LD C,RANDOM
CALL BDOSCALL ; Read at tof
JP NORML2 ; (Will overwrite "Uncrunching" msg)
CHK1ERROR:
PUSH AF
CALL CRLF
POP AF
CP 1
JR Z,ERR1
CP 5
JR NZ,CHK3ERROR
ERR1: CALL MSG
DB 'Unknown crunched format',0
JP QUITNOSUM
CHK3ERROR:
CP 3
JR NZ,CHK4ERROR
CALL MSG
DB '++ File is corrupt ++',0
JP QUITNOSUM
CHK4ERROR:
CP 4
JR NZ,UNCRUNKERROR
CALL MSG
DB '++ Out of memory ++',0
JP QUITNOSUM
UNCRUNKERROR:
PUSH AF
CALL MSG
DB '++ Uncrunch error: ',0
POP AF
ADD A,'0' ; Make an ascii #
CALL PUTC
JP QUITNOSUM
; i/o rtns for uncrel.azm
; these are also used by unsq code
GETBYT: PUSH BC ; Save working regs
PUSH HL
LD HL,(UNCRSRC)
LD A,H
CP 1 ; At 100h?
JR C,STILLINSECT
; read another sector of the file
PUSH DE ; Save dst ptr fr BDOS destruction
LD C,SETDMA
LD DE,80H ; Use default buffer
CALL BDOSC1
LD C,READSEQ
CALL BDOSCALL ; Read next sector into it
POP DE ; Restore DE
LD HL,80H ; Set ptr to start of this sector
STILLINSECT:
LD A,(HL) ; Get a char to uncr
INC HL ; *ch++
LD (UNCRSRC),HL
POP HL ; Restore working regs
POP BC
RET
OUT: PUSH AF
PUSH DE ; Save working regs
LD DE,(UNCRDST)
LD (DE),A
INC DE
; chk for DE > workarea
LD A,(WORKAREA+1)
CP D ; Hi bytes only
JR NZ,OUTOK
; else, uncr/unsq text is about to run into workarea
; so if we are extracting from a library, we flush the buffer now
CALL EXTCHK ; Are we indeed extracting?
JR NZ,OUT0
LD SP,(SPSAVE) ; Restore our sp
CALL CRLF
DEC DE ; DE pts to last byte uncr
JR TOOLARGE
OUT0: LD DE,(WORKAREA) ; Pass ptr to buffer top in DE
LD E,0
CALL OUTFLUSH
OUTOK: LD (UNCRDST),DE ; Reset destination ptr
POP DE ; Rst working regs
POP AF
RET
OUTFLUSH:
PUSH HL ; Save last 2 working regs
PUSH BC ;
LD HL,(BUFPTR) ;
EX DE,HL ; Put last sector used addr in HL
OR A ; Clear carry for 16-bit subtract
SBC HL,DE ; HL is now length of full buffer
PUSH HL ; Save it
LD B,0 ; BC will be sector counter
LD C,H ;
SLA L ;
RL C ;
RL B ; Now BC has correct sector count
OUTF0: PUSH BC
PUSH DE
LD C,SETDMA ; Set DMA to this sector
CALL BDOSC1
LD C,WRITSEQ ; Write sector
LD DE,FCB3 ; Extraction FCB
CALL BDOSC1
JP NZ,NOSPACE ; NZ means write failed
LD HL,(FLSECTS) ; Count one more sector flushed
INC HL
LD (FLSECTS),HL
POP DE
POP BC
LD HL,80H ; Point to next sector
ADD HL,DE
EX DE,HL ; Swap into DE
DEC BC ; V4.0 need 2-byte loop counter, as mentioned
LD A,B ;
OR C ;
JR NZ,OUTF0 ;
POP HL ; Get back orig buffer length
LD A,L ; Low byte
AND 127 ; This many bytes were not flushed
LD C,A ; Move to BC
LD B,0
EX DE,HL ; Point to unflushed bytes
LD DE,(BUFPTR) ; Point to start of buffer
JR Z,OUTF1 ; If there were no bytes, skip it
LDIR
OUTF1:
POP BC ; Restore regs
POP HL
RET ; And DE points to first free location
;..............................................................................
;
TOOLARGE:
LD A,0FFH ; Flag incomplete read
LD (INCOMPLETE),A
; (Second half, QL.002 follows....)
;.............................................................................
LD C,WRITSEQ ; Write sector
LD DE,FCB3 ; Extraction FCB
CALL BDOSC1
JP NZ,NOSPACE ; N