ghc-9.13: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.CmmToAsm.LA64.Instr

Synopsis

Documentation

stackFrameHeaderSize :: Int Source #

Stack frame header size Each stack frame contains ra and fp -- prologue.

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)

0 | 1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 | 10 | 11 | 12 | 13 | 14 | 15 | 16 | 17 | 18 | 19 | 20 | 21 | 22 | 23 | 24 | 25 | 26 | 27 | 28 | 29 | 30 | 31 |

zero| ra | tp | sp | a0 | a1 | a2 | a3 | a4 | a5 | a6 | a7 | t0 | t1 | t2 | t3 | t4 | t5 | t6 | t7 | t8 | Rv | fp | s0 | s1 | s2 | s3 | s4 | s5 | s6 | s7 | s8 |

32 | 33 | 34 | 35 | 36 | 37 | 38 | 39 | 40 | 41 | 42 | 42 | 44 | 45 | 46 | 47 | 48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57 | 58 | 59 | 60 | 61 | 62 | 63 |

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 :: HasCallStack => NCGConfig -> RegWithFormat -> Int -> Int -> [Instr] Source #

Make a spill instruction, spill a register into spill slot.

mkLoadInstr :: NCGConfig -> RegWithFormat -> Int -> Int -> [Instr] Source #

Make a reload instruction, reload from spill slot to a register.

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.

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

Increment SP to deallocate stack space.

data Instr Source #

Constructors

COMMENT SDoc 
MULTILINE_COMMENT SDoc 
ANN SDoc Instr 
LOCATION Int Int Int LexicalFastString 
NEWBLOCK BlockId 
DELTA Int 
LDATA Section RawCmmStatics

Static data spat out during code generation.

PUSH_STACK_FRAME 
POP_STACK_FRAME 
ADD Operand Operand Operand 
SUB Operand Operand Operand 
ALSL Operand Operand Operand Operand 
ALSLU Operand Operand Operand Operand 
LU12I Operand Operand 
LU32I Operand Operand 
LU52I Operand Operand Operand 
SSLT Operand Operand Operand 
SSLTU Operand Operand Operand 
PCADDI Operand Operand 
PCADDU12I Operand Operand 
PCADDU18I Operand Operand 
PCALAU12I Operand Operand 
AND Operand Operand Operand 
OR Operand Operand Operand 
XOR Operand Operand Operand 
NOR Operand Operand Operand 
ANDN Operand Operand Operand 
ORN Operand Operand Operand 
MUL Operand Operand Operand 
MULW Operand Operand Operand 
MULWU Operand Operand Operand 
MULH Operand Operand Operand 
MULHU Operand Operand Operand 
DIV Operand Operand Operand 
DIVU Operand Operand Operand 
MOD Operand Operand Operand 
MODU Operand Operand Operand 
SLL Operand Operand Operand 
SRL Operand Operand Operand 
SRA Operand Operand Operand 
ROTR Operand Operand Operand 
EXT Operand Operand 
CLO Operand Operand 
CTO Operand Operand 
CLZ Operand Operand 
CTZ Operand Operand 
BYTEPICK Operand Operand Operand Operand 
REVB2H Operand Operand 
REVB4H Operand Operand 
REVB2W Operand Operand 
REVBD Operand Operand 
REVH2W Operand Operand 
REVHD Operand Operand 
BITREV4B Operand Operand 
BITREV8B Operand Operand 
BITREVW Operand Operand 
BITREVD Operand Operand 
BSTRINS Format Operand Operand Operand Operand 
BSTRPICK Format Operand Operand Operand Operand 
MASKEQZ Operand Operand Operand 
MASKNEZ Operand Operand Operand 
NOP 
MOV Operand Operand 
NEG Operand Operand 
CSET Cond Operand Operand Operand 
J Target 
J_TBL [Maybe BlockId] (Maybe CLabel) Reg 
B Target 
BL Target [Reg] 
CALL36 Target 
TAIL36 Operand Target 
BCOND Cond Operand Operand Target Operand 
BEQZ Operand Target 
BNEZ Operand Target 
LD Format Operand Operand 
LDU Format Operand Operand 
ST Format Operand Operand 
LDX Format Operand Operand 
LDXU Format Operand Operand 
STX Format Operand Operand 
LDPTR Format Operand Operand 
STPTR Format Operand Operand 
DBAR BarrierType 
IBAR BarrierType 
FCVT Operand Operand 
SCVTF Operand Operand 
FCVTZS Operand Operand Operand 
FMAX Operand Operand Operand 
FMIN Operand Operand Operand 
FMAXA Operand Operand Operand 
FMINA Operand Operand Operand 
FNEG Operand Operand 
FABS Operand Operand 
FMA FMASign Operand Operand Operand Operand 

data BarrierType Source #

Constructors

Hint0 

data Operand Source #

Instances

Instances details
Eq Operand Source # 
Instance details

Defined in GHC.CmmToAsm.LA64.Instr

Methods

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

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

Show Operand Source # 
Instance details

Defined in GHC.CmmToAsm.LA64.Instr

Orphan instances

Outputable RegUsage Source # 
Instance details

Methods

ppr :: RegUsage -> SDoc Source #