- archWordSize :: Size
- data Instr
- = COMMENT FastString
- | LDATA Section [CmmStatic]
- | NEWBLOCK BlockId
- | DELTA Int
- | MOV Size Operand Operand
- | MOVZxL Size Operand Operand
- | MOVSxL Size Operand Operand
- | LEA Size Operand Operand
- | ADD Size Operand Operand
- | ADC Size Operand Operand
- | SUB Size Operand Operand
- | MUL Size Operand Operand
- | IMUL Size Operand Operand
- | IMUL2 Size Operand
- | DIV Size Operand
- | IDIV Size Operand
- | AND Size Operand Operand
- | OR Size Operand Operand
- | XOR Size Operand Operand
- | NOT Size Operand
- | NEGI Size Operand
- | SHL Size Operand Operand
- | SAR Size Operand Operand
- | SHR Size Operand Operand
- | BT Size Imm Operand
- | NOP
- | GMOV Reg Reg
- | GLD Size AddrMode Reg
- | GST Size Reg AddrMode
- | GLDZ Reg
- | GLD1 Reg
- | GFTOI Reg Reg
- | GDTOI Reg Reg
- | GITOF Reg Reg
- | GITOD Reg Reg
- | GADD Size Reg Reg Reg
- | GDIV Size Reg Reg Reg
- | GSUB Size Reg Reg Reg
- | GMUL Size Reg Reg Reg
- | GCMP Cond Reg Reg
- | GABS Size Reg Reg
- | GNEG Size Reg Reg
- | GSQRT Size Reg Reg
- | GSIN Size CLabel CLabel Reg Reg
- | GCOS Size CLabel CLabel Reg Reg
- | GTAN Size CLabel CLabel Reg Reg
- | GFREE
- | CVTSS2SD Reg Reg
- | CVTSD2SS Reg Reg
- | CVTTSS2SIQ Size Operand Reg
- | CVTTSD2SIQ Size Operand Reg
- | CVTSI2SS Size Operand Reg
- | CVTSI2SD Size Operand Reg
- | FDIV Size Operand Operand
- | SQRT Size Operand Reg
- | TEST Size Operand Operand
- | CMP Size Operand Operand
- | SETCC Cond Operand
- | PUSH Size Operand
- | POP Size Operand
- | JMP Operand
- | JXX Cond BlockId
- | JXX_GBL Cond Imm
- | JMP_TBL Operand [BlockId]
- | CALL (Either Imm Reg) [Reg]
- | CLTD Size
- | FETCHGOT Reg
- | FETCHPC Reg
- data Operand
- x86_regUsageOfInstr :: Instr -> RegUsage
- interesting :: Reg -> Bool
- x86_patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr
- x86_isJumpishInstr :: Instr -> Bool
- x86_jumpDestsOfInstr :: Instr -> [BlockId]
- x86_patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr
- x86_mkSpillInstr :: Reg -> Int -> Int -> Instr
- x86_mkLoadInstr :: Reg -> Int -> Int -> Instr
- spillSlotSize :: Int
- maxSpillSlots :: Int
- spillSlotToOffset :: Int -> Int
- x86_takeDeltaInstr :: Instr -> Maybe Int
- x86_isMetaInstr :: Instr -> Bool
- x86_mkRegRegMoveInstr :: Reg -> Reg -> Instr
- x86_takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg)
- x86_mkJumpInstr :: BlockId -> [Instr]
- i386_insert_ffrees :: [GenBasicBlock Instr] -> [GenBasicBlock Instr]
- is_G_instr :: Instr -> Bool
- data JumpDest
- = DestBlockId BlockId
- | DestImm Imm
- canShortcut :: Instr -> Maybe JumpDest
- shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr
- shortcutStatic :: (BlockId -> Maybe JumpDest) -> CmmStatic -> CmmStatic
- shortBlockId :: (BlockId -> Maybe JumpDest) -> UniqSet Unique -> BlockId -> CLabel
Documentation
Outputable Instr | |
Instruction Instr | Instruction instance for x86 instruction set. |
interesting :: Reg -> BoolSource
x86_jumpDestsOfInstr :: Instr -> [BlockId]Source
spillSlotToOffset :: Int -> IntSource
x86_takeDeltaInstr :: Instr -> Maybe IntSource
See if this instruction is telling us the current C stack delta
x86_isMetaInstr :: Instr -> BoolSource
x86_mkRegRegMoveInstr :: Reg -> Reg -> InstrSource
Make a reg-reg move instruction. On SPARC v8 there are no instructions to move directly between floating point and integer regs. If we need to do that then we have to go via memory.
x86_takeRegRegMoveInstr :: 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.
x86_mkJumpInstr :: BlockId -> [Instr]Source
Make an unconditional branch instruction.
is_G_instr :: Instr -> BoolSource
canShortcut :: Instr -> Maybe JumpDestSource