;
;*****************************************************************************
;
;	This program provides a table based command line monitor accessable to a
;	user via an ascii terminal (9600,8,n,1) connected to USART1 or 
;	accessable via interprocessor communication over the i2c bus.
;
; All PICos source files are intended to be viewed with tabs set to 4 spaces.
;
; Input is echoed back to the USART and accumulated in a buffer one character 
;  at a time. Each command line of text is delivered to the command processor
;  Cmd when it is terminated by a CR character. The file uart1.asm contains
;  the user I/O utilities.
;
; Input is also accumulated by the i2c slave peripheral. The first byte
;  received is the sending devices i2c slave address and the next byte is a
;  count of the bytes to follow. Once the transmission is complete the buffer
;  is submitted to Cmd just as if it had been entered by a user.
;
; Each command line is passed to a command processor which matches it against 
;  the commands listed in a program memory table. Each table entry contains
;  a format string to match the command against, a function address to involke 
;  if the string matches and a string describing the command. The table begins 
;  at the address CmdMenu and the entry for each command is added using a block
;  of directives at the beginning of the function for that command. Therefore
;  the source for the function and the command table entry are all coded
;  together in one source location which can even be in another file. If so
;  this file must be included. If a function provides a non null output
;  string this string is submitted back to the command processor at the source
;  which provided the command, i.e. If the command was entered locally by a
;  user via the usart then the result string is resubmitted to the local Cmd.
;  If the command was received from the i2c slave then the result string is
;  trasnmitted back to the sending device to be executed there. Typically
;  the function executed by a result string is u1: which transmits the string
;  parameter via the local usart providing output to the user including
;  redrawing the command prompt.
;
; NOTE:	CR terminates command input buffer
;	0 terminates string parameter overwriting CR
;	LF terminating output string causes ui: to redisplay cmd line prompt
; Therefore strings output by functions must end in \n\r since \r is replaced
;	with a 0 by Cmd when parsing the string parameter for u1: and the remaining
;	\n causes u1: to redraw the prompt.
;
; Revision history:
;	John E. Andrews
Version	equ	0x0104	; machine readable version 1.04
;	Oct 17th 1998	ver 1.04	- Qualcomm Hardware Test Platform
;	fix EE byte read and write, add register and bit read and write
;	Mar 22nd 1998	ver 1.03	- ESC East Chicago
;	I2C remote command execution and response protocol
;	Mar 13th 1998	ver 1.02	- '756 workshop San Diego
;	Modular CmdMenu table entry definition along with function source
;	Feb 13th 1998	ver 1.01	- Disti FAE certification San Diego
;	Modular peripheral isr bit test macro InstallIsr
;	Feb 7th 1998	ver 1.00
;	Initial command monitor
;
; Needed Improvements:
;	1) port to MPLINK (use relocatable object modules)
;	2) elliminate buffer copy w/ string parameters in Cmd, especially for u1:
;	use pointer to string in cmdPrmBuff, leave string were it is?
;	2.1) string parameters containing CR screw up the parameter copy
;	2.1.1) s param copy should be to next format string char not CR
;	2.2) Cmd buffer management is weak overall, need system strategy
;	3) make cmd line parameters compatible with C17 auto input variables
;	4) make command line of CR only reexecute last cmd entered
;	5) eeprom routines need to be converted to byte count based binary
;	6) major error (nack) detection needed in i2c, even before arbitration
;	7) add interprocess cmd ready flag like rxRdy and i2cRxRdy elim return cmd?
;	8) StartTx doesn't handle special characters. Need a subroutine called by
;	UART1Tx isr and StartTx called U1TxByte. (rename UART1Tx to U1TxIsr)
;	9) Interactive user I/O while command is running
;
;*****************************************************************************
;
	; specify processor, default constant radix, spaces/tab, and width
	list	p=17C756,r=dec,b=4,c=132
	#include	<p17C756.inc>	; include processor specific declarations
	; specify microcontroller mode, WDT off, Brown out on, external clock
	__CONFIG _MC_MODE & _WDT_OFF & _BODEN_ON & _EC_OSC
	; don't produce the following listed messages and warnings
	errorlevel	-207, -302, -305
	;
	; Suppressed Warnings
	; 207 Found label after column 1.
	; 	A label was found after column one, which is often due to a
	; 	misspelled opcode.
	;
	; Suppressed Messages
	; 302 Register in operand not in bank 0. 
	;	Ensure that bank bits are correct.
	; 	Register address was specified by a value that included the 
	;	bank bits. For example, RAM locations in the PIC16CXX are 
	;	specified with 7 bits in the instruction and one or two 
	;	bank bits.
	; 305 Using default destination of 1 (file).
	; 	If no destination bit is specified, the default is used.
;
;*****************************************************************************
;	Reset Vector
;*****************************************************************************
;
	org	0		; reset vector location
	goto	Start	; goto beginning of execution after reset
;
;*****************************************************************************
;	Peripheral Interrupt Vector
;*****************************************************************************
;
	org 0x20
	; ***** Variable and symbol declarations for peripheral int *****
	cblock	0x1A		; declare unbanked variables
	ALUSTA_S		; context save variables for isr
	BSR_S
	WREG_S
	PCLATH_S
	FSR0_S
	FSR1_S			; last unbanked location
	endc
	; ***** Executable code for peripheral int *****
	; save context
	movfp	ALUSTA, ALUSTA_S	; save ALUSTA
	movfp	BSR, BSR_S		; save BSR
	movfp	WREG, WREG_S		; save WREG
	movfp	PCLATH, PCLATH_S	; save PCLATH
	movfp	FSR0, FSR0_S		; save FSR0
	movfp	FSR1, FSR1_S		; save FSR1
	; 
	; All interrupt flag tests and the jumps to the associated isr 
	;  functions are installed here via usage of the InstallISR macro.
	;
	; init the MPASM variable to the current assembly time PC value
	CurIsrTstAdr = $
	;
	;**********************************************************************
InstallISR	macro	IFRegBank, IFReg, IF
	;
	; IFRegBank	- sfr bank containing register with interrupt flag
	; IFReg	- register address containing interrupt flag bit
	; IF	- high active interrupt flag bit
	;
	; This macro allows installation at assembly time of isr functions
	;  at any source code location. This permits source code for the isr
	;  and the bit testing that occurs at the processors interrupt vector, 
	;  and determines which isr to involke, to be located with the source 
	;  code for other associated functions, even in other files. When MPASM
	;  assembles the source the org statements cause the executable to be 
	;  placed at the correct locations.
	;
	; This macro must be used immediately following the label at the 
	;  beginning of the isr function and prior to any executable code. 
	;
	; Note: This is only a macro definition, code is generated where the 
	;  macro is used at the beginning of the isr function.
	;**********************************************************************
	;
	InlinePC = $			; save current inline assembly PC value
	org CurIsrTstAdr		; set assembly PC to addr for new isr test
	movlb	IFRegBank		; switch to the sfr bank containing the reg
	btfsc	IFReg, IF		; skip if the int flag in its reg is clear
	btfss	IFReg+1, IF		; IF is set, skip if IE is set in next reg
	goto	$+3			; jump to test next installed int flag
	call	InlinePC		; int is active so call isr function 
	goto	ExitInt			; then goto restore context and exit int
	CurIsrTstAdr = $		; set current tst addr to next entry
	org InlinePC			; begin isr code gen at inline address
	endm				; end of isr install macro
	;
	; InstallISR is composed of 6 instructions. This org allows room for 
	; 10 interrupts to have service routines installed.
	org $ + 60
	;
ExitInt	; restore context and exit interrupt
	movfp	FSR1_S, FSR1		; FSR1
	movfp	FSR0_S, FSR0		; FSR0
	movfp	PCLATH_S, PCLATH	; restore PCLATH
	movfp	WREG_S, WREG		; restore WREG
	movfp	BSR_S, BSR		; restore BSR
	movfp	ALUSTA_S, ALUSTA	; restore ALUSTA
	retfie				; return from int
	;
; **** end of peripheral interrupt processing ****
;
;*****************************************************************************
;	Included code begins here after isr return
;*****************************************************************************
;
	; utility and driver files included here
	include "oututil.asm"		; output string generation utilities
	include	"uart1.asm"		; uart1 isr and init code

	CurCmdMenuAdr = CmdMenu		; starting addr for CmdMenu entries
					; Note: must be before files are included

	; ***** Note: Include files here to add commands to PICos ****************
	include "stdcmd.asm"		; standard PICos commands
	include "capcmd.asm"		; capture commands
	include "a2dcmd.asm"		; a/d commands
	include "pwmcmd.asm"		; pwm commands
	include "i2ccmd.asm"		; i2c commands
	include "lcd.asm"		; lcd module utilities
;
;*****************************************************************************
;	Entry Point from Reset Vector
;*****************************************************************************
;
Start	; start execution here after reset
	;
	call	InitLCD			; init lcd flag byte
	;
	call	InitU1			; init USART1 
	;
	call	InitI2C			; init I2C state var
	;
	; init peripheral and global interrupts
	bcf	INTSTA, PEIF		; init periph int flag
	bsf	INTSTA, PEIE		; enable periph ints
	bcf	CPUSTA, GLINTD		; enable global ints
	;
	; init portd as debug LED outputs displaying i2c slave address
	movlb	1			; select SFR bank for PORTD
	clrf	DDRD			; set to all outputs
	movlw	DfltSlvAddr		; load default i2c slave addr into W
	movwf	PORTD			; display on portd
	;
	; preload rxBuffer w/ null command to gen first prompt
	movlw	'\r'			; load CR char
	movwf	rxBuffer		;  into uart1 Rx buffer
	bsf	u1Flags, RxRdy		; set bit to tell wait loop to process
	;
	;**********************************************************************
	; Main loop of command monitor
	;**********************************************************************
	;
Wt4Cmd	; wait here for next cmd line from uart1 or i2c slave
	btfsc	u1Flags, RxRdy		; skip if no new UART1 data buffer ready
	call	U1Rdy			; otherwise uart1 has cmd buffer ready
	btfsc	i2cFlags, i2cRxRdy	; skip if no new i2c data buffer ready
	call	I2CRdy			; otherwise i2c has cmd buffer ready
	goto	Wt4Cmd			; retest until input is ready
	;
U1Rdy	; a locally entered cmd line is ready from uart1
	movlw	rxBuffer		; load cmd buffer addr into W
	call	Cmd			; process cmd line
	; output string is returned in cmdOutBuff
	movlw	cmdOutBuff		; load addr of output buffer into W
	tstfsz	cmdOutBuff		; skip if output buffer is null
	goto	$-3			; otherwise resubmit output to Cmd
	; reset USART1 Rx buffer pointers
	movlw	rxBuffer-1		; load prestart of Rx buffer
	movwf	rxPtr			;  into Rx buffer pointer
	bsf	u1Flags, RstRxPtr	; tell isr to reset IntRx pointer
	bcf	u1Flags, RxRdy		; clear data ready flag
	return				; return to wait for next command
	;
I2CRdy	; a new cmd line is ready from i2c
	bcf	i2cFlags, i2cRxRdy	; clear flag: no new i2c data buffer ready
	movlw	i2cRxBuffer		; load cmd buffer addr into W
	call	Cmd			; process cmd line
	; output string is returned in cmdOutBuff
	movlw	cmdOutBuff		; load start of output buffer into W
	tstfsz	cmdOutBuff		; skip if output buffer is null
	call	KickI2CRpy		; otherwise start int based reply on i2c
	return				; return to wait for next command
	;
	;**********************************************************************
Cmd	; Command Processor
	;**********************************************************************
	;
	; Parse and execute received cmd based on format strings stored in
	;  program memory table at location CmdMenu. The received cmd buffer 
	;  pointer is passed in as a parameter in W. The cmd format strings 
	;  specify the text and input parameters that are matched against 
	;  the characters in the cmd buffer. If a cmd line is identified
	;  by a format string then execution is redirected to the function 
	;  address which is stored after the format string in each CmdMenu 
	;  table entry. Input parameters are converted from ascii as 
	;  decimal or hexidecimal integers or as strings and passed to the 
	;  cmd functions in the command parameter buffer: cmdPrmBuff. Each 
	;  cmd function generates an output string in the buffer starting at
	;  address cmdOutBuff. During command parsing FSR0 is used to point
	;  into the command string buffer and FSR1 points into the parameter
	;  buffer.
	;
	; ***** Variable and symbol declarations for command processor *****
	; 
	cmdPrmBuffSize	equ 30		; size of buffer for command parameters
	cmdOutBuffSize	equ 40		; size of buffer for command output
	;
	cblock
	cmdPrmC				; cmd parameter digit count
cmdPrmBuff:
	cmdPrmBuffSize			; cmd parameter buffer
	cmdTblChar			; CmdMenu table value
	cmdBuffPtr			; head of cmd buffer provided as input in W
	cmdFlags			; flags for cmd proccessor
cmdOutBuff:
	cmdOutBuffSize+10		; cmd function output buffer
	cmdOutPtr			; ptr to current location in output buff
	testaddr			; dummy to show address of end of used ram
	endc
	;
	; bit flag definitions for cmdFlags
	CmdByte	equ	0		; last cmd byte from TABLAT was hi or lo
	DataByte	equ	1	; last data byte from TABLAT was hi or lo
	Hundreds	equ 2		; number > 100 in decimal to ascii conv
	;
	; ***** Executable code for command processor *****
	;

; support lcd command line display here?
;	call	Cmd2LCD			; display new cmd line on LCD

	; Parse and execute cmd line
	movwf	FSR0			; load cmd buffer addr into FSR0
	movwf	cmdBuffPtr		; save cmd buffer start in cmdBuffPtr
	movlw	cmdPrmBuff		; load cmd parameter buffer addr
	movwf	FSR1			; into FSR1
	movlw	high(CmdMenu)		; load upper byte of menu addr
	movwf	TBLPTRH			; place it in the table pointer
	movlw	low(CmdMenu)		; load lower byte of menu addr
	movwf	TBLPTRL			; place it in the table pointer
	tablrd	0, 1, WREG		; perform dummy read to init TABLAT
	bcf	cmdFlags, CmdByte	; init CmdByte flag causing hi read first
	;
RdTbl	; FSR0 points to cmd char, read next format string char from CmdMenu
	btfss	cmdFlags, CmdByte	; if last table byte read was hi then skip
	tlrd	1, cmdTblChar		; otherwise fetch upper byte
	btfsc	cmdFlags, CmdByte	; if last table byte read was lo then skip
	tablrd	0, 1, cmdTblChar	; otherwise fetch lower byte 
	btg	cmdFlags, CmdByte	; toggle bit indicating hi or lo byte read
	;
	; analyze the format string and compare with each cmd char
	;
	; test for 0 termination of CmdMenu
	tstfsz	cmdTblChar		; skip if 0 at end of CmdMenu was read
	goto	NotCmdZ			; otherwise not at end
	goto	UnCmd			; end of format strings with no match
NotCmdZ	; if here valid format string char is available
	;
	; test for format string indicating cmd termination by carriage return
	movlw	0x0D			; load CR character
	cpfseq	cmdTblChar		; skip if carriage return is indicated
	goto	NotCmdC			; otherwise not a carriage return
	cpfseq	INDF0			; skip if cmd char is CR
	goto	SkpCmd			; CR not found, advance past this menu cmd
	; cmd has been matched with format string, execute function 
	btfsc	cmdFlags, CmdByte	; if last table byte read was lo then skip
	tablrd	0, 1, cmdTblChar	; otherwise update TABLAT and skip 0 pad
	; init output buffer to cause u1: to display new prompt after cmd
	movlw	cmdOutBuff		; load start of output buffer
	movwf	FSR1			;  into FSR1
	movlw	'u'			; load ascii u
	movwf	INDF1			;  into buffer
	incf	FSR1			; point to next location
	movlw	'1'			; load ascii 1
	movwf	INDF1			;  into buffer
	incf	FSR1			; point to next location
	movlw	':'			; load ascii :
	movwf	INDF1			;  into buffer
	incf	FSR1			; point to next location
	movlw	'\n'			; load ascii LF
	movwf	INDF1			;  into buffer
	movpf	FSR1, cmdOutPtr		; save current location in output pointer
	incf	FSR1			; point to next location
	movlw	'\r'			; load ascii CR into last location in buff
	movwf	INDF1			;  CR terminates cmd line when resubmited
	; fetch command function address pointer from CmdMenu table and vector
	tlrd	1, PCLATH		; fetch upper byte of pointer into PCLATH
	tlrd	0, PCL			; fetch lower byte into PCL causing jump
NotCmdC	; if here format string char is not a carriage return
	;
	; test for format string indicating string parameter
	movlw	's'			; load string parameter indicating char
	cpfseq	cmdTblChar		; skip if string parameter indicated
	goto	NotPrmS			; otherwise not a string parameter
	movlw	0x0D			; load CR character into W
NxtPrmS	movfp	INDF0, INDF1		; move char from cmd into parameter 
	cpfseq	INDF1			; skip if last parameter is CR
	goto	PrmSc			; CR not found, copy next char
	; CR has terminated string parameter copy
	clrf	INDF1			; replace CR with 0 termination
	incf	FSR1			; point to next parameter addr
	goto	RdTbl			; evaluate next format string char
PrmSc	; prepare to copy next char
	incf	FSR0			; point to next cmd char
	incf	FSR1			; point to next parameter addr
	goto	NxtPrmS			; copy next char
NotPrmS	; if here format string char does not indicate a string parameter
	;
	; test for format string indicating decimal parameter
	movlw	'n'			; load decimal parameter indicating char
	cpfseq	cmdTblChar		; skip if decimal parameter indicated
	goto	NotPrmN			; otherwise not a decimal parameter
	clrf	cmdPrmC			; clear parameter digit count
	clrf	INDF1			; init current parameter
GetPrmN	movlw	'0'-1			; load ascii 0 - 1
	cpfsgt	INDF0			; skip if cmd char is >= ascii 0
	goto	EndPrmN			; otherwise determine if param was read
	movlw	'9'+1			; load ascii 9 + 1
	cpfslt	INDF0			; skip if cmd char is <= ascii 9
	goto	EndPrmN			; otherwise determine if param was read
	; cmd char is a valid decimal digit
	incf	cmdPrmC			; increment parameter digit count
	movlw	10			; load 10
	mulwf	INDF1			; multiply by current parameter value
	movfp	PRODL, INDF1		; update current parameter with x10 value
	movlw	0x0F			; load lower nibble mask
	andwf	INDF0, W		; mask new cmd param digit into W
	addwf	INDF1			; add to current parameter
	incf	FSR0			; point to next cmd char
	goto	GetPrmN			; see if still a parameter digit
EndPrmN	; current cmd char is not a decimal digit
	tstfsz	cmdPrmC			; if param digit count is zero then skip
	goto	$+2			; param was read, move to next cmd char
	goto	SkpCmd			; nothing read, advance past this menu cmd
	incf	FSR1			; point to next parameter addr
	goto	RdTbl			; evaluate next format string char
NotPrmN	; if here format string char does not indicate a decimal parameter
	;
	; test for format string indicating hexidecimal parameter
	movlw	'x'			; load hexidecimal param indicating char
	cpfseq	cmdTblChar		; skip if hexidecimal parameter indicated
	goto	NotPrmX			; otherwise not a hexidecimal parameter
	clrf	cmdPrmC			; clear parameter digit count
	clrf	INDF1			; init current parameter
GetPrmX	movlw	'0'-1			; load ascii 0 - 1
	cpfsgt	INDF0			; skip if cmd char is >= ascii 0
	goto	EndPrmX			; otherwise determine if param was read
	movlw	'9'+1			; load ascii 9 + 1
	cpfslt	INDF0			; skip if cmd char is <= ascii 9
	goto	PrmXA			; otherwise check for upper case alpha
	movlw	0x0F			; load lower nibble mask
	andwf	INDF0, W		; mask new cmd param digit into W
	goto	VldPrmX			; char is a valid hexidecimal digit
PrmXA	movlw	'A'-1			; load ascii A - 1
	cpfsgt	INDF0			; skip if cmd char is >= ascii A
	goto	EndPrmX			; otherwise determine if param was read
	movlw	'F'+1			; load ascii F + 1
	cpfslt	INDF0			; skip if cmd char is <= ascii F
	goto	PrmXa			; otherwise check for lower case alpha
	movlw	0x0F			; load lower nibble mask
	andwf	INDF0, W		; mask new cmd param digit into W
	addlw	9			; adjust to correct numeric value
	goto	VldPrmX			; char is a valid hexidecimal digit
PrmXa	movlw	'a'-1			; load ascii a - 1
	cpfsgt	INDF0			; skip if cmd char is >= ascii a
	goto	EndPrmX			; otherwise determine if param was read
	movlw	'f'+1			; load ascii f + 1
	cpfslt	INDF0			; skip if cmd char is <= ascii f
	goto	EndPrmX			; otherwise determine if param was read
	movlw	0x0F			; load lower nibble mask
	andwf	INDF0, W		; mask new cmd param digit into W
	addlw	9			; adjust to correct numeric value
	; fall through to valid hexidecimal digit
VldPrmX	; valid hexidecimal value is in W
	incf	cmdPrmC			; increment parameter digit count
	bcf	INDF1, 7		; clear upper nibble
	bcf	INDF1, 6
	bcf	INDF1, 5
	bcf	INDF1, 4
	swapf	INDF1			; multiply current parameter value by 16
	addwf	INDF1			; add new value to current parameter
	incf	FSR0			; point to next cmd char
	goto	GetPrmX			; see if still a parameter digit
EndPrmX	; current cmd char is not a hexidecimal digit
	tstfsz	cmdPrmC			; if param digit count is zero then skip
	goto	$+2			; param was read, move to next cmd char
	goto	SkpCmd			; nothing read, advance past this menu cmd
	incf	FSR1			; point to next parameter addr
	goto	RdTbl			; evaluate next format string char
NotPrmX	; if here format string char does not indicate a decimal parameter
	;
	; test for alphabetic format string char, automatically capitalize cmd
	movlw	'A'-1			; load ascii A - 1
	cpfsgt	cmdTblChar		; skip if format string char is >= A
	goto	NotCmdA			; otherwise not an alphabetic char
	movlw	'Z'+1			; load an ascii Z + 1
	cpfslt	cmdTblChar		; skip if format string char <= Z
	goto	NotCmdA			; otherwise not an alphabetic char
	movfp	INDF0, WREG		; alphabetic, load cmd char into W
	bcf	WREG, 5			; capitalize cmd buffer char
	cpfseq	cmdTblChar		; skip if cmd char equals format string
	goto	SkpCmd			; no match, advance past this menu cmd
	; current cmd char matches alphabetic format string char
	incf	FSR0			; point to next cmd char
	goto	RdTbl			; evaluate next format string char
NotCmdA	; if here format string char is not alphabetic
	;
	; char is not alphabetic, parametric or CR so cmd must match exactly
	movfp	INDF0, WREG		; load cmd char into W
	cpfseq	cmdTblChar		; skip if cmd char equals format string
	goto	SkpCmd			; no match, advance past this menu cmd
	; current cmd char matches format string char
	incf	FSR0			; point to next cmd char
	goto	RdTbl			; evaluate next format string char
	;
SkpCmd	; cmd line does not match, advance to next format string
	; test for format string indicating cmd termination by carriage return
	movlw	0x0D			; load CR character
	call	Adv2Mch			; adv thru format string until CR is found
	; current format string char is CR 
	btfsc	cmdFlags, CmdByte	; if last table byte read was lo then skip
	tablrd	0, 1, cmdTblChar	; otherwise update TABLAT and skip 0 pad
	tablrd	0, 1, WREG		; flush cmd pointer from TABLAT
	; cmd function pointer is flushed, TABLAT contains start of description
	tlrd	1, cmdTblChar		; read first byte of command description
	bsf	cmdFlags, CmdByte	; set flag to cause lo byte read first
	movlw	0x0A			; load LF character
	call	Adv2Mch			; adv thru descrip string until LF is found
	; current desription string char is LF
	btfsc	cmdFlags, CmdByte	; if last table byte read was lo then skip
	tablrd	0, 1, cmdTblChar	; otherwise update TABLAT and skip 0 pad
	bcf	cmdFlags, CmdByte	; clear flag to cause hi byte read first
	movfp	cmdBuffPtr, FSR0	; reload cmd buffer addr into FSR0
	movlw	cmdPrmBuff		; reload start of parameter buffer
	movwf	FSR1			; into FSR1
	goto	RdTbl			; analyze new format string
	;
Adv2Mch	; advance thru table entry until char in W is found
	cpfseq	cmdTblChar		; skip if carriage return is indicated
	goto	$+2			; otherwise get next table character
	return				; if CR then return
	btfss	cmdFlags, CmdByte	; if last table byte read was hi then skip
	tlrd	1, cmdTblChar		; otherwise fetch upper byte 
	btfsc	cmdFlags, CmdByte	; if last table byte read was lo then skip
	tablrd	0, 1, cmdTblChar	; otherwise fetch lower byte 
	btg	cmdFlags, CmdByte	; toggle bit indicating hi or lo byte read
	goto	Adv2Mch			; check new format string char for match
	;
UnCmd	; end of format string entries was reached without matching the cmd
	movlw	cmdOutBuff		; load start of output buffer
	movwf	cmdOutPtr		;  into output pointer
	; copy result string into output buffer using FSR0
	CpyTbl2Out	UnCmdD		; copy in unknown command string
	return				; return from Cmd
	; This is the end of the functions executable code
	;
	; These data statements store constant ascii output strings in program 
	;  memory. They're accessed using the CpyTbl2Out macro.
UnCmdD	; constant string for unknown command
	data	"u1:\nUnknown Command\n\r",0
	;
	;**********************************************************************
	; Location of lookup table defining all commands available to Cmd
	org 0x1000	; hardcode table start address to 1000 hex
	;**********************************************************************
CmdMenu	; Cmd line menu
	;**********************************************************************
	; 
	; All cmd format strings, descriptions and the jumps to the associated 
	;  functions are installed here via directives at the beginning of each
	;  command functions source file. The following directives are used:
	;
;	CmdPC = $			; save current inline assembly PC value
;	org CurCmdMenuAdr		; set assembly PC to addr for new entry
;	data	"CmdFormatString", CmdPC, "CmdDescription"	; CmdMenu table entry
;	CurCmdMenuAdr = $		; set current CmdMenu addr for next entry
;	org CmdPC			; begin function code gen at inline address
	;
	; CmdFormatString	- format string defining syntax of command
	; CmdDescription	- string with < 40 char description of command
	;
	; CurCmdMenuAdr, the current entry address as each entry is added to 
	;  the table, is initialized to CmdMenu, the beginning of the table, 
	;  early in this file before the command source files are included.
	;
	; When MPASM assembles the source the first org statement causes the 
	;  strings and function pointer to be placed in the CmdMenu lookup 
	;  table after any previously installed commands, The second org 
	;  returns to the previous program memory address for generation of
	;  command functions executable code.
	; The data statement that defines each entry includes a cmd format 
	;  string, a cmd function pointer and a command description string. 
	;  These three items together comprise one entry in the cmd menu table
	;  which defines all of the commands available to the cmd processor.
	;  The table is terminated by a 0 were a format string should start. 
	;  This 0 is added by a data staement following these comments.
	; Each format string is comprised of the characters of the cmd, all 
	;  in upper case, and the input parameters of the function indicated 
	;  by the lower case n, x, and s characters. An n indicates a decimal 
	;  integer 0-255, x indicates a hexidecimal integer from 0-FF, and s 
	;  indicates a string parameter comprised of all the remaininng 
	;  characters from the cmd line and a 0 termination. 
	; The decimal and hex input parameters are converted by Cmd from ascii
	;  text in the cmd line input buffer into numerical values in the 
	;  parameter buffer were they are available to the command function. 
	; The format string in each CmdMenu table entry is terminated by a \r 
	;  carriage return character and is automatically padded by MPASM to 
	;  fill whole words. Care must be taken in the ordering of entries 
	;  since some input parameters are supersets of others.
	;
	; These directives must be used immediately following the label at 
	;  the beginning of the cmd function and prior to any executable code.
	;  They allow installation at assembly time of an entry into the
	;  CmdMenu lookup table from any source code location. This permits 
	;  source code for the function, which is executed when the command is
	;  matched; the format string that the command processor matches the 
	;  command against; and a string describing the command, to all be 
	;  in one source location. Therfore addition of commands to the 
	;  command processor is modular with all necessary source located in 
	;  one file together. Therefore no changes are required to the central
	;  command processor source code other than including the command file.
	;
	; Examples of the use of these directives and of receiving input 
	;  parameters from the cmdPrmBuff and generating output strings into
	;  the cmdOutBuff are given in "stdcmd.asm" the command definition file
	;  for standard PICos commands.
	;
	; Add terminating 0 to end of entire command list
	org CurCmdMenuAdr		; set assembly PC to addr for new entry
	data	0			; add table terminating zero
	;
	;**********************************************************************
	; Note: this macro doesn't work since no space or \ are allowed in text
	;       substitution and are required as part of the format string.
	;**********************************************************************
InstallCmd	macro	CmdFormatString, CmdDescription
	CmdPC = $			; save current inline assembly PC value
	org CurCmdMenuAdr		; set assembly PC to addr for new entry
	data	"CmdFormatString", CmdPC, "CmdDescription"	; CmdMenu table entry
	CurCmdMenuAdr = $		; set current CmdMenu addr for next entry
	data	0			; add table terminating zero
	org CmdPC			; begin cmd code gen at inline address
	endm				; end of cmd install macro

	end	; MPASM stops assembling here