home *** CD-ROM | disk | FTP | other *** search
Text File | 1993-10-25 | 26.3 KB | 1,020 lines |
- ; SAP v50 -- Sort & Pack Directory, 8/7/86
- ;
- ;; .Z80 ; Needed for M80, ignore error otherwise
- ;; ASEG ; Needed for M80, ignore error otherwise
- ;
- ;=======================================================================
- ;
- ; User-customizable options:
- ;
-
- NO EQU 0
- YES EQU .NOT.NO
-
- MAXDRIVE EQU 'B' ; Set to maximum drive in system, in UPPER CASE!
-
- ONLY22 EQU YES ; Set this to YES if SAP will be running ONLY under
- ; CP/M v2.2. If not sure, set to NO.
-
- ONLY14 EQU NO ; Set this to YES if SAP will be running ONLY under
- ; CP/M v1.4. If not sure, set to NO.
-
- CPMONLY EQU YES ; Set this to YES if SAP will be running ONLY under
- ; CP/M, either v1.4 or 2.2 If possibility exists
- ; That SAP might be executed under MP/M or CP/M 3.0,
- ; Set to NO.
-
- ASCENDING EQU YES ; Set this to NO for a descending sort of directory
- ; Entries.
-
-
- DELZRO EQU YES ; Set this to YES to cause SAP to delete all
- ; Zero-length files if SAVDASH is NO, or to delete
- ; All zero-length files not beginning with "-" if
- ; SAVDASH is YES.
-
- SAVDASH EQU YES ; Set this to YES and DELZRO to YES to cause SAP to
- ; Delete all zero-length files not beginning with
- ; "-" (as in SAP40). Set this to NO to not check
- ; Filenames before deleting zero-length files (if
- ; DELZRO is set YES).
- ;
- ; End of user-selected options
- ;
- ;=======================================================================
- ;
- ; Various system equates
- ;
-
- UNSPECI EQU .NOT.(ONLY22.OR.ONLY14)
-
- BOOT EQU 0000H ; BDOS warm boot vector.
- BDOS EQU 0005H ; BDOS entry point vector.
- FCB EQU 005CH ; Default CP/M file control block.
- CMDBUF EQU 0080H ; CP/M command line buffer.
-
- PRINT EQU 9 ; BDOS print string function.
- VERNO EQU 12 ; BDOS CP/M version number function.
- SELDRV EQU 14 ; BDOS select drive function.
- GETDSK EQU 25 ; BDOS "get disk #" function.
-
- ENTRYLEN EQU 32 ; Length of directory entry on disk in bytes.
-
- CR EQU 0DH
- LF EQU 0AH
- EOS EQU '$' ; BDOS fnc #9, end of string marker.
-
- ;
- ;=======================================================================
- ;
- ; Start of code.
- ;
- ; The code has been rearranged to make the flow linear. Thus we no longer have
- ; a mainline with several calls to subroutines. This optimizes execution time
- ; and code space at the expense of complexity. C'est la vie!
- ;
-
- ORG 100H
-
- ; Obtain certain BIOS vectors.
- LD SP,STACK ; Use our own stack.
- LD C,PRINT
- LD DE,IDENTITY ; Tell user who we are.
- CALL BDOS
- LD HL,(0001H) ; Addr of warm boot BIOS vector
- LD BC,24 ; Offset to SELDSK
- ADD HL,BC ; Source
- LD DE,SELDSK ; Destination
- LD BC,24 ; Get all BIOS vectors from SELDSK to the end.
- LDIR
-
- IF UNSPECI
- LD C,VERNO ; Returns H=0 for CP/M, H=1 for MP/M,
- CALL BDOS ; And L=0 for pre-2.0, else L = 2x or 3x.
- ENDIF
-
- IF UNSPECI.AND.(.NOT.CPMONLY)
- LD DE,BADOPSYS ; Tell user we can't work with MP/M or CP/M 3.0
- ; This is only printed if we detect a problem.
- DEC H ; H=1 for MPM
- JP NZ,PRLAST ; If MP/M then print error and die.
- CP 30H
- JP NC,PRLAST ; Exit if CP/M 3.0 or higher, we can't use it.
- ENDIF ; UNSPECI AND (NOT CPMONLY)
-
- IF UNSPECI
- LD (VERFLG),A ; Store the version num.
- ENDIF
-
- ;
- ;=======================================================================
- ;
- ; Select drive, load disk parm block, and calculate free mem.
- ;
-
- SETUP: LD A,(FCB) ; (FCB) = (0=default, 1=A, 2=B, 3=C, etc.)
- DEC A ; SELDSK needs 0=A, 1=B, 2=C, etc.
- JP P,SETUP1 ; Skip BDOS call if drive mentioned,
- LD C,GETDSK ; Otherwise get current default drive.
- CALL BDOS ; Returns current drive code in A.
-
- BIGDRIVE EQU (MAXDRIVE-'A')+1
-
- SETUP1: CP BIGDRIVE ; Verify that specified drive is not too big.
- JP C,OKDRIVE
- LD DE,BADDRIVE ; Else tell user it is an improper drive spec.
- JP PRLAST ; Print message and die.
-
- OKDRIVE:
- LD C,A ; SELDSK needs drive code in reg C.
- CALL SELDSK ; Returns addr of DPH in HL for selected drive.
-
- IF UNSPECI
- LD A,(VERFLG)
- OR A
- JP NZ,CPM22 ; If ver 2.2 then jump to CPM22,
- ENDIF ; Else must be 1.4
-
- ;
- ;-----------------------------------------------------------------------
- ;
- ; CP/M 1.4 routine
- ;
-
- IF ONLY14.OR.UNSPECI
- CPM14: LD HL,(BDOS+1)
- LD L,0
- LD A,(JP) ; This bizarre inst loads the op code for a JP!
- LD (RECTRN),A
- EX DE,HL ; Store ptr in DE.
- LD HL,15 ; RECTRAN offset from BDOS in CP/M 1.4
- ADD HL,DE
- LD (RECTRN+1),HL
- EX DE,HL ; Restore ptr to HL.
- LD DE,3AH ; Offset from BDOS to 1.4 DPB
- ADD HL,DE
- ;
- ; Note that the previous LD DE,003AH zeroed out the D registor for us.
- ;
- ; LD D,0 ; Note that D=0 for rest of procedure.
- ;
- LD E,(HL)
- LD (SPT),DE
- INC HL
- LD E,(HL)
- LD (DRM),DE
- LD E,5 ; Offset to systrk field. (since D=0)
- ADD HL,DE
- LD E,(HL)
- LD (SYSTRK),DE
- ENDIF ; ONLY14 OR UNSPECI
-
- IF UNSPECI ; If CPM22 not present then just fall through,
- JP CALCSPACE ; Else we need to jump around CPM22.
- ENDIF
-
- ;
- ;-----------------------------------------------------------------------
- ;
- ; CP/M 2.2 routine
- ;
- ; Implementation Note: BC is used here only for loading offsets < 256.
- ; Thus after 1st 16 bit load, B=0 for rest of routine.
- ;
-
- IF ONLY22.OR.UNSPECI
- CPM22: LD E,(HL) ; On entry HL points to DPH.
- INC HL
- LD D,(HL)
- LD (RECTBL),DE ; Save the XLTO addr.
-
- LD BC,9 ; Offset to ptr to DPB (in DPH) (Now B=0)
- ADD HL,BC
- LD E,(HL)
- INC HL
- LD D,(HL)
- EX DE,HL ; Now HL = addr of DPB.
-
- LD E,(HL)
- INC HL
- LD D,(HL)
- LD (SPT),DE
-
- LD C,6 ; Offset to DRM (in DPB) (since B=0)
- ADD HL,BC
- LD E,(HL)
- INC HL
- LD D,(HL)
- LD (DRM),DE
-
- LD C,5 ; Offset to SYSTRK (in DPB) (since B=0)
- ADD HL,BC
- LD E,(HL)
- INC HL
- LD D,(HL)
- LD (SYSTRK),DE ; Now drop into CALCSPACE.
- ENDIF ; ONLY22 OR UNSPECI
-
- ;
- ;=======================================================================
- ;
- ; Determine if directory will fit in available memory.
- ; If not, determine how much of it will.
- ;
-
- CALCSPACE:
- ; First compute amount of free space in bytes.
- LD HL,(BDOS+1) ; Get addr of 1st byte of BDOS.
- LD DE,BUF ; Get addr of 1st byte of BUF.
- ;
- ; OR A ; Clear carry.
- ; SBC HL,DE
- ;
- ; Since we know that BUF starts on an even page boundary, E=0, so just go:
- ;
- LD A,H
- SUB D
- LD H,A ; Now HL = HL - DE, (since E=0).
- ; Note that E=0 is used in next paragraph.
- DEC HL ; This is for the extra 0E5H at the end of the
- ; Buf: needed for CLEAN to be bullet proof.
-
- ; Compute HL = HL/128 by HL = (HL * 2) / 256.
- SLA L ; New carry was msb of L.
- RL H ; Rotate left H (moving carry into lsb).
- ; The new carry was msb of H.
- LD L,H ; Effectively go HL = HL/256 (carry saved)
- LD H,E ; Zero H reg (since E=0 before) (carry saved)
- RL H ; Set H = carry. Now HL = HL/128.
- LD (NUMDIRRECS),HL ; Assume we need all space until proven wrong.
-
- ; Now determine how many 128-byte records the directory takes up.
- LD DE,(DRM) ; Get # 32-byte directory entries . . .
- INC DE ; Relative to 1.
- LD (NUMFNAMES),DE ; Save as a more convenient count for later.
- SRL D
- RR E ; Divide by 2.
- SRL D
- RR E ; Now DE = # 128-byte records needed.
- ; Note HL = # 128-byte records available.
- ;
- ; Now see if it all fits in available memory
- ;
- ; Note that carry flag = 0 from the above RR E
- ; since # direc entries is always a multiple of 4.
- ; Thus I don't need to go:
- ;
- ; OR A ; clear carry
- ;
- SBC HL,DE
- JR C,NOMEM ; If need > space then process exception.
- LD (NUMDIRRECS),DE ; Save needed recs as num to process. This
- JP BYESETUP ; Finally synchronizes NUMDIRRECS and NUMFNAMES.
-
- NOMEM: LD HL,(NUMDIRRECS) ; Recall available space (in records).
- ADD HL,HL
- ADD HL,HL ; Now HL = available space (in direc entries).
- LD (NUMFNAMES),HL ; Save new num dirc entries. This finally
- LD C,PRINT ; Synchronizes NUMDIRRECS and NUMFNAMES.
- LD DE,LACKMEMORY ; Warn user we'll do only as much as we can.
- CALL BDOS ; BDOS will return for me.
-
- BYESETUP:
-
- ;
- ;=======================================================================
- ;
-
- GETDIR: CALL RDDIR ; Read in the directory entries.
-
- ;
- ;=======================================================================
- ;
- ; CLEAN out the erased file entries to all E5's.
- ;
- ; While we're at it, move all empty entries to the bottom of the buffer.
- ; This way we can avoid adding them to the sort's work. For large underused
- ; directories (such as on my hard disk) this can speed up the sort
- ; substantially.
- ;
- ; The dummy entries before and after the buffer are generated to prevent this
- ; algorithm from leaving the buffer's boundaries. When we are scanning backward
- ; with the right pointer looking for a non-empty entry we must guard against
- ; the chance that all entries are empty. Similarly, when we scan forward with
- ; the left pointer looking for empty entries we must guard against the chance
- ; that all entries are non-empty.
- ;
-
- CLEAN: ; First we need to create a dummy non-empty record before BUF, and a
- ; Dummy empty record at end of buffer.
- LD A,0FFH
- LD (BUF-ENTRYLEN),A ; Mark a dummy entry as not deleted.
-
- IF DELZRO
- LD (BUF-ENTRYLEN+15),A ; And as having >0 number of records.
- ENDIF
-
- LD HL,(NUMFNAMES)
- ADD HL,HL ; Take advantage of ENTRYLEN = 32 = 2 ^ 5.
- ADD HL,HL
- ADD HL,HL
- ADD HL,HL
- ADD HL,HL ; Compute HL = NUMFNAMES * 32.
- LD DE,BUF
- ADD HL,DE ; Now HL = 1st entry after end of buffer.
- LD A,0E5H ; Needed at the entry point.
- ; Note that if .NOT.DELZRO then this register
- ; Will be preserved throughout the routine!
- LD (HL),A ; Mark as a dummy empty record.
- LD BC,-ENTRYLEN
- ADD HL,BC ; Now HL = last entry = BUF + 32*(NUMFNAMES-1).
- ; DE = 1st entry = BUF.
- JP CLNENTRY ; Jump to entry point within the big loop.
-
- ;
- ;-----------------------------------------------------------------------
- ;
- ; Swap left and right entries.
- ; DE = right = non-empty entry.
- ; HL = left = empty entry.
- ;
-
- CLSWAP: PUSH DE ; Save right pointer.
- EX DE,HL
- LD BC,ENTRYLEN
- LDIR ; Left <== Right. Now DE = left + 32.
- POP HL ; Recall right pointer.
- ; To finish the swap drop into FILLE5.
- ;
- ;
- ;-----------------------------------------------------------------------
- ;
- ; Here we clear out the entry at (HL).
- ;
-
- FILLE5: LD B,ENTRYLEN ; Number of bytes to clear
-
- IF DELZRO ; The cond. code for DELZRO won't preserve A.
- LD A,0E5H ; Load up char to replicate.
- ENDIF
-
- FILLOP: LD (HL),A
- INC HL
- DJNZ FILLOP
-
- ;
- ; Now we need to continually back up the right pointer as long as the entries
- ; are empty. I.e., we need to search for the 1st non-empty entry from the
- ; right.
- ;
- LD BC,-(ENTRYLEN*2) ; FILLE5 made HL = right + 32.
- ADD HL,BC ; Now HL = right - 32.
-
- CLNENTRY:
-
- CP (HL) ; Is the right pointer at an empty entry?
- JP Z,FILLE5 ; If so then clear it.
-
- ;
- ; This is all conditional code to implement DELZRO and SAVDASH.
- ;
-
- IF DELZRO
- PUSH HL ; Save right pointer.
- ENDIF
-
- IF DELZRO.AND.(.NOT.ONLY14)
- LD BC,14
- ADD HL,BC
- LD A,(HL) ; Get s2 byte (extended rc).
- AND 0FH ; For CP/M 2.2, 0 for CP/M 1.4
- INC HL
- OR (HL) ; Check record count field.
- ENDIF
-
- IF DELZRO.AND.ONLY14
- LD BC,15
- ADD HL,BC
- LD A,(HL) ; Check record count field.
- OR A
- ENDIF
-
- IF DELZRO
- POP HL ; Recall right pointer. (Flags unaffected)
- ENDIF
-
- IF DELZRO.AND.(.NOT.SAVDASH)
- JR Z,FILLE5 ; IF record count = 0 then delete it.
- ENDIF
-
- IF DELZRO.AND.SAVDASH
- JP NZ,NEXTLFT ; If record count <> 0 then don't delete.
- INC HL
- LD A,(HL) ; Get first character of filename.
- DEC HL ; Now HL is start of entry.
- CP '-' ; Don't delete files with '-' as 1st char.
- JR NZ,FILLE5
- ENDIF
-
- ;
- ;-----------------------------------------------------------------------
- ;
- ; Now we have HL = right = non-empty record. So keep bumping the left pointer
- ; until we find an empty record to trade with. Note that DE = next left, so
- ; check the current record at DE first.
- ;
-
- NEXTLFT:
-
- EX DE,HL ; Now HL = left, and DE = right.
-
- IF .NOT.DELZRO ; If we don't need to delete 0 length files,
- LD BC,ENTRYLEN ; Then pull this constant out of the loop.
- ENDIF
-
- JP LFTENTRY ; Skip bumping the left pointer.
-
- LFTLOOP:
-
- IF DELZRO ; The conditional code for DELZRO will not
- LD BC,ENTRYLEN ; Preserve this register pair.
- ENDIF
-
- ADD HL,BC ; Bump left pointer by an entry.
-
- LFTENTRY:
-
- IF DELZRO ; The conditional code for DELZRO will not
- LD A,0E5H ; Preserve this register.
- ENDIF
-
- CP (HL) ; Is it marked for deletion?
-
- IF .NOT.DELZRO
- JP NZ,LFTLOOP
- ENDIF
- ;
- ; The following is all conditional code to handle DELZRO and SAVDASH.
- ;
- IF DELZRO
- JR Z,LFTFND ; If marked for deletion then we're done.
- PUSH HL ; Save left pointer.
- ENDIF
-
- IF DELZRO.AND.(.NOT.ONLY14)
- LD BC,14
- ADD HL,BC
- LD A,(HL) ; Get s2 byte (extended rc).
- AND 0FH ; For CP/M 2.2, 0 for CP/M 1.4
- INC HL
- OR (HL) ; Check record count field.
- ENDIF
-
- IF DELZRO.AND.ONLY14
- LD BC,15
- ADD HL,BC
- LD A,(HL) ; Check record count field.
- OR A ; Is A = 0 ?
- ENDIF
-
- IF DELZRO
- POP HL ; Recall left pointer. (Flags unaffected)
- JP NZ,LFTLOOP ; If record count <> 0 then it's not empty.
- ENDIF
-
- IF DELZRO.AND.SAVDASH
- INC HL
- LD A,(HL) ; Get first character of filename.
- DEC HL ; Now HL is start of entry.
- CP '-' ; Don't delete files with '-' as 1st char.
- JR Z,LFTLOOP ; If '-' is 1st char then it's not empty to us.
- ENDIF
-
- ;
- ;-----------------------------------------------------------------------
- ;
- ; Now we have HL = left = an empty entry, and DE = right = a non-empty record.
- ; Check if right address < left address. (Note that DE = HL is impossible.)
- ;
-
- LFTFND: LD A,E ; Do a CP DE,HL (as if it existed).
- SUB L
- LD A,D
- SBC A,H
- JP NC,CLSWAP ; If left < right then we're ok, do the swap.
-
- ; Ok, now we need to compute the minimum NUM2DO and return.
- ; DE = last non-empty entry, HL = DE + 32 = 1st empty entry.
- LD DE,-BUF
- ADD HL,DE ; Now HL = # bytes in buffer to sort.
-
- ; Now compute HL = HL / 32 quickly.
- ; Note that HL is a multiple of 32.
- OR A ; Clear carry.
- LD A,H ; This will allow me to use RRA several times.
- RRA
- RR L ; By 2.
- RRA
- RR L ; By 4.
- RRA
- RR L ; By 8.
- RRA
- RR L ; By 16.
- RRA
- RR L ; By 32.
- LD H,A
- LD (NUM2DO),HL ; Now we won't have to add the overhead of the
- ; Empty entries to the sort routine.
-
- BYECLEAN: ; This symbol is useful for debugging.
-
- ;
- ;=======================================================================
- ;
- ; SORT the directory with a Shell-Metzner sort.
- ;
- ; Brief Synopsis:
- ;
- ; A shell sort works by comparing entries that are far apart (by INXOFFSET)
- ; and successively shrinking the offset (by a factor of 2 at each iteration)
- ; until the sort degenerates into a simple version of an insert sort. There is
- ; a notion of a "left" and a "right" pointer at all times. In general, the
- ; current "left" pointer = LFTPTR, and the current "right" pointer = LFTPTR +
- ; PTROFFSET. The "left" entry is analagous to the higher entry in the sorted
- ; list. The index variables are used for counting and determining how many
- ; more entries need to be compared against at the current INXOFFSET value.
- ;
-
- SORT: XOR A
- LD (NOSWAP),A ; Zero the flag in case already sorted.
- LD C,PRINT
- LD DE,SORTING
- CALL BDOS
- LD HL,(NUM2DO) ; Get # direc entries to process.
- JP SRTENTRY ; Skip the next instruction and go.
-
- ;
- ;-----------------------------------------------------------------------
- ;
- ; Now divide index offset size by 2.
- ;
-
- DIVIDE: LD HL,(INXOFFSET)
-
- SRTENTRY:
-
- SRL H
- RR L ; Now HL = HL / 2
- LD (INXOFFSET),HL
- LD A,L
- OR H
- JP Z,BYESORT ; If INXOFFSET=0 then we're done.
-
- EX DE,HL ; DE = INXOFFSET.
- LD HL,(NUM2DO) ; Get # direc entries to process.
- SCF ; Set carry flag.
- SBC HL,DE
- LD (MAXINX),HL ; Store (NUM2DO-1) - INXOFFSET.
- ; The -1 part is to make the index 0 relative.
- ; Thus our 0 relative indexes will all be
- ; Consistent.
- LD HL,0
- LD (CURINX),HL
- LD (SAVINX),HL
- EX DE,HL ; Now HL = INXOFFSET.
- ADD HL,HL ; Take advantage of ENTRYLEN = 32 = 2 ^ 5.
- ADD HL,HL
- ADD HL,HL
- ADD HL,HL
- ADD HL,HL ; Now HL = INXOFFSET * 32.
- LD (PTROFFSET),HL
- LD HL,BUF ; Load initial LFTPTR.
-
- ;
- ;-----------------------------------------------------------------------
- ;
- ; On entry to NDONE we have HL = next left pointer.
- ; On entry to NDONE1 we also have DE = (PTROFFSET).
- ;
-
- NDONE: LD (SAVLFT),HL
- LD DE,(PTROFFSET)
-
- NDONE1: LD (LFTPTR),HL ; This is an alternate entry point for SWITCH.
- EX DE,HL
- ADD HL,DE ; Now HL = right, DE = left.
-
- LD B,ENTRYLEN
- CMPARE: LD A,(DE)
- AND 7FH
- LD C,A ; C = (DE) AND 7FH
- LD A,(HL)
- AND 7FH ; A = (HL) AND 7FH
- CP C ; Form (HL) - (DE) == (right) - (left).
-
- IF ASCENDING
- JP C,SWITCH ; If (right) < (left) then switch.
- JR Z,EQUAL
- ENDIF
-
- IF .NOT.ASCENDING
- JR Z,EQUAL
- EX AF,AF' ; Save carry flag.
- LD A,B ; Get loop counter.
- CP ENTRYLEN ; Are we looking at the 1st byte of entry?
- JR Z,CP1ST ; User area byte must be compared ascending.
- EX AF,AF'
- JP C,NOSWITCH ; If (right) < (left) then don't switch.
- JP SWITCH
-
- CP1ST: EX AF,AF'
- JP C,SWITCH ; If (right) < (left) then switch.
- ENDIF
-
- ;
- ;-----------------------------------------------------------------------
- ;
- ; Either drop into here or jump in from SWITCH or from above if descending sort.
- ;
-
- NOSWITCH:
- LD HL,(SAVINX)
- INC HL
- LD (SAVINX),HL
- LD (CURINX),HL
- EX DE,HL ; Now DE = CURINX
- LD HL,(MAXINX)
- LD A,L ; Now do a CP HL,DE (as if it existed).
- SUB E
- LD A,H
- SBC A,D
- JR C,DIVIDE ; IF CURINX > MAXINX then DIVIDE.
- LD HL,(SAVLFT)
- LD DE,ENTRYLEN
- ADD HL,DE ; Bump left by 32 bytes.
- JP NDONE
-
- ;
- ;-----------------------------------------------------------------------
- ;
-
- EQUAL: INC HL
- INC DE
- DJNZ CMPARE ; Keep checking each byte of entry.
- JP NOSWITCH ; If equal then don't switch.
-
- ;
- ;-----------------------------------------------------------------------
- ;
- ; Note that on entry B contains the number of chars we need to move.
- ;
-
- SWITCH: LD A,0FFH
- LD (NOSWAP),A ; Mark that we've switched something once.
- LD DE,(LFTPTR) ; Get the left pointer,
- LD HL,(PTROFFSET) ; And the offset from left to the right ptr.
- ADD HL,DE ; Now HL = right, DE = left.
- LD B,ENTRYLEN ; Length of entry to swap.
-
- SWLOOP: LD C,(HL)
- LD A,(DE)
- LD (HL),A ; (HL) <== (DE)
- LD A,C
- LD (DE),A ; (HL) ==> (DE)
- INC HL
- INC DE ; Bump both pointers.
- DJNZ SWLOOP
-
- LD HL,(CURINX)
- LD DE,(INXOFFSET)
- OR A ; Clear carry.
- SBC HL,DE
- JR C,NOSWITCH ; A bug fix for SAP 46, traces back to 43.
- ; If CURINX-INXOFFSET < 0 then NOSWITCH.
- LD (CURINX),HL ; Now CURINX = CURINX - INXOFFSET.
- LD HL,(LFTPTR)
- LD DE,(PTROFFSET)
- ;
- ; Since we just did a conditional jump on carry set we know that when we
- ; are here we have carry clear.
- ;
- ; OR A ; Clear carry.
- ;
- SBC HL,DE ; Now HL = left = LFTPTR - PTROFFSET.
- JP NDONE1
-
- BYESORT: ; This is the sort's procedure exit location.
-
- ;
- ;=======================================================================
- ;
- ; PACK the directory entries.
- ;
-
- PACK: LD HL,0 ; I = 0
- LD BC,BUF+9 ; This is a constant taken out of the loop.
-
- PACK1: PUSH HL ; Save index i.
- ADD HL,HL
- ADD HL,HL
- ADD HL,HL
- ADD HL,HL
- ADD HL,HL ; Compute HL = 32 * i
- ADD HL,BC ; Now HL = buf + 9 + 32 * i = addr of file type.
-
- LD A,(HL) ; Jump if filetype not 'x??'.
- SUB '0'
- JR C,PACK2
- CP 10
- JP NC,PACK2
- EX AF,AF' ; Save extent number x in A'.
-
- LD A,'$' ; Make sure file type is '.x$$'.
- INC HL
- CP (HL)
- JP NZ,PACK2 ; If not '$' then next entry.
- INC HL
- CP (HL)
- JR NZ,PACK2 ; If not '$' then next entry.
-
- INC HL ; Bump to extent number field.
- EX AF,AF' ; Recall x.
- LD (HL),A ; Set extent number to x.
- DEC HL
- DEC HL
- DEC HL ; Point back to the x.
- LD (HL),'$' ; Make file type .$$$ once again.
-
- PACK2: POP HL ; Recall index i.
- INC HL
- LD DE,(NUM2DO) ; Skip the empty entries at end of buffer.
- LD A,E ; Now do a CP DE,HL (as if it existed).
- SUB L
- LD A,D
- SBC A,H
- JP NZ,PACK1 ; Loop until i = # file names to process.
-
- BYEPACK: ; This convenient symbol helps in debugging.
-
- ;
- ;=======================================================================
- ;
- ; Now write the directory back and finish up. The PUTDIR symbol is only used
- ; for debugging purposes - nothing actually references it.
- ;
-
- PUTDIR: CALL WRDIR ; Write the modified directory to disk.
- LD DE,FINISHED ; Drop into PRLAST to finish up.
-
- ;
- ;=======================================================================
- ;
- ; Print the message pointed to by DE and terminate.
- ; This routine is used to compress needless code repetition.
- ;
-
- PRLAST: LD C,PRINT
- CALL BDOS
- JP BOOT
-
- ;
- ;=======================================================================
- ;
- ; READ DIRECTORY entry point.
- ;
-
- RDDIR: LD C,PRINT
- LD DE,READING ; Tell user we're about to read the directory.
- CALL BDOS
- XOR A ; A=0 to indicate directory read.
- JP DODIR ; Enter main directory routines.
-
- ;
- ; WRITE DIRECTORY entry point.
- ;
-
- WRDIR: LD A,(NOSWAP)
- OR A ; Is noswap = 0?
- JP NZ,WRDIR1 ; If not zero then needed sorting,
- LD C,PRINT
- LD DE,PREVIOUS ; Else tell user no swaps were needed.
- CALL BDOS
-
- WRDIR1: LD C,PRINT
- LD DE,WRITING ; Tell user we're now writing the directory.
- CALL BDOS
- LD A,1 ; A <> 0 signals writes instead of reads.
- ; Fall into DODIR.
-
- ;
- ;=======================================================================
- ;
- ; The main read/write directory routine.
- ;
-
- DODIR: LD (RWFLAG),A ; Save read/write flag.
- LD BC,(SYSTRK) ; Get track num of directory.
- LD (TRACK),BC ; Save as current track.
- CALL SETTRK
- LD HL,0
- LD (RECORD),HL ; Set current record to 0.
- LD HL,(NUMDIRRECS)
- LD (DIRCNT),HL ; Init loop counter.
- LD HL,BUF
- LD (DMAPTR),HL ; Start at buf for dma.
-
- DIRLOP: LD BC,(RECORD)
- INC BC ; Bump to next record.
- LD HL,(SPT) ; Get num records per track.
- LD A,L ; Now do a CP HL,BC (as if it existed).
- SUB C
- LD A,H
- SBC A,B
- JP NC,NOTROV ; If spt >= record then we're ok,
- ; Else we drop into track bumping.
-
- LD BC,(TRACK) ; Track overflow, bump to next.
- INC BC
- LD (TRACK),BC
- CALL SETTRK
- LD BC,1 ; Rewind record number to start of track.
-
- NOTROV: LD (RECORD),BC ; Save computed record number.
- DEC BC ; Make relative to 0 instead of to 1.
- LD DE,(RECTBL)
- CALL RECTRN ; Returns HL = physical record number.
-
- IF UNSPECI
- LD B,H
- LD C,L ; SETREC needs BC = record number.
- LD A,(VERFLG)
- OR A
- CALL NZ,SETREC ; If CP/M 2.2 then call SETREC.
- ENDIF
-
- IF ONLY22
- LD B,H
- LD C,L ; SETREC needs BC = record number.
- CALL SETREC
- ENDIF
-
- LD BC,(DMAPTR)
- CALL SETDMA
- LD A,(RWFLAG) ; Are we reading the directory, or writing it?
- OR A
- JR NZ,DWRT
-
- ; Read the directory.
- CALL READ
- OR A ; Test flags on read.
- JP Z,MORE ; If 0 then ok, else . . . .
-
- LD DE,RDERR ; Oops, a read error.
- JP PRLAST ; Print message and die.
-
- ; Write the directory.
- DWRT: LD C,1 ; For CP/M 2.2 deblocking BIOS's.
- CALL WRITE
- OR A ; Test flags on write.
- JR NZ,BADWRT ; If A <> 0 then an error.
-
- ; The read or write succeeded.
- MORE: LD HL,(DMAPTR)
- LD DE,128
- ADD HL,DE
- LD (DMAPTR),HL ; Bump dma address for next pass
- LD HL,(DIRCNT)
- DEC HL
- LD (DIRCNT),HL ; Count down entries.
- LD A,H
- OR L
- JP NZ,DIRLOP ; Loop till zero left,
- RET ; And then we're done.
-
- ; Come here if we get a write error.
- BADWRT: LD DE,WRTERR
- JP PRLAST ; Print message and die.
-
- ;
- ;=======================================================================
- ;
- ; Various Messages
- ;
-
- IDENTITY:
- DEFB CR,LF,'Sort and Pack Directory v'
- DEFB '50 8/7/86',CR,LF,EOS
-
- READING:
- DEFB LF,'---> Reading, ',EOS
-
- SORTING:
- DEFB 'Sorting',EOS
-
- PREVIOUS:
- DEFB ', (Previously Sorted)',EOS
-
- WRITING:
- DEFB ', Writing',EOS
-
- FINISHED:
- DEFB ', done'
- DEFB CR,LF,EOS
-
- RDERR:
- DEFB CR,LF,'++ Read Error - no change made ++',CR,LF,EOS
-
- WRTERR:
- DEFB CR,LF,'++ Write Error '
- DEFB '- directory left in unknown condition ++',CR,LF,EOS
-
- IF UNSPECI.AND.(.NOT.CPMONLY)
- BADOPSYS:
- DEFB LF,'++ SAP not useable with MP/M or CP/M 3.0 ++',CR,LF,EOS
- ENDIF ; UNSPECI AND (NOT CPMONLY)
-
- LACKMEMORY:
- DEFB LF,'++ Directory too large - '
- DEFB 'SAP will process as much as possible. ++',CR,LF,EOS
-
- BADDRIVE:
- DEFB LF,'++ Only drives A through ',MAXDRIVE,' are valid ++'
- DEFB CR,LF,EOS
- ;
- ;=======================================================================
- ;
- ; Stack and Buffer Area.
- ;
-
- DEFS 4+ENTRYLEN ; Minimum stack depth (of 2), plus a
- ; Dummy entry used for CLEAN.
- ; Note that BDOS will switch to its own
- ; Stack when called, so this is
- ; Enough.
-
- EVEN EQU (($+255)/256)*256 ; Start buffer on even page, which also
- ; Increases stack area greatly.
- ORG EVEN
- STACK EQU $-ENTRYLEN ; Note that stacks grow downward.
- BUF EQU $
-
- ;
- ;=======================================================================
- ;
- ; Variable Area.
- ;
-
- ORG CMDBUF ; The CP/M command line buffer is convenient.
- ; This gives me 128 bytes of free storage!
-
- ;
- ; The BIOS vectors we use.
- ;
- SELDSK: DEFS 3
- SETTRK: DEFS 3
- SETREC: DEFS 3
- SETDMA: DEFS 3
- READ: DEFS 3
- WRITE: DEFS 3
- LSTS: DEFS 3 ; Only in CP/M 2.2 (not used here)
- RECTRN: DEFS 3 ; Only in CP/M 2.2
-
- IF UNSPECI
- VERFLG EQU LSTS ; Squeeze him in where he fits!
- ENDIF
-
- NUMDIRRECS EQU LSTS+1 ; Squeeze him in where he fits!
-
- ;
- ; Disk parameter block vars.
- ;
- SPT: DEFS 2 ; Sectors per track
- DRM: DEFS 2 ; # direc entries - 1, before calcspace
- SYSTRK: DEFS 2 ; # reserved tracks = 1st direc track
- RECTBL: DEFS 2 ; Logical ==> physical, record translation table addr
- NUMFNAMES EQU DRM ; This is drm + 1 = # direc entries, after calcspace.
-
- ;
- ; Temp vars for reads/writes.
- ;
- RWFLAG: DEFS 1
- DIRCNT: DEFS 2
- DMAPTR: DEFS 2
- RECORD: DEFS 2
- TRACK: DEFS 2
-
- ;
- ; Temp vars for sorting.
- ;
- NOSWAP: DEFS 1 ; Flag: 00h = no swaps, 0FFh = some swaps.
- NUM2DO: DEFS 2 ; Number of entries to sort.
- MAXINX: DEFS 2 ; Maximum left pointer value.
- SAVLFT: DEFS 2 ; Save for left pointer.
- LFTPTR: DEFS 2 ; Current left pointer.
- SAVINX: DEFS 2 ; Save for entry index.
- CURINX: DEFS 2 ; Current entry index.
- INXOFFSET: DEFS 2 ; Index offset (or comparison distance).
- PTROFFSET: DEFS 2 ; Pointer offset = entrylen * INXOFFSET.
-
- END