## LSU EE 4720 -- Spring 2003 -- Computer Architecture
#
## Assembler Notes -- RISC ISAs: MIPS, DLX, SPARC
## Under Construction
#
# Time-stamp: <12 February 2003, 15:28:55 CST, koppel@drop>
## Contents
#
# Major ISA Families
# Summary of MIPS, DLX, and SPARC Instructions
# MIPS, DLX, and SPARC Floating-Point Instructions
## Objectives
#
# Major ISA Families
# Define, know main features of.
# DLX and SPARC
# Understand enough to figure out simple programs and use a reference
# for less simple ones.
# MIPS v. SPARC: Instruction Similarities and Differences
# Floating point, jumps, overflow, branch conditions, etc.
# Coding and Instructions
# Understand how coding affects instructions. (Immed. sizes, opcodes, etc.)
# Understand basic tradeoffs in coding alternatives.
# (Simpler format vs. larger immediates, etc.)
# Floating Point
# Read and write MIPS programs using floating point instructions.
# Understand how SPARC and DLX use floating point.
################################################################################
## Major ISA Families
## ISA Families
# :Def: ISA Family
# A broad classification of ISAs based on a contemporary understanding
# of significant features and characteristics.
# There are many ISAs, with many characteristics.
#
# Two ISAs can be similar (MIPS, Alpha) or different (MIPS, IA-32).
#
# There are generally accepted families of ISAs.
# ISAs in the same family are similar.
# ISAs in the different family are very different.
#
# Three families are described below.
# More details covered in a different set.
#
# RISC: Simple Design
# CISC: Powerful Instructions
# VLIW: Faster Multiple-Issue (covered later) Implementations.
#
# The families above are mutually exclusive (an ISA can't be in more
# than one).
# There are additional families. (An ISA may not fit in to any of the three.)
## RISC
#
# Reduced Instruction Set Computing
## Goals
#
# Simple to write compilers for.
# Low-cost and fast implementations (based on 1980's technology).
## Current Status
#
# Dominant for technical workstations, servers, and other large computers.
# ISAs and implementations continue to be developed though momentum slowing.
## Characteristics
#
# All instructions are the same size, (usually 32 bits).
# Moderate number of registers.
# Only "load" and "store" instructions allowed to access memory.
# (Arithmetic instructions cannot access memory.)
# Amount of work done by instructions balanced.
## Examples
#
# MIPS, SPARC, Alpha, PA-RISC, PowerPC
#
# This class will frequently use MIPS and SPARC.
## CISC
#
# Complex Instruction Set Computing
## Goals
#
# Provide powerful (do-everything) instructions. (1970s/1980s)
## Characteristics
#
# Instruction sizes vary.
# Moderate number of registers.
# Arithmetic and other instructions can access memory.
## Examples
#
# VAX
# Arguably: IA-32 (80x86,Pentium)
## Current Status
#
# Little new development, except for IA-32
# In 20th century outperformed by RISC.
## VLIW
#
# Very-Large Instruction Word
## Goals
#
# Allow fast multiple issue implementations by handling
# instructions in bundles.
## Characteristics
#
# Instructions handles in groups (usually of 3) called /bundles/.
# Information about instruction relationships provided to hardware.
## Examples
#
# Itanium, Tera
## Current Status
#
# Used in special purpose applications, such as signal processing.
# Being introduced for general purpose use. Itanium
################################################################################
## ISAs Used in EE 4720
## MIPS
#
# Used in the Patterson & Hennessy and Hennessy & Patterson 3rd Edition texts.
# An early and still popular RISC ISA.
## DLX
#
# Used in the Hennessy & Patterson 2nd Edition text.
# A simplified form of MIPS.
## SPARC
#
# Used in ECE Sun computers.
## Use in EE 4720
# Many ISAs will be used, some are briefly covered.
#
# Details, including implementations, given for MIPS and DLX.
#
# Emphasis this semester (Spring 2002) and later on MIPS.
# Older material uses DLX.
################################################################################
## MIPS, DLX, and SPARC
# MIPS refers to MIPS-I
# SPARC refers to SPARC V8
## Registers and Memory
#
# All : 32 general-purpose registers (GPR), 32 floating-point registers.
# GPR are 32 bits.
# FP registers are 32 bits but can be used in pairs.
# FP instructions can only access floating-point registers.
#
#
# MIPS: Two 32-bit integer multiplication and division registers (hi/lo).
# SPARC: Y register for use in multiplication.
# SPARC: Implementation can provide more than 32 GPRs.
#
# Registers
#
# DLX GPR: r0 - r31. Register r0 is always zero.
# MIPS GPR: $0 - $31. Register $0 is always zero.
# MIPS GPRs also have names. E.g., $t0, $ra
# MIPS: $hi, $lo. Used for product, quotient, and remainder.
# SPARC: Divided into four sets of 8:
# %g0-%g7 Global. %g0 is always zero.
# %l0-%l7 Local.
# %i0-%i7 Input. Used for function arguments.
# %o0-%o7 Output. Used for function arguments.
# SAVE and RESTORE instructions "copy" registers.
#
# DLX FPR: f0 - f31.
# MIPS FPR: $f0 - $f31
# SPARC FPR: %f0 - %f31
#
#
# Memory
#
# All: 32-bit address space.
# Aligned Access
#
# SPARC, DLX: Big Endian.
# MIPS: Either. (Big endian used in class.)
# Assembly Language Differences
#
# MIPS, DLX: Destination is first (leftmost) operand.
add r1, r2, r3 # r1 = r2 + r3
# SPARC: Destination is last (rightmost) operand.
add %l2, %l3, %l1 # %l1 = %l2 + %l3
#
# MIPS, DLX: Parenthesis used for dereference, offset is outside parens.
lw $s1, 4($s2)
# SPARC: Square brackets used for dereference, offset is inside:
ld [%l2+4], %l1
################################################################################
## Instruction Coding
## The Three MIPS, DLX Instruction Formats
#
# R Format: Typically used for three-register instructions.
# I Format: Typically used for instructions requiring an immediate.
# J Format: Used for jump instructions.
## The Three (or six) SPARC Instruction Formats
#
# Format 1: Used for calls.
# Format 2a: Used for sethi (like lui).
# Format 2b: Used for branches.
# Format 3a: Typically used for three-register and load/store instructions.
# Format 3b: Typically used for instructions requiring an immediate.
# Format 3c: Typically used for three-register floating-point instructions.
## MIPS R Format
# _________________________________________________________________
# | opcode | rs | rt | rd | sa | function |
# ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
# 3 3 2 2 2 2 2 2 2 2 2 2 1 1 1 1 1 1 1 1 1 1 0 0 0 0 0 0 0 0 0 0
# 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0
#
# Bits Field Name Unabbreviated Name Typical Use
#
# 31:26: opcode First part of opcode.
# 25:21: rs (Register Source) Source register one.
# 20:16: rt (Register Target) Source register two.
# 15:11: rd (Register Destination) Destination register.
# 10:6: sa (Shift Amount) Five-bit immediate.
# 5:0 function Second part of opcode.
#
add $s0, $s1, $s2 # $s0 = $s1 + $s2
## DLX Type-R Instruction
# _________________________________________________________________
# | opcode | rs1 | rs2 | rd | func |
# ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
# 0 0 0 0 0 0 0 0 0 0 1 1 1 1 1 1 1 1 1 1 2 2 2 2 2 2 2 2 2 2 3 3
# 0 1 2 3 4 5 6 7 8 9 0 1 2 3 4 5 6 7 8 9 0 1 2 3 4 5 6 7 8 9 0 1
#
# Bits Field Name Typical Use
#
# 0: 5 opcode First part of opcode.
# 6:10: rs1 Source register one.
# 11:15: rs2 Source register two.
# 16:20: rd Destination register.
# 21:31 function Second part of opcode.
#
add r1, r2, r3 # r1 = r2 + r3
## SPARC Format 3a (op =2 or 3, i = 0)
# _________________________________________________________________
# | op| rd | op3 | rs1 |i| asi | rs2 |
# ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
# 3 3 2 2 2 2 2 2 2 2 2 2 1 1 1 1 1 1 1 1 1 1 0 0 0 0 0 0 0 0 0 0
# 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0
#
# Bits Field Name Description
#
# 31:30: op Opcode
# 29:25: rd Destination Register
# 24:19: op3 Opcode part 3. (No part 2.)
# 18:14: rs1 Source operand 1 register number.
# 13:13: i Immediate Sub-format. Zero in this case.
# 12:05: asi Address space identifier. Used by loads and stores.
# 04:00: rs2 Source operand 2 register number.
add %l2, %l3, %l1 # %l1 = %l2 + %l3
## MIPS I Format
# _________________________________________________________________
# | opcode | rs | rt | immed |
# ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
# 3 3 2 2 2 2 2 2 2 2 2 2 1 1 1 1 1 1 1 1 1 1 0 0 0 0 0 0 0 0 0 0
# 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0
#
# Bits Field Name Unabbreviated Name Typical Use
#
# 31:26: opcode Entire opcode (for I and J).
# 25:21: rs (Register Source) Source register one.
# 20:16: rt (Register Target) Source register two.
# 15:0: immed (Immediate) Immediate value.
## DLX Type I
# _________________________________________________________________
# | opcode | rs1 | rd | immed |
# ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
# 0 0 0 0 0 0 0 0 0 0 1 1 1 1 1 1 1 1 1 1 2 2 2 2 2 2 2 2 2 2 3 3
# 0 1 2 3 4 5 6 7 8 9 0 1 2 3 4 5 6 7 8 9 0 1 2 3 4 5 6 7 8 9 0 1
#
# Bits Field Name Typical Use
#
# 0: 5 opcode First part of opcode.
# 6:10: rs1 Source register one.
# 11:15: rd Destination register.
# 16:31 immed Immediate
## SPARC Format 3b (op =2 or 3, i = 1)
# _________________________________________________________________
# | op| rd | op3 | rs1 |i| simm13 |
# ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
# 3 3 2 2 2 2 2 2 2 2 2 2 1 1 1 1 1 1 1 1 1 1 0 0 0 0 0 0 0 0 0 0
# 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0
#
# Bits Field Name Description
#
# 31:30: op Opcode
# 29:25: rd Destination Register
# 24:19: op3 Opcode part 3. (No part 2.)
# 18:14: rs1 Source operand 1 register number.
# 13:13: i Immediate Sub-format. One in this case.
# 12:00: simm13 The immediate.
# Used for memory and arithmetic / logical.
## SPARC Format 2a (op = 0) (sethi)
# _________________________________________________________________
# | op| rd | op2 | imm22 |
# ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
# 3 3 2 2 2 2 2 2 2 2 2 2 1 1 1 1 1 1 1 1 1 1 0 0 0 0 0 0 0 0 0 0
# 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0
#
# Bits Field Name Description
#
# 31:30: op Opcode
# 29:25: rd Destination Register
# 24:22: op2 Opcode part 2.
# 21:00: imm22 The immediate.
#
# Used for sethi.
## SPARC Format 2b (op = 0) (branches)
# _________________________________________________________________
# | op|a| cond | op2 | imm22 |
# ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
# 3 3 2 2 2 2 2 2 2 2 2 2 1 1 1 1 1 1 1 1 1 1 0 0 0 0 0 0 0 0 0 0
# 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0
#
# Bits Field Name Description
#
# 31:30: op Opcode
# 29:29: a Typical: If one instruction in delay slot annulled.
# 28:25: cond Condition. Some function of condition code register.
# 21:00: imm22 The immediate, a branch displacement.
#
# Used for branches.
## MIPS J Format
# _________________________________________________________________
# | opcode | ii |
# ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
# 3 3 2 2 2 2 2 2 2 2 2 2 1 1 1 1 1 1 1 1 1 1 0 0 0 0 0 0 0 0 0 0
# 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0
#
# Bits Field Name Unabbreviated Name Typical Use
#
# 31:26: opcode Entire opcode (for I and J).
# 25:0: ii (Instruction Index) Part of jump target.
## SPARC Format 1 (op = 1)
# _________________________________________________________________
# | op| disp30 |
# ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
# 3 3 2 2 2 2 2 2 2 2 2 2 1 1 1 1 1 1 1 1 1 1 0 0 0 0 0 0 0 0 0 0
# 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0
#
# Bits Field Name Unabbreviated Name Typical Use
#
#
# Used for calls.
## Basic Type-R Instructions
# DLX: add, addu, sub, subu, and, or, xor
# MIPS: add, addu, sub, subu, and, or, xor
# SPARC: add, sub, and, or, xor
# The MIPS addu and subu instructions are not unsigned, DLX are.
add $1, $2, $3 # MIPS
add r1, r2, r3 # DLX
## Basic Type-I Instructions
# DLX: addi, subi, andi, ori, xori
# MIPS: addi, andi, ori, xori
# SPARC: add, and, or, xor (Immediate uses same opcode.)
# DLX, MIPS Use 16-bit immediates; SPARC uses 13 bits.
addi $t0, $t1, 5 # MIPS
addi r2, r3, #5 # DLX
add %l1, 5, %l0 # SPARC
# MIPS does not have a subi, DLX does.
## Load Upper
# Loads the upper bits of a register with a constant.
# MIPS and DLX have different instruction names, but otherwise the same.
# MIPS: lui Load upper 16 bits.
# DLX: lhi Load upper 16 bits.
# SPARC: sethi Load upper 22 bits.
lui $1, 0x1234 # MIPS
lhi r1, #0x1234 # DLX
sethi 0x123456, %l1 # SPARC
# SPARC assembler "hi" macro extracts upper 22 bits from constant.
sethi %hi(0x12345678), %l1
## Shift Instructions
# MIPS: sllv, srlv, srav, sll, srl, sra
# DLX: sll, srl, sra, slli, srli, srai
# SPARC: sll, srl, sra
# MIPS constant shift instructions use special sa field, DLX use immed field.
sllv $1, $2, $3 # MIPS
sll r1, r2, r3 # DLX
sll $1, $2, 5 # MIPS
slli r1, r2, #5
## Load and Store Instructions
# DLX, MIPS: lb, lbu, lh, lhu, lw, sb, sh, sw
# SPARC: ldsb, ldub, ldsh, lduh, ld, stb, sth, st
# (SPARC instruction does same thing as MIPS above, e.g., lhu same as lduh).
# MIPS and DLX very similar.
lw $1, 16($2) # MIPS
lw r1, 16(r2) # DLX
ld [%l2+16], %l1 # SPARC
ld [%l2+%l3], %l1 # SPARC
sw $1, 16($t5) # MIPS
sw 16(r10), r1 # DLX
sd %l1, [%l5+16] # SPARC
## Integer Branches
# MIPS: beq, bne, bgtz, bgez, bltz, blez
# DLX: beq, bne
# SPARC: be, bne, bg, bge, blt, ble
# Integer Condition Code Register: ICC, four bits: N, Z, V, C
# MIPS: Branches have delay slots.
# Can compare registers.
#
# DLX: No delay slots.
# Can only test if a register is zero.
#
# SPARC: Delay slots (sometimes).
# Branch based on condition codes. (Covered later.)
# DLX
sub r6, r3, r4
beq r6, TARGET
xor r5, r6, r7
# MIPS
beq $3, $4, TARGET
nop
xor $5, $6, $7
# SPARC
subcc %l3, %l4, %g0 # Subtract and set condition codes.
beq TARGET
nop
xor %l6, %l7, %l5
TARGET:
add $1, $2, $3
## Jump
# MIPS: j, jr
# DLX: j, jr
# SPARC: Special cases of jump and link (jmpl) and branch instruction.
# MIPS: Delayed
# DLX: Not delayed.
# MIPS: Immediate is region.
# DLX: Immediate is displacement.
# PC= 0x12345678
# ii 0x3ffffff
# Region Address
# PC= 0x12345678
# 4ii 0x0ffffffc
# targ 0x1ffffffc
# Displacement (DLX)
# PC= 0x12345678
# 4ii 0x0ffffffc
# targ PC + 4ii = 0x22345674
# MIPS: TARGET is a 26-bit region.
# DLX: TARGET is a 26-bit displacement.
j TARGET
nop
# SPARC
# Use branch always instruction for jumps.
# TARGET is specified using a 22-bit displacement.
ba TARGET
# MIPS, DLX
# TARGET in $t0
jr $t0
nop
# SPARC
# TARGET in %l0, %g0 is zero register.
jmpl %l0 + 0, %g0
nop
TARGET:
## Jump and Link Instructions
# MIPS and DLX: jal, jalr
# SPARC: jmpl rs1 + simm13, rd (Jump to rs1 + simm13, save return in rd.)
# SPARC: jmpl rs1 + rs2, rd (Jump to rs1 + rs2, save return in rd.)
# SPARC: call disp30 (Jump to PC + 4 * disp30 )
# MIPS, DLX: Register 31 holds return address (link) (by default)
# MIPS: Can specify return address register.
jal TARG
nop
TARG:
################################################################################
## Floating Point Summary
## Separate Floating Point Registers
#
# A feature of many RISC ISAs.
# Eases implementation.
## MIPS Floating Point
#
# Supports IEEE 754 Single and Double FP Numbers
#
# Floating point handled by co-processor 1, one of 4 co-processors.
#
# MIPS floating point registers also called co-processor 1 registers.
# MIPS floating point instructions called co-processor 1 instructions.
#
# Registers named f0-f31.
# Load, store, and move instructions have "c1" in their names.
# Arithmetic instructions use ".s" (single) or ".d" (double) , or ".w" (int)
# /completers/ to indicate operand type.
#
## MIPS Co-Processors (Briefly)
#
# Each co-processor has a register set and instructions.
# Co-processor x abbreviated cpx.
#
# cp0: Used for virtual memory and exceptions (covered later).
# cp1: Used for floating point in MIPS32 (used in class).
# cp2: Reserved for custom implementations.
# cp3: Used for floating point in MIPS64.
## DLX Floating Point
#
# Supports IEEE 754 Single and Double FP Numbers
#
# Storage for FP registers called the FP register file.
#
# Registers named f0-f31.
# Load, store, and move instructions have "fp" in their names.
# Arithmetic instructions use "f" (single) or "d" (double)
# /completers/ to indicate operand type.
## Types of Floating-Point Instructions
#
# Briefly here, in detail later.
#
#
## Arithmetic Operations
#
# MIPS: add.d $f0, $f2, $f4
# DLX: addd f0, f2, f4
# SPARC: faddd %f0, %f2, %f4
#
#
## Load and Store
#
# MIPS: ldc1 $f0, 8($t0)
# DLX: ld f0, 8(r1)
# SPARC: ldf [%l0+8], %f0
#
#
## Move Between Register Files (E.g., integer to FP)
#
# MIPS: mtcp1 $f0, $t0
# DLX: movi2fp f0, r2
# SPARC: No such instructions. Use store / load:
# sd %l0, [%sp+16]
# lf [%sp+16], %f0
#
## Format Conversion
#
# Convert from one format to another, e.g., integer to double.
#
# MIPS: cvt.d.w $f0, $f2
# DLX: cvt.i2d $f0, $f2
# SPARC: fitod $f0, $f2
#
#
## Floating Point Condition Code Setting
#
# Compare and set condition code.
#
# MIPS: c.gt.d $f0, $f2
# DLX: gtd f0, f2
# SPARC: fcmpd $f0, $f2 # Condition codes set to =, <, >, or ?
#
#
## Conditional Branch
#
# Branch on floating-point condition.
#
# MIPS: bc1f TARGET # Branch coprocessor 1 [condition code] false.
# DLX: bfpf TARGET # Branch floating-point [condition code] false.
# SPARC: fbg TARGET # Branch condition code greater than.
#
## MIPS FP Load and Store
# Load word in to coprocessor 1
lwc1 $f0, 4($t4) # $f0 = Mem[ $t4 + 4 ]
# Load double in to coprocessor 1
ldc1 $f0, 0($t4) # $f0 = Mem[ $t4 + 0 ]; $f1 = Mem[ $t4 + 4 ]
# Store word from coprocessor 1.
swc1 $f0, 4($t4) # $f0 = Mem[ $t4 + 4 ]
# Store double from coprocessor 1.
sdc1 $f0, 0($t4) # $f0 = Mem[ $t4 + 0 ]; $f1 = Mem[ $t4 + 4 ]
## DLX FP Load and Store
# Load float (32 bit)
lf f0, 0(r1)
# Load double (64 bit)
ld f0, 0(r1)
## MIPS Move Instructions
# Move to coprocessor 1
mtc1 $f0, $t0
# Move from coprocessor 1.
mfc1 $t0, $f0
## DLX Move
# Move X to Y
# X,Y: fp, i
# X,Y: f,d
movX2Y rd, rs
## MIPS Conversion
# To: s, d, w; From: s, d, w
cvt.TO.FROM rd, rs
cvt.d.w $f0, $f2
## DLX Conversion
# X,Y: s, d, i
cvtXtoY
## MIPS Condition Setting
# Compare: fs COND ft
# COND: eq, gt, lt, le, ge
# FMT: s, d
c.COND.FMT fs, ft
c.lt.d $f0, $f2
## DLX Condition Setting
# Cond: gt, lt, eq, etc.
# FMT: f, d
<COND><FMT>
## MIPS FP Branch
# Branch coprocessor 1 true.
# Delayed branch.
bc1t TARG
bc1f TARG
# DLX FP Branch
bfpt TARG
bfpf TARG
## Integer Multiplication and Division
# MIPS/DLX: Not an ordinary integer arithmetic instruction.
#
# (After MIPS I ordinary integer multiplication added to ISA.)
#
# Early SPARC (before v8): No multiply instruction, use a multiply
# step (muls) many times to perform a multiplication.
# SPARC v8 has a multiply instruction that uses ordinary registers
# for the low 32 bits and a special register "Y" for the high 32 bits.
## Differing Approaches
#
# MIPS: Use a special integer multiply and divide unit.
# DLX: Use floating-point unit for integer multiply and divide.
# SPARC: Use any integer register for low 32 bits and Y register for high 32 bits
## MIPS Multiplication
#
# Product goes in to lo and hi registers.
#
# To multiply integers:
#
# Multiply
# Move product from lo and hi (if necessary) to integer registers.
mult $t0, $t1 # {hi,lo} = $t0 * $t1
mflo $t2 # $t2 = $lo
## DLX Multiplication
#
# Integer multiplication uses fp regs.
# r3 = r1 x r2
movi2fp f0, r1
movi2fp f1, r2
mul f3, f0, f1
movfp2i r3, f3
## SPARC Multiplication
#
#
# l3 = l1 x l2
smul %l1, %l2, %l3