Safe Haskell | None |
---|---|
Language | GHC2021 |
GHC.CmmToAsm.LA64.Instr
Contents
Synopsis
- stackFrameHeaderSize :: Int
- spillSlotSize :: Int
- stackAlign :: Int
- maxSpillSlots :: NCGConfig -> Int
- spillSlotToOffset :: Int -> Int
- regUsageOfInstr :: Platform -> Instr -> RegUsage
- callerSavedRegisters :: [Reg]
- patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr
- isJumpishInstr :: Instr -> Bool
- jumpDestsOfInstr :: Instr -> [BlockId]
- patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr
- mkSpillInstr :: HasCallStack => NCGConfig -> RegWithFormat -> Int -> Int -> [Instr]
- mkLoadInstr :: NCGConfig -> RegWithFormat -> Int -> Int -> [Instr]
- takeDeltaInstr :: Instr -> Maybe Int
- isMetaInstr :: Instr -> Bool
- canFallthroughTo :: Instr -> BlockId -> Bool
- mkRegRegMoveInstr :: Reg -> Reg -> Instr
- takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg)
- mkJumpInstr :: BlockId -> [Instr]
- mkStackAllocInstr :: Platform -> Int -> [Instr]
- mkStackDeallocInstr :: Platform -> Int -> [Instr]
- allocMoreStack :: Platform -> Int -> NatCmmDecl statics Instr -> UniqDSM (NatCmmDecl statics Instr, [(BlockId, BlockId)])
- data Instr
- = COMMENT SDoc
- | MULTILINE_COMMENT SDoc
- | ANN SDoc Instr
- | LOCATION Int Int Int LexicalFastString
- | NEWBLOCK BlockId
- | DELTA Int
- | LDATA Section RawCmmStatics
- | 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 = Hint0
- instrCon :: Instr -> String
- data Target
- data Operand
- opReg :: Reg -> Operand
- opRegNo :: RegNo -> Operand
- zero :: Operand
- ra :: Operand
- sp :: Operand
- tp :: Operand
- fp :: Operand
- tmp :: Operand
- x0 :: Operand
- x1 :: Operand
- x2 :: Operand
- x3 :: Operand
- x4 :: Operand
- x5 :: Operand
- x6 :: Operand
- x7 :: Operand
- x8 :: Operand
- x9 :: Operand
- x10 :: Operand
- x11 :: Operand
- x12 :: Operand
- x13 :: Operand
- x14 :: Operand
- x15 :: Operand
- x16 :: Operand
- x17 :: Operand
- x18 :: Operand
- x19 :: Operand
- x20 :: Operand
- x21 :: Operand
- x22 :: Operand
- x23 :: Operand
- x24 :: Operand
- x25 :: Operand
- x26 :: Operand
- x27 :: Operand
- x28 :: Operand
- x29 :: Operand
- x30 :: Operand
- x31 :: Operand
- d0 :: Operand
- d1 :: Operand
- d2 :: Operand
- d3 :: Operand
- d4 :: Operand
- d5 :: Operand
- d6 :: Operand
- d7 :: Operand
- d8 :: Operand
- d9 :: Operand
- d10 :: Operand
- d11 :: Operand
- d12 :: Operand
- d13 :: Operand
- d14 :: Operand
- d15 :: Operand
- d16 :: Operand
- d17 :: Operand
- d18 :: Operand
- d19 :: Operand
- d20 :: Operand
- d21 :: Operand
- d22 :: Operand
- d23 :: Operand
- d24 :: Operand
- d25 :: Operand
- d26 :: Operand
- d27 :: Operand
- d28 :: Operand
- d29 :: Operand
- d30 :: Operand
- d31 :: Operand
- fitsInNbits :: Int -> Int -> Bool
- isUnsignOp :: Int -> Bool
- isNbitEncodeable :: Int -> Integer -> Bool
- isEncodeableInWidth :: Width -> Integer -> Bool
- isIntOp :: Operand -> Bool
- isFloatOp :: Operand -> Bool
- isFloatReg :: Reg -> Bool
- widthToInt :: Width -> Int
- widthFromOpReg :: Operand -> Width
- lessW64 :: Width -> Bool
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.
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.
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.
allocMoreStack :: Platform -> Int -> NatCmmDecl statics Instr -> UniqDSM (NatCmmDecl statics Instr, [(BlockId, BlockId)]) Source #
Constructors
Instances
data BarrierType Source #
Constructors
Hint0 |
Instances
isUnsignOp :: Int -> Bool Source #
isFloatReg :: Reg -> Bool Source #
widthToInt :: Width -> Int Source #
widthFromOpReg :: Operand -> Width Source #