home *** CD-ROM | disk | FTP | other *** search
Text File | 1992-10-03 | 34.1 KB | 1,484 lines |
- .printx Reading ZFCMDS2.Z80
- ;===========================================================================
- ;
- ; ZFCMDS2.Z80 - Print and View Commands and Code (P, V)
- ; Copy Command and Unsqueeze Code (C)
- ; Move, Delete, Rename Files (M, D, R)
- ;
- ;===========================================================================
-
- ; * * * COMMAND: V
-
- ; Type file to console with pagination set to 'lps' from ENV
- ; <space> single-line scroll using
- ; <ctrl-S> pause screen output
- ; <ctrl-C> cancel operation
- ; <ctrl-X> go to next file
- ; other scroll one page
-
- fview:
- xor a ; Set flags
- ld (first$m),a ; First view
- ld (mflag),a ; Not a mass view
- call view ; View file at ringpos
- jp runsh4 ; Rebuild screen and continue user input
-
-
- ; VIEW - View file at RINGPOS
-
- view:
- call cls
- ld a,1 ; Initialize..
- ld (lpscnt),a ; Lines-per-screen counter
- ld a,swcon ; Console output switch value for SOUT routine
- jr current ; To common i/o processing
-
-
- ; * * * COMMAND: P
-
- ; Send file to logical list device (any keypress cancels)
-
- flist:
- xor a ; Set flags
- ld (first$m),a ; Set for prompt for print
- ld (mflag),a ; Not a mass print
- call lstfile ; Print file at ringpos
- call erclr ; Clear error message line.
- jp loop ; Return for next command.
-
-
- ; LISTFILE - Print file at RINGPOS
-
- lstfile:
- ld a,(first$m) ; Bypass prompt if already issued.
- or a
- jr nz,lstskip
-
- ld hl,msg55 ; "Print (Y/N)? "
- call cprmptyn
- call keyin ; Get response
- call testyn ; Test for YES/NO answer
- jr z,lstf1 ; Proceed if YES
- jp loop ; ..else refresh screen & continue
- lstf1:
- ld (first$m),a ; Bypass prompt next file print.
-
- lstskip:
- ld hl,0 ; Initialize page number
- ld (pagenum),hl
- ld hl,msg56 ; "Printing "
- call ermsg2
- ld hl,(ringpos) ; Pt to file name
- inc hl
- call prfnskip ; Print it
- xor a
- ld (eoflag),a ; File not completed yet.
- ld a,2 ; Initialize lines-per-page counter
- ld (lpscnt),a
- ld a,swlst ; Printer output switch flag for SOUT routine
-
- ; output character for console/list processing
-
- current:
- ld (sctlfl),a ; Set output switch for SOUT routine
- xor a ; Clear the skip-to-end-of-file flag
- ld (skipfl),a
-
- ; output file to console/list
-
- call ringfcb ; Position name to 'fcb'
- call fi0$close ; Close input file if previously opened.
- ld de,s$fcb ; Get fcb with file id.
- call fi0$open ; Open file for byte i/o.
- jr z,zerocr ; If okay, bypass error message.
-
- endfnf:
- cp 4 ; See if fi0$open end-of-file.
- jr nz,fnf ; Br if not. assume file not found.
-
- ; Empty File Error
-
- endf:
- call endf1 ; Print 'empty file' message.
- jr fnfxit ; Exit after user prompt.
-
- ; File Not Found Error
-
- fnf:
- call fnf1 ; Print 'file not found' message
- fnfxit:
- call bottom0 ; Wait for user to respond.
- ld a,(mflag) ; Mass operation?
- or a
- ret nz ; Group operation - continue.
- jp runsh4a ; Single file - refresh screen & continue
-
- ; Print File Not Found Message
-
- fnf1:
- ld hl,msg57 ; "File NOT Found"
- jp ermsg2
-
- ; Print Empty File Message
-
- endf1:
- ld hl,msg58 ; "Empty File"
- jp ermsg2
-
- ; Continue
-
- zerocr:
- xor a
- ld (s$fcb+32),a ; Zero file 'current record' field
- if exptab
- ld (charcnt),a ; Zero char count for tabbing
- endif
- if unsqz
- call usqhdr ; Check for squeezed file.
- endif
- call phead ; Print heading
-
- readlp: ; Get next character (squeezed or not)
-
- if unsqz
- ld a,(usqflg) ; Squeezed file?
- or a
- jr nz,rdlp1 ; Br if not.
- call usqnxt ; Unsqueeze next char.
- jr rdlp2 ; Continue.
- endif ;unsqz
- rdlp1:
- call f0$get ; Get a character
-
- rdlp2:
- jr nz,curdone ; Finished on physical eof.
-
- and 7fh ; Force to ascii
- cp eofchar ; See if end-of-file
- jr z,curdone ; Back to ring loop if 'eof'
-
- call dspchr ; Output to list/console (char in E on return)
- call pager ; Check for 'lf'.
- call condin ; See if user entered a character
- and 7fh ; If character there, then abort..
- call nz,canview ; Already got char
- jr readlp ; If not, continue with next character.
-
- ; EOF reached (if 'view', wait for user before returning to command mode)
-
- curdone:
- ld a,(sctlfl) ; Console output?
- cp swcon
- jp z,bottom ; If so, prompt user
- ld (eoflag),a ; Force final form feed
- jp formfd ; Complete processing this file.
-
- ; Test for end of page and prompt for continuation if so
-
- if usedseg
- dseg
- endif
-
- skipfl: ds 1 ; Skip-to-end-of-file flag
-
- if usedseg
- cseg
- endif
-
- pager:
- ld a,e ; (character in e-reg)
- cp lf
- ret nz
- if exptab
- xor a ; Zero char count
- ld (charcnt),a
- endif
- ld a,(sctlfl) ; Check switch flag for printer output
- cp swlst
- jr z,pagep ; Branch if outputting to printer
-
- ld a,(skipfl) ; If skip-to-end-of-file is active
- or a ; ..then return to displaying
- ret nz ; ..the file
-
- ld b,22 ; Lines per screen
- ld a,(lpscnt) ; Check for lines-per-screen limit
- inc a
- ld (lpscnt),a
- cp b
- ret c ; If not, return
- xor a ; Else, initialize for next screenful
- ld (lpscnt),a
- ld hl,msg59 ; " [sp=line cr=screen ^x=file..."
- call pstri
- call dkeyin ; Wait for keyboard input
- push af ; Save it while clearing the prompt
- ld b,60
- call ereol ; Clear to End of Line
- ld a,cr
- call cout
- pop af ; Get character back
- cp skipch ; See if skip-to-end character
- jr nz,pager1 ; If not, continue
- ld a,0ffh ; Set skip flag
- ld (skipfl),a
- ret ; Back to displaying file
- pager1:
- cp ' ' ; See if <space> bar..
- jr nz,canview ; If not, see if cancel.
- ld a,22 ; Set for single line
- dec a
- ld (lpscnt),a ; Scroll and..
- ret ; Return for one more line.
-
- ; Check for new page on printer
-
- pagep:
- ld a,(ltpp) ; Get number of lines of text per page
- ld b,a ; ..in B
- ld a,(lpscnt) ; Is counter at limit of lines-per-page
- inc a
- ld (lpscnt),a
- cp b
- ret c ; If not, return; else, fall thru to formfd
-
- ; Print Form Feed
-
- formfd:
- ld a,(lpscnt) ; Get lines printed already into B
- ld b,a
- ld a,(lppp) ; Get total lines per physical page
- sub b ; Compute lines to skip
- ret z ; If zero, we are done already
- ld b,a ; Else, move count into B
- ld a,2 ; Reinitialize lines-per-screen counter
- ld (lpscnt),a
- ld a,(lffeed) ; Form feed available?
- or a ; 0=no
- jr nz,prfeed
-
- ; No formfeed capability available in printer
-
- ld c,list ; Lst output
- pagelst:
- call lcrlf ; New line on lst
- djnz pagelst
- jr ffhdrck ; Print heading and continue.
-
- ; Printer has formfeed capability
-
- prfeed:
- call lcrlf ; New line
- ld a,ff ; Send form feed char
- call lout
-
- ffhdrck:
- ld a,(eoflag) ; End of current file?
- or a
- ret nz ; No heading after final form feed.
- jr phead ; Print header and done
-
- canview:
- cp ctrlc ; ^c?
- jp z,runsh4 ; Quit to command prompt
- cp ctrlx ; Cancel this file?
- jr z,canview1 ; Branch if so
- cp ctrls ; Pause request?
- ret nz ; If not, continue display
- call dkeyin ; If so, wait for another key
- cp ctrls ; If not another control-s
- jr nz,canview ; ..test again for control-c or control-x
- ret ; Otherwise, resume
- canview1:
- pop bc ; Yes. return one level higher
- ret
-
- ; Print Heading
-
- phead:
- ld hl,headmsg ; Pt to heading
- ld b,6 ; Get length.
- call phead3a ; Print string.
-
- ld hl,s$fcb+1 ; Pt to file name
- call pheadfn ; Print file name in heading
-
- if unsqz
- ld a,(usqflg) ; Squeezed file?
- or a
- jr nz,phead2 ; Br if not.
-
- ld hl,usqsep ; Pt to usq file name separator.
- ld b,5 ; Get length.
- call phead3a ; Print string.
-
- ld hl,d$fcb+1 ; Pt to original file name
- call pheadfn ; Print file name in heading
- endif ;unsqz
- phead2:
- ld a,(sctlfl) ; Check for printer output switch
- cp swlst
- jr nz,phead2a ; If not printing, skip page number display
-
- ld hl,pagehdr ; Print 'Page' header
- ld b,8
- call phead3a
- ld hl,(pagenum) ; Get last page number
- inc hl ; Increment to current page
- ld (pagenum),hl ; Save it
- call shlfdc ; Print current page number
-
- phead2a:
- ld hl,headskp ; New line, blank line
- ld b,4 ; 4 chars
-
- phead3a:
- ld c,0 ; Display all chars
- jr phead3
- phead3b:
- ld c,' ' ; Skip spaces
- phead3:
- ld a,(hl) ; Get char
- push bc
- cp c ; Is it char to skip?
- call nz,dspchr ; If not, output to list/console
- pop bc ; Restore regs.
- inc hl ; Pt to next
- djnz phead3
-
- if exptab
- xor a ; Reset character counter
- ld (charcnt),a ; ..after header has been printed
- endif ; exptab
-
- ret
-
- ; Print a file name in heading, suppressing imbedded spaces. Called with
- ; HL pointing to name in FCB.
-
- pheadfn:
- ld b,8 ; 8 chars
- call phead3b
- ld a,'.' ; Dot
- call dspchr
- ld b,3 ; 3 more chars
- jr phead3b
-
- ; Output character to list/console (return character in E register,
- ; preserve HL)
-
- dspchr:
- push hl
- ld e,a ; Save character in E
- push de
-
- if exptab
-
- ld a,e ; Check for tab character
- and 7fh
- cp tab
- jr nz,notab ; Skip if not
-
- ld e,' ' ; Output space characters
- tabl:
- ld a,e
- call sout ; Switched output
- ld hl,charcnt ; Increment char count
- inc (hl)
- ld a,(hl) ; Get new count
- and 7 ; Check for done at every 8
- jr nz,tabl
- jr tabdn
-
- notab:
- call vwchar ; Output character
- ; call sout ; Switched output library routine
- ld hl,charcnt ; Increment char count
- inc (hl)
- tabdn:
- pop de ; Get char in e in case pager is called
- pop hl
- ret
-
- else ; not exptab
-
- call vwchar ; Output viewable char
- ; call sout ; Switched output library routine
- pop de ; Get char in e in case pager is called
- pop hl
- ret
-
- endif ; exptab
-
- ; Filter output per FILTFLA setting
- ; If filter, remove high bit and only output CR and LF controls.
- ; Char in A
-
- vwchar:
- ex af,af' ; Save char
- ld a,(filtfla) ; Filter?
- or a
- jr z,vwchar1 ; No
- ex af,af' ; Recover char
- and 7fh ; Remove high bit
- cp 7fh
- ret z ; DEL
- cp 20h ; First printable char
- jr nc,vwchar2 ; Alpha, send it
- cp cr
- jr z,vwchar2
- cp lf
- jr z,vwchar2
- iff exptab ; not exptab
- cp tab
- jr z,vwchar2
- endif ; not exptab
- ret
-
- vwchar1:
- ex af,af' ; Recover char
- vwchar2:
- jp sout ; Switched output
-
- ; BOTTOM - Position at Bottom of Screen and Prompt for Continuation of Listing
- ; by Entering ^X or ^C
-
- bottom:
- ld hl,botadr ; Position cursor
- call gotoxy
- call vprint
- db ' EOF ',0
- bottom0:
- ld hl,botadr+5
- call gotoxy
- ld hl,msg60 ; "[^x:next ^c:abort] "
- call pstri
- bottom1:
- call dkeyin
- cp ctrlx
- ret z ; If control-x, return and continue
- cp ctrlc
- jr nz,bottom1 ; If not control-c, loop until one of the two
- ld a,(mflag) ; Mass operation?
- or a
- call nz,stag ; If so, soft-tag the file just viewed
- jp runsh4 ; If control-c, start over at command level
-
-
- ; * * * COMMAND: C
-
- ; Copy source file at current 'ring' position to another drive.
- ; Set-up FCB's and buffer area and check for correct keyboard inputs.
- ; Contains auto-CRC file copy verification.
-
- fcopy:
-
- ; Set Flags for First Time Thru and No Mass Copy
-
- xor a ; A=0
- ld (first$m),a ; Set for prompt for destination
- ld (mflag),a ; Not a mass copy
-
- ; Do Copy
-
- ld hl,msg61 ; "Copy File"
- call ermsg2
- call copy ; Do copy of file at ringpos
- call erclr
-
- jp loop ; Return to Same File
-
- ; Copy File at RINGPOS
-
- if usedseg
- dseg
- endif
-
- cflag:
- ds 1 ; Copy-success flag (ff = good copy)
- tattrfl:
- ds 1 ; Temporary set attributes option flag
- tdestfl:
- ds 1 ; Temporary use destination attributes flag
- tarcfl:
- ds 1 ; Temporary always set archive attribute flag
-
- if usedseg
- cseg
- endif
-
- copy:
- ld hl,attrfla ; Source of attribute control flags
-
- copym: ; Entry point for copy part of move cmd
- ld de,tattrfl ; Destination for flags
- ld b,3 ; Copy three flags
- call movec
- xor a ; Initialize copy flag
- ld (cflag),a
-
- if datestamp
- ld (gotstp),a ; Initialize got stamp flag
- endif ;datestamp
-
- ld hl,0 ; Initialize storage for..
- ld (crcval),hl ; 'crc' working value.
- call ringfcb ; Move from 'ring' to 'sfcb' with attributes
- ld b,32 ; Copy source 'fcb' to destination 'fcb'
- ld hl,s$fcb+1 ; From point..
- ld de,d$fcb+1 ; To point..
- call movea ; Copy, stripping attributes
- ld de,s$fcb ; Open file for reading
- ld c,open ; Open function
- call bdosptr
-
- if datestamp
- ld (ssector),de ; Save source sector number
- ld (sindex),a ; ..and directory offset
- endif ;datestamp
-
- inc a ; 0ffh --> 00h if bad open
- jp z,fnf ; File not found
-
- ; Source File is Open
-
- copy2:
- ld de,s$fcb+1 ; Save attributes of source
- call saveattr
- ld a,(first$m) ; If not first time through
- or a ; ..skip getting destination directory
- jr nz,copy3m ; ..and resetting disk system
- dec a ; A=0ffh
- ld (first$m),a ; Set not first time any more
- ld hl,msg62 ; "to Dir: "
- call cprmpt2 ; Prompt for drive selection
- call cpy$d$u
- ld a,(vflag) ; Copy default verify flag into temporary flag
- ld (tvflag),a
- ld a,(qryvfya) ; See if verify option is set
- or a
- call nz,vfyreq
-
- ; Check to ensure that either drives or user areas are different
-
- ld hl,(du$req) ; Get requested du
- ld de,(du$dest) ; And destination du
- call cmpdehl ; Compare..
- jr nz,copy3 ; Branch if different
- ld hl,msg63 ; "Src Dir = Dest Dir"
- call ermsg2 ; If not, show error condition:
- jp loop ; Try again?
-
- ; First File Copy - Reset System
-
- copy3:
- call reset ; Make sure disk is read/write
- ; And return to source du:
-
- ; Nth File Copy - Copy without Resetting System
-
- copy3m:
- if datestamp
- call cpm3
- jr nc,notzs ; Don't do it if Plus
- ld c,setdma ; Set up for Get Stamp
- ld de,tdbuff
- call bdosptr
- ld de,s$fcb ; ..of source
- ld c,getstp
- call bdosptr
- ld (gotstp),a ; Save result for Set
- notzs:
- call resdma
- endif ;datestamp
-
- call cufile ; Make new file, erase old if required.
-
- ; Perform Copy
-
- copy6:
- call cprmpt ; Clear prompt and position the cursor
- ld a,(massop) ; Get letter of command requested
- cp 'A' ; Archiv?
- jr z,copy60b
- cp 'M' ; Move?
- jr z,copy60a
- ld hl,msg64 ; "Copying "
- call pstri ; Must be normal copy
- jr copy60c
- copy60a:
- ld hl,msg65 ; "Moving "
- call pstri
- jr copy60c
- copy60b:
- ld hl,msg66 ; "Archiving "
- call pstri
- copy60c:
- ld hl,d$fcb+1 ; Print file name
- call prfnsx
- ld hl,msg67 ; " to "
- call pstri
- ld a,(du$dest+1) ; Print dest du
- add a,'A'
- call cout ; Print disk
- ld a,(du$dest) ; Get user
- call pafdc ; Print user
- ld a,':'
- call cout
- xor a ; Clear 'eof' flag
- ld (eoflag),a
-
- copy6a:
- ld bc,(du$req) ; Get current du
- call logud ; And set it up.
- ld hl,0 ; Clear current-record..
- ld (rec$cnt),hl ; Counter.
- ld hl,(bufstart) ; Set buffer start pointer..
- ld (buf$pt),hl ; To begin pointer.
-
- ; read source file -- fill buffer memory or stop on 'EOF'
- ; -- update 'CRC' on-the-fly
-
- copy7:
- ld hl,(buf$pt) ; Set dma address to buffer pointer
- ex de,hl ; De --> dma address
- ld c,setdma
- call bdosptr
- ld de,s$fcb ; Source 'fcb' for reading
- ld c,read ; Record read function
- call bdosptr
- or a ; 00h --> read okay
- jr z,s$rd$ok
- dec a ; Eof?
- jr z,copy8 ; Yes, end-of-file, set 'eof' flag.
- call resdma ; Reset dma address.
- ld hl,msg68 ; "Read Error"
- call ermsg2
- jp cankey ; Cancel group operation
-
- ; Read OK - Update CRC
-
- s$rd$ok:
- ld a,(tvflag)
- or a
- jr z,copy7b ; Don't bother if no verify
-
- ld hl,(buf$pt)
- ld b,128
- copy7a:
- ld a,(hl) ; Get character and..
- call updcrc ; Add to 'crc' value.
- inc hl
- djnz copy7a ; Loop 'till record read finished
- copy7b:
-
- ; Update Buffer Ptr and Record Count
-
- ld hl,(buf$pt) ; Bump buffer pointer..
- ld de,128 ; By..
- add hl,de ; One..
- ld (buf$pt),hl ; Record.
- ld hl,(rec$cnt) ; Bump buffer..
- inc hl ; Record count and..
- ld (rec$cnt),hl ; Store.
- ex de,hl ; Ready to compare to..
-
- ; Check for Full Buffer
-
- ld hl,(rec$max) ; Maximum record count (full-buffer).
- call cmpdehl ; Compare
- jr nz,copy7 ; If not full, get next record.
- jr copy9 ; Full, start first write session.
-
- ; Indicate end-of-file read
-
- copy8:
- ld a,true ; Set 'eof' flag
- ld (eoflag),a
-
- ; Write source file from memory buffer to destination
-
- copy9:
- ld hl,(bufstart) ; Adjust buffer pointer..
- ld (buf$pt),hl ; To start address.
- call cuwrite ; Write buffer to disk.
- jp z,copy6a ; Branch to read next buffer full
- ld a,(tvflag) ; Verify?
- or a
- jp z,cua$log ; No verify
- jp crc$cmp ; Compare file crc's and return
-
- ; Get Destination drive and user for Copy/Usq (full check of drive/user)
-
- cpy$d$u:
- call getfspec ; Get file specification from user
- jr z,nullin ; Exit on null input line.
- call vfy$d$u ; Resolve, verify du or dir access.
- jr z,edef_dir ; Not defined?
- jr c,eacc_dir ; Access error?
- ld (du$dest),bc ; Return destination du
- ret
- nullin:
- call erclr
- jp loop
-
- edef_dir:
- ld hl,msg69 ; "Destination Dir Entry Invalid"
- call ermsg2
- jp loop
-
- eacc_dir:
- ld hl,msg70 ; "Destination Dir Access Denied"
- call ermsg2
- jp loop
-
-
- ; Create New Destination Copy File
-
- cufile:
- ld bc,(du$dest) ; Get destination du
- call logud ; And set it up.
- ld de,d$fcb ; Search for duplicate
- xor a ; Clear destination drive id.
- ld (de),a
- ld c,srchf ; Search for file
- call bdosptr
- inc a ; If not found, 0ffh --> 00h. then..
- jp z,cufile2 ; Go to 'make' function for new file.
-
- call chkpub ; Check if dest. found via Public
- jp nz,cankey ; Abort if so
-
- ; Destination exists -- handle attribute setting
-
- ; Bug - DOS error if copy file to destination where r/o file already is
- ; Fix - d$fcb doesn't contain correct attributes is OPEN doesn't occur here
- ; <rdf>
-
- ; ld a,(tattrfl) ; See if attributes are to be set
- ; or a
- ; jr z,cufile0 ; If not, leave attributes as they are
-
- ld de,d$fcb ; Get dest attributes now.
- ld c,open
- call bdosptr
-
- ld de,d$fcb+1 ; Prepare pointer to destination file name
- ld a,(tdestfl) ; See if destination is to be used
- or a
- call nz,saveattr ; ..and save them
-
- ; Check all the query possibilities
-
- cufile0:
- ld a,(mflag) ; See if single or multiple file operation
- or a
- jr z,single ; Jump if single
- ld a,(massop) ; Is it an archive copy
- cp 'A'
- jr nz,multiple ; If not, go to multiple file case
- ld a,(qryarca) ; Check archive query flag
- or a
- jr z,cufile1 ; If not, get on with it
- jr query ; Else query
- multiple:
- ld a,(qrygrpa) ; Is group query option set
- or a
- jr z,cufile1 ; If not, get on with it
- jr query ; Else, query for overwrite
- single:
- ld a,(qryrepa) ; Is single file replace query option set
- or a
- jr z,cufile1 ; If not, get on with it
- query:
- call atcmd ; Position cursor at command prompt
-
- ld hl,(du$dest) ; Destination drive/user
- ld a,h ; Drive
- add a,'A'
- call cout
- ld a,l
- call pafdc
- ld a,':'
- call cout
- ld hl,d$fcb+1
- call prfnskip
- ld hl,msg71 ; " Exists. Erase (Y/N)? "
- call pstri
- call keyin ; Get answer
- cp ctrlc
- jp z,cancel ; Restart if Control C
- call testyn ; Test for YES/NO answer
- jr z,cufile1 ; Proceed if YES
- jr cufile3 ; ..else skip delete and copy/usq ...
-
- ; Erase destination file and proceed
-
- cufile1:
-
- ; Check destination R/O attribute and prompt if so for deletion.
-
- ld hl,d$fcb ; Pt to fcb
- call attrib ; Clear bytes in fcb and set file r/w if needed
- jr z,cufile3 ; Return to caller if r/w not permitted
-
- ; Delete old file at dest
-
- cufile1a:
- ld de,d$fcb ; Delete existing file
- ld c,erase ; Erase function
- call bdosptr
-
- ; Create new file at dest
-
- cufile2:
- ld de,d$fcb ; Create new file and open for writing
- ld c,make ; Make function
- call bdosptr
-
- if datestamp
- ld (dsector),de ; Save destination sector number
- ld (dindex),a ; ..and directory index
- endif ;datestamp
-
- inc a ; If directory full, 0ffh --> 00h.
- ret nz ; If not, return.
- ld hl,msg72 ; "Dest Dir Full"
- call ermsg2
- jp cankey ; Wait for keystroke
-
- ; Existing file not deleted - return.
-
- cufile3:
- ld bc,(du$req) ; Else get current du
- call logud ; And set it up.
- pop hl ; And return 1 level higher.
- ret
-
-
- ; Write Copy/Usq Memory buffer to Destination File
- ;
- ; Parm: BUFF$PT = start of buffer to be written
- ; REC$CNT = # records to write.
- ;
- ; Returns Z if EOFLAG reset,
- ; NZ if " set, file closed OK.
-
- cuwrite:
- ld bc,(du$dest) ; Get destination du
- call logud ; And set it up.
- cuwrt1:
- ld hl,(rec$cnt) ; Buffer empty?
- ld a,h
- or l
- jr z,cuwrt2 ; Buffer empty, check 'eof' flag.
- dec hl ; Dec buffer record count for each write
- ld (rec$cnt),hl
- ld hl,(buf$pt) ; Set up dma address
- push hl ; Save for size bump
- ex de,hl ; Pointer in de
- ld c,setdma
- call bdosptr
- pop hl
- ld de,128 ; Bump pointer one record length
- add hl,de
- ld (buf$pt),hl
- ld de,d$fcb ; Destination file 'fcb'
- ld c,write ; Write record function
- call bdosptr
- or a ; 00h --> write okay
- jr z,cuwrt1 ; Okay, do next record. else..
- ld hl,msg73 ; "Disk Full"
- call ermsg2 ; Say disk write error.
- ld c,close ; <rdf> - free up disk space
- call bdosptr
-
-
- ; Error in Write -- Delete Destination File and Abort
-
- c$era:
- call resdma ; Reset dma address.
- ld de,d$fcb ; Delete..
- ld c,erase ; Partial..
- call bdosptr ; From directory.
- ld bc,(du$req) ; Source du:
- call logud ; Log it in
- jp cankey ; Back to ring
-
- ; Destination Buffer Written - Check for End
-
- cuwrt2:
- ld a,(eoflag) ; Buffer all written, check for 'eof'.
- or a
- ret z ; Return to read next buffer full
- ld de,d$fcb ; Point at 'fcb' for file closure
- ld c,close
- call bdosptr
- inc a ; If no-close-error then..
- jr nz,cuwrt3 ; Copy attributes
- ld hl,msg74 ; "Close Error"
- call ermsg2
- jr c$era
-
- ; Copy attributes as required
-
- cuwrt3:
- if datestamp
- ld a,(gotstp) ; See if ZSDOS Get Stamp succeeded
- dec a ; 1 means ok
- jr nz,cuwrt3a ; No
- ld de,tdbuff ; Point to stamp
- ld c,setdma
- call bdosptr
- ld de,d$fcb ; Point to file
- call initfcb ; SYSLIB (prepare for SetStp)
- ld c,setstp
- call bdosptr
- cuwrt3a:
- endif ;datestamp
-
- ld a,(tattrfl) ; Check option to set attributes
- or a
- jr z,cuwrt4 ; If not set, skip copying attributes
-
- ld de,d$fcb+1 ; Pointer to destination file name
- call restattr ; Get the saved attributes back
-
- cuwrt4:
- ld a,(tarcfl) ; Should destination be marked as archived?
- or a
- jr z,cuwrt5 ; No
-
- ld hl,d$fcb+11 ; Point to archive attribute position
- set 7,(hl) ; Set high bit
- jr cuwrt6 ; ..and set attributes
-
- cuwrt5:
- ld hl,(attribs) ; Were any attributes saved?
- ld a,h
- or l
- jr z,cuwrt7 ; No, so skip set
- cuwrt6:
- ld de,d$fcb ; Set attributes in directory
- ld c,attr
- call bdosptr
- cuwrt7:
- or 255 ; Flag no error
- ret
-
- ; Read Destination File and Compare CRCs
-
- crc$cmp:
- ld hl,(crcval) ; Transfer 'crc' value to..
- ld (crcval2),hl ; New storage area.
- ld hl,0 ; Clear working storage..
- ld (crcval),hl ; To continue.
- call resdma ; Reset dma address
- ld de,d$fcb
- call initfcb
- ld c,open
- call bdosptr
- inc a ; 0ffh --> 00h if bad open
- jr z,badcrc ; If bad open, just say 'bad-crc'.
- xor a ; Zero 'fcb'..
- ld (d$fcb+32),a ; 'cr' field.
- ld hl,msg75 ; "Vfy"
- call pstri
-
- crcwf1:
- ld de,d$fcb
- ld c,read
- call bdosptr
- or a ; Read okay?
- jr z,d$rd$ok ; Yes, read more.
- dec a ; Eof?
- jr z,fincrc ; Yes, finish up and make 'crc' comparison.
- ld hl,msg76 ; "Verify Read Error"
- call ermsg2
- jp cankey ; Wait for keystroke
-
- ; Block Read OK - Update CRC
-
- d$rd$ok:
- ld hl,tbuff
- ld b,128
- crcwf2:
- ld a,(hl) ; Get character to..
- call updcrc ; Add to 'crc' value.
- inc hl
- djnz crcwf2
- jr crcwf1
-
- ; Read Complete - Check CRCs
-
- fincrc:
- ld de,(crcval) ; Put written-file 'crc' into de
- ld hl,(crcval2) ; Put read-file 'crc' and..
- call cmpdehl ; Compare 'de/hl' for equality.
- jr nz,badcrc ; If not zero, show copy-error message.
-
- ; Log into Current User Area, Return to caller
-
- cua$log:
- call vprint
- db ' OK ',0
- ld a,0ffh ; Show successful copy
- ld (cflag),a
-
- if datestamp
- ld a,(gotstp) ; If copied via ZSDOS?
- dec a
- call nz,copydate ; No, copy via COPYDATE
- endif ;datestamp
-
- call resdma ; Set default dmaadr
- ld bc,(du$req) ; Get current du
- jp logud ; Set it up, and return to caller.
-
- ; Error on Copy
-
- badcrc:
- call cua$log ; Return to current user
- ld hl,msg77 ; " -- CRC Error"
- call ermsg2
- jp cankey
-
-
- ; CHKPUB - Check for Public Conflicts
- ;
- ; Entry: D$FCB holds FCB of opened file
- ; Exit: (Z) if no conflict
- ; Message printed and (NZ) if conflict
- chkpub:
- ld ix,d$fcb
- bit 7,(ix+7) ; File opened via ZSDOS path/public?
- ret z ; No conflicts
- ld hl,msg78 ; "Public File Conflict"
- call ermsg2
- or 0ffh
- ret
-
-
- ; ATTRIB - Check for destination R/O file
- ;
- ; If destination is R/O, prompt for permission to erase it and, if granted,
- ; set the file to R/W. This routine is called by the C and D functions.
- ;
- ; Return code: 0FFH (NZ) indicates OK to proceed
- ; 0 (Z) indicates abort
- ;
- ; Note - now assumes attributes of FCB at HL have been initialized with
- ; File Open (copy) or from ring (delete).
- ;
- attrib:
- push hl ; Save d$fcb pointer
- push hl
- pop ix ; Copy pointer
- bit 7,(ix+9) ; Test file r/o
- jr z,attrib1 ; r/w
-
- call erclr ; Position cursor to error line
- pop hl ; Get the fcb ptr again
- push hl ; And save it again
- inc hl ; Pt to file name
- call prfnskip ; Print file name
- ld hl,msg79 ; " is R/O. Erase (Y/N)? "
- call pstri ; And query
- call keyin ; Get response
- push af
- call erclr ; Clear error line
- pop af
- cp ctrlc
- jp z,cancel ; Restart if Control C
- call testyn ; Test for YES/NO answer
- jr z,attrib1 ; Proceed if YES
- pop hl ; ..else clean up and
- xor a ; ..return error
- ret
- ;
- ; Reset all attributes in FCB for Make File. If file is
- ; r/o, also reset on disk for Erase.
- ; <rdf> changes
- ;
- attrib1:
- ; xor a ; Clear carry
- pop ix ; Get ptr to d$fcb
- bit 7,(ix+9) ; Test r/o again
- ; jr z,attrib2
- ; ccf ; Set carry if r/o
- attrib2:
- push af ; Save r/o test result <rdf>
- push ix
- pop hl ; Get ptr to d$fcb
- push hl ; Save again
- inc hl ; Point to first character
- ld b,11 ; 11 Bytes
- attrib3:
- res 7,(hl) ; Remove attributes
- inc hl ; Pt to next
- djnz attrib3 ; Count down
- pop de ; Pt to d$fcb
- pop af ; Recover r/o test
- ld c,attr
- ; call c,bdosptr ; Reset attributes on disk if r/o
- call nz,bdosptr
- or 0ffh ; No error return
- ret
-
-
- ; SAVE and RESTORE ATTRIBUTES
- ;
- ; These routines save and restore the attributes of a file. On entry DE
- ; points to the file name in the FCB after the file has been opened so that
- ; the attribute bits are set.
-
- if usedseg
- dseg
- endif
-
- attribs:
- ds 2 ; Place to keep the attribute bits
-
- if usedseg
- cseg
- endif
-
- saveattr:
- ld hl,0 ; Initialize HL
- ld b,16 ; Read 16 characters to fill HL
- saveattr1:
- ld a,(de) ; Get character from file name
- inc de ; Point to next one
- rla ; Move attribute bit into carry
- rl l ; Move it into L
- rl h ; Move carry from L into H
- djnz saveattr1 ; Loop
- res 6,h ; Always set dest. to "private"
- ld (attribs),hl ; Save the bits
- ret
-
- restattr:
- ld hl,(attribs) ; Get stored attribute bits
- ex de,hl ; Now HL points to name in dest FCB
- ld b,11 ; Attributes to copy
- restattr1:
- xor a ; Initialize A
- rl e ; Shift a bit left out of DE into carry
- rl d
- rra ; Move it into high bit of A
- or (hl) ; Add in file name character
- ld (hl),a ; Put result back
- inc hl ; Point to next character
- djnz restattr1 ; Loop
- ret
-
-
- ; COMMAND: 'M' Move files
-
- move:
- ld hl,msg80 ; "Move File"
- call ermsg2
- xor a
- ld (mflag),a ; Not mass operation
- ld (first$m),a ; Ask destination
- call copy
- ld a,(cflag) ; See if copy performed successfully
- or a
- jr nz,fdel0 ; If so, go delete source
- call erclr ; If not, clear 'Move File' message
- jp loop
-
-
- ; * * * COMMAND: D
-
- fdel:
- xor a ; Set no mass operation
- ld (mflag),a
- call ringfcb ; Get filename into s$fcb
- call delprmpt ; Prompt for deletion
- jp nz,loop ; If rejected, back to command loop
- fdel0:
- call delete ; Delete file
-
- ; Was Deletion Done? Abort if Not
-
- ld a,(delcode) ; 0=not done
- or a
- jp z,loop ; Abort if not
-
- ; Check for deletion of All local files
-
- ld hl,(locend) ; Move in end
- ld de,-eltsiz
- add hl,de
- ld de,(locbeg) ; Erased all local files?
- call cmpdehl
- jr nz,fdel1 ; No - continue
- ld (locend),hl ; Yes - set new local end.
- jp cmdloop ; Start on first screen again.
-
- ; Check for deletion with full screen of files remaining.
-
- fdel1:
- ld de,(ringend) ; Last screen of files?
- call cmpdehl
- jr nz,fdel4 ; No. redisplay with new last file.
-
- ; Check for Deletion of last file in ring.
-
- push hl ; Save new local end.
- ld de,(ringpos) ; Deleted file was last file in ring?
- call cmpdehl
- jr nz,fdel2 ; No? rebuild shorter display.
-
- ; Last file in ring deleted - move back one position
-
- ld de,-eltsiz ; Reset position to new end.
- add hl,de
- ld (ringpos),hl
- call psn$back ; Back up cursor by one file
-
- ; Erase file at previous last file position
-
- fdel2:
- ld hl,(curat) ; Save current cursor position
- ld (scurat),hl
- call cur$last ; Position to previous last file.
-
- ld b,entsiz ; Blank it
- ld a,' '
- fdel3:
- call cout
- djnz fdel3
-
- ld hl,(scurat) ; Restore current cursor position
- ld (curat),hl
- pop hl ; Set new local end.
- ld (locend),hl
-
- ; Redisplay files starting at RINGPOS
-
- fdel4:
- call erclr ; Clear error message line.
- jp runsh5 ; Redisplay current files
-
-
- ; DELETE - Delete filename at RINGPOS - entry point for Mass Delete
-
- delete:
- xor a
- ld (delcode),a ; Set deletion not done
- call ringfcb ; Get file name
- ld a,(mflag) ; Mass operation?
- or a ; 0=no
- jr z,del1 ; Do delete
- ld a,(massop) ; Mass move?
- cp 'M'
- jr z,del1 ; If so, perform as single delete
-
- ; Test for Verify on Mass Delete
-
- ld a,(mdflg) ; Verify?
- cp 'V'
- jr nz,del1 ; Delete without verify
-
- ; Group Delete with Verify
- ; - Verify file deletion
- ; - Delete only if Approved
-
- call delprmpt ; Prompt for deletion of file
- ret nz ; Abort if not approved
-
- ; Display File Deletion Message
-
- del1:
- ld hl,msg81 ; "Deleting "
- call cprmpt2
- call prfns
-
- ; Delete File in S$FCB
-
- del2:
- ld hl,s$fcb ; Check file R/W status
- call attrib
- ret z ; Abort if R/O and delete not approved
- ld de,s$fcb ; Point at delete 'fcb'
- ld c,erase ; Erase function
- call bdosptr
- inc a
- jr nz,delcl0 ; Branch if delete succeeded
- fnf$msg:
- call fnf1 ; Show error message
- jp cankey ; Abort
-
- delcl0: ld a,0ffh
- ld (delcode),a ; Set deletion done
- ld a,(mflag)
- or a
- ret nz ; If mass operation, quit now
-
- ; Close up erased position
-
- ld hl,(ringpos) ; Prepare move up pointers
- push hl
- ld de,eltsiz ; Eltsiz bytes/entry
- add hl,de ; De = 'to' location
- pop de ; Hl = 'from' location
-
- ; Move ELTSIZ-byte ring entries from HL to DE
-
- movup: ex de,hl ; Hl=dest
- push hl ; Check if at end
- ld hl,(ringend) ; Get old end pointer
- call cmpdehl ; Check against current end location
- pop hl
- ex de,hl ; De=dest
- jr z,movdone ; Must be at end of ring
- ld b,eltsiz ; One name size
- call movec ; Move one name up
- jr movup ; Go check end parameters
-
- ; Move Complete
-
- movdone:
- ld (ringend),de ; Set new ring end if all moved
- ld hl,(ringcnt) ; One less element in array.
- dec hl
- ld (ringcnt),hl
- ret
-
-
- ; Prompt for deletion of file
-
- delprmpt:
- call erclr ; Clear the error line
- ld hl,msg82 ; "Delete "
- call cprmpt2
- call prfns ; Print file name in s$fcb
- ld hl,msgyn ; ' (Y/N?)?' message
- call pstri
- call keyin
- push af
- call atcmd ; Clear the command line
- pop af
- cp ctrlc
- jp z,cancel ; Restart if Control C
- jp testyn ; Test for YES/NO and return Z if YES
-
-
- ; * * * COMMAND: R
-
- ; Set-up to rename file at cursor position
- ; scan keyboard buffer and move filename to destination FCB (DFCB)
-
- rename:
- ld hl,(ringpos) ; Point to the file in the ring
- ld de,9 ; Offset to R/O byte
- add hl,de ; Point to it
- ld a,128 ; Set bit 7 of A
- cp (hl) ; Set carry if R/O
- jr nc,renam0 ; File is R/W
-
- call atcmd ; Cursor to command prompt
- ld hl,(ringpos) ; Get ring position
- inc hl ; Point to name
- call prfnskip ; Print file name
- ld hl,msg83 ; " is R/O. Rename anyway (Y/N)? "
- call pstri
- call keyin
- call testyn ; Test for YES/NO answer
- jr z,renam0 ; Proceed if YES
- jp loop ; ..else resume
-
- renam0:
- call erclr ; Clear error line
- renam0a:
- ld hl,msg84 ; "Rename File to: "
- call cprmpt2 ; New name prompt
- ld de,d$fcb ; Pt to fcb to fill
- call filename ; Get file name & init fcb.
-
- ld hl,d$fcb+1 ; Check for any wild cards -- none permitted
- ld b,11 ; 11 bytes
- wildchk:
- ld a,(hl) ; Get char
- inc hl ; Pt to next
- cp '?' ; Wild?
- jr z,wildfnd
- djnz wildchk
-
- ld de,d$fcb ; Search to see if this file exists
- ld c,srchf ; Search first function
- call bdosptr
- inc a ; 0ffh --> 00h if file not found
- jr z,renam1 ; To rename, if duplicate doesn't exist.
-
- ; File exists - warn user and abort
-
- call chkpub ; If found via ZSDOS Public, say so
- jr nz,renam0a ; ..and retry
- ld hl,msg85 ; "File exists"
- call ermsg2 ; File found in current directory
- jr renam0a ; Try again?
-
- renam1:
- ld hl,d$fcb ; -> file id filled in by filename
- ld de,d$fcb+16 ; -> to new file id field of fcb
- ld b,12 ; Amount to move
- call movec
-
- ld hl,(ringpos) ; Move old id from ring to rename 'fcb'
- push hl
- ld de,d$fcb ; Place to move name
- push de
- ld b,12 ; Amount to move
- call movea ; Moves name and not attributes
- pop de ; Point to old name
- pop ix ; Point to ring name
- res 7,(ix+2) ; Ensure new name Private
- bit 7,(ix+9) ; See if old name r/o
- jr z,renam1a ; Not r/o
-
- ld c,attr ; R/O, so set r/w first
- push de
- call bdosptr ; Clear attributes
- pop de
- renam1a:
- ld c,ren ; Rename file.
- call bdosptr
-
- ; Copy original drive and attribute settings to new name
-
- ld de,(ringpos) ; DE points to original file data
- ld hl,d$fcb+16 ; HL points to new file data
- push de ; Save pointer for use below
- ld b,11 ; Number of chars to scan for attributes
- renam2:
- inc hl ; Advance pointers
- inc de
- ld a,(de) ; Get char in original name
- and 80h ; Isolate attribute bit
- or (hl) ; Merge with char in new name
- ld (hl),a ; Save result in FCB
- ld (de),a ; ..and in ring
- djnz renam2 ; Loop through file name and type
-
- pop ix
- bit 7,(ix+9) ; If file was r/w
- jr z,renam3 ; ..then attributes preserved on disk
-
- ld de,d$fcb+16 ; Else restore attributes from FCB
- ld c,attr
- call bdosptr
- renam3:
- jp runsh5 ; Quit
-
- ; Wild char found in file name -- error
-
- wildfnd:
- ld hl,msg86 ; "AFN NOT Allowed"
- call ermsg2
- jp renam0a ; Try again
-
- ; End of ZFCMDS2.Z80
-