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
/
DIR14.LBR
/
DIR14.ZZ0
/
DIR14.Z80
Wrap
Text File
|
2000-06-30
|
37KB
|
1,619 lines
;
; program: dir
; author: richard conn
; version: 1.0
; date: 23 mar 84
;
vers equ 14 ; Added Print option 25 Dec 85 jww
;vers equ 13 ; Fixed fsize routine again jww
;
;vers equ 12 ;Added 'PUBLIC' support to permit
;wildcard viewing of public directories
;used by ZRDOS 1.2 dlw
;
;VERS EQU 11 ; Changed manner of calculating disk size
; Using all0 and all1 instead of drm
; Added modified dirqs and fsize jww
; Trial to list files vertically jww
;
;vers equ 10 ; release
;
month equ 1
day equ 22
year equ 86
;
z3env defl 0fe00h ; Set zcpr3 environment descriptor address
;
; equates
;
yes equ 0ffh
no equ 0
;
video equ yes ; Enhanced video?
vopt equ yes ; Print signon and vers no
vert equ yes ; List files vertically (default)
;
fcb equ 5ch
fcb2 equ 6ch
ctrlc equ 03h
cr equ 0dh
lf equ 0ah
;
; vlib, z3lib and syslib references
;
ext z3vinit,tinit,stndout,stndend,bdos
ext codend,retud,pfn1,dfree,dutdir,dparams
ext crlf,cout,pafdc,phldc,phlfdc,z3log,fillb,getcrt,cin
ext lcrlf,lout,lafdc,lhldc,lhlfdc,lfn1
;
; 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
;
call z3vinit ; Initialize the zcpr3 env
call tinit ; Initialize the terminal
;
; make fcb wild if no entry
;
ld hl,fcb+1 ; Pt to first char
ld a,(hl) ; Get it
cp ' ' ; Check for space
ld b,11 ; Prepare to set 11 bytes
ld a,'?' ; To "?"
call z,fillb ; Do it if space
;
; check for help
;
ld de,fcb+1 ; Pt to first char of fcb
ld a,(de) ; Get first char of fcb
cp '/'
jp nz,doit
call print
db 'DIR Vers '
db [vers/10]+'0','.',[vers mod 10]+'0',cr,lf
db ' Syntax: DIR dir:afn o',cr,lf
db ' Options: A=All, S=Sys, H=Horiz, V=Vert, '
db 'P=Print, '
db 'T=File Type/Name Sor','t'+80h
ret
pcrlf: ld a,(prnt)
or a
call nz,lcrlf
jp crlf
pcout:
push af
ld a,(prnt)
or a
jp z,pco0
pop af
call lout
jp cout
pco0:
pop af
jp cout
ppafdc:
push af
ld a,(prnt)
or a
jp z,ppa0
pop af
call lafdc
jp pafdc
ppa0:
pop af
jp pafdc
pphldc:
ld a,(prnt)
or a
call nz,lhldc
jp phldc
pphlfdc:
ld a,(prnt)
or a
call nz,lhlfdc
jp phlfdc
ppfn1:
ld a,(prnt)
or a
call nz,lfn1
jp pfn1
;
; perform directory function
;
doit:
dec de ; Pt to fcb
call z3log ; Log into dir
xor a ; Clear disk selection byte
ld (de),a
;
; process options in fcb2
;
ld hl,fcb2+1 ; Pt to options
ld b,8 ; Allow for up to 8 options
ld c,10000000b ; Assume just normal files
optloop:
ld a,(hl) ; Get next char
inc hl ; Advance
dec b ; Count down
jp z,setdata ; Done - set data
cp ' '
jp z,optloop
cp 'H' ; Select horizontal listing
jp z,sethoriz
cp 'V' ; Select vertical listing
jp z,setvert
cp 'T' ; File type?
jp z,settype
cp 'S' ; System?
jp z,setsys
cp 'P' ; Print?
jp z,setprnt
cp 'A' ; System and normal?
jp nz,optloop
;
; select both system and normal files
;
ld a,11000000b ; Normal and system files
jp setsys1
;
; select printer output
;
setprnt:
ld a,yes
ld (prnt),a
jp optloop
prnt:
db no ; Print option (default no)
;
; select horizontal listing
;
sethoriz:
ld a,yes
ld (horiz),a
jp optloop
;
; select vertical listing
;
setvert:
ld a,no
ld (horiz),a
jp optloop
;
horiz: db not vert ; Horizontal listing flag
;
; select file type/name alphabetization
;
settype:
ld a,c ; Get flag
or 00100000b
ld c,a
jp optloop
;
; select just system files
;
setsys:
ld a,01000000b ; System
setsys1:
push af
ld a,c
and 00111111b ; Mask out
ld c,a
pop af
or c
ld c,a
jp optloop
;
; set selection byte in a
;
setdata:
call dparams ; Init parameters
push hl
push de
push bc
call retud ; Get du
ld hl,(z3eadr)
ld de,126 ; Offset to 'PUBLIC' masks
add hl,de
ld (public),hl ; Save the mask address
ld a,(hl)
or a ; Public user drive mask set?
jp z,pub2
inc hl ; Bump pointer to user mask
ld a,(hl)
or a ; Public user mask set?
jp z,pub2
dec hl ; Go back and get the drive mask
ld e,(hl) ; Save in (E)
ld a,b ; Get current drive
inc a
cp 9 ; PUBLIC drives can only be A - H
jr nc,pub2
call bitrel ; Make current drive bit relative
jr z,pub2 ; Returned Zero if not PUBLIC
ld a,e
ld (pubdrv),a ; Save the public user drive mask
inc hl ; Bump address to public user mask
ld e,(hl)
ld a,c ; Get current user
cp 9 ; PUBLIC users can only be 1 - 8
jr nc,pub2
or a
jr z,pub2
call bitrel
jr z,pub2
ld (pubflg),a ; Set PUBLIC flag
ld a,e
ld (pubusr),a ; Save public user mask
xor a ; Now clear PUBLIC masks
ld (hl),a ; So we can use a wildcard search
dec hl ; To fill the the directory buffer
ld (hl),a
pub2: pop bc ; Original masks will be restored
pop de ; At program end.
pop hl
call codend ; Pt to free area
ld a,c ; Selection in a
;
; load and sort directory
;
call dirqs ; Quick load
ld (dirbeg),hl ; Beginning of directory area
jp nz,display
call print
db ' Ovf','l'+80h
jp progend
; RET
;
; display directory
;
display:
push hl ; Save ptr to first entry
;
; init:
; total of all file sizes
; number of files displayed
; line counter
; entry counter
;
if vopt ; Signon and version
push bc
if video
call stndout
endif
ld c,22 ; Print 22 spaces
dis0: ld a,' '
call pcout
dec c
jp nz,dis0
call print
db 'DIRectory Version '
db vers/10+'0','.',vers mod 10+'0'
db ' ',month/10+'0',month mod 10+'0','/'
db day/10+'0',day mod 10+'0','/'
db year/10+'0',year mod 10+'0'
db cr,lf+80h
if video
call stndend
endif
pop bc
endif ; Vopt
;
ld hl,0 ; Set total size count
ld (totcount),hl
ld hl,fcount ; Save file count
ld (hl),c
inc hl
ld (hl),b ; File count saved from bc
push bc ; Save file count
ld h,b
ld l,c ; Move it to hl
ld de,4
call divide ; Divide by four columns
jp z,dis1
inc bc ; Round up if remainder from division
dis1: ld h,b
ld l,c ; Quotient to hl
call x16
ld (lines),hl
pop hl ; Get file count
push hl ; And put it back
dec hl ; File count -1 points to last file
call x16 ; Multiply by 16 chars/line
ex de,hl ; Directory size to de
ld hl,(dirbeg)
add hl,de
ld (dirend),hl
pop bc ; Get file count
pop hl ; Pt to first entry
xor a
ld (lcount),a ; Init line count
ld (count),a ; Init entry count
ld a,b ; Check for done
or c
jp z,prremain ; Print remaining space on disk and exit
call print
db ' '+80h ; Print first leading space
;
; loop to display file entries
;
disploop:
;
; print separator if within a line
;
ld a,(count) ; See if new entry on line
and 3
jp z,displ1
;
; print separator if entry is within a list
;
if video
call stndout
endif
call print ; Print separator
db '|',' '+80h
if video
call stndend
endif
;
; print next entry
;
displ1:
push hl ; Save key regs
push bc ; Hl pts to next entry, bc = count
;
; print file name
;
inc hl ; Pt to file name
ex de,hl
call ppfn1 ; Print file name
ex de,hl
dec hl ; Pt to first byte of file entry
;
; print file size and increment total of all file sizes
;
push hl ; Save ptr to first byte of file entry
call fsize ; Compute file size (to de)
ld hl,(totcount) ; Increment total count
add hl,de
ld (totcount),hl
ex de,hl
call pphldc ; Print file size
pop hl ; Get ptr to first byte of file entry
;
; check r/o byte
;
ld b,' ' ; Assume r/w
ld de,9 ; Pt to r/o
add hl,de
ld a,(hl) ; Get r/o byte
and 80h ; Look at it
jp z,roout
ld b,'r' ; Set r/o
roout:
ld a,b ; Get char
call pcout
;
; increment entry count and issue new line if limit reached
;
ld a,(count) ; Increment entry count
inc a
ld (count),a
ld a,(horiz) ; Check horiz/vert listing
or a
jp z,displ2 ; Vertical listing
ld a,(count)
and 3 ; New line?
call z,newlin
jp displ2
;
; new line - increment line count and issue page break if limit reached
;
newlin: call prnl
ld a,(lcount) ; Count down lines
inc a
ld (lcount),a
call getcrt ; Get crt data
inc hl ; Pt to text line count
inc hl
dec a ; Back up again
cp (hl) ; Compare
ret nz
xor a ; Reset line count
ld (lcount),a
if video
call stndout
endif
call print
db ' Pause -',' '+80h
if video
call stndend
endif
call cin
call prnl ; Print new line with leading space
cp ctrlc ; Abort?
ret nz
pop af ; Clear the rest of the stack
pop af
pop af
jp progend
; RET ; To zcpr3
;
; advance to next entry
;
displ2:
pop bc ; Restore count and ptr to current entry
pop hl
ld a,(horiz) ; Check horiz/vert listing
or a
jp nz,disp2 ; Horizontal
ex de,hl ; Pointer to de
ld hl,(lines)
add hl,de ; Point to next entry
ex de,hl ; New pointer to de
ld hl,(dirend)
call subde ; Check if new ptr is within the directory
ex de,hl ; New pointer to hl
jp nc,disp3 ; New pointer is ok
ld hl,(dirbeg) ; Otherwise start new line
ld de,16 ; Next line
add hl,de
ld (dirbeg),hl ; Save it
xor a
ld (count),a ; Clear column count
push hl
push bc
call newlin
pop bc
pop hl
jp disp3
disp2: ld de,16 ; Skip to next entry
add hl,de
disp3: dec bc ; Count down
ld a,b ; Done?
or c
jp nz,disploop
ld a,(count) ; See if new line required
and 3
call nz,pcrlf ; New line if any entries on line
;
; print remaining space on disk and exit
;
prremain:
;
; print du
;
if video
call stndout
endif
ld a,(pubflg) ; If PUBLIC
ld b,3 ; Space over 3 spaces
or a
jr nz,gsp
ld b,8 ; Space over 8 spaces
gsp: ld a,' '
spacer:
call pcout
dec b
jp nz,spacer
call retud ; Get du in bc
ld a,b ; Print disk letter
add 'A' ; Convert to ascii
call pcout
ld a,c ; Print user number
call ppafdc ; Print floating
call print ; Print separator
db ':'+80h
call dutdir ; See if matching dir
jp z,prrem1
;
; print dir if any
;
ld b,8 ; 8 chars max
prrem0:
ld a,(hl) ; Get char
inc hl ; Pt to next
cp ' ' ; Space?
call nz,pcout ; Echo char
dec b ; Count down
jp nz,prrem0
;
; print file count
;
prrem1:
ld a,(pubflg)
or a ; PUBLIC directory?
jr z,ovrpub
ld a,' '
call pcout
call stndend
call print ; Print public message
db '[PUBLIC',']'+80h
call stndout
ovrpub:
ld hl,(fcount) ; Print number of files
call print
db ' --',' '+80h
call pphlfdc
;
; print total of all file sizes
;
ld hl,(totcount) ; Print total count
call print
db ' files using',' '+80h
call pphlfdc ; Print as floating
;
; print amount of free space remaining
;
call dfree ; Compute amount of free space
ex de,hl ; In hl
call print
db 'k ','('+80h
call pphlfdc
call print
db 'k remain of',' '+80h
call dsize
call pphlfdc
call print
db 'k total',')'+80h
if video
call stndend
endif
ld a,(prnt)
or a
call nz,lcrlf
progend:
ld a,(pubflg) ; If PUBLIC restore masks
or a
ret z
ld hl,(public) ; Get 'PUBLIC' user mask address
ld a,(pubdrv) ; Restore PUBLIC masks
ld (hl),a
inc hl
ld a,(pubusr)
ld (hl),a
ret
;
; print new line with leading space
;
prnl:
call print
db cr,lf,' '+80h ; New line with leading space
ret
;
; print routine (string at return address) which is terminated by msb
;
print:
ex (sp),hl ; Pt to string and save hl
push af
print1:
ld a,(hl) ; Get next char
and 7fh ; Mask msb
call pcout
ld a,(hl) ; Get next char
inc hl ; Pt to next
and 80h ; Check msb
jp z,print1
pop af ; Get a
ex (sp),hl ; Restore return address and hl
ret
;
; dsize returns the size of the current disk in hl (k)
;
dsize: push de
push bc
;
ld c,31 ; Return dpb address in hl
call bdos
inc hl
inc hl ; Point to bls
ld a,(hl) ; Bls in a
ld (bls),a
inc hl
inc hl
inc hl ; Point to dsm
ld e,(hl)
inc hl
ld d,(hl) ; Dsm in de
inc de ; Rel 1
push de ; Save dsm on stack
inc hl ; Point to drm
inc hl
inc hl ; Point to all0
ld d,(hl)
inc hl ; Point to all1
ld e,(hl)
ex de,hl ; Allocation vector in hl
ld de,-1 ; Clear a counter
ds0: inc de
call shlhl
jp c,ds0
call subde ; Get complement of count
pop de ; Get dsm from stack
add hl,de ; Hl = groups available
ld a,(bls) ; Block shift factor
sub 3 ; From bls in a
jp z,dsx
dsiz0: add hl,hl
dec a
jp nz,dsiz0
dsx:
pop bc
pop de
ret
;
; divide divides hl by de returning quotient in bc and remainder in hl
; zero flag is set if no remainder
;
divide: ld bc,0 ; Clear quotient
div0: call subde ; Subtract de from hl
jp c,div1 ; Overflow
inc bc ; Increment quotient
jp div0 ; Again..
div1: add hl,de ; Restore remainder in hl
ld a,h ; Check for remainder
or l ; Equal zero
ret
;
; subde subtracts de from hl returning carry set if de > hl
;
subde: ld a,l
sub e
ld l,a
ld a,h
sbc a,d
ld h,a
ret
;
; x16 simply shifts hl left four times
;
x16: add hl,hl
add hl,hl
add hl,hl
add hl,hl
ret
;
; shlhl shifts hl left into carry
;
shlhl: or a ; Reset carry
ld a,l
rla
ld l,a
ld a,h
rla
ld h,a
ret
;
; syslib module name: sdirqs
; author: richard conn
; part of syslib3 sdir series
; syslib version number: 3.0
; module version number: 1.4
; module entry points:
; dirqs
; module external references:
; none
;
;*
;* equates
;*
cpm equ 0
buff equ 80h ; Dma buffer
esize equ 16 ; 16 bytes/entry
;*
;* general-purpose directory select routine without sizing information
;* this routine scans for the fcb pted to by de and loads all entries
;* which match it into the memory buffer pted to by hl. on exit,
;* bc=number of files in buffer, and hl pts to first file in buffer.
;* the directory buffer generated by dirq contains entries which may not
;* be used to compute the size of the files using the fsize routine. the
;* dirqs routine is designed for this purpose. the basic tradeoff between
;* the two routines is the dirq runs faster than dirqs, and this is noticable
;* if there is a significant number of files to be processed.
;*
;* the dirq/dirqs routines are intended to be used in applications where
;* the only thing desired is a directory load of the current directory
;* (disk and user). dirf/dirfs provide more flexibility at a greater cost
;* in terms of size.
;*
;* input parameters:
;* hl pts to buffer, de pts to fcb, a is select flag:
;* bit 7 - select non-sys, bit 6 - select sys
;* bit 5 - sort by file name and type (0) or other (1)
;* bits 4-0 - unused
;* output parameters:
;* hl pts to first file in buffer
;* bc = number of files
;* a=0 and z flag set if tpa overflow
;* de unchanged
;*
dirqs:
push de ; Save ptr to fcb
ld (selflg),a ; Save select flag for selection and alphabetization
ld (hold),hl ; Set ptr to hold buffer
ld bc,36 ; Allow 36 bytes
add hl,bc ; Hl now points to temp fcb
ld (tfcb),hl ; Set ptr to temp fcb
add hl,de ; Hl now pts to scratch area
push de ; Save ptr to fcb
call dbuffer ; Get ptrs
pop de ; Get ptr to fcb
push hl ; Save ptr to buffer
call dirload ; Load directory (fast load)
pop hl ; Get ptr to buffer
pop de ; Get ptr to fcb
ret z ; Abort if tpa overflow
push af ; Save flag to indicate no tpa overflow
call diralpha ; Alphabetize
pop af ; Get psw (tpa overflow flag)
ret
;*
;* this routine accepts a base address for the dynamic buffers
;* required, determines how much space is required for the buffers,
;* and sets the order ptr to pt to the first and dirbuf to pt to
;* the second (order space = dirmax*2 and dirbuf = dirmax * esize)
;* on input, hl pts to available base
;* on output, hl pts to dirbuf
;* a=0 and zero flag set if ccp overrun
;*
dbuffer:
ld (order),hl ; Pt to order table
call dparams0 ; Get parameters
ld hl,(dirmax) ; Number of entries in dir
ex de,hl ; In de
ld hl,(order) ; Add to order base
add hl,de ; *1
call memchk ; Check for within range
add hl,de ; Hl pts to dirbuf
call memchk ; Check for within range
ld (dirbuf),hl ; Set ptr and hl pts to directory buffer
xor a ; Ok
dec a ; Set flags (nz)
ret
memchk:
push hl ; Save regs
push de
ex de,hl ; Next address in de
ld hl,(bdos+1) ; Get address of bdos
ld a,d ; Check for page overrun
cp h
jp nc,memorun ; Overrun if d>=h
pop de
pop hl
ret
memorun:
pop de ; Restore
pop hl
pop af ; Clear stack
xor a ; Return 0
ret
;*
;* this routine extracts disk parameter informaton from the dpb and
;* stores this information in:
;* blkshf <-- block shift factor (1 byte)
;* blkmsk <-- block mask (1 byte)
;* extent <-- extent mask (1 byte) [not any more]
;* blkmax <-- max number of blocks on disk (2 bytes)
;* dirmax <-- max number of directory entries (2 bytes)
;*
dparams0:
;*
;* version 2.x or mp/m
;*
ld c,31 ; 2.x or mp/m...request dpb
call bdos
inc hl
inc hl
ld a,(hl) ; Get block shift
ld (blkshf),a ; Block shift factor
inc hl ; Get block mask
ld a,(hl)
ld (blkmsk),a ; Block mask
inc hl
inc hl
ld e,(hl) ; Get max block number
inc hl
ld d,(hl)
ex de,hl
inc hl ; Add 1 for max number of blocks
ld (blkmax),hl ; Maximum number of blocks
ex de,hl
inc hl
ld e,(hl) ; Get directory size
inc hl
ld d,(hl)
ex de,hl
inc hl ; Add 1 for number of entries
ld (dirmax),hl ; Maximum number of directory entries
ret
;*
;* build directory table at dirbuf
;* this is the optimal directory load routine; it only loads unique
;* file names from disk, but the information is not sufficient
;* to compute the file sizes
;* on input, hl pts to directory buffer (16 x n max)
;* de pts to fcb (only 12 bytes needed)
;* on output, bc is num of files
;* a=0 and zero flag set if tpa overflow
;*
dirload:
ld (dstart),hl ; Set start of buffer area
inc de ; Pt to file name
ld hl,(tfcb) ; Pt to tfcb
ld (hl),0 ; Select current disk
inc hl ; Pt to file name in tfcb
ld b,11 ; 11 chars
dlloop:
ld a,(de) ; Copy
ld (hl),a
inc hl ; Pt to next
inc de
dec b ; Count down
jp nz,dlloop
ld (hl),'?' ; Select all extents
inc hl ; Pt to next char
ld (hl),0
inc hl
ld (hl),'?' ; And all modules
inc hl
ld b,21 ; 23 chars
xor a ; Zero rest of tfcb
dlloop1:
ld (hl),a ; Store zero
inc hl ; Pt to next
dec b ; Count down
jp nz,dlloop1
;*
;* this section of code initializes the counters used
;*
ld hl,0 ; Hl=0
ld (fcount0),hl ; Total files on disk = 0
;*
;* now we begin scanning for files to place into the memory buffer
;*
ld c,17 ; Search for file
jp dirlp1
dirlp:
call pentry ; Place entry in dir
jp z,dirovfl ; Memory overflow error
ld c,18 ; Search for next match
dirlp1:
ld hl,(tfcb) ; Pt to fcb
ex de,hl
call bdos
cp 255 ; Done?
jp nz,dirlp
;*
;* now we are done with the load -- set up return values
;*
dirdn:
xor a ; Load ok
dec a ; Set flags (nz)
dirdnx:
ld hl,(fcount0) ; Get total number of files
ld b,h ; In bc
ld c,l
ret
;*
;* memory overflow error
;*
dirovfl:
xor a ; Load error
jp dirdnx
;*
;* pentry --
;* place entry in directory buffer if not an erased entry
;*
;* on input, a=0-3 for adr index in buff of entry fcb
;* fcount0=number of files in dir so far
;* on output, fcount0=number of files in dir so far
;* a=0 and zero flag set if memory overflow error
;*
pentry:
rrca ; Multiply by 32 for offset computation
rrca
rrca
and 60h ; A=byte offset
ld de,buff ; Pt to buffer entry
ld l,a ; Let hl=offset
ld h,0
add hl,de ; Hl=ptr to fcb
;*
;* hl=adr of fcb in buff
;*
call attest ; Test attributes
jp z,pedone ; Skip if attribute not desired
;*
;* scan directory entries as loaded so far for another entry by the same
;* name; if found, set that entry to be the entry with the larger ex
;* and return with the zero flag set, indicating no new file; if not
;* found, return with zero flag reset (nz)
;*
call dupentry ; Check for duplicate and select ex
jp z,pedone ; Skip if duplicate
;*
;* copy fcb pted to by hl into directory buffer
;*
ex de,hl ; Save ptr in de
ld hl,(dirbuf) ; Pt to next entry location
ex de,hl ; Hl pts to fcb, de pts to next entry location
ld b,esize ; Number of bytes/entry
call sdmove ; Copy fcb into memory buffer
ex de,hl ; Hl pts to next entry
ld (dirbuf),hl ; Set ptr
ex de,hl ; Ptr to next entry in de
ld hl,(bdos+1) ; Base address of bdos in hl
ld a,h ; Get base page of bdos
sub 9 ; Compute 1 page in front of base page of ccp
cp d ; Is ptr to next entry beyond this?
ret z
;* increment total number of files
ld hl,(fcount0) ; Total files = total files + 1
inc hl
ld (fcount0),hl
;* done with pentry and no error
pedone:
xor a ; No error
dec a ; Set flags (nz)
ret
;*
;* check attributes of file entry pted to by hl against selflg
;* if system file and system attribute set, return nz
;* if normal file and normal attribute set, return nz
;*
attest:
push hl ; Save ptr
ld bc,10 ; Pt to system attribute
add hl,bc
ld a,(hl) ; Get system attribute
pop hl ; Restore ptr
and 80h ; Check for sys
ld a,(selflg) ; Get selection flag
jp z,atdir
and 01000000b ; Check system attribute
ret
atdir:
and 10000000b ; Check normal attribute
ret
;*
;* scan directory entries as loaded so far for another entry by the same
;* name; if found, set that entry to be the entry with the larger ex
;* and return with the zero flag set, indicating no new file; if not
;* found, return with zero flag reset (nz)
;* on input, hl pts to entry to scan for, fcount0 = number of entries so far,
;* and (dstart) = starting address of directory loaded
;* on output, a=0 and zero flag set if duplicate entry found; a=0ffh and nz
;* if no dup entry found
;* only hl not affected
;*
dupentry:
push hl ; Save ptr to entry to scan for
ex de,hl ; Ptr in de
ld hl,(fcount0) ; Check count
ld a,h ; No entries?
or l
jp z,nodup ; No duplicate entry return
ld b,h ; Bc=number of entries
ld c,l
ld hl,(dstart) ; Hl pts to first entry
dupeloop:
push bc ; Save count
push hl ; Save ptrs
push de
inc hl ; Pt to fn
inc de
ld b,11 ; Compare fn and ft
call comp
jp nz,nodupl ; Continue looking for another entry
; duplicate entries have been identified at this point
ld c,(hl) ; Extent in low order
inc hl
inc hl
ld b,(hl) ; Module in high order
push bc ; Save entry size a moment
ex de,hl ; Point hl to target
ld e,(hl) ; Extent in low order
inc hl
inc hl
ld d,(hl) ; Module in high order
pop hl ; Dir in hl, target in de
ex de,hl
call subde ; Subtract dir size from target size
pop de ; Get ptrs
pop hl
jp c,dupsmall ; Target is smaller
; new target is larger than stored entry
ex de,hl ; Hl pts to target, de pts to dir entry
ld b,esize ; Number of bytes to move
call sdmove ; Move it
; new target is smaller than stored entry
dupsmall:
pop bc ; Clear count from stack
xor a ; Indicate dup found
pop hl ; Restore ptr to entry to scan for
ret
; no duplicate found; advance to next entry
nodupl:
pop de ; Restore ptrs
pop hl
ld bc,esize ; Hl pts to current entry in buffer, so add esize to it
add hl,bc
pop bc ; Get count
dec bc ; Count down
ld a,b ; Check for done
or c
jp nz,dupeloop
; no duplicate found
nodup:
xor a ; Indicate dup not found
dec a ; Set flags (nz)
pop hl ; Restore ptr to entry to scan for
ret
;*
;* diralpha -- alphabetizes directory pted to by hl; bc contains
;* the number of files in the directory and a = sort flag
;* (0=sort by file name/type, <>0 = sort by file type/name)
;*
diralpha:
ld a,b ; Any files?
or c
ret z
push hl ; Save regs
push de
push bc
ld (dirbuf),hl ; Save ptr to directory
push hl ; Save hl
ld h,b ; Hl=bc=file count
ld l,c
ld (n),hl ; Set "N"
pop hl
;*
;* 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
;*
sort:
ex de,hl ; Pointer to directory in de
ld hl,(order) ; Pt to order table
;*
;* set up order table; hl pts to next entry in order table, de pts to next
;* entry in directory, bc = number of elements remaining
;*
sort1:
ld (hl),e ; Store low-order address
inc hl ; Pt to next order byte
ld (hl),d ; Store high-order address
inc hl ; Pt to next order entry
push hl ; Save ptr
ld hl,esize ; Hl=number of bytes/entry
add hl,de ; Pt to next dir1 entry
ex de,hl ; De pts to next entry
pop hl ; Get ptr to order table
dec bc ; Count down
ld a,b ; Done?
or c
jp nz,sort1
;*
;* this is the main sort loop for the shell sort in "SOFTWARE TOOLS" by k&p
;*
;*
;* shell sort from "SOFTWARE TOOLS" by kerninghan and plauger
;*
ld hl,(n) ; Number of items to sort
ld (gap),hl ; Set initial gap to n for first division by 2
;* for (gap = n/2; gap > 0; gap = gap/2)
srtl0:
or a ; Clear carry
ld hl,(gap) ; 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 zero
or h
jp z,sdone ; Done with sort if gap = 0
ld (gap),hl ; Set value of gap
ld (idx),hl ; Set i=gap for following loop
;* for (i = gap + 1; i <= n; i = i + 1)
srtl1:
ld hl,(idx) ; Add 1 to i
inc hl
ld (idx),hl
;* test for i <= n
ex de,hl ; I is in de
ld hl,(n) ; Get n
ld a,l ; Compare by subtraction
sub e
ld a,h
sbc a,d ; Carry set means i > n
jp c,srtl0 ; Don't do for loop if i > n
ld hl,(idx) ; Set j = i initially for first subtraction of gap
ld (j),hl
;* for (j = i - gap; j > 0; j = j - gap)
srtl2:
ld hl,(gap) ; Get gap
ex de,hl ; In de
ld hl,(j) ; Get j
ld a,l ; Compute j - gap
sub e
ld l,a
ld a,h
sbc a,d
ld h,a
ld (j),hl ; J = j - gap
jp c,srtl1 ; If carry from subtractions, j < 0 and abort
ld a,h ; J=0?
or l
jp z,srtl1 ; If zero, j=0 and abort
;* set jg = j + gap
ex de,hl ; J in de
ld hl,(gap) ; Get gap
add hl,de ; J + gap
ld (jg),hl ; Jg = j + gap
;* if (v(j) <= v(jg))
call icompare ; J in de, jg in hl
;* ... then break
jp 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 of inner-most for loop
jp srtl2
;*
;* sort is done -- restructure dir1 in sorted order in place
;*
sdone:
ld hl,(n) ; Number of entries
ld b,h ; In bc
ld c,l
ld hl,(order) ; Ptr to ordered pointer table
ld (ptptr),hl ; Set ptr ptr
ld hl,(dirbuf) ; Ptr to unordered directory
ld (ptdir),hl ; Set ptr dir buffer
;* find ptr to next dir1 entry
srtdn:
ld hl,(ptptr) ; Pt to remaining pointers
ex de,hl ; In de
ld hl,(ptdir) ; Hl pts to next dir entry
push bc ; Save count of remaining entries
;* find ptr table entry
srtdn1:
ld a,(de) ; Get current pointer table entry value
inc de ; Pt to high-order pointer byte
cp l ; Compare against dir1 address low
jp nz,srtdn2 ; Not found yet
ld a,(de) ; Low-order bytes match -- get high-order pointer byte
cp h ; Compare against dir1 address high
jp z,srtdn3 ; Match found
srtdn2:
inc de ; Pt to next ptr table entry
dec bc ; Count down
ld a,c ; End of table?
or b
jp nz,srtdn1 ; Continue if not
;* fatal error -- internal error; pointer table not consistent
ferr$ptr:
ld e,7 ; Ring bell
ld c,2 ; Output
call bdos
jp cpm
;* found the pointer table entry which points to the next unordered dir1 entry
;* make both pointers (ptr to next, ptr to current unordered dir1 entry)
;* point to same location (ptr to next dir1 entry to be ordered)
srtdn3:
ld hl,(ptptr) ; Get ptr to next ordered entry
dec de ; De pts to low-order pointer address
ld a,(hl) ; Make ptr to next unordered dir1 pt to buffer for
ld (de),a ; Dir1 entry to be moved to next unordered dir1 pos
inc hl ; Pt to next ptr address
inc de
ld a,(hl) ; Make high point similarly
ld (de),a
;* copy next unordered dir1 entry to hold buffer
ld b,esize ; B=number of bytes/entry
ld hl,(hold) ; Pt to hold buffer
ex de,hl
ld hl,(ptdir) ; Pt to entry
push bc ; Save b=number of bytes/entry
call sdmove
pop bc
;* copy to-be-ordered dir1 entry to next ordered dir1 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,(ptdir) ; Destination address for next ordered dir1 entry
ex de,hl ; Hl pts to entry to be moved, de pts to dest
push bc ; Save b=number of bytes/entry
call sdmove
pop bc
ex de,hl ; Hl pts to next unordered dir1 entry
ld (ptdir),hl ; Set pointer for next loop
;* copy entry in hold buffer to loc previously held by latest ordered entry
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 dest
call sdmove ; B=number of bytes/entry
;* point to next entry in pointer table
ld hl,(ptptr) ; Pointer to current entry
inc hl ; Skip over it
inc hl
ld (ptptr),hl
;* count down
pop bc ; Get counter
dec bc ; Count down
ld a,c ; Done?
or b
jp nz,srtdn
pop bc ; Restore regs
pop de
pop hl
ret ; Done
;*
;* 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
dec hl ; 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,bc ; Hl now pts to pointer involved
ex de,hl ; De now pts to pointer indexed by hl
dec hl ; Adjust 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,bc ; Hl now pts to pointer involved
ld c,(hl) ; Exchange pointers -- get old (de)
ld a,(de) ; -- get old (hl)
ex de,hl ; Switch
ld (hl),c ; Put new (hl)
ld (de),a ; Put new (de)
inc hl ; Pt to next byte of pointer
inc de
ld c,(hl) ; Get old (hl)
ld a,(de) ; Get old (de)
ex de,hl ; 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 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 hl ; Save hl
ld hl,(order) ; Address of order - 2
ld b,h ; In bc
ld c,l
pop hl
dec hl ; Adjust index to 0...n-1 from 1...n
add hl,hl ; Double the element number to point to the ptr
add hl,bc ; Add to this the base address of the ptr table
ex de,hl ; Result in de
dec hl ; Adjust 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 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 ptr and hl
;* to the 4th pointer
;*
ld c,(hl) ; Bc is made to point to the object indexed to
inc hl ; By the original hl
ld b,(hl)
ex de,hl
ld e,(hl) ; De is made to point to the object indexed to
inc hl ; By the original de
ld d,(hl)
ld h,b ; Set hl = object pted to indirectly by bc
ld l,c
;*
;* compare dir entry pted to by hl with that pted to by de;
;* no net effect on hl, de; ret w/carry set means de<hl
;* ret w/zero set means de=hl
;*
cmp$entry:
ld a,(selflg) ; Group by file type?
and 00100000b
jp z,cmp$fn$ft
;*
;* compare by file type and file name (in that order)
;*
push hl
push de
ld bc,9 ; Pt to ft (8 bytes + 1 byte for user number)
add hl,bc
ex de,hl
add hl,bc
ex de,hl ; De, hl now pt to their ft's
ld b,3 ; 3 bytes
call comp ; Compare ft's
pop de
pop hl
ret nz ; Continue if complete match
ld b,8 ; 8 bytes
jp cmp$ft1
;*
;* compare by file name and file type (in that order)
;*
cmp$fn$ft:
ld b,11 ; 11 bytes for fn and ft
cmp$ft1:
push hl
push de
inc hl ; Pt to fn
inc de
call comp ; Do comparison
pop de
pop hl
ret
;*
;* comp compares de w/hl for b bytes; ret w/carry if de<hl
;* msb is disregarded
;*
comp:
ld a,(hl) ; Get (hl)
and 7fh ; Mask msb
ld c,a ; In c
ld a,(de) ; Compare
and 7fh ; Mask msb
cp c
ret nz
inc hl ; Pt to next
inc de
dec b ; Count down
jp nz,comp
ret
;*
;* copy from hl to de for b bytes
;*
sdmove:
ld a,(hl) ; Copy
ld (de),a
inc hl ; Pt to next
inc de
dec b ; Count down
jp nz,sdmove
ret
;*
;* buffers
;*
hold:
ds 2 ; Exchange hold buffer for fcb's
ptptr:
ds 2 ; Pointer pointer
ptdir:
ds 2 ; Directory pointer
idx:
ds 2 ; Indexes for sort
j:
ds 2
jg:
ds 2
n:
ds 2 ; Number of elements to sort
gap:
ds 2 ; Binary gap size
tfcb:
ds 2 ; Address of temporary fcb
dstart:
ds 2 ; Pointer to first directory entry
fcount0:
ds 2 ; Total number of files/number of selected files
blkshf:
db 0 ; Block shift factor
blkmsk:
db 0 ; Block mask
blkmax:
dw 0 ; Max number of blocks
dirmax:
dw 0 ; Max number of directory entries
selflg:
db 0 ; File attribute flag
order:
dw 0 ; Pointer to order table
dirbuf:
dw 0 ; Pointer to directory
; end
;
; buffers
;
count: ds 1 ; Counter used in display
fcount: ds 2 ; Number of files displayed
lcount: ds 1 ; Line counter
totcount: ds 2 ; Total of sizes of all files
bls: ds 1 ; Block shift factor
lines: ds 2 ; Lines to be displayed
dirbeg: ds 2 ; Beginning of directory area
dirend: ds 2 ; End of directory area
pubflg: db 0 ; Public user flag
public: dw 0 ; Address of public du mask
pubdrv: ds 1 ; Public Drive mask save area
pubusr: ds 1 ; Public User mask save area
; end
;
; syslib module name: sdir04
; author: richard conn
; part of syslib3 sdir series
; syslib version number: 3.0
; module version number: 1.4
; module entry points:
; fsize
; module external references:
;
;
; include sdirhdr.lib
;*
;* compute size of file whose last extent is pointed to by hl
;* file size is returned in de in k
;* note that the routine dparams must have been called before this routine
;* is used
;*
fsize:
push bc ; Save regs
push hl
push af
ld de,12 ; Point to extent
add hl,de
ld e,(hl) ; Get extent #
ld d,0
inc hl ; S1
inc hl ; S2 is the module number (512 k)
ld a,(hl) ; Get module #
or a ; Reset carry
rla
rla
rla
rla
rla ; * 32 extents
push af
or e
ld e,a ; Add to e
pop af
jp nc,fs0 ; Check high order bit
inc d ; If carry
fs0: inc hl ; Hl pts to record count field
ld a,(hl) ; Get record count of last extent
ex de,hl
add hl,hl ; Number of extents times 16k
add hl,hl
add hl,hl
add hl,hl
ex de,hl ; Total size of previous extents in de
ld hl,blkmsk
add a,(hl) ; Round last extent to block size
rrca
rrca ; Convert from records to k
rrca
and 1fh
ld l,a ; Add size of last extent to total of previous extents
ld h,0 ; Hl=size of last extent, de=total of previous extents
add hl,de ; Hl=total file size in blocks
ld a,(blkmsk) ; Get records/blk-1
rrca
rrca ; Convert to k/blk
rrca
and 1fh
cpl ; Use to finish rounding
and l
ld l,a ; Hl now equals the size of the file in k increments
ex de,hl ; De=file size in k
pop af ; Restore regs
pop hl
pop bc
ret
;
bitrel: ld d,a
ld a,80h
bitlp: rlc a
dec d
jr nz,bitlp
and a,e
ret
;
end