Talk:NS32000/Archives/2015

Page contents not supported in other languages.
From Wikipedia, the free encyclopedia

Instruction set (WIP)

The NS32000 series instructions follow a consistent pattern:

  • 1 to 3 bytes of opcode, which may specify up to 1 register operand and 2 general operands
  • An optional index byte for general operand 1 (usually the source)
  • An optional index byte for general operand 2 (usually the destination)
  • Up to 2 displacements for general operand 1, or operand 1's immediate value
  • Up to 2 displacements for general operand 2 (or operand 2's immediate value if not a destination)
  • Up to 2 additional displacements or 8-bit immediate constants, depending on the instruction.

The 2 main general-purpose operands are each specified by 5-bit fields, which specify the operand addressing mode and thus the presence of index and displacement bytes for each operand. The additional displacements or constants depend on instruction only.

A very few "quick" instructions embed a 4-bit signed immediate operand value in the instruction itself.

Addressing is generally consistently little-endian, but constants in the instruction stream (displacements and immediate constants) are stored most significant byte first.

As mentioned above, the size of the displacement is encoded in the most significant bits of the first byte of the displacement itself:

  • If the msbit of the displacement is 0, one byte supplies a 7-bit signed displacement (−64–63)
  • If the msbits of the displacement are 10, two bytes supply a 14-bit signed displacement (−8192–8191)
  • If the msbits of the displacement are 11, four bytes supply a 30-bit signed displacement (−536870912–536870911)

Processor registers

There are 8 general purpose registers (R0 through R7) and 4 special-purpose address registers:

  • FP (Frame pointer)
  • SP (Stack pointer)
  • SB (Static base, for global variable access)
  • PC (Program counter)

The addressing modes below refer to these address registers as A0 through A3, respectively.

Additional significant registers:

  • There are actually two stack pointers. Interrupts use the interrupt stack pointer SP0, while user-level code uses the user stack pointer SP1. The choice depends on the PSR's S bit (referred to as PSR.S).
  • The 32-bit INTBASE register points to an array of 127 interrupt vectors. The first 11 entries are assigned by hardware to non-vectored interrupts, non-maskable interrupts, and 9 traps that can be caused by instruction execution.
  • The 16-bit Processor Status Register (PSR) contains 6 or 7 user flags in the low byte, and 4 system flags in the high byte.
  • The 16-bit module register (MOD) points to the curent module descriptor; this is explained in more detail below. It is often combined with the PSR into one 32-bit word.
  • The 4- or 8-bit write-only configuration (CFG) register enables support for additional processor features:
    • CFG.I: NS32202 interrupt controller is present; use vectored interrupts.
    • CFG.F: NS32x81 floating-point coprocessor is present; allow FP instructions
    • CFG.M: NS32x82 memory-management unit is present
    • CFG.C: Custom coprocessor is present; enable format 15 instructions
    • CFG.FF: (32332+ only) FPU supports faster 32-bit protocol
    • CFG.FM: (32332+ only) MMU supports faster 32-bit protocol
    • CFG.FC: (32332+ only) Custom coprocessor supports faster 32-bit protocol
    • CFG.P: (32332+ only) MMU has page size ≥4K; makes detecting virtual aliases faster — Preceding unsigned comment added by 71.41.210.146 (talk) 22:44, 15 January 2012 (UTC)

Processor Status Register

The user flags are set implicitly by various instructions. Compared to other microprocessors, flag setting is extremely parsimonious; most instructions, including logical, shift, and multiply/divide instructions, do not modify the flags at all. Add and subtract instructions set only C (carry) and F (overflow); they do not set Z. Compares (integer, floating-point, or string) set Z, N and L. ABS, CHECK, string operations, and the bit operations set F. Other than that, only the instructions that explicitly modify the PSR modify the flags.

PSR bits 0 through 7 are user flags:

  • PSR.C: A traditional carry flag. This is a borrow flag when subtracting. It is not set by comparisons.
  • PSR.T: A status flag that enables program tracing.
  • PSR.L: A "lower flag", set only for comparison operations. It is set if the second operand is less than the first when interpreted as unsigned integers, i.e. op2−op1 generates a borrow. Most other microprocessors would use the C bit for this purpose.
  • (PSR bit 3 is unused)
  • PSR.V: In early NS32xxx processors, PSR bit 4 is unused. In later models (NS32532 and NS32GX32), this bit, called PSR.V, enables a trap on integer overflow. Note that this is different from other processors' V flags.
  • PSR.F: A general-purpose condition flag. It is set as an overflow flag by addition and subtraction operations, and bit test instructions copy the target bit to this flag. It is also set by the bounds-check instruction (to 1 if out of bounds), address validation instructions, and string instructions (to 1 if until/while condition is met). There is a special instruction which can trap if this bit is set.
  • PSR.Z: A traditional zero flag, if a comparison result is equal. It is not set by arithmetic or logical operations.
  • PSR.N: While this is called a "negative flag", it is different from other processors' negative flags; it is set only by comparison operations and indicates that the second operand is less than the first when interpreted as signed integers; i.e. op2−op1 is negative. Unlike other processors, this depends on the true result of the subtraction, before it is truncated to the destination width, and thus is not corrupted by integer overflow. Most other microprocessors would have conditional instructions that tested both N and V bits for this purpose.

PSR bits 8 through 15 are system flags, and may not be accessed in user mode:

  • PSR.U: User flag. If set, privileged instructions are forbidden.
  • PSR.S: Stack pointer select. Cleared by interrupt. This selects which SP register is used. Typically has same value as U.
  • PSR.P: Trace pending. The T flag is copied here once per instruction; it prevents repeated trace traps.
  • PSR.I: Interrupt enable. If clear, only NMI is accepted.
  • (PSR bits 12–15 are unused)

Modules and external references

The NS32000 series provides support for run-time linking of multiple independent "modules" of code. There is always a current module, identified by the 16-bit MOD register, which points to a 3-word module descriptor located somewhere in the first 64K of memory.

NS32k module descriptor
Offset Name Function
0 SB = Static base Base address of module's global data, loaded into SB register
4 LB = Link base Base address of link table (array of 32-bit words)
8 PB = Program base Base address of code, used by inter-module procedure call

One of those descriptor words is the link base (LB), which points to a "link table" of 32-bit references to other modules. Each reference to an external object in another module is assigned a slot in the link table, and only the link tables need to be adjusted to link modules together.

Link table entries are either 32-bit data pointers, or external procedure descriptors consisting of a 16-bit module and a 16-bit entry point offset.

External data

To reference "external" data in another module, the addressing mode specifies two displacements. The first specifies an index into the link table, where a 32-bit data pointer is stored, and the second is the offset from the resultant data pointer. The final address is [LB + 4×disp1] + disp2 (which may also, like all addressing modes, have a scaled index added to it).

External procedures

When making procedure calls between modules, things are more intricate. The "call external procedure" (CXP) instruction specifies a single displacement into the link table, and the selected word (at 4×disp + LB) contains an "external procedure descriptor" consisting of a 16-bit target module and a 16-bit entry point offset.

After saving the original module and program counter on the stack, the MOD register is loaded with the target module and the three words of the descriptor it points to are used as follows:

  • The first word is loaded into the SB register, for accessing module-local data. (The previous SB value is not saved, but will be reloaded from the module descriptor when returning.)
  • The second word is used as the new link base (LB). (NS320xx processors do not have a dedicated LB register which caches this value, but load it from the descriptor each time it is needed.)
  • The third word is the program base (PB). This is added to the 16-bit offset from the link table to produce the final PC value that control transfers to.

When returning from an external procedure (using the RXP instruction), the PC and MOD are restored from the stack, and SB is restored from the module descriptor.

Interrupts

Interrupts also take the form of external procedure calls. Instead of using the link base and a software-specified index, the interrupt base register points to an array of procedure descriptors, and the index is provided by hardware depending on the type of interrupt. On interrupt, the appropriate descriptor is fetched and an external procedure call is performed.

The only other difference is that the PSR is saved on the stack in addition to the current module and program counter.

Although it is possible to modify the MOD and SB registers independently using the LPR instruction, this is unwise unless interrupts are disabled; like external procedure calls, interrupts do not save the SB register but restore its value from the descriptor as part of interrupt return. Thus, normally the SB register should only be updated as part of changing modules.

Comparison to x86 segments

While some aspects of this resemble 80x86 segmentation, in particular the use of a 16-bit selector which points to an in-memory descriptor that is loaded into registers when the selector changes, and the use of separate "near" and "far" subroutine call/return instructions, there are significant differences. In particular, descriptors are part of the user address space and cannot be used to enforce protection boundaries. Also, there is only one current module, not separate segments for code, data, etc.

Addressing modes

General purpose operands are specified by a 5-bit field:

NS32000 operand encoding
Bit Meaning
4 3 2 1 0
0 0 n Register Rn (Register direct)
0 1 n disp(Rn) (Register indirect with displacement)
1 0 0 n disp2(disp1(An)) (Address register double indirect)
1 0 0 1 1 (Reserved; PC double-indirect is not supported)
1 0 1 0 0 #k (Immediate)
1 0 1 0 1 @disp (Absolute)
1 0 1 1 0 disp2(4×disp1(LB)) (External; peculiar to NS32000)
1 0 1 1 1 TOS (Top of stack, push or pop as appropriate)
1 1 0 n disp(An) (Address register indirect)
1 1 1 s base[Rn:S] (Indexed: base + 2S×Rn)

The top-of-stack mode pops the data from the stack pointer when used as a source operand, and pushes it when used as a destination. When used as both a source and a destination, it is equivalent to (but shorter than) 0(SP).

The indexed mode specifies an additional offset to be added to a base addressing mode.

A following index byte specifies (in its low 3 bits) an index register Rn, and (in its high 5 bits) a base operand. The index register is multiplied by a scale factor of 1, 2, 4 or 8 (indicated by a size letter S of B, W, D, or Q respectively), and added to the address of the base operand. Immediate and indexed modes are illegal as the base operand. TOS mode uses the SP as a base register without modifying it.

In contexts where a memory address is required, including as the base operand for indexed addressing mode, and some instructions which are unable to operate on register operands, register direct modes are interpreted as register-indirect with zero displacement.

String instructions

The NS32000 includes an orthogonal series of memory-to-memory string operations. These use registers R0 to R4 for fixed purposes in a way that lets the instruction be interrupted partway and seamlessly resumed. Not all instructions use all the registers. String instructions come in byte, word, and long sizes.

  • R0: Limit count. This specifies the maximum number of bytes or words to copy, and is decremented as the operation proceeds.
  • R1: Source string. This points to the beginning of the source, and is updated as the operation proceeds.
  • R2: Destination string.
  • R3: Translation table pointer. For byte operations only, a "translated" variant can be used, where a source byte is looked up in the table pointed to be R3 before being used.
  • R4: Comparison value. String operations can be halted before R0 runs out by a byte or word in the source whose (translated) value matches this register.

Options are specified by a 4-bit field:

Bit Letter Meaning
3 U Repeat until match with R4 (also set bit 2)
2 W Repeat while match with R4 (or until if bit 3 is also set)
1 B Work backward, decrementing R1 and R2
0 T Translated. Use "T" instead of size letter "B".

The mapping of bit 2 is not explained perfectly by the above table; it is set to cause matching with R4 to be a termination condition; the polarity of bit 3 controls whether the letter to use is W (if not set, repeat while match) or U (if set, repeat until match). If this happens, the PSR.F bit is set to 1, and responsible datum is not copied.

All string instructions set the PSR.F flag; it is set to 0 if the operation is terminated by the count in R0 running out, and 1 if the operation is terminated due to comparison with R4. If the W or U options are not specified, this is the only case which ever occurs.

Bit and bit-field instructions

Bits are addressed using a 32-bit "base" byte address plus a 32-bit bit offset. These are combined in a 35-bit bit address, which is consistently little-endian. (E.g. bit 11 is bit 3 of byte 1.)

The bit manipulation instructions (test, set, clear, and invert) copy the bit to the PSR.F flag before modifying it.

Bit fields add a length field, and can be accessed using "insert" and "extract" instructions to copy a general operand to a bit field and vice-versa, respectively. Extraction is unsigned; the field is zero-extended to fit the destination. In the general case, the bit offset is a register value, and the length is a constant displacement. If the offset and length are both small constants, there are "short" forms of these instructions which pack them both into an 8-bit immediate (5 bits of length−1, followed by 3 bits of offset).

Another bit-field instruction is "find first set", FFS. This updates the offset operand to the index of the first set bit in the field and clears PSR.F, or sets PSR.F=1 if the field is all zero.

Floating point

Floating point was performed by an external coprocessor: NS32081, NS32381, or a combination of the NS32580 controller and Weitek WTL 3164 FPU. The original '081 had 8 32-bit registers (F0 through F7), and even-numbered pairs were available for long (64-bit IEEE double) operands.

Later models provided 8 64-bit registers, L0 through L7, with the 32-bit registers aliased to the halves of the even-numbered L registers.

Instruction encoding

A trailing i represents an integer operand size letter: (B)yte, (W)ord or (D)oubleword. These are 8, 16 and 32 bits, and represented by the values 0, 1 and 3 in the size field, respectively. The value 2 is used to encode other instructions. A trailing f indicates a floating-point operand size letter, encoded using a 1-bit size field: (L)long (64-bit, size bit 0), or (F)loat (32-bit, size bit 1). Note that the terms "long" and "double" are swapped relative to the C language.

NS32000 operand size encodings
Abbrev Encoding Suffix Meaning
size 00 B Byte, 8 bit integer
01 W Word, 16 bit integer
11 D Doubleword, 32-bit integer
f 0 L Long, 64-bit floating point
1 F Float, 32-bit floating point
c 0 Q Quad word, 64-bit coprocessor value
1 D Doubleword, 32-bit coprocessor value

The most common instructions are 2 bytes long, and have the operand size in the least-significant bits of the first byte. The unused integer operand size encoding "10" is used for 1-byte instructions (whose lsbits are "010"), and 3-byte instructions (whose lsbits are "110"). 3-byte instructions encode the operand size in the lsbits of the second byte.

The opcode assignments are clearest if presented with the least significant bit (bit 0) first, and opcodes sorted as if lower-numbered bits were more significant, so the tables below lists them that way. Embedded values (such as register numbers) still have their most significant bits in higher-numbered bit positions. Also, binary numbers included in running text without explicit bit-number headers use the conventional msb-first ordering.

NS32000 series instruction size encoding
Byte 0 Description
0 1 2 3 4 5 6 7
0 0 opcode 2-byte instruction, (8-bit) byte operands
1 0 opcode 2-byte instruction, (16-bit) word operands
1 1 opcode 2-byte instruction, (32-bit) doubleword operands
0 1 0 opcode 1-byte instruction
0 1 1 opcode 3-byte instruction; size in lsbits of 2nd byte
NS32000 series 1-byte instructions
Byte 0 Description
0 1 2 3 4 5 6 7
0 1 0 0 opcode Format 1 instructions: Procedure calls and returns
0 1 0 0 0 0 0 0 BSR disp (Push PC, PC += disp)
0 0 0 1 RET disp (Pop PC, then SP += disp)
0 0 1 0 CXP disp (Call external procedure; descriptor at LB + 4*disp)
0 0 1 1 RXP disp (Return from external procedure; pop PC and MOD, then SP += 2 + disp)
0 1 0 0 RETT disp (Return from trap: RETI, then SP += disp)
0 1 0 1 RETI (Return from interrupt: pop PC, pop MOD, pop PSR)
0 1 1 0 SAVE [register list] (Push multiple registers to stack, 8-bit immediate map)
0 1 1 1 RESTORE [register list] (Restore multiple registers from stack)
1 0 0 0 ENTER [register list], disp (Push FP, FP = SP, SP −= disp, push registers)
1 0 0 1 EXIT [register list] (Pop registers, SP = FP, pop FP)
1 0 1 0 NOP: No operation.
1 0 1 1 WAIT: Wait for interrupt.
1 1 0 0 DIA: Hardware breakpoint, branch to self.
1 1 0 1 FLAG (if PSR.F=1, take flag trap)
1 1 1 0 SVC (supervisor call trap)
1 1 1 1 BPT (breakpoint trap)
0 1 0 1 condition Format 0 instructions: If condition is true, PC += disp
0 1 0 1 0 0 0 0 BEQ disp (branch if PSR.Z=1)
0 0 0 1 BNE disp (branch if PSR.Z=0)
0 0 1 0 BCS disp (branch if PSR.C=1)
0 0 1 1 BCC disp (branch if PSR.C=0)
0 1 0 0 BHI disp (branch if PSR.L=1)
0 1 0 1 BLS disp (branch if PSR.L=0)
0 1 1 0 BGT disp (branch if PSR.N=1)
0 1 1 1 BLE disp (branch if PSR.N=0)
1 0 0 0 BFS disp (branch if PSR.F=1)
1 0 0 1 BFC disp (branch if PSR.F=0)
1 0 1 0 BLO disp (branch if (PSR.L|PSR.Z) = 0)
1 0 1 1 BHS disp (branch if (PSR.L|PSR.Z) = 1)
1 1 0 0 BHI disp (branch if (PSR.N|PSR.Z) = 0)
1 1 0 1 BLS disp (branch if (PSR.N|PSR.Z) = 1)
1 1 1 0 BR disp (branch always)
1 1 1 1 B?? disp (branch never)
NS32000 series 2-byte instructions
Byte 0 Byte 1 Description
0 1 2 3 4 5 6 7 0 1 2 3 4 5 6 7
size opcode dest src Format 4 instructions: Common 2-operand arithmetic
size 0 0 0 0 dest src ADDi src, dest (dest += src)
size 0 0 0 1 dest src SUBi src, dest (dest −= src)
size 0 0 1 0 dest src ADDCi src, dest (dest += src + carry)
size 0 0 1 1 dest src SUBCi src, dest (dest −= src + carry)
size 0 1 0 0 dest src BICi src, dest (dest &= ~src)
size 0 1 0 1 dest src ANDi src, dest (dest &= src)
size 0 1 1 0 dest src ORi src, dest (dest |= src)
size 0 1 1 1 dest src XORi src, dest (dest ^= src)
size 1 0 0 0 dest src CMPi src, dest (dest − src, set flags only)
size 1 0 0 1 dest src ADDR src, dest (dest = &src, AKA Load Effective Address)
1 1 1 0 0 1 dest 0 1 1 0 1 LXPD n,dest ("load external procedure descriptor" = ADDR EXT(n), dest)
size 1 0 1 0 dest src MOVi src, dest (dest = src)
size 1 0 1 1 base offset TBITi base, offset (F = bit at base+offset)
size 1 1 x Format 2 or 3; see below
size 1 1 opcode k dest Format 2 instructions; k is a 4-bit signed immediate constant.
size 1 1 0 0 0 k dest ADDQi #k,dest
size 0 0 1 k dest ACBi #k, dest, disp (dest += #simm4, branch to disp(PC) if non-zero)
size 0 1 0 k dest SPRi special, dest (k specifies system register)
size 0 1 1 k src LPRi special, src (k specifies system register)
size 1 0 0 k src CMPQi #k, src (src − k, set flags only)
size 1 0 1 k dest MOVQi #k, dst (dst = k)
size 1 1 0 cond dest Scondi dst (If condition is true, set dest = 1; see BEQ et. al.)
size 1 1 1 x Format 3; see below
size 1 1 1 1 1 0 opcode src Format 3 instructions: Common single-operand instructions
1 1 1 1 1 1 1 0 0 0 0 src CXPD dest (Call external procedure using descriptor at src)
0 0 1 (Undefined, illegal instruction)
1 1 0 1 0 addr JUMP addr (PC = addr)
1 1 0 1 1 addr JSR addr (Push PC, PC = addr)
s 0 1 0 0 src BICPSRi src (PSR &= ~src)
size 1 0 1 src ADJSPi src (SP −= src)
s 0 1 1 0 src BISPSRi src (PSR |= src)
size 1 1 1 src CASEi src (PC += src)
1 1 1 1 1 1 x (Undefined, illegal instruction)

For the LPR and SPR instructions, the 4-bit k value specifies the processor register as:

  • 0: User stack pointer, SP1
  • 8: FP
  • 9: SP (current SP, based on PSR.S)
  • 10: SB
  • 13: PSR (only allowed when PSR.U=0)
  • 14: INTBASE (only allowed when PSR.U=0)
  • 15: MOD

Values of 1–7, 11 and 12 are undefined. Note that changing SB or MOD this way is dangerous unless interrupts are disabled, as SB is not saved across interrupts, but rather restored from the descriptor pointed to by MOD.

NS32000 series 3-byte instructions
Byte 0 Byte 1 Byte 2 Description
0–4 5 6–7 0 1 2 3 4 5 6 7 0 1 2 3 4 5 6 7
01100 xxx Format 19: Undefined, illegal instruction
01101 nnn Format 15: Custom coprocessor operations
01101 000 size opcode x k src Format 15.0: Privileged operations
100 size c opcode dest src Format 15.1: Conversion operations
101 c x opcode dest src Format 15.5: General calculate/move operations
111 c x opcode dest src Format 15.7: General calculate/move operations
01110000 size opc. 0 0 0 T B W U — 0 — Format 5: String instructions
01110000 size 0 0 0 0 0 0 B W U — 0 — MOVSi: move from string1 to string2
0 0 0 0 1 B W U — 0 — MOVST: move translated from string1 to string2
size 0 1 k 0 SETCFG: Set CFG register to 8-bit value k.
size 1 0 0 B W U — 0 — CMPSi: Compare string1 to string2
0 0 1 0 1 B W U — 0 — CMPST: Compare translated string1 to string2
size 1 1 0 B W U — 0 — SKPSi: Skip string 1 (returns unskipped length in R0)
0 0 1 1 1 B W U — 0 — SKPST: Skip translated string 1 (returns unskipped length in R0)
1 Undefined, illegal instruction
1 Undefined, illegal instruction
1 Undefined, illegal instruction
01110001 Format 18: Undefined, illegal instruction
01110010 size opcode dest src Format 6: Additional 2-operand instructions.
01110010 size 0 0 0 0 dest src ROTi: Rotate dest left by src.B bits (right if src is negative)
0 0 1 0 (Undefined, illegal instruction)
size 1 0 0 0 dest src ASHi: Arithmetic shift left (src always byte, right if negative)
size 1 0 1 0 dest src LSHi: Logical shift left (src always byte, right if negative)
size 0 0 0 1 dest src NEGi: dest = −src, sets C and F.
size 0 0 1 1 dest src ABSi: dest = |src|, sets F.
size 1 0 0 1 dest src NOTi: dest = !src
size 1 0 1 1 dest src COMi: dest = ~src
size 0 1 0 0 base offset CBITi: Copy bit at base+offset to F, then clear
size 0 1 1 0 base offset SBITi: Copy bit at base+offset to F, then set
size 1 1 0 0 base offset CBITIi: Clear bit, interlocked (atomic)
size 1 1 1 0 base offset SBITIi: Set bit, interlocked (atomic)
0 1 0 1 (Undefined, illegal instruction)
size 0 1 1 1 base offset IBITi: Copy bit at base+offset to F, then invert
size 1 1 0 1 dest src SUBPi (subtract packed decimal)
size 1 1 1 1 dest src ADDPi (add packed decimal)
01110011 size opcode dest src Format 7: Additional 2-operand instructions.
01110011 size 0 0 0 0 dest src MOVMi src, dest, len: Move multiple, length is displacement constant
size 1 0 0 0 dest src CMPMi src, dest, len: Compare multiple
size 0 1 0 0 base src INSSi base, dest, #offset3, #len5 (insert bit string short)
size 1 1 0 0 dest base EXTSi src, base, #offset3, #len5 (extract bit string short)
0 0 0 0 1 0 dest src MOVXBW: Move byte to word, sign-extending
0 0 1 0 1 0 dest src MOVZBW: Move byte to word, zero-extending
s 0 0 1 1 0 dest src MOVZiD: Move size to doubleword, zero-extending
s 0 1 1 1 0 dest src MOVXiD: Move size to doubleword, sign-extending
size 0 0 0 1 dest src MULi: dest *= src
size 1 0 0 1 dest src MEIi: dest[1:0] = dest[0] * src (unsigned, double-size destination)
0 1 0 1 (Undefined, illegal instruction)
size 1 1 0 1 dest src DEIi: dest[0] = dest[1:0] % src, dest[1] = dest[1:0] / src (unsigned)
size 0 0 1 1 dest src QUOi: dest /= src (signed, round to 0)
size 1 0 1 1 dest src REMi: dest %= src (signed, round to 0)
size 0 1 1 1 dest src MODi: dest %= src (signed, round to −∞)
size 1 1 1 1 dest src DIVi: dest /= src (signed, round to −∞)
011101 opc. size o reg dest src Format 8: 3+-operand instructions.
011101 00 size 0 reg dest src EXTi (extract bitfield: copy disp bits starting reg bits after src to dest)
10 size 0 reg dest src CVTP: dest = ADDR(src)*8 + reg (convert to bitfield pointer)
01 size 0 reg dest src INSi (insert bitfield: copy disp bits from src to reg bits after dest)
11 size 0 reg bounds src CHECKi: reg = src−lower_bound, or F=1 if out of bounds
00 size 1 reg index length INDEXi: reg = reg * (length+1) + index
10 size 1 reg dest src FFSi: Search starting dst.B bits after src; reg is length.
01 size 1 1 0 0 dest src MOVSUi: Move from supervisor to user space
01 size 1 1 1 0 dest src MOVUSi: Move from user to supervisor space
11 1 (Undefined, illegal instruction)
01111000 size opcode 0 k src Format 14: System instructions
01111000 size 0 0 0 0 0 — 0 — src RDVALi: Test if src is readable in user mode, result in PSR.F
size 1 0 0 0 0 — 0 — dest WRVALi: Test if dest is writeable in user mode, result in PSR.F
size 0 1 0 0 0 k src LMR: Load MMU reg k from src
size 1 1 0 0 0 k dest SMR: Store MMU reg k to dest
x 1 x 0 (Undefined, illegal instruction)
0 x 1 0 (Undefined, illegal instruction)
1 1 1 0 0 1 0 D I A 0 src CINV [flags],src: Cache invalidate. A=All (0=line containing src), D=Data, I=instruction
x 1 x 1 0 (Undefined, illegal instruction)
x 1 1 0 (Undefined, illegal instruction)
01111001 Format 13: Undefined, illegal instruction
01111010 Format 16: Undefined, illegal instruction
01111011 Format 17: Undefined, illegal instruction
01111100 size f opcode dest src Format 9: Floating point conversions
01111100 size f 0 0 0 dest src MOVif: Convert integer to floating-point
1 1 f 1 0 0 — 0 — src LFSR: FSR = src
0 0 1 0 1 0 dest src MOVLF: Convert (64-bit) long float to (32-bit) float
1 1 0 1 1 0 dest src MOVFL: Convert (32-bit) float to (64-bit) long float
size f 0 0 1 dest src ROUNDfi: Convert floating-point to integer, round to nearest
size f 1 0 1 dest src TRUNCfi: Convert floating-point to integer, round to 0
1 1 f 0 1 1 dest — 0 — SFSR: dest = FSR
size f 1 1 1 dest src FLOORfi: Convert floating-point to integer, round to −∞
01111101 f 0 opcode dest src Format 11: Floating-point operations
01111101 f 0 0 0 0 0 dest src ADDf: dest += src
f 0 1 0 0 0 dest src MOVf: dest = src
f 0 0 1 0 0 dest src CMPf
f 0 0 0 1 0 dest src SUBf: dest −= src
f 0 1 0 1 0 dest src NEGf: dest = −src
f 0 0 0 0 1 dest src DIVf: dest /= src
f 0 0 0 1 1 dest src MULf: dest *= src
f 0 1 0 1 1 dest src ABSf: dest = |src|
f 0 other dest src (Opcodes 0011 & 1010 alias to CMPf, x110 to ADDf, others to MOVf)
01111110 Format 10: Undefined, illegal instruction
01111111 f 0 opcode dest src Format 12: Floating-point extensions (not on NS32081)
01111111 f 0 0 0 0 0 dest src REMf: dest %= src
f 0 1 0 0 0 dest src SQRTf: dest = SQRT(src) (32580 only)
f 0 0 1 0 0 src2 src POLYf: Accumulate polynomial in f0 (f0 = f0 * src + src2, 32381 only)
f 0 1 1 0 0 src2 src DOTf: Accumulate dot product in f0 (f0 += src * src2, 32381 only)
f 0 0 0 1 0 dest src SCALBf: dest *= 2src, src must be integer (32381 only)
f 0 1 0 1 0 dest src LOGBf: dest = unbiased exponent of src (32381 only)
0 x 1 1 0 (Undefined, illegal instruction)
0 x 0 0 1 (Undefined, illegal instruction)
f 0 0 1 0 1 src2 src MACf: Multiply accumulate (f1 += src * src2, 32580 only)
0 1 1 0 1 (Undefined, illegal instruction)
f 0 0 0 1 1 dest src ATAN2f (?? listed in 32332 data sheet)
f 0 1 0 1 1 dest src SICOSf, results in dest & f0 (?? listed in 32332 data sheet)
0 x 1 1 1 (Undefined, illegal instruction)

This is being worked on here until is ready for inclusion in the article. Main reference, see e.g. page 143 et seq. Detailed instruction definitions begin on p. 1259. Also 32532 data sheet and NS32381 data sheet. 71.41.210.146 (talk) 08:40, 25 April 2010 (UTC)