Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data Instr
- = COMMENT FastString
- | LOCATION Int Int Int String
- | LDATA Section (Alignment, RawCmmStatics)
- | NEWBLOCK BlockId
- | UNWIND CLabel UnwindTable
- | DELTA Int
- | MOV Format Operand Operand
- | MOVD Format Operand Operand
- | CMOV Cond Format Operand Reg
- | MOVZxL Format Operand Operand
- | MOVSxL Format Operand Operand
- | LEA Format Operand Operand
- | ADD Format Operand Operand
- | ADC Format Operand Operand
- | SUB Format Operand Operand
- | SBB Format Operand Operand
- | MUL Format Operand Operand
- | MUL2 Format Operand
- | IMUL Format Operand Operand
- | IMUL2 Format Operand
- | DIV Format Operand
- | IDIV Format Operand
- | ADD_CC Format Operand Operand
- | SUB_CC Format Operand Operand
- | AND Format Operand Operand
- | OR Format Operand Operand
- | XOR Format Operand Operand
- | VXOR Format Operand Reg Reg
- | NOT Format Operand
- | NEGI Format Operand
- | BSWAP Format Reg
- | SHL Format Operand Operand
- | SAR Format Operand Operand
- | SHR Format Operand Operand
- | SHRD Format Operand Operand Operand
- | SHLD Format Operand Operand Operand
- | BT Format Imm Operand
- | NOP
- | X87Store Format AddrMode
- | CVTSS2SD Reg Reg
- | CVTSD2SS Reg Reg
- | CVTTSS2SIQ Format Operand Reg
- | CVTTSD2SIQ Format Operand Reg
- | CVTSI2SS Format Operand Reg
- | CVTSI2SD Format Operand Reg
- | FMA3 Format FMASign FMAPermutation Operand Reg Reg
- | FDIV Format Operand Operand
- | SQRT Format Operand Reg
- | TEST Format Operand Operand
- | CMP Format Operand Operand
- | SETCC Cond Operand
- | PUSH Format Operand
- | POP Format Operand
- | JMP Operand [RegWithFormat]
- | JXX Cond BlockId
- | JXX_GBL Cond Imm
- | JMP_TBL Operand [Maybe JumpDest] Section CLabel
- | CALL (Either Imm Reg) [RegWithFormat]
- | CLTD Format
- | FETCHGOT Reg
- | FETCHPC Reg
- | POPCNT Format Operand Reg
- | LZCNT Format Operand Reg
- | TZCNT Format Operand Reg
- | BSF Format Operand Reg
- | BSR Format Operand Reg
- | PDEP Format Operand Operand Reg
- | PEXT Format Operand Operand Reg
- | PREFETCH PrefetchVariant Format Operand
- | LOCK Instr
- | XADD Format Operand Operand
- | CMPXCHG Format Operand Operand
- | XCHG Format Operand Reg
- | MFENCE
- | VBROADCAST Format Operand Reg
- | VEXTRACT Format Imm Reg Operand
- | INSERTPS Format Imm Operand Reg
- | MOVU Format Operand Operand
- | VMOVU Format Operand Operand
- | MOVL Format Operand Operand
- | MOVH Format Operand Operand
- | MOVDQU Format Operand Operand
- | VMOVDQU Format Operand Operand
- | PXOR Format Operand Reg
- | VPXOR Format Reg Reg Reg
- | VADD Format Operand Reg Reg
- | VSUB Format Operand Reg Reg
- | VMUL Format Operand Reg Reg
- | VDIV Format Operand Reg Reg
- | SHUF Format Imm Operand Reg
- | VSHUF Format Imm Operand Reg Reg
- | PSHUFD Format Imm Operand Reg
- | VPSHUFD Format Imm Operand Reg
- | MOVHLPS Format Reg Reg
- | PUNPCKLQDQ Format Operand Reg
- | PSLLDQ Format Operand Reg
- | PSRLDQ Format Operand Reg
- | MINMAX MinOrMax MinMaxType Format Operand Operand
- | VMINMAX MinOrMax MinMaxType Format Operand Reg Reg
- data Operand
- data PrefetchVariant
- data FMAPermutation
- data JumpDest
- getJumpDestBlockId :: JumpDest -> Maybe BlockId
- canShortcut :: Instr -> Maybe JumpDest
- shortcutStatics :: (BlockId -> Maybe JumpDest) -> (Alignment, RawCmmStatics) -> (Alignment, RawCmmStatics)
- shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
- allocMoreStack :: Platform -> Int -> NatCmmDecl statics Instr -> UniqDSM (NatCmmDecl statics Instr, [(BlockId, BlockId)])
- maxSpillSlots :: NCGConfig -> Int
- archWordFormat :: Bool -> Format
- takeRegRegMoveInstr :: Platform -> Instr -> Maybe (Reg, Reg)
- regUsageOfInstr :: Platform -> Instr -> RegUsage
- takeDeltaInstr :: Instr -> Maybe Int
- mkLoadInstr :: HasDebugCallStack => NCGConfig -> RegWithFormat -> Int -> Int -> [Instr]
- mkJumpInstr :: BlockId -> [Instr]
- mkStackAllocInstr :: Platform -> Int -> [Instr]
- mkStackDeallocInstr :: Platform -> Int -> [Instr]
- mkSpillInstr :: HasDebugCallStack => NCGConfig -> RegWithFormat -> Int -> Int -> [Instr]
- mkRegRegMoveInstr :: HasDebugCallStack => NCGConfig -> Format -> Reg -> Reg -> Instr
- movInstr :: HasDebugCallStack => NCGConfig -> Format -> Operand -> Operand -> Instr
- jumpDestsOfInstr :: Instr -> [BlockId]
- canFallthroughTo :: Instr -> BlockId -> Bool
- patchRegsOfInstr :: HasDebugCallStack => Platform -> Instr -> (Reg -> Reg) -> Instr
- patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr
- isMetaInstr :: Instr -> Bool
- isJumpishInstr :: Instr -> Bool
- movdOutFormat :: Format -> Format
- data MinOrMax
- data MinMaxType
- = IntVecMinMax {
- minMaxSigned :: Bool
- | FloatMinMax
- = IntVecMinMax {
Documentation
Instances
Instances
shortcutStatics :: (BlockId -> Maybe JumpDest) -> (Alignment, RawCmmStatics) -> (Alignment, RawCmmStatics) Source #
allocMoreStack :: Platform -> Int -> NatCmmDecl statics Instr -> UniqDSM (NatCmmDecl statics Instr, [(BlockId, BlockId)]) Source #
maxSpillSlots :: NCGConfig -> Int Source #
archWordFormat :: Bool -> Format Source #
takeRegRegMoveInstr :: Platform -> Instr -> Maybe (Reg, Reg) Source #
Check whether an instruction represents a reg-reg move. The register allocator attempts to eliminate reg->reg moves whenever it can, by assigning the src and dest temporaries to the same real register.
regUsageOfInstr :: Platform -> Instr -> RegUsage Source #
Returns which registers are read and written as a (read, written) pair.
takeDeltaInstr :: Instr -> Maybe Int Source #
See if this instruction is telling us the current C stack delta
mkLoadInstr :: HasDebugCallStack => NCGConfig -> RegWithFormat -> Int -> Int -> [Instr] Source #
Make a spill reload instruction.
mkJumpInstr :: BlockId -> [Instr] Source #
Make an unconditional branch instruction.
mkSpillInstr :: HasDebugCallStack => NCGConfig -> RegWithFormat -> Int -> Int -> [Instr] Source #
Make a spill instruction.
mkRegRegMoveInstr :: HasDebugCallStack => NCGConfig -> Format -> Reg -> Reg -> Instr Source #
Make a reg-reg move instruction.
movInstr :: HasDebugCallStack => NCGConfig -> Format -> Operand -> Operand -> Instr Source #
A move instruction for moving the entire contents of an operand
at the given Format
.
jumpDestsOfInstr :: Instr -> [BlockId] Source #
patchRegsOfInstr :: HasDebugCallStack => Platform -> Instr -> (Reg -> Reg) -> Instr Source #
Applies the supplied function to all registers in instructions. Typically used to change virtual registers to real registers.
isMetaInstr :: Instr -> Bool Source #
isJumpishInstr :: Instr -> Bool Source #
movdOutFormat :: Format -> Format Source #
MIN
or MAX
data MinMaxType Source #
What kind of minmax operation: signed or unsigned vector integer minmax, or (scalar or vector) floating point min/max?
Instances
Show MinMaxType Source # | |
Defined in GHC.CmmToAsm.X86.Instr showsPrec :: Int -> MinMaxType -> ShowS # show :: MinMaxType -> String # showList :: [MinMaxType] -> ShowS # | |
Eq MinMaxType Source # | |
Defined in GHC.CmmToAsm.X86.Instr (==) :: MinMaxType -> MinMaxType -> Bool # (/=) :: MinMaxType -> MinMaxType -> Bool # |