please dont rip this site

Parallax SX Embedded Controller Instruction Set

The SX instruction set is PIC 16x54 compatible with a few additions....

Use Al Williams Microchip-style mnemonics (cached 20000731) for PIC coding in the SXKey.

Use sxdefs.inc from Richard Ottosen for Scenix coding in MPLAB then program the Hex file to the SX using just about any SX Programmer

Also:

See also:

SX Instruction set table:

Instruction Cycles Flags     Affects Refs Description Details Microchip Menomics
byte-oriented operations
MOV W,#lit 1 - W lit Move literal into W ( W = lit ) Users Manual p103 MOVLW lit
MOV W,fr 1 Z W fr Move fr into W ( W = fr ) Users Manual p95 MOVF fr,0
MOV fr,W 1 - fr W Move W into fr ( fr = W ) Users Manual p89 MOVWF fr
MOV fr,#lit 2 - W fr lit Move literal into fr ( fr = lit ) See: mov W, #lit; mov fr, W MOVLW lit; MOVWF fr
MOV fr1,fr2 2 Z W fr1 fr2 Move fr2 into fr1 ( fr1 = fr2 ) See: mov W, fr2; mov fr1, W MOVF fr2,0; MOVWF fr1
ADD W,fr 1 C DC Z W fr Add fr into W ( W += fr ) Users Manual p70 ADDWF fr,0
ADD fr,W 1 C DC Z fr W Add W into fr ( fr += W ) Users Manual p69 ADDWF fr,1
ADD fr,#lit 2 C DC Z W fr lit Add literal into fr ( fr += W = lit ) See: mov W, #lit; add fr, W MOVLW lit; ADDWF fr,1
ADD fr1,fr2 2 C DC Z W fr1 fr2 Add fr2 into fr1 ( fr1 += W = fr2 ) See: mov W, fr2; add fr1, W MOVF fr2,0; ADDWF fr1,1
MOV W,fr-W 1 C DC Z W fr Move fr - W into W ( W -= fr ) Users Manual p97 SUBWF fr,0
SUB fr,W 1 C DC Z fr W Subtract W from fr ( fr -= W ) Users Manual p124 SUBWF fr,1
SUB fr,#lit 2 C DC Z W fr lit Subtract lit from fr ( fr -= W = lit ) See: mov W, #lit; sub fr, W MOVLW lit; SUBWF fr,1
SUB fr1,fr2 2 C DC Z W fr1 fr2 Subtract fr2 from fr1 ( fr1 -= W = fr2 ) See: mov W, fr2; sub fr1, W MOVF fr2,0; SUBWF fr1,1
AND W,#lit 1 Z W lit AND literal into W ( W &= lit ) Users Manual p73 ANDLW lit
AND W,fr 1 Z W fr AND fr into W ( W &= fr ) Users Manual p72 ANDWF fr,0
AND fr,W 1 Z fr W AND W into fr ( fr &= W ) Users Manual p71 ANDWF fr,1
AND fr,#lit 2 Z W fr lit AND literal into fr ( fr &= W = lit ) See: mov W, #lit; and fr, W MOVLW lit; ANDWF fr,1
AND fr1,fr2 2 Z W fr1 fr2 AND fr2 into fr1 ( fr1 &= W = fr2 ) See: mov W, fr2; and fr, W MOVF fr2,0; ANDWF fr,1
OR W,#lit 1 Z W lit OR literal into W ( W |= lit ) Users Manual p111 IORLW lit
OR W,fr 1 Z W fr OR fr into W ( W |= fr ) Users Manual p110 IORWF fr,0
OR fr,W 1 Z fr W OR W into fr ( fr |= W ) Users Manual p109 IORWF fr,1
OR fr,#lit 2 Z W fr lit OR literal into fr ( fr |= W = lit ) See: mov W, #lit; or  fr, W MOVLW lit; IORWF fr,1
OR fr1,fr2 2 Z W fr1 fr2 OR fr2 into fr1 ( fr1 |= W = fr2 ) See: mov W, fr2; or  fr1, W MOVF fr2,0; IORWF fr1,1
XOR W,#lit 1 Z W lit XOR literal into W ( W ^= lit ) Users Manual p130 XORLW lit
XOR W,fr 1 Z W fr XOR fr into W ( W ^= fr ) Users Manual p129 XORWF fr,0
XOR fr,W 1 Z fr W XOR W into fr ( fr ^= W ) Users Manual p128 XORWF fr,1
XOR fr,#lit 2 Z W fr lit XOR literal into fr ( fr ^= W = lit ) See: mov W, #lit; xor fr, W MOVLW lit; XORWF fr,1
XOR fr1,fr2 2 Z W fr1 fr2 XOR fr2 into fr1 ( fr1 ^= W = fr2 ) See: mov W, fr2; xor fr1, W MOVF fr2,0; XORWF fr1,1
CLR W 1 Z W - Clear W ( W = 0 ) Users Manual p79 CLRW
CLR fr 1 Z fr - Clear fr ( fr = 0 ) Users Manual p78 CLRF fr
MOV W,++fr 1 Z W fr Move fr + 1 into W ( W = 1 + fr ) Users Manual p99 INCF fr,0
INC fr 1 Z fr fr Increment fr ( fr = 1 + fr ) Users Manual p84 INCF fr,1
MOV W,--fr 1 Z W fr Move fr - 1 into W ( W = -1 + fr ) Users Manual p98 DECF fr,0
DEC fr 1 Z fr fr Decrement fr ( fr = -1 + fr ) Users Manual p82 DECF fr,1
MOV W,<FR 1 C W fr Move left-rotated fr into W ( W = C + fr << 1 fr ) Users Manual p100 RLF fr,0
RL fr 1 C fr fr Rotate left fr ( fr = C + fr << 1 fr ) Users Manual p118 RLF fr,1
MOV W,>>fr 1 C W fr Move right-rotated fr into W ( W = C * 128 + fr >> 1 fr ) Users Manual p101 RRF fr,0
RR fr 1 C fr fr Rotate right fr ( fr = C * 128 + fr >> 1 fr ) Users Manual p119 RRF fr,1
MOV W,<>fr 1 - W fr Move nibble-swapped fr into W ( W = (( fr & 0xF0 ) >> 4 ) | (( fr & 0x0F ) << 4 ) fr ) Users Manual p102 SWAPF fr,0
SWAP fr 1 - fr fr Swap nibbles in fr ( fr = (( fr & 0xF0 ) >> 4 ) | (( fr & 0x0F ) << 4 ) fr ) Users Manual p126 SWAPF fr,1
NOT W 1 Z W W Perform not on W ( W = 0xFF ^ W ) See: xor w,#$FF XORLW 0FFh
MOV W,/fr 1 Z W fr Move not'd fr into W ( W = 0xFF ^ fr ) Users Manual p96 COMF fr,0
NOT fr 1 Z fr fr Perform not on fr ( fr = 0xFF ^ fr ) Users Manual p108 COMF fr,1
TEST W 1 Z W W Test W for zero ( W = 0 | W ) See: or W,#lit IORLW 0
TEST fr 1 Z fr fr Test fr for zero ( fr = 0 | fr ) Users Manual p127 MOVF fr,1
TSTN w 1 Z W W Test W for $FF ( W ) See: xor W,#$FF XORLW 0FFh
TSTN fr 1 Z fr fr Test fr for $FF ( fr ) See: mov W,/fr COMF fr,1
"Secret" instructions
PushW 1 ? Wstack W Push W to the "secret" W stack Secrets: DW $048
PopW 1 ? W Wstack Pop W from the "secret" W stack Secrets: DW $04C
PushSTAT 1 ? STATstack W Push W to the "secret" Status stack Secrets: DW $049
PopSTAT 1 ? W STATstack Pop Status from the "secret" W stack Secrets: DW $04D
PushFSR 1 ? FSRstack W Push W to the "secret" FSR stack Secrets: DW $04A
PopFSR 1 ? W FSRstack Pop W from the "secret" FSR stack Secrets: DW $04E
bit-oriented operations
CLRB bit 1 - fr bit fr Clear bit ( fr,bit = !( 1 << bit ) & fr ) Users Manual p81 BCF bit
CLC 1 C - - Clear carry ( - ) See: CLRB bit BCF 3,0
CLZ 1 Z - - Clear zero ( - ) See: CLRB bit BCF 3,2
SETB bit 1 - fr bit fr Set bit ( fr,bit = ( 1 << bit ) | fr ) Users Manual p121 BSF bit
STC 1 C - - Set carry ( - ) See: setb 3.0 BSF 3,0
STZ 1 Z - - Set zero ( - ) See: setb 3.2 BSF 3,2
CC 2 C, DC Status Status Complement Carry Macro: clrb 3.1; incsz 3 BCF 3,1; INCFSZ 3,1
ADDB fr,bit 2 Z fr bit Add bit into fr ( fr += bit ) See: snb bit; inc fr BTFSC bit; INCF fr,1
ADDB fr,/bit 2 Z fr bit Add not bit into fr ( fr += ! bit ) See: sb  bit; inc fr BTFSS bit; INCF fr,1
SUBB fr,bit 2 Z fr bit Subtract bit from fr ( fr -= bit ) See: snb bit; dec fr BTFSC bit; DECF fr,1
SUBB fr,/bit 2 Z fr bit Subtract not bit from fr ( fr -= ! bit ) See: sb  bit; dec fr BTFSS bit; DECF fr,1
MOVB bit1,bit2 4 - bit1 bit2 Move bit2 into bit1 ( bit1 = bit2 ) See: sb  bit2; clrb bit1; snb bit2; setb bit1 BTFSS bit2; BCF bit1; BTFSC bit2; BSF bit1 (doesn't work)
MOVB bit1,/bit2 4 - bit1 bit2 Move not bit2 into bit1 ( bit1 = ! bit2 ) See: snb bit2; clrb bit1; sb  bit2; setb bit1 BTFSC bit2; BCF bit1; BTFSS bit2; BSF bit1 (doesn't work)
inc/dec-conditional branches
MOVSZ W,++fr 1 - W fr Move fr + 1 into W, skip if zero ( W = 1 + fr ) Users Manual p106 INCFSZ fr,0
INCSZ fr 1 - fr PC fr Increment fr , skip if zero ( ++ fr == 0 ? PC++ ) Users Manual p85 INCFSZ fr,1
IJNZ fr,addr 2 * - fr PC fr Increment fr , jump if not zero ( ++ fr == 0 ? PC = addr ) See: incsz fr; jmp addr INCFSZ fr,1; GOTO addr
MOVSZ W,--fr 1 - W PC fr Move fr - 1 into W, skip if zero ( ( W = --fr ) == 0 ? PC++ ) Users Manual p105 DECFSZ fr,0
DECSZ fr 1 - fr PC fr Decrement fr , skip if zero ( -- fr == 0 ? PC++ ) Users Manual p83 DECFSZ fr,1
DJNZ fr,addr 2 * - fr PC fr Decrement fr , jump if not zero ( -- fr == 0 ? PC = addr ) See: decsz fr; jmp addr DECFSZ fr,1; GOTO addr
compare-conditional branches (see also: Program Flow Methods - Comparing values)
CSE fr,#lit 3 C DC Z W PC fr lit Compare, skip if equal ( ( W = lit - fr ) == 0 ? PC++ ) See: mov W, #lit; mov W, fr-w; sb 3.2 MOVLW lit; SUBWF fr,0; BTFSS 3,2
CSE fr1,fr2 3 C DC Z W PC fr1 fr2 Compare, skip if equal ( ( W = fr1 - fr2 ) == 0 ? PC++ ) See: mov W, fr2; mov W, fr1-w; sb 3.2 MOVF fr2,0; SUBWF fr1,0; BTFSS 3,2
CSNE fr,#lit 3 C DC Z W PC fr lit Compare, skip if not equal ( ( W = lit - fr ) != 0 ? PC++ ) See: mov W, #lit; mov W, fr-w; snb 3.2 MOVLW lit; SUBWF fr,0; BTFSC 3,2
CSNE fr1,fr2 3 C DC Z W PC fr1 fr2 Compare, skip if not equal ( ( W = fr1 - fr2 ) != 0 ? PC++ ) See: mov W, fr2; mov W, fr1-w; snb 3.2 MOVF fr2,0; SUBWF fr1,0; BTFSC 3,2
CSA fr,#lit 3 C DC Z W PC fr lit Compare, skip if above ( ( W = lit - fr ) < 0 ? PC++ ) See: mov W, #/lit; add W, fr; sb 3.0 MOVLW /lit; ADDWF fr,0; BTFSS 3,0
CSA fr1,fr2 3 C DC Z W PC fr1 fr2 Compare, skip if above ( ( W = fr1 - fr2 ) < 0 ? PC++ ) See: mov W, fr1; mov W, fr2-w; snb 3.0 MOVF fr1,0; SUBWF fr2,0; BTFSC 3,0
CSAE fr,#lit 3 C DC Z W PC fr lit Compare, skip if above or equal ( ( W = lit - fr ) <= 0 ? PC++ ) See: mov W, #lit; mov W, fr-w; sb 3.0 MOVLW lit; SUBWF fr,0; BTFSS 3,0
CSAE fr1,fr2 3 C DC Z W PC fr1 fr2 Compare, skip if above or equal ( ( W = fr1 - fr2 ) <= 0 ? PC++ ) See: mov W, fr2; mov W, fr1-w; sb 3.0 MOVF fr2,0; SUBWF fr1,0; BTFSS 3,0
CSB fr,#lit 3 C DC Z W PC fr lit Compare, skip if below ( ( W = lit - fr ) > 0 ? PC++ ) See: mov W, #lit; mov W, fr-w; snb 3.0 MOVLW lit; SUBWF fr,0; BTFSC 3,0
CSB fr1,fr2 3 C DC Z W PC fr1 fr2 Compare, skip if below ( ( W = fr1 - fr2 ) > 0 ? PC++ ) See: mov W, fr2; mov W, fr1-w; snb 3.0 MOVF fr2,0; SUBWF fr1,0; BTFSC 3,0
CSBE fr,#lit 3 C DC Z W PC fr lit Compare, skip if below or equal ( ( W = lit - fr ) >= 0 ? PC++ ) See: mov W, #/lit; add W, fr; snb 3.0 MOVLW /lit; ADDWF fr,0; BTFSC 3,0
CSBE fr1,fr2 3 C DC Z W PC fr1 fr2 Compare, skip if below or equal ( ( W = fr1 - fr2 ) >= 0 ? PC++ ) See: mov W, fr1; mov W, fr2-w; sb 3.0 MOVF fr1,0; SUBWF fr2,0; BTFSS 3,0
bit-conditional branches
CJE fr,#lit,addr 4 * C DC Z W PC fr lit Compare, jump if equal ( ( W = lit - fr ) != 0 ? PC = addr ) See: mov W, #lit; mov W, fr-w; snb 3.2; jmp addr MOVLW lit; SUBWF fr,0; BTFSC 3,2; GOTO addr
CJE fr1,fr2,addr 4 * C DC Z W PC fr1 fr2 Compare, jump if equal ( ( W = fr1 - fr2 ) != 0 ? PC = addr ) See: mov W, fr2; mov W, fr1-w; snb 3.2; jmp addr MOVF fr2,0; SUBWF fr1,0; BTFSC 3,2; GOTO addr
CJNE fr,#lit,addr 4 * C DC Z W PC fr lit Compare, jump if not equal ( ( W = lit - fr ) == 0 ? PC = addr ) See: mov W, #lit; mov W, fr-w; sb 3.2; jmp addr MOVLW lit; SUBWF fr,0; BTFSS 3,2; GOTO addr
CJNE fr1,fr2,addr 4 * C DC Z W PC fr1 fr2 Compare, jump if not equal ( ( W = fr1 - fr2 ) == 0 ? PC = addr ) See: mov W, fr2; mov W, fr1-w; sb 3.2; jmp addr MOVF fr2,0; SUBWF fr1,0; BTFSS 3,2; GOTO addr
CJA fr,#lit,addr 4 * C DC Z W PC fr lit Compare, jump if above ( ( W = lit - fr ) >= 0 ? PC = addr ) See: mov W, #/lit; add W, fr; snb 3.0; jmp addr MOVLW /lit; ADDWF fr,0; BTFSC 3,0; GOTO addr
CJA fr1,fr2,addr 4 * C DC Z W PC fr1 fr2 Compare, jump if above ( ( W = fr1 - fr2 ) >= 0 ? PC = addr ) See: mov W, fr1; mov W, fr2-w; sb 3.0; jmp addr MOVF fr1,0; SUBWF fr2,0; BTFSS 3,0; GOTO addr
CJAE fr,#lit,addr 4 * C DC Z W PC fr lit Compare, jump if above or equal ( ( W = lit - fr ) > 0 ? PC = addr ) See: mov W, #lit; mov W, fr-w; snb 3.0; jmp addr MOVLW lit; SUBWF fr,0; BTFSC 3,0; GOTO addr
CJAE fr1,fr2,addr 4 * C DC Z W PC fr1 fr2 Compare, jump if above or equal ( ( W = fr1 - fr2 ) > 0 ? PC = addr ) See: mov W, fr2; mov W, fr1-w; snb 3.0; jmp addr MOVF fr2,0; SUBWF fr1,0; BTFSC 3,0; GOTO addr
CJB fr,#lit,addr 4 * C DC Z W PC fr lit Compare, jump if below ( ( W = lit - fr ) <= 0 ? PC = addr ) See: mov W, #lit; mov W, fr-w; sb 3.0; jmp addr MOVLW lit; SUBWF fr,0; BTFSS 3,0; GOTO addr
CJB fr1,fr2,addr 4 * C DC Z W PC fr1 fr2 Compare, jump if below ( ( W = fr1 - fr2 ) <= 0 ? PC = addr ) See: mov W, fr2; mov W, fr1-w; sb 3.0; jmp addr MOVF fr2,0; SUBWF fr1,0; BTFSS 3,0; GOTO addr
CJBE fr,#lit,addr 4 * C DC Z W PC fr lit Compare, jump if below or equal ( ( W = lit - fr ) < 0 ? PC = addr ) See: mov W, #/lit; add W, fr; sb 3.0; jmp addr MOVLW /lit; ADDWF fr,0; BTFSS 3,0; GOTO addr
CJBE fr1,fr2,addr 4 * C DC Z W PC fr1 fr2 Compare, jump if below or equal ( ( W = fr1 - fr2 ) < 0 ? PC = addr ) See: mov W, fr1; mov W, fr2-w; snb 3.0; jmp addr MOVF fr1,0; SUBWF fr2,0; BTFSC 3,0; GOTO addr
SB bit 1 - PC bit Skip if bit ( ( fr & ( 1 << bit )) == 1 ? PC++ ) Users Manual p120 BTFSS bit
SC 1 - PC C Skip if carry ( C ) See: sb 3.0 BTFSS 3,0
SZ 1 - PC Z Skip if zero ( Z ) See: sb 3.2 BTFSS 3,2
SNB bit 1 - PC bit Skip if not bit ( ( fr & ( 1 << bit )) == 0 ? PC++ ) Users Manual p123 BTFSC bit
SNC 1 - PC C Skip if not carry ( C ) See: snb 3.0 BTFSC 3,0
SNZ 1 - PC Z Skip if not zero ( Z ) See: snb 3.2 BTFSC 3,2
JB bit,addr 2 * - PC bit Jump TO address if bit ( ( fr & ( 1 << bit )) == 1 ? PC = addr ) See: snb bit; jmp addr BTFSC bit; GOTO addr
JC addr 2 * - PC C Jump TO address if carry ( C ) See: snb 3.0; jmp addr BTFSC 3,0; GOTO addr
JZ addr 2 * - PC Z Jump TO address if zero ( Z ) See: snb 3.2; jmp addr BTFSC 3,2; GOTO addr
JNB bit,addr 2 * - PC bit Jump TO address if not bit ( ( fr & ( 1 << bit )) == 0 ? PC = addr ) See: sb bit; jmp addr BTFSS bit; GOTO addr
JNC addr 2 * - PC C Jump TO address if not carry ( C ) See: sb 3.0; jmp addr BTFSS 3,0; GOTO addr
JNZ addr 2 * - PC Z Jump TO address if not zero ( Z ) See: sb 3.2; jmp addr BTFSS 3,2; GOTO addr
unconditional branches
SKIP 1 - PC - Skip next instruction word ( PC++ ) See: sb 2.0 /snb 2.0 BTFSC/BTFSS 2,0
JMP addr 1 * - PC - Jump TO (9 bit) address ( PC = ( page << 9 ) + addr ) Users Manual p88 GOTO addr
JMP PC+W 1 C DC Z PC W Add W into PC(L), clear bit 8 ( PC = ( PC & 0xFEFF ) + W ) See: add 2, W ADDWF 2,1
JMP W 1 - PC W Move W into PC(L), clear bit 8 ( PC = ( PC & 0xFE00 ) + W ) See: mov 2, W MOVWF 2
CALL addr 1 * - PC - Call TO address, clear bit 8 ( STACK[SP++] = PC; PC = ( page << 9 ) + addr ) Users Manual p76
RETW lit,lit... 1 - W PC lit Return from call, literal in W ( PC = STACK[SP--]; W = lit ) Users Manual p117
RET 1 - PC - Return from call ( PC = STACK[SP--] ) Users Manual p113
RETP 1 PA0..2 PC - Return from call, affect PA2 : PA0 ( PC = STACK[SP--]; page = PC >> 9 ) Users Manual p116
RETI 1 - PC W FSR - Return from interrupt ( PC = STACK[SP--] ) Users Manual p114
RETIW lit 1 - RTCC PC W FSR lit Return from interrupt, compensate RTCC ( PC = STACK[SP--]; RTCC += lit ) Users Manual p115
i/o and control operations
PAGE addr 1 PA0..2 - - Transfer addr .11:addr .9 into PA2 : PA0 , will delay skipping ( page = addr >> 9 ) Users Manual p112
BANK fr 1 - FSR - Transfer fr .7:fr .5 into FSR .7:FSR .5 ( FSR = &( fr ) & 0xE0 ) Users Manual p74
MOV M,#lit 1 - M lit Move literal into M ( M = lit ) Users Manual p90
MOV M,W 1 - M W Move W into M ( M = W ) Users Manual p91
MOV M,fr 2 Z W M fr Move fr into M ( M = W = fr ) See: mov W, fr; mov M, W
MOV W,M 1 - W M Move M into W ( W = M ) Users Manual p104
MOV fr,M 2 - W fr M Move M into fr ( fr = W = M ) See: mov W, M; mov fr, W
MOV !port,W 1 - !PORT W Move W into port's TRIS ( !PORT = W ) Users Manual p93 TRIS port (port=5 to 7)
MOV !port,#lit 2 - W !PORT lit Move literal into port's TRIS ( !PORT = W = lit ) See: mov W, #lit; mov !port,W MOVLW lit; TRIS port (port=5 to 7)
MOV !port,fr 2 Z W !PORT fr Move fr into port's TRIS ( !PORT = W = fr ) See: mov W, fr; mov !port,W MOVF fr,0; TRIS port (port=5 to 7)
MOV !OPTION,W 1 - !OPTION W Move W into !OPTION ( !OPTION = W ) Users Manual p92 OPTION
MOV !OPTION,#lit 2 - W !OPTION lit Move literal into !OPTION ( !OPTION = W = lit ) See: mov W, #lit; mov !OPTION, W MOVLW lit; OPTION
MOV !OPTION,fr 2 Z W !OPTION fr Move fr into !OPTION ( !OPTION = W = fr ) See: mov W, fr; mov !OPTION, W MOVF fr,0; OPTION
CLR !WDT 1 TO PD - - Clear WDT and prescaler ( TO = PD = 0 ) Users Manual p80 CLRWDT
SLEEP 1 TO PD - - Clear WDT and enter sleep mode ( TO = PD = 0 ) Users Manual p112 SLEEP
IREAD 4 - M : W M W Read instruction at M : W into M : W ( M : W = PROGRAM[M<<8+W] ) Users Manual p86
NOP 1 - - - No operation ( - - ) Users Manual p107 NOP
	
There are *12* undocumented instructions!
Four new push instructions that push W onto the W, FSR, STATUS, and PC “shadow registers,” which are actually 2-level stacks; 
There appears to be a secret FIFO for saving and restoring values and a breakpoint register or two.

					L A B E L S

-------------------------------------------------------------------------------------------------------------------------------
	Label					Description
-------------------------------------------------------------------------------------------------------------------------------

	labelname				global label
	:labelname				local label


						O P E R A T O R S

-------------------------------------------------------------------------------------------------------------------------------
	Expression Operator			Description
-------------------------------------------------------------------------------------------------------------------------------

	||					Absolute	Unaries
	+					(no effect)
	-					Negate
	~					Not

	&					And		Binaries
	|					Or
	^					Xor
	+					Add
	-					Subtract
	*					Multiply
	/					Divide
	//					Mod
	<< 					Shift left 
	>>					Shift right (arithmetic)
	><					Reverse bits . Bit Address 
	=< 					Below or equal Conditionals 
	=>					Above or equal
	=					Equal
	<>					Not equal
	<					Below
	>					Above

	(					Begin sub expression
	)					End sub expression

	#					Literal (default radix is decimal)
	$					Hexadecimal (#$ prefixes a hexidecimal literal)
	%					Binary (#% prefixes a binary literal)

						D I R E C T I V E S

-------------------------------------------------------------------------------------------------------------------------------
	Directive				Description
-------------------------------------------------------------------------------------------------------------------------------

	DEVICE	setting,setting...		Establish device settings (should precede other directives/instructions)

	ID	wordvalue			Establish device ID

	RESET	address				Assemble 'jmp address' at last location for reset

label	EQU	value				Equate label to value

	ORG	address				Set origin to address

	DS	locations			Define space: origin=origin+locations

	DW	data,data,...			Define word(s)

	MACRO

	WATCH	Variable{.Bit}, Count, Format	allows File Register Variables to be "WATCH"ed when debugging.

-------------------------------------------------------------------------------------------------------------------------------
Pre-Defined Symbols
-------------------------------------------------------------------------------------------------------------------------------

******** DEVICE Directive Symbols Set bits in the FUSE register

	- used to establish device parameters
	- multiple DEVICE statements allowed to accomodate parameters


    Example:	DEVICE	SX28L, OSCIN, BOR42
		DEVICE	TURBO, STACKX_OPTIONX, CARRYX, PROTECT

SX18				SX18 native mode				(default: SX18)
SX18L				Same as SX18
SX28				SX28 native mode
SX28L				Same as SX28
SX48				SX48 mode
SX52				SX52 mode

OSCHS3				External crystal/resonator - high-speed level 3	(default: OSCHS3)
OSCHS2				External crystal/resonator - high-speed level 2
OSCHS1				External crystal/resonator - high-speed level 1
OSCXT2				External crystal/resonator - standard level 2
OSCXT1				External crystal/resonator - standard level 1
OSCLP2				External crystal/resonator - low-power level 2
OSCLP1				External crystal/resonator - low-power level 1
OSCRC				External RC network
OSC4MHZ				Internal 4MHz oscillator
OSC1MHZ				Internal 1MHz oscillator
OSC128KHZ			Internal 128KHz oscillator
OSC32KHZ			Internal 32KHz oscillator

DRIVEOFF	   (48/52 only)	OSC2 output drive off (use for clock/osc packs)	(default: on)
FEEDBACKOFF			OSC feedback resistor off (for clock/osc packs)	(default: on)
XTLBUFD		   (48/52 only)	Same as DRIVEOFF
IFBD				Same as FEEDBACKOFF

BOR42				Brownout reset at VDD < 4.2V				(default: Brownout off)
BOR26				Brownout reset at VDD < 2.6V
BOR22				Brownout reset at VDD < 2.2V

TURBO				Turbo mode enabled (1:1 execution)		    (default: 1:4 execution)
STACKX_OPTIONX			Stack is 8 levels, OPTION is 8 bits		    (default: Stack is 2 levels, OPTION is 6 bits)
CARRYX				ADD/SUB uses carry flag				    (default: ADD/SUB ignores Carry flag)
SYNC				Input Syncing enabled - 2-clock delay on inputs	    (default: Input Syncing disabled)
SLEEPCLOCK	   (48/52 only)	Enables clock operation during sleep (fast startup) (default: Clock is disabled during sleep)
WATCHDOG			Watchdog Timer enabled				    (default: Watchdog Timer disabled)
PROTECT				Code Protect enabled				    (default: Code Protect disabled)

DRT18MS		   (48/52 only)	Reset timer (18 ms start-up delay after reset)	    (default: 18 ms)
DRT960MS	   (48/52 only)	Reset timer (960 ms start-up delay after reset)
DRT60MS		   (48/52 only)	Reset timer (60 ms start-up delay after reset)
DRT60US		   (48/52 only)	Reset timer (60 us start-up delay after reset)


******** Dynamic Equates (always reflect current values)

%		=	Current REPT index (=0 if outside of a REPT block)
$		=	Current origin


******** Register/Bit Equates

IND			=	$00			Indirect addressing register

RTCC			=	$01			RTCC register
WREG			=	$01			W register

PC			=	$02			Program counter low-byte register

STATUS			=	$03			Status register
C			=	STATUS.0		Carry bit
DC			=	STATUS.1		Digit carry bit
Z			=	STATUS.2		Zero bit
PD			=	STATUS.3		Power-down bit
TO			=	STATUS.4		Time-out bit
PA0			=	STATUS.5		Page preselect bit 0
PA1			=	STATUS.6		Page preselect bit 1
PA2			=	STATUS.7		Page preselect bit 2

FSR			=	$04			File select register

RA			=	$05			RA i/o register
RB			=	$06			RB i/o register
RC			=	$07			RC i/o register
RD			=	$08			RD i/o register  (48/52 only)
RE			=	$09			RE i/o register  (48/52 only)

******** The Equates Below Are For Write Access Only *********
******** On the SX48/52, add $10 to the Equate for read access *******

TIMER_CAPTURE_LOW	=	$00			Low Timer Capture register    (48/52 only)
TIMER_CAPTURE_HIGH	=	$01			High Timer Capture register   (48/52 only)
TIMER_COMPARE2_LOW	=	$02			Low Timer Compare register 2  (48/52 only)
TIMER_COMPARE2_HIGH	=	$03			High Timer Compare register 2 (48/52 only)
TIMER_COMPARE1_LOW	=	$04			Low Timer Compare register 1  (48/52 only)
TIMER_COMPARE1_HIGH	=	$05			High Timer Compare register 1 (48/52 only)
TIMER_CONTROL_B		=	$06			Timer Control register B      (48/52 only)
TIMER_CONTROL_A		=	$07			Timer Control register A      (48/52 only)
CMP   -or- COMPARATOR	=	$08			Comparator register
WKPEN -or- WAKE_PENDING	=	$09			Wake-up Pending register
WKED  -or- WAKE_EDGE	=	$0A			Wake-up Edge register
WKEN  -or- WAKE_ENABLE	=	$0B			Wake-up Enable register
ST    -or- SCHMITT	=	$0C			Schmitt-Trigger register
LVL   -or- LEVEL	=	$0D			Logic Level register
PLP   -or- PULL_UP	=	$0E			Pull-up resister register
TRIS  -or- DIRECTION	=	$0F			Tristate (direction) register



******** Backward-Compatibility Symbols for Parallax PIC16Cxx Assembler (SPASM.EXE)

		DEVICE Directive Symbols

PIC16C54					PIC16C54 emulation using SX18L	(default: SX18L)
PIC16C55					PIC16C55 emulation using SX28L
PIC16C56					PIC16C56 emulation using SX18L
PIC16C57					PIC16C57 emulation using SX28L
PIC16C58					PIC16C58 emulation using SX18L

HS_OSC						OSCHS3				(default: HS_OSC)
XT_OSC						OSCXT2
LP_OSC						OSCLP1
RC_OSC						OSCRC

WDT_OFF						(no equivalent)			(default: WDT_OFF)
WDT_ON						WATCHDOG

PROTECT_OFF					(no equivalent)			(default: PROTECT_OFF)
PROTECT_ON					PROTECT

		Register Equates

INDIRECT	=	$00			Indirect addressing register
INDF		=	$00

TMR0		=	$01			RTCC register

PCL		=	$02			Program counter low-byte register

PORT_A		=	$05			RA i/o register
PORT_B		=	$06			RB i/o register
PORT_C		=	$07			RC i/o register


----------------------------------------------------------------------------------
Hex Format:

Low-byte/high-byte (8-bit) format used - byte counts and addresses are doubled.

$0000-$0FFF	=	CODE words
$1000-$100F	=	ID words (nibble-per-word used to make 8 characters)
$1010		=	FUSE word
$1011		=	FUSEX word


Use these macros to program the SX with a '68HC11 like' instruction set

See:


file: /Techref/scenix/inst.htm, 105KB, , updated: 2013/7/22 18:20, local time: 2025/10/25 11:33,
TOP NEW HELP FIND: 
216.73.216.188,10-3-157-36:LOG IN

 ©2025 These pages are served without commercial sponsorship. (No popup ads, etc...).Bandwidth abuse increases hosting cost forcing sponsorship or shutdown. This server aggressively defends against automated copying for any reason including offline viewing, duplication, etc... Please respect this requirement and DO NOT RIP THIS SITE. Questions?
Please DO link to this page! Digg it! / MAKE!

<A HREF="http://ecomorder.com/techref/scenix/inst.htm"> Parallax SX, Embedded Controller, Microcontroller programming</A>

After you find an appropriate page, you are invited to your to this massmind site! (posts will be visible only to you before review) Just type a nice message (short messages are blocked as spam) in the box and press the Post button. (HTML welcomed, but not the <A tag: Instead, use the link box to link to another page. A tutorial is available Members can login to post directly, become page editors, and be credited for their posts.


Link? Put it here: 
if you want a response, please enter your email address: 
Attn spammers: All posts are reviewed before being made visible to anyone other than the poster.
Did you find what you needed?

 

Welcome to ecomorder.com!

 

Welcome to ecomorder.com!

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

  .