ghc-9.11: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.CmmToAsm.RV64.Instr

Synopsis

Documentation

stackFrameHeaderSize :: Int Source #

Stack frame header size in bytes.

The stack frame header is made of the values that are always saved (regardless of the context.) It consists of the saved return address and a pointer to the previous frame. Thus, its size is two stack frame slots which equals two addresses/words (2 * 8 byte).

spillSlotSize :: Int Source #

All registers are 8 byte wide.

stackAlign :: Int Source #

The number of bytes that the stack pointer should be aligned to.

maxSpillSlots :: NCGConfig -> Int Source #

The number of spill slots available without allocating more.

spillSlotToOffset :: Int -> Int Source #

Convert a spill slot number to a *byte* offset.

regUsageOfInstr :: Platform -> Instr -> RegUsage Source #

Get the registers that are being used by this instruction. regUsage doesn't need to do any trickery for jumps and such. Just state precisely the regs read and written by that insn. The consequences of control flow transfers, as far as register allocation goes, are taken care of by the register allocator.

RegUsage = RU [regs] [regs]

callerSavedRegisters :: [Reg] Source #

Caller-saved registers (according to calling convention)

These registers may be clobbered after a jump.

patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr Source #

Apply a given mapping to all the register references in this instruction.

isJumpishInstr :: Instr -> Bool Source #

Checks whether this instruction is a jump/branch instruction.

One that can change the flow of control in a way that the register allocator needs to worry about.

jumpDestsOfInstr :: Instr -> [BlockId] Source #

Get the BlockIds of the jump destinations (if any)

patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr Source #

Change the destination of this (potential) jump instruction.

Used in the linear allocator when adding fixup blocks for join points.

mkSpillInstr Source #

Arguments

:: HasCallStack 
=> NCGConfig 
-> Reg

register to spill

-> Int

current stack delta

-> Int

spill slot to use

-> [Instr] 

Generate instructions to spill a register into a spill slot.

mkLoadInstr Source #

Arguments

:: NCGConfig 
-> Reg

register to load

-> Int

current stack delta

-> Int

spill slot to use

-> [Instr] 

Generate instructions to load a register from a spill slot.

takeDeltaInstr :: Instr -> Maybe Int Source #

See if this instruction is telling us the current C stack delta

isMetaInstr :: Instr -> Bool Source #

Not real instructions. Just meta data

mkRegRegMoveInstr :: Reg -> Reg -> Instr Source #

Copy the value in a register to another one.

Must work for all register classes.

takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg) Source #

Take the source and destination from this (potential) reg -> reg move instruction

We have to be a bit careful here: A MOV can also mean an implicit conversion. This case is filtered out.

mkJumpInstr :: BlockId -> [Instr] Source #

Make an unconditional jump instruction.

mkStackAllocInstr :: Platform -> Int -> [Instr] Source #

Decrement sp to allocate stack space.

The stack grows downwards, so we decrement the stack pointer by n (bytes). This is dual to mkStackDeallocInstr. sp is the RISCV stack pointer, not to be confused with the STG stack pointer.

mkStackDeallocInstr :: Platform -> Int -> [Instr] Source #

Increment SP to deallocate stack space.

The stack grows downwards, so we increment the stack pointer by n (bytes). This is dual to mkStackAllocInstr. sp is the RISCV stack pointer, not to be confused with the STG stack pointer.

data Instr Source #

Constructors

COMMENT SDoc

Comment pseudo-op

MULTILINE_COMMENT SDoc

Multi-line comment pseudo-op

ANN SDoc Instr

Annotated instruction. Should print instr # doc

LOCATION Int Int Int LexicalFastString

Location pseudo-op .loc (file, line, col, name)

LDATA Section RawCmmStatics

Static data spat out during code generation.

NEWBLOCK BlockId

Start a new basic block.

Useful during codegen, removed later. Preceding instruction should be a jump, as per the invariants for a BasicBlock (see Cmm).

DELTA Int

Specify current stack offset for benefit of subsequent passes

PUSH_STACK_FRAME

Push a minimal stack frame consisting of the return address (RA) and the frame pointer (FP).

POP_STACK_FRAME

Pop the minimal stack frame of prior PUSH_STACK_FRAME.

ADD Operand Operand Operand

Arithmetic addition (both integer and floating point)

rd = rs1 + rs2
SUB Operand Operand Operand

Arithmetic subtraction (both integer and floating point)

rd = rs1 - rs2
AND Operand Operand Operand

Logical AND (integer only)

rd = rs1 & rs2
OR Operand Operand Operand

Logical OR (integer only)

rd = rs1 | rs2
SLL Operand Operand Operand

Logical left shift (zero extened, integer only)

rd = rs1 << rs2
SRL Operand Operand Operand

Logical right shift (zero extened, integer only)

rd = rs1 >> rs2
SRA Operand Operand Operand

Arithmetic right shift (sign-extened, integer only)

rd = rs1 >> rs2
STR Format Operand Operand

Store to memory (both, integer and floating point)

LDR Format Operand Operand

Load from memory (sign-extended, integer and floating point)

LDRU Format Operand Operand

Load from memory (unsigned, integer and floating point)

MUL Operand Operand Operand

Arithmetic multiplication (both, integer and floating point)

rd = rn × rm
NEG Operand Operand

Negation (both, integer and floating point)

rd = -op2
DIV Operand Operand Operand

Division (both, integer and floating point)

rd = rn ÷ rm
REM Operand Operand Operand

Remainder (integer only, signed)

rd = rn % rm
REMU Operand Operand Operand

Remainder (integer only, unsigned)

rd = |rn % rm|
MULH Operand Operand Operand

High part of a multiplication that doesn't fit into 64bits (integer only)

E.g. for a multiplication with 64bits width: rd = (rs1 * rs2) >> 64.

DIVU Operand Operand Operand

Unsigned division (integer only)

rd = |rn ÷ rm|
XOR Operand Operand Operand

XOR (integer only)

rd = rn ⊕ op2
ORI Operand Operand Operand

ORI with immediate (integer only)

rd = rn | op2
XORI Operand Operand Operand

OR with immediate (integer only)

rd = rn ⊕ op2
MOV Operand Operand

Move to register (integer and floating point)

rd = rn or rd = #imm

CSET Operand Operand Operand Cond

Pseudo-op for conditional setting of a register.

if(o2 cond o3) op <- 1 else op <- 0
J_TBL [Maybe BlockId] (Maybe CLabel) Reg

A jump instruction with data for switch/jump tables

B Target

Unconditional jump (no linking)

BL Reg [Reg]

Unconditional jump, links return address (sets ra/x1)

BCOND Cond Operand Operand Target

branch with condition (integer only)

FENCE FenceType FenceType

Fence instruction

Memory barrier.

FCVT FcvtVariant Operand Operand

Floating point conversion

FABS Operand Operand

Floating point ABSolute value

FMA FMASign Operand Operand Operand Operand

Floating-point fused multiply-add instructions

  • fmadd : d = r1 * r2 + r3
  • fnmsub: d = r1 * r2 - r3
  • fmsub : d = - r1 * r2 + r3
  • fnmadd: d = - r1 * r2 - r3

data FenceType Source #

Operand of a FENCE instruction (r, w or rw)

data FcvtVariant Source #

Variant of a floating point conversion instruction

data Target Source #

Constructors

TBlock BlockId 
TReg Reg 

data Operand Source #

Constructors

OpReg Width Reg

register

OpImm Imm

immediate value

OpAddr AddrMode

memory reference

Instances

Instances details
Show Operand Source # 
Instance details

Defined in GHC.CmmToAsm.RV64.Instr

Eq Operand Source # 
Instance details

Defined in GHC.CmmToAsm.RV64.Instr

Methods

(==) :: Operand -> Operand -> Bool #

(/=) :: Operand -> Operand -> Bool #

fitsIn12bitImm :: (Num a, Ord a) => a -> Bool Source #

fitsIn32bits :: (Num a, Ord a, Bits a) => a -> Bool Source #

Orphan instances

Outputable RegUsage Source # 
Instance details

Methods

ppr :: RegUsage -> SDoc Source #