André's 8-bit Pages  Projects  Code  Resources  Tools  Forum
(by Google)

65002 Operation Documentation

This page lists all the opcodes of the 65002 with appropriate explanations.

List of operations

  • ADB - Add value to B register
  • ADC - Add content of memory location to accumulator
  • ADD - Add content of memory location to accumulator without using carry as input
  • ADE - Add value to E register
  • ADS - Add value to stack pointer
  • AND - Bitwise AND accumulator with content of memory location
  • ASL - Arithmetic Shift Left - shift accumulator one bit to the left, shifting in zero in bit 0
  • ASR - Arithmetic Shift Right - Similar to LSR, but shifts in the sign of the value, not zero
  • BCC - Branch on carry clear - take branch when C flag is cleared
  • BCN - Bit Count: counts 1-bits in AC or in given location, stores number of 1-bits back in AC
  • BCS - Branch on carry set - take branch when C flag is set
  • BEQ - Branch on equal - take branch when Z flag is set
  • BEV - Branch on even
  • BGES - Branch on signed greater or equal than
  • BGT - Branch if greater - take branch when C flag is set but Z flag is clear
  • BGTS - Branch if greater - take branch when signed greater or equal G flag is set but Z flag is clear
  • BIT - Bitwise test with accumulator - AND the memory location with the accumulator, and set N (=bit 7), V (=bit 7), Z (iff all bits zero) flags from the result. In case of the accumulator addressing, simply set the flags from the accumulator
  • BLE - Branch if less or equal - take branch when C flag is clear or Z flag is set
  • BLES - Branch if less or equal - take branch when signed greater or equal flag G is clear or Z flag is set
  • BLTS - Branch on signed less than
  • BMI - Branch on minus - take branch when N flag is set
  • BNE - Branch on not equal - take branch when Z flag is cleared
  • BOD - Branch on odd
  • BPL - Branch on plus - take branch when N flag is cleared
  • BRA - Branch always - branch independent from any flags
  • BRK - Starts the break routine.
  • BSR - Branch subroutine - similar to JSR, but use relative addressing similar to branch opcodes
  • BVC - Branch on overflow clear - take branch when V flag is cleared
  • BVS - Branch on overflow set - take branch when V flag is set
  • CLC - Clear the C flag
  • CLD - Clear the decimal (D) flag
  • CLI - Clear the interrupt (I) flag
  • CLV - Clear the overflow (V) flag
  • CMP - Compare accumulator with content of memory location
  • CPX - Compare X register with content of memory location
  • CPY - Compare Y register with content of memory location
  • DEC - Decrement the content of a memory location by one
  • DEX - Decrement the content of the X register by one
  • DEY - Decrement the Y register by one
  • EOR - Bitwise Exclusive-OR accumulator with content of memory location
  • EXT - Extend a value in AC from RS to the full size. Setting LE defines the type of extension.
  • INC - Increment the content of a memory location by one
  • INV - invert AC, i.e. set AC to the 2s-complement of AC
  • INX - Increment the content of the X register by one
  • INY - Increment the content of the Y register by one
  • JMP - Jump to new code address
  • JSR - Jump subroutine - jump to a new code location, save return address on stack for RTS
  • LDA - Load accumulator
  • LDB - Load B with an immediate value
  • LDE - Load E with an immediate value
  • LDX - Load X register
  • LDY - Load Y register
  • LEA - Load Effective Address: compute the effective address and store it in the E (effective Address) register (always full width)
  • LSR - Logical Shift Right - shift accumulator one bit to the right, shifting in zero in the highest bit
  • NOP - No operation
  • ORA - Bitwise OR accumulator with content of memory location
  • PEA - Push Effective Address: compute the effective address and push it onto the stack (always full width)
  • PHA - Push contents of the accumulator onto the stack
  • PHB - Push B onto stack (full width)
  • PHE - Push E onto stack (always full width)
  • PHP - Push processor status register onto the stack
  • PHX - Push contents of the X register onto the stack
  • PHY - Push contents of the Y register onto the stack
  • PLA - Pull the contents of the accumulator from the stack
  • PLB - Pull E from stack (full width)
  • PLE - Pull E from stack (full width)
  • PLP - Pull processor status register from the stack
  • PLX - Pull the contents of the X register from the stack
  • PLY - Pull the contents of the Y register from the stack
  • PRB - Push and Replace Base register: Push base offset register to the stack, then transfer accumulator to the base register
  • RDL - Rotate Direct Left - similar to ROL, but do not shift in carry, but the highest bit of the original value
  • RDR - Rotate Direct Right - similar to ROR, but do not shift in carry, but the lowest bit of the original value
  • ROL - Rotate Left - shift accumulator one bit to the left, shifting in the carry flag in bit 0, and shifting the highest bit into the carry flag instead.
  • ROR - Rotate Right - shift accumulator one bit to the right, shifting in the carry flag in the highest bit, and shifting bit 0 into the carry flag instead.
  • RTI - Return from interrupt
  • RTS - Return from subroutine - read return address from stack
  • RTU - Return from trap handler.
  • SAB - Swap A register with B register. Always done full width, no flags set.
  • SAE - Swap AC with E register. Always done full width, no flags set.
  • SAX - Swap AC with X register. Always done full width, no flags set.
  • SAY - Swap AC with Y register. Always done full width, no flags set.
  • SBB - Substract value from B register
  • SBC - Substract content of memory location from accumulator
  • SBE - Add value to E register
  • SBS - Substract value from stack pointer
  • SEB - Swap E register with B register. Always done full width, no flags set.
  • SEC - Set the C flag
  • SED - Set the decimal (D) flag
  • SEI - Set the interrupt (I) flag
  • STA - Store the content of the accumulator into a memory location
  • STX - Store the content of the X register to memory.
  • STY - Store the content of the Y register to memory.
  • STZ - Store zero into a memory location
  • SUB - Substract content of memory location from accumulator without using the carry flag as input
  • SWP - swap upper and lower part nibble / byte / word / long word of a byte / word / long / quad (longlong) operand in Accumulator
  • SXY - Swap X with Y register. Always done full width, no flags set.
  • TAB - Transfer AC to B register
  • TAE - Transfer AC to E register
  • TAX - Transfer the contents of accumulator into the X register
  • TAY - Transfer the contents of accumulator into the Y register
  • TBA - Transfer base register B to Accumulator
  • TBE - Transfer content of B register into E register (full width)
  • TEA - Transfer E register to Accumulator
  • TEB - Transfer E to B register (full width)
  • TPA - Transfer Program counter to Accumulator
  • TRB - Test and Reset Bit - AND the memory location with the accumulator, and set the Z flag from the result, then CLEAR all bits in the memory location that are set in the accumulator.
  • TRP - Trap into 65k supervisor mode
  • TSB - Test and Set Bit - AND the memory location with the accumulator, and set the Z flag from the result, then SET all bits in the memory location that are set in the accumulator.
  • TSX - Transfer the contents of the stack pointer into the X register (Note: needs RS to keep compatibility with 6502)
  • TSY - Transfer stack pointer to Y
  • TXA - Transfer the contents of the X register into the accumulator
  • TXS - Transfer the contents of X register into the stack pointer (Note: needs RS to keep compatibility with 6502)
  • TYA - Transfer the contents of the Y register into the accumulator
  • TYS - Transfer Y to stack pointer

ADB

Add value to B register

ADB
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x6565kRS, LE, NFImmediate
EXT0x7565kRS, NFAccumulator

ADC

Add content of memory location to accumulator

ADC
PageOpcodeClassPrefixesAddressing ModeSyntax
0x61AM, OF, RS, LE, UM, NFZeropage indexed with X indirect 16bit
0x6365kAM, OF, RS, LE, UM, NFZeropage indexed with X indirect 64bit
0x65AM, OF, RS, LE, UM, NFZeropage
0x69RS, LE, NFImmediate
0x6dAM, OF, RS, LE, UM, NFAbsolute 16bit
0x71AM, OF, RS, LE, UM, NFZeropage indirect 16bit indexed with Y
0x72cmosAM, OF, RS, LE, UM, NFZeropage indirect 16bit
0x7365kAM, OF, RS, LE, UM, NFZeropage indirect 64bit indexed with Y
0x75AM, OF, RS, LE, UM, NFZeropage indexed with X
0x7765kAM, OF, RS, LE, UM, NFZeropage indirect 64bit
0x79AM, OF, RS, LE, UM, NFAbsolute 16bit indexed with Y
0x7dAM, OF, RS, LE, UM, NFAbsolute 16bit indexed with X
EXT0x6965kRS, LE, UM, NFE indirect

Description

Add the operand to the accumulator and store back in the accumulator. Set the flags from the result. Use Decimal or Binary add depending on whether the decimal mode status bis is set or not respectively.

        		AC, C, V <= AC + Operand, C
        		N <= Tmp(7)
        		Z <= Z(Tmp)
        	

For a handling of the V-flag please see http://www.6502.org/tutorials/vflag.html.

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS and LE together also determine the width of the operation. Note that the default is to use BYTE-wide operation without load extension.

ADD

Add content of memory location to accumulator without using carry as input

ADD
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x05RS, LE, NFImmediate
EXT0x0065kRS, LE, UM, NFE indirect

Description

Add the operand to the accumulator and store back in the accumulator. Set the flags from the result. Use Binary mode add only. Do not use the Carry flag as input.

        		AC, C, V <= AC + Operand
        		N <= Tmp(7)
        		Z <= Z(Tmp)
        	

For a handling of the V-flag please see http://www.6502.org/tutorials/vflag.html.

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS and LE together also determine the width of the operation. Note that the default is to use BYTE-wide operation without load extension.

ADE

Add value to E register

ADE
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x2565kRS, LE, NFImmediate
EXT0x3565kRS, NFAccumulator

ADS

Add value to stack pointer

ADS
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x4565kRS, LE, NFImmediate
EXT0x5565kRS, NFAccumulator

AND

Bitwise AND accumulator with content of memory location

AND
PageOpcodeClassPrefixesAddressing ModeSyntax
0x21AM, OF, RS, LE, UM, NFZeropage indexed with X indirect 16bit
0x2365kAM, OF, RS, LE, UM, NFZeropage indexed with X indirect 64bit
0x25AM, OF, RS, LE, UM, NFZeropage
0x29RS, LE, NFImmediate
0x2dAM, OF, RS, LE, UM, NFAbsolute 16bit
0x31AM, OF, RS, LE, UM, NFZeropage indirect 16bit indexed with Y
0x32cmosAM, OF, RS, LE, UM, NFZeropage indirect 16bit
0x3365kAM, OF, RS, LE, UM, NFZeropage indirect 64bit indexed with Y
0x35AM, OF, RS, LE, UM, NFZeropage indexed with X
0x3765kAM, OF, RS, LE, UM, NFZeropage indirect 64bit
0x39AM, OF, RS, LE, UM, NFAbsolute 16bit indexed with Y
0x3dAM, OF, RS, LE, UM, NFAbsolute 16bit indexed with X
EXT0x2965kRS, LE, UM, NFE indirect

Description

Bitwise AND the accumulator with the operand and store back in the accumulator. Set the flags from the result.

        		AC <= AC & Operand
        		N <= Tmp(7)
        		Z <= Z(Tmp)
        	

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS and LE together also determine the width of the operation. Note that the default is to use BYTE-wide operation without load extension.

ASL

Arithmetic Shift Left - shift accumulator one bit to the left, shifting in zero in bit 0

ASL
PageOpcodeClassPrefixesAddressing ModeSyntax
0x06AM, OF, RS, UM, NFZeropage
0x0aRS, NFAccumulator
0x0eAM, OF, RS, UM, NFAbsolute 16bit
0x16AM, OF, RS, UM, NFZeropage indexed with X
0x1eAM, OF, RS, UM, NFAbsolute 16bit indexed with X
EXT0x0f65kAM, OF, RS, UM, NFAbsolute 16bit indexed with Y
EXT0x0d65kRS, UM, NFE indirect

Description

Shift the operand or accumulator left one bit (i.e. multiply by 2). Shift in a zero from the right. The bit shifted out is moved into the carry flag. Note this opcode is a read-modify-write opcode and not only has memory-oriented addressing modes but can work on the accumulator alone as well.

        		C <= AC(7)
        		AC(7-1) <= AC(6-0)
        		AC(0) <= 0
        		N <= AC7)
        		Z <= Z(AC)
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS also determine the width of the operation. There is no LE prefix, as the read and write widths are the same. Note that the default is to use BYTE-wide operation without load extension.

ASR

Arithmetic Shift Right - Similar to LSR, but shifts in the sign of the value, not zero

ASR
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x0665kAM, OF, RS, UM, NFZeropage
EXT0x0a65kRS, NFAccumulator
EXT0x0e65kAM, OF, RS, UM, NFAbsolute 16bit
EXT0x1665kAM, OF, RS, UM, NFZeropage indexed with X
EXT0x1e65kAM, OF, RS, UM, NFAbsolute 16bit indexed with X
EXT0x1f65kAM, OF, RS, UM, NFAbsolute 16bit indexed with Y
EXT0x1d65kRS, UM, NFE indirect

Description

Shift the operand or accumulator right one bit (i.e. divide by 2). Shift in the sign (uppermost bit) from the left. The bit shifted out is moved into the carry flag. Note this opcode is a read-modify-write opcode and not only has memory-oriented addressing modes but can work on the accumulator alone as well.

        		C <= AC(0)
        		AC(6-0) <= AC(7-1)
        		N <= AC7)
        		Z <= Z(AC)
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS also determine the width of the operation. There is no LE prefix, as the read and write widths are the same. Note that the default is to use BYTE-wide operation without load extension.

BCC

Synonyms: BLT

Branch on carry clear - take branch when C flag is cleared

BCC
PageOpcodeClassPrefixesAddressing ModeSyntax
0x90RSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the carry status flag is clear. After a CMP this is a synonym for "less than". The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when N=1 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BCN

Bit Count: counts 1-bits in AC or in given location, stores number of 1-bits back in AC

BCN
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xb465kRS, NFAccumulator

BCS

Synonyms: BGE

Branch on carry set - take branch when C flag is set

BCS
PageOpcodeClassPrefixesAddressing ModeSyntax
0xB0RSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the carry status flag is set. After a CMP this is a synonym for "greater or equal". The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when N=1 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BEQ

Branch on equal - take branch when Z flag is set

BEQ
PageOpcodeClassPrefixesAddressing ModeSyntax
0xf0RSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the zero status flag is set. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when N=1 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BEV

Branch on even

BEV
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x1065kRSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) if the odd status flag is set. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when O=0 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BGES

Branch on signed greater or equal than

BGES
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x7065kRSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) if the signed greater or equal status flag G is set. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when G=1 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BGT

Branch if greater - take branch when C flag is set but Z flag is clear

BGT
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xB065kRSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the carry status flag is set and the zero status flag is not set. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when (N=1 and Z=0) else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BGTS

Branch if greater - take branch when signed greater or equal G flag is set but Z flag is clear

BGTS
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xF065kRSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the signed greater status flag is set and the zero status flag is not set. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when (G=1 and Z=0) else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BIT

Bitwise test with accumulator - AND the memory location with the accumulator, and set N (=bit 7), V (=bit 7), Z (iff all bits zero) flags from the result. In case of the accumulator addressing, simply set the flags from the accumulator

BIT
PageOpcodeClassPrefixesAddressing ModeSyntax
0x24AM, OF, RS, LE, UM, NFZeropage
0x2cAM, OF, RS, LE, UM, NFAbsolute 16bit
0x34cmosAM, OF, RS, LE, UM, NFZeropage indexed with X
0x3ccmosAM, OF, RS, LE, UM, NFAbsolute 16bit indexed with X
0x89cmosRS, LE, NFImmediate
EXT0x8965kRS, LE, UM, NFE indirect
EXT0x3465kRS, NFAccumulator

Description

Read the operand and set the N and V flags from the value (from the highest and next-to-highest bit respectively). Then take the operand, and AND it with the accumulator and evaluate the Z-flag.

        		N <= Operand(7)
        		V <= Operand(6)
        		Tmp <= Operand & AC 
        		Z <= Z(Tmp)
        	

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. The UM prefix determines whether the operand resides in user space or not.

The NF prefix allows to implement a read-modify-write AND of a memory location (without the usual and/store sequence) - without setting a flag though.

BLE

Branch if less or equal - take branch when C flag is clear or Z flag is set

BLE
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x9065kRSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the carry status flag is clear or the zero status flag is set. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when (N=1 and Z=0) else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BLES

Branch if less or equal - take branch when signed greater or equal flag G is clear or Z flag is set

BLES
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xD065kRSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the signed greater status flag is clear or the zero status flag is set. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when (G=0 or Z=1) else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BLTS

Branch on signed less than

BLTS
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x5065kRSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) if the signed greater status or equal flag is not set. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when G=0 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BMI

Branch on minus - take branch when N flag is set

BMI
PageOpcodeClassPrefixesAddressing ModeSyntax
0x30RSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the negative status flag is set. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when N=1 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BNE

Branch on not equal - take branch when Z flag is cleared

BNE
PageOpcodeClassPrefixesAddressing ModeSyntax
0xD0RSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the zero status flag is clear. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when N=1 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BOD

Branch on odd

BOD
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x3065kRSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) if the odd status flag is set. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when O=1 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BPL

Branch on plus - take branch when N flag is cleared

BPL
PageOpcodeClassPrefixesAddressing ModeSyntax
0x10RSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the negative status flag is clear. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when N=1 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BRA

Branch always - branch independent from any flags

BRA
PageOpcodeClassPrefixesAddressing ModeSyntax
0x80cmosRSRelative

Description

Branch (always) to the address given by adding the parameter to the address of the next operation (after the branch opcode). The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BRK

Starts the break routine.

BRK
PageOpcodeClassPrefixesAddressing ModeSyntax
0x00RSImmediate

Description

The BRK opcode is used to jump to the BRK vector. It pushes the return address and the status on the stack, then reads the BRK vector (doubling as IRQ vector) and jumps there.

Please note that the address put on the stack is the address of the next instruction. And the BRK opcode is using the immediate addressing mode (although the MOS manual does not state it). Thus the address put on the stack is two bytes behind the address of the BRK!

Before storing the status on the stack, the opcode sets the I-flag to avoid recursive calling of the interrupt routine.

When storing the status on the stack, the B-flag is set to indicate that the shared IRQ/BRK vector has been called from a BRK and not an IRQ.

        		Stack(SP--) <= > NextPC
        		Stack(SP--) <= < NextPC
        		Stack(SP--) <= Status | B | I
        		PC <= ($FFFE)
        	

65k

On the 65k, the RS prefix determines the size of the immediate operand, so that the return address that is pushed onto the stack depends on it.

As opposed to the IRQ, the BRK opcode stays in the user resp. hypervisor mode where it is executed.

In hypervisor mode, once the processor configuration register for abort vector table is set, the BRK vector is taken from the abort vector table. For details see the interrupt handling description.

In user mode the BRK always uses the standard two-byte $FFFE IRQ vector, sign-expanded to full address length.

BSR

Branch subroutine - similar to JSR, but use relative addressing similar to branch opcodes

BSR
PageOpcodeClassPrefixesAddressing ModeSyntax
0x8265kAM, RSRelative (BSR)
0x4465kAM, RSRelative 16bit (BSR)

Description

Branch to the address given by the operand as computed similar to the branch opcodes. Store the return address (-1) on the stack to prepare for the RTS opcode.

        		Stack(SP--) <= > NextPC-1
        		Stack(SP--) <= < NextPC-1
        		PC <= NextPC + Operand
        	

65k

The AM prefix is evaluated by the relative addressing modes. Note that the RS prefix is used to determine the return address size on the stack, so it cannot be used as parameter width selector. Thus there are two opcodes to define 8-bit or 16-bit parameter width, using the AM prefix to make that 32- or 64-bit respectively.

Note that the UM prefix is not supported.

If the operand is not wide enough as required for an address, it is sign-extended.

The RS prefix determines the width of the return address put on the stack. Note that the BYTE width prefix denotes the natural width of the processor (respectively its current mode). This is the default.

The stack pointer used is the stack pointer of the current mode.

BVC

Branch on overflow clear - take branch when V flag is cleared

BVC
PageOpcodeClassPrefixesAddressing ModeSyntax
0x50RSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the overflow status flag is clear. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when N=1 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

BVS

Branch on overflow set - take branch when V flag is set

BVS
PageOpcodeClassPrefixesAddressing ModeSyntax
0x70RSRelative

Description

Branch to the address given by adding the parameter to the address of the next operation (after the branch opcode) given the condition that the overflow status flag is set. The parameter is a signed 8-bit value, i.e. jump distances can be from -128 to +127.

        		PC <= NextPC + Operand when N=1 else NextPC
        	

65k

The RS prefix determines the width of the parameter, the default is 8-bit. With a 16-bit parameter the jump distances can be from -32768 to +32767 and so on.

CLC

Clear the C flag

CLC
PageOpcodeClassPrefixesAddressing ModeSyntax
0x18Implied

Description

Clear the carry status flag.

CLD

Clear the decimal (D) flag

CLD
PageOpcodeClassPrefixesAddressing ModeSyntax
0xd8Implied

Description

Clear the decimal mode status flag.

CLI

Clear the interrupt (I) flag

CLI
PageOpcodeClassPrefixesAddressing ModeSyntax
0x58Implied

Description

Clear the interrupt status flag.

65k

Note that the interrupt handling is much more sophisticated in the 65k. In hypervisor mode setting the interrupt status flag disables all interrupts except the non-maskable interrupt. In user mode setting the interrupt status flag disables all "user level interrupts", but hypervisor interrupts are served. The interrupt level for user level interrupts can be configured in a configuration register.

CLV

Clear the overflow (V) flag

CLV
PageOpcodeClassPrefixesAddressing ModeSyntax
0xb8Implied

Description

Clear the overflow status flag.

CMP

Compare accumulator with content of memory location

CMP
PageOpcodeClassPrefixesAddressing ModeSyntax
0xc1AM, OF, RS, UM, LEZeropage indexed with X indirect 16bit
0xc365kAM, OF, RS, UM, LEZeropage indexed with X indirect 64bit
0xc5AM, OF, RS, UM, LEZeropage
0xc9RS, LEImmediate
0xcdAM, OF, RS, UM, LEAbsolute 16bit
0xd1AM, OF, RS, UM, LEZeropage indirect 16bit indexed with Y
0xd2cmosAM, OF, RS, UM, LEZeropage indirect 16bit
0xd365kAM, OF, RS, UM, LEZeropage indirect 64bit indexed with Y
0xd765kAM, OF, RS, UM, LEZeropage indirect 64bit
0xd5AM, OF, RS, UM, LEZeropage indexed with X
0xd9AM, OF, RS, UM, LEAbsolute 16bit indexed with Y
0xddAM, OF, RS, UM, LEAbsolute 16bit indexed with X
EXT0xc965kRS, UM, LEE indirect

Description

Compare the operand with the accumulator and set the flags appropriately. I.e. substract the operand from AC with an implicitely set carry in binary mode (even if decimal mode status bit is set), and set the flags from the result.

        		Tmp, C <= Y - Operand, C=1
        		N <= Tmp(7)
        		Z <= Z(Tmp)
        	

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space.

Note that the default is to use BYTE-wide operation without load extension.

CPX

Compare X register with content of memory location

CPX
PageOpcodeClassPrefixesAddressing ModeSyntax
0xe0RS, LEImmediate
0xe4AM, OF, RS, UM, LEZeropage
0xecAM, OF, RS, UM, LEAbsolute 16bit
EXT0xe065kRS, UM, LEE indirect

Description

Compare the operand with the X register and set the flags appropriately. I.e. substract the operand from X with an implicitely set carry in binary mode (even if decimal mode status bit is set), and set the flags from the result.

        		Tmp, C <= X - Operand, C=1
        		N <= Tmp(7)
        		Z <= Z(Tmp)
        	

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space.

Note that the default is to use BYTE-wide operation without load extension.

CPY

Compare Y register with content of memory location

CPY
PageOpcodeClassPrefixesAddressing ModeSyntax
0xc0RS, LEImmediate
0xc4AM, OF, RS, UM, LEZeropage
0xccAM, OF, RS, UM, LEAbsolute 16bit
EXT0xc065kRS, UM, LEE indirect

Description

Compare the operand with the Y register and set the flags appropriately. I.e. substract the operand from Y with an implicitely set carry in binary mode (even if decimal mode status bit is set), and set the flags from the result.

        		Tmp, C <= Y - Operand, C=1
        		N <= Tmp(7)
        		Z <= Z(Tmp)
        	

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space.

Note that the default is to use BYTE-wide operation without load extension.

DEC

Decrement the content of a memory location by one

DEC
PageOpcodeClassPrefixesAddressing ModeSyntax
0xc6AM, OF, RS, UM, NFZeropage
0x3acmosRS, NFAccumulator
0xceAM, OF, RS, UM, NFAbsolute 16bit
0xd6AM, OF, RS, UM, NFZeropage indexed with X
0xdeAM, OF, RS, UM, NFAbsolute 16bit indexed with X
EXT0xcf65kAM, OF, RS, UM, NFAbsolute 16bit indexed with Y
EXT0xcd65kRS, UM, NFE indirect

Description

Decrement the operand by one, i.e. binary substract one. Note this opcode is a read-modify-write opcode and not only has memory-oriented addressing modes but can work on the accumulator alone as well.

        		Operand <= Operand - 1
        		N <= OperandC7)
        		Z <= Z(AC)
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS also determine the width of the operation. There is no LE prefix, as the read and write widths are the same. Note that the default is to use BYTE-wide operation without load extension.

DEX

Decrement the content of the X register by one

DEX
PageOpcodeClassPrefixesAddressing ModeSyntax
0xcaRS, NFImplied

Description

Decrement the X register by one (binary).

        	X <= X-1
        

65k

The RS prefix determines the width of the operation. The NF flag allows to perform the operation without setting flags.

DEY

Decrement the Y register by one

DEY
PageOpcodeClassPrefixesAddressing ModeSyntax
0x88RS, NFImplied

Description

Decrement the Y register by one (binary).

        	Y <= Y-1
        

65k

The RS prefix determines the width of the operation. The NF flag allows to perform the operation without setting flags.

EOR

Bitwise Exclusive-OR accumulator with content of memory location

EOR
PageOpcodeClassPrefixesAddressing ModeSyntax
0x41AM, OF, RS, LE, UM, NFZeropage indexed with X indirect 16bit
0x4365kAM, OF, RS, LE, UM, NFZeropage indexed with X indirect 64bit
0x45AM, OF, RS, LE, UM, NFZeropage
0x49RS, LE, NFImmediate
0x4dAM, OF, RS, LE, UM, NFAbsolute 16bit
0x51AM, OF, RS, LE, UM, NFZeropage indirect 16bit indexed with Y
0x52cmosAM, OF, RS, LE, UM, NFZeropage indirect 16bit
0x5365kAM, OF, RS, LE, UM, NFZeropage indirect 64bit indexed with Y
0x55AM, OF, RS, LE, UM, NFZeropage indexed with X
0x5765kAM, OF, RS, LE, UM, NFZeropage indirect 64bit
0x59AM, OF, RS, LE, UM, NFAbsolute 16bit indexed with Y
0x5dAM, OF, RS, LE, UM, NFAbsolute 16bit indexed with X
EXT0x4965kRS, LE, UM, NFE indirect

Description

Bitwise Exclusive-OR the accumulator with the operand and store back in the accumulator. Set the flags from the result.

        		AC <= AC ^ Operand
        		N <= Tmp(7)
        		Z <= Z(Tmp)
        	

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS and LE together also determine the width of the operation. Note that the default is to use BYTE-wide operation without load extension.

EXT

Extend a value in AC from RS to the full size. Setting LE defines the type of extension.

EXT
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xc465kRS, NFAccumulator

INC

Increment the content of a memory location by one

INC
PageOpcodeClassPrefixesAddressing ModeSyntax
0xe6AM, OF, RS, UM, NFZeropage
0x1acmosRS, NFAccumulator
0xeeAM, OF, RS, UM, NFAbsolute 16bit
0xf6AM, OF, RS, UM, NFZeropage indexed with X
0xfeAM, OF, RS, UM, NFAbsolute 16bit indexed with X
EXT0xef65kAM, OF, RS, UM, NFAbsolute 16bit indexed with Y
EXT0xed65kRS, UM, NFE indirect

Description

Increment the operand by one, i.e. binary add one. Note this opcode is a read-modify-write opcode and not only has memory-oriented addressing modes but can work on the accumulator alone as well.

        		Operand <= Operand + 1
        		N <= OperandC7)
        		Z <= Z(AC)
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS also determine the width of the operation. There is no LE prefix, as the read and write widths are the same. Note that the default is to use BYTE-wide operation without load extension.

INV

invert AC, i.e. set AC to the 2s-complement of AC

INV
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xa465kRS, NFAccumulator

INX

Increment the content of the X register by one

INX
PageOpcodeClassPrefixesAddressing ModeSyntax
0xe8RS, NFImplied

Description

Increment the X register by one (binary).

        	X <= X+1
        

65k

The RS prefix determines the width of the operation. The NF flag allows to perform the operation without setting flags.

INY

Increment the content of the Y register by one

INY
PageOpcodeClassPrefixesAddressing ModeSyntax
0xc8RS, NFImplied

Description

Increment the Y register by one (binary).

        	Y <= Y+1
        

65k

The RS prefix determines the width of the operation. The NF flag allows to perform the operation without setting flags.

JMP

Jump to new code address

JMP
PageOpcodeClassPrefixesAddressing ModeSyntax
0x0765kAM, OF, UM, LEAbsolute indirect 64bit
0x2765kAM, OF, UM, LEAbsolute indexed with X indirect 64bit
0x4cAM, OF, UM, LEAddress
0x6cAM, OF, UM, LEAbsolute indirect 16bit
0x7ccmosAM, OF, UM, LEAbsolute indexed with X indirect 16bit
EXT0x4c65kUM, LEE indirect
EXT0x6cAM, OF, UM, LEAddress Long

Description

Jump to the address given by the operand (as computed depending on the respective addressing mode).

        		PC <= Operand
        		Status |= U when UM is set
        	

65k

The AM, OF, LE and UM prefixes are evaluated by the addressing modes. Note that if UM is set, then the processor jumps into user mode.

If the operand is not as wide as required for an address, it is sign-extended.

JSR

Jump subroutine - jump to a new code location, save return address on stack for RTS

JSR
PageOpcodeClassPrefixesAddressing ModeSyntax
0x20AM, OF, RS, LEAddress
EXT0xdcAM, OF, RS, LEAddress Long
0xdc65kAM, OF, RS, LEAbsolute indirect 16bit
0xfc65kAM, OF, RS, LEAbsolute indexed with X indirect 16bit
0x8765kAM, OF, RS, LEAbsolute indirect 64bit
0xa765kAM, OF, RS, LEAbsolute indexed with X indirect 64bit
EXT0x2065kRS, LEE indirect

Description

Jump to the address given by the operand (as computed depending on the respective addressing mode) and store the return address (-1) on the stack to prepare for the RTS opcode

        		Stack(SP--) <= > NextPC-1
        		Stack(SP--) <= < NextPC-1
        		PC <= Operand
        	

65k

The AM, OF, and LE prefixes are evaluated by the addressing modes. Note that the UM prefix is not supported.

If the operand is not wide enough as required for an address, it is sign-extended.

The RS prefix determines the width of the return address put on the stack. Note that the BYTE width prefix denotes the natural width of the processor (respectively its current mode).

The stack pointer used is the stack pointer of the current mode.

LDA

Load accumulator

LDA
PageOpcodeClassPrefixesAddressing ModeSyntax
0x0265kAM, OF, RS, LE, UM, NFZeropage indexed with Y
0x4265kAM, OF, RS, LE, UM, NFAbsolute indirect 16bit indexed with Y
0x4765kAM, OF, RS, LE, UM, NFAbsolute indirect 64bit indexed with Y
0x6265kAM, OF, RS, LE, UM, NFAbsolute indexed with X indirect 16bit
0x6765kAM, OF, RS, LE, UM, NFAbsolute indexed with X indirect 64bit
0xa1AM, OF, RS, LE, UM, NFZeropage indexed with X indirect 16bit
0xa365kAM, OF, RS, LE, UM, NFZeropage indexed with X indirect 64bit
0xa5AM, OF, RS, LE, UM, NFZeropage
0xa9RS, LE, NFImmediate
0xadAM, OF, RS, LE, UM, NFAbsolute 16bit
0xb1AM, OF, RS, LE, UM, NFZeropage indirect 16bit indexed with Y
0xb2cmosAM, OF, RS, LE, UM, NFZeropage indirect 16bit
0xb365kAM, OF, RS, LE, UM, NFZeropage indirect 64bit indexed with Y
0xb5AM, OF, RS, LE, UM, NFZeropage indexed with X
0xb765kAM, OF, RS, LE, UM, NFZeropage indirect 64bit
0xb9AM, OF, RS, LE, UM, NFAbsolute 16bit indexed with Y
0xbdAM, OF, RS, LE, UM, NFAbsolute 16bit indexed with X
EXT0xa965kRS, LE, UM, NFE indirect

Description

Read the operand and store it in the Accumulator. Set the flags appropriately.

        		N <= Operand(7)
        		Z <= Z(Operand)
        		Y <= Operand
        	

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. The UM prefix determines whether the operand resides in user space or not.

Note that the default load extension is "zero-extended", to "not surprise" programmers.

The NF prefix lets the flags unmodified.

LDB

Load B with an immediate value

LDB
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x5965kRS, LE, NFImmediate

Description

Read the operand and store it in the B register. Set the flags appropriately.

        		N <= Operand(7)
        		Z <= Z(Operand)
        		B <= Operand
        	

65k

The LE and RS prefixes are evaluated by the addressing modes.

Note that the default load extension is "sign-extended".

The NF prefix lets the flags unmodified.

LDE

Load E with an immediate value

LDE
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x3965kRS, LE, NFImmediate

Description

Read the operand and store it in the E register. Set the flags appropriately.

        		N <= Operand(7)
        		Z <= Z(Operand)
        		E <= Operand
        	

65k

The LE and RS prefixes are evaluated by the addressing modes.

Note that the default load extension is "sign-extended".

The NF prefix lets the flags unmodified.

LDX

Load X register

LDX
PageOpcodeClassPrefixesAddressing ModeSyntax
0xa2RS, LE, NFImmediate
0xa6AM, OF, RS, LE, UM, NFZeropage
0xaeAM, OF, RS, LE, UM, NFAbsolute 16bit
0xb6AM, OF, RS, LE, UM, NFZeropage indexed with Y
0xbeAM, OF, RS, LE, UM, NFAbsolute 16bit indexed with Y
EXT0xad65kRS, LE, UM, NFE indirect

Description

Read the operand and store it in the X register. Set the flags appropriately.

        		N <= Operand(7)
        		Z <= Z(Operand)
        		X <= Operand
        	

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. The UM prefix determines whether the operand resides in user space or not.

Note that the default load extension is "zero-extended", to "not surprise" programmers.

The NF prefix lets the flags unmodified.

LDY

Load Y register

LDY
PageOpcodeClassPrefixesAddressing ModeSyntax
0xa0RS, LE, NFImmediate
0xa4AM, OF, RS, LE, UM, NFZeropage
0xacAM, OF, RS, LE, UM, NFAbsolute 16bit
0xb4AM, OF, RS, LE, UM, NFZeropage indexed with X
0xbcAM, OF, RS, LE, UM, NFAbsolute 16bit indexed with X
EXT0xa065kRS, LE, UM, NFE indirect

Description

Read the operand and store it in the Y register. Set the flags appropriately.

        		N <= Operand(7)
        		Z <= Z(Operand)
        		Y <= Operand
        	

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. The UM prefix determines whether the operand resides in user space or not.

Note that the default load extension is "zero-extended", to "not surprise" programmers.

The NF prefix lets the flags unmodified.

LEA

Load Effective Address: compute the effective address and store it in the E (effective Address) register (always full width)

LEA
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xf665kAM, OF, UM, NFZeropage indexed with Y
EXT0x6165kAM, OF, UM, NFAbsolute indirect 64bit indexed with Y
EXT0x7165kAM, OF, UM, NFAbsolute indexed with X indirect 64bit
EXT0x2165kAM, OF, UM, NFAbsolute indirect 16bit indexed with Y
EXT0x3165kAM, OF, UM, NFAbsolute indexed with X indirect 16bit
EXT0xa265kAM, OF, UM, NFRelative
EXT0xa165kAM, OF, UM, NFZeropage indexed with X indirect 16bit
EXT0x4665kAM, OF, UM, NFZeropage
EXT0xae65kAM, OF, UM, NFAbsolute 16bit
EXT0xb165kAM, OF, UM, NFZeropage indirect 16bit indexed with Y
EXT0xb265kAM, OF, UM, NFZeropage indirect 16bit
EXT0x3265kAM, OF, UM, NFAbsolute indirect 16bit
EXT0xf265kAM, OF, UM, NFZeropage indirect 64bit
EXT0x7265kAM, OF, UM, NFAbsolute indirect 64bit
EXT0x5665kAM, OF, UM, NFZeropage indexed with X
EXT0xbf65kAM, OF, UM, NFAbsolute 16bit indexed with Y
EXT0xbe65kAM, OF, UM, NFAbsolute 16bit indexed with X
EXT0x2265kAM, OF, UM, NFRelative 16bit
EXT0xe165kAM, OF, UM, NFZeropage indirect 64bit indexed with Y
EXT0xf165kAM, OF, UM, NFZeropage indexed with X indirect 64bit

Description

Load the effective address given by the addressing mode into the E register (without accessing the memory pointed to by the parameter).

        	E <= EffectiveAddress
        

65k

The value stored in E is always in the natural (full) width of the processor.

The AM and OF prefixes are interpreted as usually when computing the address.

The memory and stack pointers used are the current ones when the user mode prefix is not set. When the user mode prefix is set in hypervisor mode, the memory and stack pointer is that of the user mode. When set in user mode an ABORT is triggered.

With this approach you can use this in trap handling:

        		LEA.U S,$08			; load user space address of offset 8 on the user mode stack
        		LDA.U (E)			; load the value from user space
        	

LSR

Logical Shift Right - shift accumulator one bit to the right, shifting in zero in the highest bit

LSR
PageOpcodeClassPrefixesAddressing ModeSyntax
0x46AM, OF, RS, UM, NFZeropage
0x4aRS, NFAccumulator
0x4eAM, OF, RS, UM, NFAbsolute 16bit
0x56AM, OF, RS, UM, NFZeropage indexed with X
0x5eAM, OF, RS, UM, NFAbsolute 16bit indexed with X
EXT0x4f65kAM, OF, RS, UM, NFAbsolute 16bit indexed with Y
EXT0x4d65kRS, UM, NFE indirect

Description

Shift the operand or accumulator right one bit (i.e. divide by 2). Shift in a zero from the left. The bit shifted out is moved into the carry flag. Note this opcode is a read-modify-write opcode and not only has memory-oriented addressing modes but can work on the accumulator alone as well.

        		C <= AC(0)
        		AC(6-0) <= AC(7-1)
        		AC(7) <= 0
        		N <= AC7)
        		Z <= Z(AC)
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS also determine the width of the operation. There is no LE prefix, as the read and write widths are the same. Note that the default is to use BYTE-wide operation without load extension.

NOP

No operation

NOP
PageOpcodeClassPrefixesAddressing ModeSyntax
0xeaImplied

Description

No Operation.

ORA

Bitwise OR accumulator with content of memory location

ORA
PageOpcodeClassPrefixesAddressing ModeSyntax
0x01AM, OF, RS, LE, UM, NFZeropage indexed with X indirect 16bit
0x0365kAM, OF, RS, LE, UM, NFZeropage indexed with X indirect 64bit
0x05AM, OF, RS, LE, UM, NFZeropage
0x09RS, LE, NFImmediate
0x0dAM, OF, RS, LE, UM, NFAbsolute 16bit
0x11AM, OF, RS, LE, UM, NFZeropage indirect 16bit indexed with Y
0x12cmosAM, OF, RS, LE, UM, NFZeropage indirect 16bit
0x1365kAM, OF, RS, LE, UM, NFZeropage indirect 64bit indexed with Y
0x15AM, OF, RS, LE, UM, NFZeropage indexed with X
0x1765kAM, OF, RS, LE, UM, NFZeropage indirect 64bit
0x19AM, OF, RS, LE, UM, NFAbsolute 16bit indexed with Y
0x1dAM, OF, RS, LE, UM, NFAbsolute 16bit indexed with X
EXT0x0965kRS, LE, UM, NFE indirect

Description

Bitwise OR the accumulator with the operand and store back in the accumulator. Set the flags from the result.

        		AC <= AC | Operand
        		N <= Tmp(7)
        		Z <= Z(Tmp)
        	

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS and LE together also determine the width of the operation. Note that the default is to use BYTE-wide operation without load extension.

PEA

Push Effective Address: compute the effective address and push it onto the stack (always full width)

PEA
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x4165kAM, OF, UMAbsolute indirect 64bit indexed with Y
EXT0x5165kAM, OF, UMAbsolute indexed with X indirect 64bit
EXT0xd665kAM, OF, UMZeropage indexed with Y
EXT0x0165kAM, OF, UMAbsolute indirect 16bit indexed with Y
EXT0x1165kAM, OF, UMAbsolute indexed with X indirect 16bit
EXT0x8265kAM, OF, UMRelative
EXT0x8165kAM, OF, UMZeropage indexed with X indirect 16bit
EXT0x8665kAM, OF, UMZeropage
EXT0xce65kAM, OF, UMAbsolute 16bit
EXT0x9165kAM, OF, UMZeropage indirect 16bit indexed with Y
EXT0x9265kAM, OF, UMZeropage indirect 16bit
EXT0x1265kAM, OF, UMAbsolute indirect 16bit
EXT0xd265kAM, OF, UMZeropage indirect 64bit
EXT0x5265kAM, OF, UMAbsolute indirect 64bit
EXT0x9665kAM, OF, UMZeropage indexed with X
EXT0xdf65kAM, OF, UMAbsolute 16bit indexed with Y
EXT0xde65kAM, OF, UMAbsolute 16bit indexed with X
EXT0x0265kAM, OF, UMRelative 16bit
EXT0xc165kAM, OF, UMZeropage indirect 64bit indexed with Y
EXT0xd165kAM, OF, UMZeropage indexed with X indirect 64bit

Description

Push the effective address given by the addressing mode onto the stack (without accessing the memory pointed to by the parameter).

        	Stack(SP--) <= >EffectiveAddress
        	Stack(SP--) <= <EffectiveAddress
        

65k

The value pushed is always in the natural (full) width of the processor.

The AM and OF prefixes are interpreted as usually when computing the address.

The memory and stack pointers used are the current ones when the user mode prefix is not set. When the user mode prefix is set in hypervisor mode, the memory and stack pointer is that of the user mode. When set in user mode an ABORT is triggered.

Note that the stack used to actually store the address is always (no matter the user mode bit) the current stack!

PHA

Push contents of the accumulator onto the stack

PHA
PageOpcodeClassPrefixesAddressing ModeSyntax
0x48RS, UMImplied

Description

Push the content of the accumulator on the stack.

        		Stack(SP--) <= A
        	

65k

The RS prefix determines the width of the accumulator value as written on the stack.

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

PHB

Push B onto stack (full width)

PHB
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x4865kUMImplied

Description

Push the content of the B register on the stack.

        		Stack(SP--) <= B
        	

65k

The value stored is always in the natural width of the processor (mode).

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

PHE

Push E onto stack (always full width)

PHE
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x0865kUMImplied

Description

Push the content of the E register on the stack.

        		Stack(SP--) <= E
        	

65k

The value stored is always in the natural width of the processor (mode).

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

PHP

Push processor status register onto the stack

PHP
PageOpcodeClassPrefixesAddressing ModeSyntax
0x08UM, RSImplied

Description

Push the standard status register on the stack.

        		Stack(SP--) <= Status
        	

65k

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

The not-extended bit is set (so the status is compatible with the 6502 and would denote a standard stack frame) as long as RS is 00.

If RS indicates a word-wide push, the G and OE flags of the extended status registers are pushed (with all other bits zero) before the standard status register. The standard status register has the not-extended bit cleared in this case.

RS set to long or quad lengths are illegal and trap into an ABORT.

PHX

Push contents of the X register onto the stack

PHX
PageOpcodeClassPrefixesAddressing ModeSyntax
0xdacmosRS, UMImplied

Description

Push the content of the X register on the stack.

        		Stack(SP--) <= X
        	

65k

The RS prefix determines the width of the accumulator value as written on the stack.

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

PHY

Push contents of the Y register onto the stack

PHY
PageOpcodeClassPrefixesAddressing ModeSyntax
0x5acmosRS, UMImplied

Description

Push the content of the Y register on the stack.

        		Stack(SP--) <= Y
        	

65k

The RS prefix determines the width of the accumulator value as written on the stack.

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

PLA

Pull the contents of the accumulator from the stack

PLA
PageOpcodeClassPrefixesAddressing ModeSyntax
0x68RS, LE, UM, NFImplied

Description

Pull the value of the accumulator from the stack.

        		A <= Stack(++SP)
        	

65k

The RS prefix determines the width of the accumulator value as written on the stack.

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

PLB

Pull E from stack (full width)

PLB
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x6865kUM, NFImplied

Description

Pull the value of the B register from the stack.

        	B <= Stack(++SP)
        	

65k

The value retrieved is always in the natural width of the processor (mode).

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

PLE

Pull E from stack (full width)

PLE
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x2865kUM, NFImplied

Description

Pull the value of the E register from the stack.

        		E <= Stack(++SP)
        	

65k

The value retrieved is always in the natural width of the processor (mode).

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

PLP

Pull processor status register from the stack

PLP
PageOpcodeClassPrefixesAddressing ModeSyntax
0x28Implied

Description

Pull the standard status register on the stack.

        		Status <= Stack(++SP)
        	

65k

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

When the status register has bit 5 (the not-extended bit) set, then PLP reads the standard status register only.

When the status register has bit 5 cleared, it reads a second byte from the stack and restores the G and OE flags from that byte into the extended status register. (Note that this introduces a slight incompatibility with the 6502. So this behaviour may change to require the RS width set to word.)

PLX

Pull the contents of the X register from the stack

PLX
PageOpcodeClassPrefixesAddressing ModeSyntax
0xfacmosRS, LE, UM, NFImplied

Description

Pull the value of the X register from the stack.

        		X <= Stack(++SP)
        	

65k

The RS prefix determines the width of the accumulator value as written on the stack.

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

PLY

Pull the contents of the Y register from the stack

PLY
PageOpcodeClassPrefixesAddressing ModeSyntax
0x7acmosRS, LE, UM, NFImplied

Description

Pull the value of the Y register from the stack.

        		Y <= Stack(++SP)
        	

65k

The RS prefix determines the width of the accumulator value as written on the stack.

The stack pointer used is the one of the current stack if the UM prefix is not set. If UM is set and the opcode is executed in hypervisor mode, the stack pointer used is the user mode stack pointer and the value is stored in user mode memory. If executed in user mode with UM set an ABORT exception is triggered.

PRB

Push and Replace Base register: Push base offset register to the stack, then transfer accumulator to the base register

PRB
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x5865kUM, NFImplied

RDL

Rotate Direct Left - similar to ROL, but do not shift in carry, but the highest bit of the original value

RDL
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x2665kAM, OF, RS, UM, NFZeropage
EXT0x2a65kRS, NFAccumulator
EXT0x2e65kAM, OF, RS, UM, NFAbsolute 16bit
EXT0x3665kAM, OF, RS, UM, NFZeropage indexed with X
EXT0x3e65kAM, OF, RS, UM, NFAbsolute 16bit indexed with X
EXT0x3f65kAM, OF, RS, UM, NFAbsolute 16bit indexed with Y
EXT0x3d65kRS, UM, NFE indirect

Description

Shift the operand or accumulator left one bit (i.e. multiply by 2). Shift in the sign (uppermost bit) of the original value from the right. The bit shifted is also moved into the carry flag. Note this opcode is a read-modify-write opcode and not only has memory-oriented addressing modes but can work on the accumulator alone as well.

        		C <= AC(7)
        		AC(7-1) <= AC(6-0)
        		AC(0) <= C
        		N <= AC7)
        		Z <= Z(AC)
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS also determine the width of the operation. There is no LE prefix, as the read and write widths are the same. Note that the default is to use BYTE-wide operation without load extension.

RDR

Rotate Direct Right - similar to ROR, but do not shift in carry, but the lowest bit of the original value

RDR
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x6665kAM, OF, RS, UM, NFZeropage
EXT0x6a65kRS, NFAccumulator
EXT0x6e65kAM, OF, RS, UM, NFAbsolute 16bit
EXT0x7665kAM, OF, RS, UM, NFZeropage indexed with X
EXT0x7e65kAM, OF, RS, UM, NFAbsolute 16bit indexed with X
EXT0x7f65kAM, OF, RS, UM, NFAbsolute 16bit indexed with Y
EXT0x7d65kRS, UM, NFE indirect

Description

Shift the operand or accumulator right one bit (i.e. divide by 2). Shift in bit 0 (lowermost bit) of the original value from the left. The bit shifted is also moved into the carry flag. Note this opcode is a read-modify-write opcode and not only has memory-oriented addressing modes but can work on the accumulator alone as well.

        		C <= AC(0)
        		AC(6-0) <= AC(7-1)
        		AC(7) <= C
        		N <= AC7)
        		Z <= Z(AC)
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS also determine the width of the operation. There is no LE prefix, as the read and write widths are the same. Note that the default is to use BYTE-wide operation without load extension.

ROL

Rotate Left - shift accumulator one bit to the left, shifting in the carry flag in bit 0, and shifting the highest bit into the carry flag instead.

ROL
PageOpcodeClassPrefixesAddressing ModeSyntax
0x26AM, OF, RS, UM, NFZeropage
0x2aRS, NFAccumulator
0x2eAM, OF, RS, UM, NFAbsolute 16bit
0x36AM, OF, RS, UM, NFZeropage indexed with X
0x3eAM, OF, RS, UM, NFAbsolute 16bit indexed with X
EXT0x2f65kAM, OF, RS, UM, NFAbsolute 16bit indexed with Y
EXT0x2d65kRS, UM, NFE indirect

Description

Shift the operand or accumulator left one bit (i.e. multiply by 2). Shift in the carry flag from the right. The bit shifted out is moved into the carry flag. Note this opcode is a read-modify-write opcode and not only has memory-oriented addressing modes but can work on the accumulator alone as well.

        		Tmp <= AC(7)
        		AC(7-1) <= AC(6-0)
        		AC(0) <= C
        		C <= Tmp
        		N <= AC7)
        		Z <= Z(AC)
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS also determine the width of the operation. There is no LE prefix, as the read and write widths are the same. Note that the default is to use BYTE-wide operation without load extension.

ROR

Rotate Right - shift accumulator one bit to the right, shifting in the carry flag in the highest bit, and shifting bit 0 into the carry flag instead.

ROR
PageOpcodeClassPrefixesAddressing ModeSyntax
0x66AM, OF, RS, UM, NFZeropage
0x6aRS, NFAccumulator
0x6eAM, OF, RS, UM, NFAbsolute 16bit
0x76AM, OF, RS, UM, NFZeropage indexed with X
0x7eAM, OF, RS, UM, NFAbsolute 16bit indexed with X
EXT0x6f65kAM, OF, RS, UM, NFAbsolute 16bit indexed with Y
EXT0x6d65kRS, UM, NFE indirect

Description

Shift the operand or accumulator right one bit (i.e. divide by 2). Shift in the carry flag from the left. The bit shifted out is moved into the carry flag. Note this opcode is a read-modify-write opcode and not only has memory-oriented addressing modes but can work on the accumulator alone as well.

        		Tmp <= AC(0)
        		AC(6-0) <= AC(7-1)
        		AC(7) <= C
        		C <= Tmp
        		N <= AC7)
        		Z <= Z(AC)
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS also determine the width of the operation. There is no LE prefix, as the read and write widths are the same. Note that the default is to use BYTE-wide operation without load extension.

RTI

Return from interrupt

RTI
PageOpcodeClassPrefixesAddressing ModeSyntax
0x40Implied

Description

Returns from an interrupt or a BRK opcode handling. It first pulls the status register from the stack, then takes the return address from the stack, increment it by one, and continue at the new address.

        		Status <= Stack(++SP)		-- bit 5=1
        		Tmp(0-7) <= Stack(++SP)
        		Tmp(8-15) <= Stack(++SP)
        		PC <= Tmp;
        	

65k

The RTI prefix first reads the status from the current stack. If the "Not extended" flag is set (bit 5 is always 1 in the 6502 status register, so here it is used as "not extended" flag), then the normal handling as described above takes place.

If the "not extended" flag is clear, i.e. an extended stack frame is used:

        		Status <= Stack(++SP)		-- bit 5=0
        		ExtStatus <= Stack(++SP)
        		Tmp(0-7) <= Stack(++SP)
        		Tmp(8-15) <= Stack(++SP)
        		...
        		PC <= Tmp;
        	

Here the extended status byte is pulled from the stack after the standard status. In this extended status there are two bit that determine the size of the return address following on the stack. So the return address can be 16-, 32- or 64-bit. Note that the "00" designation (otherwise used for BYTE width) maps to the natural address width of the processor executing the code.

Also the user mode bit is stored in the extended stack frame. If the user mode bit is the same as the current mode, the execution continues in that mode. If the RTI code is executed in the supervisor mode, and the user mode bit is set, then the return address is interpreted as user mode address, and the execution continues in the user mode. If RTI is executed in user mode, and the user mode bit is clear (i.e. hypervisor mode), and ABORT sequence is triggered.

Note that the "natural" address width is taken from the target environment in case the process jumps from hypervisor to user mode.

If the operand is not wide enough as required for an address, it is sign-extended.

RTS

Return from subroutine - read return address from stack

RTS
PageOpcodeClassPrefixesAddressing ModeSyntax
0x60RSImplied

Description

Take the return address from the stack, increment it by one, and continue at the new address.

        		Tmp(0-7) <= Stack(++SP)
        		Tmp(8-15) <= Stack(++SP)
        		PC <= Tmp + 1;
        	

65k

The RS prefix determines the width of the return address read from the stack. Note that the BYTE width prefix denotes the natural width of the processor (respectively its current mode). This is the default.

If the operand is not wide enough as required for an address, it is extended with the rest of the current PC. This is to support running "narrow" code within a e.g. a 64k window in a wide system.

The stack pointer used is the stack pointer of the current mode.

RTU

Return from trap handler.

RTU
PageOpcodeClassPrefixesAddressing ModeSyntax
SYS0x6065kImmediate

Description

Return from trap handling. Reads the extended status byte and the return address from hypervisor stack, then jumps to the return address.

        		<Tmp <= Stack(++SP)
        		>Tmp <= Stack(++SP)
        		Tmp <= Tmp+1
        		PC <= Tmp;
        		ExtStatus <= Stack(++SP)
        	

65k

The extended status byte contains the width bits for the return address as well as the user mode bit from where the trap came. In RTU the user mode bit is restored, so the RTU opcode can return to user as well as hypervisor mode.

The stack pointer used is that of the hypervisor stack.

Note for future expansions the RS prefix may extend the number of traps to word, or even wider widths.

When executed in user mode, this opcode triggers an ABORT exception.

SAB

Swap A register with B register. Always done full width, no flags set.

SAB
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xa865kImplied

SAE

Swap AC with E register. Always done full width, no flags set.

SAE
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xd865kImplied

SAX

Swap AC with X register. Always done full width, no flags set.

SAX
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xba65kImplied

SAY

Swap AC with Y register. Always done full width, no flags set.

SAY
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xda65kImplied

SBB

Substract value from B register

SBB
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xe565kRS, LE, NFImmediate
EXT0xf565kRS, NFAccumulator

SBC

Substract content of memory location from accumulator

SBC
PageOpcodeClassPrefixesAddressing ModeSyntax
0xe1AM, OF, RS, LE, UM, NFZeropage indexed with X indirect 16bit
0xe365kAM, OF, RS, LE, UM, NFZeropage indexed with X indirect 64bit
0xe5AM, OF, RS, LE, UM, NFZeropage
0xe9RS, LE, NFImmediate
0xedAM, OF, RS, LE, UM, NFAbsolute 16bit
0xf1AM, OF, RS, LE, UM, NFZeropage indirect 16bit indexed with Y
0xf2cmosAM, OF, RS, LE, UM, NFZeropage indirect 16bit
0xf365kAM, OF, RS, LE, UM, NFZeropage indirect 64bit indexed with Y
0xf5AM, OF, RS, LE, UM, NFZeropage indexed with X
0xf765kAM, OF, RS, LE, UM, NFZeropage indirect 64bit
0xf9AM, OF, RS, LE, UM, NFAbsolute 16bit indexed with Y
0xfdAM, OF, RS, LE, UM, NFAbsolute 16bit indexed with X
EXT0xe965kRS, LE, UM, NFE indirect

Description

Substract the operand from the accumulator and store back in the accumulator. Set the flags from the result. Use Decimal or Binary add depending on whether the decimal mode status bis is set or not respectively. C status flag is used as borrow.

        		AC, C, V <= AC - Operand, C
        		N <= Tmp(7)
        		Z <= Z(Tmp)
        	

For a handling of the V-flag please see http://www.6502.org/tutorials/vflag.html.

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS and LE together also determine the width of the operation. Note that the default is to use BYTE-wide operation without load extension.

SBE

Add value to E register

SBE
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xa565kRS, LE, NFImmediate
EXT0xb565kRS, NFAccumulator

SBS

Substract value from stack pointer

SBS
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xc565kRS, LE, NFImmediate
EXT0xd565kRS, NFAccumulator

SEB

Swap E register with B register. Always done full width, no flags set.

SEB
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xb865kImplied

SEC

Set the C flag

SEC
PageOpcodeClassPrefixesAddressing ModeSyntax
0x38Implied

Description

Set the carry status flag.

SED

Set the decimal (D) flag

SED
PageOpcodeClassPrefixesAddressing ModeSyntax
0xf8Implied

Description

Set the decimal mode status flag.

SEI

Set the interrupt (I) flag

SEI
PageOpcodeClassPrefixesAddressing ModeSyntax
0x78Implied

Description

Set the interrupt status flag.

65k

Note that the interrupt handling is much more sophisticated in the 65k. In hypervisor mode setting the interrupt status flag disables all interrupts except the non-maskable interrupt. In user mode setting the interrupt status flag disables all "user level interrupts", but hypervisor interrupts are served. The interrupt level for user level interrupts can be configured in a configuration register.

STA

Store the content of the accumulator into a memory location

STA
PageOpcodeClassPrefixesAddressing ModeSyntax
0x2265kAM, OF, RS, UMZeropage indexed with Y
0x81AM, OF, RS, UMZeropage indexed with X indirect 16bit
0x8365kAM, OF, RS, UMZeropage indexed with X indirect 64bit
0x85AM, OF, RS, UMZeropage
0x8dAM, OF, RS, UMAbsolute 16bit
0x91AM, OF, RS, UMZeropage indirect 16bit indexed with Y
0x92cmosAM, OF, RS, UMZeropage indirect 16bit
0x9365kAM, OF, RS, UMZeropage indirect 64bit indexed with Y
0x95AM, OF, RS, UMZeropage indexed with X
0x9765kAM, OF, RS, UMZeropage indirect 64bit
0x99AM, OF, RS, UMAbsolute 16bit indexed with Y
0x9dAM, OF, RS, UMAbsolute 16bit indexed with X
0xc265kAM, OF, RS, UMAbsolute indirect 16bit indexed with Y
0xc765kAM, OF, RS, UMAbsolute indirect 64bit indexed with Y
0xe265kAM, OF, RS, UMAbsolute indexed with X indirect 16bit
0xe765kAM, OF, RS, UMAbsolute indexed with X indirect 64bit
EXT0x8d65kRS, UME indirect

Description

Store the accumulator into the address given by the operand.

        		Operand <= A
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space.

RS also determine the width of the operation. Note that the default is to use BYTE-wide operation without load extension.

STX

Store the content of the X register to memory.

STX
PageOpcodeClassPrefixesAddressing ModeSyntax
0x86AM, OF, RS, UMZeropage
0x8eAM, OF, RS, UMAbsolute 16bit
0x96AM, OF, RS, UMZeropage indexed with Y
EXT0xaf65kAM, OF, RS, UMAbsolute 16bit indexed with Y
EXT0x9d65kRS, UME indirect

Description

Store the content of the X register into the address given by the operand.

        		Operand <= A
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space.

RS also determine the width of the operation. Note that the default is to use BYTE-wide operation without load extension.

STY

Store the content of the Y register to memory.

STY
PageOpcodeClassPrefixesAddressing ModeSyntax
0x84AM, OF, RS, UMZeropage
0x8cAM, OF, RS, UMAbsolute 16bit
0x94AM, OF, RS, UMZeropage indexed with X
EXT0x8f65kAM, OF, RS, UMAbsolute 16bit indexed with X
EXT0x8c65kRS, UME indirect

Description

Store the content of the Y register into the address given by the operand.

        		Operand <= A
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space.

RS also determine the width of the operation. Note that the default is to use BYTE-wide operation without load extension.

STZ

Store zero into a memory location

STZ
PageOpcodeClassPrefixesAddressing ModeSyntax
0x64cmosAM, OF, RS, UMZeropage
0x74cmosAM, OF, RS, UMZeropage indexed with X
0x9ccmosAM, OF, RS, UMAbsolute 16bit
0x9ecmosAM, OF, RS, UMAbsolute 16bit indexed with X
EXT0x9e65kAM, OF, RS, UMAbsolute 16bit indexed with Y
EXT0x9c65kRS, UME indirect

Description

Store the zero into the address given by the operand.

        		Operand <= 0
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space.

RS also determine the width of the operation. Note that the default is to use BYTE-wide operation without load extension.

SUB

Substract content of memory location from accumulator without using the carry flag as input

SUB
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x85RS, LE, NFImmediate
EXT0x8065kRS, LE, UM, NFE indirect

Description

Substract the operand from the accumulator and store back in the accumulator. Set the flags from the result. Use Binary mode add only. C status flag is not used as input, but set as borrow from the result.

        		AC, C, V <= AC - Operand
        		N <= Tmp(7)
        		Z <= Z(Tmp)
        	

For a handling of the V-flag please see http://www.6502.org/tutorials/vflag.html.

65k

The AM, OF, LE and RS prefixes are evaluated by the addressing modes. UM determines whether the operand is in user space. NF allows to not set the flags.

RS and LE together also determine the width of the operation. Note that the default is to use BYTE-wide operation without load extension.

SWP

swap upper and lower part nibble / byte / word / long word of a byte / word / long / quad (longlong) operand in Accumulator

SWP
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xd465kRS, NFAccumulator

SXY

Swap X with Y register. Always done full width, no flags set.

SXY
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x9a65kImplied

TAB

Transfer AC to B register

TAB
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xe865kNF, LE, RSImplied

TAE

Transfer AC to E register

TAE
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x8865kNF, LE, RSImplied

TAX

Transfer the contents of accumulator into the X register

TAX
PageOpcodeClassPrefixesAddressing ModeSyntax
0xaaRS, LE, NFImplied

Description

Transfer the value of the accumulator to the X register

        	X <= A
        

65k

The RS and LE prefixes determines the width of the operation. LE determines how to extend the value loaded to the full (natural) width. The NF flag allows to perform the operation without setting flags.

TAY

Transfer the contents of accumulator into the Y register

TAY
PageOpcodeClassPrefixesAddressing ModeSyntax
0xa8RS, LE, NFImplied

Description

Transfer the value of the accumulator to the Y register

        	Y <= A
        

65k

The RS and LE prefixes determines the width of the operation. LE determines how to extend the value loaded to the full (natural) width. The NF flag allows to perform the operation without setting flags.

TBA

Transfer base register B to Accumulator

TBA
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xf865kNFImplied

TBE

Transfer content of B register into E register (full width)

TBE
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xfa65kNFImplied

TEA

Transfer E register to Accumulator

TEA
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x9865kNFImplied

TEB

Transfer E to B register (full width)

TEB
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xea65kNFImplied

TPA

Transfer Program counter to Accumulator

TPA
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xc865kNFImplied

TRB

Test and Reset Bit - AND the memory location with the accumulator, and set the Z flag from the result, then CLEAR all bits in the memory location that are set in the accumulator.

TRB
PageOpcodeClassPrefixesAddressing ModeSyntax
0x14cmosAM, OF, RS, UM, NFZeropage
0x1ccmosAM, OF, RS, UM, NFAbsolute 16bit
EXT0x1c65kRS, UM, NFE indirect

Description

Take the operand, and AND it with the accumulator and evaluate the Z-flag. Then clear all bits in the operand that are set in the accumulator (basically AND with the inverse of the accumulator), and store the value back.

The use case for this opcode is the synchronization between processes and implements a variant of the "test-and-clear" primitive. Thus this is a Read-Modify-Write operation and will trigger a Memory-Lock between the read and write to make that operation atomic.

        		Tmp <= operand & AC 
        		Z <= Z(Tmp)
        		operand < operand | AC
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. The UM prefix determines whether the operand resides in user space or not.

The NF prefix allows to implement a read-modify-write AND of a memory location (without the usual and/store sequence) - without setting a flag though.

TRP

Trap into 65k supervisor mode

TRP
PageOpcodeClassPrefixesAddressing ModeSyntax
0xf465kImmediate

Description

Trap into supervisor mode. Pushes the return address and the extended status byte on the hypervisor stack and jumps into hypervisor mode, using the appropriate trap vector. To return from the trap, the RTU operations is used. For compatibility with RTS, the return address minus one is stored on the stack.

        		Stack(SP--) <= > NextPC-1
        		Stack(SP--) <= < NextPC-1
        		Stack(SP--) <= ExtStatus
        		PC <= TrapVector(Operand)
        	

65k

The address put on the stack always has the natural width of the processor. Currently no further prefix is supported. The stack pointer used is that of the hypervisor stack.

This opcode can be used in user mode as well as in hypervisor mode. The extended status byte contains the user mode bit, so that the RTU opcode knows whether to return to user mode or hypervisor mode.

The extendend status byte also contains width bits that store the width of the return address on stack. BYTE is not used, but the real width is stored with the width bits.

Note for future expansions the RS prefix may extend the trap number (the immediate operand) to word, or even wider widths.

TSB

Test and Set Bit - AND the memory location with the accumulator, and set the Z flag from the result, then SET all bits in the memory location that are set in the accumulator.

TSB
PageOpcodeClassPrefixesAddressing ModeSyntax
0x04cmosAM, OF, RS, UM, NFZeropage
0x0ccmosAM, OF, RS, UM, NFAbsolute 16bit
EXT0x0c65kRS, UM, NFE indirect

Description

Take the operand, and AND it with the accumulator and evaluate the Z-flag. Then OR the operand with the accumulator and store the value back.

The use case for this opcode is the synchronization between processes and implements a variant of the "test-and-set" primitive. Thus this is a Read-Modify-Write operation and will trigger a Memory-Lock between the read and write to make that operation atomic.

        		Tmp <= operand & AC 
        		Z <= Z(Tmp)
        		operand < operand | AC
        	

65k

The AM, OF and RS prefixes are evaluated by the addressing modes. The UM prefix determines whether the operand resides in user space or not.

The NF prefix allows to implement a read-modify-write OR of a memory location (without the usual or/store sequence) - without setting a flag though.

TSX

Transfer the contents of the stack pointer into the X register (Note: needs RS to keep compatibility with 6502)

TSX
PageOpcodeClassPrefixesAddressing ModeSyntax
0xbaUM, NF, RS, LEImplied

Description

Transfer the value of the stack pointer to the X register

        	X <= S
        

65k

The RS and LE prefixes determines the width of the operation. LE determines how to extend the value loaded to the full (natural) width. The NF flag allows to perform the operation without setting flags.

The stack pointer used is the current stack pointer. If the user mode bit is set in hypervisor mode, the stack pointer used is the user mode stack pointer. If the user mode bit is set in user mode, an ABORT exception is triggered.

TSY

Transfer stack pointer to Y

TSY
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0xca65kNF, UM, RS, LEImplied

TXA

Transfer the contents of the X register into the accumulator

TXA
PageOpcodeClassPrefixesAddressing ModeSyntax
0x8aRS, LE, NFImplied

Description

Transfer the value of the X register to the accumulator

        	A <= X
        

65k

The RS and LE prefixes determines the width of the operation. LE determines how to extend the value loaded to the full (natural) width. The NF flag allows to perform the operation without setting flags.

TXS

Transfer the contents of X register into the stack pointer (Note: needs RS to keep compatibility with 6502)

TXS
PageOpcodeClassPrefixesAddressing ModeSyntax
0x9aRS, LE, UMImplied

Description

Transfer the value of the X register to the stack pointer.

        	S <= X
        

65k

The RS and LE prefixes determines the width of the operation. LE determines how to extend the value loaded to the full (natural) width. The NF flag allows to perform the operation without setting flags.

The stack pointer used is the current stack pointer. If the user mode bit is set in hypervisor mode, the stack pointer used is the user mode stack pointer. If the user mode bit is set in user mode, an ABORT exception is triggered.

TYA

Transfer the contents of the Y register into the accumulator

TYA
PageOpcodeClassPrefixesAddressing ModeSyntax
0x98RS, LE, NFImplied

Description

Transfer the value of the Y register to the accumulator

        	A <= Y
        

65k

The RS and LE prefixes determines the width of the operation. LE determines how to extend the value loaded to the full (natural) width. The NF flag allows to perform the operation without setting flags.

TYS

Transfer Y to stack pointer

TYS
PageOpcodeClassPrefixesAddressing ModeSyntax
EXT0x8a65kLE, RS, UMImplied
 

Disclaimer

All Copyrights are acknowledged. The information here is provided under the terms as described in the license section.

Last updated 2012-04-23. Last modified: 2013-11-17
follow

Follow my 8-bit tweets on Mastodon (In new window) or Bluesky

discuss

Discuss my site on this 6502.org forum thread

(Forum registration required to post)

hot!

Dive into the retro feeling and build yourself a Micro-PET or a Multi-board Commodore 4032 replica

Need more speed? Speed up your 6502 computer with this 10 MHz 6502 CPU accelerator board

Interested in electronics design? Look at the design lesson I got from Bil Herd, the hardware designer of the C128

Want 64bit? - pimp the 6502 with the 65k processor design!