home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
CP/M
/
CPM_CDROM.iso
/
mbug
/
mbug117.arc
/
ZCMD-1.LBR
/
ZCMD.ASM
next >
Wrap
Assembly Source File
|
1979-12-31
|
27KB
|
1,049 lines
;SET UP TO CREATE SYSTEM FILE
AORG 0CF80H
NOP
DEFB 0E7H
NOP
DEFB 0D0H
DEFB 0EEH
DEFB 08H
DEFS 7AH
ENTRY: JP CPR
JP CPR1
BIOS = 0E700H
DRVPFATT= 1
SYSDRV = 'A'-'@'
SYSUSR = 0
ERDFLG = 'V'
CMDSEP = ';'
NLINES = 24
FENCE = ':'
PGDFLG = 'P'
USRMAX = 003FH
MAXUSR = 15
DRVMAX = 003DH
MAXDISK = 2
SYSFLG = 'A'
SOFLG = 'S'
SPRMPT = '$'
CPRMPT = '>'
NUMBASE = 'H'
SECTFLG = 'S'
CURIND = '$'
COMMENT = ';'
NCHARS = 4
CR = 0DH
LF = 0AH
TAB = 09H
WBOOT = 0000H
UDFLAG = 0004H
BDOS = 0005H
TFCB = 005CH
TBUFF = 0080H
TPA = 0100H
BUFLEN = 80
BUFSIZ: DEFB BUFLEN ; Maximum buffer length
CHRCNT: DEFB 0 ; Number of valid chars in command line
CMDLIN: DEFM ' '; Default (cold boot) command
DEFB 0 ; Command string terminator
DEFS BUFLEN-($-CMDLIN)+1; Total is 'BUFLEN' bytes
NXTCHR: DEFW CMDLIN ; Pointer to command input buffer
COMMSG: DEFM 'COM'
FCBDN: DEFS 1 ; Disk name
FCBFN: DEFS 8 ; File name
FCBFT: DEFS 3 ; File type
DEFS 1 ; Extent number
DEFS 2 ; S1 and S2
DEFS 1 ; Record count
FCBDM: DEFS 16 ; Disk group map
FCBCR: DEFS 1 ; Current record number
PAGCNT: DEFB NLINES-2 ; Lines left on page
CMDTBL: DEFM 'DIR '
DEFW DIR
DEFM 'LIST'
DEFW LIST
DEFM 'TYPE'
DEFW TYPE
DEFM 'GO '
DEFW GO
DEFM 'ERA '
DEFW ERA
DEFM 'SAVE'
DEFW SAVE
DEFM 'REN '
DEFW REN
DEFM 'GET '
DEFW GET
DEFM 'JUMP'
DEFW JUMP
NCMNDS = 9
CPR: LD SP,STACK ; Set the stack
PUSH BC
PUSH DE
LD A,CR
CALL CONOUT ; This is required to make BYE's BDCHEK
LD C,32 ; Reset locations 6 and 7 after warmboot
LD E,241
CALL BDOS ; Call BYE's BDOS
POP DE
POP BC
CP 77 ; BYE up and running?
JR Z,CPR1
LD A,MAXUSR+1 ; Set USRMAX on cold boot
LD (USRMAX),A
LD A,MAXDISK-1 ; Set DRVMAX on cold boot
LD (DRVMAX),A
CPR1: LD A,5
RST 28H
LD A,(HL)
OR A
JP Z,CPR2
LD DE,BUFSIZ
LD BC,128
LDIR
CPR2: LD SP,STACK
PUSH BC
LD A,C ; C=user/disk number (see loc 4)
RRA ; Extract user number
RRA
RRA
RRA
AND 0FH
LD (CURUSR),A ; Set user
CALL SETUSR
CALL RESET ; Reset disk system
POP BC
LD A,C ; C=user/disk number (see loc 4)
AND 0FH ; Extract current disk drive
LD (CURDR),A ; Set it
CALL LOGIN ; Log in default disk
CALL SETUD ; Set user/disk flag
CALL DEFDMA
CONT: LD HL,(NXTCHR) ; Point to next character to process
LD A,(HL) ; Get it
CP 3 ; Restart if CTL-C
JR Z,RESTRT
OR A ; 0 if no command line present
JR NZ,RS1
RESTRT: LD SP,STACK ; Reset stack
CALL CRLF ; Print prompt
LD A,(CURDR) ; Current drive is part of prompt
ADD A,'A' ; Convert to ASCII A-P
CALL CONOUT
LD A,(CURUSR) ; Get user number
CP 10 ; User < 10?
JR C,RS00
SUB 10 ; Subtract 10 from it
PUSH AF ; Save it
LD A,'1' ; Output 10's digit
CALL CONOUT
POP AF
RS00: ADD A,'0' ; Output 1's digit (convert to ASCII)
CALL CONOUT
RS000: LD HL,CMDLIN ; Set pointer to first character
LD (NXTCHR),HL ; Pointer to next character to process
LD (HL),0 ; Zero out command line
PUSH HL ; Save pointer
CALL REDBUF ; Input command line from user
POP HL ; Get pointer
LD A,(HL) ; Check for comment line
CP COMMENT ; Begins with comment character?
JR Z,RESTRT
OR A ; No input?
JR Z,RESTRT
RS1: LD SP,STACK ; Reset stack
LD A,(HL)
CP CMDSEP
JR NZ,RS2
INC HL
LD (NXTCHR),HL
RS2: LD (CMDCH1),HL ; Set pointer to first character
CAPBUF: LD A,(HL) ; Capitalize command character
CALL UCASE
LD (HL),A
INC HL ; Point to next character
OR A ; Eol?
JR NZ,CAPBUF
CALL SCANER ; Parse command name from command line
JR NZ,ERROR
LD DE,RSTCPR ; Put return address of command
PUSH DE ; On the stack
COLON = $+1
LD A,0 ; Command of the form 'DU:command'?
OR A ; 0=no
JP NZ,COM ; Process as com file if not
CALL CMDSER ; Scan for cpr-resident command
JP NZ,COM ; Not cpr-resident
LD A,(HL) ; Found it: get low-order part
INC HL ; Get high-order part
LD H,(HL) ; Store high
LD L,A ; Store low
JP (HL) ; Execute cpr routine
RSTCPR: CALL DLOGIN ; Log in current user/disk
RCPRNL: CALL SCANER ; Extract next token from command line
LD A,(FCBFN) ; Get first char of token
CP ' ' ; Any char?
JP Z,CONT ; Continue with next command if no error
ERROR: CALL CRLF ; New line
CURTOK = $+1
LD HL,0 ; Pt to beginning of command line
ERR1: LD A,(HL) ; Get character
CP ' '+1 ; Simple '?' if <sp> or less
JR C,ERR2
CALL CONOUT ; Print command char
INC HL ; Pt to next char
JR ERR1 ; Continue
ERR2: CALL PRINT ; Print '?'
DEFB '?'+80H
ERR3: CALL DLOGIN ; Panic restore of default user/disk
JP RESTRT ; Restart CPR
PRNNF: CALL PRINTC ; No file message
DEFM 'NO FIL','E'+80H
RET
CRLF: LD A,CR
CALL CONOUT
LD A,LF
JR CONOUT
CONIN: LD C,1 ; Input character
CALL BDOS ; Get input character with ^S
JP UCASE ; Capitalize
CONOUT: PUSH BC
PUSH DE
PUSH HL
LD C,2
OUTPUT: LD E,A
CALL BDOS
POP HL
POP DE
POP BC
RET
LCOUT: PUSH AF ; Output character to CRT
PRFLG = $+1
LD A,0 ; 2nd byte (immediate argument)
OR A ; 0=type
JR Z,LC1
POP AF ; Get character
LSTOUT: PUSH BC ; Save regs
PUSH DE
PUSH HL
LD C,5
JR OUTPUT
LC1: POP AF ; Get character
PUSH AF
CALL CONOUT ; Output to CRT
POP AF
CP LF ; Check for paging
RET NZ
PAGER: PUSH HL
LD HL,PAGCNT ; Count down
DEC (HL)
JR NZ,PAGER1
LD (HL),NLINES-2 ; Refill counter
PGFLG = $+1
LD A,0 ; 0 may be changed by pgflg equate
CP PGDFLG ; Page default override option wanted?
JR Z,PAGER1
PUSH BC ; Save registers
BIOCAL1:CALL BIOS+9 ; BIOS console input routine
POP BC ; Get register
CP 'C'-'@' ; ^C
JP Z,RSTCPR ; Restart CPR
PAGER1: POP HL ; Restore HL
RET
READF: LD DE,FCBDN ; Fall through to read
READ: LD C,14H ; Fall through to BDOSB
BDOSB: PUSH BC
CALL BDOS
POP BC
OR A
RET
PRINTC: CALL CRLF ; New line
PRINT: EX (SP),HL ; Get ptointer to string
CALL PRIN1 ; Print string
EX (SP),HL ; Restore HL and return address
RET
PRIN1: LD A,(HL) ; Get next byte
INC HL ; Point to next byte
OR A ; End of string?
RET Z ; String terminated by binary 0
PUSH AF ; Save flags
AND 7FH ; Mask out MSG
CALL CONOUT ; Print character
POP AF ; Get flags
RET M ; String terminated by MSB set
JR PRIN1
GETDRV: LD C,19H
JR BDOSJP
DEFDMA: LD DE,TBUFF ; 80H=TBUFF
DMASET: LD C,1AH
JR BDOSJP
RESET: LD C,0DH
BDOSJP: JP BDOS
LOGIN: LD E,A
LD C,0EH
JR BDOSJP ; Save some code space
OPENF: XOR A
LD (FCBCR),A
LD DE,FCBDN ; Fall thrrough to OPEN
OPEN: LD C,0FH ; Fall through to GRBDOS
GRBDOS: CALL BDOS
INC A ; Set zero flag for error return
RET
CLOSE: LD C,10H
JR GRBDOS
SEARF: LD DE,FCBDN ; Specify FCB
SEAR1: LD C,11H
JR GRBDOS
SEARN: LD C,12H
JR GRBDOS
DELETE: LD C,13H
JR BDOSJP ; Save more space
GETUSR: LD A,0FFH ; Get current user number
SETUSR: LD E,A ; User number in 'E'
LD C,20H ; Set user number to value in 'E'
JR BDOSJP ; More space saving
SETUD: CALL GETUSR ; Get number of current user
AND 0FH ; Mask sure 4 bits
ADD A,A ; Place it in high nybble
ADD A,A
ADD A,A
ADD A,A
LD HL,CURDR ; Mask in current drive number
OR (HL) ; Mask in
LD (UDFLAG),A ; Set user/disk number
RET
UCASE: AND 7FH ; Mask out MSB
CP 61H ; Lower-case 'A'
RET C
CP 7BH ; Greater than lower-case Z?
RET NC
AND 5FH ; Capitalize
RET
REDBUF: LD A,CPRMPT
RB2: CALL CONOUT
LD C,0AH ; Read command line from user
LD DE,BUFSIZ
CALL BDOS
LD HL,CHRCNT ; Point to character count
LD A,(HL) ; Get character count
INC HL ; Pt to first character of command line
CALL ADDAH ; Pt to after last char of command line
LD (HL),0 ; Store ending zero
RET
BREAK: PUSH BC ; Save registers
PUSH DE
PUSH HL
BIOCAL2:CALL BIOS+6 ; Console status check
OR A ; Set flags
BIOCAL3:CALL NZ,BIOS+9 ; Get input char with ^s processing
CP 'S'-'@' ; Pause if ^S
BIOCAL4:CALL Z,BIOS+9 ; Get next character
POP HL ; Restore registers
POP DE
POP BC
CP 'C'-'@' ; Check for abort
RET
SDELM: LD A,(DE)
OR A ; 0=delimiter
RET Z
CP ' '+1 ; Delim if <= <SP>
JR C,ZERO
CP '=' ; '='=delimiter
RET Z
CP 5FH ; Underscore=delimiter
RET Z
CP '.' ; '.'=delimiter
RET Z
CP ':' ; ':'=delimiter
RET Z
CP ',' ; ','=delimiter
RET Z
CP ';' ; ';'=delimiter
RET Z
CP '<' ; '<'=delimiter
RET Z
CP '>' ; '>'=delimiter
RET Z
CP CMDSEP
RET
ZERO: XOR A ; Set zero flag
RET
ADVAN: LD DE,(NXTCHR)
SBLANK: LD A,(DE) ; Get character
OR A ; Zero?
RET Z
CP CMDSEP
RET Z
CALL SDELM ; Skip over delimiter
RET NZ
INC DE ; Advance to next char
JR SBLANK
ADDAH: ADD A,L
LD L,A
RET NC
INC H
RET
NUMBER: CALL SCANER ; Parse number and place in fcbfn
LD HL,FCBFN+10 ; Pt to end of token for conversion
LD B,11 ; 11 characters maximum
NUMS: LD A,(HL) ; Get character from end
DEC HL ; Back up
CP ' ' ; Space?
JR NZ,NUMS1
DJNZ NUMS ; Count down
JR NUM0 ; By default, process
NUMS1: CP NUMBASE ; Check against base switch flag
JR Z,HNUM0
NUM0: LD HL,FCBFN ; Point to beginning of token
NUM0A: LD BC,1100H ; C=accumulated value, b=char count
NUM1: LD A,(HL) ; Get character
CP ' ' ; Done if <SP>
JR Z,NUM2
CP ':' ; Done if colon
JR Z,NUM2
INC HL ; Pt to next char
SUB '0' ; Convert to binary
CP 10 ; Error if >= 10
JR NC,NUMERR
LD D,A ; Digit in d
LD A,C ; New value = old value * 10
RLCA ; *2
JR C,NUMERR
RLCA ; *4
JR C,NUMERR
RLCA ; *8
JR C,NUMERR
ADD A,C ; *9
JR C,NUMERR
ADD A,C ; *10
JR C,NUMERR
ADD A,D ; New value = old value * 10 + digit
JR C,NUMERR
LD C,A ; Set new value
DJNZ NUM1 ; Count down
NUM2: LD A,C ; Get accumulated value
RET
NUMERR: JP ERROR ; Use error routine
HEXNUM: CALL SCANER ; Parse number and place in FCBFN
HNUM0: LD HL,FCBFN ; Point to token for conversion
LD DE,0 ; De=accumulated value
LD B,11 ; B=character
HNUM1: LD A,(HL) ; Get character
CP ' ' ; Done?
JR Z,HNUM3
CP NUMBASE ; Done if numbase suffix
JR Z,HNUM3
SUB '0' ; Convert to binary
JR C,NUMERR
CP 10 ; 0-9?
JR C,HNUM2
SUB 7 ; A-F?
CP 10H ; Error?
JR NC,NUMERR
HNUM2: INC HL ; Point to next characer
LD C,A ; Digit in 'C'
LD A,D ; Get accumulated value
RLCA ; Exchange nybbles
RLCA
RLCA
RLCA
AND 0F0H ; Mask out low nybble
LD D,A
LD A,E ; Switch low-order nybbles
RLCA
RLCA
RLCA
RLCA
LD E,A ; High nybble of e=new high of e
AND 0FH ; Get new low of d
OR D ; Mask in high of d
LD D,A ; New high byte in d
LD A,E
AND 0F0H ; Mask out low of e
OR C ; Mask in new low
LD E,A ; New low byte in e
DJNZ HNUM1 ; Count down
HNUM3: EX DE,HL ; Returned value in hl
LD A,L ; Low-order byte in a
RET
DIRPTR: LD HL,TBUFF ; Point to temporary buffer
ADD A,C ; Point to 1st byte of directory entry
CALL ADDAH ; Point to desired byte in dir entry
LD A,(HL) ; Get desired byte
RET
SLOGIN: XOR A ; A=0 for default disk
LD (FCBDN),A ; Select default disk since user/disk
TEMPDR = $+1
LD A,0 ; 2nd byte (immediate arg) is tempdr
OR A ; 0=current drive
JR NZ,SLOG1
LD A,(CURDR) ; Log in current drive
INC A ; Add 1 for next dcr
SLOG1: DEC A ; Adjust for proper disk number (a=0)
CALL LOGIN ; Log in new drive
TEMPUSR = $+1
LD A,0 ; 2nd byte is user to be selected
JP SETUSR ; Log in new user
DLOGIN: DEFS 0
CURDR = $+1
LD A,0 ; Prep to log in current drive
CALL LOGIN ; Login current drive
CURUSR = $+1
LD A,0 ; Prep to log in current user number
JP SETUSR ; Log in new user
SCANLOG:CALL SCANER ; Do scan
PUSH AF ; Save flag
CALL SLOGIN ; Log in temporary user/disk
POP AF ; Get flag
RET
SCANER: LD HL,FCBDN ; Point to FCBDN
SCANX: XOR A ; A=0
LD (TEMPDR),A ; Set temporary drive number to default
LD (HL),A ; Set first byte of FCBDN
LD (COLON),A ; Set no colon flag
LD A,(CURUSR) ; Get current user
LD (TEMPUSR),A ; Set tempusr
CALL ADVAN ; Skip to non-blank or end of line
LD (CURTOK),DE
LD B,11 ; Prep for possible space fill
JR Z,SCAN4
PUSH DE ; Save pointer to first character
CALL SDELM ; Check for delimiter and get first char
CP 'A' ; In letter range?
JR C,SCAN1
CP 'P'+1 ; In letter range?
JR C,SCAN1A
SCAN1: CP '0' ; Check for digit range
JR C,SCAN2
CP '9'+1 ; In digit range?
JR NC,SCAN2
SCAN1A: INC DE ; Pt to next char
CALL SDELM ; Check for delimiter, else digit
JR SCAN1
SCAN2: POP DE ; Restore ptr to first char
CP ':' ; Was delimiter a colon?
JR NZ,SCAN3
LD (COLON),A ; Set colon found
LD A,(DE) ; Get first character
CP 'A' ; Convert possible drive spec to number
JR C,SUD1
SUB 'A'-1
PUSH BC ; Save 'BC'
PUSH AF ; Save drive request
LD A,(DRVMAX) ; Get maximum legal drive
ADD A,2 ; Bump it two for the compare
LD B,A ; Save maximum drive in 'B'
POP AF ; Restore drive request
CP B ; See if illegal drive
POP BC ; Restore bc
JP NC,ERROR ; Invalid disk number
LD (TEMPDR),A ; Set temporary drive number
LD (HL),A ; Set fcbdn
INC DE ; Pt to next char
LD A,(DE) ; See if it is a colon (:)
CP ':'
JR Z,SUD2
SUD1: PUSH HL ; Save pointer to FCBDN
EX DE,HL ; Hl pts to first digit
CALL NUM0A ; Get number
EX DE,HL ; De pts to terminating colon
LD HL,USRMAX
CP (HL)
POP HL ; Get pointer to FCBDN
JP NC,ERROR
LD (TEMPUSR),A ; Save user number
SUD2: INC DE ; Point to character after colon
SCAN3: XOR A ; A=0
LD (QMCNT),A ; Init question mark count
LD B,8 ; Max of 8 chars in file name
CALL SCANF ; Fill FCB file name
LD B,3 ; Prepare to extract type
LD A,(DE) ; Get last char which stopped scan
CP '.' ; Have a type if de) delimiter is a '.'
JR NZ,SCAN4
INC DE ; Pt to char in command line after '.'
CALL SCANF ; Fill fcb file type
JR SCAN5 ; Skip to next processing
SCAN4: CALL SCANF4 ; Space fill
SCAN5: LD B,4 ; 4 bytes
XOR A ; A=0
CALL SCANF5 ; Fill with zeroes
LD (NXTCHR),DE
QMCNT = $+1
LD A,0 ; Number of question marks
OR A ; Set zero flag to indicate any '?'
RET
SCANF: CALL SDELM ; Done if delimiter encountered
JR Z,SCANF4
INC HL ; Point to next byte in FCBDN
CP '*' ; Is (DE) a wild card?
JR NZ,SCANF1
LD (HL),'?' ; Place '?' in FCB
CALL SCQ ; Scanner count question marks
JR SCANF2
SCANF1: LD (HL),A ; Store filename char in fcb
INC DE ; Pt to next char in command line
CP '?' ; Check for question mark (wild)
CALL Z,SCQ ; Scanner count question marks
SCANF2: DJNZ SCANF ; Decrement char count until 8 elapsed
SCANF3: CALL SDELM ; 8 chars or more - skip until delimiter
RET Z ; Zero flag set if delimiter found
INC DE ; Pt to next char in command line
JR SCANF3
SCANF4: LD A,' ' ; Fill with spaces
SCANF5: INC HL ; Point to next byte in FCB
LD (HL),A ; Fill with byte in A-reg.
DJNZ SCANF5
RET
SCQ: PUSH HL ; Save HL
LD HL,QMCNT ; Get count
INC (HL) ; Increment
POP HL ; Get HL
RET
CMDSER: LD HL,CMDTBL ; Point to command table
LD C,NCMNDS ; Set command counter
LD A,C ; Check number of commands
OR A ; If none, then abort
JR Z,CMS5
CMS1: LD DE,FCBFN ; Point to stored command name
LD B,NCHARS ; Number of chars/command (8 max)
CMS2: LD A,(DE) ; Compare against table entry
CP (HL)
JR NZ,CMS3
INC DE ; Point to next character
INC HL
DJNZ CMS2 ; Count down
LD A,(DE) ; Next char must be a space
CP ' '
JR NZ,CMS4
RET ; Command is CPR-resident
CMS3: INC HL ; Skip to next command table entry
DJNZ CMS3
CMS4: INC HL ; Skip address
INC HL
DEC C ; Decrement table entry number
JR NZ,CMS1
CMS5: INC C ; Clear zero flag
RET ; Command is disk-resident
DIR: CALL SCANLOG ; Extract possible D:FILENAME.TYP token
LD HL,FCBFN ; Make FCB wild (all '?') if no NAME.TYP
LD A,(HL) ; Get first chararacter of NAME.TYPE
CP ' ' ; If space, all wild
CALL Z,FILLQ
CALL ADVAN ; Look at next input char
LD B,80H ; Prepare for dir-only selection
JR Z,DIRDN
LD B,1 ; Set for both dir and sys files
CP SYSFLG ; System and dir flag specifier?
JR Z,GOTFLG
CP SOFLG ; Sys only?
JR NZ,DIRDN
DEC B ; B=0 for sys files only
GOTFLG: INC DE ; Pt to char after flag
DIRDN: LD (NXTCHR),DE
DIRPR: LD A,B ; Get flag
LD (SYSTST),A ; Set system test flag
LD E,0 ; Set column counter to zero
PUSH DE ; Save column counter (e)
CALL SEARF ; Search for specified file
JR NZ,DIR3
CALL PRNNF ; Print no file msg; reg a not changed
XOR A ; Set zero flag
POP DE ; Restore de
RET
DIR3: CALL GETSBIT ; Get and test for type of files
JR Z,DIR6
POP DE ; Get entry count (=<CR> counter)
LD A,E ; Add 1 to it
INC E
PUSH DE ; Save it
AND 03H ; Output <CRLF> if 4 entries printed
JR NZ,DIR4
CALL CRLF ; New line
JR DIR5
DIR4: CALL PRINT
DEFM ' '
DEFB FENCE ; Then fence char
DEFB ' ',' '+80H ; Then 2 more spaces
DIR5: LD B,01H ; Pt to 1st byte of file name
LD A,B ; A=offset
CALL DIRPTR ; Hl now pts to 1st byte of file name
CALL PRFN ; Print file name
DIR6: CALL BREAK ; Check for abort
JR Z,DIR7
CALL SEARN ; Search for next file
JR NZ,DIR3
DIR7: POP DE ; Restore stack
LD A,0FFH ; Set nz flag
OR A
RET
PRFN: LD B,8 ; 8 chars
CALL PRFN1
LD A,'.' ; Dot
CALL CONOUT
LD B,3 ; 3 chars
PRFN1: LD A,(HL) ; Get char
INC HL ; Pt to next
CALL CONOUT ; Print char
DEC B ; Count down
JR NZ,PRFN1
RET
GETSBIT:DEC A ; Adjust to returned value
RRCA ; Convert number to offset into tbuff
RRCA
RRCA
AND 60H
LD C,A ; Offset into TBUFF in c
LD A,10 ; Add 10 to point to SYS file attribute
CALL DIRPTR ; A=system byte
AND 80H ; Look at only system bit
SYSTST = $+1
XOR 0 ; If SYSTST=0, sys only; if =80h, DIR
RET ; NZ if ok, Z if not ok
FILLQ: LD B,11 ; Number of characters in FN & FT
FQLP: LD (HL),'?' ; Store '?'
INC HL
DJNZ FQLP
RET
ERA: CALL SCANLOG
LD B,1 ; Display all matching files
CALL DIRPR ; Print directory of erased files
RET Z ; Abort if no files
CALL PRINTC
DEFM 'OK TO ERASE','?'+80H
CALL CONIN ; Get reply
CP 'Y' ; Yes?
RET NZ ; Abort if not
ERA2: LD DE,FCBDN ; Delete file specified
CALL DELETE
RET ; Reenter cpr
LIST: LD A,0FFH ; Turn on printer flag
JR TYPE0
TYPE: XOR A ; Turn off printer flag
TYPE0: LD (PRFLG),A ; Set flag
CALL SCANLOG ; Extract FILENAME.TYP toden
JP NZ,ERROR ; Error if any question marks
CALL ADVAN ; Get pgdflg if it's there
LD (PGFLG),A ; Save it as a flag
JR Z,TYPE1
INC DE ; Put new buf pointer
TYPE1: LD (NXTCHR),DE
CALL OPENF ; Open selected file
JP Z,ERROR ; Abort if error
CALL CRLF ; New line
LD A,NLINES-1 ; Set line count
LD (PAGCNT),A
LD BC,080H ; Set character position and tab count
TYPE2: LD A,C ; Get character count
CP 80H
JR C,TYPE3
PUSH HL ; Read next block
PUSH BC
CALL READF
POP BC
POP HL
JR NZ,TYPE7
LD C,0 ; Set character count
LD HL,TBUFF ; Poin to first character
TYPE3: LD A,(HL) ; Get next char
AND 7FH ; Mask out msb
CP 1AH ; End of file (^z)?
RET Z ; Restart cpr if so
CP CR
JR Z,TYPE4
CP LF ; Reset tab count?
JR Z,TYPE4
CP TAB ; Tab?
JR Z,TYPE5
CALL LCOUT ; Output char
INC B ; Increment tab count
JR TYPE6
TYPE4: CALL LCOUT ; Output <CR> or <LF>
LD B,0 ; Reset tab counter
JR TYPE6
TYPE5: LD A,' ' ; Space
CALL LCOUT
INC B ; Increment position count
LD A,B
AND 7
JR NZ,TYPE5
TYPE6: INC C ; Increment char count
INC HL ; Pt to next char
CALL BREAK ; Check for abort
RET Z ; Restart if so
JR TYPE2
TYPE7: DEC A ; No error?
RET Z ; Restart cpr
JP ERROR
SAVE: CALL NUMBER ; Extract number from command line
LD L,A ; HL=page count
LD H,0
PUSH HL ; Save page count
CALL EXTEST ; Test for existence of file
LD C,16H ; Bdos make file
CALL GRBDOS
POP HL ; Get page count
JR Z,SAVE3
XOR A ; Set record count field
LD (FCBCR),A
CALL ADVAN ; Look for 's' for sector option
INC DE ; Pt to after 's' token
CP SECTFLG
JR Z,SAVE0
DEC DE ; No 's' token, so back up
ADD HL,HL ; Double it for HL=record (128 bytes)
SAVE0: LD (NXTCHR),DE
LD DE,TPA ; Point to start of SAVE area (TPA)
SAVE1: LD A,H ; Done with save?
OR L ; HL=0 if so
JR Z,SAVE2
DEC HL ; Count down on record
PUSH HL ; Save pointer to block to save
LD HL,128 ; 128 bytes per record
ADD HL,DE ; Point to next record
PUSH HL ; Save on stack
CALL DMASET ; Set DMA address for write (addr in DE)
LD DE,FCBDN ; Write record
LD C,15H ; Bdos write record
CALL BDOSB ; Save bc
POP DE ; Get ptr to next record in DE
POP HL ; Get record count
JR NZ,SAVE3
JR SAVE1 ; Continue
SAVE2: LD DE,FCBDN ; Close saved file
CALL CLOSE
INC A ; Error?
JR NZ,SAVE4
SAVE3: CALL PRNLE ; Print 'no space' error
SAVE4: JP DEFDMA ; Set DMA to 0080 and restart cpr
EXTEST: CALL SCANLOG ; Extract file name and log in user/disk
JP NZ,ERROR ; '?' is not permitted
CALL SEARF ; Look for specified file
LD DE,FCBDN ; Point to file FCB
RET Z ; Ok if not found
PUSH DE ; Save pointer to FCB
CALL PRINTC
DEFM 'ERASE',' '+80H
LD HL,FCBFN ; Point to file name field
CALL PRFN ; Print it
LD A,'?' ; Print question
CALL CONOUT
CALL CONIN ; Get response
POP DE ; Get ptr to fcb
CP 'Y' ; Key on yes
JP NZ,ERR3 ; Restart as error if no
PUSH DE ; Save ptr to fcb
CALL DELETE ; Delete file
POP DE ; Get ptr to fcb
RET
REN: CALL EXTEST ; Test for file existence and return
LD A,(TEMPDR) ; Save selected disk
PUSH AF ; Save on stack
REN0: LD HL,FCBDN ; Save new file name
LD DE,FCBDM
LD BC,16 ; 16 bytes
LDIR
CALL ADVAN ; Advance to next character (non-delim)
JR Z,REN4
REN1: LD (NXTCHR),DE
CALL SCANER ; Extract FILENAME.TYP token
JR NZ,REN4
POP AF ; Get old default drive
LD B,A ; Save it
LD HL,TEMPDR ; Compare it against selected drive
LD A,(HL) ; Default?
OR A
JR Z,REN2
CP B ; Check for drive error
JR NZ,REN4
REN2: LD (HL),B
XOR A
LD (FCBDN),A ; Set default drive
LD DE,FCBDN ; Rename file
LD C,17H ; BDOS rename FCT
CALL GRBDOS
RET NZ
REN3: CALL PRNNF ; Print NO FILE message
REN4: JP ERROR
RSTJMP: JP RCPRNL ; Restart cpr
JUMP: CALL HEXNUM ; Get load address in HL
JR CALLPROG ; Perform call
GO: LD HL,TPA ; Always to TPA
JR CALLPROG ; Perform call
COM: LD A,(FCBFN) ; Any command?
CP ' ' ; ' ' means command was 'D:' to switch
JR NZ,COM1
LD A,(COLON) ; Look for colon flag
OR A ; If zero, just blank
RET Z ; Return to main routine
LD A,(TEMPUSR) ; Get selected user
CP 10H ; Make sure 4 bits
JP NC,ERROR ; Range error?
LD (CURUSR),A ; Set current user
CALL SLOGIN ; Log in user/disk as if temporarily
LD A,(TEMPDR) ; Get selected drive
OR A ; If 0 (default), no change
JR Z,COM0
DEC A ; Adjust for log in
LD (CURDR),A ; Set current drive
COM0: JP SETUD ; Set current user/disk
COM1: LD DE,FCBFT ; Point to file type
LD A,(DE) ; Get first character of file type
CP ' ' ; Must be blank, or error
JP NZ,ERROR
LD HL,COMMSG ; Place default file type (com) into fcb
LD BC,3 ; 3 bytes
LDIR
LD HL,TPA ; Set execution/load address
PUSH HL ; Save for execution
CALL MLOAD ; Load memory with file specified
POP HL ; Get execution address
CALLPROG: LD (EXECADR),HL ; Perform in-line code modification
CALL SCANER ; Search command line for next token
LD HL,TEMPDR ; Save pointer to drive specification
PUSH HL
LD A,(HL) ; Set drive specification
LD (FCBDN),A
LD HL,FCBDN+10H ; Pt to 2nd file name
CALL SCANX ; Scan for it and load it into fcb+16
POP HL ; Set up drive specs
LD A,(HL)
LD (FCBDM),A
XOR A
LD (FCBCR),A
LD DE,TFCB ; Copy to default FCB
LD HL,FCBDN ; From FCBDN
LD BC,33 ; Set up default FCB
LDIR
CMDCH1 = $+1
LD HL,CMDLIN
CALLP1: LD A,(HL) ; Skip to end of 2nd file name
OR A ; End of line?
JR Z,CALLP2
CP CMDSEP
JR Z,CALLP2
CP ' ' ; End of token?
JR Z,CALLP2
INC HL
JR CALLP1
CALLP2: LD B,0 ; Set character count
LD DE,TBUFF+1 ; Point to character position
CALLP3: LD A,(HL) ; Copy command line to TBUFF
LD (DE),A
OR A ; Done if zero
JR Z,CALLP5
CP CMDSEP
JR Z,CALLP4
INC B ; Increment character count
INC HL ; Point to next
INC DE
JR CALLP3
CALLP4: XOR A
LD (DE),A
CALLP5: LD (NXTCHR),HL
LD A,B ; Save character count
LD (TBUFF),A
CALL CRLF ; New line
CALL DEFDMA ; Set DMA to 0080
PUSH AF
PUSH BC
PUSH DE
PUSH HL
LD A,5
RST 28H
LD DE,BUFSIZ
LD BC,128
EX DE,HL
LDIR
POP HL
POP DE
POP BC
POP AF
EXECADR = $+1
CALL TPA ; Call transient
CALL DEFDMA ; Set DMA to 0080 in case it was changed
CALL DLOGIN ; Login current user/disk
JP CONT ; Restart CPR and continue command
GET: CALL HEXNUM ; Get load address in hl
PUSH HL ; Save address
CALL SCANER ; Get file name
POP HL ; Restore address
JP NZ,ERROR ; Must be unambiguous
MLOAD: LD (LOADADR),HL ; Set load address
MLA: LD A,DRVPFATT
LD (SYSTST),A ; Test flag in getsbit
CALL SLOGIN ; Look under temporary user/disk
CALL SEARF ; Look for file
MLARUN: LD HL,PATH ; Point to path for failure possibility
JR NZ,MLA4
MLA0: LD A,(HL) ; Get drive
OR A ; 0=done=command not found
NOCRUN: JP Z,ERROR
CP CURIND ; Current drive specified?
JR NZ,MLA1
LD A,(CURDR) ; Get current drive
INC A ; Set a=1
MLA1: LD (TEMPDR),A ; Select different drive if not current
LD A,1 ; Accept both SYS and DIR files
LD (SYSTST),A ; Test flag is 1 for both
INC HL ; Point to user number
LD A,(HL) ; Get user number
INC HL ; Poin to next entry in path
PUSH HL ; Save pointer
AND 7FH ; Mask out system bit
CP CURIND ; Current user specified?
JR NZ,MLA2
LD A,(CURUSR) ; Get current user number
MLA2: LD (TEMPUSR),A ; Set temporary user number
CPL
AND 80H
JR NZ,MLA3
LD (SYSTST),A
MLA3: CALL SLOGIN
MLA3RT: CALL SEARF
POP HL
JR Z,MLA0
MLA4: PUSH HL
CALL GETSBIT
POP HL
JR Z,MLA0
CALL OPENF
LOADADR = $+1
LD HL,TPA
MLA5: LD A,ENTRY/256-1
CP H ; Are we going to overwrite the CPR?
JR C,PRNLE
PUSH HL ; Save address of next sector
EX DE,HL ; In DE
CALL DMASET ; Set DMA address for load
LD DE,FCBDN ; Read next sector
CALL READ
POP HL ; Get address of next sector
JR NZ,MLA6
LD DE,128 ; Move 128 bytes per sector
ADD HL,DE ; Point to next sector in HL
JR MLA5
MLA6: DEC A ; Load complete
JP Z,DLOGIN ; Ok if zero, else fall thru to prnle
PRNLE: CALL PRINTC
DEFM 'FUL','L'+80H
CALL DLOGIN
JP RESTRT ; Restart zcmd
PATH: DEFM '$$'
DEFM 'A'-'@',0
DEFB 0
DEFS 48 ; STACK AREA
STACK: DEFM '$'
END
DLOGIN
JP RESTRT ; Restart zcmd
PATH: DEFM '$$'
DEFM 'A'-'@',0
DEFB 0
DEFS 48 ; STACK AREA
STACK: DEFM '$'