;
;  PROGRAM:  PAGE
;  VERSION:  1.2
;  DATE:  26 Apr 83
;  AUTHOR:  RICHARD CONN
;  PREVIOUS VERSIONS:  1.1 (25 Apr 83), 1.0 (22 Apr 83)
;
VERS    equ     12

;
;       PAGE is THE file screen print utility for ZCPR2.  Installable by
; GENINS, PAGE provides a wide range of options for the user.  First, PAGE
; allows the user to employ wild cards and file name lists (lists of files
; separated by commas, like: file1,file2,file3,...).  Second, PAGE provides
; the following options:
;               0-9     Set Character Print Speed Delay
;               I       Inspect Files
;                               The user approves each file to be printed
;                               before the printing process begins
;               L       Toggle Line Numbering
;                               Each line may or may not begin with a line
;                               number
;               P       Toggle Screen Paging
;               Snnnn   Skip to Specified Page
;                               Printing begins on the indicated page
;
;       During paged output, various parameters can be changed dynamically.
; In particular, the letter P toggles screen paging and the digits 0-9
; vary the speed WHILE the output is being presented.  The effect is immediate.
; Control characters may be used to perform additional control functions:
; ^S pauses the output, ^X aborts paging of current file and advances to
; the next file, and ^C aborts to the operating system.
;


;
;       This program is Copyright (c) 1983 by Richard Conn
;       All Rights Reserved
;
;       ZCPR2 and its utilities, including this one, are released
; to the public domain.  Anyone who wishes to USE them may do so with
; no strings attached.  The author assumes no responsibility or
; liability for the use of ZCPR2 and its utilities.
;
;       The author, Richard Conn, has sole rights to this program.
; ZCPR2 and its utilities may not be sold without the express,
; written permission of the author.
;

FALSE   EQU     0
TRUE    EQU     NOT FALSE

;
;  BASIC SYSLIB ROUTINES NEEDED BY TEMPLATE
;
ESIZE   EQU     16      ; SIZE OF DIR ENTRY (FROM SYSLIB DIRF ROUTINE)

       EXT     DIRFS   ; DIRECTORY PROCESSOR
       EXT     DIRPACK ; PACK DIRECTORY

       EXT     ZGPINS  ; INIT BUFFERS
       EXT     ZFNAME  ; FILE NAME PROCESSOR

       EXT     INITFCB ; INIT FCB
       EXT     RETUD   ; RETURN CURRENT USER/DISK
       EXT     PUTUD   ; SAVE CURRENT USER/DISK
       EXT     GETUD   ; RESTORE CURRENT USER/DISK
       EXT     LOGUD   ; LOG INTO USER/DISK
       EXT     PRINT   ; PRINT STRING PTED TO BY RET ADR
       EXT     PADC    ; PRINT A IN DEC
       EXT     COUT    ; CONSOLE OUTPUT ROUTINE
       EXT     CST     ; CONSOLE STATUS ROUTINE
       EXT     CIN     ; CONSOLE INPUT ROUTINE
       EXT     CAPS    ; CAPITALIZE ROUTINE
       EXT     CRLF    ; NEW LINE ROUTINE
       EXT     CLINE   ; COMMAND LINE STRING SAVE ROUTINE
       EXT     CODEND  ; CODE END COMPUTATION ROUTINE

       EXT     F$OPEN  ; FILE OPEN
       EXT     F$READ  ; BLOCK READ
       EXT     F$CLOSE ; FILE CLOSE

       EXT     EVAL10  ; STRING TO BINARY CONVERSION
       EXT     PHLDC   ; PRINT HL IN DECIMAL ROUTINE
       EXT     MOVEB   ; MOVEB ROUTINE

;
;  CP/M EQUATES
;
CPM     EQU     0       ; WARM BOOT
BDOSE   EQU     CPM+5   ; BDOS ENTRY
FCB     EQU     CPM+5CH ; FCB
TBUFF   EQU     CPM+80H ; INPUT LINE BUFFER
DEL     EQU     7FH     ; <DEL>
CR      EQU     13      ; <CR>
FF      EQU     12      ; <FF>
LF      EQU     10      ; <LF>
CTRLC   EQU     'C'-'@' ; ^C
CTRLG   EQU     'G'-'@'
CTRLH   EQU     'H'-'@'
CTRLI   EQU     'I'-'@'
CTRLS   EQU     'S'-'@'
CTRLX   EQU     'X'-'@'
CTRLZ   EQU     'Z'-'@'

;
;  OTHER EQUATES
;
EOLD    EQU     0FFH    ; END OF LOAD DELIMITER

;
;  Branch to Start of Program
;
       JMP     START

;
;******************************************************************
;
;  SINSFORM -- ZCPR2 Utility Standard General Purpose Initialization Format
;
;       This data block precisely defines the data format for
; initial features of a ZCPR2 system which are required for proper
; initialization of the ZCPR2-Specific Routines in SYSLIB.
;

;
;  EXTERNAL PATH DATA
;
EPAVAIL:
       DB      0FFH    ; IS EXTERNAL PATH AVAILABLE? (0=NO, 0FFH=YES)
EPADR:
       DW      40H     ; ADDRESS OF EXTERNAL PATH IF AVAILABLE

;
;  INTERNAL PATH DATA
;
INTPATH:
       DB      0,0     ; DISK, USER FOR FIRST PATH ELEMENT
                       ; DISK = 1 FOR A, '$' FOR CURRENT
                       ; USER = NUMBER, '$' FOR CURRENT
       DB      0,0
       DB      0,0
       DB      0,0
       DB      0,0
       DB      0,0
       DB      0,0
       DB      0,0     ; DISK, USER FOR 8TH PATH ELEMENT
       DB      0       ; END OF PATH

;
;  MULTIPLE COMMAND LINE BUFFER DATA
;
MCAVAIL:
       DB      0FFH    ; IS MULTIPLE COMMAND LINE BUFFER AVAILABLE?
MCADR:
       DW      0FF00H  ; ADDRESS OF MULTIPLE COMMAND LINE BUFFER IF AVAILABLE

;
;  DISK/USER LIMITS
;
MDISK:
       DB      4       ; MAXIMUM NUMBER OF DISKS
MUSER:
       DB      31      ; MAXIMUM USER NUMBER

;
;  FLAGS TO PERMIT LOG IN FOR DIFFERENT USER AREA OR DISK
;
DOK:
       DB      0FFH    ; ALLOW DISK CHANGE? (0=NO, 0FFH=YES)
UOK:
       DB      0FFH    ; ALLOW USER CHANGE? (0=NO, 0FFH=YES)

;
;  PRIVILEGED USER DATA
;
PUSER:
       DB      10      ; BEGINNING OF PRIVILEGED USER AREAS
PPASS:
       DB      'chdir',0       ; PASSWORD FOR MOVING INTO PRIV USER AREAS
       DS      41-($-PPASS)    ; 40 CHARS MAX IN BUFFER + 1 for ending NULL

;
;  CURRENT USER/DISK INDICATOR
;
CINDIC:
       DB      '$'     ; USUAL VALUE (FOR PATH EXPRESSIONS)

;
;  DMA ADDRESS FOR DISK TRANSFERS
;
DMADR:
       DW      80H     ; TBUFF AREA

;
;  NAMED DIRECTORY INFORMATION
;
NDRADR:
       DW      00000H  ; ADDRESS OF MEMORY-RESIDENT NAMED DIRECTORY
NDNAMES:
       DB      64      ; MAX NUMBER OF DIRECTORY NAMES
DNFILE:
       DB      'NAMES   '      ; NAME OF DISK NAME FILE
       DB      'DIR'           ; TYPE OF DISK NAME FILE

;
;  REQUIREMENTS FLAGS
;
EPREQD:
       DB      0FFH    ; EXTERNAL PATH?
MCREQD:
       DB      000H    ; MULTIPLE COMMAND LINE?
MXREQD:
       DB      0FFH    ; MAX USER/DISK?
UDREQD:
       DB      000H    ; ALLOW USER/DISK CHANGE?
PUREQD:
       DB      000H    ; PRIVILEGED USER?
CDREQD:
       DB      0FFH    ; CURRENT INDIC AND DMA?
NDREQD:
       DB      0FFH    ; NAMED DIRECTORIES?
Z2CLASS:
       DB      11      ; CLASS 11
       DB      'ZCPR2'
       DS      10      ; RESERVED

;
;  END OF SINSFORM -- STANDARD DEFAULT PARAMETER DATA
;
;******************************************************************
;

;
;  **** Special Initial Value Area for GENINS
;
LWIDTH:
       DB      132     ; WIDTH OF LINE
LTPP:
       DB      44      ; LINES OF TEXT PER PAGE
LSPP:
       DB      5       ; LINES TO SKIP PER PAGE
CWIDTH:
       DB      80      ; WIDTH OF SCREEN
CTPP:
       DB      22      ; LINES OF TEXT PER SCREEN
CSPP:
       DB      1       ; LINES TO SKIP PER SCREEN
;
;  NOTE:  LTPP + LSPP + 2 (HEADER SIZE) = TOTAL LINES PER PAGE ON PRINTER
;  NOTE:  CTPP + CSPP + 1 (FOOTER SIZE) = TOTAL LINES PER SCREEN ON CONSOLE
;
DLNUMFL:
       DB      0       ; LINE NUMBER FLAG (DEFAULT TO NO)
DPAGEFL:
       DB      0FFH    ; PAGE NUMBER FLAG (DEFAULT TO YES)
DINSPECT:
       DB      0       ; INSPECT FILES (DEFAULT TO NO)
DDELAY:
       DB      0       ; DELAY COUNT (DEFAULT TO 0)
;
;  OTHER BUFFERS
;
SKIPFL:
       DB      0       ; SKIP FLAG (DEFAULT TO NO)
SKIPNUM:
       DS      2       ; PAGE NUMBER TO SKIP TO
LNUM:
       DS      2       ; CURRENT LINE NUMBER
PNUM:
       DS      2       ; CURRENT PAGE NUMBER
LNUMFL:
       DB      0       ; LINE NUMBER FLAG (DEFAULT TO NO)
PAGEFL:
       DB      0FFH    ; PAGE NUMBER FLAG (DEFAULT TO YES)
INSPECT:
       DB      0       ; INSPECT FILES (DEFAULT TO NO)
DELAY:
       DB      0       ; DELAY COUNT (DEFAULT TO 0)

;
;  Start of Program
;
START:
       LXI     H,0     ; GET STACK PTR
       DAD     SP
       SHLD    STACK   ; SAVE IT
       LXI     SP,STACK        ; SET SP
       CALL    PUTUD   ; SAVE CURRENT USER/DISK AWAY
       CALL    RETUD   ; GET CURRENT USER/DISK
       MOV     A,B     ; SAVE DISK
       STA     DISK
       MOV     A,C     ; SAVE USER
       STA     USER

       CALL    ZGPINS  ; INIT BUFFERS

       LXI     H,TBUFF ; SAVE COMMAND LINE
       CALL    CLINE
       SHLD    CMDLNE  ; SAVE PTR

;
;  **** Banner of Program
;
       CALL    PRINT
       DB      'PAGE,  Version '
       DB      VERS/10+'0','.',(VERS MOD 10)+'0',0

;
;  Check for Help Request
;
       LDA     FCB+1   ; GET FIRST CHAR OF FILE NAME
       CPI     ' '     ; NO FILE SPEC?
       JZ      HELP
       CPI     '/'     ; OPTION CAUGHT?
       JNZ     ECONT

;
;  **** Print Help Information
;
HELP:
       CALL    PRINT
       DB      CR,LF,'PAGE Command --'
       db      cr,lf,' PAGE is invoked by the following command line:'
       db      cr,lf,'         PAGE file1,file2,...,filen o...'
       db      cr,lf,'where each "filen" is an ambiguous file name and type'
       db      cr,lf,'and "o" is zero or more of the following options:'
       db      cr,lf,' 0-9     Select Delay Constant'
       db      cr,lf,' I       Inspect and Select Files First'
       db      cr,lf,' L       Toggle Numbering of Each Line'
       db      cr,lf,' P       Toggle Paging'
       db      cr,lf,' Snnnn   Skip to Specified Page before Printing'
       db      cr,lf,'Examples:'
       db      cr,lf,'   PAGE MYFILE.TXT,*.MAC LI'
       db      cr,lf,'         -- Number Lines, Inspect Files'
       db      cr,lf,'   PRINT MYFILE.* S25'
       db      cr,lf,'         -- Skip to Page 25'
       db      cr,lf
       db      cr,lf,' While the displays are being printed, the user may'
       db      cr,lf,'strike ^C to abort PAGE, ^X to skip to next file,'
       db      cr,lf,'^S to suspend output (any key will resume, and ^C, ^X,'
       db      cr,lf,'P, and 0-9 are effective as commands at this point),'
       db      cr,lf,'P to toggle the paging, or a digit (0-9) to change'
       db      cr,lf,'the speed of the display'
       DB      0

;
;  RETURN TO OS
;
RETURN:
       LHLD    STACK   ; GET OLD STACK
       SPHL            ; SET IT
       RET

;
;  PROGRAM'S INIT ROUTINE
;
ECONT:
       CALL    INIT    ; PROG INIT ROUTINE
;
;  EXTRACT FLAGS IF PRESENT
;
       LXI     H,0     ; SET FILE COUNT
       SHLD    FILECNT
       LHLD    CMDLNE  ; PT TO BUFFER
;
;  SKIP TO FILE NAME STRING
;
       CALL    SBLANK  ; SKIP OVER BLANKS
;
;  SKIP TO END OF FILE NAME STRING
;
       CALL    SNBLANK ; SKIP OVER NON-BLANKS
;
;  CHECK FOR LEADING SLASH ON OPTION AND SKIP IT IF SO
;
OPT:
       CPI     '/'     ; OPTION CHAR?
       JNZ     OPTION
       INX     H       ; SKIP SLASH
;
;  PROCESS LIST OF OPTIONS
;
OPTION:
       MOV     A,M     ; GET BYTE
       ORA     A       ; DONE?
       JZ      DSPEC
       INX     H       ; PT TO NEXT CHAR
       CPI     ' '     ; SKIP OVER SPACES
       JZ      OPTION
       MOV     C,A     ; COMMAND IN C
       LXI     D,OPTAB ; PT TO OPTION TABLE
OPTL:
       LDAX    D       ; GET OPTION LETTER
       ORA     A       ; END OF TABLE?
       JZ      HELP    ; HELP IF SO
       CMP     C       ; MATCH?
       JZ      OPTM    ; PROCESS IF SO
       INX     D       ; PT TO NEXT ENTRY
       INX     D
       INX     D
       JMP     OPTL
;
;  PROCESS OPTION
;
OPTM:
       PUSH    H       ; SAVE HL ON STACK
       LXI     H,OPTION        ; GET RETURN ADDRESS
       XTHL            ; ... ON STACK AND RESTORE HL
       INX     D       ; PT TO ADDRESS
       LDAX    D       ; GET ADDRESS LOW
       MOV     B,A     ; ... IN B
       INX     D
       LDAX    D       ; GET ADDRESS HIGH
       MOV     D,A     ; ... IN D
       MOV     E,B     ; LOW IN E
       PUSH    D       ; PUT ADDRESS ON STACK
       MOV     A,C     ; COMMAND IN A
       RET             ; "CALL" OPTION ROUTINE

;
;  **** PROGRAM INIT ROUTINE
;       THIS ROUTINE IS USED BY THE PROGRAM TO PERFORM ANY INITS
;
INIT:
       lxi     h,dlnumfl       ;copy defaults into buffers
       lxi     d,lnumfl
       mvi     b,4             ;4 bytes
       call    moveb           ;do copy
       xra     a       ;A=0
       sta     skipfl  ;set no skip
       RET

;
;  **** OPTION TABLE
;       EACH OPTION IS A CAPITAL LETTER OR SPECIAL CHAR FOLLOWED BY
;               AN ADDRESS; THE TABLE IS TERMINATED BY A BINARY ZERO
;
OPTAB:
       db      '0'
       dw      optnum
       db      '1'
       dw      optnum
       db      '2'
       dw      optnum
       db      '3'
       dw      optnum
       db      '4'
       dw      optnum
       db      '5'
       dw      optnum
       db      '6'
       dw      optnum
       db      '7'
       dw      optnum
       db      '8'
       dw      optnum
       db      '9'
       dw      optnum
       db      'I'
       dw      optinsp
       db      'L'
       dw      optln
       db      'P'
       dw      optpage
       db      'S'
       dw      optskip
       DB      0       ; END OF TABLE
;
;  Set Delay Constant
;
optnum:
       sui     '0'     ;set constant
       sta     delay
       ret
;
;  Toggle Inspect Option
;
optinsp:
       lda     inspect ;flip flag
       cma
       sta     inspect
       ret
;
;  Set Line Number Flag
;
optln:
       lda     lnumfl  ;flip flag
       cma
       sta     lnumfl
       ret
;
;  Toggle Paging
;
optpage:
       lda     pagefl  ;flip flag
       cma
       sta     pagefl
       ret
;
;  Set Skip Flag and get number
;
optskip:
       mvi     a,0ffh  ;set flag
       sta     skipfl
       call    eval10  ;get number
       xchg
       shld    skipnum ;set page number to skip to
       xchg            ;HL pts to next char
       mov     a,d     ;see if page number was zero
       ora     e
       jnz     option
       xra     a       ;if zero, just turn off skip flag
       sta     skipfl
       ret
;
;  BEGIN MOVING THROUGH FILE NAMES, SEPARATED BY COMMAS
;
DSPEC:
       LHLD    CMDLNE  ; PT TO FIRST BYTE
       CALL    SBLANK  ; SKIP TO NON-BLANK
;
;  MAJOR REENTRY POINT WHEN FILE SPECS ARE SEPARATED BY COMMAS
;    HL PTS TO FIRST BYTE OF NEXT FILE SPEC
;
DSPEC1:
       LXI     SP,STACK        ; RESET STACK
       CALL    GETUD   ; RESET USER IF NECESSARY
       LXI     D,NTFCB ; PT TO FCB IN DE, PT TO FIRST CHAR OF FILE NAME IN HL

       CALL    ZFNAME  ; EXTRACT FILE NAME INTO FCB, AND GET DISK AND USER
       JZ      DERR    ; ERROR HANDLER

       SHLD    NEXTCH  ; SAVE PTR TO DELIMITER WHICH ENDED SCAN
       MOV     A,B     ; SAVE POSSIBLE DRIVE SPEC
       CPI     0FFH    ; CURRENT DISK?
       JZ      DSPEC2
       LDA     MDISK   ; GET MAX DISK NUMBER
       DCR     B       ; ADJUST TO WITHIN BOUNDS 0-15
       CMP     B       ; WITHIN BOUNDS?
       MOV     A,B     ; GET DISK NUMBER IN A
       JNC     USPEC
DERR:
       CALL    PRINT
       DB      CR,LF,'Invalid Disk Specification',0
       JMP     DRETURN

;
;  SET CURRENT DISK
;
DSPEC2:
       LDA     DISK    ;GET CURRENT DISK
       MOV     B,A     ;... IN B

;  CHECK FOR USER NUMBER
USPEC:
       MOV     A,C     ; GET NEW USER NUMBER
       CPI     0FFH    ; DEFAULT USER?
       JZ      USPEC1
       CPI     '?'     ; ALL USERS NOT ALLOWED?
       JZ      UERR
       LDA     MUSER   ; GET MAX USER NUMBER
       CMP     C
       MOV     A,C     ; USER NUMBER IN A
       JNC     FCT
UERR:
       CALL    PRINT
       DB      CR,LF,'Invalid User Number',0
       JMP     DRETURN
USPEC1:
       LDA     USER    ;GET CURRENT USER
       MOV     C,A     ;... IN C

;
;  LOAD DIRECTORY AND PERFORM FUNCTION
;
FCT:
       MOV     A,B     ; SAVE NEW DISK/USER AWAY
       STA     CDISK   ; CURRENT DISK
       MOV     A,C
       STA     CUSER   ; CURRENT USER
       CALL    LOGUD   ; LOG INTO ACCOUNT
       CALL    CODEND  ; PT TO END OF CODE
       CALL    RETUD   ; GET USER NUMBER FOR DIRFS
       MVI     A,11000000B     ; SELECT SYS AND NON-SYS FILES
       ORA     C       ; OR IN USER NUMBER
       LXI     D,NTFCB ; PT TO FCB
       CALL    INITFCB ; INIT THE FCB
       CALL    DIRFS   ; LOAD DIR, SELECT FILES, PACK, AND ALPHABETIZE
;
;  DETERMINE BEGINNING OF SCRATCH AREA (SCRATCH) AND SIZE IN PAGES (BCNT)
;
       PUSH    H       ; SAVE PTR AND COUNT
       PUSH    B
       LXI     D,ESIZE ; SET PTR TO NEXT FREE BLOCK
FCTFRE:
       MOV     A,B     ; DONE?
       ORA     C
       JZ      FCTFR1
       DAD     D       ; PT TO NEXT
       DCX     B       ; COUNT DOWN
       JMP     FCTFRE
FCTFR1:
       INR     H       ; NEXT PAGE
       MVI     L,0
       SHLD    SCRATCH ; SET PTR TO SCRATCH AREA
       XCHG            ; PTR IN DE
       LHLD    BDOSE+1 ; COMPUTE BLOCK BUFFER SIZE
       MOV     A,H     ; ADJUST FOR ZCPR2
       SUI     10
       SUB     D       ; A=SIZE IN BLOCKS
       STA     BCNT    ; SET BLOCK COUNT
       POP     B       ; RESTORE AND SAVE REGS
       POP     H
;
;  ALLOW USER TO INSPECT FILES
;
       PUSH    H
       PUSH    B
       CALL    ICHECK  ; CHECK FOR INSPECT OPTION AND INSPECT IF SET
       POP     B       ; RESTORE COUNT AND PTR
       POP     H

;
;  PERFORM FUNCTION; HL PTS TO FILE AND BC CONTAINS NUMBER OF FILES
;
FCTL:
       MOV     A,B             ; CHECK FOR COMPLETION (COUNT = 0)
       ORA     C
       JZ      FCTL1
       DCX     B               ; COUNT DOWN
       LXI     SP,STACK        ; RESET STACK
       PUSH    B               ; SAVE COUNT AND PTR
       PUSH    H
       CALL    FUNCTION        ; PERFORM FUNCTION
FCTLNXT:
       LXI     SP,STACK-4      ; RESTORE STACK
       POP     H               ; RESTORE PTR
       POP     B               ; RESTORE COUNT
       LXI     D,ESIZE         ; PT TO NEXT ENTRY
       DAD     D
       JMP     FCTL

;
;  CHECK FOR NEXT FILE SPEC
;
FCTL1:
       CALL    GETUD   ; RETURN TO BASE USER/DISK
       LHLD    NEXTCH  ; GET PTR
       MOV     A,M     ; GET DELIM
       CPI     ','     ; ANOTHER FILE?
       JNZ     DRETURN
       INX     H       ; PT TO CHAR AFTER COMMA
       JMP     DSPEC1  ; CONTINUE PROCESSING

;
;  **** EMERGENCY ABORT
;
ABORT:
       CALL    PRINT
       DB      CR,LF,'** PAGE Abort **',CR,LF,0
       CALL    GETUD   ; RETURN HOME AND FALL THRU TO DRETURN
;
;  **** FUNCTION COMPLETE -- CLEANUP AND EXIT
;       FILL THIS IN WITH CLEANUP CODE FOR EXIT
;
DRETURN:
       JMP     RETURN

;
;  **** INSPECT FILES -- THIS ROUTINE IS TO PERFORM A FILE INSPECTION
;       ON INPUT, HL PTS TO FIRST 16-BYTE ENTRY AND BC=NUMBER OF ENTRIES
;
ICHECK:
       mov     a,b     ;any files?
       ora     c
       rz
       push    h       ;save ptrs
       push    b
       lxi     d,esize ;size of entry
ichk1:
       mvi     m,0     ;clear MSBytes
       dad     d       ;pt to next
       dcx     b       ;count down
       mov     a,b     ;done?
       ora     c
       jnz     ichk1
       pop     b       ;restore ptrs
       pop     h
       lda     inspect ;inspect?
       ora     a       ;0=no
       rz
       call    print
       db      cr,lf,'PAGE File Inspect Mode',0
ichk2:
       call    print
       db      cr,lf,'Select ',0
       call    prfn    ;print file name
       call    print
       db      ' -- (Y/N/Q=Select Rest/S=Skip Rest/other=Y)? '
       db      0
       call    cin     ;get response
       call    caps    ;capitalize
       call    cout    ;echo
       cpi     'Q'     ;select rest?
       jz      ichkyr
       cpi     'S'     ;skip rest
       jz      ichknr
       cpi     'N'     ;no to this one?
       jnz     ichk3
       mvi     m,0ffh  ;set NO flag in file FCB
ichk3:
       dad     d       ;pt to next one
       dcx     b       ;count down
       mov     a,b     ;done?
       ora     c
       jnz     ichk2
       RET
;  Check Rest of Files as Selected
ichkyr:
       call    print
       db      cr,lf,' Rest of Files Selected',0
       ret
;  Check Rest of Files as NOT Selected
ichknr:
       mvi     m,0ffh  ;set NO flag
       dad     d       ;pt to next
       dcx     b       ;count down
       mov     a,b     ;done?
       ora     c
       jnz     ichknr
       call    print
       db      cr,lf,' Rest of Files NOT Selected',0
       ret
;
;  **** FUNCTION -- MAIN FUNCTION OF TEMPLATE
;       ON ENTRY, HL PTS TO NAME OF FILE (16 BYTES) AND USER IS LOGGED INTO
;               DIRECTORY CONTAINING INDICATED FILE
;
FUNCTION:
;
;  FILE PAGE Routine -- Page the File Whose Name is Pointed to by
;       HL; we are already logged into the correct directory
;
       mov     a,m     ;file selected?
       ora     a       ;0=yes
       rnz
       call    prinit  ;init print buffers
       call    fload   ;load buffer initially
       lhld    scratch ;pt to first char in file
       shld    nxtln   ;set pointer to next line
fprloop:
       call    prline  ;print line of file
       jnz     fprloop ;done if EOF
       call    page    ;advance to top of next page
       call    prfoot  ;print footer
       ret
;
;  Init Print Buffers and Print File
Name
;
prinit:
       lxi     d,tfcb  ;set up FCB
       mvi     b,12    ;12 bytes
       call    moveb
       lxi     h,0     ;HL=0
       shld    pnum    ;set page number
       shld    lnum    ;set line number
       lda     ctpp    ;set line count
       dcr     a       ;1 less for first line
       sta     lcount
       call    print
       db      cr,lf,'PAGE File: ',0
       lxi     h,tfcb  ;print file name
       call    prfn
       call    crlf
       ret
;
;  FILE LOAD (FLOAD) Routine -- Initial Load of memory buffer
;
fload:
       lxi     d,tfcb  ;pt to file fcb
       call    initfcb ;init file's fcb
       call    f$open  ;open file for input
       jz      fload1  ;open was OK
       call    print
       db      cr,lf,'File ',0
       xchg            ;HL pts to FCB
       call    prfn    ;print file name
       call    print
       db      ' NOT Found',0
       pop     d       ;clear return address
       ret             ;abort printout of this file
;
;  This is an entry point for further memory loads of the file
;
fload1:
       lda     bcnt    ;get number of blocks to load
       mov     c,a     ;... in C
       lhld    scratch ;get address of first block to load into
       shld    nxtblk  ;set pointer to next block to load
fload2:
       call    rdblk   ;read a block (128 bytes)
       jnz     eof     ;eof encountered?
       call    rdblk   ;read another block (128 bytes)
       jnz     eof     ;eof encountered?
       dcr     c       ;count down
       jnz     fload2
       lhld    nxtblk  ;pt to next byte to load
       mvi     m,eold  ;mark end of load
       ret
eof:
       lxi     d,tfcb  ;close file
       call    f$close
       lhld    nxtblk  ;ensure ^Z
       mvi     m,ctrlz
       ret
rdblk:
       lxi     d,tfcb  ;pt to FCB
       call    f$read  ;read next block
       ora     a       ;error?
       rnz
       lhld    nxtblk  ;get ptr to next block
       xchg            ; as dest
       lxi     h,tbuff ;ptr to DMA address
       mvi     b,128   ;copy 128 bytes
rdblk1:
       mov     a,m     ;get byte
       ani     7fh     ;mask out msb
       stax    d       ;put byte
       inx     h       ;pt to next
       inx     d
       dcr     b       ;count down
       jnz     rdblk1
       xchg            ;new nxtblock
       shld    nxtblk
       ret

;
;  Line Print Routine
;       Print Next Line with Optional Disk Load
;       Input Parameter is NXTLN, which is the address of the first char
; on the next line
;       Output Parameter is Zero Flag, with Z meaning done with print, NZ
; meaning more yet to print
;
prline:
       lhld    lnum    ;increment line number
       inx     h
       shld    lnum
       lhld    nxtln   ;pt to first char of next line
       mvi     c,0     ;init char count
       mov     a,m     ;get first char of line
       cpi     ctrlz   ;EOF?
       cnz     prlnum  ;print line number (optional)
prl1:
       mov     a,m     ;get char
       cpi     eold    ;end of load?
       jz      prload
       cpi     ctrlz   ;eof?
       jz      prexit
       inx     h       ;pt to next char
       cpi     ctrli   ;tab?
       jz      prtab
       cpi     cr      ;<CR>?
       jz      prcr
       cpi     ff      ;form feed?
       jz      prff
       cpi     lf      ;end of line?
       jz      prldn
       cpi     ctrlh   ;back space?
       jz      prbs
       cpi     ctrlg   ;ring bell?
       jz      prbell
       cpi     del     ;delete char?
       jz      prl1    ;skip it
       cpi     ' '     ;other control char?
       jc      prl1    ;skip if other control char
       call    prout   ;print char
       inr     c       ;increment char count
       call    eoltest ;check to see if at end of line and newline if so
       jmp     prl1
;
;  End of Load Reached -- Load More of File from Disk
;
prload:
       push    b       ;save char count
       call    fload1  ;use load routine
       pop     b       ;get char count
       lhld    scratch ;next byte is here
       jmp     prl1    ;continue processing
;
;  Tabulate
;
prtab:
       mvi     a,' '   ;space
       call    prout
       inr     c       ;new char
       call    eoltest ;process EOL
       mov     a,c     ;done?
       ani     7
       jnz     prtab   ;continue tabulation
       jmp     prl1    ;continue processing
;
;  Exit with Zero Flag Set if Done
;
prexit:
       xra     a       ;set zero flag
       ret
;
;  Carriage Return -- Reset Character Count and Continue
;
prcr:
       call    prout   ;send CR to printer
       mvi     c,0     ;reset char count
       jmp     prl1    ;continue processing
;
;  Form Feed -- Advance to Top of Next Page
;
prff:
       call    page    ;page eject with heading
       mvi     c,0     ;reset char count
       jmp     prl1    ;continue processing
;
;  Line Feed -- End of Routine
;
prldn:
       call    prout   ;echo LF to printer
       shld    nxtln   ;set ptr to first char of next line
       mvi     a,0ffh  ;set not done
       ora     a       ;set flags
       ret
;
;  Backspace on Printer
;
prbs:
       mov     a,c     ;check for beginning of line
       ora     a
       jz      prl1    ;continue if at BOL
       mvi     a,ctrlh ;backspace
       call    prout
       dcr     c       ;back up char position
       jmp     prl1    ;continue
;
;  Ring Bell on Printer
;
prbell:
       call    prout   ;ring the bell
       jmp     prl1    ;continue without advancing char position
;
;  Test for End of Line and Process if so
;
eoltest:
       lda     cwidth  ;get line width
       sui     4       ;4 chars less for continuation mark
       mov     b,a     ;result in B
       lda     lnumfl  ;line numbering (lines are 7 chars shorter if so)
       ora     a       ;0=no
       jz      eolt1
       mov     a,b     ;reduce by 7 for line numbers
       sui     7
       mov     b,a
eolt1:
       mov     a,b     ;get line width
       cmp     c       ;there?
       rnz             ;continue if not
       mov     a,m     ;get next char
       cpi     cr      ;new line next?
       rz              ;continue if so
       cpi     ctrlh   ;backspace next?
       rz              ;continue if so
       mvi     a,' '   ;print continuation chars
       call    prout
       mvi     a,'<'
       call    prout
       mvi     a,'<'
       call    prout
       mvi     a,cr    ;new line
       call    prout
       mvi     a,lf
       call    prout
       mvi     c,0     ;reset char position
       lda     skipfl  ;skipping?
       ora     a       ;0=no
       rnz
       lda     lnumfl  ;printing line numbers?
       ora     a       ;0=no
       rz
       call    print
       db      '     : ',0
       ret
;
;  Output a character to the console
;       A = Character
;
prout:
       mov     b,a     ;char in B
       call    cst     ;check for abort
       jnz     prout1
       call    ctrlin  ;get control input
prout1:
       lda     skipfl  ;skipping?
       ora     a       ;set flags (Z=no skip=print char)
       mov     a,b     ;restore char
       cz      ctrlout ;send character to printer
       cpi     lf      ;special tests if it is a line feed
       rnz             ;done if non-LF char
       lda     lcount  ;decrement line counter
       dcr     a
       sta     lcount
       rnz
;
;  Paging Required
;       Skip to top of next page; reset LCOUNT (Lines Left on Page Count);
;       increment PNUM (Screen Number); test for skip stop; print header
;
prout0:
       lda     ctpp    ;get number of text lines per page
       sta     lcount  ;set as new line count
       push    h       ;save ptr
       lhld    pnum    ;increment page number
       inx     h
       shld    pnum
       lda     cspp    ;number of lines to skip
       call    lineskp ;skip lines
       pop     h       ;restore ptr
       mov     a,m     ;check next character
       cpi     ctrlz   ;EOF?
       cnz     prfoot  ;print 1-line footer
       lda     skipfl  ;skipping?
       ora     a       ;0=no
       push    h
       cnz     skiptst ;affects HL
       pop     h
       ret
;
;  Skip out rest of page
;       Form Feed Function
;
page:
       lda     lcount  ;get count of remaining lines
       call    lineskp ;skip lines
       jmp     prout0  ;process top of new page
;
;  Skip out lines on page
;
lineskp:
       mov     b,a     ;line count in B
       ora     a       ;any?
       rz
       lda     skipfl  ;skipping?
       ora     a
       rnz
       lda     pagefl  ;paging?
       ora     a
       rz
lines1:
       mvi     a,cr    ;output new line to printer
       call    cout
       mvi     a,lf
       call    cout
       dcr     b       ;count down
       jnz     lines1
       ret
;
;  Control Input
;       CTRLIN -- Main Routine Entry Point; Implements Dynamic Commands,
;               including P, 0-9, ^S, ^X, and ^C
;       CTRLCS -- ^S Reentry Point; Implements all Dyanamic Commands except ^S
;
ctrlcs:
       call    cin     ;get input
       jmp     ctrlns
ctrlin:
       call    cin     ;get input
       cpi     ctrls   ;pause?
       jz      ctrlcs
ctrlns:
       call    caps    ;capitalize
       cpi     ctrlc   ;abort?
       jz      abort
       cpi     ctrlx   ;skip to next
       jz      fctlnxt
       cpi     'P'     ;page now?
       jz      ctrlip
       cpi     '0'     ;delay?
       rc
       cpi     '9'+1
       rnc
       sui     '0'     ;convert to binary
       sta     delay   ;set delay count
       ret
ctrlip:
       lda     pagefl  ;toggle paging
       cma
       sta     pagefl
       ret
;
;  Control Output
;
ctrlout:
       push    psw     ;save char
       call    cout    ;output char
       lda     delay   ;pause?
       ora     a       ;any delay?
       jz      ctrloz
       push    h       ;delay
       push    b
       mov     b,a     ;delay count
del1:
       lxi     h,500   ;delay constant
del2:
       xthl            ;long NOP
       xthl
       dcx     h       ;count down
       mov     a,h     ;done?
       ora     l
       jnz     del2
       dcr     b       ;count down
       jnz     del1
       pop     b       ;restore regs
       pop     h
ctrloz:
       pop     psw     ;restore A
       ret
;
;  Print Line Number (optional)
;
prlnum:
       lda     skipfl  ;skipping?
       ora     a       ;0=no
       rnz
       lda     lnumfl  ;get flag
       ora     a       ;0=don't number lines
       rz
       push    h       ;save ptr
       lhld    lnum    ;get line number
       call    phldc   ;print line number
       call    print   ;print separator
       db      ': ',0
       pop     h       ;restore ptr
       ret
;
;  Print 1-line footer
;
prfoot:
       lda     skipfl  ;skipping?
       ora     a       ;0=no
       rnz
       lda     pagefl  ;paging?
       ora     a
       rz
       push    h       ;save ptr
       call    prpnum  ;print page heading and number
       call    prdash  ;print dash
       lxi     h,tfcb  ;pt to file FCB
       call    prfn    ;print file name
       pop     h       ;restore ptr
       call    print
       db      ' -- Strike Any Key ',0
       call    ctrlin  ;get control response
       jmp     crlf    ;new line
;
;  Test for completion of skipping
;
skiptst:
       lhld    pnum    ;get page number
       inx     h       ;increment for test
       xchg            ;... in DE
       lhld    skipnum ;get page to skip to
       mov     a,h     ;compare them
       cmp     d
       rnz
       mov     a,l
       cmp     e
       rnz
       xra     a       ;A=0 to stop skipping
       sta     skipfl  ;set flag
       ret
;
;  Print Page Number
;
prpnum:
       call    print   ;print header
       db      'Screen ',0
       lhld    pnum    ;print current page number
       call    phldc   ;print as decimal
       ret
;
;  Print Separator
;
prdash:
       call    print
       db      ' -- ',0
       ret
;
;  UTILITIES
;       SBLANK  -- SKIP BLANKS PTED TO BY HL UNTIL NON-BLANK ENCOUNTERED; HL
;       SNBLANK -- SKIP NON-BLANKS PTED TO BY HL UNTIL BLANK OR EOL; HL
;       PRFN    -- PRINT FILE NAME PTED TO BY HL; AFFECT NOTHING
;

;
;  SKIP UNTIL NON-BLANK
;
SBLANK:
       MOV     A,M     ; LOOK FOR BLANK
       INX     H       ; PT TO NEXT
       CPI     ' '     ; BLANK?
       JZ      SBLANK
       DCX     H       ; BACK UP
       RET

;
;  SKIP UNTIL BLANK OR EOL
;
SNBLANK:
       MOV     A,M     ; GET CHAR
       INX     H       ; PT TO NEXT
       CPI     ' '     ; BLANK?
       JZ      SNB1
       ORA     A       ; EOL?
       JNZ     SNBLANK
SNB1:
       DCX     H       ; BACK UP
       RET

;
;  PRINT FILE NAME PTED TO BY HL
;       OUTPUT TO CON:
;
PRFN:
       PUSH    H       ; SAVE REGS
       PUSH    B
       CALL    RETUD   ; GET CURRENT USER/DISK
       MOV     A,B     ; PRINT DISK
       ADI     'A'     ; LETTER
       CALL    COUT
       MOV     A,C     ; PRINT USER
       CALL    PADC
       CALL    PRINT
       DB      ': ',0
       INX     H       ; PT TO FILE NAME
       MVI     B,8     ; PRINT NAME
       CALL    PRNT
       MVI     A,'.'   ; DECIMAL
       CALL    COUT
       MVI     B,3     ; PRINT TYPE
       CALL    PRNT
       POP     B       ; GET REGS
       POP     H
       RET

;
;  PRINT CHARS PTED TO BY HL FOR B BYTES
;       OUTPUT TO CON:
;
PRNT:
       MOV     A,M     ; GET CHAR
       CALL    COUT
       INX     H       ; PT TO NEXT
       DCR     B       ; COUNT DOWN
       JNZ     PRNT
       RET

;
;  BUFFERS
;
DISK:
       DS      1       ; HOME DISK NUMBER
USER:
       DS      1       ; HOME USER NUMBER
CDISK:
       DS      1       ; CURRENT DISK NUMBER
CUSER:
       DS      1       ; CURRENT USER NUMBER
CMDLNE:
       DS      2       ; PTR TO COMMAND LINE STRING
NEXTCH:
       DS      2       ; PTR TO NEXT CHAR IN MULTIFILE COMMAND LINE
FILECNT:
       DS      2       ; COUNT OF NUMBER OF FILES RENAMED
SCRATCH:
       DS      2       ; ADDRESS OF FIRST BYTE OF SCRATCH AREA
BCNT:
       DS      1       ; NUMBER OF PAGES IN SCRATCH AREA
NTFCB:
       DS      36      ; FCB FOR NEW FILE
;
;  PAGE Buffers
;
tfcb:
       ds      36      ; FCB for current file
nxtblk:
       ds      2       ; pointer to next block to load
nxtln:
       ds      2       ; pointer to next line to read
lcount:
       ds      1       ; count of text lines left on page
;
;  Stack
;
       DS      100     ; STACK AREA
STACK:
       DS      2       ; OLD STACK PTR

       END