home *** CD-ROM | disk | FTP | other *** search
- ;=============================================================================
- ;
- ; M C C O M M A N D
- ;
- ;============================================================================
-
- ; +++++++ NOT AN OFFICIAL RCP SEGMENT
-
- ; Command: MC
- ; Function: Multi Copy: Wild Card File Copier
- ; Author: Rob Friefeld, 4607 Colorado St., Long Beach, CA 213-434-7338
- ; Date: 25 Nov 1987 Version 1.2
- ; Comment: ERAON = YES assures all routines from rcpsubs.lib available.
- ; MC size, not counting support routines -
- ; ~700 bytes with command line options = yes
- ; ~600 bytes bare
- ; Starting address is MLTCPY:
-
- ; Version 1.2:
- ; - Command line takes option for selecting files
- ; - User number reported correctly above #15
- ; - Code more efficient
-
- ; Usage: MC SOURCE [DESTINATION] [/o]
- ; Source is the afn to be copied and destination is an optional
- ; afn. If omitted, source comes to current DU:
- ; Frequent checks made for ^C to abort operation
- ; R/O files are copied to R/W.
- ; /o options ...
- ; /A - Copy Archived files only
- ; /S - Copy System files only
- ; /1..4 - Copy F1..F4 attribute files only (set by SFA, NSWEEP)
- ; /~o - Reverse sense of above option
- ; /I - Inspect files before copy (like ERA)
- ;
- ; MC EQUATES
- ;
-
- ; # RECORDS TO READ ON EACH PASS (Byte value)
- ; With these equates, a program smaller than 32k which runs at tpa can be
- ; copied and started with a GO
-
- FILELOC EQU TPA ; Location file read in
- RECBLKS EQU 255 ; About 32k buffer. Leaves transient at 8000h alone.
-
-
- ; SHOW REMAINING SPACE ON EXIT
-
- MCSPA EQU YES ; Show free space
- MCSP EQU MCSPA AND SPACEON
-
- ; INCLUDE COMMAND LINE OPTION PROCESSING
-
- MCOPT EQU YES
-
- ; THIS CODE IS IN PEEP (if enabled)
-
- if [not peepon]
- filcheck:
- ld hl,fcb1+1
- ld a,' '
- cp (hl)
- filcx: ret nz
- CALL PRFNF ; ROUTINE IS ELSEWHERE IN RCP
- JP EXIT
-
- opensource:
- ld de,fcb1
- ld c,openf
- call bdos
- inc a
- jr filcx
-
- endif ; not peepon
-
- ;
- ; START OF MULTI-COPY
- ;
-
- MLTCPY:
- CALL RETSAVE ; Set up CPR return
-
- call filcheck ; Look at command line
-
- call savspecs ; Save destination filename and du's
-
- call logsu ; Log source user for search function
- cpyflg equ $+1 ; In code mod of selection flag
- ld a,81h ; Flag SYS and DIR
- CALL GETDIR ; Get list of afn matches
- jp z,filcx ; No matches
-
- ; SET UP DESTINATION FCB POINTER
- push hl ; Points to start of file list
- ld de,-36 ; Room for an fcb
- add hl,de
- ld (destfcb),hl
- ld a,(fcb2) ; Save dest drive now that we know where
- ld (hl),a
- or a
- call z,getdefdrive ; Make drive explicit
- pop hl
-
- ;
- ; MAIN PROGRAM LOOP
- ;
- ; Enter with HL -> first file name in list
-
- loop:
- push hl ; Save list position
- ld de,fcb1+1 ; Move name to source fcb
- ld bc,11
- ldir
- CALL INITFCB1 ; Zero out rest of fcb
- pop hl ; Restore list postion
- ld de,(destfcb) ; Copy same name to dest fcb
- inc de ; -> name
- ld bc,11
- ldir ; When done, HL -> next name on list
- push hl ; Save list position
- ld hl,(destfcb)
- CALL INITFCB2 ; Clean up the dest fcb
-
- if mcopt
- call specs ; Examine file for attributes
- jp p,lp21 ; Doesn't have selected att
- endif ;mcopt
-
- call rename ; If dest to be renamed, do it
- call pfil ; Display file name
- call opfiles ; Open source and dest files
- jr z,lp2 ; Z = dest file exists AND don't erase it
- lp1:
- call r$wfiles ; Read and write RECBLKS records
- ld a,(cflag) ; Is entire file copied?
- or a
- jr nz,lp1 ; No
- call close ; Close the destination file
-
- lp2: call crlf
- lp21: pop hl ; Restore list pointer
- ld a,(hl) ; 0 terminator of name list
- or a
- jr z,mcexit
- call BREAK ; Routine in RCPSUBS to abort on ^C
- jr loop
-
- mcexit:
- IF MCSP
- ld hl,(destfcb)
- ld a,(hl) ; Report space on destination disk
- ld (fcb),a
- jp spaexit ; DONE
- ELSE
- jp exit
- ENDIF
-
-
-
- ;
- ; SUBROUTINES
- ;
-
- ; COMMAND LINE INTERP
- savspecs:
-
- ; Save destination filename. Set renaming flag.
- savdest:
- ld hl,fcb2+1
- sd00: ld a,(hl) ; Name blank?
- cp '/' ; Option trig
- jr nz,sd01
- ld (hl),' '
- jr sd00
- sd01: sub ' '
- ld (rflag),a ; Rename flag: Z = don't
-
- ld bc,11 ; Dest name -> savfcb
- ld de,savfcb
- ldir
-
- if mcopt
- call filspec ; Get any option
- endif ;mcopt
-
- ; Save the drives and users of source + destination
-
- savdu:
- ld a,(fcb+13) ; Get and store user #'s
- ld (susr),a
- ld a,(fcb2+13)
- ld (dusr),a
- ld hl,fcb ; If drive is default, make it explicit
- ld a,(hl)
- or a
- ret nz
-
- getdefdrive: ; Load default drive into @HL
- push hl
- ld c,inqdiskf
- call bdos
- pop hl
- inc a
- ld (hl),a
- ret
-
- if mcopt
- ; Check command line for an option
- filspec:
- xor a
- ld (aflag),a ; Init attribute flag Z = none
- ld (sflag),a ; Sense Z= normal
- ld (iflag),a ; Init inspect Z = no
- inc a
- ld (cpyflg),a
-
- ld hl,tbuf ; Scan tail for '/'
- fspec1: inc hl
- ld a,(hl)
- or a
- ret z ; Z = no '/'
- cp '/'
- jr nz,fspec1
-
- fspec2:
- inc hl ; Char after '/'
- ld a,(hl)
- cp '~' ; Negation option
- jr z,fspecN ; Set a flag
- cp 'I'
- jr z,fspecI
- cp 'A'
- jr z,fspecA
- cp 'S'
- jr z,fspecS
- sub '0'
- cp 1
- ret c
- cp 5
- ret nc
- fspec21:
- ld (aflag),a
- ret
-
- fspecA:
- ld a,11 ; Offset of archive att byte
- jr fspec21
- fspecI:
- ld (iflag),a
- ret
- fspecN:
- ld a,80h
- ld (sflag),a
- jr fspec2
-
- fspecS:
- ld a,(sflag) ; 0 = sys, 80h = dir
- ld (cpyflg),a
- ret
-
- fspec4:
- ld a,' ' ; Don't take '/' as second file name
- ld (fcb2+1),a
- ret
-
-
- ;
- ; CHECK MATCHED FILE NAME FOR ATT BIT SET
- ;
- specs:
- ld a,(aflag)
- dec a
- ret m ; A = 0..3,10
- ld hl,(destfcb)
- inc hl
- ld e,a
- ld d,0
- add hl,de
- ld a,80h
- and (hl) ; If high bit set, A = 80h, else A= 0
- ex af,af' ; Save flags
- ld a,(sflag) ; What is sense of flag?
- or a
- jr nz,spec01
- ex af,af' ; Normal sense, restore flags
- ret ; Test for P on return.
- spec01:
- ex af,af'
- dec a ; Reverse sense A = 7fh or ffh
- ret
-
- endif ;mcopt
-
- ; RENAME DESTINATION FILE
-
- rename:
- ld a,(rflag) ; Rename wanted?
- or a
- ret z ; No (leaves att alone except for r/o)
-
- ld b,11 ; Matched source name has been copied
- ld hl,savfcb ; Use template to overwrite unambig chars
- ld de,(destfcb)
- inc de ; Point to file name
- ren1: ld a,(hl)
- cp '?' ; Leave wild card parts alone
- jr z,ren2
- ld (de),a ; Rename other parts
- ren2: inc hl ; Next pair of chars
- inc de
- djnz ren1
- ret
-
-
- ; Log source or dest user
-
- logsu: ld a,(susr)
- jr log
- logdu: ld a,(dusr)
- log: JP SETUSR
-
-
-
- ; OPEN SOURCE AND DESTINATION FILES
- opfiles:
-
- ; Open source file
- opsrc:
- call logsu
- call opensource ; Routine in rpeep
-
-
- ; Open destination file
- opdest:
- ld de,tbuf ; Restore DMA to 80h
- ld c,setdmaf
- call bdos
-
- call logdu ; Dest user
-
- ld de,(destfcb) ; Make sure file is not R/O
- ld hl,9 ; Offset of attr
- add hl,de
- res 7,(hl) ; Reset bit 7
-
- if mcopt
- ld a,(iflag) ; Are we in inspect mode?
- or a
- jr z,od0 ; No
-
- call eraq1 ; Do it?
- jr z,od0 ; Yes
- xor a ; Return Z= skip
- ret
- endif ;mcopt
-
- od0:
- ld c,srchff ; Check existence of destination
- call bdosde
- cp 0ffh ; Preserve offset in A
- jr z,od1 ; No file
-
- call file$exists ; Deal with existence of file
- ret z ; Copy aborted
-
- od1:
- ld c,makef ; Make new file
- call bdosde
- inc a
- jp z,DIRERR ; Unable to make new file
- ret ; Normal exit returns NZ
-
-
- ; Destination file exists:
- ; Locate file name in tbuf
- ; Make sure file is not being copied to itself
- ; Find out if file is R/O and warn user
- ; Finally, do we want to erase it?
-
- file$exists:
- rrca ; Find entry into TBUF
- rrca
- rrca
- add a,80h
- ld l,a
- ld h,0 ; Now pointing to user number of entry
-
- ld a,(susr) ; Compare users
- cp (hl)
- jr nz,fil$ex2 ; Different
- ld a,(fcb) ; Compare drives
- ld c,a
- ld de,(destfcb)
- ld a,(de)
- cp c
- jr nz,fil$ex2 ; OK
-
- call print ; Don't do copy
- db ' ?','?'+80h
- xor a
- ret
-
- fil$ex2:
- inc hl ; Point to start of name
- CALL ROTEST ; R/O ?
- call ERAQ ; Erase?
- jr z,erase1 ; Answered yes
- xor a
- ret
-
- erase1:
- ld c,attrf ; Take care of R/O status
- call bdosde ; DE -> dest fcb
- ld c,erasef ; Erase the file
- call bdosde
- or a,-1 ; NZ return means we said "YES"
- ret
-
- ; FORMAT THE RUNNING FILE NAME DISPLAY
- pfil:
- call print
- db ' Copying -->',' '+80h
- ld de,fcb1
- call pdsk
- ld a,(susr)
- call pusr
- call pfn
- call print
- db ' to',' '+80h
- ld de,(destfcb)
- call pdsk
- ld a,(dusr)
- call pusr
- ld a,(rflag) ; Don't reprint name if same
- or a
- ret z
-
- pfn: ex de,hl
- inc hl
- JP PRFN
-
-
- pdsk: ld a,(de) ; Print file drive DE -> fcb
- add 'A'-1
- pdsk0: jp CONOUT
-
- pusr: ld c,'0' ; Print user number in A
- cp 10
- jr c,pusr1
- pusr00:
- inc c
- sub 10
- cp 10
- jr nc,pusr00
- push af
- ld a,c
- call CONOUT
- pop af
- pusr0: add '0'
- call CONOUT
- ld a,':'
- jr pdsk0
- pusr1: call pusr0
- ld a,' '
- jr pdsk0
-
-
- ;
- ; READ AND WRITE THE FILES
- ; Loop through this routine until entire file copied.
- r$wfiles:
-
- ; READ SOURCE FILE INTO MEMORY
-
- get$fil:
- call logsu ; Log source user #
- xor a
- ld (cflag),a ; Reset copy flag
- ld b,recblks ; Zero count of records read
- ld hl,fileloc ; Location of file buffer
-
- getlp: push bc ; Save count
- call setloc ; Save pointer and set DMA
- ld de,fcb1
- ld c,readf ; Note that readf returns A <> 0
- call bdos ; when reading record after EOF.
- or a ; Hence RCOUNT = 1 on one rec file
- pop bc
- jr nz,wrtfil ; EOF encountered, exit loop
- ld hl,(nxtfile) ; Available scratch pointer
- ld de,128
- add hl,de
-
- CALL BREAK ; ALLOW ABORT
-
- djnz getlp ; Still room
- or a,-1 ; Out of room
- ld (cflag),a ; Set flag copy
-
- ; WRITE FILE TO DESTINATION
-
- wrtfil: ld a,recblks ; B = recblks - (records read)
- sub b ; A = records read
- or a
- ret z ; 0 records copied
- ld b,a ; Count in B
-
- push bc ; Has record count
- call logdu ; Log dest user
- pop bc
-
- ld hl,fileloc ; Write buffer to file
- wrtlp:
- push bc
- call setloc
- ld c,writef
- call bdosde
- or a
- pop bc
- jp nz,full ; Disk full error
- ld hl,(nxtfile) ; Move pointer along 128 bytes
- ld de,128
- add hl,de
-
- CALL BREAK
-
- djnz wrtlp ; And get next record
- ret
-
- ; Save file pointer and set up DMA
- setloc:
- ld (nxtfile),hl
- ex de,hl
- ld c,setdmaF
- jp bdos
-
-
- close:
- ld c,closef
- JP bdosde
-
- ; DEST FILLED. ERASE INCOMPLETE COPY AND RESET DISK.
- full:
- ld c,ERASEF
- call bdosde
- call print
- db cr,lf,'Disk ful','l'+80h
- ld c,13 ; Disk reset BDOS function
- call bdos
- fullx: xor a
- jp mcexit ; Quit
-
-
- bdosde: ld de,(destfcb)
- jp bdos
-
- ;
- ; Data
- ;
- susr: ds 1 ; Source user
- dusr: ds 1 ; Dest user
- savfcb: ds 11 ; Destination name template
- rflag: ds 1 ; Rename flag Z = no rename
- cflag: ds 1 ; Copy flag Z = finished
- if mcopt
- aflag: ds 1 ; Attribute flag
- iflag: ds 1 ; Inspect flag
- sflag: ds 1 ; Sense flag
- endif ;mcopt
- destfcb:
- ds 2 ; Temp storage for destination FCB
-
- ; END OF RCPMC.LIB
- ct flag
- sflag: d