680xx instruction set outline –addressing modes –move instructions –arithmetic & logical...

39
680XX Instruction Set Outline Addressing Modes Move Instructions Arithmetic & Logical Instructions Shift/Rotate/Bit Instructions Compare & Bounds Checking Instructions Branch/Jump & Subroutine Instructions Synchronization Instructions Exception Instructions Misc. Instructions Goal Understand addressing modes Understand instructions Reading Microprocessor Systems Design, Clements, Ch. 2.3-2.9

Post on 20-Dec-2015

222 views

Category:

Documents


1 download

TRANSCRIPT

Page 1: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

680XX Instruction Set

• Outline– Addressing Modes

– Move Instructions

– Arithmetic & Logical Instructions

– Shift/Rotate/Bit Instructions

– Compare & Bounds Checking Instructions

– Branch/Jump & Subroutine Instructions

– Synchronization Instructions

– Exception Instructions

– Misc. Instructions

• Goal– Understand addressing modes

– Understand instructions

• Reading– Microprocessor Systems Design, Clements, Ch. 2.3-2.9

Page 2: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Addressing Modes

• Immediate or literal– operand follows instruction

– e.g. constant

– byte, word, or longword– ADD.L #&9,D0 - add 9 to D0

» # - indicates value is immediate

» & - indicates value is decimal (default is hexadecimal)

• Absolute or direct– address specified as constant - e.g. I/O register

– short - 16-bit address, sign extended to 32-bits prior to use

» access bottom and top 32KB of memory

– long - 32-bit address

– assembler picks appropriate form– MOVE.L D3,$1234 - copy D3 to location $1234

» $ - indicates value is hex (default)

Page 3: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Addressing Modes

• Register direct– operands in registers - no memory access– MOVE.L D0,D3 - copy D0 to D3

– note MOVE from data to address register is illegal

• Register indirect– operand address in address register - a pointer register

– efficient way of specifying address– MOVE.L (A0),D3 - contents of location whose address is in

A0 copied to D3

» () - specifies contents of– MOVEA.L (A0),A0 - dereference a pointer

Page 4: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Addressing Modes

• Register indirect with autoincrement– add 1, 2, or 4 to register after use - depends on operand size

– use to step through arrays

– + - specifies autoincrement– MOVE.L (A0)+,D3 - copy (A0) to D3, add 4 to A0

• Register indirect with autodecrement– subtract 1, 2, or 4 from register before use

– use to step through arrays, especially stack

– - - specifies autodecrement– MOVE.L -(A0),D3 - sub 4 from A0, copy (A0) to D3

• Register indirect with displacement– add signed 16-bit constant to register before use

– use to access structures– MOVE.L 12(A4),D3 - copy location A4+12 to D3

» may be hex by default in 162 board

Page 5: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Addressing Modes

• Register indirect with index– add address register, another register, 8-bit signed displacement

– two-dimensional table access

– other register is index register– MOVE.L 9(A1,D0.W),D3 - copy contents of A1+9+D0[0:15] to D3– MOVE.L 9(A1,D0.L),D3 - copy contents of A1+9+D0[0:31] to D3

• PC relative– like register indirect but uses PC

» PC with displacement

» PC with index

– can write position-independent code

– only with source operand, not destination– MOVE.L 8(PC),D2 - copy contents of PC+8 to D2– MOVE.L 8(PC,D0.W),D3 - copy contents of PC+8+D0[0:15] to D3

Page 6: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Move Instructions

• MOVE src,dst– move 8, 16, 32-bit values

– cannot move to address registers, immediate, PC relative

– clear V,C, set N,Z bits

• MOVEA src,dst– to move to address registers

– only register direct destination

– does not set CCR

• MOVE src,CCR– copy low order byte to CCR

• MOVE src,SR, MOVE SR,dst– copy word to/from status register

– privileged

Page 7: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

MOVE Instructions

• MOVE.L USP,An, MOVE.L An,USP– move address to/from user stack pointer

– privileged

– similarly for SSP

• MOVEM reglist,dst MOVEM src,reglist– move to/from multiple registers and memory

– consecutive memory locations

– CCR not affected– MOVEM.L D0-D7/A0-A6,-(SP) - copy D0-D7, A0-A6 to stack

pointed to by A7

Page 8: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

MOVE Instructions

• MOVEQ lit,Dn– move 32-bit literal in -128 to +127 range to data register

• MOVEP– move to/from 8-bit peripheral, maps bytes

• LEA <ea>,An– calculate effective address and load into address register– compute complex address once, reuse

• PEA <ea>– calculate effective address of operand and push onto stack– used to pass parameters to subroutine

• EXG Xi,Xj– exchange registers Xi and Xj– CCR not changed

• SWAP Dn– exchange upper and lower words of Dn– CCR updated like move

Page 9: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Integer Instructions

• ADD src,dst– one of src,dst must be Dn

– byte, word, or long

– set CCR

• ADDA src,An– add to address register

• ADDI #<data>,dst– add immediate byte, word, long to dst

– dst can be An

– more compact than immediate with ADD

• ADDQ #<data>,dst– add quick

– add constant 0-7 to dst

– dst can be An

Page 10: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Integer Instructions

• ADDX Dsrc,Ddst, ADDX -(Asrc),-(Adst)– add src and extend bit (X) to dst– X set to same as carry– allows multiple precision addition– example - 64-bit addition

» ADD.L D0,D2 - add low-order longword» ADDX.L D1,D3 - add high-order longword with X

• CLR dst– clear dst

– dst is Dn or memory

– use SUBA.L An,An to clear An

» only want to clear An if it will be part of an address computation

• SUB src,dst, SUBA, SUBQ, SUBI, SUBX– same as ADD, except subtract src from dst

Page 11: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Integer Instructions

• NEG dst– 0 - dst -> dst

– dst is memory or Dn

– byte, word, long

– set CCR

• NEGX dst– 0 - dst - X -> dst

– multiple precision negation

• EXT Dn– extend byte to word, word to longword

– extend byte to longword - EXTB.L Dn

– replicate sign bit to left

– use to convert data type

Page 12: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Integer Instructions

• DIVS src,dst– signed divide of dst by src and store result in dst

– two’s complement representation

– DIVS.W <ea>,Dn - 32/16 -> 16r-16q

» store quotient in 16 LSBs, remainder in 16 MSBs

– DIVS.L <ea>,Dq - 32/32 -> 32q

» discard remainder - quotient chopped, not rounded

– DIVS.L <ea>,Dr:Dq - 64/32 -> 32r-32q

» Dr:Dq - quadword

» Dr gets remainder, Dq gets quotient

– DIVSL.L <ea>,Dr:Dq - 32/32 -> 32r-32q

» divide Dr by src

» Dr gets remainder, Dq gets quotient

– divide by 0 causes trap

– overflow sets V, leaves dst unchanged

• DIVU - unsigned divide

Page 13: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Integer Instructions

• MULS src,dst– signed multiple of src and dst, stored in dst

– two’s complement representation

– MULS.W <ea>,Dn - 16x16 -> 32

» 16 LSBs of Dn used as multiplicand, all 32 bits for dst

– MULS.L <ea>,DI - 32x32 -> 32

» dst gets 32 MSBs of 64-bit result

– MULS.L <ea>,Dh-DI - 32x32 -> 64

» Dh - gets 32 LSBs of result, Dl gets 32 LSBs of result

– overflow (V) set if 32x32 -> 32 and 32 MSBs of result are not sign extension of 32 LSBs

• MULU - unsigned multiply– overflow on 32x32 -> 32 if 32 MSBs are not zero

Page 14: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Integer Instructions

• BCD - binary coded decimal– also sometimes called packed decimal

– each 4-bit nibble stores decimal digit

– instructions to add, subtract, negate them

– avoids the need to convert to/from binary

– handy for business/COBOL programs

Page 15: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Logical Instructions

• AND src,dst– src && dst -> dst

– one must be Dn

– byte, word, long

– set Z if zero, set N if MSB is 1

• ANDI #<data>,dst– #<data> && dst -> dst

– dst can be CCR - clear condition codes

– byte, word, long - byte for CCR

• OR src,dst– src || dst -> dst

• ORI #<data>,dst– dst can be CCR - set condition codes

Page 16: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Logical Instructions

• NOT dst– ~dst -> dst

– one’s complement of dst

– byte, word, long

– set N, Z

• EOR Dn,dst– Dn XOR dst -> dst

– exclusive OR

– byte, word, long

– set N, Z

• EORI #<data>,dst– dst can be CCR - flip condition codes

Page 17: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Shift/Rotate Instructions

• ASL,ASR– arithemetic shift left/right

– byte, word, long

– ASd Dx,Dy

» shift by Dx modulo 64

– ASd #<data>,Dy

» shift count 1-8

– ASd <ea>

» one bit shift, word only

– d - L for left and R for right

– shift into carry (C) and extend (X) bits

» can then branch on it

– V indicates if sign change occurred

– set N, Z bits

– left shift - shift in 0

– right shift - shift in MSB (sign bit)

Page 18: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Shift/Logical Instructions

• LSL,LSR– logical shift left/right

– byte, word, long

– LSd Dx,Dy

» shift by Dx modulo 64

– LSd #<data>,Dy

» shift count 1-8

– LSd <ea>

» one bit shift, word only

– d - L for left and R for right

– shift into carry (C) and extend (X) bits

» can then branch on it

– shift in 0

– set N, Z bits, clear V

Page 19: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Shift/Rotate Instructions

• ROL, ROR– rotate left/right

– byte, word, long

– ROd Dx,Dy

» rotate by Dx modulo 64

– ROd #<data>,Dy

» rotate count 1-8

– ROd <ea>

» one bit rotate, word only

– d - L for left and R for right

– bits rotated out into carry (C) bit

» can then branch on it

– set N, Z bits, clear V

Page 20: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Shift/Rotate Instructions

• ROXL, ROXR– rotate left/right including extend bit

– byte, word, long

– ROXd Dx,Dy

» rotate by Dx modulo 64

– ROXd #<data>,Dy

» rotate count 1-8

– ROXd <ea>

» one bit rotate, word only

– d - L for left and R for right

– bits rotated out into carry (C) bit

» can then branch on it

– set N, Z bits, clear V

– used with multiple precision operations

Page 21: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Bit Manipulation

• BTST - test a bit– BTST Dn,<ea>

– BTST #<data>,<ea>

– byte if memory

» number modulo 8

– long if register

» number modulo 32

– number 0 is LSB

– set Z if bit is 0, clear otherwise

• BSET - same as BTST, but set the bit

• BCLR - same as BTST, but clear the bit

• BCHG - same as BTST, but flip the bit

Page 22: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Bit Field Manipulation

• BFTST <ea>{offset:width}– test a bit field

– set Z if zero

– set N if MSB of bit field is set

• BFSET - same as BFTST, but sets the bits

• BFCLR - same as BFTST, but clears the bits

• BFCHG - same as BFTST, but flips the bits

• BFINS Dn,<ea>{offset:width}– insert bit field from low-order bits of Dn

– set N, Z

• BFEXTS <ea>{offset:width},Dn– extract bit field, sign extend to 32-bits, load in Dn

– set N, Z

• BFEXTU - same as BFEXTS except zero extends

Page 23: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Bit Field Instructions

• BFFFO <ea>{offset:width},Dn– find first one in bit field

– scan in MSB order

– store offset from ea in Dn

» offset given in instruction + offset of bit location

» store offset+width if no bit found

– set N if MSB in field is set

– set Z if zero

Page 24: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Fiddling Bits

• Lots of ways to look at bits– logical operations - use constant masks to twiddle bit/bits

» ANDI #$FFFFFFFE D0 - set D0 LSB to 0

– shift/rotate operations - look at bits

» shift into C, branch on it» LSR #$4,D0 - C now has bit 3

» rotate - put it all back when done

– bit operations - directly test/set bits» BSET #&20,D0 - set Z if bit 20 of D0 is 0, set it

– bit field operations - sets of bits» BFSET D0{D1:D2} - set D0 starting at bit specified by D1

modulo 32 and width specified by D2 modulo 32

– note: bits are numbered 31 MSB to 0 LSB

Page 25: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Compare Instructions

• CMP <ea>,Dn– Dn - <ea>, set N, Z, V, C (if borrow)

– byte, word, long

– can then branch on result

• CMPI #<data>,<ea>

• CMPA <ea>,An– word, long

– sign extend word to long

• CMPM (Ay)+,(Ax)+– compare memory locations

– byte, word, long

• TST <ea>– compare <ea> with 0, set N, Z

– byte, word, long

– clears V, C

A0 - first blockA1 - second blocksize - block length

MOVE.W #size-1,D0LOOP: CMPM.L (A0)+,(A1)+ BNE DIFF DBRA D0,LOOPSAME:DIFF:

Page 26: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Bounds Checking Instructions

• CMP2 <ea>,Rn– compare Rn against bounds, set CCR

– <ea> has lower bound followed by upper bound

– Rn - data or address register

– byte, word, long

– Z - set if Rn = LB or Rn = UB

– C - set if Rn < LB or Rn > UB

• CHK <ea>,Dn– if Dn < 0 or Dn > bound, then TRAP to exception vector 6

– <ea> has 2’s complement bound, so can be negative

– word or long

– N - set if Dn < 0, clear if Dn > src

• CHK2 <ea>,Rn– like CMP2, except TRAP to vector 6 if ea is out of bounds

Page 27: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Branch/Jump Instructions• Bcc <label>

– branch on condition cc true to label– label is 2’s complement byte, word, long displacement– branch to (PC)+displacement– PC contains instruction address + 2– conditions (and what is tested)

» CC - carry clear, ~C» CS - carry set, C» EQ - equal, Z» GE - >=, (N and V) or (~N and ~V)» GT - >, (N and V and ~Z) or (~N and ~V and ~Z)» HI - high, ~C and ~Z» LE - <=, Z or (N and ~V) or (~N and V)» LS - low or same, C or Z» LT - <, (N and ~V) or (~N and V)» MI - minus/negative, N» NE - not equal, ~Z» PL - plus/positive, ~N» VC - overflow clear, ~V» VS - overflow set, V

Page 28: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Branch/Jump Instructions

• Condition hazard– MI, PL can be in error since sign changes on overflow for

signed values

• Scc <ea>– set on condition code

– true <ea> <-- 1’s

– false <ea> <-- 0’s

– byte

• DBcc Dn,<label>– test, decrement, and branch

– if cc false, Dn--, if Dn != -1, PC <-- PC+label

– loop control - a for statement

– Dn is word, displacement is signed word

Page 29: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Branch/Jump Instructions

• BRA <label>– unconditional branch to label

– byte, word, long signed displacement

• JMP <ea>– jump to <ea>

– <ea> must be a control address, e.g. not Dn, An, immediate, (An)+, -(An)

– a computed GOTO

» dispatch table - JMP 50(A0,D1)

» case statement - JMP 50(A0)

Page 30: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Subroutine Instructions• BSR <label>

– branch to subroutine

– SP <-- SP-4, (SP) <-- PC, PC <-- PC+displacement

– PC has instruction+2

– byte, word, long signed displacement

• JSR <ea>– jump to subroutine

– SP <-- SP-4, (SP) <-- PC, PC <-- <ea>

– can use for subroutine dispatch table

• RTS– return from subroutine

– PC <-- (SP), SP <-- SP+4

• RTD– return and restore condition codes

– CCR <-- (SP), SP <-- SP+2, PC <-- (SP), SP <-- SP+4

– caller had saved CCR on stack

Page 31: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Subroutine Instructions

• RTD #<displacement>– return and deallocate

– PC <-- (SP), SP <-- SP+4+displacement

– signed 16-bit displacement

– pops off stuff put on stack before subroutine call

• LINK An,#<displacement>– link and allocate

– SP <-- SP-4, (SP) <-- An, An <-- SP, SP <-- SP+displacement

– word or long displacement

» negative to allocate stack area

– use to maintain linked list of local and parameter data on stack for nested subroutine calls

• UNLK An– unlink

– SP <-- An, An <-- (SP), SP <-- SP+4

Page 32: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Synchronization Instructions

• TAS <ea>– test and set

– test byte at <ea>, set N, Z, set MSB of operand

– use locked or read/modify/write memory cycle - no interruptions

– use for flags or semaphores

• CAS Dc,Du,<ea>– compare and swap

– compare <ea> operand to Dc, if equal, put Du in <ea>, otherwise put <ea> operand into Dc

– byte, word, long

– use locked or read/modify/write memory cycle

– implement semaphore

• CAS2 Dc1:Dc2,Du1:Du2,(Rn1):(Rn2)– compare (Rn1) to Dc1, if equal, compare (Rn2) to Dc2, if also equal,

write Du1 to Rn1 and Du2 to Rn2, else write (Rn1) to Dc1 and (Rn2) to Dc2

– word, long

Page 33: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Exceptions

• Exception– stop normal processing

– enter supervisor state

– only way for user to get into supervisor state

• Causes– reset

» loads PC and supervisor stack from memory and sets up status register

– hardware error

» bus error - BERR pin active low

– hardware interrupt

» on interrupt request lines

» 7 levels, encoded into 3 bits IPL0-IPL2

» ignored if I0-I2 in status register is larger

– TRAP - a software interrupt

Page 34: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Exceptions

• Exception vector– each exception has a vector

– 32-bit absolute address of appropriate exception handling routine

» operating system must provide routines

– all vectors are stored in a table of 256 longwords

» 256 different exception numbers

– some exception numbers preallocated

» e.g. 4 is illegal instruction

Page 35: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Exceptions

• Types of exceptions– address error - attempt to access word/long at odd address

» unaligned address

– illegal instruction - unrecognized instruction opcode

– divide by zero

– privilege violation - CPU in user mode, tried to execute privileged op

» e.g. STOP, RESET, MOVE <ea>,SR, MMU, cache

– trace - if T-bit of SR is set, trace exception after each instruction execution

– line 1010,1111 Emulators - opcode with 1010,1111 in MSBs, are illegal

– uninitialized interrupt vector - no interrupt vector provided by device after interrupt, must be initialized

– spurious interrupt - interrupt, CPU acknowledges, no device response

– TRAP - 16 types 0-15, calls 1 of 16 routines

– TRAPV - trap on overflow

– double bus fault - second bus error when saving PC on stack

» CPU is lost

Page 36: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Privileged State

• Supervisor state - higher privilege than user state– when S-bit of SR is 1

– can access SSP, and also USP

• Change from user to supervisor - exception

• Change from supervisor to user– clear S-bit

» RTE - return from exception

» MOVE.W <ea>,SR

» ANDI.W #$XXXX,SR

» EORI.W #$XXXX,SR

Page 37: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Exception Instructions

• RESET– if supervisor state, assert ~RSTO line for 512 clock periods, else TRAP

– resets external devices

• RTE– return from exception

– if supervisor state, SR <-- (SP), SP <-- SP+2, PC <-- (SP), SP <-- SP+4, restore state and deallocate stack according to (SP), else TRAP

– different stack frames for different exceptions

– clears S-bit, returns to user mode

• STOP #<data>– load SR and stop

– if supervisor state, SR <-- #<data>, stop, else trap

– trace, interrupt, or external reset continues processing

» take appropriate exception

Page 38: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Exception Instructions

• TRAP #<vector>– set S-bit

– SSP <-- SSP-2, (SSP) <-- format/offset, SSP <-- SSP-4, (SSP) <-- PC, SSP <-- SSP-2, (SSP) <-- SR, PC <-- vector address

– vector is 0-15

– vector number is vector+32

– vector address obtained by indexing with vector number into vector table

• TRAPcc #<data>– if cc, then TRAP with vector #7

– word or long

– #<data> passed to trap handler

• TRAPV– if V, then TRAP with vector #7

• ILLEGAL– TRAP to vector #4 (illegal instruction)

Page 39: 680XX Instruction Set Outline –Addressing Modes –Move Instructions –Arithmetic & Logical Instructions –Shift/Rotate/Bit Instructions –Compare & Bounds

Misc. Instructions

• NOOP– does nothing

• BKPT #<data>– run breakpoint acknowledge cycle on bus

– address lines A2-A4 contain <data>

– TRAP as illegal instruction

• MOVE16 src,dst– move 16-byte aligned block

– src or dst can be pointed to by An, optionally autoincrement

» increment by 16

– src or dst can be absolute long address

» starting address of block