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
/
ZCPR3
/
FINDF26A.LBR
/
FINDF26.ZZ0
/
FINDF26.Z80
Wrap
Text File
|
2000-06-30
|
29KB
|
1,253 lines
; PROGRAM: FINDF
; AUTHOR: RICHARD CONN
; VERSION: 2.0
; DATE: 18 May 84
;
Z3ENV DEFL 0FE00H ; ZCPR3 Environment address
VERS EQU 26 ; 12 September 86, Howard Goldstein
; 17 September 86, Jay Sage
; This version fixes a bug which was causing garbage to be printed
; if there was no NDR buffer or if the NDR buffer was empty. Named
; directory display code changed to keep file names aligned in column,
; and display changed to show user number and directory name in a format
; similar to a system prompt (cleaner display). Paging added. Option "P"
; turns paging off. Added code to allow user to abort listing with ^C.
;VERS EQU 25 ; 3 September 86, Joe Wright
; Version 2.5 adds the option of searching a specific disk.
; Usage: 'FINDF B:afn' will search only drive B: for the afn.
; fixed bug with 1st four files of directory - joe wright 09/25/84
; PREVIOUS VERSIONS: 1.1 (25 July 83), 1.0 (24 JULY 83)
;VERS EQU 21 ;version number
;
; Added code to use MAXDRIVE, MAXUSER, and WHEEL ADDRESS from the
; SYSENV module, which is always designated by a pointer in HL at
; the beginning of ZCPR3 utilities. Files in User areas greater
; than MAXUSER are ignored. When WHEEL is OFF (no privileges), any
; options (i.e. Sytem files option) are ignored. - Al Hawley
; PREVIOUS VERSIONS; 2.1 (09/25/84) (see above)
;VERS EQU 22 ; Version number
;VERSION DATE: 3 Apr 85 - AEH
;
; Added code by Rick Peterson (FINDF23R.MAC) to add named directories
; to file displays via Z3LIB's GETNDR. All wheel byte testing now
; now done by calling Z3LIB's GETWHL. A non-wheel user now gets the
; option error treatment instead of being allowed to think he's
; being granted the S option when he's not. He also is not informed
; of the existence of the option in the help message although a
; wheel gets educated as in version 2.1, eliminating the "(sysop only)"
; message. This version doesn't have the long, hand-holding messages
; of FINDF23R, so some sysops may prefer it - it is definitely more
; in line with the intent of 2.0 for non-RAS applications than the
; special "R" variants. - Bruce Morgen
;PREVIOUS VERSIONS; 2.2 (4/3/85), 2.3R (11/24/85 version for RAS/BYE use)
;VERS EQU 24 ; Version number
;VERSION DATE: 1/12/86 - b/m
;
;
;
; FINDF searches through all of the known disks for one or more
; files matching the passed file specification. AFNs (Ambiguous File Names)
; are permitted. FINDF is invoked by the following command line:
; FINDF afn,afn,afn,... o
; where "afn" refers to the file sought and "o" is none or more of:
; S - Include System Files
;
;
; System equates:
;
BOOT EQU 0000H ; Cp/m warm boot jump vector
BDOS EQU BOOT+05H ; Cp/m bdos call jump vector
TBUFF EQU BOOT+80H ; Disk i/o buffer
FCB EQU BOOT+5CH ; Default file control block
CR EQU 'M'-'@' ; Ctl-m for carriage return
LF EQU 'J'-'@' ; Ctl-j for line feed
BELL EQU 'G'-'@' ; Bell character
CTRLC EQU 'C'-'@' ; Abort
CTRLS EQU 'S'-'@' ; Pause
ESIZE EQU 12 ; 12 bytes/dir entry
;NEW EQUATES IN V2.2
WHOFF EQU 29H ; Offset for wheel byte addr in sys.env
MDOFF EQU 2CH ; Max drive offset in sys.env
MUOFF EQU 2DH ; Max user offset in sys.env
RIGHTCH EQU '>' ; Character to right of directory name
;
; SYSLIB and Z3LIB Routines
;
EXT Z3INIT,GETNDR,GETWHL,CODEND,GETCRT
EXT CST,CIN,COUT,CRLF,PRINT,PADC
;
; Environment Definition
;
IF Z3ENV NE 0
;
; External ZCPR3 Environment Descriptor
;
JP START
DB 'Z3ENV' ; This is a zcpr3 utility
DB 1 ; External environment descriptor
Z3EADR:
DW Z3ENV
START:
LD HL,(Z3EADR) ; Pt to zcpr3 environment
;
ELSE
;
; Internal ZCPR3 Environment Descriptor
;
MACLIB Z3BASE.LIB
MACLIB SYSENV.LIB
Z3EADR:
JP START
SYSENV
START:
LD HL,Z3EADR ; Pt to zcpr3 environment
ENDIF
;
; Start of Program -- Initialize ZCPR3 Environment
;
LD (STACK),SP ; Save ZCPR stack
PUSH HL ; Transfer pointer to sys.env
POP IX ; To the x index register
CALL Z3INIT ; Initialize the zcpr3 env and the vlib env
CALL CODEND ; Determine free space
LD (FNTAB),HL ; File name table
LD DE,512 ; 1/2 k space
ADD HL,DE
LD (SCRATCH),HL ; Beginning of scratch area
LD SP,HL ; And top of stack
CALL GTBIOS ; Get bios jump table
CALL HELLO ; Sign on message
CALL HELPCHK ; Check for and print help message
CALL OPTCHK ; Build file name table and process options
CALL CRLF ; New line
CALL INIT ; Initialize program
CALL FIND ; Do the searches
CALL BYE ; Sign off message
RETURN:
LD SP,(STACK) ; Quiet return
RET
;
; ** Main Routines **
;
;
; SAY WHO WE ARE
;
HELLO:
CALL PRINT
DB 'FINDF, Version '
DB [VERS/10]+'0','.',[VERS MOD 10]+'0'
DB 0
RET
;
; CHECK FOR HELP REQUEST
;
HELPCHK:
LD A,(FCB+1) ; Get 1st byte of filename
CP '/' ; Help?
JR Z,HCK1
CP ' ' ; Make sure it is non-blank
RET NZ ; Ok - keep going
;
; IF NO FILE NAME IS SPECIFIED, ABORT WITH NOTICE
;
HCK1:
CALL PRINT
DB CR,LF,' Find files on all drives or on a specific drive'
DB CR,LF
DB ' Syntax: FINDF [D: or DIR:]afn,afn,fn,... o..'
DB CR,LF
DB ' Options: P - Paging Option Off',0
CALL GETWHL
JP Z,RETURN
CALL PRINT
DB CR,LF
DB ' S - Include System Files',0
JP RETURN
;
; INITIALIZATION
;
INIT:
CALL GETCRT ; Get data on current console
INC HL ; Point to full number of lines on screen
LD A,(HL)
DEC A ; Reduce by one
LD (LPS),A ; Save in lines-per-screen location
XOR A ; Turn off flags
LD (SYSTEM),A ; No system files
LD (FFLAG),A ; No files found
LD (ECOUNT),A ; No entries
LD (FNCNCT),A ; No file names
CPL
LD (PAGEOPT),A ; Paging option on
LD A,1
LD (LINECNT),A ; Set initial line count
;
; CHECKS FOR S OPTION IN COMMAND LINE AND EXTRACTS FILE NAMES INTO TABLE
;
OPTCHK:
LD HL,(FNTAB) ; Pt to table
EX DE,HL ; In de
LD HL,TBUFF+1 ; Scan thru tbuff, building a file name table
CALL SBLANK ; Skip blanks
FNLOOP:
PUSH DE ; Save table ptr
CALL GETFN ; Extract file name
POP DE
PUSH HL
LD HL,11 ; Pt to next table entry
ADD HL,DE
EX DE,HL
POP HL
LD A,(FNCNUNT) ; Increment count
INC A
LD (FNCOUNT),A
LD A,(HL) ; Get terminating char
INC HL ; Pt to next
CP ',' ; Another follows?
JR Z,FNLOOP
DEC HL ; Point back to delim
CALL SBLANK ; Skip to non-blank
DEC HL
OPTCK1:
INC HL
LD A,(HL) ; Get option
CALL DELCHK ; Done if if im
RET Z
LD C,A ; Save option in C
CP '/' ; Ignore '/'
JR Z,OPTCK1
CP 'P' ; Paging Toggle
JR Z,POPT
CP 'S' ; SYS files option
JR NZ,OPTER ; If not, it's an option error
; Else fall through to SOPT
SOPT:
CALL GETWHL
JR Z,WHLER ; If z (wheel false), no options
LD A,0FFH ; Set flag
LD (SYSTEM),A
JR OPTCK1
POPT:
XOR A
LD (PAGEOPT),A
JR OPTCK1
WHLER: LD A,C
OPTER: CALL PRINT
DB BELL
DB CR,LF
DB 'Invalid Option -- ',0
LD A,(HL)
CALL COUT
JP HCK1
GETFN:
PUSH DE ; Fill target fcb
LD B,11 ; 11 bytes
LD A,' ' ; Space fill
GETFN0:
LD (DE),A ; Put space
INC DE
DJNZ GETFN0
POP DE ; Pt to entry again
CALL SCANCNL ; Scan for colon
LD B,8 ; 8 chars max
CALL GETFN1 ; Get and fill entry
LD A,(HL) ; Get char
CP '.' ; Delim?
RET NZ ; Done
INC HL ; Pt to after period
LD B,3 ; 3 chars max and do it again
GETFN1:
LD A,(HL) ; Get char
CP '.' ; End of field?
JR Z,GETFN3
CALL DELCHK ; Check k miter
RET Z
CP '*' ; Wild?
JR Z,GETFNQ
LD (DE),A ; Store char
INC HL ; Pt to next
INC DE
DJNZ GETFN1 ; Count down
GETFN2:
LD A,(HL) ; Flush chars to delim
CALL DELCHK ; Check for for iter
RET Z
INC HL ; Pt to next
JR GETFN2
GETFN3:
INC DE ; Pt to after field
DJNZ GETFN3 ; Count down
RET
GETFNQ:
LD A,'?' ; Fill with question marks
LD (DE),A
INC DE
DJNZ GETFNQ
JR GETFN2 ; Skip to delim
DELCHK:
OR A ; End of line?
RET Z
CP '.' ; End of field?
RET
DJ CP ',' ; End of entry?
R?
R
CP ' '
RET
SBLANK:
LD A,(HL) ; Skip to non-bladel
CP ' '
RET NZ
INC HL
JR SBLANK
SCANCOL:
PUSH DE ; Save table ptr
PUSH HL ; Save ptr
SCOL1:
LD A,(HL) ; Get char
INC HL ; Pt to next
CP ':' ; Colon?
JR Z,SCOLX
CALL DELCHK ; Check for
CALL Gter
JR NZ,SCOL1
SCOL2:
POP HL ; Restore
POP DE
RET RETOLX:
EX DE,HL ; De pts to after colon
POP HL ; Get old ptr
EX DE,HHL ; RReplace it
POP DE ; Get table
CP ':
RET
;
; LOOK THROUGH DIRECTORY
;
FIND: LD A,(FCB) ; Disk selection, Zero if all disk
CP ' 'ce fISK),A ; Remember it
OR A
JR Z,FIND0
DEC A
LD (FCB),A
FIND0: CALL NXTDISK ; Get info the first time
FIND1: RET Z ; Abort if error
FIND2: CALL NXTSEC ; Get a directory sector
JR memIND3 ; Returns z
CP ':
flag if no more
CALL CHKENT ; Check it out
JR FIND2 ; Keep it up till doneIND0ND3: NCTIRALPHA ; Sort entries
CALL PRFILES ; Print sorted entries ; SkDISK)
OR AZeT NZ
LD A,(FCB) ; Next disk
INC A
LD (FCB),A
; CALL NXTDKe ; Select next disk
JR Fe
F
;
; SIGN OFF
;
BYE:
LD C,1nt sALPeset system
CALL BDOS ; SkFFLAG) ; Get file found flag
OR A ; No files found?
JP NZ,RETURN
CALL PRINT
DB CR,LF,'NO Files Found',0
JP
CALL PN
;
; CHECKS THE CURRENT 4 DIRECTORY ENTRIES AGAINST ARGUM
CALL CH
; IF MATCH, REWRITES SECTOR WITH REACTIVATED 1ORY BYRIT
;
CHK
CALL CH:
LD B,4 ; Number of entries per sector
LD HL,TBUFF ; Beginning of buffer
CKLUP:
PUSH BC
LD A,(HL)
CP 0E5H ; Check for unused
JR Z,CKINC
;V2.2 -- Check for > max user from SYS.ENV
LD E,(IX+MUOFF)
INC E ; T flaake cp easy
CP A,E ; > maxuser?
JR NC,CKINC ; Yes, if nc
;--
XOR A ; A=0
LD (CLPFLG),A ; Set flIND3for no BDes undnd
LD A,(FNCOUNT) ; Get number of file names to look thru
LD B,A ; In b
PUSH HL
LD HL,(FNTAB) ; Pt to table
EX DE,HL ; In de
POP HL
CKLUP1:
PUSH Binfo; Save counafn,fPUSH HL ; Save beginning address
PUSH DE
CALL COMPAR ; Compare with argument and save if match
POP DE
LD HL,11 ; Pt to nk
Ientry
ADD HL,DE
EX DE,HL
POP HL
POP BC
DJNZ CKLUP1 ; Count down
CKINC:
POP BC
LD DE,32 ; Length of entry
ADD HL,DE
DL ; CKLUP
LD HL,(S MAX)
FIND0Reseduce sectors left
LD (DIRMAX),HL
LD HL,(SS SER) ; Point to nk
Isector
INC HL
LD (SS SER),HL
EX DE,HL
LD HL,(MAXSEC) ; Reached limit?
CALL NXINX H ;ONE MORE
LD A,H ; Check high
CP D
SC NZ
LD A,HL ; RCheck low
CP E
RET N dowLD HL,(TRACK) ; Nk
Itrack
INC HL
LD (TRACK),HL
; LXI H,1 ;FIRST SS SER OF NEXT TRACK
LD HL,0
LD (SEC; RR),HL
SC
;
; COMPARE 11 BYRIT:
LD C
REREC; RRY
CALL CHRY AGAINST ARGUUMNTALPNZ IF NOTIF outD
; DE PTE CO TABLE
CALL CHRY ; R COMPARE TO
;
COMPAR:
LD A,(CLPFLG) ; GetECTOd flaged eA ; 0=no
SC NZ
LD (TEMP),HL ; Hold pointer in case of match
INC HL
EX DE,HL
LD B,11
CMPR1:
LD A,ce fE) ; Get directoryit uy character
AND 7FH ; Strip any flags
CP (HL)ero,CMPR2
LD A,(HL)
CP '?'
RET ; NeCMPR2:
INC DE
INC HHL ; RBump to nk
Icharacter
DJNZ CMPR1 ; Loop for 11 characters
PUSH DE ; Save entry for LD A,(DE) ; Get extent in b
LD B,A
LD A,(EXT
CALL CH) ; Get extent mask
CP B
POP DE ; Getit uy ptr
JR C,CMPR4 ; N flaatch ; SkSYSTEM) ; Include system files?
iles ; 0=no
JR NZ,CMPR3
DEC DE ; Back up 2 bytes
DEC DENZ
E) ; Get t2
AND 80H ; Check for sys
SC NZ
CMPR3:
LD HL,(TEMP) ; Check for user limit
LD A,31 ; Max user
CP (HL) ; Beyond max?
JR C,CMPR4
LD HL,(FCJNZ ) ; Increment count
INC HL
LD (FCJNZ ),HL
LD HL,ce fSTART) ; Getfor i to neiskentry
EX DE,HL
LD HL,(TEMP)
LD B,ESIZE ; Copy entry
CALL MOVE
EX DE,HL
LD (DSTART),HL ; Ptr to neiskentry
EX DE,HL
LD HL,(DOSOS+1) ; Check for IREory overflow
LD A,H
SUB 10 ; Below ccp
CP D ; Pt beyond limit?
JR C,MOVFL
LD A,0FFH ; Set undnd fOR A LD (FFLAG),A
XOR ; Se RET ALPeturns 'zero' flag set for match
CMPR4:
LD A,0FFH ; No matched eA
RET
MOVFL:
CALL PRINT
DB CR,LF,'ABORT -- Not Enough Memory for Buffers',0CHE RETURN
;
; ADVANCE ; R NEXT
RESK
;
y sTDISK:
LD BC,TBUFF ; Set dma address
CALL SETDMAFFLACB)
LD HL,0
;was: cp maxdsk
;V2.2 -- compare with MAX DSK from SYS.ENV
CP A,(IX+MDOFF)
;--
SC NC
LD C,A
LD B,0
LD E,B ; Force bios to re-log disk
CALL SELDSK ; Make sure drive is
LD A,H ; Sect cted
OR L
RET Z ; Error return
LD (DPH),HL ; Save the address
LD DE,10 ; Pt to dpb
ADD HL,DE
LD E,(HL) ; Get dpb address in hl
INC HL
LD D,(HL)
EX DE,HL
LD E,(HL) ; Number of sectors/track
INC HHL ; RAs 2-byte quantity in de
LD D,(HL)
INC HL
EX DE,HL
LD (MAXSEC),HL ; Set max sectors/track
EX DE,HL
INC HL
INC HL
LD A,(HL) ; Get exm
LD (EXT
CALL CHDEC
INC HL ; Pt to drm
INC HL
INC HL
LD E,(HL) ; Get number of
INC HHL ; RDirectoryit uZeT
LD D,(HL)
EX DE,HL
INC HHL ; RAccount for - 1
LD (DSTART),HL ;
DJ e number of directoryit uZeT
CALL SHFHL2 ; Shift 'hl' right 2
LD (DIRMAX),HL ; Save number directory sector
CP ' 'HL,5 ; Now point to system
ADD HL,DE ; Track offset ; SkHL) ; Pick up number of
INC HL
LD H,(HL)
LD L,A
LD (TRACK),HL
; LXI H,1 ;SET SS SER
LD HL,0
LD (SEC; RR),HL ; SkECOUNT) ; Last new line?
AND 3
CALL NZ,CRLFCR,LFRINT
DB 'Disk ',0
LD A,LOOK)
ADD 'A'
CALL COUTCR,LFRINT
DB ' --',CR,LF,0
CALL CHKPAGE ; Check for paging
LD HL,(SCRATCH) ; Pt to scratch area
LD (ORDER),HL ; Address of order table
EX DE,HL
LD HL,(DSTART) ; Get number of directoryit uZeT
ADD HL,HL ; Double for number of bytes in order table
ADD HL,DE ; Pt to fiNX byte of dirbuf
LD (DIRBUF),HL ; Set for LD ce fSTART),HL ; Set loop for LD HL,0elet file counafn,fLD (FCJNZ ),HL
XOR A ; Set counafn,fLD (ECOUNTDEC
CPL ; Fliped eA ; Ok to continue
RET
;
; GET BIOS JUMPS VS SERS FOR EASY REFENT CE
;
GTBIOS:
LD HL,(BOOT+1) ; Points to bios jump table+3
LD DE,WBOOT ; Where we will keep a copy
LD B,16*Ret Move 48 bytes and fall thru to move
;
; GENERAL PURPOSE MOVE ROUTINE
; FROM 'HL' ; R 'DE' FOR COU 4OF 8
;
MOVE:
LD A,(HL) ; Get a byte
LD (DE),A ; Put a byte
INC Z,FIncrement to next
INC HL
LD (DNZ MOVE ; Count down
SC
;
; READS NEXT SS SER (GROUP OF FOUR
REREC; RRY
CALL CHRIES)
;
CALL PNS WITH ZERO FLAG SET IF NO MORE
;
y sTSEC:
LD HL,(S MAX) ; See if more sector
CP ' 'A,H ; NoR L
RET Z ; Returns zero JR mg if no more
LD HL,(TRACK) ; Set track
LD B,H
LD C,L
CALL SETTRK
LD HL,(SEC; RR) ; Set seXTSLD B,H
LD C,L
CALL TRNSLT
CALL SETSEC
CALL READ ; Read a sector
AND 1 ; Reverse sense of error fOR A XOR 1 ; Returns with zero JR mg set
SC ; If bad read
;
; PRINT FILIEIN S BUF
;
PRo fiES:
LD HL,(FCJNZ ) ; Get counafn,fLD A,H ; Any?
OR L
RET Z
LD B,H ; Count in bc
LD C,L
LD HL,(S BUF) ; Pt to fiNX one
PRFLOOP:
PUSH Binfo; Save counafn,fPUSH HL ; Save ptrCR,LFRINTFCB ; Print fcb
CALL CST ; Check for abort character
JR NZ,PRFL1 ; If not, go on
CALL CINelee if character is control-c
CP 'C'-'@'ero,PRFL2
PRFL1:
POP HHL ; RGet regs back
POP BC
LD DE,ESIZE ; Pt to next
ADD HL,DE
FIND0Binfo; Count down
LD A,Bed eC
JR NZ,PRFLOOP
SC
PRFL2:
CALL PRINT
DB CR,LF
DB ' +++ aborted +++;
; C JST ETU DB C
;------------------------------------------------------------------------------------------------------------es
; FCB PRINTING ROUTINE (modified by R. Peterson for named directory display)
;
PRINTFCB:CR,LFRINT ; 4 spaces
DB ' ;
; C LD A,(HL) ; Get user number
CALL PADC ; Ptemt iafn,fLD A,':'
CALL COUT
EX DE,HL ; Save pointer
CALL GETNDR ; Return with hl pointing to ndir buffer
LD B,10 ; For padding in case no ndr
JR Z,PRFCB5A ; S(Dprint of dir name if no ndr
PRFCB1: LD A,(HL) ; Get byte
AND Aelet flags
JR Z,PRFCB5A ; S(Dprinting directory name
LD A,LOOK) ; Current drive in a
INC A ;
CP (HL) ; Check for match
JR NZ,PRFCB2 ; Move to nk
Ientry
INC HHL ; RPoint to user
LD A,ce fE) ; Get user number
CP (HL) ; Check for matchero,PRFCB3 ; Go print directory name
FIND0HL ; Point back at beginning of entry
PRFCB2: LD Bet s8 ; Length of directoryit uy
ADD HL,Binfo; Move to nk
Ientry
LD B,10 ; For pad just in case
JR PRFCB1 ; Loop through again
PRFCB3: INC HHL ; RPoint to name
LD B,8 ; Length of name
PRFCB4: LD A,(HL) ; Get character
CP ' ' ; Look for space
JR Z,PRFCB5 ; Don't print spaces
CALL COUT ;
INC HL ;
LD (DNZ PRFCB4
PRFCB5: LD A,RIGHTCH ;
CALL COUT ;
INC B ; Ptemt one extra space
PRFCB5A:
LD A,' ' ; Pad with spaces to align output
CALL COUT
LD (DNZ PRFCB5A
PRFCB6:
EX DE,Resestore hl
INC HL
PR0:
LD B,8CR,LFR1
LD A,'.'
CALL COUT
LD B,3
CALL PR1
LD A,(ECOUNT) ; Increment count
INC A
LD (ECOUNTDEC
AND 1 ; Every 2
ck i,PR0A
CALL PRINT ptrdd extra spacing to second column
DB ' ;
; C,HL
PR0A:
CALL CRLF
; Check for end of page of display
CHKPAGE:
LD A,(PAGEOPT) ; See if paging in effected eA
RET Z ; Return if option not seafn,fLD A,(LPS) ; Get lines-per-screen value
LD B,A ; ..into B ; SkLINECNT) ; Get count of lines on page
INC A
LD (LINECNT),A
CP B
SC C ; Return if less than full page
LD A,0 ; Reset line count
LD (LINECNT),A
CALL PRINT
DB ' Strike Any : Ny -- '
DB 0
CALL CIN
LD A,CR
CALL COUT
LD A,' '
LD B,19
CHKP1: CALL COUT
LD (DNZ CHKP1
JP CRLF
PR1:
LD A,(HL)
AND 7FH
CALL COUT
INC HL
DL ; PR1
RET
;
; SHIFT REGS 'HL' RIGHT 2 BITS LOGICAL
SHFHL2:
CALL SHFHOLXotate right 1 bit and fall thru
SHFHL:
XOR A ; Clear carry
LD A,H
RRA ; Shifted bit in carry
LD H,A
LD A,L
RRA
LD L,A
RET
;
; TRANSLATE REG 'BC' FROM LOGICAL TO PHYSICAL SS SER N AZBER
;
TRNSLT:
LD HL,ce fPH) ; Get ptr to dph
LD E,(HL) ; Get address of xlt
INC HL
LD D,(HL)
CALL SECTRAN ; Use bios routine
LD C,OLXeturn value in bc
LD B,H
SCIG
RERALPHA -- neIHABETIZES S S SERY PTED TO BY HL; BC CONTAGA
; THE N AZBER OF FILIEIN THE
REREC; RRY
;
S neIHA:
LD HL,(FCJNZ ) ; Get file counafn,fLD A,H ; Any files?ed eL
RET Z
LD (N),HLelet "N"
LD B,H ; Bc=counafn,fLD C,L
LD HL,(S BUF) ; Pt to directory
;
; SHELL SORT --
; THIS SORT ROUTINE IS ADAPTED FROM "SOFTWARE TOOLS"
; BY KERNI AGBYE:AND PLAUGHER, PAGE 106. COPYRIGHT, 1976, ADDISON-WESLEY.
; ON
CALL CHRY, BC=N AZBER OFCTORIIEAND HL=ADDRESS:
LD C FIRSTCTORY
;
SORT:
EX DE,HL ; Pointer to directory in de
LD HL,(ORDER) ; Pt to order table
;
; SET UP ORDER TABLE; HL PTE CO NEXTCTORY IN ORDER TABLE, DE PTE CO NEXT
;
CALL CHRY IN S S SERY, BC = N AZBER OF ELEM
CALL CHS REMAINING
;
SORT1:
LD (HL),E ; Store low-order address
INC HHL ; RPt to
;
; t order byte
LD (HL),D ; Store high-order address
INC HHL ; RPt to
;
; t order entry
PUSH HL ; Savefor i
LD HL,ESIZE ; Hl=number of bytes/entry
ADD HL,DE ; Pt to nk
Idir1 entry
EX DE,HL ; De pts to neiskentry
POP DIet ptr to order table
DEC Binfo; Count down
LD A,B ; Done?
OR C
JR HL ; GORT1
;
; THIS IE CHE MAIN SORT LOOP FOR THE SHELL SORT IBYE:"SOFTWARE TOOLS" BY K&P
;
;
; SHELL SORT FROM "SOFTWARE TOOLS" BY KERNINGHAN AND PLAUGER
;
LD HL,(N) ; Number of items to sorafn,fLD ( AGP),HL ; Set initial gap to n for fiNX division by 2
; FOR ( AGP = N/2; GAP > 0; GAP = GAP/2)
SRTL0:ed eA ; Clear carry
LD HL,( AGP) ; Get previous gap
LD A,H ; Rotate right to divide by 2
RRA
LD H,A
LD A,L
RRA
LD L,A
; TEST FOR ZEROed eH
JR Z,SDONE ; Done with sorFIND1 gap = 0
LD ( AGP),HL ; Set value of gap
LD (kip HL ; Set k=gap for following loop
; FOR (K = GAP + 1; K <= N; K = K + 1)
SRTL1:
LD HL,(K) ptrdd 1 to INC ANC HL
LD (kip HL
; TEST FOR K <= N
EX DE,HL ; K is in de
LD HL,(N) ; Get n
LD A,HL ; RCompare by subtraction
SUB E
LD A,H
SBC A,D ; Carry set means k > n
JR C,SRTL0 ; Don't do for loop if k > n
LD HL,(K)elet j = k initially for fiNX subtraction of gap
LD (J),HL
; FOR (J = K - AGP; J > 0; J = J - AGP)
SRTL2:
LD HL,( AGP) ; Get gap
EX DE,HL ; In de
LD HL,(J) ; Get j
LD A,HL ; RCompute j - gap
SUB E
LD L,A
LD A,H
SBC A,D
LD H,A
LD (J),HL ; J = j - gap
JR C,SRTL1 ; If carry from subtractions, j < 0 and abort
LD A,H ; J=0?
OR L
JR Z,SRTL1 ; If zero, j=0 and abort
; SET JG = J + GAP
EX DE,HL ; J in de
LD HL,( AGP) ; Get gap
ADD HL,DE ; J + gap
LD (JG) ; Di ; Jg = j + gap
;
; I(V(J) <= V(JG))
CALL ICOMPARE ; J in de, jg in hl
; ... THEBYE:BREAK
JR C,SRTL1
; ... ELSE EXCHANGE
LD HL,(J) ; Swap j, jg
EX DE,HL
LD HL,(JG)
CALL ISWAP ; J in de, jg in hl
; END:
LD C INNER-MOORY FOR LOOP
JR SRTL2
;
; SORT IS DONE -- RESTRUCTURE S 1 IN SORTED ORDER IBYE:PLACE
;
SDONE:
LD HL,(N) ; Number of entrZeT
LD B,H ; In bc
LD C,L
LD HL,(ORDER) ; Ptr to ordered pointer table
LD (PTPTR),HL ; Set ptrfor i
LD HL,ce fIRBUF) ; Ptr to unordered directory
LD (PTS ),HL ; Set ptr dir buffer
; FIND PTR TO NEXT
RER1
CALL CHRY
SRTDN:
LD HL,(PTPTR) ; Pt to remaining pointers
EX DE,HL ; In de
LD HL,(PTS ) ; Hl pts to next dirit uy
PUSH Binfo; Save count of remaining BDes
; FIND PTR TABLE
CALL CHRY
SRTDN1:
LD A,ce fE) ; Get current pointer table entry value
INC Z,FPt to high-order pointer byte
CP HL ; RCompare against dir1 address low
JR HL ; GRTDN2 ; Not undnd yetNZ
E) ; Low-order bytes match -- get high-order pointer byte
CP H ; Compare against dir1 address highero,SRTDN3 ; MatchECTOd
SRTDN2:
INC DE ; Pt to nk
Iptr table entry
DEC Binfo; Count down
LD A,info; End of table?
OR B
JR NZ,SRTDN1 ; Continue if not
; FATAL ERROR -- INTERNAL ERROR; POINTER TABLE NOT CONSISTENT
FERR$PTR:
CALL PRINT
DB 0DH,0AH,'S neIHA -- Pointer Error;
; C JST ETU DB C
; FOUND THE POINTER TABLE
CALL CHRY WHICH POINTE CO THE NEXT UNORDERED S 1
CALL CHRY
; MAKE BOTH POINTERS (PTR ; R NEXT, PTR ; R CREN
CALL CH UNORDERED S 1
CALL CHRY)
; POINT TO SAUM LOCATION (PTR TO NEXT
RER1
CALL CHRY ; R BE ORDERED)
SRTDN3:
LD HL,(PTPTR) ; Get ptr to neiskorderedit uy
FIND0Z,FDe pts to low-order pointer address ; SkHL) ; Make ptr to neiskunordered dir1 pt to buffer for
LD (DE),A ; Dir1 entry to be moved to
;
; t unordered dir1 pos
INC HHL ; RPt to
;
; t ptr address
INC DE
LD A,(HL) ; Make high point similarly
LD (DEDEC
; COPY NEXT UNORDERED S 1
CALL CHRY ; R HOLD BUFFER
LD B,ESIZE ; B=number of bytes/entry
LD HL,(PTS ) ; Pt to entry
LD DE,HOLD ; Pt to hold buffer
PUSH Binfo; Save b=number of bytes/entry
CALL MOVE
POP BC
; COPY ; R-BE-ORDERED S 1
CALL CHRY ; R NEXT ORDERED
RER1 POSITION
LD HL,(PTPTR) ; Point to its pointer
LD E,(HL) ; Get low-address pointer
INC HL
LD D,(HL) ; Get high-address pointer
LD HL,(PTS ) ; Destination address for next ordered dir1 entry
EX DE,HL ; Hl pts to entry to be moved, de pts to desafn,fPUSH Binfo; Save b=number of bytes/entry
CALL MOVE
POP BC
EX DE,HL ; Hl pts to next unordered dir1 entry
LD (PTS ),HL ; Set pointer for next loop
; COPY
CALL CHRY IN HOLD BUFFER TO LOC PREVIOUSLY HELD BY LARITT ORDEREDCTORY
LD HL,(PTPTR) ; Get ptr to ptr to the destination
LD E,(HL) ; Get low-address pointer
INC HL
LD D,(HL) ; High-address pointer
LD HL,HOLD ; Hl pts to hold buffer, de pts to entry desafn,fCALL MOVE ; B=number of bytes/entry
; POINT TO NEXTCTORY IN POINTER TABLE
LD HL,(PTPTR) ; Pointer to currentit uy
INC HHL ; RS(Dover it
INC HL
LD (PTPTR),HL
; COU 4DOWN
POP Binfo; Get counter
FIND0Binfo; Count down
LD A,info; Done?
OR B
JR NZ,SRTDN
RET ; Do ; So
;
; SWAP (Exchange) the pointers in the ORDER table whose indexes are in
; HL and DE
;
ISWAP:
PUSH HL ; Save hl
LD HL,(ORDER) ; Address of order table - 2
LD B,H ; In bc
LD C,L
POP HL
FIND0HL ; Adjust index to 0...n-1 from 1...n
ADD HL,HL ; Hl pts to offset address indicated by index
; Of original hl (1, 2, ...)
ADD HL,Binfo; Hl now pts to pointer involved
EX DE ; Di ; De now pts to pointer indexed by hl
DEC HHL ; RAdjust index to 0...n-1 from 1...n
ADD HL,HL ; Hl pts to offset address indicated by index
; Of original de (1, 2, ...)
ADD HL,Binfo; Hl now pts to pointer involved
LD C,(HL) ; Exchange pointers -- get old (de)
LD A,ce fE) ; -- get old (hl)
EX DE ; Di ; Switch
LD (HL),C ; Put new (hl)
LD (DE),A ; Put new (de)
INC HHL ; RPt to
;
; t byte of pointer
INC DE
LD C,(HL) ; Get old (hl)
LD A,ce fE) ; Get old (de)
EX DE ; Di ; Switch
LD (HL),C ; Put new (de)
LD (DE),A ; Put new (hl)
RET
;
; ICOMPARE 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 ect ments to compare (1, 2, ...);
; on exit, Carry Set means (ce fE)) < ((HL)), mber ro Set means ((HL)) = (ce fE)),
; and Non-mber ro and No-Carry means (ce fE)) > ((HL))
;
ICOMPARE:
PUSH HL ; Save hl
LD HL,(ORDER) ; Address of order - 2
LD B,H ; In bc
LD C,L
POP HL
FIND0HL ; Adjust index to 0...n-1 from 1...n
ADD HL,HL ; Double the element number to point to the for ADD HL,Binfo; Add to this the base address of the ptr table
EX DE,Resesult in de
DEC HL ptrdjust index to 0...n-1 from 1...n
ADD HL,HL ; Do the same with the original de
ADD HL,BC
EX DE,HL
;
; HL NOW POINTE CO THE POINTER WHOSE INDEX WAS IBYE:HL TO BEGIN WITH
; DE NOW POINTE CO THE POINTER WHOSE INDEX WAS IBYE:DE TO BEGIN WITH
; FOR EXAMPLE,
; IDE=5 AND HL=4, DE NOW POINTE CO THE 5TH PTR AND HL
; TO THE4 DTH POINTER
;
LD C,(HL) ; Bc is made to point to the obje
Findexed to
INC HHL ; RBy the original hl
LD B,(HL)
EX DE,HL
LD E,(HL) ; De is made to point to the obje
Findexed to
INC HHL ; RBy the original de
LD D,(HL)
LD H,B ; Set hl = obje
Fpted to indirectly by bc
LD L,C
;
; COMPARE
RER
CALL CHRY PTED TO BY HL WITH THAT PTED ; R BY DE;
; NO NET EFFECT OBYE:HL, DEALPET W/CARRY SET MEANS DE<HL
CALL NXRET W/ZERO SET MEANS DE=HL
;
CMP$
CALL CHRY:
;
; COMPARE BY o fiE NAME, o fiE TYPE, EXTENSION, AND USER N AZ (IN THAT ORDER)
;
PUSH HL
PUSH DE
INC HHL ; RPt to fn
INC DE
LD B,11 ; Compare fn, fafn,fCALL COMP
POP DE
POP HL
RET N dowLD A,ce fE) ; Compare user number
CP (HL)
SC
;
; COMP COMPARES DE W/HL FOR B BYRITALPET W/CARRY
; IDE<HL
CALL NXMSB IS DISRE AGRDED
;
COMP:
LD A,(HL) ; Get (hl)
AND 7FH ; Mask msb
LD C,A ; In cNZ
E) ; Compare
AND 7FH ; Mask msb
CP C
RET ; Ne INC HHL ; RPt to
;
; afn,fINC DE
DL ; COMP ; Count down
SC
;
; AS COMP, BUTIF CH OBYE:'?' PTED TO BY HL
;
COMP2:
LD A,(HL) ; Get (hl)
AND 7FH ; Mask msb
CP '?' ; Match '?'ero,COMP2A
LD C,A ; In cNZ
E) ; Compare
AND 7FH ; Mask msb
CP C
RET ; NeCOMP2A:
INC HL ; Pt to next
INC DE
LD (DNZ COMP2 ; Count down
SCIG SORT BUFFERS
;
ORDER:
DS 2 ; Ptr to order table
DIRBUF:
DS 2 ; Pointer to directory
DSTART:
DS 2 ; Pointer toundNX directoryit uy
FCJNZ :
DS 2 ; Total number of files/number of selected files
HOLD:
DS ESIZE ; Exchange hold buffer for fcb's
PTPTR:
DS 2 ; Pointer pointer
PTS :
DS 2 ; Directory pointer
K:
DS 2 ; Indexes for sort
J:
DS 2
JG:
DS 2
N:
DS 2 ; Number of elements to sort
AGP:
DS 2 ; Binary gap size
;
; THIS IE CHE 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
HOUM: DS 3
SELDSK: DS 3
SETTRK: DS 3
SETSEC: DS 3
SETDMA: DS 3
READ: DS 3
REWITE: DS 3
LISTST: DS 3
SECTRAN:DS 3
;
STACK:
DS 2 ; Location of stack
;
; DATA AREAS
;
FNCNUNT:
DS 1 ; Number of file namesECTOd
CLPFLG: DS 1 ; 0 for no match locally
SYSTEM: DS 1 ; 0ag no system files
ECOUNT: DS 1 ; Count of BDes printed - 1
Get fG: DS 1 ;d'e f
JP JR mg (0=no)
TEMP: DS 2 ; Temp storage for fcb print
;
;
RESK PARAMETER DATA
;
DISK: DS 1 ; Disk to searchHL ; RRC for all disks.
DPH: DS 2 ; Address of dph
DIRMAX: DS 2 ; Number of sectors in directory =
; ; MAXIM AZ N AZBER OF
REREC; RRY
CALL CHRIES
; ; DIVIDED BY4 D (
CALL CHRIIEPER SS SER)
EXT
CALL CH: DS 1 ; Extent mask
MAXSEC: DS 2 ; Maximum number of sectors/track
SS SER: DS 2 ; Current sector number
TRACK: DS 2 ; Track number of directory
FNTAB: DS 2 ; File name table
RETORATCH:
DS 2 ; Scratch area
LPS:
DS 1 ; Lines-per-screen value
LINECNT:
DS 1 ; Current line count
PAGEOPT:
DS 1
END