ghc-9.2.5: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.CmmToAsm.AArch64.Instr

Synopsis

Documentation

stackFrameHeaderSize :: Platform -> Int Source #

TODO: verify this!

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 :: NCGConfig -> Int -> Int Source #

Convert a spill slot number to a *byte* offset, with no sign.

callerSavedRegisters :: [Reg] Source #

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 | | 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 | |== General Purpose registers ==================================================================================================================================| | argument passing ------------- | IR | tmp registers -------- | IP0| IP1| PL | callee saved ------------ | FP | LR | SP | | free registers -------------------------------------------------------------------- | BR | Sp | Hp | R1 | R2 | R3 | R4 | R5 | R6 | SL | -- | -- | -- | |== SIMD/FP Registers ==========================================================================================================================================| | argument passing ------------- | callee saved (lower 64 bits) --- | caller saved ---------------------- | | free registers ------------- | F1 | F2 | F3 | F4 | D1 | D2 | D3 | D4 | free registers ----------------------------------------------------- | '---------------------------------------------------------------------------------------------------------------------------------------------------------------' IR: Indirect result location register, IP: Intra-procedure register, PL: Platform register, FP: Frame pointer, LR: Link register, SP: Stack pointer BR: Base, SL: SpLim

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 #

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.

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

Change the destination of this jump instruction. Used in the linear allocator when adding fixup blocks for join points.

mkSpillInstr :: HasCallStack => NCGConfig -> Reg -> Int -> Int -> [Instr] Source #

An instruction to spill a register into a spill slot.

takeDeltaInstr :: Instr -> Maybe Int Source #

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

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 reg -> reg move instruction or Nothing if it's not one

mkJumpInstr :: BlockId -> [Instr] Source #

Make an unconditional jump instruction.

data Instr Source #

Constructors

COMMENT SDoc 
MULTILINE_COMMENT SDoc 
ANN SDoc Instr 
LOCATION Int Int Int String 
LDATA Section RawCmmStatics 
NEWBLOCK BlockId 
DELTA Int 
SXTB Operand Operand 
UXTB Operand Operand 
SXTH Operand Operand 
UXTH Operand Operand 
PUSH_STACK_FRAME

SXTW Operand Operand | SXTX Operand Operand

POP_STACK_FRAME 
ADD Operand Operand Operand

ADC Operand Operand Operang -- rd = rn + rm + C | ADCS ...

CMN Operand Operand

ADDS Operand Operand Operand -- rd = rn + rm | ADR ... | ADRP ...

CMP Operand Operand 
MSUB Operand Operand Operand Operand

MADD ... | MNEG ...

MUL Operand Operand Operand 
NEG Operand Operand 
SDIV Operand Operand Operand

NEGS ... | NGC ... | NGCS ... | SBC ... | SBCS ...

SMULH Operand Operand Operand

SMADDL ... | SMNEGL ... | SMSUBL ...

SMULL Operand Operand Operand 
SUB Operand Operand Operand 
UDIV Operand Operand Operand

SUBS ...

SBFM Operand Operand Operand Operand

UMADDL ... -- Xd = Xa + Wn × Wm | UMNEGL ... -- Xd = - Wn × Wm | UMSUBL ... -- Xd = Xa - Wn × Wm | UMULH ... -- Xd = (Xn × Xm)_127:64 | UMULL ... -- Xd = Wn × Wm

UBFM Operand Operand Operand Operand 
SBFX Operand Operand Operand Operand 
UBFX Operand Operand Operand Operand 
AND Operand Operand Operand 
ANDS Operand Operand Operand 
ASR Operand Operand Operand 
BIC Operand Operand Operand 
BICS Operand Operand Operand 
EON Operand Operand Operand 
EOR Operand Operand Operand 
LSL Operand Operand Operand 
LSR Operand Operand Operand 
MOV Operand Operand 
MOVK Operand Operand 
MVN Operand Operand

MOVN Operand Operand | MOVZ Operand Operand

ORN Operand Operand Operand 
ORR Operand Operand Operand 
ROR Operand Operand Operand 
TST Operand Operand 
STR Format Operand Operand 
LDR Format Operand Operand 
STP Format Operand Operand Operand 
LDP Format Operand Operand Operand 
CSET Operand Cond 
CBZ Operand Target 
CBNZ Operand Target 
J Target 
B Target 
BL Target [Reg] [Reg] 
BCOND Cond Target 
DMBSY 
FCVT Operand Operand 
SCVTF Operand Operand 
FCVTZS Operand Operand 
FABS Operand Operand 

data ExtMode Source #

Constructors

EUXTB 
EUXTH 
EUXTW 
EUXTX 
ESXTB 
ESXTH 
ESXTW 
ESXTX 

Instances

Instances details
Show ExtMode Source # 
Instance details

Defined in GHC.CmmToAsm.AArch64.Instr

Eq ExtMode Source # 
Instance details

Defined in GHC.CmmToAsm.AArch64.Instr

Methods

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

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

data ShiftMode Source #

Constructors

SLSL 
SLSR 
SASR 
SROR 

Instances

Instances details
Show ShiftMode Source # 
Instance details

Defined in GHC.CmmToAsm.AArch64.Instr

Eq ShiftMode Source # 
Instance details

Defined in GHC.CmmToAsm.AArch64.Instr

Orphan instances

Outputable 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]

Instance details

Methods

ppr :: RegUsage -> SDoc Source #