Appendix B. SPARC Instruction Set

Now that you have a feel for the SPARC processor hardware, let’s talk about the native instruction set and software language of the SPARC processor. In this section we’ll cover most of the instructions in some detail; however, we’ll refer you to The SPARC Architecture Manual, Version 8 from SPARC International as the definitive reference.

Instruction set summary

The SPARC instruction set consists of 69 instructions. Each instruction takes exactly 32 bits. The complete set is often described as having six basic categories, as follows:

We will cover each of these categories in detail.

Operation codes & instruction formats

When discussing a processor’s native language, we sometimes talk about the individual operation codes (opcodes) of each instruction. This discussion often involves learning the specific bit-by-bit organization of the instructions, or instruction formats.

The SPARC processor uses three basic instruction formats for the complete instruction set. As a software analyst examining system crash dumps, it is rare indeed that you will ever need to look at the raw instructions of a program in hexadecimal, because kadb and adb will be converting the values into assembly language for you. This process is referred to as “disassembling.” Should you want to explore this extremely detailed aspect of the instruction set, please refer to The SPARC Architecture Manual, Version 8.

The SPARC assembly language instructions, with which we will be working, and the SPARC opcodes are usually the same. We will point out the few cases where they differ.

Assembly language syntax

When looking at SPARC assembly language via adb, we will see adb’s disassembled interpretation of the opcodes it finds. In very simple terms, the general syntax of assembly instructions we will see are as follows:

label:  instruction source destination 
        instruction label 

As we discuss each category of instruction, we will show the syntax of the instructions and some examples of assembly language code.

Instruction syntax

Throughout the rest of this chapter, while discussing the individual instructions in the SPARC instruction set and their syntax, we will use the following conventions. These are the same conventions you will find in The SPARC Architecture Manual, Version 8.

Registers

When we refer to reg in the instruction syntax, we are referring to any Integer Unit, general-purpose register name. It may be any one of the following:

%r0 through %r31

General-purpose registers

%g0 through %g7

Globals

(aka %r0 through %r7)

%o0 through %o7

Out registers

(aka %r8 through %r15)

%l0 through %l7

Local registers

(aka %r16 through %r24)

%i0 through %i7

In registers

(aka %r25 through %r31)

%fp

Frame pointer

(aka %i6 and %r30)

%sp

Stack pointer

(aka %o6 and %r14)

When we refer to sreg and dreg in the instruction syntax, one general-purpose register is the source register and the other is a destination register.

Note

In SPARC assembly language, the percent sign, %, must be used in front of all register names.

The symbols freg and creg will be used in instruction syntax to represent any floating-point processor and coprocessor register names.

%f0 through %f31

The floating-point registers

%c0 through %c31

Possible coprocessor registers

When we refer to sfreg and dfreg in the instruction syntax, one floating-point register is the source register and the other is a destination register.

Special symbol names

The following special symbols are used in SPARC assembly language. You’ll recognize most of these from the chapter about the SPARC processor. We will discuss the last two, %hi and %lo, later on in this chapter.

%psr

Processor state register

%fsr

Floating-point state register

%csr

Coprocessor state register

%wim

Window invalid mask register

%tbr

Trap base register

%y

Multiply / divide register

%fq

Floating-point queue

%cq

Coprocessor queue

%hi

Unary operator that extracts the high 22 bits of its operand

%lo

Unary operator that extracts the low 10 bits of its operand

Operand values

SPARC instructions use operands that may include the following symbols.

simm13

A signed immediate constant that can be represented in 13 bits.

const22

A constant that can be represented in 22 bits.

as

An alternate address space identifier (0 to 255)

value

An unspecified, integer value

Register values

When discussing instructions that access memory, we will use [address ] in the instruction syntax to represent any of the following methods of deriving a memory address.

reg

Address = Contents of register (address is stored in register)

simm13

Address = Signed 13-bit immediate value or offset

reg +/- simm13

Address = Contents of register plus or minus an offset value

reg1 + reg2

Address = Value of one register + value of a second register

Some instructions only use register values (the above methods, which don’t involve use of a simm13 offset value). When discussing those instructions, we will use [regaddr ] in the instruction syntax instead of [address ].

For instructions that can only use either one register or a signed 13-bit immediate value to represent an address or other value, we will use reg_or_imm in the instruction syntax.

When talking about the trap instructions, we will use sw_trap_num in the instruction syntax to represent software trap numbers, which may be any value from 0 to 127.

Labels

When discussing instructions that branch or jump, we will use label to represent a location within the routine. Labels in SPARC assembler may consist of alphanumeric characters (a–z, A–Z, 0–9), underscores (_), dollar signs ($), and periods (.). The first letter of a label cannot be a decimal digit (0-9). When examining disassembled code (from adb), labels used by branch instructions will usually be shown as a variable (routine name) plus an offset value.

Note that the 4.x bundled C compiler automatically prefaced C variable and function names with an underscore (_). This convention allows you to identify assembly code labels, which are normally not defined with a leading underscore unless they are to be callable from C-language functions. This convention was discarded with the ANSI C compilers.

Memory access instructions

Unlike some other instruction sets, the SPARC Version 8 instruction set never embeds memory addresses into the instructions. Thus, no instructions can directly modify the contents of memory. Instead, all data manipulation is performed in the SPARC general purpose registers.

Two basic memory access operations can be performed on SPARC systems. These are “load” and “store” or, in other words, “read from memory” and “write to memory.” There are several variations of these two operations which handle different data sizes.

Using load instructions, data is read in from memory and stored into a register. Once in a register, the data can be manipulated as needed. Using store instructions, the modified data is written back to memory.

Load instructions

The load instruction is used to read a value stored in memory, placing the data into a register when it can then be manipulated. Here are six commonly used load instructions:

Table B-1. SPARC load instructions

Instruction Syntax

Operation

ld [address ], reg

Read word from memory (address) and load into register

ldd [address ], reg

Read double word and load into register and next register

ldsb [address ], reg

Read signed byte from memory and load into register

ldsh [address ], reg

Read signed half-word and load into register

ldub [address ], reg

Read unsigned byte and load into register

lduh [address ], reg

Read unsigned half-word and load into register

Now let’s look at a couple of examples. The instruction below reads the word of data stored at the memory address indicated by input register %i0 and loads it into output register %o1.

ld [%i0], %o1 

The next example reads an unsigned byte of data from memory, loading it into output register %o3. The memory address where the byte is read is the contents of input register %i4 plus hexadecimal 8. In a case like this, the value in %i4may often be the pointer to a structure. The offset of 8 points to the most significant byte of the third word in the structure, the 9th byte.

ldub [%i4 + 0x8], %o3 

The example below reads a double word (two words) from memory and loads the data into two registers starting with register %l4. So, if %i3contains address 0xfea603b0, this load instruction will read memory location 0xfea603b0 and 0xfea603b4, loading the data into registers %l4 and %l5, respectively.

ldd [%i3], %l4 

Loading from alternate address space

Each of the six load instructions shown above also has a variation that says to load the information from an alternate address space, such as the control registers for the Memory Management Unit. Each SPARC implementation may offer different alternate addressable registers that can be accessed via the load alternate address space instructions. During system crash dump analysis, odds are very good you will not run into these instructions, since they are not generated by the compiler, but we’ll show them just in case you do encounter them. Here they are.

Table B-2. Load instructions from alternate address space

Instruction Syntax

Operation

lda [reg ] asi, reg

Load word from alternate space

ldda [reg ] asi, reg

Load double word from alternate space

ldsba [reg ] asi, reg

Load signed byte from alternate space

ldsha [reg ] asi, reg

Load signed half-word from alternate space

lduba [reg ] asi, reg

Load unsigned byte from alternate space

lduha [reg ] asi, reg

Load unsigned half-word from alternate space

Loading from the floating-point unit & coprocessor

The next six load instructions are specifically for the optional floating-point unit and the optional coprocessor. While in assembly language they appear to be instructions we’ve seen earlier, the actual opcodes differ.

Table B-3. Load instructions for optional FPU

Opcode

Instruction Syntax

Operation

LDF

ld [address ], freg

Load word from memory into freg

LDDF

ldd [address ], freg

Load double word from memory into freg

LDFSR

ld [address ], %fsr

Load word into floating-point state reg

LDC

ld [address ], creg

Load word from memory into creg

LDDC

ldd [address ], creg

Load double word from memory into creg

LDCSR

ld [address ], %csr

Load word into coprocessor state register

Store instructions

If you feel comfortable with the various load instructions, the store instructions will be a piece of cake. After data in a register has been manipulated, we use the store instruction to write the data to a specified memory location.

There are four basic store operations and four alternate address space variations of them. They are as follows:

Table B-4. SPARC store instructions

Instruction Syntax

Operation

stb reg , [address ]

Store least significant byte to memory (aka stub and stsb)

sth reg , [address ]

Store least significant half-word (aka stuh and stsh)

st reg , [address ]

Store word to memory

std reg , [address ]

Store double word to memory

stba reg , [regaddr ] asi

Store byte to alternate space (aka stuba and stsba)

stha reg , [address ] asi

Store half-word to alternate space (aka stuha and stsha)

sta reg , [address ] asi

Store word to alternate space

stda reg , [address ] asi

Store double word to alternate space

Let’s take a look at a couple of examples of store instructions. The one below stores the contents of input register %i3 into the memory location whose address is in local register %l6.

st %i3, [%l6] 

The next example stores the least significant byte in register %i0 into the 2nd byte of the word whose address is contained in register %l5.

stb %i0, [%l5 + 1] 

Storing from the floating-point unit & coprocessor

Of course, we also have additional store instructions that are used in conjunction with the optional floating-point processor and optional coprocessor. As with the load instructions, these instructions differ a bit between assembly language and the actual SPARC opcode.

Table B-5. SPARC additional store instructions

Opcode

Instruction Syntax

Operation

STF

st freg , [address ]

Store word in freg to memory

STDF

std freg , [address ]

Store double word in freg to memory

STFSR

st %fsr, [address ]

Store %fsr to memory

STDFQ

st %fq, [address ]

Store double %fq to memory

STC

st creg , [address ]

Store word in creg to memory

STDC

std creg , [address ]

Store double word in creg to memory

STCSR

st %csr, [address ]

Store %csr to memory

STDQC

std %cq, [address ]

Store double %cq to memory

Atomic memory access instructions

Two instructions in the SPARC instruction set and two alternate address space variations of them can perform a read from memory and a write to memory atomically.

What do we mean by atomically? The instruction cannot be interrupted during its execution; the read and the write happen in the same breath. In a multiprocessor system, two or more processors executing the instructions addressing the same byte simultaneously are guaranteed to execute them in an undefined, but serial order.

Here are the instructions:

Table B-6. SPARC atomic energy access instructions

Instruction Syntax

Operation

ldstub [address ], reg

Atomic load-store unsigned byte

ldstuba [regaddr ] asi, reg

Atomic load-store unsigned byte into alternate space

swap [address ], reg

Swap register with memory

swapa [regaddr ] asi, reg

Swap register with alternate space memory

The ldstub instructions read an unsigned byte from memory into a register, then write all ones (hexadecimal 0xff) to that byte of memory. The swap instructions interchange the contents of a memory location with the contents of a register.

In general terms, both of these instructions, since they involve a lot of work, usually take longer to execute than others. However, when integrity of the data being manipulated is critical and timing is everything, these atomic instructions are invaluable. For example, it is the ldstub instruction that provides SPARC systems the ability to have safe, predictable locking mechanisms.

Note

Instruction execution times differ with each SPARC implementation. Refer to the specific processor’s technical manual for timing data.

Possible traps during memory access instructions

The memory access instructions generate the most traps. With the exception of the floating-point and coprocessor trap conditions, the traps shown below will cause a user program to terminate, dumping core. When these conditions are detected during execution of kernel code, it is considered catastrophic, and the system will immediately panic with a “bad trap.”.

Table B-7. SPARC trap conditions and causes

Trap Condition

How The Condition Is Caused

Illegal instruction

The operation code of the instruction being executed did not represent a valid instruction.

Privileged instruction

The processor is not in privileged mode and the instruction being executed is a privileged instruction. Alternate address space instructions, stdfq and stdcq are all privileged instructions and will cause this when PSR bit S is 0.

Memory address not aligned

A double word, full word or half-word instruction is trying to access memory that is not double word, full word or half-word aligned. Byte instructions cannot cause this condition.

Data access exception

Failure to access the data due to a condition such as the page of memory being marked as invalid or write-protected.

Data access error

The instruction failed to complete access of the data due to a condition such as a data cache parity error or an uncorrectable ECC memory error.

Data store error

The instruction failed to complete storage of the data due to a condition such as a bus parity error.

FP / CP disabled

Attempt to access the floating-point processor (or coprocessor) that is not present or while PSR EF (or EC) bit is set to 0.

FP / CP exception

A floating-point (or coprocessor) instruction generated an exception.

When analyzing a system crash dump caused by a “bad trap,” you’ll usually find that a load or store instruction caused the crash.

Arithmetic / logical / shift instructions

Using the memory access instructions, we can move data between the processor’s registers and memory. Now let’s discuss the instructions used to manipulate the data once it is loaded into the registers. This set of register-based instructions is used to:

  • Perform integer math

  • Perform logical operations (AND, OR, exclusive OR, etc.)

  • Shift or rotate data

  • Save and restore windows

The syntax we will see most often used in this set of instructions follows:

instruction sreg, reg_or_imm, dreg 

In this syntax, sreg and reg_or_imm are the source operands and dreg is the destination register where the result of the instruction is stored. Most often, sreg contains the data to be manipulated, and reg_or_imm is the value used in conjunction with the data to generate the final result. reg_or_imm can be either another register or a signed 13-bit value.

Let’s look at an example:

add %g2, 1, %g2 

This example instruction’s source register, sreg , is register %g2. The reg_or_imm is simply a value of 1. The contents of %g2and the value of 1 are added together. The result is stored in the destination register, dreg , register %g2.

Note

The sreg , reg_or_imm and dreg values in arithmetic / logical / shift instructions may reference the same registers.

Integer arithmetic

Okay, let’s start off with the most commonly used arithmetic instructions:

Table B-8. SPARC arithmetic instructions

Instruction Syntax

Operation

add sreg, reg_or_imm, dreg

Add the contents of sreg to the value represented by reg_or_imm and store result in dreg

addcc sreg, reg_or_imm, dreg

Add and modify the PSR icc fields

addx sreg, reg_or_imm, dreg

Add and add in icc carry bit

addxcc sreg, reg_or_imm, dreg

Add, add in carry bit and modify icc fields

sub sreg, reg_or_imm, dreg

Subtract the value represented by reg_or_imm from the contents of sreg and store result in dreg

subcc sreg, reg_or_imm, dreg

Subtract and modify the PSR icc fields

subx sreg, reg_or_imm, dreg

Subtract and subtract icc carry bit

subxcc sreg, reg_or_imm, dreg

Subtract, subtract carry bit and modify icc fields

umul sreg, reg_or_imm, dreg

Unsigned integer multiply

smul sreg, reg_or_imm, dreg

Signed integer multiply

umulcc sreg, reg_or_imm, dreg

Unsigned multiply and modify PSR icc fields

smulcc sreg, reg_or_imm, dreg

Signed multiply and modify icc fields

udiv sreg, reg_or_imm, dreg

Unsigned integer divide

sdiv sreg, reg_or_imm, dreg

Signed integer divide

udivcc sreg, reg_or_imm, dreg

Unsigned divide and modify PSR icc fields

sdivcc sreg, reg_or_imm, dreg

Signed divide and modify icc fields

We’ve already seen one example of these instructions. What do you think this next example instruction does?

sub %g4, %l3, %g4 

In programming terms, this might be expressed as:

%g4 = %g4 - %l3 

The contents of local register %l3 is subtracted from the contents of global register %g4and the result is stored back into %g4. Here’s another instruction.

addxcc %l0, 20, %l1 

This instruction adds the contents of %l0 and 20. It also adds in the PSRicc carry bit, which is either 0 or 1. The result is stored in %l1. Meanwhile, any integer condition codes occurring during the addition are recorded in the PSR icc fields. For example, if the result of the addition was negative, the icc negative bit would be set.

The next set of integer arithmetic instructions are not used often and are unlikely to appear during the course of system crash dump analysis.

Table B-9. SPARC integer arithmetic instructions

Instruction Syntax

Operation

taddcc sreg, reg_or_imm, dreg

Tagged add and modify the PSR icc fields

taddcctv sreg, reg_or_imm, dreg

Tagged add, modify icc fields and trap on overflow

tsubcc sreg, reg_or_imm, dreg

Tagged subtract and modify icc fields

tsubcctv sreg, reg_or_imm, dreg

Tagged sub, modify icc fields and trap on overflow

Tagged arithmetic operations assume tagged-format data where the least significant two bits of the operands have special meaning. Languages such as LISP and Smalltalk use tagged arithmetic for dynamically typed data.

The tagged arithmetic instructions taddcctv and tsubcctv can cause tag overflow traps that would be handled by the operating system. These traps would not cause the system to panic and crash.

Logical instructions

The logical instructions perform bitwise operations. The general syntax used is the same as the integer arithmetic instructions:

instruction sreg, reg_or_imm, dreg 

Here are the instructions.

Table B-10. SPARC logical instructions

Instruction Syntax

Operation

and sreg, reg_or_imm, dreg

Bitwise AND

andcc sreg, reg_or_imm, dreg

AND and modify PSR icc fields

andn sreg, reg_or_imm, dreg

AND NOT

andncc sreg, reg_or_imm, dreg

AND NOT and modify PSR icc fields

or sreg, reg_or_imm, dreg

Bitwise inclusive OR

orcc sreg, reg_or_imm, dreg

Inclusive OR & modify PSR icc fields

orn sreg, reg_or_imm, dreg

Inclusive OR NOT

orncc sreg, reg_or_imm, dreg

Inclusive OR NOT and modify PSR icc fields

xor sreg, reg_or_imm, dreg

Bitwise exclusive OR

xorcc sreg, reg_or_imm, dreg

Exclusive OR and modify PSR icc fields

xnor sreg, reg_or_imm, dreg

Exclusive NOR (Exclusive OR NOT)

xnorcc sreg, reg_or_imm, dreg

Exclusive NOR and modify PSR icc fields

Let’s try a few examples. Given that %g4contains 0x055, what would register %l2contain after each of the following instructions?

and %l0, 73, %l2     Answer: 51 
or %l0, 73, %l2      Answer: 77 
xor %l0, 73, %l2     Answer: 26 
xnor %l0, 73, %l2    Answer: ffff ffd6 

If you aren’t clear about how these answers were reached, you might want to talk to a programmer or refer to a good programming book.

None of the logical instructions generate traps.

Shift instructions

The shift instructions use the same general syntax we’ve seen in the integer arithmetic and logical instructions.

instruction sreg, reg_or_imm, dreg 

The shift instructions shift the value in sreg left or right by a certain number of bit positions, as represented by reg_or_imm , and place the result in dreg . As the shift occurs, bits that drop off the end of the working register are lost. The PSRicc fields are not modified by the shift instructions.

There are no true “rotate” instructions in the SPARC instruction set. However, if a rotate is needed, the clever assembly language programmer can use the addcc instruction and the PSR icc overflow bit to his advantage.

Here are the three shift instructions:

Table B-11. SPARC shift instructions

Instruction Syntax

Operation

sll sreg, reg_or_imm, dreg

Shift left logical

srl sreg, reg_or_imm, dreg

Shift right logical

sra sreg, reg_or_imm, dreg

Shift right arithmetic

The logical shifts replace the vacated bits with zeroes. The arithmetic shift replaces the vacated bits with the most significant bit of the value in sreg .

Here is an example of a shift instruction.

sll %l7, 2, %l7 

If the contents of %l7 started as 0x04, the result after shifting left two positions would be 0x10.

Note

In effect, each shift left by 1 is the same as multiplying by 2. Shift rights are like divides. This is good to remember as, on some SPARC implementations, the integer multiply and divide instructions take longer to execute than the shift instructions.

The shift instructions do not generate traps.

Miscellaneous arithmetic / logical / shift instructions

There are only a few miscellaneous instructions in the arithmetic / logical /shift set of SPARC instructions. Unlike the others, these instructions have differing syntaxes.

The sethi instruction is usually used in conjunction with a second command, such as a load. Let’s look at an example.

sethi %hi(0xf0155000), %o3 
ld [%o3 + 0x2a0], %l2 

The sethi instruction sets the high-order 22 bits of output register %03 to the high-order 22 bits of the value 0xf0155000. The load instruction then reads the value stored in memory location [%o3 + 0x2a0] (which calculates to 0xf01552a0) into local register %l2.

Why was this method used to read the value at memory location f01552a0? If you remember, due to the 32-bit width restriction of SPARC instructions, it is not possible to say “put 0xf01552a0 into %03.” If we add up the number of opcode bits used to identify the put instruction, the 32 bits of the value 0xf01552a0 and the bits needed to point to %03, we would have an instruction that is well over 32 bits in width.

The sethi instruction only contains the high-order 22 bits of the value 0xf01552a0 (thus, f0155000). The load instruction can include an offset of 13 bits in the [address] field, more than is needed to construct a valid memory address.

The nop instruction is actually a variation of the sethi instruction, as shown below.

sethi 0, %g0 

Register %g0 is rather like the /dev/null of registers. Reading %g0always results in zero. Writing to %g0 has no effect.

The nop instruction is actually executed, but it makes no modifications to the registers or memory. nopsare used when timing delays are required. There are actually many different instructions which could serve equally well as a nop. The compiler uses sethi. adb should recognize other varieties and display them as nop.

The mulscc instruction is a very busy little instruction that conditionally shifts a value, conditionally performs addition and updates the icc fields. You will see the mulsccinstruction used on systems that do not have the integer multiply and divide instructions implemented in the hardware.

save and restore instructions are used to manipulate the register windows.

In the set of miscellaneous arithmetic / logical / shift instructions, only the save and restore instructions can generate traps. The saveinstruction can cause a “window overflow” trap and the restore can cause a “window underflow” trap. Neither of these traps will cause the system to crash. Instead, the kernel kicks in and does some special window handling. We discuss windows in more detail in Chapter 17, “Stacks.”

Control transfer instructions

We talked a little bit about control transfer instructions in Chapter 16 on the SPARC assembly language, specifically regarding the delay instruction. Now let’s talk about them in more detail.

Control transfer instructions perform the following tasks:

  • Test and branch based on the values of the PSR icc fields (integer condition codes)

  • Test and branch based on the values of the floating-point unit’s condition codes

  • Test and branch based on the values of the coprocessor unit’s condition codes

  • Unconditional branches

  • Test and trap based on the values of the PSR icc fields

  • Orderly return from a trap

We will start with the test and branch or conditional branch instructions. They all have the same general instruction format, as shown here:

instruction{,a} label 

{,a} represents an option that each conditional branch instruction offers and refers to the annul bit. If , ais appended to the instruction, the annul bit is set. We will talk about the annul bit again later on.

Branch on integer condition codes instructions

The next table shows the conditional test and branch instructions for the integer unit. The third column shows which conditions the PSR icc bits must satisfy in order for the branch to be taken. As a reminder, the icc bits are:

  • Condition N, negative result occurred

  • Condition Z, result was zero

  • Condition V, overflow occurred

  • Condition C, bit 31 was carried or borrowed

Here are the branch on integer condition codes instructions:

Table B-12. Branch on integer condition codes instructions

Instruction Syntax

Operation

icc Test

ba{,a} label

Branch always to label

 

bn{,a} label

Branch never to label

 

bne{,a} label

Branch on not equal

not Z

be{,a} label

Branch on equal

Z

bg{,a} label

Branch on greater

not (Z or (N xor V))

ble{,a} label

Branch on less or equal

Z or (N xor V)

bge{,a} label

Branch on greater or equal

not (N xor V)

bl{,a} label

Branch on less

N xor V

bgu{,a} label

Branch on greater unsigned

not (C or Z)

bleu{,a} label

Branch on less or equal unsigned

C or Z

bcc{,a} label

Branch on carry clear (greater or equal unsigned)

not C

bcs{,a} label

Branch on carry set (less unsigned)

C

bpos{,a} label

Branch on positive

not N

bneg{,a} label

Branch on negative

N

bvc{,a} label

Branch on overflow clear

not V

bvs{,a} label

Branch on overflow set

V

Here is a snippet of assembly code that demonstrates how a branch instruction might be used.

main+0x34:      ld      [%l4 - 0x8], %l0 
main+0x38:      subcc   %l0, 0x6, %g0 
main+0x3c:      bne     main + 0x5c 
main+0x40:      nop 
main+0x44:      ld      [%fp - 0x8], %l0 

A value is read in from memory and placed into local register %l0.

Using the “subtract & modify icc” instruction, we subtract 6 from the value in %l0. No result is stored because the dreg or destination register is the /dev/null of registers, %g0; however, the icc bits are modified as appropriate.

Using the “branch on not equal” instruction, we test the setting of the Z bit. If it is set to 1, the values were equal; the value in memory was a 6. If the Z bit is clear, the values were not equal and we jump to location main+0x5c.

While doing the branch, the delay instruction, nop, gets executed.

If the branch is not taken, we still execute the nop instruction and then continue to the following load instruction at location main+0x44.

The branch on integer condition codes instructions do not generate traps.

Branch on FPU condition codes instructions

The fcc field of the floating-point status register, %fsr, is updated by the floating-point compare instructions. The branch on floating-point condition codes instructions test the fcc field and branches accordingly. As a reminder, here are the fcc codes.

fcc bits

Code

Relationship Between Two Floating Point Values

00

E

freg 1 = freg 2

Values were equal

01

L

freg 1 < freg 2

freg 1 less than freg 2

10

G

freg 1 > freg 2

freg 1 greater than freg 2

11

U

freg 1 ? freg 2

freg 1 and freg 2 are unordered

If a floating-point unit exists, the following branch instructions can be executed:

Table B-13. Branch instructions, FPU

Instruction Syntax

Operation

fcc Test

fba{,a} label

Branch always to label

 

fbn{,a} label

Branch never to label

 

fbu{,a} label

Branch on unordered

U

fbg{,a} label

Branch on greater

G

fbug{,a} label

Branch on unordered or greater

G or U

fbl{,a} label

Branch on less

L

fbul{,a} label

Branch on unordered or less

L or U

fblg{,a} label

Branch on less or greater

L or G

fbne{,a} label

Branch on not equal

L or G or U

fbe{,a} label

Branch on equal

E

fbue{,a} label

Branch on unordered or equal

E or U

fbge{,a} label

Branch on greater or equal

E or G

fbuge{,a} label

Branch on unordered, greater, or equal (not less)

E or G or U

fble{,a} label

Branch on less or equal

E or L

fbule{,a} label

Branch on unordered, less, or equal (not greater)

E or L or U

fbo{,a} label

Branch on ordered

E or L or G

These commands can generate fp disabled and fp exception traps, neither of which should cause panics. When one of these traps does occur, the operating system, not the hardware, is responsible for performing the floating-point operation.

Branch on coprocessor condition codes instructions

When this book was being written, there were no SPARC processor implementations that had yet incorporated a coprocessor. Even so, The SPARC Architecture Manual, Version 8 does define recommended instructions specific to the coprocessor.

The branch on coprocessor condition codes instructions assume there are two bits in the coprocessor status register that are used to represent conditions. The possible values for these two bits are: 0, 1, 2, and 3.

Here are the branch on coprocessor condition codes instructions.

Table B-14. Branch on coprocessor condition codes

Instruction Syntax

Operation Based on ccc

cba{,a} label

Branch always to label

cbn{,a} label

Branch never to label

cb3{,a} label

Branch on 3

cb2{,a} label

Branch on 2

cb23{,a} label

Branch on 2 or 3

cb1{,a} label

Branch on 1

cb13{,a} label

Branch on 1 or 3

cb12{,a} label

Branch on 1 or 2

cb123{,a} label

Branch on 1 or 2 or 3

cb0{,a} label

Branch on 0

cb03{,a} label

Branch on 0 or 3

cb02{,a} label

Branch on 0 or 2

cb023{,a} label

Branch on 0 or 2 or 3

cb01{,a} label

Branch on 0 or 1

cb013{,a} label

Branch on 0 or 1 or 3

cb012{,a} label

Branch on 0 or 1 or 2

Like the floating-point unit branch instructions, these instructions can cause coprocessor disabled and coprocessor exception traps. Both of these traps should not cause system panics and should instead cause the operating system to intervene and perform the required task.

The annul bit

The delayed transfer control instructions that we’ve seen all have an optional annul flag or bit which can be specified in the instruction by appending ,a to the instruction opcode. When set, the annul bit says to execute the delay instruction only if we take the branch. If we don’t take the branch, a set annul bit annuls or nullifies the execution of the delay instruction; the delay instruction is not executed.

Here is the same snippet of assembly code we used earlier to demonstrate how a branch instruction might be used. This time, the bneinstruction has been changed to bne,a.

main+0x34:      ld      [%l4 - 0x8], %l0 
main+0x38:      subcc   %l0, 0x6, %g0 
main+0x3c:      bne, a  main + 0x5c 
main+0x40:      nop 
main+0x44:      ld      [%fp - 0x8], %l0 

This time, if the value in %l0 is not equal to 6, we will jump to main+0x5c while executing the nop instruction. Conversely, if the value in %l0is equal to 6, we will skip the delay instruction all together and move on to the load instruction. Usually the delay instruction consists of something that does real work, instead of a nop. Unoptimized compiler output will often contain nop instructions.

For the “branch always” and “branch never” instructions, the delay instruction is executed if the annul bit is not set, and it is not executed when the annul bit is set.

Unconditional branches

Two instructions perform unconditional branches. They are:

Table B-15. Unconditional branch instructions

Instruction Syntax

Operation

call label

Save PC in %o7 and branch to label

jmpl address, reg

Save PC in reg and branch to address

The call instruction transfers control to an address relative to the current PC, whereas the jump and link, jmpl, instruction performs a register-indirect control transfer.

The call instruction places the current value of the Program Counter into register %o7, whereas the jmpl instruction allows the programmer to specify in which register to store the PC.

The call instruction does not generate any traps.

The jmpl instruction generates a “memory address not aligned” trap when address is not word aligned.

Trap on integer condition codes instructions

We talk about traps in detail in another chapter. For now, let’s just say that normally a trap is any condition in the hardware that shouldn’t have occurred. Generalizing, we could say when an instruction is executing, if something goes wrong, the instruction gets stuck or trapped and can’t finish its job. When this happens, the hardware suddenly switches to “Plan B,” records the current Program Counter and jumps to a special trap handler. The operating system gets involved and may decide to panic, kill the offending program, or simply provide assistance to the hardware via software routines.

The SPARC processor offers the programmer a way to force a trap condition. Using the PSR icc field, a routine can test the condition codes and based on the results, force a trap. When the trap is “taken,” the hardware still switches to “Plan B,” records the PC, and jumps into the trap handler, specifically to the section set aside for software trap number specified as sw_trap_num . This is the way a user program actually issues a system call— by trapping into the kernel with a specific code.

Here are the trap on integer condition codes instructions. You’ll see that they are quite similar to the branch on icc instructions.

Table B-16. Trap on integer condition codes instructions

Instruction Syntax

Operation

icc Test

ta sw_trap_num

Trap always

 

tn sw_trap_num

Trap never

 

tne sw_trap_num (aka tnz)

Trap on not equal

not Z

te sw_trap_num (aka tnz)

Trap on equal

Z

tg sw_trap_num

Trap on greater

not (Z or (N xor V))

tle sw_trap_num

Trap on less or equal

Z or (N xor V)

tge sw _trap_num

Trap on greater or equal

not (N xor V)

tl sw_trap_num

Trap on less

N xor V

tgu sw_trap_num

Trap on greater unsigned

not (C or Z)

tleu sw_trap_num

Trap on less or equal unsigned

C or Z

tcc sw_trap_num (aka tgeu)

Trap on carry 0 (> or = unsigned)

not C

tcs sw_trap_num (aka tlu)

Trap on carry 1 (<unsigned)

C

tpos sw_trap_num

Trap on positive

not N

tneg sw_trap_num

Trap on negative

N

tvc sw_trap_num

Trap on overflow clear

not V

tvs sw_trap_num

Trap on overflow set

V

The trap on integer condition codes instructions never execute the delay instruction.

These instructions all generate a trap instruction trap.

Orderly return from a trap

After a trap condition is handled by the operating system and everyone is happy again, instruction execution returns to the previously scheduled program that had caused the condition. The instruction, rettor return from a trap, does this control transfer.

Instruction Syntax

Operation

rett address

Return from trap, returning to address

Under various conditions, rett can cause any of the following traps.

Table B-17. rett traps

Trap Condition

How The Condition Is Caused

Illegal instruction

The bit-by-bit operation code of the instruction being executed did not represent a valid instruction.

Privileged instruction

The processor is not in privileged mode and the instruction being executed is a privileged instruction. Alternate address space instructions, stdfq and stdcq are all privileged instructions and will cause this condition when PSR bit S is 0.

Memory address not aligned

A double word, full word or half-word instruction is trying to access memory that is not double-word-, full-word- or half-word-aligned. Byte instructions can not cause this condition.

Window underflow

Register window management needed.

rett is a privileged instruction.

State register instructions

As we saw earlier in Appendix A on the SPARC processor, there are several special registers. To read and write to those registers, we use the following instructions.

Table B-18. State register instructions

Opcode

Instruction Syntax

Operation

RDY

rd %y, dreg

Read contents of %y and place into a register

RDASR

rd asr_reg, dreg

Read an ancillary state register into dreg

RDPSR

rd %psr, dreg

Read contents of %psr into dreg

RDWIM

rd %wim, dreg

Read contents of %wim into dreg

RDTBR

rd %tbr, dreg

Read contents of %tbr into dreg

WRY

wr sreg, reg_or_imm , %y

xor the values of sreg and reg_or_imm and write result into %y

WRASR

wr sreg, reg_or_imm, asr_reg

xor the values of sreg and reg_or_imm and write result into an ancillary state register

WRPSR

wr sreg, reg_or_imm , %psr

xor the values of sreg and reg_or_imm and write result into %psr

WRWIM

wr sreg, reg_or_imm , %wim

xor the values of sreg and reg_or_imm and write result into %wim

WRTBR

wr sreg, reg_or_imm , %tbr

xor the values of sreg and reg_or_imm and write result into %tbr

The write instructions are delayed-write instructions. This means that the changes to the register may not be completed until up to three instructions later! When you encounter write instructions while looking at your running kernel or a system crash dump, you will note that they are usually followed by three nop instructions. This programming practice guarantees that the new value has been written to the specified register before the program moves on to the next task.

All but the instructions that address register %y are privileged and therefore are capable of generating privileged instruction traps. Also, these instructions can generate illegal instruction traps under certain conditions.

Miscellaneous state register instructions

The other three SPARC instructions in the state register category are:

Table B-19. Miscellaneous SPARC instructions

Instruction Syntax

Operation

unimp

Unimplemented

stbar

Store barrier

flush address

Flush

The unimp instruction is an unimplemented instruction that, when executed, will generate an illegal instruction trap.

The stbar instruction forces all pending stores and atomic load-stores to complete prior to moving on to subsequent stores and atomic load-stores. The stbarinstruction does not generate any traps.

The flush instruction forces all pending memory access instructions involving the specified address to complete before subsequent accesses are attempted.

The stbar and flush instructions are made available for memory management implementations that use memory caches, thus not guaranteeing instant modification of memory.

Floating-point unit instructions

The floating-point instructions perform several operations, including:

  • Floating-point arithmetic

  • Floating-point value conversions

  • Floating-point value comparisons

We will see that the floating-point instructions follow three general syntax rules:

instruction freg 1 , freg 2

instruction sfreg, dfreg

instruction sfreg 1 , sfreg 2 , dfreg

Floating-point arithmetic instructions

Here are the arithmetic instructions.

Table B-20. SPARC floating-point arithmetic instructions

Instruction Syntax

Operation

fsqrts sfreg, dfreg

Put square root of single word in sfreg into dfreg

fsqrtd sfreg, dfreg

Square root, double word

fsqrtq sfreg, dfreg

Square root, quad word

fadds sfreg 1 , sfreg 2 , dfreg

Add single words sfreg1 and sfreg2 , put result in dfreg

faddd sfreg 1 , sfreg 2 , dfreg

Add double words

faddq sfreg 1 , sfreg 2 , dfreg

Add quad words

fsubs sfreg 1 , sfreg 2 , dfreg

Subtract single word sfreg2 from sfreg1 , put result in dfreg

fsubd sfreg 1 , sfreg 2 , dfreg

Subtract double words

fsubq sfreg 1 , sfreg 2 , dfreg

Subtract quad words

fdivs sfreg 1 , sfreg 2 , dfreg

Divide single word sfreg1 by sfreg2 , result in dfreg

fdivd sfreg 1 , sfreg 2 , dfreg

Divide double words, result in dfreg

fdivq sfreg 1 , sfreg 2 , dfreg

Divide quad words, result in dfreg

fmuls sfreg 1 , sfreg 2 , dfreg

Multiply single words, single word result in dfreg

fmuld sfreg 1 , sfreg 2 , dfreg

Multiply double words, double word result

fmulq sfreg 1 , sfreg 2 , dfreg

Multiply quad words, quad word result

fsmuld sfreg 1 , sfreg 2 , dfreg

Multiply single words, double word result

fsmulq sfreg 1 , sfreg 2 , dfreg

Multiply double words, quad word result

Floating-point value conversions

When working with floating-point values, it is often necessary to convert the values to integer values, or from integer back to floating-point. There are also times when a conversions from one floating-point precision to another are needed. The following instructions perform all of the floating-point value conversions:

Table B-21. Floating-point value conversion instructions

Instruction Syntax

Operation

fitos sfreg, dfreg

Convert integer value in sfreg to single word, result in dfreg

fitod sfreg, dfreg

Convert integer value sfreg to double word dfreg

fitoq sfreg, dfreg

Convert integer value sfreg to double word dfreg

fstoi sfreg, dfreg

Convert single word in sfreg to integer value, result in dfreg

fdtoi sfreg, dfreg

Convert double word sfreg to integer value dfreg

fqtoi sfreg, dfreg

Convert quad word sfreg to integer value dfreg

fstod sfreg, dfreg

Convert single word in sfreg to double word, result in dfreg

fstoq sfreg, dfreg

Convert single word sfreg to quad word dfreg

fdtos sfreg, dfreg

Convert double word sfreg to single word dfreg

fdtoq sfreg, dfreg

Convert double word sfreg to quad word dfreg

fqtos sfreg, dfreg

Convert quad word sfreg to single word dfreg

fqtod sfreg, dfreg

Convert quad word sfreg to double word dfreg

Floating-point value comparisons

Earlier, we saw that the floating-point unit has a set of condition code bits and that there are a set of branch on floating-point conditions codes instructions. What we have not yet seen is how the fcc bits get modified.

As a reminder, the comparison instructions set the fcc bits, as shown below.

fcc bits

Code

Relationship Between Two Floating-Point Values

00

E

freg 1 = freg 2

Values were equal

01

L

freg 1 < freg 2

freg 1 less than freg 2

10

G

freg 1 > freg 2

freg 1 greater than freg 2

11

U

freg 1 ? freg 2

freg 1and freg 2 are unordered

Here are the floating-point value comparison instructions.

Table B-22. Floating-point value comparison instructions

Instruction Syntax

Operation

fcmps freg 1 , freg 2

Compare single words

fcmpd freg 1 , freg 2

Compare double words

fcmpq freg 1 , freg 2

Compare quad words

Table B-22. Floating-point value comparison instructions

Instruction Syntax

Operation

fcmpes freg 1 , freg 2

Compare single words and cause an fp exception if unordered

fcmped freg 1 , freg 2

Compare double words and cause exception if unordered

fcmpeq freg 1 , freg 2

Compare quad words and cause exception if unordered

Miscellaneous floating-point instructions

There are three miscellaneous floating-point instructions, as follows:

Table B-23. Miscellaneous floating-point instructions

Instruction Syntax

Operation

fmovs sfreg, dfreg

Copy sfreg into dfreg

fnegs sfreg, dfreg

Copy sfreg into dfreg with the sign bit complemented (reversed)

fabss sfreg, dfreg

Copy sfreg into dfreg with the sign bit cleared

The floating-point instructions can generate fp exception and fp disabled traps, all of which must result in the operating system processing the requested instruction via software, such as floating-point library routines.

Coprocessor instructions

Each SPARC Version 8 implementation that utilizes the optional coprocessor unit must define its own instructions. However, there are two instruction opcodes reserved for coprocessor instructions:

Table B-24. Instruction opcodes reserved for coprocessor instructions

Opcode

Recommended Instruction Syntax

COop1

cpop1 opc, screg 1 , screg 2 , dcreg

COop2

cpop2 opc, screg 1 , screg 2 , dcreg

opc would represent the specific operation, two source registers screg1 and screg2 could be specified, and of course, there would be a destination register, dcreg . All of the registers would reside on the coprocessor.

The coprocessor instructions can generate cp exception and cp disabled traps.

Synthetic instructions

At this point, we’ve covered every instruction in the SPARC Version 8 instruction set. However, during system crash dump analysis, you may run into several additional SPARC instructions that are referred to as synthetic instructions. These instructions may be provided in a SPARC assembler for the convenience of assembly language programmers. They tend to be more suitable, some have easier-to-remember instruction names, and the syntax is often slimmed down. As you read the table, you’ll see what we mean:

Table B-25. Common SPARC synthetic instructions

Synthetic Instruction

Actual Instruction

Description

jmp address

jmpl address , %g0

Jump

call address

jmpl address , %o7

Call a subroutine

tst reg

orcc %g0, reg , %g0

Test

ret

jmpl %i7+8, %g0

Return from subroutine

restore

restore %g0, %g0, %g0

Trivial restore

save

save %g0, %g0, %g0

Trivial save

set value, reg

sethi %hi (value), reg

When (value&0x1ffff)==0

 

OR or %g0, value, reg

When (-4096<=value<=4095)

 

OR sethi %hi (value), reg

Otherwise. Warning: Do not use

 

or reg, %lo (value), reg

set as a delay instruction.

not sreg, dreg

xnor sreg , %g0, dreg

One’s complement

not reg

xnor reg , %g0,

One’s complement

neg sreg, dreg

sub %g0, reg, reg

Two’s complement

neg reg

sub %g0, reg, reg

Two’s complement

inc reg

add reg , 1, reg

Increment by 1

inc const13, reg

add reg, const13, reg

Increment by const13

inccc reg

addcc reg , 1,

Increment by 1 and set ICC

inccc const13, reg

addcc reg , const13,

Increment by const13 and set ICC

dec reg

sub reg , 1, reg

Decrement by 1

dec const13, reg

sub reg, const13, reg

Decrement by const13

deccc reg

subcc reg , 1,

Decrement by 1 and set ICC

deccc const13, reg

subcc reg, const13, reg

Decrement by const13 and set ICC

btst reg_or_imm, reg

andcc reg, reg_or_imm , %g0

Bit test

bset reg_or_imm, reg

or reg, reg_or_imm, reg

Bit set

bclr reg_or_imm, reg

andn reg , reg_or_imm , reg

Bit clear

btog reg_or_imm, reg

xor, reg_or_imm, reg

Bit toggle

clr reg

or %g0, %g0, reg

Clear (zero) register

clrb [address ]

stb %g0, [address ]

Clear byte

clrh [address ]

sth %g0, [address ]

Clear half-word

clr [address ]

st %g0, [address ]

Clear word

mov reg_or_imm, reg

or %g0, reg_or_imm, reg

Move value into register

mov %y, reg

rd %y, reg

Move %y into reg (Variations exist for %asm, %psr, %wim, %tbr)

mov reg_or_imm , %y

wr %g0, reg_or_imm , %y

Move reg into %y (Variations exist for %asm, %psr, %wim, %tbr)

Always keep an instruction set reference handy!

When working with system crash dumps, you will be working with code that was most likely originally written in C. In the best of scenarios, you’ll have access to the source code, but even then, it is assembly language that you will see when using adb, not C. Therefore, it is important to feel comfortable with the native language of the processor on which you’re working.

We don’t expect anyone to learn assembly language overnight! However, we know from our own experience that it’s always very helpful to have a assembly language reference handy for those times when you do need to remember the instruction set. If your own system is not a SPARC Version 8 processor and you haven’t done so already, get your hands on some sort of assembly language instruction set cheatsheet and keep it handy! Write your own, if you have to. During system crash dump analysis, you are going to need it.

..................Content has been hidden....................

You can't read the all page of ebook, please click here login for view all page.
Reset
3.142.119.114