home *** CD-ROM | disk | FTP | other *** search
- ; SDD - Super Duper Directory program
- ; Version 1.02 by "ESKAY"
- ;
- ; NOTE:
- ; This program is not meant to be competition for the SDxxx
- ; series. Rather, it is intended to be what SD was before it
- ; got out of hand --- a small, fast directory display program
- ; for everyone using CP/M.
- ; I have decided to write this program in such a way that
- ; anyone with MAC (maybe even ASM -- I don't know) can modify,
- ; edit and reassemble it. The code is very well commented
- ; except for some "canned" routines out of my software library.
- ;
- ; A WORD AS TO CODE SIZE...
- ; One of SD's original authors mentioned the fact that it was
- ; meant to be less than 2k (look where it's now...), so SDD will
- ; be kept below 2k and will be coded to have only a minimum
- ; of "frills". If you in any way modify this program, PLEASE
- ; keep the code size below 2k.
- ; In a CP/M environment, SDD will always preserve the resident
- ; CCP by returning to the caller's stacked return address.
- ; Users of large CP/M directories should not be concerned about
- ; overflowing the TPA; even in a small 32k TPA, over 3000
- ; file names can be processed.
- ;
- ; +------------------+
- ; | REVISION HISTORY |
- ; +------------------+
- ;
- ; 07/28/85 v1.00 Created (Big Bang)
- ; 08/03/85 v1.01 Sent out into the world to conquer...
- ; 08/04/85 V1.02 Added check for option only (as in SDD $K)
- ;
- ; +-----------------+
- ; | GENERAL EQUATES |
- ; +-----------------+
- ;
- CR EQU 0DH
- LF EQU 0AH
- ODELIM EQU '$' ; option delimiter
- COLS EQU 4 ; number of columns per screen
- ROWS EQU 24 ; number of lines per screen
- ;
- ; +--------------------------+
- ; | OPERATING SYSTEM EQUATES |
- ; +--------------------------+
- ;
- ORG 100H
- ;
- BDOS EQU 5 ; function entry point
- DFCB EQU 5CH ; default FCB
- DBUF EQU 80H ; default buffer
- ;
- COUT EQU 2 ; console output
- LOUT EQU 5 ; list output
- DCIO EQU 6 ; direct console IO
- PSTR EQU 9 ; print string
- VERSN EQU 12 ; version number
- SELDK EQU 14 ; select disk
- SEARF EQU 17 ; search for first
- SEARN EQU 18 ; search for next
- CURDK EQU 25 ; return current disk
- GETDPB EQU 31 ; get disk parameter block
- GSUSR EQU 32 ; get/set user number
- FSIZE EQU 35 ; compute file size
- ;
- ; +----------------------+
- ; | START OF THE PROGRAM |
- ; +----------------------+
- ;
- SDD: LXI H,0 ; clear HL
- DAD SP ; get stack pointer
- SHLD STKSAV ; save it
- LXI SP,STACK ; set up new stack pointer
- CALL INIT ; initialize
- CALL PREPFN ; prepare optional filename
- CALL SETOPT ; set options
- CALL LODBUF ; load buffer with directory data
- CALL SORTBF ; sort the buffer
- CALL DSPBUF ; display the buffer
- CALL DSPSTA ; display statistics
- QUIT: LHLD STKSAV ; get caller stack back
- SPHL ; set up entry stack
- RET ; and return to caller
- ;
- ; +--------------------+
- ; | INITIALIZE PROGRAM |
- ; +--------------------+
- ;
- INIT: MVI A,0FFH
- STA BUFFER
- MVI C,CURDK ; get current drive
- CALL BDOS
- STA CDRIV ; save it
- MVI C,GSUSR ; get current user
- MVI E,0FFH
- CALL BDOS
- STA CUSER ; save it
- MVI C,VERSN ; get CP/M version
- CALL BDOS
- MOV A,H ; get MP/M flag
- ORA A ; test for MP/M
- MOV A,L ; get BDOS version
- JZ NMPM ; skip if not MP/M
- MVI A,30H ; set flag
- NMPM: STA CPMV ; store CP/M version
- RET ; and return
- ;
- ; +---------------------------------+
- ; | PREPARE INPUT FILENAME FOR SCAN |
- ; +---------------------------------+
- ;
- PREPFN: MVI A,0FFH ; Set default disk and user
- STA DISK
- STA USER
- LXI H,DBUF ; point to command line
- MOV A,M ; get length
- INX H ; point to first char of cl
- SHLD TEMP1 ; save cl pointer
- ORA A ; anything typed at all?
- JZ NTYPD ; nothing typed
- SKLB: MOV A,M ; get char
- CPI ' ' ; blank?
- JNZ NBL ; no
- INX H
- JMP SKLB
- ;
- NBL: LXI D,DFCB ; point to default fcb
- CALL FNAME ; parse the file name
- MVI A,1 ; set error code
- JZ ERROR
- LDA DFCB+1 ; check for empty fn
- CPI '$' ; option only?
- JZ NTYPD ; yes (ignore rare case of fn with $)
- SHLD TEMP1 ; save cl pointer
- CPI ' ' ; blank?
- RNZ ; no, all ok
- NTYPD: LXI H,DFCB+1 ; fill with "?"
- MVI B,11
- MKWLD: MVI M,'?'
- INX H
- DCR B
- JNZ MKWLD
- RET
- ;
- ; +---------------------+
- ; | GET AND SET OPTIONS |
- ; +---------------------+
- ;
- SETOPT: LHLD TEMP1 ; get cl pointer
- MVI B,ODELIM ; get delimiter
- SRHOPT: MOV A,M ; get byte
- INX H
- ORA A ; end of line?
- RZ ; yes, return
- CMP B ; delimiter?
- JZ FNDDEL ; yes
- JMP SRHOPT
- ;
- FNDDEL: LXI D,OPTNS ; DE points to options list
- GNOPT: LDAX D ; get an option
- CPI 0FFH ; all options checked?
- JZ NXTBOP ; yes, check next byte
- CMP M ; match?
- JZ GOPTN ; yes
- INX D ; get next option
- JMP GNOPT
- ;
- GOPTN: XRA A ; else mark that option
- STAX D
- NXTBOP: MOV A,M ; get byte
- ORA A ; end of line?
- RZ ; yes
- INX H
- JMP FNDDEL ; go check next byte
- ;
- ; +-----------------------------+
- ; | LOAD BUFFER WITH FILE NAMES |
- ; +-----------------------------+
- ;
- LODBUF: LDA DISK ; get target drive
- DCR A ; make 0..15
- JM SAMEDR ; skip if same drive
- MOV E,A
- MVI C,SELDK
- CALL BDOS
- ;
- ; WHILE WE'RE AT IT, GET DPB
- ;
- SAMEDR: MVI C,GETDPB
- CALL BDOS
- INX H
- INX H
- MOV A,M ; get BSH
- STA BLSHFT
- INX H
- MOV A,M ; get BLM
- STA BLMASK
- INX H
- INX H
- MOV E,M
- INX H
- MOV D,M
- XCHG
- SHLD NUMBLK ; store disk size
- XCHG
- INX H
- MOV E,M
- INX H
- MOV D,M
- XCHG
- SHLD DIRSZ ; store directory size
- LDA USER ; get target user
- MOV E,A
- INR A
- JZ SAMEUS ; skip if no change
- MVI C,GSUSR
- CALL BDOS
- SAMEUS: LXI D,DFCB ; point to filename
- MVI C,SEARF ; search for first
- CALL BDOS
- CPI 0FFH ; if first fails, then no file
- JNZ FRSTOK ; else ok
- MVI A,2 ; error code
- JMP ERROR
- ;
- FRSTOK: CALL MOVEFN ; move filename
- LXI D,DFCB ; point to filename
- MVI C,SEARN ; search for next
- CALL BDOS
- CPI 0FFH
- RZ ; done!
- JMP FRSTOK ; else loop
- ;
- MOVEFN: LXI H,DBUF
- LXI D,20H
- CPL: DCR A
- JM CPLE
- DAD D
- JMP CPL
- ;
- CPLE: PUSH H
- MVI B,12
- SHBL: MOV A,M
- ANI 7FH
- MOV M,A
- INX H
- DCR B
- JNZ SHBL
- POP D ; get filename ptr
- LHLD BUFPTR ; get buffer ptr
- MOV A,M ; get a byte
- LXI H,BUFFER
- SRHBFL: CPI 0FFH ; end of buffer?
- JZ MOVNOW ; yes
- CALL CPDEHL ; duplicate?
- RZ ; yes, go get next
- LXI B,12 ; advance ptr
- DAD B
- MOV A,M
- JMP SRHBFL
- ;
- MOVNOW: LHLD BUFPTR
- MVI B,12
- MOVLP: LDAX D
- MOV M,A
- INX D
- INX H
- DCR B
- JNZ MOVLP
- SHLD BUFPTR
- MVI M,0FFH
- LHLD NMBFLS
- INX H
- SHLD NMBFLS
- RET
- ;
- ; +-----------------------+
- ; | SORT FILE NAME BUFFER |
- ; +-----------------------+
- ;
- SORTBF: LDA SOPT ; sort off?
- ORA A
- RZ ; do not sort
- LHLD NMBFLS ; get number of files
- MOV B,H ; into BC
- MOV C,L
- LXI D,12 ; 12 characters per field
- LXI H,BUFFER ; point to buffer
- ;
- ; SHELL-METZNER SORT
- ; Call with the following information:
- ;
- ; BC = Number of records to be sorted
- ; DE = Record length
- ; HL = Buffer address
- ;
- SORT: SHLD SSTADR
- PUSH H
- XCHG
- SHLD SRECLEN
- PUSH H
- MOV H,B
- MOV L,C
- SHLD SNUMRT
- SHLD SNUMRW
- ;
- ; NOW DIVIDE # OF FIELDS BY 2
- ;
- DIVIDE: LHLD SNUMRW ; GET VALUE
- CALL DIVBY2 ; DIVIDE BY 2
- SHLD SNUMRW ;SAVE RESULT
- MOV A,L ;IF SNUMRW<>0
- ORA H ; THEN
- JNZ NOTDONE ; NOT DONE
- ;
- ; ALL FIELDS SORTED
- ;
- POP B ;CLEAN UP STACK
- POP D
- RET
- ;
- NOTDONE:XCHG
- LHLD SNUMRT
- MOV A,L
- SUB E
- MOV L,A
- MOV A,H
- SBB D
- MOV H,A
- SHLD SRECLEN
- LXI H,1
- SHLD SORTV1
- SHLD SSTADR
- DCR L
- POP B
- PUSH B
- NDONE1: DAD D
- DCX B
- MOV A,B
- ORA C
- JNZ NDONE1
- SHLD SORTV2
- XCHG
- POP B
- POP H
- PUSH H
- PUSH B
- NDONE2: SHLD SORTV4
- SHLD SORTV3
- XCHG
- DAD D
- XCHG
- COMPRE: POP B
- PUSH B
- COMPR1: LDAX D
- SUB M
- JNZ NOTEQU
- INX H
- INX D
- DCX B
- MOV A,B
- ORA C
- JNZ COMPR1
- JMP NOSWITCH
- ;
- NOTEQU: JNC NOSWITCH
- SWITCH: PUSH B
- MOV B,M
- LDAX D
- MOV M,A
- MOV A,B
- STAX D
- INX H
- INX D
- POP B
- DCX B
- MOV A,B
- ORA C
- JNZ SWITCH
- LHLD SNUMRW
- MOV A,H
- CMA
- MOV D,A
- MOV A,L
- CMA
- MOV E,A
- LHLD SORTV1
- DAD D
- JNC NOSWITCH
- INX H
- SHLD SORTV1
- LHLD SORTV3
- XCHG
- LHLD SORTV2
- MOV A,E
- SUB L
- MOV L,A
- MOV A,D
- SBB H
- MOV H,A
- SHLD SORTV3
- JMP COMPRE
- ;
- NOSWITCH:
- LHLD SSTADR
- INX H
- SHLD SSTADR
- SHLD SORTV1
- XCHG
- LHLD SRECLEN
- MOV A,L
- SUB E
- MOV A,H
- SBB D
- JC DIVIDE
- LHLD SORTV4
- POP D
- PUSH D
- DAD D
- XCHG
- LHLD SORTV2
- XCHG
- JMP NDONE2
- ;
- ; UTILITY SUBTRACTION SUBROUTINE...
- ; HL=HL-DE
- ;
- SUBDE: MOV A,L
- SUB E
- MOV L,A
- MOV A,H
- SBB D
- MOV H,A
- RET
- ;
- ; +-------------------------+
- ; | DISPLAY BUFFER CONTENTS |
- ; +-------------------------+
- ;
- DSPBUF: CALL CRLF ; new line
- LXI H,BUFFER ; load buffer ptr
- SHLD BUFPTR
- DSPBL1: MVI A,ROWS-1 ; get lines/page
- STA CURROW ; save it
- DSPBL2: MVI A,COLS ; get number of columns
- STA CURCOL ; save it
- DSPBLP: LHLD BUFPTR ; get buffer pointer
- MOV A,M ; get byte
- CPI 0FFH ; end of buffer?
- RZ ; yes, return
- CALL PUTFN ; display filename
- SHLD BUFPTR ; save advanced pointer
- CALL DSPSZ ; display size
- LDA CURCOL ; get column
- DCR A ; count down
- STA CURCOL
- JNZ DSPBLP ; loop till done
- CALL CRLF ; new line
- LDA LOPT ; check if print
- ORA A
- JZ DSPBL2 ; yes, no paging
- LDA CURROW
- DCR A
- STA CURROW
- JNZ DSPBL2 ; keep on looping
- CALL CONTLP ; else get a character (any)
- JMP DSPBL1
- ;
- PUTFN: INX H
- MVI B,8 ; display file name
- CALL PUTFC
- MVI A,'.'
- CALL PUTCH
- MVI B,3
- PUTFC: MOV A,M
- CALL PUTCH
- INX H
- DCR B
- JNZ PUTFC
- RET
- ;
- DSPSZ: LDA KOPT ; check size option
- ORA A ; display without size?
- JZ NOSIZE ; yes, go display blanks
- LHLD BUFPTR ; point to next filename
- LXI D,-12 ; set up this filename's addr
- DAD D
- LXI D,DFCB ; destination = default FCB
- MVI B,12 ; 12 chars to move
- MVFNSZ: MOV A,M
- STAX D
- INX H
- INX D
- DCR B
- JNZ MVFNSZ ; loop till all moved
- LXI H,DFCB ; point to FCB
- MVI M,0 ; zero drive byte
- XCHG ; get FCB to DE
- MVI C,FSIZE ; get file size
- CALL BDOS
- LHLD DFCB+33 ; get sector count
- CALL SECTOK ; translate into 'k'
- XCHG ; move out of the way
- LHLD CUMSIZ ; get cumulative file size
- DAD D ; add this file
- SHLD CUMSIZ ; save it
- XCHG ; get this size back to HL
- CALL HEXDC1 ; convert to decimal
- MVI A,'k' ; print 'k'
- CALL PUTCH
- MVI B,2
- JMP DSPBNK
- ;
- NOSIZE: MVI B,7 ; number of blanks
- DSPBNK: MVI A,' ' ; a blank
- CALL PUTCH ; print it
- DCR B ; countdown
- JNZ DSPBNK ; do more
- MVI C,DCIO ; see if something typed
- MVI E,0FFH
- CALL BDOS
- CPI 3 ; a ^C?
- JZ EXIT ; yep, quit!
- CPI 'S'-40H ; A ^S?
- RNZ ; no, return
- ;
- ; wait for character
- ;
- CONTLP: MVI C,DCIO ; wait for any char
- MVI E,0FFH
- CALL BDOS
- ORA A ; anything typed?
- JZ CONTLP ; no, wait more
- CPI 3 ; abort now?
- RNZ ; no
- JMP EXIT
- ;
- SECTOK: LDA BLMASK ; get block mask
- MOV E,A ; set up DE...
- MVI D,0
- DAD D ; ..to add to HL
- CMA
- ANA L
- MOV L,A ; round off
- CALL DIVBY2 ; SEC/2
- CALL DIVBY2 ; SEC/4
- JMP DIVBY2 ; SEC/8 (K)
- ;
- ; +--------------------+
- ; | DISPLAY STATISTICS |
- ; +--------------------+
- ;
- DSPSTA: LDA CURCOL ; see if at end of line
- CPI 4
- CNZ CRLF ; new line if not
- LDA KOPT ; any sizes wanted?
- ORA A
- RZ ; no, return
- LHLD NMBFLS ; see if no files
- MOV A,H
- ORA L
- RZ ; no files, no message
- LXI D,SUMM1 ; send message
- CALL PRINTM
- MVI C,CURDK
- CALL BDOS
- ADI 'A'
- CALL PUTCH ; print drive
- MVI C,GSUSR
- MVI E,0FFH
- CALL BDOS ; get user
- MOV L,A
- MVI H,0
- CALL HEXDC2 ; print user
- LXI D,SUMM2
- CALL PRINTM
- LHLD NMBFLS ; get number of files
- CALL HEXDC1
- LXI D,SUMM3
- CALL PRINTM
- LHLD CUMSIZ ; get cumulative size
- CALL HEXDEC
- LXI D,SUMM4
- JMP PRINTM
- ;
- ; +-------------+
- ; | SUBROUTINES |
- ; +-------------+
- ;
- ; +-----------------------------+
- ; | CARRIAGE RETURN / LINE FEED |
- ; +-----------------------------+
- ;
- CRLF: MVI A,CR
- CALL PUTCH
- MVI A,LF
- ;
- ; +----------------------+
- ; | PRINT CHARACTER IN A |
- ; +----------------------+
- ;
- PUTCH: PUSH PSW
- PUSH B ; save registers
- PUSH D
- PUSH H
- MOV E,A ; character to E
- MVI C,COUT ; preload console out
- LDA LOPT ; test if list out
- ORA A
- JNZ PCH ; not list out - skip
- MVI C,LOUT ; load list out
- PCH: CALL BDOS ; do it
- POP H
- POP D
- POP B
- POP PSW
- RET
- ;
- ; THE FOLLOWING ROUTINE WAS WRITTEN BY RICHARD L CONN
- ;
- MAXDISK EQU 16 ; Maximum number of disks
- MAXUSER EQU 31 ; Maximum user number
- ;
- ; ON ENTRY, DE PTS TO FCB TO BE FILLED AND HL PTS TO FIRST BYTE OF
- ; TARGET STRING; FCB IS 36 BYTES LONG
- ; ON EXIT, B=DISK NUMBER (1 FOR A, ETC) AND C=USER NUMBER
- ; HL PTS TO TERMINATING CHAR
- ; A=0 AND Z SET IF ERROR IN DISK OR USER NUMBERS,
- ; A=0FFH AND NZ
- ; IF OK
- ;
- FNAME: PUSH D ; Save de
- MVI B,36 ; Initialize fcb
- PUSH D ; Save pointer
- XRA A ; A=0
- ;
- FNINI: STAX D ; Store zero
- INX D ; Point to next
- DCR B ; Count down
- JNZ FNINI
- POP D ; Get pointer back
- ;
- ; Scan for colon in string
- ;
- PUSH H ; Save pointer
- ;
- COLON: MOV A,M ; Scan fora colon or space
- INX H ; Point to next
- CPI ':' ; Colon found?
- JZ COLON1
- CPI ',' ; Comma found?
- JZ GETF1
- CPI ' '+1 ; Delimiter?
- JC GETF1
- JMP COLON ; Continue if not end of line
- ;
- COLON1: POP H ; Clear stack
- MOV A,M ; Save possible drive specification
- CALL CAPS ; Capitalize
- CPI 'A' ; Digit if less than 'a'
- JC USERCK ; Process user number
- SUI 'A' ; Convert to 0-31
- CPI MAXDISK ; Within bounds?
- JC SVDISK
- ;
- ERREXIT:XRA A ; Error indicator
- POP D ; Restore 'de'
- RET
- ;
- ; Log in specified disk
- ;
- SVDISK: INR A ; Adjust to 1 for 'a'
- STA DISK ; Save flag
- INX H ; Point to next character
- ;
- ; Check for user
- ;
- USERCK: MOV A,M ; Get possible user number
- CPI ':' ; No user number
- JZ GETFILE
- CPI '?' ; All user numbers?
- JNZ USERC1
- STA USER ; Set value
- INX H ; Point to after
- MOV A,M ; Must be colon
- CPI ':'
- JZ GETFILE
- JMP ERREXIT ; Fatal error if not colon after ?
- ;
- USERC1: XRA A ; Zero user number
- MOV B,A ; 'b' = accumulator for user number
- ;
- USRLOOP:MOV A,M ; Get digit
- INX H ; Point to next
- CPI ':' ; Done?
- JZ USRDN
- SUI '0' ; Convert to binary
- JC ERREXIT ; User number error?
- CPI 10
- JNC ERREXIT
- MOV C,A ; Next digit in 'c'
- MOV A,B ; Old number in 'a'
- ADD A ; *2
- ADD A ; *4
- ADD B ; *5
- ADD A ; *10
- ADD C ; *10+new digit
- MOV B,A ; Result in 'b'
- JMP USRLOOP
- ;
- USRDN: MOV A,B ; Get nuer user number
- CPI MAXUSER+1 ; Within range?
- JNC ERREXIT
- STA USER ; Save in flag
- JMP GETFILE
- ;
- ; Extract file name
- ;
- GETF1: POP H ; Get pointer to byte
- ;
- GETFILE:MOV A,M ; Pointing to colon?
- CPI ':'
- JNZ GFILE1
- INX H ; Skip over colon
- ;
- GFILE1: MOV A,M ; Get next character
- CPI ',' ; Delimiter?
- JZ GFQUES
- CPI ' '+1 ; Not a delimiter?
- JNC GFILE2
- ;
- GFQUES: INX D ; Fill with ???
- MVI B,11 ; 11 bytes
- MVI A,'?'
- ;
- GFFILL: STAX D ; Put?
- INX D ; Point to next
- DCR B ; Count down
- JNZ GFFILL
- ;
- FNDONE: LDA DISK ; Get disk number
- MOV B,A ; In 'b'
- LDA USER ; Get user number
- MOV C,A ; In 'c'
- POP D ; Restore registers
- MVI A,0FFH ; No error
- ORA A ; Set flags
- RET
- ;
- ; Get file name fields
- ;
- GFILE2: MVI B,8 ; At most, 8 bytes for filename
- CALL SCANF ; Scan and fill
- MVI B,3 ; At most, 3 bytes for filetype
- MOV A,M ; Get delimiter
- CPI '.' ; Filename ending in '.'?
- JNZ GFILE3
- INX H ; Point to character after '.'
- CALL SCANF ; Scan and fill
- JMP FNDONE ; Done...return to 'args'
- ;
- GFILE3: CALL SCANF4 ; Fill with spaces
- JMP FNDONE
- ;
- ; Scanner routine
- ;
- SCANF: CALL DELCK ; Check for delimiter
- JZ SCANF4 ; Fill with spaces if found
- INX D ; Point to next byte in filename
- CPI '*' ; Question mark fill ?
- JNZ SCANF1
- MVI A,'?' ; Place '?'
- STAX D
- JMP SCANF2
- ;
- SCANF1: STAX D ; Place character
- INX H ; Point to next position
- ;
- SCANF2: DCR B ; Count down
- JNZ SCANF ; Continue loop
- ;
- SCANF3: CALL DELCK ; "b" chars or more - skip to delimiter
- RZ
- INX H ; Point to next
- JMP SCANF3
- ;
- SCANF4: INX D ; Point to next filename or filetype
- MVI A,' ' ; Fill with spaces
- STAX D
- DCR B ; Count down
- JNZ SCANF4
- RET
- ;
- ; Check character pointed to by 'HL' for a delimiter, return with Zero
- ; flage set if the character is a delimiter
- ;
- DELCK: MOV A,M ; Get the character
- CALL CAPS ; Capitalize
- ORA A ; 0=delimiter
- RZ
- CPI ' '+1 ; Space character+1
- JC DELCK1 ; Space character or less
- CPI '='
- RZ
- CPI 5FH ; Underscore
- RZ
- CPI '.'
- RZ
- CPI ':'
- RZ
- CPI ';'
- RZ
- CPI ','
- RZ
- CPI '<'
- RZ
- CPI '>'
- RET
- ;
- DELCK1: CMP M ; Compare with self for ok
- RET
- ;
- CAPS: CPI 'a'
- RC
- CPI 'z'+1
- RNC
- SUI 20H
- RET ; END OF RICK CONN'S "FNAME"
- ;
- ; +----------------+
- ; | DIVIDE HL BY 2 |
- ; +----------------+
- ;
- DIVBY2: ORA A
- MOV A,H
- RAR
- MOV H,A
- MOV A,L
- RAR
- MOV L,A
- RET
- ;
- ; +----------------------------------+
- ; | HEX TO DECIMAL CONVERT AND PRINT |
- ; +----------------------------------+
- ;
- HEXDC1: XRA A
- STA LZF
- JMP HD1
- ;
- HEXDEC: XRA A ;SET ACC
- STA LZF
- LXI B,-10000 ;10-THOUSANDS
- CALL MAKEDEC ;MAKE THEM
- HD1: LXI B,-1000 ;THOUSANDS
- CALL MAKEDEC ;MAKE THEM
- LXI B,-100 ;HUNDREDS
- CALL MAKEDEC ;MAKE THEM
- HEXDC2: LXI B,-10 ;TENS
- CALL MAKEDEC ;MAKE THEM
- LXI B,-1 ;UNITS
- MVI A,1
- STA LZF
- ;
- MAKEDEC:
- MVI D,-1 ;SET COUNTER
- MDECLP: SHLD TEMP1 ;SAVE HEX
- INR D ;INC DE
- DAD B ;ADD BC TO HEX
- JC MDECLP ;LOOP IF CY
- LHLD TEMP1 ;GET HEX
- MOV B,D ;DIGIT TO B
- MVI A,'0' ;SET ASCII
- ADD B ;ADD DIGIT
- CPI '0'
- JNZ NLZ
- MOV B,A ;SAVE
- LDA LZF ;GET LZ FLAG
- ORA A ;SUPPRESS?
- JZ LZS ;YES
- MOV A,B
- NLZ: STA LZF
- JMP PUTCH
- ;
- LZS: MVI A,' '
- JMP PUTCH
- ;
- ; +-----------------------+
- ; | COMPARE [DE] AND [HL] |
- ; +-----------------------+
- ;
- CPDEHL: PUSH H
- PUSH D
- MVI B,12 ; test 12 characters
- CPDL: LDAX D
- CMP M
- JNZ CPDX
- INX D
- INX H
- DCR B
- JNZ CPDL
- CPDX: POP D
- POP H
- RET
- ;
- ; +--------------------------+
- ; | PRINT [DX] AT CON OR LST |
- ; +--------------------------+
- ;
- PRINTM: LDAX D ; get character
- CPI '$' ; delimiter?
- RZ ; yes, exit
- CALL PUTCH
- INX D
- JMP PRINTM
- ;
- ; +-----------------------+
- ; | ERROR MESSAGE DISPLAY |
- ; +-----------------------+
- ;
- ERROR: DCR A ; error 1?
- LXI D,ERR1
- JZ PRERR
- DCR A
- LXI D,ERR2
- PRERR: MVI C,PSTR
- JMP BDOS
- ;
- ; +-----------------------------+
- ; | SNEAKY WAY OUT OF THIS MESS |
- ; +-----------------------------+
- ;
- EXIT: CALL CRLF ; new line
- JMP QUIT ; spaghetti code
- ;
- ; +--------------+
- ; | DATA STORAGE |
- ; +--------------+
- ;
- CDRIV: DB 0 ; current drive
- CUSER: DB 0 ; current user #
- CPMV: DB 0 ; CP/M version
- STKSAV: DW 0
- ;
- DISK: DB 0
- USER: DB 0
- TEMP1: DW 0
- ;
- OPTNS:
- KOPT: DB 'K' ; K-option (size display)
- LOPT: DB 'L' ; L-option (printer)
- SOPT: DB 'S' ; S-option (sort)
- DB 0FFH
- ;
- BLSHFT: DB 0
- BLMASK: DB 0
- DIRSZ: DW 0
- NUMBLK: DW 0
- LZF: DB 0
- ;
- NMBFLS: DW 0 ; number of files
- ;
- SSTADR: DW 0
- SRECLEN:DW 0
- SNUMRT: DW 0
- SNUMRW: DW 0
- SORTV1: DW 0
- SORTV2: DW 0
- SORTV3: DW 0
- SORTV4: DW 0
- ;
- BUFPTR: DW BUFFER
- CURROW: DB 0
- CURCOL: DB 0
- CUMSIZ: DW 0 ; cumulative filesizes
- ;
- ; +----------+
- ; | MESSAGES |
- ; +----------+
- ;
- SUMM1: DB 9,'DRIVE/USER $'
- SUMM2: DB ': DISPLAYED$'
- SUMM3: DB ' FILES IN$'
- SUMM4: DB 'k TOTAL',CR,LF,'$'
- ;
- ERR1: DB CR,LF,'Invalid drive or user',CR,LF,'$'
- ERR2: DB CR,LF,'No file(s)',CR,LF,'$'
- ;
- ORG $+80
- STACK EQU $
- ORG (($/100H)*100H)+100H
- BUFFER EQU $
- END
- w line
- JMP QUIT ; spaghetti code
- ;
-