InstructionsUbicom 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 the Code Library SX Instruction set table: InstructionCyclesFlags AffectsRefsDescriptionDetailsMicrochip Menomics byte-oriented operations MOV W,#lit1-WlitMove literal into W ( W = lit )Users Manual p103MOVLW lit MOV W,fr1ZWfrMove fr into W ( W = fr )Users Manual p95MOVF fr,0 MOV fr,W1-frWMove W into fr ( fr = W )Users Manual p89MOVWF fr MOV fr,#lit2-W frlitMove literal into fr ( fr = lit )See: mov W, #lit; mov fr, WMOVLW lit; MOVWF fr MOV fr1,fr22ZW fr1fr2Move fr2 into fr1 ( fr1 = fr2 )See: mov W, fr2; mov fr1, WMOVF fr2,0; MOVWF fr1 ADD W,fr1C DC ZWfrAdd fr into W ( W += fr )Users Manual p70ADDWF fr,0 ADD fr,W1C DC ZfrWAdd W into fr ( fr += W )Users Manual p69ADDWF fr,1 ADD fr,#lit2C DC ZW frlitAdd literal into fr ( fr += W = lit )See: mov W, #lit; add fr, WMOVLW lit; ADDWF fr,1 ADD fr1,fr22C DC ZW fr1fr2Add fr2 into fr1 ( fr1 += W = fr2 )See: mov W, fr2; add fr1, WMOVF fr2,0; ADDWF fr1,1 MOV W,fr-W1C DC ZWfrMove fr - W into W ( W -= fr )Users Manual p97SUBWF fr,0 SUB fr,W1C DC ZfrWSubtract W from fr ( fr -= W )Users Manual p124SUBWF fr,1 SUB fr,#lit2C DC ZW frlitSubtract lit from fr ( fr -= W = lit )See: mov W, #lit; sub fr, WMOVLW lit; SUBWF fr,1 SUB fr1,fr22C DC ZW fr1fr2Subtract fr2 from fr1 ( fr1 -= W = fr2 )See: mov W, fr2; sub fr1, WMOVF fr2,0; SUBWF fr1,1 AND W,#lit1ZWlitAND literal into W ( W &= lit )Users Manual p73ANDLW lit AND W,fr1ZWfrAND fr into W ( W &= fr )Users Manual p72ANDWF fr,0 AND fr,W1ZfrWAND W into fr ( fr &= W )Users Manual p71ANDWF fr,1 AND fr,#lit2ZW frlitAND literal into fr ( fr &= W = lit )See: mov W, #lit; and fr, WMOVLW lit; ANDWF fr,1 AND fr1,fr22ZW fr1fr2AND fr2 into fr1 ( fr1 &= W = fr2 )See: mov W, fr2; and fr, WMOVF fr2,0; ANDWF fr,1 OR W,#lit1ZWlitOR literal into W ( W |= lit )Users Manual p111IORLW lit OR W,fr1ZWfrOR fr into W ( W |= fr )Users Manual p110IORWF fr,0 OR fr,W1ZfrWOR W into fr ( fr |= W )Users Manual p109IORWF fr,1 OR fr,#lit2ZW frlitOR literal into fr ( fr |= W = lit )See: mov W, #lit; or fr, WMOVLW lit; IORWF fr,1 OR fr1,fr22ZW fr1fr2OR fr2 into fr1 ( fr1 |= W = fr2 )See: mov W, fr2; or fr1, WMOVF fr2,0; IORWF fr1,1 XOR W,#lit1ZWlitXOR literal into W ( W ^= lit )Users Manual p130XORLW lit XOR W,fr1ZWfrXOR fr into W ( W ^= fr )Users Manual p129XORWF fr,0 XOR fr,W1ZfrWXOR W into fr ( fr ^= W )Users Manual p128XORWF fr,1 XOR fr,#lit2ZW frlitXOR literal into fr ( fr ^= W = lit )See: mov W, #lit; xor fr, WMOVLW lit; XORWF fr,1 XOR fr1,fr22ZW fr1fr2XOR fr2 into fr1 ( fr1 ^= W = fr2 )See: mov W, fr2; xor fr1, WMOVF fr2,0; XORWF fr1,1 CLR W1ZW-Clear W ( W = 0 )Users Manual p79CLRW CLR fr1Zfr-Clear fr ( fr = 0 )Users Manual p78CLRF fr MOV W,++fr1ZWfrMove fr + 1 into W ( W = 1 + fr )Users Manual p99INCF fr,0 INC fr1ZfrfrIncrement fr ( fr = 1 + fr )Users Manual p84INCF fr,1 MOV W,--fr1ZWfrMove fr - 1 into W ( W = -1 + fr )Users Manual p98DECF fr,0 DEC fr1ZfrfrDecrement fr ( fr = -1 + fr )Users Manual p82DECF fr,1 MOV W,>fr1CWfrMove right-rotated fr into W ( W = C * 128 + fr >> 1 fr )Users Manual p101RRF fr,0 RR fr1CfrfrRotate right fr ( fr = C * 128 + fr >> 1 fr )Users Manual p119RRF fr,1 MOV W,<>fr1-WfrMove nibble-swapped fr into W ( W = (( fr & 0xF0 ) >> 4 ) | (( fr & 0x0F ) << 4 ) fr )Users Manual p102SWAPF fr,0 SWAP fr1-frfrSwap nibbles in fr ( fr = (( fr & 0xF0 ) >> 4 ) | (( fr & 0x0F ) << 4 ) fr )Users Manual p126SWAPF fr,1 NOT W1ZWWPerform not on W ( W = 0xFF ^ W )See: xor w,#$FFXORLW 0FFh MOV W,/fr1ZWfrMove not'd fr into W ( W = 0xFF ^ fr )Users Manual p96COMF fr,0 NOT fr1ZfrfrPerform not on fr ( fr = 0xFF ^ fr )Users Manual p108COMF fr,1 TEST W1ZWWTest W for zero ( W = 0 | W )See: or W,#litIORLW 0 TEST fr1ZfrfrTest fr for zero ( fr = 0 | fr )Users Manual p127MOVF fr,1 TSTN w1ZWWTest W for $FF ( W )See: xor W,#$FFXORLW 0FFh TSTN fr1ZfrfrTest fr for $FF ( fr )See: mov W,/frCOMF fr,1 bit-oriented operations CLRB bit1-fr bitfrClear bit ( fr,bit = !( 1 << bit ) & fr )Users Manual p81BCF bit CLC 1C--Clear carry ( - )See: CLRB bitBCF 3,0 CLZ 1Z--Clear zero ( - )See: CLRB bitBCF 3,2 SETB bit1-fr bitfrSet bit ( fr,bit = ( 1 << bit ) | fr )Users Manual p121BSF bit STC 1C--Set carry ( - )See: setb 3.0BSF 3,0 STZ 1Z--Set zero ( - )See: setb 3.2BSF 3,2 ADDB fr,bit2ZfrbitAdd bit into fr ( fr += bit )See: snb bit; inc frBTFSC bit; INCF fr,1 ADDB fr,/bit2ZfrbitAdd not bit into fr ( fr += ! bit )See: sb bit; inc frBTFSS bit; INCF fr,1 SUBB fr,bit2ZfrbitSubtract bit from fr ( fr -= bit )See: snb bit; dec frBTFSC bit; DECF fr,1 SUBB fr,/bit2ZfrbitSubtract not bit from fr ( fr -= ! bit )See: sb bit; dec frBTFSS bit; DECF fr,1 MOVB bit1,bit24-bit1bit2Move bit2 into bit1 ( bit1 = bit2 )See: sb bit2; clrb bit1; snb bit2; setb bit1BTFSS bit2; BCF bit1; BTFSC bit2; BSF bit1 (doesn't work) MOVB bit1,/bit24-bit1bit2Move not bit2 into bit1 ( bit1 = ! bit2 )See: snb bit2; clrb bit1; sb bit2; setb bit1BTFSC bit2; BCF bit1; BTFSS bit2; BSF bit1 (doesn't work) inc/dec-conditional branches MOVSZ W,++fr1-WfrMove fr + 1 into W, skip if zero ( W = 1 + fr )Users Manual p106INCFSZ fr,0 INCSZ fr1-fr PCfrIncrement fr , skip if zero ( ++ fr == 0 ? PC++ )Users Manual p85INCFSZ fr,1 IJNZ fr,addr2 *-fr PCfrIncrement fr , jump if not zero ( ++ fr == 0 ? PC = addr )See: incsz fr; jmp addrINCFSZ fr,1; GOTO addr MOVSZ W,--fr1-W PCfrMove fr - 1 into W, skip if zero ( ( W = --fr ) == 0 ? PC++ )Users Manual p105DECFSZ fr,0 DECSZ fr1-fr PCfrDecrement fr , skip if zero ( -- fr == 0 ? PC++ )Users Manual p83DECFSZ fr,1 DJNZ fr,addr2 *-fr PCfrDecrement fr , jump if not zero ( -- fr == 0 ? PC = addr )See: decsz fr; jmp addrDECFSZ fr,1; GOTO addr compare-conditional branches (see also: Program Flow Methods - Comparing values) CSE fr,#lit3C DC ZW PCfr litCompare, skip if equal ( ( W = lit - fr ) == 0 ? PC++ )See: mov W, #lit; mov W, fr-w; sb 3.2MOVLW lit; SUBWF fr,0; BTFSS 3,2 CSE fr1,fr23C DC ZW PCfr1 fr2Compare, skip if equal ( ( W = fr1 - fr2 ) == 0 ? PC++ )See: mov W, fr2; mov W, fr1-w; sb 3.2MOVF fr2,0; SUBWF fr1,0; BTFSS 3,2 CSNE fr,#lit3C DC ZW PCfr litCompare, skip if not equal ( ( W = lit - fr ) != 0 ? PC++ )See: mov W, #lit; mov W, fr-w; snb 3.2MOVLW lit; SUBWF fr,0; BTFSC 3,2 CSNE fr1,fr23C DC ZW PCfr1 fr2Compare, skip if not equal ( ( W = fr1 - fr2 ) != 0 ? PC++ )See: mov W, fr2; mov W, fr1-w; snb 3.2MOVF fr2,0; SUBWF fr1,0; BTFSC 3,2 CSA fr,#lit3C DC ZW PCfr litCompare, skip if above ( ( W = lit - fr ) < 0 ? PC++ )See: mov W, #/lit; add W, fr; sb 3.0MOVLW /lit; ADDWF fr,0; BTFSS 3,0 CSA fr1,fr23C DC ZW PCfr1 fr2Compare, skip if above ( ( W = fr1 - fr2 ) < 0 ? PC++ )See: mov W, fr1; mov W, fr2-w; snb 3.0MOVF fr1,0; SUBWF fr2,0; BTFSC 3,0 CSAE fr,#lit3C DC ZW PCfr litCompare, skip if above or equal ( ( W = lit - fr ) <= 0 ? PC++ )See: mov W, #lit; mov W, fr-w; sb 3.0MOVLW lit; SUBWF fr,0; BTFSS 3,0 CSAE fr1,fr23C DC ZW PCfr1 fr2Compare, skip if above or equal ( ( W = fr1 - fr2 ) <= 0 ? PC++ )See: mov W, fr2; mov W, fr1-w; sb 3.0MOVF fr2,0; SUBWF fr1,0; BTFSS 3,0 CSB fr,#lit3C DC ZW PCfr litCompare, skip if below ( ( W = lit - fr ) > 0 ? PC++ )See: mov W, #lit; mov W, fr-w; snb 3.0MOVLW lit; SUBWF fr,0; BTFSC 3,0 CSB fr1,fr23C DC ZW PCfr1 fr2Compare, skip if below ( ( W = fr1 - fr2 ) > 0 ? PC++ )See: mov W, fr2; mov W, fr1-w; snb 3.0MOVF fr2,0; SUBWF fr1,0; BTFSC 3,0 CSBE fr,#lit3C DC ZW PCfr litCompare, skip if below or equal ( ( W = lit - fr ) >= 0 ? PC++ )See: mov W, #/lit; add W, fr; snb 3.0MOVLW /lit; ADDWF fr,0; BTFSC 3,0 CSBE fr1,fr23C DC ZW PCfr1 fr2Compare, skip if below or equal ( ( W = fr1 - fr2 ) >= 0 ? PC++ )See: mov W, fr1; mov W, fr2-w; sb 3.0MOVF fr1,0; SUBWF fr2,0; BTFSS 3,0 bit-conditional branches CJE fr,#lit,addr4 *C DC ZW PCfr litCompare, jump if equal ( ( W = lit - fr ) != 0 ? PC = addr )See: mov W, #lit; mov W, fr-w; snb 3.2; jmp addrMOVLW lit; SUBWF fr,0; BTFSC 3,2; GOTO addr CJE fr1,fr2,addr4 *C DC ZW PCfr1 fr2Compare, jump if equal ( ( W = fr1 - fr2 ) != 0 ? PC = addr )See: mov W, fr2; mov W, fr1-w; snb 3.2; jmp addrMOVF fr2,0; SUBWF fr1,0; BTFSC 3,2; GOTO addr CJNE fr,#lit,addr4 *C DC ZW PCfr litCompare, jump if not equal ( ( W = lit - fr ) == 0 ? PC = addr )See: mov W, #lit; mov W, fr-w; sb 3.2; jmp addrMOVLW lit; SUBWF fr,0; BTFSS 3,2; GOTO addr CJNE fr1,fr2,addr4 *C DC ZW PCfr1 fr2Compare, jump if not equal ( ( W = fr1 - fr2 ) == 0 ? PC = addr )See: mov W, fr2; mov W, fr1-w; sb 3.2; jmp addrMOVF fr2,0; SUBWF fr1,0; BTFSS 3,2; GOTO addr CJA fr,#lit,addr4 *C DC ZW PCfr litCompare, jump if above ( ( W = lit - fr ) >= 0 ? PC = addr )See: mov W, #/lit; add W, fr; snb 3.0; jmp addrMOVLW /lit; ADDWF fr,0; BTFSC 3,0; GOTO addr CJA fr1,fr2,addr4 *C DC ZW PCfr1 fr2Compare, jump if above ( ( W = fr1 - fr2 ) >= 0 ? PC = addr )See: mov W, fr1; mov W, fr2-w; sb 3.0; jmp addrMOVF fr1,0; SUBWF fr2,0; BTFSS 3,0; GOTO addr CJAE fr,#lit,addr4 *C DC ZW PCfr litCompare, jump if above or equal ( ( W = lit - fr ) > 0 ? PC = addr )See: mov W, #lit; mov W, fr-w; snb 3.0; jmp addrMOVLW lit; SUBWF fr,0; BTFSC 3,0; GOTO addr CJAE fr1,fr2,addr4 *C DC ZW PCfr1 fr2Compare, jump if above or equal ( ( W = fr1 - fr2 ) > 0 ? PC = addr )See: mov W, fr2; mov W, fr1-w; snb 3.0; jmp addrMOVF fr2,0; SUBWF fr1,0; BTFSC 3,0; GOTO addr CJB fr,#lit,addr4 *C DC ZW PCfr litCompare, jump if below ( ( W = lit - fr ) <= 0 ? PC = addr )See: mov W, #lit; mov W, fr-w; sb 3.0; jmp addrMOVLW lit; SUBWF fr,0; BTFSS 3,0; GOTO addr CJB fr1,fr2,addr4 *C DC ZW PCfr1 fr2Compare, jump if below ( ( W = fr1 - fr2 ) <= 0 ? PC = addr )See: mov W, fr2; mov W, fr1-w; sb 3.0; jmp addrMOVF fr2,0; SUBWF fr1,0; BTFSS 3,0; GOTO addr CJBE fr,#lit,addr4 *C DC ZW PCfr litCompare, jump if below or equal ( ( W = lit - fr ) < 0 ? PC = addr )See: mov W, #/lit; add W, fr; sb 3.0; jmp addrMOVLW /lit; ADDWF fr,0; BTFSS 3,0; GOTO addr CJBE fr1,fr2,addr4 *C DC ZW PCfr1 fr2Compare, jump if below or equal ( ( W = fr1 - fr2 ) < 0 ? PC = addr )See: mov W, fr1; mov W, fr2-w; snb 3.0; jmp addrMOVF fr1,0; SUBWF fr2,0; BTFSC 3,0; GOTO addr SB bit1-PCbitSkip if bit ( ( fr & ( 1 << bit )) == 1 ? PC++ )Users Manual p120BTFSS bit SC 1-PCCSkip if carry ( C )See: sb 3.0BTFSS 3,0 SZ 1-PCZSkip if zero ( Z )See: sb 3.2BTFSS 3,2 SNB bit1-PCbitSkip if not bit ( ( fr & ( 1 << bit )) == 0 ? PC++ )Users Manual p123BTFSC bit SNC 1-PCCSkip if not carry ( C )See: snb 3.0BTFSC 3,0 SNZ 1-PCZSkip if not zero ( Z )See: snb 3.2BTFSC 3,2 JB bit,addr2 *-PCbitJump TO address if bit ( ( fr & ( 1 << bit )) == 1 ? PC = addr )See: snb bit; jmp addrBTFSC bit; GOTO addr JC addr2 *-PCCJump TO address if carry ( C )See: snb 3.0; jmp addrBTFSC 3,0; GOTO addr JZ addr2 *-PCZJump TO address if zero ( Z )See: snb 3.2; jmp addrBTFSC 3,2; GOTO addr JNB bit,addr2 *-PCbitJump TO address if not bit ( ( fr & ( 1 << bit )) == 0 ? PC = addr )See: sb bit; jmp addrBTFSS bit; GOTO addr JNC addr2 *-PCCJump TO address if not carry ( C )See: sb 3.0; jmp addrBTFSS 3,0; GOTO addr JNZ addr2 *-PCZJump TO address if not zero ( Z )See: sb 3.2; jmp addrBTFSS 3,2; GOTO addr unconditional branches SKIP 1-PC-Skip next instruction word ( PC++ )See: sb 2.0 /snb 2.0BTFSC/BTFSS 2,0 JMP addr1 *-PC-Jump TO (9 bit) address ( PC = ( page << 9 ) + addr )Users Manual p88GOTO addr JMP PC+W1C DC ZPCWAdd W into PC(L), clear bit 8 ( PC = ( PC & 0xFEFF ) + W )See: add 2, WADDWF 2,1 JMP W1-PCWMove W into PC(L), clear bit 8 ( PC = ( PC & 0xFE00 ) + W )See: mov 2, WMOVWF 2 CALL addr1 *-PC-Call TO address, clear bit 8 ( STACK[SP++] = PC; PC = ( page << 9 ) + addr )Users Manual p76 RETW lit,lit...1-W PClitReturn 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 1PA0..2PC-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 lit1-RTCC PC W FSRlitReturn from interrupt, compensate RTCC ( PC = STACK[SP--]; RTCC += lit )Users Manual p115 i/o and control operations PAGE addr1PA0..2--Transfer addr .11:addr .9 into PA2 : PA0 , will delay skipping ( page = addr >> 9 )Users Manual p112 BANK fr1-FSR-Transfer fr .7:fr .5 into FSR .7:FSR .5 ( FSR = &( fr ) & 0xE0 )Users Manual p74 MOV M,#lit1-MlitMove literal into M ( M = lit )Users Manual p90 MOV M,W1-MWMove W into M ( M = W )Users Manual p91 MOV M,fr2ZW MfrMove fr into M ( M = W = fr )See: mov W, fr; mov M, W MOV W,M1-WMMove M into W ( W = M )Users Manual p104 MOV fr,M2-W frMMove M into fr ( fr = W = M )See: mov W, M; mov fr, W MOV !port,W1-!PORTWMove W into port's TRIS ( !PORT = W )Users Manual p93TRIS port (port=5 to 7) MOV !port,#lit2-W !PORTlitMove literal into port's TRIS ( !PORT = W = lit )See: mov W, #lit; mov !port,WMOVLW lit; TRIS port (port=5 to 7) MOV !port,fr2ZW !PORTfrMove fr into port's TRIS ( !PORT = W = fr )See: mov W, fr; mov !port,WMOVF fr,0; TRIS port (port=5 to 7) MOV !OPTION,W1-!OPTIONWMove W into !OPTION ( !OPTION = W )Users Manual p92OPTION MOV !OPTION,#lit2-W !OPTIONlitMove literal into !OPTION ( !OPTION = W = lit )See: mov W, #lit; mov !OPTION, WMOVLW lit; OPTION MOV !OPTION,fr2ZW !OPTIONfrMove fr into !OPTION ( !OPTION = W = fr )See: mov W, fr; mov !OPTION, WMOVF fr,0; OPTION CLR !WDT1TO PD--Clear WDT and prescaler ( TO = PD = 0 )Users Manual p80CLRWDT SLEEP 1TO PD--Clear WDT and enter sleep mode ( TO = PD = 0 )Users Manual p112SLEEP IREAD 1-M : WM WRead instruction at M : W into M : W ( M : W = PROGRAM[M<<8+W] )Users Manual p86 NOP 1---No operation ( - - )Users Manual p107NOP 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 ------------------------------------------------------------------------------------------------------------------------------- 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 PINS18, PAGES4, BANKS8, OSCHS DEVICE BOR40, TURBO, STACKX, OPTIONX, CARRYX, PROTECT PINS18 Pins (default: PINS18) PINS28 PINS40 PINS64 PAGES1 E2Flash pages (default: PAGES1) PAGES2 PAGES4 PAGES8 BANKS1 RAM banks (default: BANKS1) BANKS2 BANKS4 BANKS8 OSCHS External crystal/resonator (default: OSCHS) OSCXT External crystal/resonator OSCLP External crystal/resonator OSCRC External RC OSC4MHZ Internal 4MHz OSC2MHZ Internal 2MHz OSC1MHZ Internal 1MHz OSC500KHZ Internal 500KHz OSC250KHZ Internal 250KHz OSC125KHZ Internal 125KHz OSC62KHZ Internal 62KHz OSC31KHZ Internal 31KHz BOR40 4.0V Brownout Reset (default: Brownout Reset is disabled) BOR25 2.5V Brownout Reset BOR13 1.3V Brownout Reset TURBO Turbo mode enabled (1:1 execution) (default: 1:4 execution) STACKX Stack is extended to 8 levels (default: Stack is 2 levels) OPTIONX OPTION is extended to 8 bits (default: OPTION is 6 bits) CARRYX ADD/SUB uses carry flag (default: ADD/SUB ignores carry flag) SYNC Input Syncing enabled (default: Input Syncing disabled) WATCHDOG Watchdog Timer enabled (default: Watchdog Timer disabled) PROTECT Code Protect enabled (default: Code Protect disabled) ******** Dynamic Equates (always reflect current values) $ = 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 RE = $09 RE i/o register RF = $0A RF i/o register RG = $0B RG i/o register ******** Backward-Compatibility Symbols for Parallax PIC16Cxx Assembler (SPASM.EXE) DEVICE Directive Symbols PIC16C54 PINS18+PAGES1+BANKS1 (default: PIC16C54) PIC16C54A PINS18+PAGES1+BANKS1 PIC16C55 PINS28+PAGES1+BANKS1 PIC16C56 PINS18+PAGES2+BANKS1 PIC16C57 PINS28+PAGES4+BANKS4 PIC16C58 PINS18+PAGES4+BANKS4 PIC16C58A PINS18+PAGES4+BANKS4 HS_OSC OSCHS (default: HS_OSC) XT_OSC OSCXT LP_OSC OSCLP 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 WKED_B (Mode=0Ah) 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.