SPARC Assembly/Printable version


SPARC Assembly

The current, editable version of this book is available in Wikibooks, the open-content textbooks collection, at
https://en.wikibooks.org/wiki/SPARC_Assembly

Permission is granted to copy, distribute, and/or modify this document under the terms of the Creative Commons Attribution-ShareAlike 3.0 License.

Introduction

What This Book is About edit

This book is about programming SPARC Assembly language. This book will cover basics of the assembly language (instructions, syntax, etc), but will also discuss more advanced topics as well. In short, this book is attempting to be a complete SPARC reference, for readers of all skill levels.

Two versions of the architecture are currently in use, SPARCv8 and SPARCv9. Most programs written for one of them should work on the other, since SPARCv9 is backward compatible with SPARCv8 and SPARCv8 is upward compatible with SPARCv9. The main differences lie at the system-programming level, and therefore do not concern user programs. More information can be found on SPARC.

Who This Book is For edit

Because this book contains both low-level information, as well as deeper advanced material, this book is for people of all skill levels. Beginners to SPARC will find this to be an excellent introduction and teaching aide to the language. Advanced users will (hopefully) find this to be a valuable quick reference. Readers are assumed to have at least some background in assembly language programming, but it is not strictly required.

How This Book is Organized edit

This book is ordered according to ascending skillset. That is, the easiest material is presented first, and the more advanced material is presented towards the end. Beginners, and people who are only looking to learn the basics of SPARC assembly need only read the first 2 sections. Later sections are targeted towards people who are doing advanced projects in SPARC, such as the creation of operating system kernels, and SPARC Assemblers.

Where to Go From Here edit

This book attempts to be a complete reference to SPARC programming. As such, there are no wikimedia projects (actual or planned) that will continue the discussion of this material any further. However, the reader may benefit from some of the other materials available, such as the other assembly languages discussed, and the various high-level languages with entire books devoted to them.

Additional information can be obtained from the following links :

  • www.sparc.org : The official SPARC reference, containing SPARCv8 and SPARCv9 architectures specifications,
  • SPARC : Wikipedia's page about SPARC,
  • Microprocessor Design : for a general discussion about microprocessor design.


SPARC Architecture

SPARC History edit

 
A Sun 4 SPARCstation.

The first version of the architecture, SPARCv7 (for Scalable Processor Architecture, version 7), was originally developed by Sun Microsystems in 1986 ; the first implementation became available in 1987. In 1989, SPARC International, an independent, non-profit organization, was created to promote the SPARC and provide conformance testing. Implementations of the original 32-bit SPARC architecture were initially designed and used for Sun's Sun-4 workstation and server systems, replacing their earlier Sun-3 systems based on the Motorola 68000 family of processors. Later, SPARC processors were used in SMP servers produced by Sun Microsystems, Solbourne and Fujitsu, among others.

A new version, SPARCv8, was released in 1990. It added integer multiply and divide instructions, which weren't previously available, and quad-precision floating point numbers, encoded on 128 bits.

The specification of the first 64-bit version of the SPARC, SPARCv9, was published in 1994, and Sun and Fujitsu both started shipping SPARCv9 processors at the end of 1995.

SPARC International (http://sparc.org) was formed in 1989 to open up the SPARC architecture to make a larger ecosystem for the design. The architecture is freely licensable for a nominal fee[citation needed]. SPARC processors have been designed and produced by several manufacturers, including Texas Instruments, Atmel, Cypress Semiconductor, and Fujitsu. As a result of SPARC International, the SPARC architecture is fully open and non-proprietary.

SPARC Architecture edit

The SPARC is of the Reduced Instruction Set Computing (RISC) architecture. The theory is that having the bare minimum of instructions needed to complete a job, the resulting architecture is faster, as most instructions take only one clock cycle to decode, leading to rapid execution. This is in contrast to CISC machines, which have specialized variable length instructions, and can take multiple clock cycles to decode and execute.

The SPARC architecture also prefetches instructions, having the next instruction fetched while the current one is executed. This has implication for branch instructions, as the next instruction might not be executed if the branch is taken, and this must be dealt with accordingly.

Why SPARC? edit

Being a RISC architecture, SPARC assembly is very clean and simple, while still being powerful. This makes it easy to learn, and a good choice before learning more complicated assembly languages if needed. Furthermore, it provides a closer look of what is going on "under the hood" of higher-level programming languages, and at the very least should foster an appreciation of the large amount of work being done by compilers when compiling such languages. If you don't have a SPARC computer, you can use a SPARC emulator.


SPARC Processors

This page is going to list, and discuss some of the computer systems in the SPARC processor family.


SPARC Details

RISC Computers edit

Registers edit

SPARC processors have 32 integer registers. These registers are broken down into 4 basic categories: globals, locals, inputs, and outputs. The table below shows the general breakdown:

Number Purpose Specific name
%r0–%r7 Globals: accessible anywhere in a program %g0–%g7
%r8–%r15 Outputs: used to pass values to/ obtain values from subroutines %o0–%o7
%r16–%r23 Locals: used within subroutines to manipulate data %l0–%l7
%r24–%r31 Inputs: contain data passed to a subroutine %i0–%i7

Dispersed throughout these categories are several special purpose registers:

Name Number Purpose Pseudonym
Stack pointer 14 Pointer to the head of the stack. %sp/ %o6
Frame pointer 30 Pointer to the current stack frame. %fp/ %i6
Return address 31 Return address of the subroutine. %i7
Called return address 15 Return address of the called subroutine. %o7

As you can see from the above tables, each register has at least two names, and some of the special purpose registers have three. Any of the available names for a given register is perfectly acceptable regardless of the usage context, and it is up to the programmer to choose which names to use at any particular time. Additionally, using the stack and frame pointer registers in a way other than which they were intended is not recommended and can cause severe functionality issues within a program.

SPARC processors also contain an array of floating-point registers and a small number of special-purpose registers. (further description needed here)

The Fetch and Execute Instruction Cycle edit

Delayed Branch edit

SPARC processors are pipelined, and branching is accomplished through a technique called Delayed Branch Execution. Control Transfer Intructions (CTI) are any instruction that changes the current program counter. For instance, a jmp or call instruction are CTI instructions.

In SPARC, when a CTI instruction is executed, the jump is not handled immediately. Instead, there is a one cycle delay before the branch is executed. This means that the first instruction after the jump instruction is actually handled before the jump takes place. Here is an example:

add %r3, %r2, %r5
jmp SetR5ToZero
add %r4, %r5, %r2

Notice that the last instruction executes before the jump takes place, not after the subroutine returns. This first instruction after a jump is called a delay slot. It is common practice to fill the delay slot with a special operation that performs no task, called a no-operation, or nop.

Instruction:
nop

This instruction performs no action, and therefore we don't need to worry about what order it acts in. However, if we put a nop after every branch instruction, we will waste a lot of processor cycles. Therefore, if you can, it is always good practice to try to squeeze additional instructions into the delay slot, so that we don't waste any processor cycles.

The Stack edit

SPARC Instructions

Instruction Format edit

Here is a quick-rundown of the arithmetic instruction format, when writing your SPARC code:

mnemonic %rsrcA, srcB, %rdest

The instruction mnemonic (commonly, but inaccurately, also referred to as the "opcode") specifies the type of operation to be performed. rsrcA is the first operand, while srcB is the second. rsrcA must be a register, and srcB can usually be a signed immediate (13 bit) constant or a second register. rdest is the destination register, and not all instructions have one (for example: cmp for compare).

Note that in SPARC assembly language, instructions always read from left to right. The left (and middle, if present) operands are source operands. If the operation writes a result anywhere (as almost all operations do), the result is written to the rightmost operand (destination register or destination memory location).

In SPARC assembly language, the following instructions are completely valid:

add %r3, %r4, %r5
add %r3, 16, %r5
  • The first instruction adds register 3 and register 4, and places the result in register 5.
  • The second instruction adds register 3, and the number 16, and places the result in register 5.


As you can see, SPARC assembly places a % sign before each register name, while numeric literals are written normally.

Warning: This syntax is backwards from Intel syntax (used in PPC chips, and some compilers).

It should also be noted that many SPARC instructions such as the logic and arithmetic instructions have a version of each instruction with "cc" appended to the end of the mnemonic. These instructions perform the same function as their non-"cc" counterpart, but also set condition codes (more on these later) that can be used to regulate branching within a program. For example, the "add" instruction mentioned above has a counterpart "addcc", which when performing an addition sets specific condition codes that later branch instructions check when deciding whether or not to branch to another part of the program.

Comments edit

Comments will not be read by the compiler, and are indicated with an exclamation point. Anything following the exclamation point on that line will be ignored. Comments help you understand what you are doing, and why you are doing it. The following is a bad example of commenting:

sub %l0, %l3, %g1  ! Subtract local register 3 from l0, and put the result in global 1.
! add %g1, %l4, %g1! We should add in local 4, but I'm not doing that yet

We can easily tell what we are doing; the code says that. The comments have told us nothing.


However this is better:

sub %l0, %l3, %g1  ! Subtract our monthly expenses from our monthly income.
                   !    This will later be used in function _foo.
! add %g1, %l4, %g1! Local 4 will hold "other" sources of income, but we're not there yet.

Now we know what we're doing (we're figuring spare change for the month), and why we're doing it (function foo will apparently use this). Also, note that the second line in both examples will not be executed as their instructions have been commented out (apparently to be implemented later).


Do note that many people comment almost every single line of code in assembly, due to the fact that it can sometimes be difficult to tell what's going on without useful things like variable names, complex structures, etc.

Labels edit

Labels are indicated by placing a "label_name:" at some point in your code. As labels are just areas that give the compiler addresses, they can be used for anything that's stored directly in the program: most popularly, these are used for function jumps (via branch or call statements), or ways to reference constant variables. If it is a function, and not a jump, ".global" must be placed before it. There is one special label/global, just like every language, and that is the "main" label, which is where the program starts.

.global main
main:   save %sp, -64, %sp
        mov 5, %l0
        cmp %l0, 5
        be,a end
        ta 1 ! Should NEVER happen
end:    mov 1, %g1
        ta 0

In this program are a bunch of things that might not be understandable, but this is a full program. It starts at the main function (defined by ".global main, followed by the label). It then copies the value "5" into a local register, and then compares that register to the value of "5". If they are equal, it branches to the label end, where the program then exits.

Sections edit

Directives edit

Arithmetic Instructions

Arithmetic Instructions edit

These are the basic operations used for addition, subtraction, and multiplication. Note that any of these arithmetic instructions may take a register or an immediate value as the op2 parameter. All other parameters (rd and rs1 must be registers).

Instruction:
add

Adds rs1 and op2, and stores result in rd.

Instruction:
addcc

Same as above, except that it sets the condition codes.

Instruction:
sub

subtracts op2 from rs1, and stores the difference in rd

Instruction:
subcc

same as above, except that it sets the condition codes.

Instruction:
mulcc

Performs a single step in the multiplication operation. Stores partial results in register Y. Complete multiplication algorithms are discussed in more detail later.

Extended Precision edit

These instructions account for the carry bit setting, so that large numbers (larger then the machine word) can be virtually manipulated as a single entity.

Instruction:
addx

Performs extended addition (adds two operands and carry bit), and stores result in rd.

Instruction:
addxcc

Same as above, but sets the condition codes.

Instruction:
subx

Performs extended subtractions (subtracts op2 and C from rs1) and stores result in rd.

Instruction:
subxcc

same as above, but sets the condition codes.

Tagged Instructions edit

Instruction:
tsubcc
Instruction:
tsubcctv
Instruction:
taddcc
Instruction:
taddcctv

Y Register edit

These operations affect the Y register.

Instruction:
rdy

reads the contents of the Y register in to the rd destination register

Instruction:
wry

exclusively ORs the rs1 and op2 values, and stores that result in the Y register.

Logic Instructions edit

Instruction:
and

performs the bitwise AND of rs1 and op2, and stores the result in rd.

Instruction:
andcc

same as above, sets the condition codes.

Instruction:
or

performs the bitwise OR of rs1 and op2, and stores the result in rd.

Instruction:
orcc

same as above, sets the condition codes.

Instruction:
xor

performs the bitwise XOR, between rs1 and op2. stores the result in rd.

Instruction:
xorcc

same as above, sets the condition codes.

Instruction:
xnor

performs the bitwise XNOR between rs1 and op2. puts result in rd.

Instruction:
xnorcc

same as above, sets condition codes.

Inverted Logic Operations edit

Instruction:
andn

ANDs rs1 and the bitwise inverse of op2. stores result in rd.

Instruction:
andncc

same as above, sets condition codes.

Instruction:
orn

ORs rs1 and the bitwise inverse of op2. stores the result in rd.

Instruction:
orncc

same as above, sets the condition codes.

Shift Instructions edit

Instruction:
sll

performs the logical left-shift of rs1. Shift amount is according to value of op2. result is stored in rd.

Instruction:
srl

performs the logical right-shift of rs1. Shift amount is the value of op2. stores the result into rd.

Instruction:
sra

performs the arithmetic right-shft of rs1. shift amount is the value of op2. stores the result in rd.


Memory Instructions

Instruction Format edit

This is going to be a quick primer for how to write these memory instructions.

Load Instruction Format edit

Memory instructions load a value from memory, or store a value into memory. The target address is computed as the addition of a base value with an optional offset value.

For example:

ld [%r4 + 10], %r5

loads the register %r5 with the value in memory located at [%r4 + 10]. If %r4 contains the number 25, then the memory location read would be [25 + 10] = 35. The op2 parameter, like the arithmetic instructions can be a register or an immediate. This means that the following are both valid:

ld [%r4 + %r3], %r5
ld [%r4 + 100], %r5

The offset value is the number of bytes offset, not the number of machine words or halfwords. This means that to load consecutive words on a 32 bit machine, the offset needs to be incremented by 4:

ld [%r4 + 4], %r5
ld [%r4 + 8], %r6
...

Also, the offset value is optional. If the offset is omitted, the assembler will assume a value of 0. For example:

ld [%r4], %r5

will read from location %r4, with no offset.

Store Instruction Format edit

Store instructions are similar to load instructions, except that the operands are reversed. This means that we have the following instruction format:

st rd, [rs1 + op2]

All the rest of the above material applies.

Load Instructions edit

Instruction:
ldub

Loads an unsigned byte from memory into rd.

Instruction:
ldsb

loads a signed byte from memory into rd. sign-extends result.

Instruction:
lduh

loads an unsigned halfword from memory into rd.

Instruction:
ldsh

loads a signed halfword from memory into rd. Sign extends result.

Instruction:
ld

loads a machine word into rd.

Instruction:
ldd

Loads a double word into 2 consecutive registers.

Store Instructions edit

Instruction:
stb

Stores a byte from register rd into memory.

Instruction:
sth

stores a halfword from register rd into memory.

Instruction:
st

stores a machine word from register rd into memory.

Instruction:
std

stores a double value from two consecutive registers into memory.

Swap Instruction edit

Instruction:
swap

performs a simultaneous load and store operation, which effectively swaps the value in memory with the value in rd. Is formatted like a load instruction, for example:

swap [%r3 + 4], %r5


Control Flow

Comparison edit

Instruction:
cmp

compares two numbers (Subtraction). Sets flags.

Instruction:
tst

tests two numbers (performs 'and' operation). Sets flags.

Jump Instructions edit

Instruction:
jmp

jumps to specified indirect address. stores return address in %o7.

Instruction:
jmpl

Performs an unconditional, register indirect jump. Target address is provided in the first operand, and the return address is then stored into the rd operand.

jmpl rs1, rd

If the return address is stored in %o7, this acts like a subroutine call. If the return address is stored in %g0, it acts like a subroutine return.

Instruction:
sethi

Sets the highest 22 bits of the target register, sets the lowest 10 bits to zero.

sethi const22, rd

const22 must be a constant value, cannot be a register.

Subroutine Instructions edit

Instruction:
call

calls a subroutine. Takes a single label as a new target address. Stores the return address in %o7. cannot jump to a register indirect address.

Instruction:
ret

return from a subroutine.

Instruction:
retl

return from a leaf subroutine.

Instruction:
rett

Return from a trap instruction, or from a register indirect control transfer.

Instruction:
save

saves the current register window and creates a new window. raises an exception if there is a register window overflow.

Instruction:
restore

restores a saved register window.

Branch Instructions edit

branches do not store the return address.

Instruction:
ba

Branch always. an unconditional jump to the target location. d

Instruction:
bn

Branch never.

Instruction:
be
Instruction:
bne

branches if the two operands are equal or not equal, respectively.

Instruction:
bl

branches on "less than"

Instruction:
ble

branches on "less than or equal"

Instruction:
bge

branches on "greater than or equal"

Instruction:
bg

branches on "greater than"

Instruction:
blu
Instruction:
bleu

Same as bl and ble, except uses unsigned numbers

Instruction:
bgeu
Instruction:
bgu

Same as bge and bg, except uses unsigned numbers

Instruction:
bpos

branches if the number is positive.

Instruction:
bneg

branches if the number is negative.

Instruction:
bcs
Instruction:
bcc

branches if the carry bit is set or clear, respectively.

Instruction:
bvs
Instruction:
bvc

branches if the signed overflow bit is set or clear, respectively.


Floating Point

Floating Point Numbers edit

Floating Point Arithmetic edit

Floating Point Comparisons edit

Floating Point Branches edit

Further Reading edit


Condition Codes & Branching

The Binary Number System edit

The binary (base two) system is the number system that computers use to represent the data stored in them. In contrast with the base ten system that we are used to, which uses numbers 0-9 to represent all possible real numbers, the binary system uses only numbers 0-1. For example, the number 2112 is represented as a binary number is 100001000000, the number 3 is 11, and as you might suspect, the number 0 is still just 0.

It may seem that choosing to represent numbers in this way only introduces unnecessary hassle and complexity that impedes usability, but actually the opposite is true. The reason computer engineers chose to use this relatively unfamiliar number system is that it is much simpler to implement and represent using computer circuitry, and thus makes the creation of more elaborate computer components much simpler than it would be if a higher base system was used.

Binary Arithmetic edit

Even though it may seem the contrary, binary numbers can be used just as base ten numbers can. You can add them, subtract them, multiply them, divide them, square them, and so on. For now, more information can be found here.

Two's Complement edit

While adding two numbers in Binary may be trivial, the subtraction of even the smallest of values is much more complicated. Fortunately the Two's complement rule allows for a binary subtraction to be converted into an addition operation which is easier to perform.

Take the following example:

 ...8421 (value in decimal system)
 ...1001 (9 in binary)

(9-15 in binary)
    1001
    1111 -
    -------
    
    To perform two's complement first you must find the one's complement which
    is simply the NAND (Negated AND) of the number that is being subtracted.
    
    To find the two's complement simply perform binary addition of 1 to the 
    one's complement.
    
                    NAND    1111
    one's complement:       0000
    
                            0000
                                1+
                            -------
     two's complement:      0001
     
(adding the first number and the two's complement)
                            1001
                            0001 +
                            -------
                            1010    
   
    The remainder should be -6, however here we have 10 in decimal, 
    the reason is because the number is a signed value. Here it should represent -6. 
    To confirm the value we have is correct we must perform an additional two's 
    complement on the result.
                            
                            1010
                            0101 
                               1 +
                            -------
                            0110 (6 in decimal)
    This proves that we have -6 as the result of the subtraction.

Signed and Unsigned Numbers edit

Condition Codes edit

Condition Code Registers are special flags (bits) contained the condition code register (CCR) that are used to record information about condition code (<opcode>cc) instructions so that branching decisions may be made by a program. As discussed above, the context of whether a number is signed or unsigned will imply very different results when it is used in calculation. As such, SPARC uses different sets of CCR's to manage signed and unsigned data.


Signed Condition Codes edit

For signed numbers, SPARC uses three of the three condition codes- the Z, N, and V bits - to regulate conditional branching:


  • Z: This flag keeps track of whether the result of a calculation of a condition code instruction was zero or not. If the result is zero it is set to 1, if not it is set to 0. For example,
mov 4, %l1         !move 4 into %l1
subcc %l1, 4, %g0  !subtract 4 from %l1
would set the Z register to 1, but
 
mov 4, %l1         !move 4 into %l1
subcc %l1, 3, %g0  !subtract 3 from %l1
would set it to zero.


  • N: This flag keeps track of whether the result of a calculation of a signed condition code instruction was negative or not. if the result is negative it is set to 1, if not it is set to 0. For example,
mov 4, %l1         !move 4 into %l1
subcc %l1, 5, %g0  !subtract 5 from %l1
would set the N register to 1, but
 
mov 4, %l1         !move 4 into %l1
subcc %l1, 3, %g0  !subtract 3 from %l1
would set it to zero.


  • V: This flag keeps track of whether the result of a signed calculation is too large to be held by a 32 bit (or possibly 64 bit) register. If the result is too large it is set to 1, if not it is set to 0.

Unsigned Condition Codes edit

Branch Instructions edit


Control Structures

If you're familiar with any higher level programming language (C, C++, Java, etc.), then you are likely aware of the tremendous capabilities that control structures afford computer programmers. Control structures allow us to have our programs make decisions about which code block to execute, and possibly even how many times to execute that block of code. Though somewhat more cryptic, control structures in SPARC afford us the same capabilities. We will discuss a few of the more common ones below.

If Then edit

As you might have guessed from the section on branching, an if-then structure is comprised simply of a branch statement that skips the code in the "if" block and branches to a label the marks the beginning of the code to be executed after the if block . For example, if in psuedocode our goal is to have a program that looks like


if register %l0 is less than zero{
::then 'and' it with register %g0 and store the result in %l0
::then and add one to %l0
}

'or' the code with the base two version of 42 and store the result back in %l0


then the SPARC version of this would be

cmp %l0, 0
bge next
nop

and %l0, %g0, %l0
add %l0, 1, %l0

next: or %l0, 42, %l0

Note that we have negated the logic of the if statement from "if %l0 is less than zero, then do this" to "if %l0 is not greater than zero, then do not do this". This is necessary because our ability to create control structures to comes from our ability to skip portions of code. So what we are telling the computer is that if this condition is not true, then skip all of this code here and move on the next set of labeled instructions.

If Else edit

This is similar to the if-then structure but requires more branching. The basic point of if-else is to do the following:

If some condition is true{
   then preform this set of instructions
}

If the condition is false (the else part){
 then execute this set of instructions
}  

So, if we want to do this in SPARC, we branch to the "else" part just like we would to the "next" label in the if-then code. However, we also need to ensure that if the 'if' block is executed, then the 'else' block is skipped when after th 'if' block finishes executing. So for sake of example, lets say that in the previous example we wanted to set %l0 to zero if the condition was not satisfied. The code is as follows:

cmp %l0, 0
bge else
nop

and %l0, %g0, %l0
add %l0, 1, %l0

ba next
nop

else: mov 0, %l0
next: or %l0, 42, %l0

Notice now that when the 'if' condition is false we now move to the 'else' statement instead of 'next'. Also notice that we now have a 'branch always' instruction at the end of the if block that allows us to skip the 'else' block when the 'if' block has been executed.

While Loops edit

Do-While Loops edit

For Loops edit

Multiplication and Division

Looking through the lists of instructions, it becomes clear that multiplication and division operations are not provided in SPARC: at least not in a form that most programmers are familiar with. This page is going to discuss the algorithms used to perform multiplication and division operations in SPARC

Example edit


To multiply %l3 and %l4 and store in %l5:

mov%l3%o0! First operand
mov%l4%o1! Second operand
call.mul! Result stored in %o0
! To divide %l3 by %l4, use .div
! To find the modulus, use .rem
nop! Delay slot
mov%o0%l5! Copy result to %l5


Data Structures

One Dimensional Arrays edit

Multi-Dimensional Arrays edit

Structures edit

Structures of Structures edit

Subroutines

This page is going to discuss the use of subroutines in SPARC Assembly.

Saving Registers edit

Subroutine Linkage edit

A typical (non-leaf) subroutine has a procedure prologue and epilogue something like this:[1][2]

do_something_useful:
    ; prologue:
    save %sp, -16, %sp

    ; main body
    ; ... perform function ...

    ; leave return value, if any, in register %i0

    ; epilogue:
    ret
    restore

Return Values edit

Further reading edit


SPARC Assemblers

This page is going to discuss some assemblers for programming SPARC Assembly.


SPARC Emulators

One possible solution is to use QuickTransit from Transitive, which allows SPARC binaries to execute on Solaris/x86, Linux/x86 or Linux/Itanium systems. It can be downloaded from the Transitive Web site at: http://www.transitive.com/evaluate. Unfortunately, IBM has acquired Transitive and is no longer selling Transitive, instead integrating it into their PowerVM product. Whether Transitive will be available as a stand-alone emulator in the future or not is yet to be seen.


Another option is QEMU. QEMU supports several SPARC platforms and is capable of booting operating systems NetBSD for example which still actively supports both 32 bit and 64 SPARC. Sources for QEMU can be found at the QEMU Wiki. Or install it via your native packaging system precompiled binaries of recent versions of QEMU are available for windows at this site: http://lassauge.free.fr/qemu/.


Pseudo-Ops

This page is going to discuss SPARC Pseudo-Ops.

Pseudo-Ops edit

In addition to the SPARC instructions and synthetic instructions, there are a number of assembler-provided "Pseudo-Ops" that create convenience for the programmer.

  • .ascii
  • .asciz
  • .text
  • .data
  • .bss
  • .skip
  • .align
  • .byte
  • .half
  • .word
  • .single
  • .double
  • .quad
  • .global
  • .common
  • .empty

This chapter will (hopefully) discuss each of these.


Synthetic Instructions

Synthetic Instructions edit

The SPARC Instruction set leaves out a number of conveniences that programmers have grown accustomed to. To fill in these gaps, SPARC assemblers implement a set of Synthetic Instructions. These Synthetic Instructions use the existing SPARC instructions to perform additional tasks. Some of these Synthetic Instructions have already been listed in the sections about the instructions, but for completeness, we are going to list the operations that are Synthetic Instructions here.

  • cmp %r1, %r2 = subcc %r1, %r2, %g0
  • jmp
  • tst
  • call
  • ret
  • retl
  • set
  • not %r1 = xnor %r1, %g0, %r1
  • neg
  • inc
  • inccc
  • dec
  • deccc
  • btst
  • bset
  • bclr
  • btog
  • clr
  • clrb
  • clrh
  • mov

These operations, strictly speaking, are not part of SPARC Assembly, but are instead provided as macros to ease the task of programming. This chapter will (hopefully) address specifically how each of these instructions are implemented.


Instruction Formats

Op Codes edit

Format Three Instructions edit

Instruction Decoding edit

Traps and Exceptions

Processor State Registers edit

Traps edit

Window Traps edit

Exceptions edit

Memory Management

Virtual Memory edit

Page Descriptor Cache edit

Cache Memory edit

Context Switching edit

Sparc V8

 
A TI SuperSPARC, based on SPARC V8.

Some examples of 32bit SPARC V8 computers are the sun4m architecture as well as the embedded systems based on the LEON SPARC which is compatible with the SPARC V8 instruction set.


Ultra SPARC

 
A Sun UltraSparc.

This page is going to discuss the upgrades in Ultra SPARC, and will discuss some issues thereof.

The UltraSPARC processors were designed by Sun Microsystems and implement the SPARC version 9 (sparcv9) architecture. This architecture natively supports 64 bit processing by extending the virtual address space to 64 bits and widening the general purpose registers to 64 bits.



Resources

Wikimedia Resources edit

External Resources edit


Licensing

The text of this book is released under the following license: