home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
CP/M
/
CPM_CDROM.iso
/
cpm
/
cpm3
/
zfile3p.lbr
/
ZFILE3.AZM
/
ZFILE3.ASM
Wrap
Assembly Source File
|
1987-07-25
|
35KB
|
1,543 lines
; ZFILE.ASM - Searches for file names (rename to FILE.ASM) - 07/17/87
;
VERS EQU 3 ; Version number
;
ASEG ; Needed for M80, disregard otherwise
ORG 0100H
;
;
JMP START
;
;
; ZFILE looks on all permitted drives and user areas for one or more
; requested files. Wild cards may be used. It usually works best to
; use just 1-2-3 characters and complete the file name with wildcards.
; The file you are looking for may be spelled a little differently or
; it may have been updated or there might be several versions on line.
; To use:
; A>FILE *.DOC,FI1*.*,FI*.COM,FILE3.TXT(,etc.)
;
; Max drive and max user that will be searched are automatically set if
; using a WHEEL byte with USEZCPR set YES, and the associated addresses
; below are remotely supplied by the BBS or RCPM system. If USEZCPR is
; set NO, you can still use a wheel byte to limit the user to the areas
; set manually at MAXDRV and MAXUSR. For private systems with no WHEEL
; byte set SYSFILE to YES if you wish to include systems files, these
; are automatically included when the WHEEL byte is set for remote use.
;
; The file may be aborted with 'c C ^C', 'x X ^X or 'k K ^K'. 's S ^S'
; to pause, and non-abort key to resume.
;
; The program automatically commences at A0: regardless of the drive or
; user area from which it is requested. Suggest you rename the program
; FILE.COM when placing on your system. (It is called ZFILE here since
; there are numerous other similar programs available most of which are
; considerably slower in operation.) Try this one, you will be very im-
; pressed with its speed. ZFILE.COM is 16 records, 2k in length.
;
; (If using ZCPR3, there are two lines commencing with ;; and ending in
; '*** ZCPR3 ?' that you can easily find that may need to be activated
; for your particular system. Just remove the two ;; and reassemble.)
;
; - notes by Irv Hoff W6FFC
;
;-----------------------------------------------------------------------
;
; 07/17/87 Rewrote the abort and pause routines. Previously needed two
; v3 consecutive CTL-C to abort or two CTL-S to pause. Now works
; properly. Pauses with 's S ^S', aborts with a message with:
; 'c C ^C', 'k K ^K' or 'x X ^X', in keeping with other pgms.
; (A pause or abort also only stops at the end of the current
; line, not in the middle of a word, or just anywhere on the
; line, etc.) Also returns directly to CCP when finished now,
; instead of requiring a warm reboot which was unecessary and
; wasted time on an otherwise super-fast program. As no writ-
; is done to the disk this is acceptable. Per a suggestion by
; Paul Foote, added a 3rd "skip drive" equate, which is needed
; by some computers such as his Xerox. Fixed an obscure bug in
; the CONTIN area reported by Bill Duerr. He was also helpful
; in testing this version and pointing out some typos. It now
; can properly handle files up to 8 Mb. ZFILE2 was duplicat-
; ing files names if over 512k long. Thanks to Joe Wright for
; this fix as well as extensive disucssions on how the program
; should work. 17 records object code when assembled. Built-
; in help guide. - Irv Hoff
; PRACSA RCPM
;
; 12/22/85 Removed the external macros, eliminated the need for special
; v2 macro assemblers with linking loaders. Systems files auto-
; matically included with WHEEL byte set, or for private use
; if not using ZCPR, if SYSFILE has been set YES. (This still
; permits RCPM use without ZCPR/ZCMD.) Several subtle changes
; in the display to better isolate and clarify the results.
; Program completely reorganized with all subroutines and data
; areas alphabetized for easy location. Help guide rewritten.
; - Irv Hoff
;
; 12/14/85 First issue of ZFILE, based upon the ZCPR3 utility FINDF by
; v1 Richard Conn. This variation was created for RAS/RCPM use
; by standard CP/M computers (non-ZCPR3). Uses std. BYE/KMD
; dynamic max. drive/max. user/wheel locations in low memory.
; Added ^X abort, ^S to stop scroll, wheel check to allow or
; disallow systems files, SKIP1 and SKIP2 equ's to allow skip-
; ping drives if needed. Minor format changes to eliminate
; unecessary scrolling if no files found. Assemble using M80
; with .LIB files included. - Norman Beeler
; ZeeMachine RAS
; 408-245-1420
;
;-----------------------------------------------------------------------
;
; System equates:
;
NO EQU 0
YES EQU NOT NO
USEZCPR EQU YES ;*Yes, if using ZCPR for MAXUSR, MAXDRV
SYSFILE EQU NO ;*To include systems files with no WHEEL
; (May be YES or NO if USEZCPR is YES)
;
; The following two should be selected for your system if USEZCPR is NO
;
MAXDRV EQU 'B'-40H ; Highest drive used if not USEZCPR
MAXUSR EQU 15 ; Highest user area used if not USEZCPR
;
MAXDRIV EQU 3DH ; ZCPR location of MAXDRIV byte
WHEEL EQU 3EH ; Location of ZCPR's wheel flag
MAXUSER EQU 3FH ; ZCPR location of MAXUSR byte
;
; General equates
;
BOOT EQU 0000H ; CP/M warm boot jump vector
BDOS EQU 0005H ; CP/M BDOS call jump vector
TBUFF EQU 0080H ; Disk I/O buffer
FCB EQU 005CH ; Default file control block
BELL EQU 07H ; Bell
BS EQU 08H ; Backspace
CR EQU 0DH ; CTL-M for carriage return
CTLC EQU 03H ; Abort
CTLS EQU 13H ; Pause
CTLX EQU 18H ; Abort
LF EQU 0AH ; CTL-J for line feed
NULL EQU 00H ; Null character
TAB EQU 09H ; Tab
;
; The following equ's allow skipping up to three drives, enter 0FFH for
; no skipping.
;
SKIP1 EQU 0FFH ; A=0,B=1,E=4,etc
SKIP2 EQU 0FFH ; F=5
SKIP3 EQU 0FFH ; G=6
;
; The following two bytes are at addresses 0103H and 0104H and may be
; set by DDT without needing to edit, assemble and reload. (Save 8
; pages for 2k.)
;
MXUSR: DB MAXUSR ; Runtime maximum user area available
MXDRV: DB MAXDRV ; Runtime maximum drive available;
;
;-----------------------------------------------------------------------
;
; Start of program
;
;-----------------------------------------------------------------------
;
START: LXI H,0 ; Save stack pointer
DAD SP
SHLD STACK
LXI SP,STACK
LXI H,BUFTBL
SHLD FNTAB ; File name table
LXI D,1024 ; 1k space
DAD D
SHLD SCRATCH ; Beginning of scratch area
IF USEZCPR
LDA MAXDRIV ; Get from ZCPR/ZCMD
INR A ; Make things come out right
STA MXDRV
LDA MAXUSER ; Get from ZCPR/ZCMD
DCR A ; Make things come out right
STA MXUSR ; Save it
ENDIF ; USEZCPR
CALL GTBIOS ; Get BIOS jump table
CALL HELLO ; Sign on message
CALL HELPCHK ; Check for and print help message
CALL OPTCHK ; Process options, build file name table
CALL CRLF ; New line
CALL FIND ; Do the searches
CALL BYE ; Sign off message
EXIT: LDA NEWCR
ORA A
CNZ CRLF
LHLD STACK ; Get CCP return address
SPHL
RET
;
;-----------------------------------------------------------------------
;
; S U B R O U T I N E S
;
;-----------------------------------------------------------------------
;
; Output character in A via BDOS call
;
BOUT: PUSH H ; Save registers
PUSH D
PUSH B
PUSH PSW
MVI C,2
MOV E,A ; Put the character into the 'E" reg.
CALL BDOS
POP PSW ; Restore the character
POP B
POP D
POP H
RET
;.....
;
; Sign off
;
BYE: LDA FFLAG ; Get 'file found' flag
ORA A ; No files found?
JNZ EXIT
CALL PRINT
DB BS,BS,BS,' [no files found]',0
JMP EXIT
;.....
;
; Check for a CTL-C or CTL-S entered from the keyboard. Jump to EXIT if
; CTL-C, pause on CTL-S.
;
CKABRT: PUSH H
PUSH D
PUSH B
MVI C,11
CALL BDOS
ORA A
JZ CKAB3 ; No character, exit
MVI C,1
CALL BDOS
ANI 5FH
CPI 'S'-40H
JZ CKAB0
CPI 'S'
JNZ CKAB1
CALL CKAB4
CKAB0: MVI C,1
CALL BDOS
ANI 5FH
CKAB1: CPI 'C'-40H ; CTL-C?
JZ CKAB2 ; Yes, quit
CPI 'K'-40H
JZ CKAB2
CPI 'X'-40H
JZ CKAB2
CPI ' ' ; Any other CTL-character, abort
JC CKAB3
CALL CKAB4 ; Clear the character from screen
CPI 'C'
JZ CKAB2
CPI 'K'
JZ CKAB2
CPI 'X'
JNZ CKAB3
CKAB2: MVI C,9
LXI D,CKMS1
CALL BDOS
POP B
POP D
POP H
LHLD STACK
SPHL
RET
CKAB3: POP B
POP D
POP H
RET
CKAB4: PUSH PSW
MVI C,9
LXI D,CKMS2
CALL BDOS
POP PSW
RET
;.....
;
; Console input routine.
;
CIN: PUSH B ; Save the registers
PUSH D
PUSH H
LHLD BOOT+1 ; Jump table address
MVI L,9 ; Console input address
LXI D,CIN1 ; Set up return address on stack
PUSH D
PCHL
CIN1: POP H ; Restore the registers
POP D
POP B
RET
;.....
;
; Console output routine with control character processing. Output the
; character in 'A' to the console, affects no registers or flags.
;
CCOUT: CPI ' ' ; See if a printing character
JNC COUT ; If yes, handle normally
;
; Trap out <NULL>, <BEL>, <BS>, <LF>, <CR>
;
CPI NULL ; <NULL>
JZ COUT
CPI BELL ; <BEL>
JZ COUT
CPI BS ; <BS>
JZ COUT
CPI LF ; <LF>
JZ COUT
CPI CR ; <CR>
JZ COUT
;
; Print as CTL-character
;
PUSH PSW ; Save the character
MVI A,'^' ; Print and 'up arrow' character'
CALL COUT
POP PSW ; Get the character
PUSH PSW ; Save it again, now that we have it
ADI 40H ; Convert from binary to ASCII
CALL COUT ; Display the character
POP PSW ; Restore the original character
RET
;.....
;
; Checks the current 4 directory entries against argument. If match,
; rewrites record with reactivated 1st bytes.
;
CHKENT: MVI B,4 ; Number of entries per record
LXI H,TBUFF ; Beginning of buffer
CKLUP: PUSH B
MOV A,M
CPI 0E5H ; Check for unused
JZ CKINC
XRA A ; A=0
STA CLPFLG ; Set flag for no entries found
LDA FNCOUNT ; Get number of file names to check
MOV B,A ; In B
PUSH H
LHLD FNTAB ; Point to table
XCHG ; In DE
POP H
CKLUP1: PUSH B ; Save count
PUSH H ; Save beginning address
PUSH D
CALL COMPAR ; Compare with argument and save if match
POP D
LXI H,11 ; Point to next entry
DAD D
XCHG
POP H
POP B
DCR B ; Count down
JNZ CKLUP1
CKINC: POP B
LXI D,32 ; Length of entry
DAD D
DCR B
JNZ CKLUP
LHLD DIRMAX
DCX H ; Reduce records left
SHLD DIRMAX
LHLD RECORD ; Point to next record
INX H
SHLD RECORD
XCHG
LHLD MAXREC ; Reached limit?
;;; inx h ; One more **** ZCPR3
MOV A,H ; Check high
CMP D
RNZ
MOV A,L ; Check low
CMP E
RNZ
LHLD TRACK ; Next track
INX H
SHLD TRACK
;;; lxi h,1 ; First record of next track *** ZCPR3
LXI H,0
SHLD RECORD
RET
;.....
;
; Compare directory entry pointed to by HL with that pointed to by DE.
; No net effect on HL or DE. Return with carry set means DE<HL. Return
; with zero set means DE=HL. Compare by file name, file type, extension
; and user number (in that order).
;
CMP$ENTRY:
PUSH H
PUSH D
INX H ; Point to filename
INX D
MVI B,11 ; Compare filename and filetype
CALL COMP
POP D
POP H
RNZ
LDAX D ; Compare user number
CMP M
RET
;.....
;
; Compare 11 bytes of directory entry against argument; RNZ if not
; matched. DE points to table entry to compare to.
;
COMPAR: LDA CLPFLG ; Get found flag
ORA A ; 0=no
RNZ
SHLD TEMP ; Hold pointer in case of match
INX H
XCHG
MVI B,11
CMPR1: LDAX D ; Get directory entry character
ANI 7FH ; Strip any flags
CMP M
JZ CMPR2
MOV A,M
CPI '?'
RNZ
CMPR2: INX D
INX H ; Bump to next character
DCR B
JNZ CMPR1 ; Loop for 11 characters
PUSH D ; Save entry pointer
LDAX D ; Get extent in B
MOV B,A
LDA EXTENT ; Get extent mask
CMP B
POP D ; Get entry pointer
JC CMPR6 ; No match
;
; Check to insure REEL number is zero
;
PUSH D ; Save DE
INX D ; S1
INX D ; S2
LDAX D ; Get it
POP D ; Restore DE
ORA A ; S2 must be zero
JNZ CMPR6 ; No match
LDA SYSTEM ; Include system files?
ORA A ; 0=no
JNZ CMPR3
DCX D ; Back up 2 bytes
DCX D
LDAX D ; Get T2
ANI 80H ; Check high bit set for system file
RNZ
CMPR3: LHLD TEMP ; Check for user limit
LDA WHEEL ; Get wheel byte
CPI 0 ; Check if set
JNZ CMPR4 ; Don't limit if wheel
LDA MXUSR ; Maximum user
JMP CMPR5
CMPR4: MVI A,15 ; Don't limit wheels
CMPR5: CMP M ; Beyond maximum?
JC CMPR6
LHLD FCOUNT ; Increment count
INX H
SHLD FCOUNT
LHLD DSTART ; Get ptr to next entry
XCHG
LHLD TEMP
MVI B,12 ; Copy entry
CALL MOVE
XCHG
SHLD DSTART ; Ptr to next entry
XCHG
LHLD BDOS+1 ; Check for memory overflow
MOV A,H
SUI 10 ; Below CCP
CMP D ; Point beyond limit?
JC MOVFL
MVI A,0FFH ; Set found flag
STA FFLAG
XRA A
RET ; Returns 'zero' flag set for match
CMPR6: MVI A,0FFH ; No match
ORA A
RET
;.....
;
; Compares DE with HL for B bytes; returns with carry set if DE<HL.
; MSB is disregarded.
;
COMP: MOV A,M ; Get (HL)
ANI 7FH ; Mask MSB, put into 'C' reg
MOV C,A
LDAX D ; Compare
ANI 7FH ; Mask MSB
CMP C
RNZ
INX H ; Point to next
INX D
DCR B ; Count down
JNZ COMP
RET
;....
;
; As COMP, but match on '?' pointed to by HL
;
COMP2: MOV A,M ; Get (HL)
ANI 7FH ; Mask MSB
CPI '?' ; Match '?'
JZ COMP3
MOV C,A ; In 'C'
LDAX D ; Compare
ANI 7FH ; Mask MSB
CMP C
RNZ
COMP3: INX H ; Point to next
INX D
DCR B ; Count down
JNZ COMP2
RET
;.....
;
CONTIN:
MOV C,A
MVI E,0
CALL SELDSK ; Make sure drive is selected
MOV A,H
ORA L
RZ ; Error return
SHLD DPH ; Save the address
LXI D,10 ; Point to DPB
DAD D
MOV E,M ; Get DPB address in HL
INX H
MOV D,M
XCHG
MOV E,M ; Number of records/track
INX H ; As 2-byte quantity in DE
MOV D,M
INX H
XCHG
SHLD MAXREC ; Set maximum records/track
XCHG
INX H
INX H
MOV A,M ; Get EXM
STA EXTENT
INX H ; Point to DRM
INX H
INX H
MOV E,M ; Get number of
INX H ; Directory entries
MOV D,M
XCHG
INX H ; Account for - 1
SHLD DSTART ; Save number of directory entries
CALL SHFHL2 ; Shift 'HL' right 2
SHLD DIRMAX ; Save number directory records
LXI H,5 ; Now point to system
DAD D ; Track offset
MOV A,M ; Pick up number
INX H
MOV H,M
MOV L,A
SHLD TRACK
LXI H,0
SHLD RECORD
LDA ECOUNT ; Last new line?
ANI 3
CNZ CRLF
LDA ECOUNT
ORA A
CNZ CRLF
CALL PRINT
DB CR,'Disk ',0
LDA FCB
ADI 'A'
STA NEWCR
CALL BOUT
CALL PRINT
DB ' -- ',0 ; ** CR,LF,0
LHLD SCRATCH ; Point to scratch area
SHLD ORDER ; Address of order table
XCHG
LHLD DSTART ; Get number of directory entries
DAD H ; Double for # of bytes in order table
DAD D ; Point to first byte of DIRBUF
SHLD DIRBUF ; Set pointer
SHLD DSTART ; Set loop pointer
LXI H,0 ; Set file count
SHLD FCOUNT
XRA A ; Set count
STA ECOUNT
CMA ; Flip
ORA A ; Ok to continue
RET
;.....
;
; Console output routine, sends character in 'A' register to console.
;
COUT: PUSH PSW
PUSH B ; Save registers
PUSH D
PUSH H
MOV C,A
LHLD BOOT+1 ; Jump table address
MVI L,12 ; Console output address
LXI D,COUT1 ; Set up return address on stack
PUSH D
PCHL
COUT1: POP H ; Restore registers
POP D
POP B
POP PSW ; Restore the character
RET
;.....
;
; Print CR and LF on the console, affects no registers
;
CRLF: PUSH PSW ; Save the character
MVI A,CR
CALL COUT
MVI A,LF
CALL COUT
POP PSW ; Restore the original character
RET
;.....
;
; Console status routine
;
CST: PUSH B ; Save the registers
PUSH D
PUSH H
LHLD BOOT+1 ; Jump table address
MVI L,6 ; Console status address
LXI D,CST1 ; Set up return address on stack
PUSH D
PCHL
CST1: CMA ; Invert the flags
ANI 1 ; Set flags, 0 = RDA
POP H ; Restore the registers
POP D
POP B
RET
;.....
;
DELCHK: ORA A ; End of line?
RZ
CPI '.' ; End of field?
RZ
CPI ',' ; End of entry?
RZ
CPI ' '
RET
;.....
;
; Alphabetize directory pointed to by HL; BC contains the number of
; files in the directory
;
DIRALPHA:
LHLD FCOUNT ; Get file count
MOV A,H ; Any files?
ORA L
RZ
SHLD NUMBR ; Set "N"
MOV B,H ; BC=count
MOV C,L
LHLD DIRBUF ; Point to directory
JMP SORT
;.....
;
; Fatal error, internal error, pointer table not consistent.
;
FERR$PTR:
CALL PRINT
DB CR,LF,'DIRALPHA -- pointer error',0
JMP EXIT
;.....
;
; Look through the directory
;
FIND: XRA A ; Select first disk
STA FCB
FIND1: CALL NXTDISK ; Get info the first time
RZ ; Abort if error
CALL CKABRT ; Want to abort now?
FIND2: CALL NXTREC ; Get a directory record
JZ FIND3 ; Returns zero flag if no more
CALL CHKENT ; Check it out
JMP FIND2 ; Keep it up till done
FIND3: CALL CKABRT ; Want to abort now?
CALL DIRALPHA ; Sort entries
CALL CKABRT ; Want to abort now?
CALL PRFILES ; Print sorted entries
LDA FCB ; Next disk
INR A
STA FCB
CALL NXTDISK ; Select next disk
JMP FIND1
;.....
;
; Get BIOS jump vectors for easy reference
;
GTBIOS: LHLD BOOT+1 ; Points to BIOS jump TABLE+3
LXI D,WBOOT ; Where we will keep a copy
MVI B,16*3 ; Move 48 bytes and fall thru to move
JMP MOVE
;.....
;
GETFN: PUSH D ; Fill target FCB
MVI B,11 ; 11 bytes
MVI A,' ' ; Space fill
GETFN0: STAX D ; Put space
INX D
DCR B
JNZ GETFN0
POP D ; Point to entry again
CALL SCANCOL ; Scan for colon
MVI B,8 ; 8 characters maximum for filename
CALL GETFN1 ; Get and fill entry
MOV A,M ; Get character
CPI '.' ; Delimimter between name and extent?
RNZ ; Done
INX H ; Point to after period
MVI B,3 ; 3 characters maximum and do it again
GETFN1: MOV A,M ; Get character
CPI '.' ; End of field?
JZ GETFN3
CALL DELCHK ; Check delimiter
RZ
CPI '*' ; Wild?
JZ GETFN4
STAX D ; Store character
INX H ; Point to next
INX D
DCR B ; Count down
JNZ GETFN1
;
GETFN2: MOV A,M ; Flush characters to the delimiter
CALL DELCHK ; Check for delimiter
RZ
INX H ; Point to next
JMP GETFN2
GETFN3: INX D ; Point to 'after' field
DCR B ; Count down
JNZ GETFN3
RET
GETFN4: MVI A,'?' ; Fill with question marks
STAX D
INX D
DCR B
JNZ GETFN4
JMP GETFN2 ; Skip to the delimiter
;.....
;
; Check for help request
;
HELPCHK:LDA FCB+1 ; Get 1st byte of filename
CPI ' ' ; Make sure it is non-blank
JZ HELP
CPI '?'
RNZ
LDA FCB+2
CPI ' '
RNZ
;.....
;
; Compares the entry pointed to by the pointer pointed to by HL with
; that pointed to by DE (1st level indirect addressing). On entry, HL
; and DE contain the numbers of the elements to compare (1, 2, ...). On
; exit, carry set means ((DE)) < ((HL)), zero set means ((HL)) = ((DE)),
; and non-zero and no-carry means ((DE)) > ((HL))
;
ICOMPARE:
PUSH H ; Save HL
LHLD ORDER ; Address of order - 2
MOV B,H ; In BC
MOV C,L
POP H
DCX H ; Adjust index to 0...n-1 from 1...n
DAD H ; Double the element number
DAD B ; Add to this the base address
XCHG ; Result in DE
DCX H ; Adjust index to 0...n-1 from 1...n
DAD H ; Do the same with the original DE
DAD B
XCHG
;
; HL now points to the pointer whose index was in HL to begin with. DE
; now points to the pointer whose index was in DE to begin with. For
; example, if DE=5 and HL=4, DE now points to the 5th pointer and HL to
; the 4th pointer.
;
MOV C,M ; BC is points to the object indexed to
INX H ; By the original HL
MOV B,M
XCHG
MOV E,M ; DE is points to the object indexed to
INX H ; By the original DE
MOV D,M
MOV H,B ; HL=object pointed to indirectly by BC
MOV L,C
JMP CMP$ENTRY
;.....
;
; Swap (exchange) the pointers in the order table whose indexes are in
; HL and DE.
;
ISWAP: PUSH H ; Save HL
LHLD ORDER ; Address of order table - 2
MOV B,H ; In BC
MOV C,L
POP H
DCX H ; Adjust index to 0...n-1 from 1...n
DAD H ; HL points to offset address
DAD B ; HL now points to pointer involved
XCHG ; De now points to pointer indexed by HL
DCX H ; Adjust index to 0...n-1 from 1...n
DAD H ; HL points to offset address
DAD B ; HL now points to pointer involved
MOV C,M ; Exchange pointers -- get old (DE)
LDAX D ; -- get old (HL)
XCHG ; Switch
MOV M,C ; Put new (HL)
STAX D ; Put new (DE)
INX H ; Point to next byte of pointer
INX D
MOV C,M ; Get old (HL)
LDAX D ; Get old (de)
XCHG ; Switch
MOV M,C ; Put new (de)
STAX D ; Put new (hl)
RET
;.....
;
; General purpose move routine from HL to DE for count of 8
;
MOVE: MOV A,M ; Get a byte
STAX D ; Put a byte
INX D ; Increment to next
INX H
DCR B ; Count down
JNZ MOVE
RET
;.....
;
MOVFL: CALL PRINT
DB CR,LF,'Aborting, not enough memory for buffers',0
JMP EXIT
;.....
;
; Advance to next disk
;
NXTDISK:LXI B,TBUFF ; Set DMA address
CALL SETDMA
LDA FCB
LXI H,MXDRV ; Maximum disk
CMP M ; Compare
LXI H,0
RNC
CPI SKIP1 ; Skip a drive?
JZ RETST ; Yes,if zero -- reset counters
CPI SKIP2 ; Skip a second drive?
JZ RETST ; Yes, reset counters
CPI SKIP3 ; Skip a third drive?
JZ RETST ; Yes, reset counters
JMP CONTIN ; No, continue
;...
;
; Reads next record (group of four directory entries). Returns with
; zero flag set if no more.
;
NXTREC: LHLD DIRMAX ; See if more records
MOV A,H
ORA L
RZ ; Returns zero flag if no more
LHLD TRACK ; Set track
MOV B,H
MOV C,L
CALL SETTRK
LHLD RECORD ; Set record
MOV B,H
MOV C,L
CALL TRNSLT
CALL SETREC
CALL READ ; Read a record
ANI 1 ; Reverse sense of error flag
XRI 1 ; Returns with zero flag set
RET ; If bad read
;.....
;
; Checks for S-option in command line and extracts file names into table
;
OPTCHK: XRA A ; Turn off flags
STA SYSTEM ; No system files
STA FFLAG ; No files found
STA ECOUNT ; No entries
STA FNCOUNT ; No file names
LHLD FNTAB ; Point to table
XCHG ; In DE
LXI H,TBUFF+1 ; Scan thru TBUFF, building a FN table
CALL SBLANK ; Skip blanks
OPTCK1: PUSH D ; Save table pointer
CALL GETFN ; Extract file name
POP D
PUSH H
LXI H,11 ; Point to next table entry
DAD D
XCHG
POP H
LDA FNCOUNT ; Increment count
INR A
STA FNCOUNT
MOV A,M ; Get terminating character
INX H ; Point to next
CPI ',' ; Another follows?
JZ OPTCK1
DCX H ; Point back to delimiter
CALL SBLANK ; Skip to non-blank
OPTCK2: IF USEZCPR
LDA WHEEL ; Load WHEEL byte
ORA A ; Check if set
JZ OPTCK3 ; Don't set flag if not wheel
ENDIF ; USEZCPR
IF NOT SYSFILE ; If SYSFILE is YES, show systems files
LDA WHEEL ; Load WHEEL byte
ORA A ; Check if set
JZ OPTCK3 ; Don't set flag if not wheel
ENDIF ; NOT SYSFILE
MVI A,0FFH ; Set flag
STA SYSTEM
;
OPTCK3: MOV A,M ; Get option
CALL DELCHK ; Done if delimiter
RZ
CALL PRINT
DB CR,LF,'Invalid option -- ',0
MOV A,M
CALL BOUT
JMP HELP
;.....
;
; Print register A value as 3 decimal characters
;
PA3DC: PUSH B ; Save registers
PUSH D
PUSH PSW ; Save the character
MVI D,0 ; Turn off the leading space flag
JMP PADC1
;.....
;
; Print register A value as decimal character with a leading space in a
; three-character field.
;
PADC: PUSH B ; Save registers
PUSH D
PUSH PSW
MVI D,1 ; Turn on leading space flag
;
; Print routine
;
PADC1: MVI B,100 ; Print hundreds
CALL PAC ; Print a character
MVI B,10 ; Print tens
CALL PAC
ADI '0' ; Convert to ASCII
CALL COUT ; Print
POP PSW ; Restore registers
POP D
POP B
RET
;.....
;
; Print result of division of A by B with leading space
;
PAC: MVI C,0 ; Set count
PAC1: SUB B ; Compute count
JC PAC2
INR C ; Increment count
JMP PAC1
PAC2: ADD B ; Add 'B' back in
MOV E,A ; Save 'A'
MOV A,C ; Get count
ORA A ; Zero?
JNZ PAC3
ORA D ; 0 means no leading space
JZ PAC3
MVI A,' ' ; Print a space
CALL COUT
MOV A,E ; Restore A
RET
PAC3: MVI D,0 ; D=0 For no leading space
MOV A,C ; Get count
ADI '0' ; Convert to decimal
CALL COUT ; Print it
MOV A,E ; Restore A
RET
;.....
;
; Print the string pointed to by the return address, terminated by a 0
;
PRINT: XTHL ; HL=address, old HL on stack
CALL PSTR ; Print string pointed to by HL
XTHL ; Restore HL and new return address
RET
;.....
;
; Print string pointed to by HL, affects only HL. When done, HL points
; to the byte after the string.
;
PSTR: PUSH D ; Save registers
PUSH B
PUSH PSW
MVI C,0 ; Set position count
PSTR1: MOV A,M ; Get byte
INX H ; Point to next
ORA A ; 0=done
JZ PSTR7
CPI TAB ; Expand tab
JZ PSTR5
;
; Print the character
;
INR C ; Increment position
CALL CCOUT ; Print it on the console
CPI CR
JZ PSTR2
CPI LF
JZ PSTR3
CPI BELL
JZ PSTR3
CPI BS
JZ PSTR4
JMP PSTR1
;...
;
; Reset position count
;
PSTR2: MVI C,0 ; Reset
JMP PSTR1
;
; LF, BELL, NULL, cursor did not advance
;
PSTR3: DCR C ; Back up count by 1
JMP PSTR1
;
; Backspace, cursor went backward, perhaps
;
PSTR4: MOV A,C ; Check for zero
ORA A
JZ PSTR1
DCR C ; Back up count by 2
DCR C
JMP PSTR1
;
; Expand tab
;
PSTR5: MOV A,C ; Get count
ANI 7 ; Mask for subtract from 8
MOV B,A ; Store temporarily
MVI A,8 ; Subtract from 8 for spaces count
SUB B
MOV B,A ; Count in B
ADD C ; Add to position count
MOV C,A
MVI A,' ' ; Print a space character
PSTR6: CALL COUT
DCR B ; Decrement the count
JNZ PSTR6
JMP PSTR1
;
; PSTR done
;
PSTR7: POP PSW ; Restore registers
POP B
POP D
RET
;.....
;
; Print files in DIRBUF
;
PRFILES:LHLD FCOUNT ; Get count
MOV A,H ; Any?
ORA L
RZ
CALL CKABRT ; Want to abort now?
CALL CRLF
MOV B,H ; Count in BC
MOV C,L
LHLD DIRBUF ; Point to first one
PRFLOOP:
PUSH B ; Save count
PUSH H ; Save pointer
CALL PRINTFCB ; Print FCB
POP H ; Get registers back
POP B
LXI D,12 ; Point to next
DAD D
DCX B ; Count down
MOV A,B
ORA C
JNZ PRFLOOP
MVI A,0FFH ; Set ok
ORA A ; Clear the flag
RET
;.....
;
; FCB printing routine
;
PRINTFCB:
CALL PRINT ; 2 spaces
DB ' ',0
MOV A,M ; Get user number
CALL PADC ; Print it
MVI A,':'
CALL BOUT
INX H
PR0: MVI B,8
CALL PR1
MVI A,'.'
CALL BOUT
MVI B,3
CALL PR1
LDA ECOUNT ; Increment count
INR A
STA ECOUNT
STA NEWCR
ANI 3 ; Every 4 filenames start a new line
RNZ
CALL CKABRT ; Want to abort or pause now?
CALL CRLF ; New line
XRA A
STA NEWCR
RET
;.....
;
PR1: MOV A,M
ANI 7FH
CALL BOUT
INX H
DCR B
JNZ PR1
RET
;.....
;
RETST: LDA ECOUNT ; Last new line?
ANI 3
CNZ CRLF
LXI H,0 ; Set file count
SHLD FCOUNT
XRA A ; Set count
STA ECOUNT
CMA ; Flip
ORA A ; Ok to continue
RET
;.....
;
SBLANK: MOV A,M ; Skip to non-blank
CPI ' '
RNZ
INX H
JMP SBLANK
;.....
;
SCANCOL:PUSH D ; Save table pointer
PUSH H ; Save pointer
SCOL1: MOV A,M ; Get character
INX H ; Point to next
CPI ':' ; Colon?
JZ SCOLX
CALL DELCHK ; Check for delimiter
JNZ SCOL1
SCOL2: POP H ; Restore
POP D
RET
;...
;
SCOLX: XCHG ; DE points after colon
POP H ; Get old pointer
XCHG ; Replace it
POP D ; Get table pointer
RET
;.....
;
; Shift regs HL right 2 bits logical.
;
SHFHL2: CALL SHFHL ; Rotate right 1 bit and fall thru
;
SHFHL: XRA A ; Clear carry
MOV A,H
RAR ; Shifted bit in carry
MOV H,A
MOV A,L
RAR
MOV L,A
RET
;.....
;
; SHELL SORT - This sort routine is adapted from "SOFTWARE TOOLS" by
; Kernigan and Plaugher, page 106. Copyright, 1976, Addison-Wesley.
; On entry, BC=number of entries and HL=address of first entry.
;
SORT: XCHG ; Pointer to directory in de
LHLD ORDER ; Pt to order table
;
; Set up order table; HL points to next entry in order table, DE points
; to next entry in directory, BC = number of elements remaining
;
SORT1: MOV M,E ; Store low-order address
INX H ; Point to next order byte
MOV M,D ; Store high-order address
INX H ; Point to next order entry
PUSH H ; Save pointer
LXI H,12 ; HL=number of bytes/entry
DAD D ; Point to next DIR1 entry
XCHG ; DE points to next entry
POP H ; Get pointer to order table
DCX B ; Count down
MOV A,B ; Done?
ORA C
JNZ SORT1
;
; This is the main sort loop for the shell sort in "SOFTWARE TOOLS" by
; Kernigan and Plaugher.
;
LHLD NUMBR ; Number of items to sort
SHLD GAP ; Initial GAP to N for 1st divide by 2
;
; For (GAP = NUMBR/2; GAP > 0; GAP = GAP/2)
;
SRTL0: ORA A ; Clear carry
LHLD GAP ; Get previous GAP
MOV A,H ; Rotate right to divide by 2
RAR
MOV H,A
MOV A,L
RAR
MOV L,A
;
; Test for zero
;
ORA H
JZ SDONE ; Done with sort if GAP = 0
SHLD GAP ; Set value of GAP
SHLD I ; Set I=GAP for following loop
;
; For (i = gap + 1; i <= n; i = i + 1)
;
SRTL1: LHLD I ; Add 1 to I
INX H
SHLD I
;
; Test for I <= NUMBR
;
XCHG ; I is in DE
LHLD NUMBR ; Get the number
MOV A,L ; Compare by subtraction
SUB E
MOV A,H
SBB D ; Carry set means I > NUMBR
JC SRTL0 ; Don't do for loop if I > NUMBR
LHLD I ; J = I initially for 1st subtr. of GAP
SHLD J
;
; For (J = I - GAP; J > 0; J = J - GAP)
;
SRTL2: LHLD GAP ; Get GAP
XCHG ; In DE
LHLD J ; Get J
MOV A,L ; Compute J - GAP
SUB E
MOV L,A
MOV A,H
SBB D
MOV H,A
SHLD J ; J = J - GAP
JC SRTL1 ; If carry from subtr. J < 0 and abort
MOV A,H ; J=0?
ORA L
JZ SRTL1 ; If zero, j=0 and abort
;
; Set JG = J + GAP
;
XCHG ; J in DE
LHLD GAP ; Get GAP
DAD D ; J + GAP
SHLD JG ; JG = J + GAP
;
; If (V(J) <= V(JG))
;
CALL ICOMPARE ; J in DE, JG in HL
JC SRTL1 ; Then break
LHLD J ; Else exchange
XCHG
LHLD JG
CALL ISWAP ; J in DE, JG in HL
;
; End of innermost for loop
;
JMP SRTL2
;.....
;
; Sort is done, restructure DIR1 in sorted order in place.
;
SDONE: LHLD NUMBR ; Number of entries
MOV B,H ; In BC
MOV C,L
LHLD ORDER ; Pointer to ordered pointer table
SHLD PTPTR ; Set pointer pointer
LHLD DIRBUF ; Pointer to unordered directory
SHLD PTDIR ; Set ppinter directory buffer
;
; Find pointer to next DIR1 entry
;
SRTDN: LHLD PTPTR ; Point to remaining pointers
XCHG ; In DE
LHLD PTDIR ; HL points to next directory entry
PUSH B ; Save count of remaining entries
;
; Find pointer table entry
;
SRTDN1: LDAX D ; Get current pointer table entry value
INX D ; Point to high-order pointer byte
CMP L ; Compare against DIR1 address, low
JNZ SRTDN2 ; Not found yet
LDAX D ; Low-order bytes match, get high-order
CMP H ; Compare against DIR1 address, high
JZ SRTDN3 ; Match found
;
SRTDN2: INX D ; Point to next pointer table entry
DCX B ; Count down
MOV A,C ; End of table?
ORA B
JNZ SRTDN1 ; Continue if not
JMP FERR$PTR
;.....
;
; Found the pointer table entry which points to the next unordered DIR1
; entry make both pointers (pointer to next, pointer to current unorder-
; ed DIR1 entry). Point to same location (pointer to next DIR1 entry to
; be ordered)
;
SRTDN3: LHLD PTPTR ; Get pointer to next ordered entry
DCX D ; DE points to low-order pointer address
MOV A,M ; Make pointer to next unordered DIR1
STAX D ; DIR1 entry to be moved to next DIR1
INX H ; Point to next pointer address
INX D
MOV A,M ; Make high point similarly
STAX D
;
; Copy next unordered dir1 entry to hold buffer
;
MVI B,12 ; B=number of bytes/entry
LHLD PTDIR ; Point to entry
LXI D,HOLD ; Point to hold buffer
PUSH B ; Save B=number of bytes/entry
CALL MOVE
POP B
;
; Copy to-be-ordered DIR1 entry to next ordered DIR1 position
;
LHLD PTPTR ; Point to its pointer
MOV E,M ; Get low-address pointer
INX H
MOV D,M ; Get high-address pointer
LHLD PTDIR ; Destination address for next DIR1
XCHG ; Hl points to entry to be moved
PUSH B ; Save B=number of bytes/entry
CALL MOVE
POP B
XCHG ; HL pts to next unordered DIR1 entry
SHLD PTDIR ; Set pointer for next loop
;
; Copy entry in hold buffer to location previously held by latest order-
; ed entry.
;
LHLD PTPTR ; Get 'pntr to ptr' to the destination
MOV E,M ; Get low-address pointer
INX H
MOV D,M ; High-address pointer
LXI H,HOLD ; HL points to hold buffer
CALL MOVE ; B=number of bytes/entry
;
; Point to next entry in pointer table.
;
LHLD PTPTR ; Pointer to current entry
INX H ; Skip over it
INX H
SHLD PTPTR
;
; Count down
;
POP B ; Get counter
DCX B ; Count down
MOV A,C ; Done?
ORA B
JNZ SRTDN
RET ; Done
;.....
;
; Translate regs BC from logical to physical record number
;
TRNSLT: LHLD DPH ; Get pointer to DPH
MOV E,M ; Get address of XLT
INX H
MOV D,M
CALL RECTRAN ; Use BIOS routine
MOV C,L ; Return value in BC
MOV B,H
RET
;.....
; end of subroutines
;-----------------------------------------------------------------------
;
; Messages
;
CKMS1: DB 13,10,13,10,'++ ABORTED ++',13,10,'$'
CKMS2: DB 8,' ',8,'$'
;
; Say who we are
;
HELLO: CALL PRINT
DB CR,LF,'ZFILE v',(VERS MOD 10)+'0',' '
DB 'S to pause - C, K or X to abort',CR,LF,0
RET
;.....
;
; If no file name is specified, send following help guide
;
HELP: CALL PRINT
DB CR,LF,'Searches all allowed drives and user '
DB 'areas',CR,LF,'for requested files. Systems files '
DB 'included',CR,LF,'if using a WHEEL byte and it is '
DB 'set. Several',CR,LF,'files can be requested at '
DB 'the same time:',CR,LF,CR,LF
DB 'A>FILE FILE1*.*,FILE2*.*,FILE3*.*(,etc.)'
DB CR,LF,CR,LF,CR,LF,0
JMP EXIT
;.....
;
; Sort buffers
;
DIRBUF: DS 2 ; Pointer to directory
DSTART: DS 2 ; Pointer to first directory entry
FCOUNT: DS 2 ; Total # of files/# of selected files
GAP: DS 2 ; Binary GAP size
HOLD: DS 12 ; Exchange hold buffer for FCB's
I: DS 2 ; Indexes for sort
J: DS 2
JG: DS 2
NUMBR: DS 2 ; Number of elements to sort
ORDER: DS 2 ; Pointer to order table
PTPTR: DS 2 ; Pointer pointer
PTDIR: DS 2 ; Directory pointer
;.....
;
; This is the working copy of the BIOS jump table
;
WBOOT: DS 3
CONST: DS 3
CONIN: DS 3
CONOUT: DS 3
LIST: DS 3
PUNCH: DS 3
READER: DS 3
HOME: DS 3
SELDSK: DS 3
SETTRK: DS 3
SETREC: DS 3
SETDMA: DS 3
READ: DS 3
WRITE: DS 3
LISTST: DS 3
RECTRAN:DS 3
;.....
;
; Data areas
;
CLPFLG: DS 1 ; 0 for no match locally
DIRMAX: DS 2 ; Number of records in directory
DPH: DS 2 ; Address of DPH
ECOUNT: DS 1 ; Count of entries printed - 1
EXTENT: DS 1 ; Extent mask
FFLAG: DS 1 ; File found flag (0=no)
FNCOUNT:DS 1 ; Number of file names found
FNTAB: DS 2 ; File name table
MAXREC: DS 2 ; Maximum number of records/track
NEWCR: DS 1 ; To finish with a new line
RECORD: DS 2 ; Current sector number
SCRATCH:DS 2 ; Scratch area
SYSTEM: DS 1 ; 0 if no system files
TEMP: DS 2 ; Temporary storage for FCB print
TRACK: DS 2 ; Track number of directory
;.....
;
DS 64 ; Minimum stack depth
ORG ($+127)/128*128
BUFTBL EQU $
STACK EQU BUFTBL-2
;.....
;
END