Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- stackFrameHeaderSize :: Platform -> Int
- spillSlotSize :: Int
- stackAlign :: Int
- maxSpillSlots :: NCGConfig -> Int
- spillSlotToOffset :: NCGConfig -> 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 -> Reg -> Int -> Int -> [Instr]
- mkLoadInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr]
- takeDeltaInstr :: Instr -> Maybe Int
- isMetaInstr :: Instr -> 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 -> UniqSM (NatCmmDecl statics Instr, [(BlockId, BlockId)])
- data Instr
- = 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
- | POP_STACK_FRAME
- | ADD Operand Operand Operand
- | CMN Operand Operand
- | CMP Operand Operand
- | MSUB Operand Operand Operand Operand
- | MUL Operand Operand Operand
- | NEG Operand Operand
- | SDIV Operand Operand Operand
- | SMULH Operand Operand Operand
- | SMULL Operand Operand Operand
- | SUB Operand Operand Operand
- | UDIV Operand Operand Operand
- | SBFM Operand Operand Operand Operand
- | 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
- | 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 Target
- data ExtMode
- data ShiftMode
- type ExtShift = Int
- type RegShift = Int
- data Operand
- opReg :: Width -> Reg -> Operand
- xzr :: Operand
- wzr :: Operand
- sp :: Operand
- ip0 :: Operand
- _x :: Int -> 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
- _d :: Int -> 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
- opRegUExt :: Width -> Reg -> Operand
- opRegSExt :: Width -> Reg -> Operand
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
isMetaInstr :: Instr -> Bool Source #
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.
allocMoreStack :: Platform -> Int -> NatCmmDecl statics Instr -> UniqSM (NatCmmDecl statics Instr, [(BlockId, BlockId)]) Source #
Instances
Show Instr Source # | |
Instruction Instr Source # | Instruction instance for aarch64 |
Defined in GHC.CmmToAsm.AArch64 regUsageOfInstr :: Platform -> Instr -> RegUsage Source # patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr Source # isJumpishInstr :: Instr -> Bool Source # jumpDestsOfInstr :: Instr -> [BlockId] Source # patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr Source # mkSpillInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr] Source # mkLoadInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr] Source # takeDeltaInstr :: Instr -> Maybe Int Source # isMetaInstr :: Instr -> Bool Source # mkRegRegMoveInstr :: Platform -> Reg -> Reg -> Instr Source # takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg) Source # mkJumpInstr :: BlockId -> [Instr] Source # mkStackAllocInstr :: Platform -> Int -> [Instr] Source # mkStackDeallocInstr :: Platform -> Int -> [Instr] Source # | |
Outputable Instr Source # | |
OpReg Width Reg | |
OpRegExt Width Reg ExtMode ExtShift | |
OpRegShift Width Reg ShiftMode RegShift | |
OpImm Imm | |
OpImmShift Imm ShiftMode RegShift | |
OpAddr AddrMode |
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. |