Safe Haskell | None |
---|---|
Language | GHC2021 |
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
- canFallthroughTo :: Instr -> BlockId -> 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
- mkRegRegMoveInstr :: Reg -> Reg -> Instr
- takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg)
- mkJumpInstr :: BlockId -> [Instr]
- mkStackAllocInstr :: Platform -> Int -> [Instr]
- mkStackDeallocInstr :: Platform -> Int -> [Instr]
- moveSp :: 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
- | LDATA Section RawCmmStatics
- | NEWBLOCK BlockId
- | DELTA Int
- | PUSH_STACK_FRAME
- | POP_STACK_FRAME
- | ADD Operand Operand Operand
- | SUB Operand Operand Operand
- | AND Operand Operand Operand
- | OR Operand Operand Operand
- | SLL Operand Operand Operand
- | SRL Operand Operand Operand
- | SRA Operand Operand Operand
- | STR Format Operand Operand
- | LDR Format Operand Operand
- | LDRU Format Operand Operand
- | MUL Operand Operand Operand
- | NEG Operand Operand
- | DIV Operand Operand Operand
- | REM Operand Operand Operand
- | REMU Operand Operand Operand
- | MULH Operand Operand Operand
- | DIVU Operand Operand Operand
- | XOR Operand Operand Operand
- | ORI Operand Operand Operand
- | XORI Operand Operand Operand
- | MOV Operand Operand
- | CSET Operand Operand Operand Cond
- | J_TBL [Maybe BlockId] (Maybe CLabel) Reg
- | B Target
- | BL Reg [Reg]
- | BCOND Cond Operand Operand Target
- | FENCE FenceType FenceType
- | FCVT FcvtVariant Operand Operand
- | FABS Operand Operand
- | FMIN Operand Operand Operand
- | FMAX Operand Operand Operand
- | FMA FMASign Operand Operand Operand Operand
- data FenceType
- data FcvtVariant
- instrCon :: Instr -> String
- data Target
- data Operand
- operandFromReg :: Reg -> Operand
- operandFromRegNo :: RegNo -> Operand
- zero :: Operand
- ra :: Operand
- sp :: Operand
- gp :: 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
- fitsIn12bitImm :: (Num a, Ord a) => a -> Bool
- intMin12bit :: Num a => a
- intMax12bit :: Num a => a
- fitsIn32bits :: (Num a, Ord a, Bits a) => a -> Bool
- isNbitEncodeable :: Int -> Integer -> Bool
- isEncodeableInWidth :: Width -> Integer -> Bool
- isIntOp :: Operand -> Bool
- isFloatOp :: Operand -> Bool
- isFloatReg :: Reg -> Bool
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.
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.
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.
:: HasCallStack | |
=> NCGConfig | |
-> RegWithFormat | register to spill |
-> Int | current stack delta |
-> Int | spill slot to use |
-> [Instr] |
Generate instructions to spill a register into a spill slot.
:: NCGConfig | |
-> RegWithFormat | 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.
allocMoreStack :: Platform -> Int -> NatCmmDecl statics Instr -> UniqDSM (NatCmmDecl statics Instr, [(BlockId, BlockId)]) Source #
COMMENT SDoc | Comment pseudo-op |
MULTILINE_COMMENT SDoc | Multi-line comment pseudo-op |
ANN SDoc Instr | |
LOCATION Int Int Int LexicalFastString | Location pseudo-op |
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 |
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: |
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)
|
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 |
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 |
FMIN Operand Operand Operand | Min dest = min(r1) |
FMAX Operand Operand Operand | Max |
FMA FMASign Operand Operand Operand Operand | Floating-point fused multiply-add instructions
|
Instances
Operand of a FENCE instruction (r
, w
or rw
)
data FcvtVariant Source #
Variant of a floating point conversion instruction
operandFromReg :: Reg -> Operand Source #
operandFromRegNo :: RegNo -> Operand Source #
intMin12bit :: Num a => a Source #
intMax12bit :: Num a => a Source #
isFloatReg :: Reg -> Bool Source #