; M4CMD/ASM ; ; Jumping to this location will cause the return address on the ; stack to be incremented by 3, and then jumped to. This is used ; in several places to make error handling easier. Code using ; this mechanism might look like. ; ; ROUTINE: EQU $ ; ... ; CALL SPACK ; JP ABORT ;Die on an error ; ... ;Continue normally ; ; RET ; SPACK: EQU $ ; ... ; LD A,B ;Check result ; CP C ;Must be equal ; RET NZ ;Error if not equal ; LD A,(LEN) ;Get the length for return ; JP RSKP ;Normal return ; RSKP POP HL ;GET THE RETURN ADDRESS. INC HL ;INCREMENT BY THREE. INC HL INC HL JP (HL) ;Return to return+3 bytes ; ; Output the value in HL as an ASCII decimal string ; NOUT EQU $ PUSH HL ;Save the registers PUSH BC PUSH DE LD DE,NBUFF ;Get the string buffer PUSH DE ;Save the address CALL XHEXDEC ;Convert from binary to ASCII EX DE,HL ;HL = end of buffer + 1 LD (HL),EOS ;Add EOS for printing POP HL ;Restore the starting address LD A,' ' ;Remove leading spaces NOUT1 IFANOT (HL),NOUT2 ;Go if not blank INC HL ;Point to next character JR NOUT1 ;Back to top of loop NOUT2 EX DE,HL ;DE is now start of string to print CALL PRTSTR ;Print the number POP DE ;Restore the registers POP BC POP HL RET ; ; ; Command parsing routines ; ; This routine prints the prompt pointed to by DE, and then ; sets up the appropriate values to allow a reparse at any point ; PROMPT POP HL ;Get the return address PUSH HL ;Put it back LD (CMRPRS),HL ;Save it as the reparse address LD (CMOSTP),SP ;Save the stack pointer as well LD (CMPRMP),DE ;Save the prompt to print LD HL,CMDBUF ;Get the start of the command buffer LD (CMCPTR),HL ;Initialize the pointer into it LD (CMDPTR),HL ;Save 2 copies XOR A LD (CMAFLG),A ;Zero the flags LD (CMCCNT),A ;No characters CPL ;Make it non zero LD (CMSFLG),A ;Set these flags LD A,(TAKFLG) ;Check if take is active IFZ PRMT10 ;Jump if not LD A,(TAKLOG) ;Is the take-file display flag set? IFZ PRMT20 ;Jump if not PRMT10 CALL NEWLIN ;Get a newline LD DE,(CMPRMP) ;Print the prompt CALL PRTSTR PRMT20 RET ;Return to the caller ; ; Come to here to initiate a reparse ; REPARS LD SP,(CMOSTP) ;GET THE OLD STACK POINTER. LD HL,CMDBUF LD (CMDPTR),HL LD A,0FFH ;TRY IT THIS WAY (DAPHNE.) LD (CMSFLG),A LD HL,(CMRPRS) ;GET THE REPARSE ADDRESS. JP (HL) ;GO THERE. ; ;THIS ADDRESS CAN BE JUMPED TO ON A PARSING ERROR. ; PRSERR LD SP,(CMOSTP) ;GET THE OLD STACK POINTER. LD HL,CMDBUF LD (CMCPTR),HL ;INITIALIZE THE COMMAND POINTER. LD (CMDPTR),HL CALL NEWLIN XOR A LD (CMAFLG),A ;ZERO THE FLAGS. LD (CMCCNT),A LD A,0FFH ;TRY IT THIS WAY (DAPHNE.) LD (CMSFLG),A LD DE,(CMPRMP) ;GET THE PROMPT. CALL PRTSTR LD HL,(CMRPRS) JP (HL) ; ;This routine parses the specified function in A. Any additional ;information is in DE and HL. ; Returns to RETURN+3 on success ; Returns to RETURN on failure. (Assumes that a JP follows CALL) ; COMND LD (CMSTAT),A ;Save what we are presently parsing. CALL CMINBF ;Get chars until action or erase char. CP CMNUM ;Is the function "PARSE a number"? JP Z,CMDNUM ;Jump if so CP CMCFM ;Parse a confirm? JP Z,CMCFRM ;Jump if so CP CMKEY ;Parse a keyword from a table? JP Z,CMKEYW ;Jump if so CP CMIFI ;Parse a file spec? JP Z,CMIFIL ;If so jump CP CMIFIN ;Other file type? JP Z,CMIFIL ;If so use same routine CP CMOFI ;ditto JP Z,CMIFIL CP CMTXT ;Parse a text string? JP Z,CMTEXT ;If so jump LD DE,CMER00 ;Otherwise parser calling error CALL PRTSTR ;So print a message RET ;And return error ; ;This routine parses arbitrary text up to a ; ; DE=address of text buffer ; ; A=number of characters typed (zero or more) on return ; CMTEXT EX DE,HL ;Put the pointer to the buffer in HL LD (CMPTAB),HL ;Save the pointer LD B,0 ;Initialize the count to zero CMTXT1 CALL CMGTCH ;Get a character OR A ;Test the high bit for some terminator JP P,CMTXT5 ;If not then jump AND 7FH ;Turn off the high bit CP ESC ;Is it escape RET Z ;Return failure if so CMTXT2 IFA '?',CMTXT7 ;Jump if the user needs help IFA ' ',CMTXT5 ;If blank, add it to text LD A,B ;Get the counter LD HL,(CMPTAB) ;Get the updated pointer LD (HL),CR ;Put the terminator in EX DE,HL ;Move ending pointer to DE JP RSKP ;Return success ; CMTXT3 LD HL,CMAFLG ;Point to the action flag LD (HL),0 ;Reset it CMTXT5 INC B ;Add one to the count of characters CMTXT6 LD HL,(CMPTAB) ;Get the pointer PUTHL A ;Add the character and increment LD (CMPTAB),HL ;Save the update pointer JR CMTXT1 ;Go get another character ; CMTXT7 LD DE,TXTHLP ;Get the help message CALL REPRNT ;Print the message JP REPARS ;Jump to the reparse ; ;This routine parses an input number in ASCII decimal ; CMDNUM LD B,0 ;Reset the character count LD HL,0 ;Initialize the value to zero LD (THEVAL),HL CMNM10 CALL CMGTCH ;Get a character OR A ;Check for high bit set terminator JP P,CMNM50 ;Jump if not AND 7FH ;Trim the high bit CP ESC ;Is it ESCAPE (abort) RET Z ;Return error if so CMNM20 IFA '?',CMNM70 ;Go if the user needs help LD A,B ;Get the count LD DE,(THEVAL) ;Get the number found JP RSKP ;Return success ; CMNM50 INC B ;Add one to count of characters PUSH HL ;Save the values PUSH DE PUSH BC LD HL,(THEVAL) ;Get the current number LD C,10 ;Multiply by 10 PUSH AF ;Save AF too CALL XMUL16 ;Multiply 8 bit by 16 bit LD H,L ;Move the 24 bit result into HL as 16 LD L,A POP AF ;Get the character to add SUB 48 ;Convert to a binary number JP P,CMNM60 ;Jump if no underflow CMNM55 POP BC ;Restore the regs POP DE POP HL LD DE,ERMES2 ;Print error message CALL PRTSTR JP KERMIT ;GET A NEW COMMAND ; CMNM60 IFAGE 10,CMNM55 ;Jump if too big LD C,A ;Get it into BC for 16 bit MATH LD B,0 ;Zero the MSB ADD HL,BC ;Compute the new number LD (THEVAL),HL ;Save the result POP BC ;Restore the registers POP DE POP HL JR CMNM10 ;Loop on ; CMNM70 LD DE,NUMHLP ;Get the HELP message CALL REPRNT ;Print the message, and reprint prompt JP REPARS ;Plus the rest of the text, and restart ; ; Get a confirmation of the command by accepting only ; CMCFRM CALL CMGTCH ;GET A CHARACTER FROM THE BUFFER OR A ;WHAT WAS IT, CONTROL? RET P ;NOPE, SO EXIT VIA ERROR RETURN AND 7FH ;STRIP THE SIGN BIT FLAG IFANOT '?',CMCFR3 ;Go if not help request LD DE,CMIN00 ;TELL THEM NO MORE HELP CALL REPRNT ;PRINT THE MESSAGE JP REPARS ;PRINT THE MESSAGE AND THE PROMPT AGAIN CMCFR3 CP ESC ;IS IT ABORT? RET Z ;TAKE ERROR EXIT IF SO JP RSKP ;TAKE NORMAL RETURN ;THIS ROUTINE PRINTS THE MESSAGE IN DE AND SETS UP FOR A REPARSE REPRNT CALL PRTSTR XOR A LD (CMAFLG),A CALL NEWLIN LD DE,(CMPRMP) CALL PRTSTR LD HL,(CMCPTR) DEC HL LD (HL),EOS LD (CMCPTR),HL LD DE,CMDBUF CALL PRTSTR RET ;THIS ROUTINE PARSES A KEYWORD FROM THE TABLE POINTED ;TO IN DE. THE FORMAT OF THE TABLE IS AS FOLLOWS ; ;ADDR DB N Where N is the number of entries in the table ; DB K Where K is 2+length of longest keyword. ; Repeated for each entry in the table... ; DB M Where M is the length of the keyword ; DB 'STRING',EOS Where string is the KEYWORD. ; DB A,B Where A & B are pieces of DATA ; to be returned, (Must be two bytes worth) ; ;THE KEYWORDS MUST BE IN ALPHABETICAL ORDER. ;**** NOTE THE DATA VALUE A IS RETURNED IN REGISTERS A AND E. THE ;**** DATA VALUE B IS RETURNED IN REGISTER D. THIS ALLOWS THE TWO DATA ;BYTES TO BE STORED AS ;DW XXX ;AND RESULT IN A CORRECTLY FORMATTED 16-BIT VALUE IN REGISTER PAIR ;DE. CMKEYW LD (CMPTAB),DE ;SAVE THE BEGINNING OF KEYWORD for ? LD A,(DE) ;GET THE NUMBER OF ENTRIES IN THE TABLE. LD B,A ;SAVE IN B INC DE ;Point past the keyword count INC DE ;POINT PAST THE MAX LENGTH NUMBER LD (CMKPTR),DE ;Save it for later LD HL,(CMDPTR) ;Save the command buffer pointer LD (CMSPTR),HL CMKEY2 LD A,B ;Get the keyword counter OR A ;ANY LEFT? RET Z ;IF NOT WE FAILED. LD HL,(CMKPTR) ;Get the current keyword pointer INC HL ;Skip the visibility LD E,(HL) ;Get the length of the keyword INC HL ;Skip the length CMKEY3 DEC E ;DECREMENT THE NUMBER OF CHARS LEFT. LD A,E CP -1 JP M,CMKEY5 ;IF SO GO TO THE NEXT. CALL CMGTCH ;GET A CHAR. OR A ;IS IT A TERMINATER? JP P,CMKEY4 ;IF POSITIVE, IT IS NOT. AND 7FH ;TURN OFF THE MINUS BIT. CP '?' ;Is this help? JP NZ,CMKY35 PUSH HL ;SAVE HL FOR A SEC PUSH DE XOR A LD (CMAFLG),A ;TURN OFF THE ACTION FLAG. LD DE,HLPMES ;PRINT ONE OF THE FOLLOWING... CALL PRTSTR LD HL,CMCCNT ;DECREMENT THE CHAR COUNT. DEC (HL) POP DE POP HL LD HL,(CMPTAB) ;GET THE START OF THE KEYWORD TABLE LD B,(HL) ;B IS HOW MANY IN THE TABLE INC HL ;Point at the column spacing value LD A,(HL) ;Get the length LD (MAXLEN),A ;Save it for later XOR A LD (CURCOL),A ;Set column to starting column INC HL ;Point at the visible attribute CM1010 LD A,(HL) ;Get the visibility LD (VISIBLE),A INC HL ;POINT AT THE FIRST ENTRY LD C,(HL) ;C IS HOW MANY CHARACTERS IN NAME LD A,C ;SAVE THE LENGTH FOR LATER LD (CURLEN),A INC HL ;POINT AT THE TEXT FOLLOWING LD (CMKPTR),HL ;SAVE THE ADDRESS TO PRINT FROM ON MATCH LD DE,(CMSPTR) ;GET THE ADDRESS OF THE TYPED KEYWORD CM1020 LD A,(DE) ;GET A CHARACTER IFA '?',CM1040 ;Go if request for help CALL CAPTAL ;MAKE SURE LETTERS ARE UPPER CASE INC DE ;POINT TO THE NEXT. CP (HL) ;SAME AS IN KEYWORD TABLE? INC HL ;POINT TO THE NEXT JR NZ,CM1050 ;JUMP IF NO MATCH DEC C ;ONE LESS CHARACTER IN THE KEYWORD JP P,CM1020 LD A,(DE) IFA '?',CM1040 ;Jump if help request CP 0 ;Set flags to P,NZ JP CM1050 ;Join other code CM1040 EQU $ LD A,(VISIBLE) ;Is this a visible command? IFZ CM1045 ;Jump if it is not PUSH DE ;SAVE THE REGS PUSH HL PUSH BC LD DE,(CMKPTR) ;Get the string CALL STRLEN ;Get length into BC LD A,(MAXLEN) ;Get the padded length LD B,A ;Save it for now LD A,(CURCOL) ;Get current screen column ADD A,B ;Compute new column LD B,A ;Save it LD A,(MAXCOL) ;Get right margin IFALT B,CM1042 ;Are we passed the edge? Jump if so LD A,B ;Get new column LD (CURCOL),A ;Save it LD A,(MAXLEN) JR CM1043 ;Join code CM1042 CALL NEWLIN ;Print a newline LD A,(MAXLEN) ;Get the padded length LD (CURCOL),A ;Set new position CM1043 SUB C ;Compute blanks to print LD C,A ;Put it into C PUSH BC ;Save count for now LD DE,(CMKPTR) ;Get the string to print CALL PRTSTR ;Print the keyword POP BC ;Restore count CM1044 LD A,' ' ;Get a blank CALL CONOUT ;Display it DEC C ;Decrement counter JR NZ,CM1044 ;Jump if not there POP BC ;RESTORE THE REGS POP HL POP DE CM1045 LD A,3 ;SKIP OVER THE EOS AND THE DISCRIPTOR ADD A,C ;PLUS THE CHARACTERS LEFT IN THE STRING LD E,A ;PUT IT IN DE TO ADD LD D,0 ;MAKE IT A BYTE VALUE IN 16 BITS ADD HL,DE ;GOT THE NEW ADDRESS DJNZ CM1010 ;GET THE NEXT JR CM1190 ;END OF THE TABLE CM1050 DEC HL ;CORRECT HL FROM LAST INCREMENT JP P,CM1045 ;IF (TABLE) > (COMMAND) KEEP LOOKING JR Z,CM1045 XOR A ;RESET THE ACTION FLAG LD (CMAFLG),A CM1190 CALL NEWLIN ;PRINT A NEW LINE CM1200 CALL NEWLIN ;PRINT A NEW LINE LD DE,(CMPRMP) ;GET THE PROMPT TO REPRINT CALL PRTSTR ;PRINT IT LD HL,(CMDPTR) ;GET THE END OF THE COMMAND LINE LD (HL),EOS ;TERMINATOR FOR PRINTING LD HL,(CMCPTR) ;GET THE LAST CHARACTER DEC HL LD (CMCPTR),HL ;IGNORE THE '?' AT THE END LD DE,CMDBUF ;GET THE START OF THE BUFFER CALL PRTSTR ;PRINT THE COMMAND LINE JP REPARS ;REPARSE THE ENTIRE LINE CMKY35 CP ESC RET Z PUSH HL PUSH DE CALL CMAMBG JP CMKY36 LD HL,(CMCPTR) ;GET THE END OF THE COMMAND LD BC,CMDBUF ;GET THE START OF THE BUFFER OR A ;RESET THE CARRY SBC HL,BC ;COMPUTE THE OFFSET LD DE,CMER01 CALL PRTSTR ;SAY ITS AMBIGUOUS. JP PRSERR ;GIVE UP. CMKY36 POP DE POP HL CMKY37 INC E ;ADD ONE IN CASE IT IS NEGATIVE. LD D,0 ADD HL,DE ;INCREMENT PAST THE KEYWORD. INC HL ;PAST THE EOS. LD E,(HL) ;GET THE DATA. INC HL LD D,(HL) LD A,E JP RSKP CMKEY4 CALL CAPTAL ;MAKE IT UPPER CASE IF LOWER CMKY41 CP (HL) ;Check the next character JR NZ,CMKEY5 INC HL JP CMKEY3 CMKEY5 LD D,0 LD A,E ;GET THE NUMBER OF CHARS LEFT. OR A ;IS IT NEGATIVE? JP P,CMKY51 LD D,0FFH CMKY51 EQU $ ADD HL,DE ;INCREMENT PAST THE KEYWORD. INC HL ;PLUS 4 INC HL INC HL INC HL LD (CMKPTR),HL DEC B ;DECREMENT THE NUMBER OF ENTRIES LEFT. LD HL,(CMSPTR) ;GET THE OLD CMDPTR. LD (CMDPTR),HL ;RESTORE IT. JP CMKEY2 ;GO CHECK THE NEXT KEYWORD. ;CONVERT CONTENTS OF A TO UPPER CASE IF IT IS LOWER CAPTAL IFALT 'a',CAPS10 IFAGE 'z'+1,CAPS10 AND 137O ;MAKE IT UPPER CASE CAPS10 RET ;RETURN TO THE CALLER ;CHECK AMBIGUITY OF A COMMAND CMAMBG DEC B ;DECREMENT THE NUMBER OF ENTRIES LEFT. RET M ;IF NONE LEFT THEN IT IS NOT AMBIGUOUS. INC E ;THIS IS OFF BY ONE;ADJUST. LD C,E ;SAVE THE CHAR COUNT. LD A,E OR A ;ANY CHARS LEFT? RET Z ;NO, IT CAN'T BE AMBIGUOUS. LD D,0 ADD HL,DE ;INCREMENT PAST THE KEYWORD. LD E,4 ;PLUS THE EOS AND DATA. ADD HL,DE LD B,(HL) ;GET THE LENGTH OF THE KEYWORD. INC HL EX DE,HL LD HL,(CMKPTR) ;GET POINTER TO KEYWORD ENTRY. INC HL LD A,(HL) ;GET THE LENGTH OF THE KEYWORD. SUB C ;SUBTRACT HOW MANY LEFT. LD C,A ;SAVE THE COUNT. IFA B,CMAMB0 RET P ;IF LARGER THAN THE NEW WORD THEN NOT AMB CMAMB0 LD HL,(CMSPTR) ;GET THE POINTER TO WHAT PARSED. CMAMB1 DEC C ;DECREMENT THE COUNT. JP M,RSKP ;IF WE ARE DONE THEN IT IS AMBIGUOUS. EX DE,HL ;EXCHANGE THE POINTERS. LD B,(HL) ;GET THE NEXT CHAR OF THE KEYWORD INC HL EX DE,HL ;EXCHANGE THE POINTERS. LD A,(HL) ;GET THE NEXT PARSED CHAR. INC HL CALL CAPTAL ;MAKE IT UPPER IF LOWER CMAMB2 CP B ;ARE THEY EQUAL? RET NZ ;IF NOT THEN ITS NOT AMBIGUOUS. JP CMAMB1 ;CHECK THE NEXT CHAR. ; ; Parse a file specification. This includes a call to @FSPEC to ; do case conversion, and any other necessary stuff to make a ; legal file spec. On normal return, A has the count of characters ; that are in the passed buffer ; CMIFIL LD (CMFCB),DE ;SAVE WHERE TO PUT THE CHARACTERS LD DE,CLBUF LD B,0 ;Set the count to zero CMIFI1 CALL CMGTCH ;GET A CHARACTER OR A ;CHECK FOR A CONTROL CHARACTER ?,CR,ESC JP P,CMIFI3 ;GO IF NOT CONTROL AND 7FH ;STRIP THE HIGH BIT CP ESC ;WAS IT ABORT? RET Z ;TAKE THE ERROR EXIT IFANOT '?',CMIFI4 ;Go if not help request LD DE,FILHLP ;PRINT A MESSAGE CALL REPRNT ;SET UP FOR REPARSE JP REPARS ;GET A NEW CHARACTER CMIFI3 LD (DE),A ;STORE THE CHARACTER INC DE ;POINT TO NEXT POS INC B ;INCREMENT CHARACTER COUNT JR CMIFI1 ;GET ANOTHER ONE CMIFI4 LD A,CR ;Get the end of name marker LD (DE),A ;Put in a terminator LD A,B ;Get the count IFZ CMIFI5 ;Skip fspec if no characters given PUSH HL ;Save the pointer LD HL,CLBUF ;GET THE TEXT TO FSPEC LD DE,(CMFCB) ;WHERE TO PUT THE RESULT CALL XFSPEC ;MAKE IT A FILE SPEC JP NZ,CMIFI6 ;Oops, bad fspec EX DE,HL ;Move start to HL LD A,3 ;Get the character to find LD BC,40 ;Get the maximum distance to look CPIR ;Find it LD HL,39 ;Find out how far we looked OR A ;Reset the carry SBC HL,BC ;Compute the distance LD B,L ;Get the length POP HL ;Restore pointer which is... CMIFI5 LD (CMDPTR),HL ;Next place to put characters at LD A,B ;Copy the length to A JP RSKP ;Return normal ; CMIFI6 POP HL ;Restore the stack JP XERROR0 ;Print a system message and return ; ; Get input characters from the keyboard, up to an action character ; The actual character input is retrieved via GETSTR(). ; CMINBF PUSH AF PUSH DE PUSH HL LD A,(CMAFLG) ;IS THE ACTION CHAR FLAG SET? IFNZ CMINB9 ;Go if it is LD HL,(CMCPTR) ;Get the position PUSH HL ;Save it for later LD DE,CMDBUF ;Get EOB OR A ;Reset carry SBC HL,DE ;Compute number of characters typed in LD B,L ;Get number of characters POP HL ;Get the value back CALL GETSTR ;Input up to an action character JP C,PRSERR ;Jump if user pressed break LD A,B ;SAVE THE COUNT LD (CMCCNT),A LD C,B ;GET THE NUMBER OF CHARACTERS IN BUFFER LD B,0 LD HL,CMDBUF ;Get the start PUSH HL ;Save it ADD HL,BC ;Add the count LD (CMCPTR),HL ;Save next input position POP BC ;Get the start OR A ;Reset the carry SBC HL,BC ;Are there any characters in the buffer? JP Z,PRSERR ;IF NO CHARACTERS START OVER CMINB6 LD A,0FFH ;SET THE ACTION FLAG. LD (CMAFLG),A CMINB9 POP HL ;Restore the registers POP DE POP AF RET ;Return ; ; Get a character from the command input buffer. If an action ; character is found, then the MSB of the character will be set ; CMGTCH PUSH HL PUSH BC CMGTC1 LD A,(CMAFLG) OR A ;IS IT SET. CALL Z,CMINBF ;IS THE ACTION CHAR FLAG SET? LD HL,(CMDPTR) ;GET A POINTER INTO THE BUFFER. LD A,(HL) ;GET THE NEXT CHAR. INC HL LD (CMDPTR),HL IFA ' ',CMGTC2 IFANOT TAB,CMGTC3 CMGTC2 LD A,(CMSFLG) ;GET THE SPACE FLAG. IFNZ CMGTC1 ;Was last char a space? LD A,0FFH ;SET THE SPACE FLAG. LD (CMSFLG),A LD A,' ' POP BC POP HL JR CMGTC5 CMGTC3 PUSH AF XOR A LD (CMSFLG),A ;ZERO THE SPACE FLAG. POP AF POP BC POP HL IFA ESC,CMGTC5 ;Go if escape abort IFA '?',CMGTC4 ;Go answer a help request IFA CR,CMGTC4 CP LF RET NZ ;NOT AN ACTION CHAR, JUST RETURN. CMGTC4 PUSH HL LD HL,(CMDPTR) DEC HL LD (CMDPTR),HL POP HL CMGTC5 OR 80H ;MAKE THE CHAR NEGATIVE TO INDICATE IT IS RET ;A TERMINATOR. STRLEN EQU $ PUSH AF PUSH DE LD BC,0 STRLEN_1 EQU $ LD A,(DE) IFA EOS,STRLEN_2 INC DE INC BC JR STRLEN_1 STRLEN_2 EQU $ POP DE POP AF RET ;end of file