This is an old revision of the document!


Sources of information

Instruction set documentation archived from sunplus website (chapter 19) - local copy

CPU

The V-Smile processor is a Sunplus uN'SP implementing version 1.1 of the ISA (source: this is how the SPG200 projects in uN'SP IDE are configured).

The documentation below was extracted from the datasheet of another chip that implements a later version (1.2). Instructions that are available only in that later version are annotated to avoid confusion, but kept for reference in case it is useful to someone else.

This document does not include information about uN'SP 2.0 architecture which is irrelevant to us and possibly not compatible (there are more registers, which would not fit the existing instruction format).

Registers

IDNameFunction
0 SP Stack Pointer
1 R1 General Purpose
2 R2 General Purpose
3 R3 General Purpose
4 R4 General Purpose
5 BP Base Pointer
6 SR Status Register
7 PC Program Counter

R3 and R4 can be used to form a 32-bit register pair for some instructions, this pair is noted MR.

Shadow Registers

Only in ABI 1.2

Registers R1-R4 have 'shadow' copies that can be enabled via the SECBANK instruction. When enabled, all reads and writes to R0-R4 are redirected to SR1-SR4. This can be used to avoid backing up, and restoring registers during Interrupt routines.

Status Register

The status register contains various status flags, as well as the current code segment (CS) and data segment (DS) base addresses.

Bits NameDescription Notes
0-5 CS Code Segment Auto-incremented when PC wraps around
6 C Carry Flag Set if a carry occurred
7 S Sign Flag Set if the result is negative (two's complement)
8 Z Zero Flag Set when the result is zero
9 N Negative FlagSet when the MSB of the result is 1
10-15DS Data Segment Auto incremented with pre/post inc/dec addressing mode as needed

Flags register

Only in ABI 1.2

This register is not accessible as a general purpose register. It can be written to by some specific instructions.

161514 13 12 10-7654 3-0
- AQBNKFRAFIRSB FIINEIRQ PRI
  • AQ: Flag for DIV/DIVS instructions
  • BNK: Set when the shadow registers are active (SECBANK ON)
  • FRA: Fraction mode
  • FIR: FIR_MOV mode
  • SB: shift buffer used by the SHIFT instruction. It makes it easy to shift values that use more than 16 bits
  • F: FIQ enable (set by the INT and FIQ instructions)
  • I: IRQ enable (set by the INT and IRQ instructions)
  • INE: IRQ nesting mode
  • IRQ PRI: current IRQ priority

In ABI 1.1 and older, there are separate SB registers for normal, FIQ and interrupt mode. The F, I and FIR flags exist, but are not exposed as a register.

Address Space

The memory map of the uN'SP is split into 64K sized pages. The entire 4M address space of the CPU is divided into 64 pages (0x00-0x3F). The current page can be selected via the segment registers, CS (for instruction fetch) and DS (for data operations).

When code execution reaches the end of the current page, the CS register is auto-incremented by the hardware.

Interrupts

The interrupt vector table is at the end of the first memory page. It contains addresses of the handlers for each interrupt, including the software interrupt (BREAK instruction) and CPU reset. Since the addresses are only 16bit, all handlers must be in the first memory page.

VectorName
0xFFF5BREAK
0xFFF6FIQ
0xFFF7RESET
0xFFF8IRQ0
0xFFF9IRQ1
0xFFFAIRQ2
0xFFFBIRQ3
0xFFFCIRQ4
0xFFFDIRQ5
0xFFFEIRQ6
0xFFFFIRQ7

Instruction Set

These tables detail the instruction both in the format used by the official uN'SP toolchain as well as the mnemonic form used by the free for non-commercial use vasm.

NOTE: Unless otherwise specified, instructions that operate on memory ignore DS and only operate on page 0 (0x0000-0xFFFF). Instruction varients that allow a “D:” prefix generate a full 22-bit address via (DS << 16 | addr)

Data Transfer

Load

Instruction Smasm Form Notes Flags Affected
Rd = Value mov rd, value 6 and 16-bit variants available NZ
Rd = [BP + offset] mov rd, [BP + offset] Offset is limited to 6 bits NZ
Rd = [addr] mov rd, [addr] 6 and 16-bit variants available NZ
Rd = Rs mov rd, rs NZ
Rd = {D:}[Rs] mov rd, {D:}[rs] Optional data-segment qualifier (D:)NZ
Rd = {D:}[++Rs] mov rd, {D:}[++rs] NZ
Rd = {D:}[Rs–] mov rd, {D:}[rs–] NZ
Rd = {D:}[Rs++] mov rd, {D:}[rs++] NZ

Store

Instruction Smasm Form Notes Flags Affected
[BP + offset] = Rd mov [BP + offset], rd Offset is limited to 6 bits
[addr] = Rd mov [addr], rd
{D:}[Rs] = Rd mov {D:}[rs], rd Optional data-segment qualifier (D:)
{D:}[++Rs] = Rd mov {D:}[++rs], rd
{D:}[Rs–] = Rd mov {D:}[rs–], rd
{D:}[Rs++] = Rd mov {D:}[rs++] = rd

Push/Pop

Instruction Smasm Form Notes Flags Affected
PUSH Rx, Ry to [Rs] push rx-ry [rs] rx-ry signifies a range of registers to push
PUSH Rx to [Rs] push rx, [rs] Push a single register
POP Rx, Ry from [Rs] pop rx-ry [rs] rx-ry signifies a range of registers to pop
POP Rx from [Rs] pop rx, [rs] Pop a single register

ALU operations

All these operations have similar syntax and support the same addressing modes

Mnemonic smasm syntax Description Flags affected
Rd += Rs ADD Rd, Rs Add NZSC
Rd += Rs,carry ADC Rd, Rs Add with carry
Rd -= Rs SUB Rd, Rs Subtract
Rd -= Rs,carry SBC Rd, Rs Subtract with carry
CMP Rd, Rs CMP Rd, Rs Compare (same effect on flags as sub)
Rd = -Rs NEG Rd, Rs Negate NZ
Rd ^= Rs XOR Rd, Rs Exclusive OR
Rd |= Rs OR Rd, Rs Bitwise OR
Rd &= Rs AND Rd, Rs Bitwise AND
Test Rd, Rs TEST Rd, Rs Same effect on flags as bitwise AND

Addressing modes

For all ALU operations, the following addressing modes are available:

Syntax smasm syntax Description
R1 += R2 ADD R1, R2 Register
R1 += R2 ASR 1 ADD R1, R2 ASR 1 Register with shift (ASR, LSL, LSR, ROR or ROL) up to 4 bits
R1 += 23 ADD R1, #23 6-bit immediate value
R1 = R2 + 1234 ADD R1, R2, #1234 3-operand 16-bit immediate
R1 += [12] ADD R1, [12] Direct (get value at 6-bit address 12)
R1 = R2 + [1234]ADD R1, R2, [1234]Direct 3-operand (get values at R2 and 16-bit address 1234)
[1234] = Rd + RsADD [1234],Rd,Rs Direct-store 3-operand
R1 += [R2] ADD R1, [R2] Indirect (register used as pointer)
R1 += [R2++] ADD R1, [R2++] … with post-increment
R1 += [R2–] ADD R1, [R2–] … with post-decrement
R1 += [++R2] ADD R1, [++R2] … with pre-decrement
R1 += D:[R2] ADD R1, D:[R2] … in data segment (address is (DS « 16) | R2))
R1 += [BP+12] ADD R1, [BP+12] 6-bit displacement from BP (Rd cannot be PC)

It is possible to combine indirect with data segment and increments and decrements in the same instruction.

The shift operations use the shift buffer (see “shift operations” section below). In particular the ROR and ROL operations do a 20-bit rotation resulting in bits from the shift buffer moving into the destination register.

Bit shift instructions

Only in ISA 1.2

Flags affected: NZ

Unlike the shift embedded in the parameters of an ALU operation, this is an independant opcode. The smasm syntax makes this clear, in the xasm syntax it can be hard to distinguish the different cases.

The main differences in behavior are:

  • This instruction can shift by up to 16 bits, instead of just 4
  • The shift operand can be a constant, but also a register, for variable shifts

Given a starting register like this:

Bits 15-0
Rs15-Rs0

And the SR bits in the flags register:

Bits 3-0
SR3-SR0

The result of the shift operations are (for a shift by 3 bits):

ASR

Arithmetic shift right (signed divide by two)

Bits 15-13Bits 12-0
Rs15 Rs15-Rs3
Bits 3-1Bit 0
Rs2-Rs0 SR3

LSL

Logical shift left (multiply by two)

Bits 15-3Bits 2-0
Rs12-Rs0 000
Bit 3Bit 2-0
SR0 Rs15-Rs13

LSR

Logical shift right (unsigned divide by two)

Bits 15-13Bits 12-0
0 Rs15-Rs3
Bits 3-1Bit 0
Rs2-Rs0 SR3

ROL

Rotate left

Bits 15-3Bits 2-0
Rs12-Rs0 SR3-SR1
Bit 3Bit 2-0
SR0 Rs15-Rs13

ROR

Rotate right

Bits 15-13Bits 12-0
SR2-SR0 Rs15-Rs3
Bits 3-1Bit 0
Rs2-Rs0 SR3

ASR-OR, LSL-OR, LSR-OR

These operations do the shift as documented above, then OR it with the original register value.

xasm syntax:

R1 |= R1 LSL R2

32-bit shifts

The assembler has a shorthand instruction for 32bit shifts (it is assembled as two consecutive 16bit instructions):

MR |= R4 asr 1

FIXME

  • The documentation says ROL and ROR can't use R4 as a source register?

Bit operations

Only in ISA 1.2

Flag affected: Z

TSTB - Test bit

CLRB - Clear bit

SETB - Set bit

INVB - Flip bit

The destination operand can be a register, or an indirect register with or without D: prefix. The source operand can be a register or an immediate value (in the range 0-15). If it is a register only the 4 LSB are used.

The Z flag is set according to the value of the bit before the operation is executed.

CLRB R3,2 Copies bit 2 of R3 in the Z flag, then clears the bit in the register.

TSTB D:[R1],13 copies bit 13 of D:[R1] in the Z flag.

Multiplication and division

Multiplication

Multiplication result is stored in R3 and R4 (the register pair is called MR)

Instruction Smasm FormNotes Flags Affected
MR = Rd x Rs MUL Rd, Rs Signed multiplication
MR = Rd x Rs,us MULU Rd, Rs Rd is unsigned, Rs is signed
MR = Rd x Rs,uu MULUU Rd, Rs Unsigned multiplication ISA 1.2 only
MR = [Rd] x [Rs],n MACU (Rd),(Rs),n Multiply-accumulate two sets of N signed values pointed by Rd and Rs S
MR = [Rd] x [Rs],us,nMAC (Rd),(Rs),nMultiply-accumulate two sets of N values pointed by Rd (unsigned values) and Rs (signed values)
MR = [Rd] x [Rs],uu,nMAC (Rd),(Rs),nMultiply-accumulate two sets of N unsigned values pointed by Rd and Rs ISA 1.2 only

Multiply-accumulate operations do the computation with 36-bit precision. The result is stored in MR and the shift buffer in the flags register. S flag is set if there is an overflow.

Division

Only in ISA 1.2

DIVS MR, R2

DIVQ MR, R2

These instructions implement 32-bit division. There are two divide primitives, DIVS and DIVQ. A single precision divide, with a 32-bit numerator and a 16-bit denominator, yielding a 16-bit quotient, executes in 16*3 cycles. Higher precision divides are also possible. The division can be either signed or unsigned, but both the numerator and denominator must be the same. Place the 32-bit numerator at R4: R3, the 16-bit denominator at R2 and clear the AQ flag then executed with the divide primitives, DIVS and DIVQ. Repeated execution of DIVQ implements a non-restoring conditional add-subtract division algorithm. At the conclusion of divide operation the quotient will be placed at R3.

FIR_MOV

FIR_MOV ON

FIR_MOV OFF

Affects the FIR bit in the flags register.

When enabled, the multiply-accumulate instructions automatically increment Rd and Rs by n. When disabled, they do not change Rd and Rs.

FRACTION

FRACTION ON

FRACTION OFF

Only in ISA 1.2

When enabled, multiply operations shift the result left by 1 bit

Other operations

EXP

Only in ISA 1.2

R1 = EXP R2

Returns the number of sign bits in R2, that is, count the from the MSB the number of bits that all have the same value.

Data Segment Access

Only in ISA 1.2

DS = Rs

Rd = DS

DS = 12

smasm syntax:

MOV DS, Rs

MOV Rd, DS

MOV DS, 12

Set or Get the DS value from SR. The other 10 bits of Rd are set to 0.

On older architecture versions, this has to be done manually by accessing SR like a normal register (masking with AND and OR).

Program Flow

Conditional jumps

Syntax:

JMP label

The target address is stored as a 6 bit displacement and a separate bit indicating forward or backward jump. So this can only jump back and forward 63 addresses.

InstructionSmasm FormNotes Flags Affected
JCC,JB,JNAE Jump if C=0
JCS,JNB,JAE Jump if C=1
JSC,JGE,JNL Jump if S=0
JSS,JNGE,JL Jump if S=1
JNE,JNZ Jump if Z=0
JZ,JE Jump if Z=1
JPL Jump if N=0
JMI Jump if N=1
JBE,JNA Jump if Z=1 or C=0
JNA Jump if Z=1 or C=0
JNBE,JA Jump if Z=0 and C=1
JLE,JNG Jump if Z=1 or S=1
JNLE,JG Jump if Z=0 and S=0
JVC Jump if N=S
JVS Jump if N != S
JMP Jump always

xasm supports the syntax SJMP for “smart jump” that will automatically be converted to a jump + GOTO if the address is outside the reachable range for a normal jump.

Other instructions

CALL

CALL label

  • PC and SR are pushed to the stack
  • PC and the code segment part of SR are loaded with the 22-bit parameter address

Because SR is pushed automatically, flags are always saved accross a CALL/RETF

Indirect call

Only in ISA 1.2

CALL MR

The target address is formed from MR (R4 and R3). R4 contains the segment (loaded into CS) and R3 contains the offset (loaded into PC).

GOTO

Like a call, but does not save PC and SR on the stack. Both direct (ISA 1.1) and indirect (ISA 1.2 only) versions are available.

In ISA 1.0, GOTO does not set the CS: so it is not possible to jump outside the current segment. In ISA 1.1 and above this problem is fixed.

RETF

Return from function. Pops PC and SR from the stack.

RETI

Return from interrupt. In addition to what RETF does, also restores the interrupt flag.

BREAK

Jumps to the BREAK software IRQ handler.

NOP

Do nothing.

Interrupt control

IRQ enable/disable

InstructionSmasm FormNotes Flags Affected
IRQ OFF Disable interrupts
IRQ ON Enable interrupts
FIQ OFF Disable fast interrupts
FIQ ON Enable fast interrupts
INT FIQ Enable FIQ, disable IRQ
INT FIQ,IRQ Enable FIQ and IRQ
INT IRQ Disable FIQ, enable IRQ
INT OFF Disable FIQ and IRQ

SECBANK

Only in ISA 1.2

SECBANK ON

SECBANK OFF

Switches to the alternate registers SR1-SR4 or restores the normal R1-R4.

The status is stored in the flags register.

IRQNEST

Only in ISA 1.2

IRQNEST ON

IRQNEST OFF

Enables IRQ nesting. IRQ will save the flags register on the stack (in addition to SR and PC) and the RETI instruction will restore it.

The IRQ priority can be set in FR to determine which interruptions are allowed to happen.

The status is stored in the INE bit of the flags register.

Direct access to FR register

Only in ISA 1.2

FR = Rs

Rd = FR

smasm syntax:

MOV FR, Rs

MOV Rd, FR

cpu.1615579384.txt.gz · Last modified: 2021/03/12 21:03 by pulkomandy
CC Attribution 4.0 International
Driven by DokuWiki Recent changes RSS feed Valid CSS Valid XHTML 1.0