home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
CP/M
/
CPM_CDROM.iso
/
beehive
/
utilitys
/
rpeep12.arc
/
RPEEP.LIB
next >
Wrap
Text File
|
1991-08-11
|
20KB
|
988 lines
; RPEEP.LIB - Resident PEEP
;=============================================================================
;
; P E E P C O M M A N D
;
;============================================================================
; +++++++ NOT an official RCP segment.
; This is a hacker's module intended to work with Z33RCP.
; Command: PEEP
; Function: Text File Browser and Lister
; Version: 1.2 4 Nov 1987
; Author: Rob Friefeld, 4607 Colorado St., Long Beach, CA 213-434-7338
; Comments: The CRT protocol has to be hard coded into this module.
; If the TCAP were used, PEEP would not be practical.
; See below for installation
; Version 1.2:
; - LF's stripped from file
; - Bug fix, now can read file which doesn't end with 1Ah (EOF)
; - Adds about 1100 bytes + printer init string to RCP
; Assembly without printer code saves about 180 bytes
;----------------------------------------------------------------------------
; USAGE: Hands rest on the home row of keys. Left hand moves ahead,
; right hand moves back through file.
; ---
; Go To Marker | 0 |
; ---
; Read More Init Set Print
; (if memory full) Printer Marker (from mark)
; --- --- --- ---
; | R | | I | | O | | P |
; --- --- --- ---
; --- --- --- --- --- --- --- --- --- ---
; | A | | S | | D | | F | | G | | H | | J | | K | | L | | ; |
; --- --- --- --- --- --- --- --- --- ---
; End Scan Next Next Find Rpt Prev Prev R/Scan Top
; Screen Line Screen Find Screen Line Screen
;
;
; X - Exit <sp> - Hop 10 lines <cr> - Next Screen (F) </,?> - File Name
;----------------------------------------------------------------------------
;
; PEEP EQUATES
;
; GET WIDTH FROM ENV
envwidth equ no ; T = use ENV, F = use crtwid below
; INCLUDE PRINTER CODE
PEEP$LST EQU yes ; Include printer related code
;bell equ 07h ; If not already added to SYSDEF.LIB
ccpsz equ 800h ; Top mem assumes 800h CCP size
textloc equ tpa ; File will be read in to TPA
crtrows equ 24 ; 24 line screen
scrlns equ crtrows-1 ; Need one line for prompts
crtcols equ 80
crtwid equ crtcols-1 ; May be optionally taken from ENV
tabsize equ 8 ; Tab expansion size
scanspd equ 2000h ; Scroll rate - smaller number goes faster
ovrlap equ 1 ; Number of lines to overlap scroll (0 is OK)
;
; STRING SEARCH BUFFER
; Set size of string to match buffer.
; The TBUF at 80h is not used because it would prevent
; doing a repeat FIND after reading in more of file.
findsz equ 12 ; Size of FIND string buffer
;
; PRINITER INITIALIZATION STRING
; If you wish to send an initialization string with the 'I' command, install
; it here. First byte must be char count.
if peep$lst
init$str:
db 1 ; char count
db cr
endif ; peep$lst
;
; CRT PROTOCOL INSTALLATION SECTION
;
; The defaults are standard for Televideo, Wyse, et al.
;
; CLEAR SCREEN, HOME CURSOR
clr_scr macro
db 1ah+80h ; Not used if CLSON is true.
endm
; CLEAR TO END OF LINE
cl_to_eol macro
db esc,'T'+80h
endm
; HOME CURSOR, DO NOT CLEAR SCREEN
hom_crs macro
db 1eh+80h
endm
; INSERT LINE
ins_line macro
db esc,'E'+80h
endm
; RETURN CURSOR TO START OF BOTTOM LINE OF CRT
ret_crs macro
db esc,'=',scrlns+32,0+32+80h
endm
; STANDOUT MODE. MUST NOT TAKE SCREEN SPACE. USE 0 IF NOT AVAILABLE.
dim_on macro
db esc,')'+80h
endm
; STANDEND
dim_off macro
db esc,'('+80h
endm
;
; END OF CRT PROTOCOL INSTALLATION SECTION
;
;
; CRT ROUTINES USING ABOVE MACROS
;
; INSERT BLANK LINE AT TOP OF SCREEN
inslin: call homcrs
call print
ins_line
; PRINT CR AND CLREOL
cr$clr:
clreol: call print
db cr
cl_to_eol
ret
; HOME CURSOR
homcrs: call print
hom_crs
ret
; RETURN CURSOR TO LAST LINE OF SCREEN
retcrs: call print
ret_crs
ret
; CLEAR SCREEN
if [ not CLSON ]
cls: call print
clr_scr
ret
endif
; START STANDOUT MODE
stndout:
call print
dim_on
ret
; END STANDOUT MODE
stndend:
call print
dim_off
ret
;
; SWITCHING CONOUT
;
if peep$lst
plcon: ld a,listf ; Switch to lst: output
plcon1: ld (conout+8),a ; Poke list byte at ld c,bdosf
ret
plcoff: ld a,wrconf ; Switch to con: output
jr plcon1
endif ; peep$lst
;
; SLOW DOWN SCAN FUNCTIONS
;
wait: ld hl,scanspd
wait0: dec hl ; Down count to 0
ld a,h
or l
ret z
jr wait0
;
; UPCASE CHAR IN A
;
mkupper:
cp 'a'
ret c
cp 'z'+1
ret nc
and 5fh
ret
;
; MAIN PROGRAM
;
peep: call retsave ; Save zcpr return
; LOAD THE SCREEN WIDTH
if envwidth
ld hl,z3env+2fh ; Offset to CRT in use
xor a
cp (hl)
jr z,pinit1 ; Using CRT 0
inc hl
inc hl
inc hl
pinit1: inc hl
inc hl
pinit2: ld a,(hl)
dec a
ld (width),a
endif ;envwidth
; READ IN THE FILE
call getfil ; Read the file into memory
call cls
; RESTART ENTRY FOR READING IN MORE TEXT ON "MEMORY FULL" MESSAGE
resrt: ld hl,textloc ; Set Start Pointer to beginning of file
ld (srtptr),hl
ld (mrkptr),hl ; Set place marker to start of text
;
; PRINT ONE SCREEN OF TEXT
;
prnscr: call homcrs ; Move cursor
call geteos ; Set end of screen pointer
ex de,hl ; Compute position relative to last screen
ld hl,(srtptr)
push hl ; If near end then print entire last screen
xor a
sbc hl,de
pop hl
jr z,prn1 ; We are at or before last screen so go ahead
jp nc,last ; We are past last screen so back up
prn1: ld b,scrlns ; Line count in B
prnlp1: call clreol
call prnline
djnz prnlp1 ; Print SCRLNS lines
ld (nxtptr),hl ; And set Next Pointer
call retcrs ; Cursor to prompt line
;
; COMMAND INPUT ROUTINE
;
command:
call getchr ; Get command
call case ; Scan list of commands
;
; COMMAND LIST: CHAR TO MATCH FOLLOWED BY ADDRESS
;
db 'A' ; Last screen of file
dw last
db 'D' ; Forward a line
dw down
db 'F' ; Next screen
dw next
db 'G' ; Find string
dw find
db 'H' ; Find string again
dw find0
if peep$lst
db 'I' ; Init printer
dw init$prt
endif ; peep$lst
db 'J' ; Previous screen
dw prev
db 'K' ; Back a line
dw up
db 'L' ; Scan backward
dw back
db 'O' ; Set place marker
dw mark
if peep$lst
db 'P' ; Print from marker
dw list
endif
db 'R' ; Read in more text
dw read
db 'S' ; Scan forward
dw scan
db 'X' ; Exit to CPR
dw exit
db ';' ; Top of file
dw top
db '0' ; Go to marker
dw gomark0
db 20h ; <sp> jump ahead 10 lines
dw hop
db cr ; <cr> next screen
dw next
db '/'
dw what ; Show filename
db '?'
dw what
db 0 ; table delimiter
jr command ; Loop back on invalid input
;
; CASE - JUMP TABLE SCANNER
; FORMAT: CALL CASE ;CALL WITH VALUE TO MATCH IN A
; DB VAL1 ;FIRST VAL TO MATCH
; DW ADDR1 ;JUMP ADDRESS
; ...
; DB 0 ;END TABLE
; ELSE NEXT INSTUCTION EXECUTES IF NO MATCH
;
case:
ex (sp),hl ;hl -> next addr after call
ex af,af' ;save char
xor a
case1:
ex af,af' ;restore char
cp (hl) ;match?
inc hl
jr z,case0 ;if match, jump
inc hl ;point to next val
inc hl
ex af,af' ;check for list terminator
cp (hl)
jr nz,case1 ;keep looking
inc hl ;execute next instruction
casex: ex (sp),hl
ret
case0: ld e,(hl) ;load address
inc hl
ld d,(hl)
ex de,hl
jr casex
;
; PRINT ONE LINE OF TEXT
; HL -> first char on entry, next char on exit
;
prnline:
push bc ; Preserve possible loop counter on entry
xor a
ld c,a ; Char counter for CRT width and tabs
ld d,a ; OVFL flag
prnl1:
ld a,(hl) ; Get char
cp eof ; At end?
jr z,prnl2 ; Can occur on text smaller than one screen
inc hl ; Bump pointer
cp cr ; Are we at end of line?
jr z,prnl2
call prnl3 ; Print the character
jr prnl1
prnl2: pop bc
call print
db cr,lf+80h
ret ; Exit routine
; PRINT THE CHAR IF THE LINE IS NOT FULL
prnl3: cp tab
jr nz,prnl5 ; No tab
; TAB EXPANSION
prnl4: ld a,c ; Compute char count MOD tabsize
sub tabsize
jr nc,$-2
neg ; Spaces to next tab in A
ld b,a ; Use as loop counter
ld a,' ' ; Print space
prnl41: call prnl5 ; Send it out, if room, and update char count
djnz prnl41
ret
prnl5:
ld e,a ; Save char
ld a,d ; OVFL flag
or a
ret nz ; Already OVFL
inc c ; Bump char counter
; DISPLAY CONTROL CHARACTERS AS ^n
; Char in E
outchr:
ld a,7fh ; Don't print DEL
cp e
ret z
if peep$lst
ld a,(conout+8) ; Listing?
cp wrconf
jr z,outc1 ; No, check line width before printing
ld a,e ; Restore char
cp 20h
jp nc,conout ; Not a control
call print
db '^'+80h
ld a,e
add 40h ; Make char printable
jp conout
endif ;peep$lst
outc1:
ld a,(width) ; OVFL?
cp c
jr nc,outc2 ; No
outc01:
dec d ; Now have OVFL, make d NZ
call stndout
call print ; Display OVFL indicator
db '>',bs+80h
jp stndend ; And quit
outc2:
ld a,e ; Restore char
cp 20h
jp nc,conout ; Not a control
call stndout
call print
db '^'+80h
inc c ; Bump tab expansion count for '^' char
ld a,(width) ; CRT, is there still room?
cp c
jr c,outc01 ; OVFL
ld a,e ; Restore char
add 40h
call conout
outx: jp stndend
;
; PRINT NEXT SCREEN
;
next: ld hl,(nxtptr)
ld a,eof ; Is there a next screen?
cp (hl)
jr z,hop0 ; No
ld a,ovrlap
or a
jr z,next1
ld b,a ; Back up scroll overlap lines
call pvline
djnz $-3
next1: ld (srtptr),hl ; Next screen is new start pointer
jr top0 ; Print the screen
;
; PRINT FIRST SCREEN
;
top: ld hl,textloc ; Start of text
ld (srtptr),hl ; To start pointer
top0: jp prnscr
;
; PRINT LAST SCREEN
;
last: call geteos ; Top of last screen
ld (srtptr),hl ; Start there
jr top0 ; Print the screen
;
; PRINT NEXT LINE
;
down: ld b,1 ; Loop counter = 1 line
jr hop1 ; Print the line
;
; HOP FORWARD 10 LINES
;
hop: ld b,10 ; Loop counter = 10 lines
hop1: push bc ; Save it
call dnline ; Print next line
pop bc
djnz hop1
hop0: jp command
;
; SCROLL CONTINUOUSLY AHEAD UNTIL A KEY PRESSED
;
scan: call dnline ; Print next line
jr z,hop0 ; Routine returns 0 on EOF
call scstop ; Check for key press
jr scan
;
; WAIT, THEN CHECK FOR BREAK
;
scstop:
call wait ; Pause a few msec
ld c,CONSTF
call bdos
or a
ret z ; No character, continue
pop af ; Dispose of return address
call getchr ; Erase screen echo and dispose of char
jr hop0 ; Back to command list
;
; PRINT NEXT LINE
;
dnline: ld hl,(nxtptr) ; Look at start of next line
ld a,eof ; Is it EOF?
cp (hl)
ret z ; There is no next line
call prnline ; Print the line
ld (nxtptr),hl ; Advance Next Pointer
ld hl,(srtptr) ; Advance Start Pointer
call nxline ; Find start of next line
ld (srtptr),hl
xor a ; A NZ flag on successful return
dec a
ret
;
; SEARCH FOR NEXT LINE OF TEXT
; HL -> starting point
;
nxline: ld a,(hl) ; Look at char
cp eof
ret z ; No more text
inc hl ; Bump pointer
cp cr
jr nz,nxline
ret ; Returns HL at character after LF
;
; PRINT PREVIOUS SCREEN
;
prev: ld hl,(srtptr) ; HL-> char at top of screen
ld a,scrlns
sub ovrlap
ld b,a ; Loop counter SCRLNS lines
prev0: call pvline ; Find start of previous line
djnz prev0
ld (srtptr),hl ; Set Start Pointer
jp prnscr ; Print the screen
;
; SEARCH FOR START OF PREVIOUS LINE OF TEXT
;
pvline: push bc ; Save possible loop counter on entry
ld de,textloc ; Are we already at beginning of file?
ld b,2
prvlp: dec hl
xor a
push hl
sbc hl,de
pop hl
jr c,prv0 ; Yes, so we are done
ld a,(hl) ; Look for last cr
cp cr
jr nz,prvlp ; Haven't found cr yet
djnz prvlp
prv0: inc hl
pop bc
ret
;
; PRINT PREVIOUS LINE
;
up: call upline
up0: jp command
;
; SCAN BACKWARDS UNTIL KEY PRESS
;
back: call upline ; Move up a line
jr z,up0 ; Returns Z if no more lines
call scstop ; Check for break
jr back
;
; MOVE DISPLAY UP A LINE
;
upline: ld de,textloc ; Are we already at start of text?
ld hl,(srtptr)
xor a
sbc hl,de
ret z ; Yes, quit and return Z
call inslin ; Home cursor and insert a blank line
ld hl,(srtptr) ; Back up a line
call pvline
ld (srtptr),hl ; Set pointer
call prnline ; Print the line
ld hl,(nxtptr) ; Set Next Pointer
call pvline
ld (nxtptr),hl
call retcrs ; Return cursor to bottom of screen
call cr$clr ; Erase dead line
xor a ; Return NZ
dec a
ret
;
; FIND A STRING
;
find:
call STNDOUT
call print ; Find string in following pages
db 'Find ->',' '+80h
ld de,fbuf ; Read string to find
ld c,RDBUFF
call bdos
call clrend
find0: ld a,(fbuf+1) ; String length
or a
jp z,command ; 0 length string ... abort
ex af,af' ; Save it
; START SEARCH AT NEXT LINE
ld hl,(srtptr)
call nxline ; HL now -> next line
finlp0:
ld de,fbuf+2 ; First char
finlp1:
call fmatch ; Compare upcase of (hl) and (de)
inc hl ; Bump text pointer
jr nz,finlp1 ; No match, keep moving through text
; AT THIS POINT, FIRST CHAR IS MATCHED
ex af,af' ; Recover string length
ld b,a
ex af,af'
dec b ; We have already found 1
jr z,findex ; Done if only 1 char to match
finlp2:
inc de
call fmatch
jr nz,finlp0 ; No match ... start looking again
inc hl ; So far, so good
djnz finlp2 ; Match next chars
; THE STRING IS IN THE CURRENT LINE, MOVE IT TO TOP OF SCREEN
findex: call pvline ; Find previous line
call nxline ; Go to beginning of this line
ld (srtptr),hl
jp prnscr ; Show the screen
; MATCH ROUTINE
fmatch:
ld a,(hl)
cp eof
jr z,finot
call mkupper
ld c,a
ld a,(de)
call mkupper
cp c
ret
; NO LUCK ON FIND
finot: pop af ; Lift stack
call cr$clr ; String not found - print message
call stndout
call print
db '???',' '+80h
finot0: call stndend
jp command
;
; SHOW FILE NAME COMMAND
;
what: call stndout
ld hl,fcb1+1
call prfn ; ROUTINE ELSEWHERE IN RCP
jr finot0 ; Finish up display
;
; SET PLACE MARKER
;
mark:
ld hl,(srtptr) ; Top of screen pointer is marker pointer
ld (mrkptr),hl
call stndout
call print
db 'Mark',bell+80h
jr finot0 ; Finish up display
;
; GO TO MARKER
;
gomark0:
ld hl,(mrkptr)
ld (srtptr),hl
jp prnscr
;
; LIST MARKED PORTION OF FILE
;
if peep$lst
list:
ld hl,lstmsg
call qprompt ; Are we serious? (And is printer on?)
jr z,listx ; Abort
call stndout
call print
db 'Printing',' '+80h
; Compute print block size
ld de,(mrkptr) ; Beginning of block
ld hl,(nxtptr) ; End of block
xor a
sbc hl,de ; Block size now in HL
jr c,lsterr ; If beginning at or after end then no go
jr z,lsterr
; Set up pointers
ex de,hl ; Block size in DE, start in HL
push de
pop bc ; Block size in BC
ld de,0 ; Count # lines in DE
ld a,cr
list1: cpir ; Count line feeds
inc de
jp po,list2 ; Loop expired at last cr
jr list1
list2:
call plcon ; Switch output to list
push de
pop bc ; Count to BC
ld hl,(mrkptr) ; Source of block
list3: call break ; Exit on ^C (routine in rcpsubs.lib)
call prnline ; Output switched to list:
dec bc
ld a,b
or c
jr nz,list3
call plcoff ; Switch output to con:
lsterr: call print ; Beep on marker error or finish print
db bell+80h
call clrend
listx: jp command
lstmsg: db 'Print from MAR','K'+80h
;
; SEND INIT STRING TO PRINTER
;
init$prt:
ld hl,initmsg
call qprompt
jr z,listx
call plcon ; Switch conout to list
ld hl,init$str ; Send string
ld b,(hl) ; Char count
ip1: inc hl
ld a,(hl)
call conout
djnz ip1
call plcoff ; Switch conout to con
jr listx
initmsg:
db 'Init LST',':'+80h
endif ; peep$lst
;
; READ FILE INTO TPA UNTIL FULL OR EOF
;
getfil:
; SET UP TOP OF MEMORY POINTER
ld hl,(bdos+1) ; BDOS location
ld de,-ccpsz-88h ; CCP size + offset + cr,eof + 1 record
add hl,de
ld (topmem),hl ; Store as top of memory
; REJECT BLANK FILE SPEC
getfil1:
call filcheck
CALL LOGUSR ; ROUTINE IS IN RCPSUBS.LIB
; OPEN THE FILE
call opensource
; RESET EOF FLAG (EOF NOT ENCOUNTERED)
xor a
ld (eoflag),a
; FILE READ LOOP
; File read into tbuf, MSB mask, lf strip, transfer to text buffer
ld de,textloc ; Start of text pointer
getlp1:
ld hl,(topmem) ; Check memory full
xor a
sbc hl,de
jr c,toobig ; Yes
push de
ld de,fcb1 ; Read a record
ld c,readf
call bdos
pop de
call loadfil ; Load it into text buffer
jr z,getlp1 ; Keep reading, eof not encountered
geteof: ld (eoflag),a ; Set EOF flag
ret
; MOVE RECORD INTO TEXT BUFFER
loadfil:
or a ; Enter with BDOS read return code
jr nz,ldfil03 ; No more to read, but no EOF char
ld hl,tbuf
ld b,80h
ldfil01:
ld a,(hl)
inc hl
and 7fh ; Mask MSB
cp lf
jr z,ldfil02 ; Skip lf
cp eof
jr z,ldfil03 ; Done, set up EOF pointers
ld (de),a
inc de
ldfil02:
djnz ldfil01
xor a ; Z = not done
ret
ldfil03:
ex de,hl
ld (hl),cr ; Add a cr to the end
inc hl
ld (hl),eof ; Mark end with eof
ld (eofptr),hl ; Save location
or -1 ; NZ = done
ret
; FILE HAS FILLED AVAILABLE MEMORY, PRINT WARNING
toobig:
call print
db 'Mem',bell+80h
call getchr ; Wait for key press
jr ldfil03 ; Read no more
;
; READ MORE TEXT COMMAND
;
read: ld a,(eoflag) ; Has EOF been encountered?
or a
jr nz,rdprompt ; If so, send message
ld de,textloc ; Else, preserve some text and read more
call geteos
ld a,eof
rdlp1: ldi ; Move last page to beginning of buffer
cp (hl) ; Check for end of file marker
jr nz,rdlp1 ; Loop until it is reached
dec de ; Back up over last CR
call getlp1 ; Fill memory with more of file
jr readx ; Re-initialize pointers and start
; PROMPT IF NO MORE TO READ
rdmsg: db 'Restar','t'+80h
rdprompt:
ld hl,rdmsg
call qprompt
jp z,command ; No
; STARTING OVER, ZERO FCB POSITION POINTERS
read1:
CALL INITFCB1 ; IN RCPSUBS.LIB
ld a,(ppusr) ; Restore user #
ld (fcb1+13),a
call getfil1 ; Read the file
readx: jp resrt ; Restart PEEP
; EXAMINE COMMAND LINE FOR FILE SPEC
filcheck:
ld a,(fcb1+13)
ld (ppusr),a
ld hl,fcb1+1
ld a,' '
cp (hl)
filcx: ret nz
call prfnf ; ROUNTINE IS ELSEWHERE IN RCP
jp exit ; NO FILE SPEC
; OPEN SOURCE FILE
opensource:
ld de,fcb1
ld c,openf
call bdos
inc a
jr filcx
; Enter with HL -> message. Return Z if answer = N.
qprompt:
call stndout
call printhl
call print
db '? (Y/n)',' '+80h
getchr:
call conin
cp 'N'
clrend:
push af
call stndend
call cr$clr
pop af
ret
; Get pointer to start of last screen in HL
geteos:
ld hl,(eofptr) ; Set End of Screen Pointer to beginning
ld b,scrlns ; of last screen
call pvline ; Back up one screen from end
djnz $-3
ret
;
; STORAGE
;
fbuf: db findsz ; Find string buffer
ds 1 ; Returned char count
ds findsz ; Buffer
width db crtwid ; Useable screen width
ppusr ds 1 ; User number
eoflag ds 1 ; EOF encountered flag
srtptr ds 2 ; Start Pointer -> top of screen
nxtptr ds 2 ; Next Pointer -> next screen
eofptr ds 2 ; End of File Pointer -> end of text
topmem ds 2 ; Top of memory pointer
mrkptr: ds 2 ; Place marker
; End RPEEP.LIB
; End of File Pointer -> end of text
topmem ds 2 ; Top