; PROGRAM: VMENU ; VERSION: 1.0 ; DATE: 26 June 84 ; AUTHOR: Richard Conn ; PREVIOUS VERSIONS: None ; z3env equ 0f400h VERS EQU 10 ;version number ; VMENU is copyright (c) 1984 by Richard Conn ; All Rights Reserved ; VMENU may be used freely by the ZCPR3 Community ; VMENU is a screen-oriented, ZCPR3-specific file utility. It can not be ; installed to run under conventional CP/M. VMENU ; extensively employs cursor addressing to position a pointer on the ; screen, allow the user to manipulate the pointer (up, down, right, left, ; next screen, previous screen, GOTO file). The pointer points to files ; in the current user directory and displays the user's position dynamically ; on the screen. Once pointing to a file, user commands can be used to ; manipulate the file according to options presented in the menu displayed to ; the user. MENU and VMENU are compatible. In the way of being ZCPR3- ; specific, VMENU can chain to external programs via the Command Line Buffer ; and then return, and it recognizes Named Directories (so the user can log ; into B:, B4:, and MYDIR:, for example). ; VMENU is installed by Z3INS. ; VMENU works with ZCPR3 only, with 32k or more of RAM. ; VMENU can be assembled for use with a Z80 or 8080 microprocessor. ; ; SYSLIB, Z3LIB, and VLIB References ; ext z3vinit,cls,gotoxy,ereol,vprint,envptr,stndout,stndend ext pafdc,dutdir ext qshell,getefcb,shpush,shpop,getcrt,getfn2,zprsfn ext putshm,getshm,getsh,getzrun,getcl1,putzex,putcst ext cin,cout,caps,crlf,bline,sksp ext f$open,f$read,f$close,initfcb ext retud ext codend ; ; Basic Definitions ; TRUE EQU 0FFH ;define true and.. FALSE EQU 0 ;..false. ; DIM EQU 1 ;GOTO DIM BRIGHT EQU 2 ;GOTO BRIGHT ELTSIZ EQU 11 ;size of file name and type element ; ; User-Customized Definition ; VMNAME MACRO ;;Name of VMENU DB 'VMENU' ENDM VMNFILL MACRO ;;Spaces to fill out name to 8 chars DB ' ' ENDM ; Z80 EQU TRUE ;TRUE to use Z80 Instructions WARMBOOT EQU FALSE ;set TRUE to warmboot on exit EPS EQU 4*4 ;N lines x 4 cols per screen ; EPS = Entries Per Screen ; ; Command Line Builder Constants ; FPESC EQU '%' ;escape char FPDISK EQU 'D' ;disk only (D) FPUSER EQU 'U' ;user only (U) FPFILE EQU 'F' ;filename.typ FPNAME EQU 'N' ;file name only FPTYPE EQU 'T' ;file type only FPPTR EQU 'P' ;file entry being pointed to MNOTE EQU '#' ;denotes comment area in macro file UIN1 EQU 27H ;single quote for user input UIN2 EQU 22H ;double quote for user input ; ; Menu Constants ; ; 1 Special Menu Command Chars RNM EQU '>' ;NEXT MENU RNMP EQU '.' ;NEXT MENU PRIME (ALTERNATE) RLM EQU '<' ;LAST MENU RLMP EQU ',' ;LAST MENU PRIME (ALTERNATE) RFM EQU '*' ;FIRST MENU ; 2 Internal Menu Control Chars MCMD EQU ':' ;COMMAND TO JUMP TO ANOTHER MENU PCHAR EQU '"' ;INDICATES AUTO PROMPT FOR SPECIFIC CMD MINDIC EQU '#' ;MENU SECTION INDICATOR MFIRST EQU '%' ;FIRST MENU INDICATOR GOPTION EQU '-' ;GLOBAL OPTION INDICATOR WOPTION EQU '!' ;ACTIVATES WAIT UPON RETURN ; 3 Menu Option Chars XOPTION EQU 'X' ;DISABLE ZCPR3 RETURN ; 4 Miscellaneous IBUFSZ EQU 254 ;SIZE OF INPUT LINE BUFFER VARFLAG EQU '$' ;VARIABLE FLAG ;(FOLLOWED BY D,U,Fn,Nn,Tn) CMDSEP EQU ';' ;ZCPR3 COMMAND SEPARATOR ; ; Cursor Positioning Addresses ; EPSLINE EQU (EPS/4)+3 ;position of last line of EPS + 1 BANADR EQU 1*256+24 ;banner address CURHOME EQU 3*256+1 ;home address of cursor BOTADR EQU 23*256+1 ;bottom of screen CPMADR EQU 22*256+1 ;command prompt message CPADR EQU CPMADR+27 ;command prompt address (cursor position) ERADR EQU CPMADR+256+15 ;error message FNADR EQU 1*256+62 ;address of current file name MOREADR EQU FNADR+1*256 ;address of more files message DUADR EQU 1*256+4 ;address of current DU ; ; System Functions ; RDCON EQU 1 WRCON EQU 2 PUNCH EQU 4 LIST EQU 5 DIRCON EQU 6 RDBUF EQU 10 CONST EQU 11 LOGIN EQU 14 OPEN EQU 15 CLOSE EQU 16 SRCHF EQU 17 SRCHN EQU 18 ERASE EQU 19 READ EQU 20 WRITE EQU 21 MAKE EQU 22 REN EQU 23 INQDISK EQU 25 SETDMA EQU 26 INQALC EQU 27 ATTR EQU 30 GETPARM EQU 31 SGUSER EQU 32 COMPSZ EQU 35 ; ; System Addresses ; OS$BASE EQU 000H ;system base.. CCP EQU 800H ;..and 'ccp' length in bytes. GET EQU 0FFH ;get user area e-reg value BDOS EQU OS$BASE+05H FCB EQU OS$BASE+5CH FCBEXT EQU FCB+12 FCBRNO EQU FCB+32 FCB2 EQU OS$BASE+6CH TBUFF EQU OS$BASE+80H TPA EQU OS$BASE+100H ; ; ASCII Definitions ; CTRLC EQU 'C'-'@' ;..control-C.. CTRLD EQU 'D'-'@' CTRLE EQU 'E'-'@' CTRLR EQU 'R'-'@' CTRLS EQU 'S'-'@' ;..XOFF.. CTRLX EQU 'X'-'@' BEL EQU 07H ;..bell.. BS EQU 08H ;..backspace.. TAB EQU 09H ;..tab.. LF EQU 0AH ;..linefeed.. FF EQU 0CH ;..formfeed.. CR EQU 0DH ;..carriage return.. CAN EQU 18H ;..cancel.. EOFCHAR EQU 1AH ;..end-of-file.. CTRLZ EQU 1AH ;..clear screen.. ESC EQU 1BH ;..and escape character. ; ; MACROS TO PROVIDE Z80 EXTENSIONS ; MACROS INCLUDE: ; ; BR - JUMP RELATIVE ; BRC - JUMP RELATIVE IF CARRY ; BRNC - JUMP RELATIVE IF NO CARRY ; BRZ - JUMP RELATIVE IF ZERO ; BRNZ - JUMP RELATIVE IF NO ZERO ; BJNZ - DECREMENT B AND JUMP RELATIVE IF NO ZERO ; BR MACRO ?N ;;JUMP RELATIVE IF Z80 .z80 jr ?N .8080 ELSE jmp ?N ENDIF ENDM ; BRC MACRO ?N ;;JUMP RELATIVE ON CARRY IF Z80 .z80 jr c,?N .8080 ELSE jc ?N ENDIF ENDM ; BRNC MACRO ?N ;;JUMP RELATIVE ON NO CARRY IF Z80 .z80 jr nc,?N .8080 ELSE jnc ?N ENDIF ENDM ; BRZ MACRO ?N ;;JUMP RELATIVE ON ZERO IF Z80 .z80 jr z,?N .8080 ELSE jz ?N ENDIF ENDM ; BRNZ MACRO ?N ;;JUMP RELATIVE ON NO ZERO IF Z80 .z80 jr nz,?N .8080 ELSE jnz ?N ENDIF ENDM ; BJNZ MACRO ?N ;;DECREMENT B AND JUMP RELATIVE ON NO ZERO IF Z80 .z80 djnz ?N .8080 ELSE dcr b jnz ?N ENDIF ENDM ; ; END OF Z80 MACRO EXTENSIONS ; ; ; Environment Definition ; if z3env ne 0 ; ; External ZCPR3 Environment Descriptor ; jmp start db 'Z3ENV' ;This is a ZCPR3 Utility db 1 ;External Environment Descriptor z3eadr: dw z3env start: lhld z3eadr ;pt to ZCPR3 environment ; else ; ; Internal ZCPR3 Environment Descriptor ; MACLIB Z3BASE.LIB MACLIB SYSENV.LIB z3eadr: jmp start SYSENV start: lxi h,z3eadr ;pt to ZCPR3 environment endif ; ; Start of Program -- Initialize ZCPR3 Environment ; Once Environment is Initialized, One of Three Major Functions ; will be Performed: ; 1. VMENU will be installed as a Shell if invoked explicitly ; by user command ; 2. The VMENU Function will be performed if VMENU is invoked ; by ZCPR3 as a Shell and ZEX is not Running ; 3. A Command Line will be Input by VMENU from ZEX and Passed ; on to ZCPR3 without Processing ; call z3vinit ;initialize the ZCPR3 Env and the VLIB Env ; ; Set Opsys Stack Pointer ; if not WARMBOOT lxi h,0 ;clear hl-pair then.. dad sp ;..add stack address. shld stack endif ;not warmboot ; ; Check to see if VMENU was executed as a shell ; call qshell ;get and test message from ZCPR3 jz runsh ;execute shell procedures ; ; Initialize VMENU as a Shell ; call shtest1 ;there must be a shell stack call shtest2 ;there must be a command line buffer ; ; FUNCTION 1: Set Up VMENU as a Shell ; Run Shell Via Exit to Opsys ; call getefcb ;determine name of program brz shgo1 ;name not given, so use default inx h ;pt to name lxi d,filercmd ;define name of program mvi b,8 call moveb ;copy name shgo1: lxi h,filercmd ;establish shell call shpush ;push onto shell stack brnz shgo2 ;error? ; ; Establish File Selection ; 3rd System File = Name of Menu File (2nd token) ; 4th System File = Name of AFN to Select Files (1st token) ; call getfn2 ;setup file name lxi d,11 ;use 2nd system file dad d xchg ;destination in DE lxi h,joker ;pt to joker mvi b,11 ;copy joker into 2nd system file call move ;... so selection is on joker xchg ;HL now pts to 3rd system file push h ;save ptr to name of Menu File lxi d,fcb2+1 ;pt to FCB xchg mvi b,11 ;copy 11 chars call move push d ;save ptr to file spec lxi h,fcb+1 ;pt to FCB (use 4th system file name) mvi b,11 ;copy 11 chars call move pop d ;get ptr to file spec lxi h,joker ;make wild if none mvi b,11 ;11 chars ldax d ;get first char cpi ' ' ;wild if space cz moveb ;copy ldax d cpi '/' ;wild if option cz moveb pop d ;get ptr to name of menu file lxi h,menufile ;pt to menu file name (default) ldax d ;check for no file name given mvi b,11 ;11 chars cpi ' ' ;if none, set default cz moveb lxi b,8 ;check file type dad b xchg dad b xchg ldax d ;check for file type mvi b,3 ;3 chars cpi ' ' ;if none, set default cz move ; ; Print Done Message ; simsg: mvi a,0 ;default to menu 0 mvi b,1 ;shell message 1 contains menu number call putshm ; mvi b,0 ;shell message 0 mvi a,0 ;no wait call putshm ;set shell message ; call vprint db ' Shell Installed',0 ; jmp os$ccp1 ;return to opsys ; ; Error in Shell Stack Installation ; shgo2: cpi 2 ;shell stack full brnz shgo3 call vprint db ' Shell Stack Full',0 ret shgo3: call vprint db ' Shell Entry Size',0 ret ; ; VMENU was invoked as a Shell ; Check for ZEX Input in Progress ; runsh: call getzrun ;check ZEX message byte jnz zexrun ;process ZEX command line if ZEX running ; ; Check for Delay Before Resuming VMENU and Delay if Set ; mvi b,0 call getshm ;get shell message 0 ani 80h ;check MSB cnz sak ;pause for input mvi a,0 ;set normal command status call putcst ; ; FUNCTION 2: Run VMENU and Perform Main Function ; call setup ;init buffers and pointers call stackset ;setup stack ; ; Begin VMENU Processing ; runsh2: call stackset ;reset stack call fileload ;load files call setscr ;set up screen display variables call findcfile ;locate current file call menuload ;load menu file ; ; Entry Point for Command Processing ; Display Screen and Input/Process Command ; runsh3: call stackset ;reset stack call refresh ;refresh screen display ; ; Display Current File and Input/Process Command ; loopfn: call prcfn1 ;print current file name ; ; Input/Process Command ; loop: call stackset ;reset stack call prompt ;get command from user call cmdproc ;process command in A call icmsg ;print invalid command msg br loop ;continue ; ; Set Stack Pointer ; stackset: pop d ;get return address lhld ibuf ;top of stack sphl ;start local stack push d ;return address on new stack ret ; ; Check for Presence of Shell Stack ; shtest1: call getsh ;get shell stack data rnz pop psw ;clear stack call vprint db 'No Shell Stack',0 ret ; ; Check for Command Line ; shtest2: call getcl1 ;get command line data rnz pop psw ;clear stack call vprint db 'No Cmd Line',0 ret ; ; FUNCTION 3: Run ZEX on Top of VMENU ; Accept Command Line and Pass it to ZCPR3 ; zexrun: call vprint ;print prompt db 'VMENU> ',0 mvi a,1 ;tell ZEX that it is prompted call putzex call getcl1 ;pt to command line buffer mov a,l ;set ptr to first char adi 4 mov c,a mov a,h aci 0 mov b,a ;BC pts to first char mov m,c ;store low inx h mov m,b ;store high inx h ;pt to char count xchg ;... in DE mvi c,rdbuf ;input line via BDOS push d ;save ptr call bdos pop h ;pt to char count inx h mov e,m ;get char count inx h ;pt to first char push h ;save ptr mvi d,0 ;DE=char count dad d xra a ;A=0 mov m,a ;store ending 0 pop h ;pt to first char call sksp ;skip to first non-blank character mov a,m ;get it cpi ';' ;comment line? jz zexrun1 ;process comment line call putzex ;resume ZEX (A=0) call putcst ;set command status to normal (A=0) ret ;return to opsys zexrun1: call crlf ;new line jmp zexrun ; ;************************************************** ; ; CRT Routine for VMENU ; VCLS: CALL CLS ;try to clear the screen RNZ ;OK if done PUSH H ;save regs PUSH B CALL GETCRT ;get CRT Data INX H ;get number of lines on screen MOV B,M ;B=number of lines VCLS1: CALL CRLF ;new line BJNZ VCLS1 POP B ;restore regs POP H RET ; ; EREOL Routine for VMENU ; VEREOL: CALL EREOL ;try to erase to EOL RNZ ;OK if done PUSH B ;save count MVI A,' ' ;space out CALL VEREOL1 ;send B spaces POP B ;get count MVI A,BS ;backspace in VEREOL1: CALL COUT ;send char BJNZ VEREOL1 ;count down RET ; ; Setup Screen Display Variables ; SETSCR: LXI H,CURHOME ;set cursor home SHLD CURAT LHLD RING ;set ring position CALL SETMORE ;set more flag if more files on screen ; ; Entry to Reset Ring Position at HL ; SETSCR1: SHLD RINGPOS ;set current file to first file in ring ; ; Entry to Reset Local Ring Position at HL ; SETSCR2: SHLD LOCBEG ;front of ring LXI D,EPS*ELTSIZ ;new end? DAD D XCHG LHLD RINGEND ;end of ring XCHG CALL CMPDEHL BRC SETSCR3 XCHG SETSCR3: XCHG SHLD LOCEND RET ; ; Set More Flag - Count Files on Screen and See if Display Exceeded ; SETMORE: PUSH H ;SAVE REGS PUSH D PUSH B XRA A ;CLEAR FLAG STA MORE MVI B,EPS ;COUNT DOWN LXI D,ELTSIZ ;SIZE OF ELEMENT SETMORE1: MOV A,M ;GET CHAR ORA A ;DONE IF ZERO JZ SETMDONE DAD D ;PT TO NEXT DCR B ;COUNT DOWN JNZ SETMORE1 MOV A,M ;GET CHAR ORA A ;DONE IF ZERO JZ SETMDONE MVI A,0FFH ;SET FLAG STA MORE SETMDONE: POP B ;RESTORE REGS POP D POP H RET ; ; Search for Current File starting at position in HL ; FINDCFILE: CALL GETFN2 ;get ptr to current file LXI D,11 DAD D ;... which is 2nd System File XCHG ;... ptr in DE ; ; Next group of EPS files for file display ; FINDCF1: LXI H,CURHOME ;set cursor SHLD CURAT LHLD LOCBEG ;pt to first file in list MVI B,EPS ;number of files in display ; ; Check current file ; FINDCF2: SHLD RINGPOS ;set position of current ring element ; ; Check for end of file ring ; MOV A,M ;end of list? ORA A ;done if so BRZ FINDCF4 ; ; Compare candidate file against file in ring ; PUSH H ;save ptr to file PUSH D ;save ptr to System File PUSH B ;save count MVI B,ELTSIZ ;compare CALL CMPSTR POP B ;get count POP D ;get ptr to System File POP H ;get ptr to file BRZ FINDCF5 ;we found it BRC FINDCF5 ;we found following file ; ; Advance to next file in ring ; PUSH B ;save count LXI B,ELTSIZ ;pt to next element DAD B ; ; Advance to next file on screen ; PUSH H LHLD CURAT ;get cursor position MOV A,L ADI 19 ;advance cursor MOV L,A CPI 70 BRC FINDCF3 MOV A,H ;get current line LXI H,CURHOME ;get home row MOV H,A ;set current line INR H ;next line FINDCF3: SHLD CURAT ;set cursor POP H POP B ;get count ; ; Count down files in current display ; BJNZ FINDCF2 ;count down MOV A,M ;any following elements in ring? ORA A ;0=no BRZ FINDCF4 ; ; End of current display - set new display ; SHLD LOCBEG ;new local beginning BR FINDCF1 ;continue search ; ; File beyond end of file display - set pointers to first file ; FINDCF4: LXI H,CURHOME ;set cursor to first file SHLD CURAT LHLD RING ;pt to first file SHLD RINGPOS SHLD LOCBEG ;set local beginning ; ; Done - Set Local Ring ; FINDCF5: LHLD LOCBEG ;pt to local ring JMP SETSCR2 ; ; Display file name of current file ; Side Effect: Change Name of 2nd System File to Current File ; PRCFN1: LXI H,FNADR ;position cursor for file name print CALL GOTOXY CALL GETFN2 ;pt to system file name LXI D,11 ;pt to 2nd System File Name DAD D XCHG ;... in DE LHLD RINGPOS ;pt to current file name MVI B,11 ;copy into 2nd System File Name CALL MOVEB JMP PRFN ;print file name ; ; Process Command ; ICMSG: CALL ERMSG DB 'Invld Cmd: ',0 MOV A,B ;get char CPI ' ' ;expand if less than space JNC COUT MVI A,'^' ;control CALL COUT MOV A,B ;get byte ADI '@' ;convert to letter JMP COUT ;return for loop processing ; ; SET UP BUFFERS ; SETUP: CALL RETUD ;get home DU MOV A,B STA H$DR ;home drive MOV A,C STA H$U$A ;home user area CALL CODEND ;start of free space LXI D,256 ;256 bytes/unit DAD D SHLD IBUF ;input line buffer and top of stack MVI M,IBUFSZ ;number of bytes in line DAD D SHLD EXPLINE ;expansion line DAD D SHLD MENUFCB ;dummy FCB DAD D ;next page SHLD BUFFER ;free space to end of TPA ; ; Begin Further Inits ; LHLD ENVPTR ;pt to ZCPR3 Env Desc LXI D,80H+10H ;pt to cursor commands DAD D LXI D,CTABLE ;pt to area MVI B,4 ;4 commands CURINIT: MOV A,M ;get command STAX D ;put it INX H ;pt to next INX D INX D INX D BJNZ CURINIT ; LHLD BUFFER ;base address SHLD RING ;beginning of ring ; XRA A ;clear error message flag STA ERMFLG ; RET ; e x i t ; return to ccp ; ; Entry point for VMENU exit ; OS$CCP: CALL SHPOP ;clear shell stack ; ; Entry point for command line exec ; OS$CCP1: LXI D,TBUFF ;..tidy up.. MVI C,SETDMA ;..before going home. CALL BDOS IF WARMBOOT JMP OS$BASE ENDIF ;warmboot IF NOT WARMBOOT LHLD STACK ;put pointer.. SPHL ;..back to 'sp'. RET ;return to ccp ENDIF ;not warmboot ; ; FLOAD loads the files into the buffer, setting up the ring ; Return with NZ if load OK, Z if no files loaded ; FILELOAD: ; ; Set up file name from System File 4 ; Select all files if no entry in System File 4 ; CALL GETFN2 ;pt to first system file name LXI D,11*3 ;pt to 4th file name DAD D LXI D,JOKER ;setup Joker if none XCHG LDAX D ;any chars? MVI B,11 ;11 bytes CPI ' ' CZ MOVEB XCHG ;HL pts to system file name LXI D,FCB+1 ;pt to FCB MVI B,11 ;11 bytes CALL MOVEB ; ; Build ring with filename positioned in default FCB area ; LHLD RING ;pt to ring MVI B,ELTSIZ ;set first element to 'noname' FILEL1: MVI M,1 ;store ^A's INX H ;pt to next BJNZ FILEL1 SHLD RINGPOS ;set ring position SHLD RINGEND ;set ring end in case this is the only one MVI M,0 ;store ending 0 MVI C,SETDMA ;initialize dma address.. LXI D,TBUFF ;..to default buffer. CALL BDOS XRA A ;clear search 'fcb'.. STA FCBEXT ;extent byte.. STA FCBRNO ;..and record number. LXI D,FCB ;default FCB for search CMA MVI C,SRCHF ;..of first occurrence. CALL BDOS INR A ; 0ffh --> 00h if no file found RZ ; put each found name in ring. a-reg --> offset into 'tbuf' name storage SETRING: DCR A ;un-do 'inr' from above and below ADD A ;times 32 --> position index ADD A ADD A ADD A ADD A ADI TBUFF+1 ;add page offset and.. MOV L,A ;..put address into.. MVI H,0 ;..hl-pair. XCHG LHLD RINGPOS ;pointer to current load point in ring XCHG MVI B,ELTSIZ ;move name to ring CALL MOVE XCHG ;de-pair contains next load point address SHLD RINGPOS ;store and search.. MVI C,SRCHN ;..for next occurrence. LXI D,FCB ;filename address field CALL BDOS INR A ;if all done, 0ffh --> 00h. BRNZ SETRING ;if not, put next name into ring. ; ; All filenames in ring -- setup ring size and copy-buffer start point ; LHLD RINGPOS ;next load point of ring is start of buffer SHLD RINGEND ;set ring end.. MVI M,0 ;store ending 0 ; ; Sort ring of filenames ; SORT: LHLD RING ;initialize 'i' sort variable and.. SHLD RINGI LXI D,ELTSIZ ;..also 'j' variable. DAD D SHLD RINGJ ; ; Main Sort Loop ; SORTLP: LHLD RINGJ ;compare names 'i & j' XCHG LHLD RINGI PUSH H ;save position pointers.. PUSH D ;..for potential swap. ; sort by file name and type MVI B,ELTSIZ ; # of characters to compare CALL CMPSTR ;do comparison ; final test for swapping purposes NOCMP: POP D POP H MVI B,ELTSIZ BRNC NOSWAP ; ; Swap if 'j' string larger than 'i' ; SWAP: MOV C,M ;get character from one string.. LDAX D ;..and one from other string. MOV M,A ;second into first MOV A,C ;first into second STAX D INX H ;bump swap pointers INX D BJNZ SWAP NOSWAP: LHLD RINGJ ;increment 'j' pointer LXI D,ELTSIZ DAD D SHLD RINGJ XCHG ;see if end of 'j' loop LHLD RINGEND CALL CMPDEHL BRNZ SORTLP ;no, so more 'j' looping. LHLD RINGI ;bump 'i' pointer LXI D,ELTSIZ DAD D SHLD RINGI DAD D ;set start over 'j' pointer SHLD RINGJ XCHG ;see if end of 'i' loop LHLD RINGEND CALL CMPDEHL BRNZ SORTLP ;must be more 'i' loop to do RET ; ; left to right compare of two strings (de-pair points to 'a' string; ; hl-pair, to 'b'; b-reg contains string length.) ; CMPSTR: LDAX D ;get an 'a' string character and.. CMP M ;..check against 'b' string character. RNZ ;if not equal, set flag. INX H ;bump compare.. INX D ;..pointers and.. BJNZ CMPSTR ;..do next character. RET ; ; Process command from table ; CTPROC: MOV B,A ;command in B LXI H,CTABLE ;pt to table MOV A,M ;any cursor commands? ORA A JNZ CTPR1 LXI H,CTAB1 ; ; Command table scanner ; HL = Table ; B = Command Letter ; CTPR1: MOV A,M ;get table command char ORA A ;end of table? RZ ;done if so CMP B ;match? BRZ CTPR2 INX H ;skip to next entry INX H INX H BR CTPR1 CTPR2: INX H ;pt to address MOV A,M ;get low INX H MOV H,M ;get high MOV L,A XTHL ;address on stack RET ;"jump" to routine ; Command Table CTABLE: DB 0 ;user cursor positioning DW UP DB 0 DW DOWN DB 0 DW FORWARD DB 0 DW REVERSE CTAB1: DB CTRLC ;if exit, then to opsys DW OS$CCP DB CTRLR ;screen refresh? DW RUNSH3 DB CTRLE ;system cursor positioning DW UP DB CTRLX DW DOWN DB CTRLD DW FORWARD DB CTRLS DW REVERSE DB CR ;nop DW LOOP DB '+' ;jump forward DW JUMPF DB '-' ;jump backward DW JUMPB DB ' ' ;go forward DW FORWARD DB BS ;back up? DW REVERSE ; DB 0 ;end of table ; ; COMMAND: - (Previous Screen) ; JUMPB: LXI H,CURHOME ;set cursor home SHLD CURAT LHLD RING ;at front? XCHG LHLD LOCBEG CALL CMPDEHL BRZ JUMPBW ;back up and wrap around SHLD LOCEND ;set new end LXI D,-EPS*ELTSIZ ;back up DAD D SHLD LOCBEG ;new beginning SHLD RINGPOS ;new position JMP RUNSH3 JUMPBW: LHLD LOCBEG ;at first screen? XCHG LHLD RING ;pt to first element of ring CALL CMPDEHL BRZ JBW0 ;advance to end LXI H,-EPS*ELTSIZ ;back up DAD D ;first element of new local ring BR JFW0 JBW0: LXI D,EPS*ELTSIZ ;pt to next screen DAD D XCHG LHLD RINGEND CALL CMPDEHL XCHG BRZ JBW1 BRC JBW0 JBW1: LXI D,-EPS*ELTSIZ DAD D ;pt to first element of new local ring BR JFW0 ; ; COMMAND: + (Next Screen) ; JUMPF: LXI H,CURHOME ;set cursor to home SHLD CURAT LHLD LOCEND ;see if Local End <= Ring End XCHG LHLD RINGEND CALL CMPDEHL BRZ CMDLOOP LHLD LOCEND ;new screen starting at LOCEND BR JFW0 ; ; Reset to Beginning of RING and Resume Command Looping ; CMDLOOP: CALL SETSCR ;reset all screen pointers CMDLRET: JMP RUNSH3 ; ; Reset RING Position to HL ; JFW0: CALL SETSCR1 ;reset RINGPOS on ... BR CMDLRET ; ; Reset Local Ring to HL ; JFW0A: CALL SETSCR2 ;reset LOCBEG on ... BR CMDLRET ; ; COMMAND: ' ', Left-Arrow ; FORWARD: CALL CLRCUR ;clear cursor CALL FOR0 ;position on screen and in ring CALL SETCUR ;set cursor JMP LOOPFN ; advance routine FOR0: LHLD RINGPOS ;at end of loop yet? LXI D,ELTSIZ ;i.e., will we be at end of loop? DAD D XCHG LHLD LOCEND CALL CMPDEHL ;compare 'present' to 'end' BRNZ FORW ;to next print position CALL CUR$FIRST ;position cursor LHLD LOCBEG ;set position pointer to beginning and.. SHLD RINGPOS RET FORW: LHLD RINGPOS ;advance in ring LXI D,ELTSIZ DAD D SHLD RINGPOS ;new position CALL CUR$NEXT ;position cursor RET ; ; COMMAND: BS, Right-Arrow ; REVERSE: CALL CLRCUR ;clear cursor CALL REV0 ;position on screen and in ring CALL SETCUR ;set cursor JMP LOOPFN ; Back Up Routine REV0: LHLD LOCBEG XCHG LHLD RINGPOS ;see if at beginning of ring CALL CMPDEHL BRNZ REV1 ;skip position pointer reset if not.. CALL CUR$LAST ;end of local ring LHLD LOCEND ;set to end +1 to backup to end LXI D,-ELTSIZ DAD D SHLD RINGPOS RET REV1: CALL CUR$BACK ;back up 1 REV2: LHLD RINGPOS LXI D,-ELTSIZ ;one ring position.. DAD D ;..backwards. SHLD RINGPOS RET ; ; COMMAND: Up-Arrow ; UP: CALL CLRCUR ;clear cursor LHLD RINGPOS ;see if wrap around LXI D,-ELTSIZ*4 ;4 entries DAD D XCHG LHLD LOCBEG ;beginning of local screen CALL CMPDEHL BRC UP2 ;wrap around MVI B,4 ;back up 4 entries UP1: PUSH B ;save count CALL REV0 ;back up in ring and on screen (no print) POP B ;get count BJNZ UP1 BR DOWN1A UP2: LHLD RINGPOS ;advance to beyond end LXI D,ELTSIZ*4 DAD D XCHG LHLD LOCEND ;compare to local end XCHG CALL CMPDEHL BRZ DOWN1A ;at end, so too far BRC DOWN1A ;beyond end, so back up SHLD RINGPOS ;new ring position LHLD CURAT ;advance cursor INR H ;next line SHLD CURAT BR UP2 ; ; COMMAND: Down-Arrow ; DOWN: CALL CLRCUR ;clear cursor LHLD RINGPOS ;see if wrap around LXI D,ELTSIZ*4 ;4 entries DAD D XCHG LHLD LOCEND ;end of local screen XCHG CALL CMPDEHL BRZ DOWN2 ;wrap around BRC DOWN2 ;wrap around MVI B,4 ;forward 4 entries DOWN1: PUSH B ;save count CALL FOR0 ;advance in ring and on screen (no print) POP B ;get count BJNZ DOWN1 DOWN1A: CALL SETCUR ;set cursor JMP LOOPFN DOWN2: LHLD CURAT ;preserve column MOV B,L ;column number in B LXI H,CURHOME ;home position SHLD CURAT ;set new position LHLD LOCBEG ;beginning of local ring SHLD RINGPOS ;new ring position DOWN3: LHLD CURAT ;check for at top of column MOV A,L ;get col CMP B ;there? BRZ DOWN1A LHLD RINGPOS ;advance in ring LXI D,ELTSIZ ;ELTSIZ bytes/entry DAD D SHLD RINGPOS LHLD CURAT ;get cursor position LXI D,19 ;advance 19 bytes/screen entry DAD D SHLD CURAT BR DOWN3 ; ;************************************************** ; ; WORKHORSE Routines ; ; conin routine (waits for response) ; KEYIN: CALL CIN ;get input JMP CAPS ;capitalize ; ; Fill buffer with 'spaces' with count in b-reg ; FILL: MVI M,' ' ;put in space character INX H BJNZ FILL ;no, branch. RET ; ; Check for legal filename character -- return with carry set if illegal ; CKLEGAL: LDAX D ;get character from de-pair INX D ;point at next character CPI ' ' ;less than space? RC ;return carry if unpermitted character PUSH H PUSH B CPI '[' ;if greater than 'z', exit with.. BRNC CKERR ;..carry set. MVI B,CHR$TEND-CHR$TBL LXI H,CHR$TBL CHR$LP: CMP M BRZ CKERR INX H BJNZ CHR$LP ORA A ;clear carry for good character POP B POP H RET CKERR: POP B POP H STC ;error exit with carry set RET CHR$TBL: DB ',',':',';','<','=','>' ;invalid character table CHR$TEND: DS 0 ; ; Print file name pted to by HL ; Advance HL 11 bytes ; PRFN: MOV A,M ;check for 'noname' CPI 1 ;no name? BRZ PRFN1 MVI B,8 ;8 chars CALL PRFNS1 MVI A,'.' CALL COUT MVI B,3 ;file type and fall thru PRFNS1: MOV A,M ;get char CALL COUT INX H ;pt to next BJNZ PRFNS1 RET PRFN1: CALL VPRINT DB ' No File' DB ' ' DB ' ',0 MVI B,11 ;advance 11 chars PRFN2: INX H ;pt to next BJNZ PRFN2 RET ; ; move subroutine -- move b-reg # of bytes from hl-pair to de-pair ; MOVE: MOV A,M ;get hl-pair referenced source byte ANI 7FH ;strip attributes STAX D ;put to de-pair referenced destination INX H ;fix pointers for next search INX D BJNZ MOVE RET MOVEB: PUSH H ;SAVE HL, DE PUSH D CALL MOVE POP D ;RESTORE DE, HL POP H RET ; ; Compare de-pair to hl-pair and set flags accordingly ; CMPDEHL: MOV A,D ;see if high bytes set flags CMP H RNZ ;return if not equal MOV A,E CMP L ;low bytes set flags instead RET ; ; Shift hl-pair b-reg bits (-1) to right (divider routine) ; SHIFTLP: DCR B RZ MOV A,H ORA A RAR MOV H,A MOV A,L RAR MOV L,A BR SHIFTLP ; ;************************************************** ; ; MESSAGE Routines ; ; Print VMENU Banner ; BANNER: CALL VCLS ;clear screen LXI H,BANADR CALL GOTOXY CALL VPRINT ;print banner DB 'VMENU, Version ' DB VERS/10+'0','.',(VERS MOD 10)+'0' IF Z80 DB ' ',DIM,'[Z80 Code]',BRIGHT ELSE DB ' ',DIM,'[8080 Code]',BRIGHT ENDIF DB 0 RET ; ; Print DU:DIR and MORE Message ; DIRMORE: LXI H,DUADR ; POSITION CURSOR CALL GOTOXY CALL RETUD ; GET CURRENT DISK AND USER MOV A,B ; PRINT DISK ADI 'A' CALL COUT MOV A,C ; PRINT USER CALL PAFDC ; FLOADING DECIMAL MVI A,':' CALL COUT CALL DUTDIR ; GET DIR NAME BRZ NODIR MVI B,8 ; 8 CHARS IN NAME PRNAME: MOV A,M ; GET CHAR CPI ' '+1 ; CHECK FOR DONE BRC PRMORE CALL COUT ; PRINT CHAR INX H BJNZ PRNAME BR PRMORE NODIR: CALL VPRINT DB 'Noname',0 PRMORE: LDA MORE ; CHECK FLAG ORA A ; 0=NO MORE RZ LXI H,MOREADR CALL GOTOXY ; POSITION CURSOR CALL VPRINT DB DIM,'[More Files]',BRIGHT,0 RET ; ; Home the Cursor ; CUR$FIRST: LXI H,CURHOME ; HOME ADDRESS SHLD CURAT ; SET CURSOR POSITION JMP GOTOXY ; ; Last File Position ; CUR$LAST: LHLD RINGPOS ; ADVANCE SHLD LOCPOS ; SET LOCAL POSITION CL0: LXI D,ELTSIZ DAD D XCHG LHLD LOCEND ; END OF LOCAL RING? CALL CMPDEHL RZ XCHG ; NEW POSITION SHLD LOCPOS PUSH H ; SAVE POSITION CALL CUR$NEXT ; ADVANCE CURSOR POP H ; GET POSITION BR CL0 ; ; Advance the Cursor ; CUR$NEXT: LHLD CURAT ; COMPUTE NEW POSITION MOV A,L ; CHECK FOR NEW LINE ADI 19 ; SIZE OF EACH ENTRY CPI 70 BRNC CN1 ; ADVANCE TO NEXT LINE MOV L,A ; NEW POSITION SHLD CURAT JMP GOTOXY CN1: MOV A,H ; GET LINE LXI H,CURHOME ; GET COL MOV H,A ; SET LINE AND FALL GO TO CUR$DOWN SHLD CURAT BR CUR$DOWN ; ; Back Up the Cursor ; CUR$BACK: LXI H,CURHOME ; GET HOME XCHG ; ... IN DE LHLD CURAT CALL CMPDEHL ; COMPARE BRZ CUR$LAST ; GOTO END IF LAST MOV A,L ; CHECK FOR FIRST COL CMP E BRZ CB1 SUI 19 ; BACK UP ONE COL MOV L,A SHLD CURAT ; NEW POS JMP GOTOXY CB1: MOV A,E ; GET HOME COL ADI 19*3 ; GET LAST COL MOV L,A DCR H ; PREV LINE SHLD CURAT JMP GOTOXY ; ; Move Cursor Down One Line ; CUR$DOWN: LXI H,CURHOME ; GET HOME ADDRESS MOV B,H ; LINE IN B LHLD CURAT ; GET CURRENT ADDRESS INR H ; MOVE DOWN MOV A,H ; CHECK FOR TOO FAR SUB B CPI EPS/4 BRNC CD1 SHLD CURAT ; OK, SO SET POSITION JMP GOTOXY CD1: MOV A,L ; GET COL LXI H,CURHOME MOV L,A SHLD CURAT JMP GOTOXY ; ; Refresh Screen ; REFRESH: LHLD CURAT ; SAVE CURSOR AND RING POSITIONS SHLD SCURAT LHLD RINGPOS SHLD SRINGPOS CALL BANNER ; PRINT BANNER CALL DIRMORE ; PRINT CURRENT DIRECTORY AND MORE MESSAGE CALL DISPFILES ; DISPLAY FILES CALL DISPMENU ; DISPLAY MENU LHLD SCURAT ; RESTORE CURSOR AND RING POSITIONS SHLD CURAT LHLD SRINGPOS SHLD RINGPOS CALL SETCUR ; RESTORE CURSOR ON SCREEN call atcmd call vprint db DIM,'Command (CR=Menu',0 lda cpmok ;OK to return to ZCPR3? ora a ;0=No cnz prmptc lhld cstart ;pt to first char mov a,m ;get it ani 7FH ;mask cpi MFIRST cnz prmptf ;print previous menu prompt if not first menu lda nmenfl ;next menu available? ora a ;0=No cnz prmptn ;print next menu prompt call vprint db ') - ',BRIGHT,0 RET ; ; Print ZCPR3 Return Prompt ; prmptc: call vprint db ', ^C=Z3',0 ret ; ; Print First/Last Menu Chars ; prmptf: call vprint db ', ',RFM,'=1st Menu, ',RLM,'=Prev Menu',0 ret ; ; Print next menu message ; prmptn: call vprint db ', ',RNM,'=Next Menu',0 ret ; ; Refresh File Display ; DISPFILES: CALL CUR$FIRST ; POSITION CURSOR AT FIRST POSITION LHLD LOCBEG ; PT TO FIRST FILE NAME SHLD LOCPOS ; SAVE LOCAL POSITION DSPF1: LHLD LOCEND ; AT END? XCHG LHLD LOCPOS CALL CMPDEHL JZ CUR$FIRST ; POSITION AT FIRST ENTRY AND RETURN MVI B,4 ; 4 SPACES MVI A,' ' DSPF2: CALL COUT BJNZ DSPF2 CALL PRFN ; PRINT FILE NAME (HL IS ADVANCED) SHLD LOCPOS CALL CUR$NEXT ; ADVANCE CURSOR BR DSPF1 ; ; Position Cursor at CURAT ; SETCUR: LHLD CURAT CALL GOTOXY CALL VPRINT DB '-->',0 RET ; ; Clear Cursor ; CLRCUR: LHLD CURAT CALL GOTOXY CALL VPRINT DB ' ',0 RET ; ; Working Message ; WORKMSG: CALL ERMSG DB DIM,'Working ...',BRIGHT,0 RET ; ; Error Message ; ERMSG: MVI A,0FFH ; SET ERROR MESSAGE FLAG STA ERMFLG LXI H,ERADR ; GET ADDRESS CALL GOTOXY JMP VPRINT ; ; Clear Error Message ; ERCLR: XRA A ; CLEAR FLAG STA ERMFLG LXI H,ERADR ; POSITION CALL GOTOXY PUSH B MVI B,76-(ERADR MOD 255) CALL VEREOL ; ERASE TO EOL POP B RET ; ; Position at Command Prompt and Clear It ; ATCMD: LXI H,CPMADR ; POSITION CALL GOTOXY PUSH B MVI B,76-(CPMADR MOD 255) CALL VEREOL ; CLEAR MESSAGE POP B LXI H,CPMADR ; REPOSITION JMP GOTOXY ; ; Position at Bottom of Screen and Prompt for Continuation ; BOTTOM: LXI H,BOTADR ; POSITION CALL GOTOXY ; ; Prompt for Continuation ; SAK: CALL VPRINT DB DIM,'Strike Any Key -- ',BRIGHT,0 JMP KEYIN ; ; Open Menu File ; menuload: lhld menufcb ;pt to menu fcb inx h push h call getfn2 ;copy FCB into MENU FCB lxi d,11*2 ;pt to 3rd system file name dad d pop d ;DE pts to first char of MENU FCB file name mvi b,11 ;11 bytes call moveb dcx d ;pt to fcb call initfcb ;init fcb call f$open ;open file brz menu1 ;abort if no menu call vprint db CR,LF,' File ',0 lhld menufcb ;pt to file name inx h call prfn call vprint db ' Not Found',0 jmp os$ccp ;abort ; ; Load Menu File from disk ; menu1: call menustrt ;get address of buffer for menu load xchg ;... in DE ; ; Load next block from Menu File -- DE pts to Load Address ; mload: lhld menufcb ;pt to FCB xchg ;... in DE, HL = load address call f$read ;read in next block ora a ;error? brnz mloaddn ;load done if error lxi d,tbuff ;copy from TBUFF into memory pted to by HL xchg ;HL is source, DE is dest mvi b,128 ;128 bytes call move lhld bdos+1 ;get address of top of TPA mov a,h ;set to bottom of ZCPR3 sui 10 cmp d ;about to overflow ZCPR3? brnc mload ;continue if not call vprint db CR,LF,' TPA Full',0 jmp os$ccp ; ; Init Flags and Clear MSB of all bytes in Menu File ; mloaddn: call f$close ;close input file mvi m,CTRLZ ;ensure EOF mark xra a ;A=0 sta cpmok ;turn off ZCPR3 return flag call menustrt ;pt to first menu char push h ;save ptr menul1: mov a,m ;get byte ani 7FH ;mask out MSB mov m,a ;put byte inx h ;pt to next cpi CTRLZ ;EOF? brnz menul1 ;continue if not ; ; Mark all Menu Sections ; pop h ;HL pts to first byte of menu mvi b,0FFH ;set menu counter ; ; Skip to Next Menu ; menul2: mov a,m ;get byte cpi CTRLZ ;error? jz mstrerr ;structure error if so cpi MINDIC ;menu indicator (start of menu?) brnz menul4 ori 80H ;beginning of menu found -- set MSB mov m,a ;put byte inr b ;increment menu count inx h ;pt to next mov a,m ;get byte cpi MINDIC ;menu indicator (end of menu?) brz menul5 ;done if so cpi CTRLZ ;error? jz mstrerr ; ; Skip out Menu Display ; menul3: call lskipt ;skip to beginning of next line brz menul4 ;found menu indicator cpi CTRLZ ;error? jz mstrerr br menul3 ;continue if not ; ; Skip to Next Menu ; menul4: call lskipt ;skip to beginning of next menu brz menul2 ;resume if at beginning of next menu cpi CTRLZ ;error? jz mstrerr br menul4 ; ; Check Menu Options ; menul5: call menustrt ;pt to first menu char mov a,m ;check for option cpi GOPTION ;global option char? jnz mfile ;if no global option, scan for menu files inx h ;pt to option char option: mov a,m ;get option char call caps ;capitalize inx h ;pt to next cpi CR ;done? brz optdn cpi XOPTION ;exit OK? jnz mstrerr ;option error if not ; ; Disable Exit to ZCPR3 ; mvi a,0FFH ;turn flag off sta cpmok br option ; ; Option Processing Done ; optdn: inx h ;skip LF ; ; Check for Menu Display ; mfile: mov a,m ;get first byte ani 7FH ;mask cpi MINDIC ;start of menu? jnz mstrerr ; ; Check and Set First Menu ; shld mstart ;save start address of first menu item mvi m,MFIRST+80H ;set first char of first menu ret ; ; Entry Point for Menu Display ; dispmenu: mvi h,epsline ;pt to first line of menu mvi l,1 ;col 1 call gotoxy ;position there lhld mstart ;pt to first byte of current menu mvi b,1 ;shell message 1 contains menu number call getshm ;get menu number flag cnz mchc0 ;skip to proper menu shld cstart ;save start address of current menu inx h ;pt to first char after menu indicator char dispm1: mov a,m ;get char call caps ;capitalize inx h ;pt to next cpi CR ;end of options? brz dispm2 cpi XOPTION ;ZCPR3 return? jnz mstrerr ;error if not ; ; Toggle ZCPR3 Return Option ; lda cpmok ;get flag cma ;toggle sta cpmok br dispm1 ; ; Done with Menu-Specific Option Processing ; dispm2: call lskip ;skip to LF call getnlines ;get line count in A sta pagcnt ;set count ; ; Print Next Line of Menu if not Starting with ESCAPE Char (MINDIC) ; dispm3: mov a,m ;get first char of line ani 7FH ;mask cpi MINDIC ;done? brz dispm4 call expand ;expand line pted to by HL push h ;save ptr to next line xchg ;HL pts to expanded line call lprintx ;print line pted to by HL ending in pop h ;pt to next line br dispm3 ; ; Done with Menu Display ; dispm4: call lskip ;skip to first char of next line (option char) shld optstrt ;set start address of options ; ; Determine if Another Menu Follows ; xra a ;A=0 sta nmenfl ;set for no next menu dispm5: mov a,m ;ok? ani 7FH ;mask cpi CTRLZ ;error if EOF jz mstrerr cpi MINDIC ;next menu? brnz dispm6 inx h ;double indicator if end mov a,m cpi MINDIC ;end? rz mvi a,0FFH ;set next menu sta nmenfl ret dispm6: call lskip ;skip to next line br dispm5 ; ; Ready for Option Input ; The following Flags/Values are now set: ; OPTSTRT -- Address of First Menu Option ; NMENFL -- 0 if no next menu, 0FFH if next menu ; CSTART -- Address of First Char of Current Menu ; MSTART -- Start Address of MINDIC Before Menu Display ; (MSTART)=MFIRST with MSB Set prompt: lxi h,cpadr ;position for input call gotoxy mvi a,0ffh sta pagcnt ;turn off paging call keyin ;get user input PUSH PSW ;save command LDA ERMFLG ;error message? ORA A ;0=no CNZ ERCLR ;erase old error message POP PSW ;get command ret ; ; Process Command ; cmdproc: call ctproc ;process movement or exit command ; ; Check for Command to Return to First Menu ; lhld cstart ;pt to first char of menu mov a,m ;get it ani 7FH ;mask cpi MFIRST brz prmpt1 mov a,b ;get command cpi RFM ;return to first menu? brnz prmpt1 lhld mstart ;pt to first menu mvi b,1 ;shell message 1 is menu number xra a ;A=0=menu 0 jmp putshm ;reenter shell at first menu ; ; Check for Command to go to Next Menu ; prmpt1: lda nmenfl ;next menu available? ora a ;0=No brz prmpt2 mov a,b ;get command cpi RNMP ;goto next menu? brz rnmx cpi RNM ;goto next menu? brnz prmpt2 rnmx: mvi b,1 ;shell message 1 is menu number call getshm ;increment menu number inr a call putshm ;reenter menu system at new menu jmp os$ccp1 ; ; Check for Command to go to Last Menu ; prmpt2: mov a,m ;get menu char ani 7FH ;at first menu? cpi MFIRST brz prmpt3 ;skip if at first menu mov a,b ;get command cpi RLMP ;goto last menu? brz lstmnu cpi RLM ;goto last menu? brnz prmpt3 lstmnu: mvi b,1 ;shell message 1 is menu number call getshm ;decrement menu number dcr a call putshm ;reenter shell at last menu jmp os$ccp1 ; ; This is where additional functions may be added ; prmpt3: ; ; Check for Option Letter ; lhld optstrt ;pt to first option char prmptx: mov a,m ;get it ani 7FH ;mask MSB call caps ;capitalize cpi MINDIC ;at next menu? rz cmp b ;match user selection? brz prmptd call lskip ;skip to next line br prmptx ; ; Process Option ; prmptd: mvi b,0 ;shell message 0, bit 7 = wait flag call getshm ani 7FH ;set no wait call putshm inx h ;pt to first letter of command mov a,m ;get it cpi MCMD ;invoke other menu? jz mchcmd ;menu change command cpi WOPTION ;turn on wait? brnz prmptg mvi b,0 ;shell message 0, bit 7 = wait flag call getshm ori 80h ;set wait flag call putshm ;set shell message inx h ;skip option char prmptg: call expand ;expand line, DE pts to result ; ; Run Command Pted to by DE ; runcmnd: call getcl1 ;get address of command buffer mov b,h ;... in BC also mov c,l mvi a,4 ;HL=HL+4 for address of first char add l mov l,a mov a,h aci 0 mov h,a mov a,l ;store address stax b inx b mov a,h stax b ; ; Copy Command Line in DE into Buffer in HL ; cmdcpy: ldax d ;get command letter call caps ;capitalize it ora a ;done? brz ccpyd cpi CR ;done? brz ccpyd cpi PCHAR ;prompt? brz ccpyp mov m,a ;store it inx h ;pt to next inx d br cmdcpy ccpyd: mvi m,0 ;store ending 0 jmp os$ccp1 ;optionally display command ; ; Prompt User for Input and Accept It ; ccpyp: inx d ;pt to first char of prompt call crlf ;new line ccpyp1: ldax d ;get char cpi PCHAR ;end of prompt? brz ccpyp2 cpi CR ;new line? brz ccpyp3 call cout ;echo char inx d ;pt to next char br ccpyp1 ;continue looping ccpyp2: inx d ;pt to char after closing PCHAR ccpyp3: push d ;save ptr to next char xchg ;DE pts to buffer mvi a,0FFH ;capitalize input from user lhld ibuf ;input line buffer call bline ;get input from user xchg ;HL pts to buffer, DE pts to user input cmdlp: ldax d ;get char from user ora a ;end of input? brz cmdlp1 ;store rest of line mov m,a ;store char inx h ;pt to next inx d br cmdlp cmdlp1: pop d ;DE pts to next char, HL pts to buffer br cmdcpy ;resume copying ; ; Menu Change Command -- Jump to Specified Menu ; mchcmd: inx h ;pt to menu number call eval ;convert to decimal number in A sta menuno ;save menu number call mchc0 ;skip to desired menu to check for it lda menuno ;get menu number mvi b,1 ;menu number is shell message 1 jmp putshm ;set message and reenter shell ; ; Entry Point if MENU is Reinvoked ; mchc0: mov b,a ;menu number in B inr b ;increment for following decrement lhld mstart ;pt to start of menu mchc1: dcr b ;count down rz ;done if found mchc2: call lskipt ;skip to next line brnz mchc2 ;continue if not end of menu display cpi CTRLZ ;EOF? jz mstrerr mchc3: call lskipt ;skip to next line brnz mchc3 ;continue if not at end of menu commands cpi CTRLZ ;EOF? jz mstrerr inx h ;end of MENU.MNU? mov a,m ;yes if double MINDIC ani 7FH ;mask cpi MINDIC jz mstrerr ;error if so dcx h ;pt to first char br mchc1 ;continue ; ; Print Line pted to by HL Ending in ; Decrement PAGCNT ; lprintx: call lprint ;print without jmp crlf ;do ; ; Print Line Pted to by HL; Decrement PAGCNT ; lprint: lda pagcnt ;check for page overflow ora a ;do nothing brz lskip ;... except skip out line mvi b,0 ;set tab counter lprnt0: mov a,m ;get char inx h ;pt to next ani 7FH ;mask MSB cpi DIM ;goto standout mode? brz lprnt3 cpi BRIGHT ;end standout mode? brz lprnt4 cpi TAB ;tabulate? brz lprnt2 cpi CR ;done? brz lprnt1 call cout ;print inr b ;incr tab counter br lprnt0 lprnt1: inx h ;pt to first char of next line lda pagcnt ;count down pages dcr a sta pagcnt ret lprnt2: mvi a,' ' ;print call cout inr b ;incr tab counter mov a,b ;done? ani 7 ;every 8 brnz lprnt2 br lprnt0 lprnt3: call stndout ;enter standout mode br lprnt0 lprnt4: call stndend ;end standout mode br lprnt0 ; ; Skip to Beginning of Next Line and Test First Char for Menu Indicator ; lskipt: call lskip ;skip mov a,m ;get char ani 7FH ;mask cpi MINDIC ;test ret ; ; Skip to Beginning of Next Line ; lskip: mov a,m ;get char ani 7FH ;mask out MSB cpi CTRLZ ;EOF? rz inx h ;pt to next cpi LF ;EOL? brnz lskip ret ; ; Menu Structure Error -- FATAL ; This message is printed to indicate an error in the structure of ; the MENU.MNU file. ; mstrerr: call vprint db CR,LF,' Structure Error',0 jmp os$ccp ; ; Expand Line Pted to by HL into Scratch Area ; Return with HL pting to next line, DE pting to current line ; expand: xchg lxi h,noname ;init no name file mvi m,1 ;set no entry lhld expline ;pt to buffer xchg exp1: mov a,m ;get next char ani 7fh ;mask MSB stax d ;store char cpi CR ;end of line? jz expx inx h ;pt to next inx d cpi VARFLAG ;variable follows? brnz exp1 ; ; Variable Identified - Process it ; mov a,m ;get next char inx h ;pt to next cpi VARFLAG ;one variable char? brz exp1 ;resume if double VARFLAG dcx d ;pt to variable position ani 7FH ;mask call caps ;capitalize variable cpi FPDISK ;current disk? brz expdisk cpi FPUSER ;current user? brz expuser cpi FPFILE ;filename.typ? brz expfile cpi FPNAME ;filename? brz expname cpi FPPTR ;file being pointed to? brz exppfile cpi FPTYPE ;filetype? brz exptype br exp1 ;resume expansion ; ; Expand Exit ; expx: inx h ;pt to line feed mov a,m ;get it cpi LF ;line feed? brnz expx1 inx h ;pt to char after line feed expx1: xchg ;DE pts to next line lhld expline ;pt to expanded line xchg ;HL pts to next line, DE pts to expanded line ret ; ; Expand Disk ; expdisk: call retud ;get disk in B mov a,b ;get disk number (A=0) adi 'A' ;convert to ASCII stax d ;store letter inx d ;pt to next br exp1 ;resume expansion ; ; Expand User ; expuser: call retud ;get user in C mov a,c ;get user number mvi b,10 ;subtract 10's mvi c,'0' ;set char expu1: sub b ;-10 brc expu2 inr c ;increment digit br expu1 expu2: add b ;+10 adi '0' ;convert 1's to ASCII mov b,a ;B=1's mov a,c ;get 10's stax d ;store 10's inx d mov a,b ;get 1's stax d ;store 1's inx d ;pt to next br exp1 ;resume ; ; Expand File ; expfile: call getfnum ;get file number jz exp1 ;resume if error push h ;save ptr to next char call ptfn ;set ptr to file name call putn ;put file name mvi a,'.' stax d ;store dot inx d ;pt to next call putt ;put file type pop h ;restore ptr jmp exp1 ;resume ; ; Expand Name ; expname: call getfnum ;get file number jz exp1 ;resume if error push h ;save ptr to next char call ptfn ;set ptr to file name call putn ;put file name pop h ;restore ptr jmp exp1 ;resume ; ; Expand Type ; exptype: call getfnum ;get file number jz exp1 ;resume if error push h ;save ptr to next char call ptfn ;set ptr to file name mvi a,8 ;add 8 add l mov l,a mov a,h aci 0 mov h,a call putt ;put file type pop h jmp exp1 ;resume ; ; Expand File at Pointer ; exppfile: mov a,m ;get option char ani 7FH ;mask call caps ;capitalize cpi FPFILE ;filename.typ? brz exppf cpi FPNAME ;filename only? brz exppn cpi FPTYPE ;filetype only? brz exppt jmp exp1 ;abort if error ; ; Extract full filename.typ of file being pointed to ; exppf: inx h ;pt to next char push h ;save ptr to next char lhld ringpos ;set ring position call cknoname ;check and substitute no file call putn ;put name pted to by HL mvi a,'.' ;store dot stax d inx d call putt ;put type pted to by HL pop h jmp exp1 ;continue ; ; Expand file name of file being pointed to ; exppn: inx h ;pt to next char push h ;save ptr to next char lhld ringpos ;set ring position call cknoname ;check and substitute no file call putn ;put name pop h jmp exp1 ; ; Expand file type of file being pointed to ; exppt: inx h ;pt to next char push h ;save ptr to next char push d ;save DE lhld ringpos ;pt to ring entry call cknoname ;check and substitute no file lxi d,8 ;pt to file type dad d pop d ;get DE call putt ;put type pop h jmp exp1 ; ; Check to see if HL pts to 'noname' and, if so, substitute name ; cknoname: push d ;save DE push b ;save BC call ckno ;do check pop b ;get BC pop d ;restore DE ret ckno: mov a,m ;get char cpi 1 ;no name? rnz lxi h,noname ;pt to no name mov a,m ;check for definition cpi 1 ;no name? rnz xchg ;HL pts to file name call ermsg db 'File Name? ',0 lhld ibuf ;pt to input buffer mvi a,0ffh ;capitalize input call bline ;get line from user call sksp ;skip spaces xchg lhld menufcb ;pt to dummy FCB xchg call zprsfn ;parse file name into FCB inx d ;pt to first char lxi h,noname ;pt to name buffer xchg mvi b,11 ;copy into buffer call moveb ret ;HL pts to name ; ; Pt to File Name whose Number (1-4) is in A ; ptfn: mov b,a ;get number in B call getfn2 ;pt to file name 2 push d ;save DE mov a,b ;file 0? ora a brz ptfnx lxi d,11 ;size of file name and type ptfn1: dad d ;pt to next bjnz ptfn1 ptfnx: pop d ;restore DE ret ; ; Put File Name pted to by HL ; putn: mvi b,8 ;8 chars br putc ; ; Put File Type pted to by HL ; putt: mvi b,3 ;3 chars ; ; Copy Chars from HL to DE for up to B bytes -- flush if space ; putc: mov a,m ;get next char cpi ' ' ;skip spaces brz putc1 stax d ;put next char inx d ;pt to next putc1: inx h ;pt to next bjnz putc ret ; ; Get File Number (1 to 4) ; If valid number, return with value in A and HL pting to next char ; If not valid, return with Z and HL pting to last char (F, N, T) ; getfnum: mov a,m ;get char sui '1' ;convert brc getfne ;error cpi 4 ;range? brnc getfne inx h ;pt to next char ret ;NZ from CPI 4 getfne: dcx h ;error return xra a ret ; ; Return Number of Lines on CRT in A ; getnlines: push h ;save HL call getcrt ;get CRT info inx h ;pt to number of lines mov a,m ;get count pop h ;restore HL sui EPSLINE+1 ;subtract number of lines in file display ; ... + 1 for footer ret ; ; Convert char string pted to by HL into decimal number in A ; On Entry, HL pts to first digit char ; On Exit, HL pts to after last digit char and A=number ; eval: push b ;save BC mvi b,0 ;set value eval1: mov a,m ;get digit sui '0' ;convert to binary brc eval2 cpi 10 ;range? brnc eval2 inx h ;pt to next digit mov c,a ;new digit in C mov a,b ;multiply B by 10 add a ;*2 add a ;*4 add b ;*5 add a ;*10 add c ;add in new digit mov b,a ;result in B br eval1 eval2: mov a,b ;result in A pop b ;restore ptr ret ; ; Compute Address of Buffer for Menu Load ; menustrt: lhld ringend ;get address of buffer for menu load inr h ;next page mvi l,0 ret ; ; S T O R A G E ; ; Initialized ; FILERCMD: VMNAME ;VMENU Name VMNFILL ;Filler DB ' ' ;one space DB 0 ;end of shell command JOKER: DB '???????????' ;*.* equivalent MENUFILE: db 'MENU ' db 'VMN' ; ; Uninitialized ; STACK: DS 2 BUFFER: DS 2 ;buffer start CURAT: DS 2 ;current cursor position ERMFLG: DS 1 ;error message flag EXPLINE: DS 2 ;buffer to expand line in H$DR: DS 1 ;home drive H$U$A: DS 1 ;home user area (must follow H$DR) IBUF: DS 2 ;input line buffer LOCBEG: DS 2 ;local beginning of ring LOCEND: DS 2 ;local end of ring LOCPOS: DS 2 ;local ring position (temp) MENUFCB: DS 2 ;FCB for Menu File NONAME: DS 11 ;dummy user-defined file name RING: DS 2 ;ptr to beginning of ring RINGI: DS 2 ;ring sort pointer RINGJ: DS 2 ;another ring sort pointer RINGEND: DS 2 ;current ring end pointer RINGPOS: DS 2 ;current ring position in scan SCURAT: DS 2 ;save cursor position SRINGPOS: DS 2 ;save ring position ; ; Menu Buffers ; more: ds 1 ;More Files Flag optstrt: ds 2 ;Address of First Option in Current Menu mstart: ds 2 ;Address of First Menu cstart: ds 2 ;Address of Current Menu nmenfl: ds 1 ;Next Menu Available Flag (0=No) menuno: ds 1 ;Number of Menu pagcnt: ds 1 ;Paging Counter cpmok: ds 1 ;OK to Return to ZCPR3 (0=No) END