ghc-9.2.5: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.CmmToAsm.X86.Instr

Synopsis

Documentation

data Instr Source #

Constructors

COMMENT FastString 
LOCATION Int Int Int String 
LDATA Section (Alignment, RawCmmStatics) 
NEWBLOCK BlockId 
UNWIND CLabel UnwindTable 
DELTA Int 
MOV 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 
NOT Format Operand 
NEGI Format Operand 
BSWAP Format Reg 
SHL Format Operand Operand 
SAR Format Operand Operand 
SHR Format 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 
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 [Reg] 
JXX Cond BlockId 
JXX_GBL Cond Imm 
JMP_TBL Operand [Maybe JumpDest] Section CLabel 
CALL

X86 call instruction

Fields

  • (Either Imm Reg)

    Jump target

  • [Reg]

    Arguments (required for register allocation)

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 

data PrefetchVariant Source #

Constructors

NTA 
Lvl0 
Lvl1 
Lvl2 

data JumpDest Source #

Instances

Instances details
Outputable JumpDest Source # 
Instance details

Defined in GHC.CmmToAsm.X86.Instr

Methods

ppr :: JumpDest -> SDoc Source #

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.

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 :: NCGConfig -> Reg -> Int -> Int -> [Instr] Source #

Make a spill reload instruction.

mkJumpInstr :: BlockId -> [Instr] Source #

Make an unconditional branch instruction.

mkSpillInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr] Source #

Make a spill instruction.

mkRegRegMoveInstr :: Platform -> Reg -> Reg -> Instr Source #

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.

patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr Source #

Applies the supplied function to all registers in instructions. Typically used to change virtual registers to real registers.