home *** CD-ROM | disk | FTP | other *** search
- ;; Changes:
- ;; 11/12/88: Added line to re-display if no files selected inside ().
- ;; 11/08/88: Added line at SELALL to print '*' when it's hit.
- ;; Fixed help msg.
-
- ;=======================================================================
- ; QFC.LIB ;
- ;==========
- ;
- ; These routines form the choose-by-number interface, which is used
- ; repeatedly. The entry point is QFC. A pointer to QFC's parameter block
- ; should be passed in register IX. This is the format of the parameter block.
-
- ;FNCNT DS 1 ; Number of entries in table.
- ;FNTBL DS 2 ; Pointer to the first entry in table.
- ;ENTLEN DS 1 ; Length of an entry.
- ;FNOFFS DS 1 ; Offset of filename from entry start.
- ;FNPARS DS 1 ; YES if filenames are in form fn.typ.
- ; NO if filenames are in form fn------typ.
- ;FNSORT DS 1 ; YES to sort before beginning.
- ; NO to leave in existing order.
- ;FNSELD DS 1 ; Count of files selected.
- ;FNMULT DS 16 ; fn numbers (if multiple selected).
- ;HEDRTN DS 2 ; Routine to print screen header.
- ;
- ; By making these values parameters, it becomes easy to use the same
- ; code for choosing a file, an LBR member, or an ARC member.
- ;
- ; Returned values:
- ; HL will point to the start of the [first] entry selected.
- ; A will hold the number of that entry.
- ; B will hold the count of files selected, or 255 for "all".
- ; Z flag is set iff an exit char was pressed.
- ; C flag is set iff an unrecognizable char was pressed (so caller can process).
- ; This allows us to handle (E)xtract/(V)iew toggling.
- ;
- ; On successive calls to QFC when a multi-selection is active,
- ; QFC loads the appropriate values and returns, without redisplaying the screen.
- ;
- ; The subroutine LOOKUP, which is used by QFC, is also available to
- ; the rest of the program. It takes the entry number in C and returns
- ; HL to point to the filename within the entry.
- ;
- ; Note that for LBR, ARC, or other 'collection' processing, some information
- ; bearing on how to find the member ought to be saved along with the entry.
- ; For LBR, this is part of the directory entry; for ARC, we store the sector
- ; and offset along with the header.
- ;=============================================================================
- ;...
- ; QFC equates
-
- QFCBLKSIZ EQU 26 ; Length of QFC param block
- FNCNT EQU 0 ; Positions of variables within block
- FNTBL EQU 1
- ENTLEN EQU 3
- FNOFFS EQU 4
- FNPARS EQU 5
- FNSORT EQU 6
- FNSELD EQU 7
- FNMULT EQU 8
- HEDRTN EQU 24
-
- ;
- ; Main entry point.
- ;
- ; Decide whether to parse and/or sort.
-
- QFC: LD A,(IX+FNPARS) ; Should we parse?
- OR A
- JR Z,NOPARS
-
- LD C,1
- CALL LOOKUP ; Point to first fn
- LD E,(IX+ENTLEN)
- LD D,0 ; DE = entry length
- LD B,(IX+FNCNT) ; B = entry count
- PARSLP: CALL PARSFN ; Parse next fn
- ADD HL,DE ; Point to next
- DJNZ PARSLP ; Loop
- LD (IX+FNPARS),0 ; Reset "must parse" flag
-
- NOPARS: LD A,(IX+FNSORT) ; Should we sort?
- OR A
- JR Z,SWEEP
-
- LD H,(IX+FNOFFS) ; H = sort key start
- LD L,11 ; L = sort key length
- CALL SORT ; Do it
-
- LD (IX+FNSORT),0 ; Reset "must sort" flag
-
- ; See if multi is active.
- ;
- SWEEP: LD A,(IX+FNSELD) ; Count of files last selected
- OR A ; Zero - multi is through.
- JR Z,SWEEP0
- CP 255 ; 255 - multi is ALL.
- JR Z,SWPALL
- CP 1 ; One - not multi.
- JR Z,SWEEP0 ; Otherwise SOME.
-
- ; Active multi is SOME.
- SWPSOM: DEC A ; One less
- LD (IX+FNSELD),A
- PUSH IX ; Move to HL
- POP HL
- LD DE,FNMULT+15 ; Point to end of FNMULT area
- ADD HL,DE
- LD BC,0+15*256 ; C=0; B=15
- MOVLP: LD A,(HL) ; Get this byte
- LD (HL),C ; Save last byte
- LD C,A ; Move this to last
- DEC HL ; Back up one byte
- DJNZ MOVLP ; Loop
- ; When done, A = first in string
- LD (HL),A ; Save it
- JP GOODFIL ; Process it
-
- ; Active multi is ALL.
- SWPALL: LD A,(IX+FNMULT) ; Last file processed
- CP (IX+FNCNT) ; Was that the last file?
- JR Z,SWEEP0 ; yes, select something new
-
- INC A ; Select next file
- LD (IX+FNMULT),A ; Save for next round
- JP GOODFIL ; Process this one
-
- ; Ready to choose next file to view.
- ;
- SWEEP0: XOR A ;
- LD (SCRNUM),A ; Init "screen#" to zero (goes, 0,72,144..)
- LD (IX+FNSELD),A ; Clear multi options
- JP NSCR ; Skip over help msg
-
- ;...............................;
- ; Help message for QFC.
- ;
- QFCHLP: CALL CLEARSCREEN
- CALL MSG
- DB CR,LF,'File selection help:'
- DB CR,LF
- DB CR,LF,' ##',TAB,'Select numbered file'
- DB CR,LF,' <ret>',TAB,'Display next page of files'
- DB CR,LF,' S',TAB,'Re-sort files starting at nth position'
- DB CR,LF,TAB,' (e.g. 8 to sort by extension)'
- DB CR,LF,' ^C',TAB,'Abort to CP/M'
- DB CR,LF,' Q',TAB,'Abort to previous level'
- DB CR,LF
- DB LF,' *',TAB,'Select ALL files'
- DB CR,LF,' (#,#)',TAB,'Select SOME files'
- DB CR,LF
- DB LF,'Press any key to redisplay files',0
- WAITCH: LD C,DIRIO ; wait for a char
- LD E,0FFH
- CALL BDOSC1
- OR A
- JR Z,WAITCH ; Loop until kbhit
- CP CR ; Trap CR separately
- JR Z,NSCR
- CALL CHEXIT ; Process 'exit' chars
- JP Z,QFCEXIT ; Fall through if no exit
- ;...............................;
- NSCR: CALL HEADER ; Display proper header:
- ; 'Files Matching: DU <afn>'
- ; 'Members of: DU <fn>'
- LD A,(IX+FNCNT) ; Count of files
- LD (HIPG),A ; Set hipg so can deduce when enuf
- INC A ; Count +1
- LD D,A ; Max #of files +1 goes into D
-
- LD E,1 ; E is line#, (init to 1)
-
- ;................................
- ;
- LINLP: LD B,4 ; Outer loop for NL lines
- LD A,(SCRNUM) ;
- ADD A,E ; 1st file# in each line = line# + scrn#
- LD C,A ;
- ;................................
- ; Inner loop, 4/line
- LP4: LD A,C ; File#
- CP D ; Compare to max
- JR NC,OUT4 ; If greater, done w/ this line
- CALL LOOKUP ; Convert file # in c to pointer to name in HL
- CALL PRNUMFN ; Print xxx:filename.typ
- LD A,C ;
- ADD A,NL ; Next file, if any, is prev# plus NL
- LD C,A ;
- DJNZ LP4 ;
- ;...............................;
-
- OUT4: CALL CRLF ;
- LD A,E ; Advance to next line
- INC A ;
- LD E,A ;
- CP NL+1 ;
- JR C,LINLP ;
- ;...............................;
-
- ; V4.1 all screens now have same msg.
- CALL MSG
- DB CR,LF,'File #, cmd, or / for help: ',0
-
- BADNUM:
- XOR A
- LD (JUMPTO),A ; Clear jumpto
- CALL GETCHNUM ; Get user response
- CALL UCASE ; Force upper case
- LD C,A ; save char response
- LD A,(JUMPTO) ; Did he enter a #?
- OR A
- JP NZ,CHKFIL ; Check it
-
- LD A,C ; Get back char
- CP '/' ; Asked for help?
- JP Z,QFCHLP
- CP '?'
- JP Z,QFCHLP
- CP CR ; Page?
- JR Z,NXTSCR
- CP TAB ; Tab also means page
- JR Z,NXTSCR
- CP 'S' ; Sort again?
- JR Z,RESORT
- CP '*' ; All files?
- JR Z,SELALL
- CP '(' ; Some files?
- JR Z,SELSOM
- NOCMD: CALL CHEXIT ; ^C, ^K straight to CP/M
- JP Z,QFCEXIT ; other exit chars return
- SCF ; If unrecognized, flag it
- RET ; and let caller handle it
-
- ; Display next screen.
- ; Wrap to first screen if at end.
- ;
- NXTSCR: LD A,(SCRNUM) ; Current "screen #"
- ADD A,72 ; Plus one screenfull
- JR C,SCROVF ; If >255, certainly too big
- CP (IX+FNCNT) ; Past end?
- JR C,NSCROVF ; If not past end, use this
- SCROVF: SUB A ; Point back to beginning
- NSCROVF:
- LD (SCRNUM),A ; Save new screen#
- JP NSCR ; Display it
- ;...............................;
- ; Re-sort the files.
- ; Ask user which char in filename to begin with.
- ; This allows sorting by type, name, or any subset thereof.
- ;
- RESORT: CALL MSG
- DB 'Sort files starting at: ',0
- LD A,10
- LD (HIPG),A ; Set hipg
- SUB A
- LD (JUMPTO),A ; Clr jumpto
- CALL GETCHNUM ; Get user response
- LD A,(JUMPTO)
- CP 11 ; Too big?
- JP NC,NSCR ; Yep, ignore
- LD C,A ; Save
- LD A,(IX+FNOFFS) ; Get offset to fn in entry
- ADD A,C ; Index into entry
- LD H,A ; move to H
- LD A,11 ; Compute length of sort key
- SUB C
- LD L,A ; Put in L
- CALL SORT ; Do the sort
- JP NSCR ; Redisplay
- ;...............................;
- ; Select all files.
- ; Set up return variables and return.
- SELALL: CALL PUTC ; Print asterisk
- LD A,255 ; mark for 'ALL'
- LD (IX+FNSELD),A
- LD A,1 ; Index to first file
- LD (IX+FNMULT),A
- LD L,(IX+FNTBL)
- LD H,(IX+FNTBL+1) ; Pointer to first entry
- OR A ; Reset Z,C flags
- RET ; All done
- ;...............................;
- ; Select 'some' files.
- ; Triggered when user types a '('.
- ; Get successive file #s until 15 have been chosen,
- ; or ')' (or CR) is typed.
- SELSOM: CALL PUTC ; Print the (
- LD B,0 ; Count the files
- LD HL,FNMULT ; Place to put them
- PUSH IX
- POP DE
- ADD HL,DE
-
- SSLP: SUB A ; Clr JUMPTO
- LD (JUMPTO),A
- PUSH BC ; Save vitals
- PUSH HL
- CALL GETCHNUM ; Get next selection
- POP HL ; Restore vitals
- POP BC
- LD C,A ; Save char
- LD A,(JUMPTO) ; Get response
- OR A ; Zero?
- JR NZ,SSCHK ; Check it out if not
- LD A,C ; Restore char
- CP ')' ; Closed parens?
- JR Z,SSDON ; Yes, finish up
- CP CR ; <cr> also finishes list
- JR Z,SSDON ;
- JR SSLP ; Others are ignored
-
- SSCHK: CP (IX+FNCNT) ; File # out of range?
- JR C,SSGOOD ; <max is ok
- JR Z,SSGOOD ; =max is ok
- CALL UNBDEC ; Erase from screen
- JR SSLP ; Try again
-
- SSGOOD: LD (HL),A ; Save it here
- INC HL ; bump save ptr
- INC B ; Count it here
- LD A,',' ; delimit char
- CALL PUTC
- LD A,B ; Full yet?
- CP 16
- JR NZ,SSLP ; Nope, loop
-
- SSDON: CALL BACKSP ; Erase last comma
- LD A,')' ; Close paren
- CALL PUTC
- LD (HL),0 ; End the sequence
- LD A,B ; Load count
- OR A
- JP Z,NSCR ; Redisplay if none selected
- LD (IX+FNSELD),A ; Save here
- LD A,(IX+FNMULT) ; index to first
- LD C,A
- CALL CALC ; Make ptr to entry start
- OR A ; Reset Z,C flags
- RET
- ;................................
- ; Check entry for single selection
-
- CHKFIL: LD C,A
- LD A,(IX+FNCNT)
- CP C
- LD A,C
- JR NC,GOOD
- CALL UNBDEC
- JP BADNUM
-
- GOOD: LD (IX+FNMULT),A ; Save file #
- LD (IX+FNMULT+1),0 ;
- LD B,1 ; One file selected
- LD (IX+FNSELD),B ; Save it
- GOODFIL:
- CALL CALC ; Point to entry
- OR A ; Reset Z,C flags
- RET ; Return
- ;...............................;
- ; Exit routine
- ; When user hits an 'exit key'
-
- QFCEXIT:
- LD HL,0 ; Point nowhere
- LD A,L ; File # = 0
- LD B,0 ; Files selected=0
- LD (IX+FNSELD),A ; No files selected
- LD (IX+FNMULT),A ; Index = 0
- OR A ; Reset C flag, set Z flag
- RET ; With Z flag set
- ;...............................;
- ; Various subroutines
- ;
- UNBDEC: CALL BELL ; Beep!
- CP 100 ; 3 digits?
- CALL NC,BACKSP ; erase hundreds
- CP 10 ; 2 digits?
- CALL NC,BACKSP ; erase tens
- ; fall through to erase ones
- BACKSP: PUSH AF
- PUSH HL
- CALL MSG
- DB 8,' ',8,0
- POP HL
- POP AF
- RET
-
- BELL: PUSH AF
- LD A,BEL ; Beep!
- CALL PUTC
- POP AF
- RET
-
- HEADER: PUSH IX ; Save IX reg
- LD HL,HEADRET ; New return address
- PUSH HL
- LD L,(IX+HEDRTN) ; Load ptr to header routine
- LD H,(IX+HEDRTN+1) ;
- JP (HL)
- HEADRET:
- POP IX ; Restore IX reg
- RET
-
- HEADJP: JP (HL)
- ;...............................;
- ; Lookup fcn
- ; Converts C, entry #, into ptr
- ; to fn within entry (HL)
- ; None destroyed
-
- LOOKUP: PUSH AF
- PUSH DE
- LD A,C
- CALL CALC
- LD E,(IX+FNOFFS)
- LD D,0
- ADD HL,DE
- POP DE
- POP AF
- RET
- ;...............................;
- ; Calc fcn
- ; Converts A, entry #, into ptr
- ; to start of entry (HL)
- ; None destroyed
-
- CALC: PUSH DE
- PUSH AF
- LD L,(IX+FNTBL)
- LD H,(IX+FNTBL+1)
- LD E,(IX+ENTLEN)
- LD D,0
- DEC A
- CALC0: SRL A
- JR NC,CALC1
- ADD HL,DE
- CALC1: EX DE,HL
- ADD HL,HL
- EX DE,HL
- OR A
- JR NZ,CALC0
- POP AF
- POP DE
- RET
- ;...............................
- ; Parse fcn
- ; Takes fn.typ at (HL) and converts
- ; to fn------typ at (HL)
- ; None destroyed
-
- PARSFN: PUSH AF ; Save all
- PUSH BC
- PUSH DE
- PUSH HL
-
- LD DE,FCB3+1 ; Temporary place to put result
- LD BC,8 ; 8 chars in first segment
- PFN0: LD A,(HL) ; Get next char
- AND 127 ; ASCII mask (no file attributes!)
- JR Z,PFN1 ; If zero, was end of string char
- CP '.' ; Dot yet?
- JR Z,PFN1
- LDI ; Transfer char
- JP PE,PFN0 ; Loop if not done
- ; if we get here, the filename may be too long. We ignore bytes until we find
- ; a dot or null.
- PFNSKP: LD A,(HL)
- OR A ; Null?
- JR Z,PFN2
- CP '.' ; Dot?
- JR Z,PFN2
- INC HL ; Test next char
- JR PFNSKP
-
- PFN1: LD A,' ' ; Fill remaining part of first segment
- LD (DE),A ; With spaces
- INC DE
- DEC C
- JR NZ,PFN1
- PFN2: INC HL ; Bump past dot
- LD BC,3 ; Three more chars
-
- PFN2B: LD A,(HL) ; Get char
- OR A ; Null means we fill with space
- JR NZ,PFN4
- LD A,' ' ; Fill with space
- PFN3: LD (DE),A
- INC DE
- DEC C
- JR NZ,PFN3
- JR PFNDON
-
- PFN4: LDI ; Transfer char
- JP PE,PFN2B ; Loop
-
- PFNDON: POP DE ; original source again
- PUSH DE ; BAck on stack
- LD HL,FCB3+1 ; Temp area
- LD BC,11 ; bytes to move
- LDIR
- POP HL ; Restore all
- POP DE
- POP BC
- POP AF
- RET
- ;..............................................................................
- ;
- ; Bubble sort all the entries. Key starts at H and has length L.
- ;
- SORT: LD (80H),HL ; Save sort key info here (re-use space)
- LD A,(IX+FNCNT) ; #of entries to be sorted
- DEC A ; minus 1
- RET Z ; Can't sort 1 entry!
- LD C,A ; Init outer loop counter
-
- ;................................
- ;
- OUTRLP: LD B,C ; Init inner loop counter
- LD E,(IX+FNTBL) ; Get table base
- LD D,(IX+FNTBL+1) ; (DE) = first entry
- LD L,(IX+ENTLEN) ; Get entry length
- LD H,0 ;
- ADD HL,DE ; (HL) = 2nd entry
- ;...............................;
- ;
- INRLP: PUSH BC ; Save loop counters
- CALL COMP ; Compare two entries
- CALL C,SWAP ; Swap if necessary
- LD C,(IX+ENTLEN) ; Bump ptrs
- LD B,0 ;
- ADD HL,BC ;
- EX DE,HL ;
- ADD HL,BC ;
- EX DE,HL ;
- POP BC ; Restore loop counters
- DJNZ INRLP ; End inner loop
- ;...............................;
-
- DEC C ; End outer loop
- JR NZ,OUTRLP ; Loop till done
-
- RET ;
-
- ;..............................................................................
- ;
- ; Compare the entries at (HL) and (DE) [ Used by SORT above]
- ;
- COMP: PUSH DE ;
- PUSH HL ;
- LD A,(81h) ; Retrieve sort key offset
- LD C,A
- LD B,0 ;
- ADD HL,BC ;
- EX DE,HL ; DE -> jth key
- ADD HL,BC ; HL -> j+1th key
- LD A,(80h) ; Retrieve sort key length
- LD B,A
-
- COMPLP: LD A,(DE) ;
- CP (HL) ;
- JR NZ,CMPRTN ; If not equal, rtn with appropriate carry stat
- INC HL ;
- INC DE ;
- DJNZ COMPLP ; Compare entire key
- OR A ; Clr for equal avoids unecessary equal swaps
-
- CMPRTN: POP HL ;
- POP DE ;
- RET ;
-
- ;..............................................................................
-
- ; Exchange the entries at (HL) and (DE). [ Used by SORT above]
- ;
- SWAP: PUSH DE ;
- PUSH HL ;
-
- LD B,(IX+ENTLEN) ; Get entry size
- SWAPLP: LD A,(DE) ; Get a corresponding byte from each
- LD C,(HL) ;
- EX DE,HL ; Exchange the pointers
- LD (DE),A ; And re-store the pair of bytes
- LD (HL),C ;
- INC HL ;
- INC DE ;
- DJNZ SWAPLP ; Loop; (note- another ex DE,HL not needed)
-
- POP HL ;
- POP DE ;
- RET ;