ghc-9.12: The GHC API
Safe HaskellNone
LanguageGHC2021

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

X86 scalar move instruction.

When used at a vector format, only moves the lower 64 bits of data; the rest of the data in the destination may either be zeroed or preserved, depending on the specific format and operands.

MOVD Format Operand Operand

MOVD/MOVQ SSE2 instructions (bitcast between a general purpose register and a float register). Format is input format, output format is calculated in the movdOutFormat function.

CMOV Cond Format Operand Reg 
MOVZxL Format Operand Operand

The format argument is the size of operand 1 (the number of bits we keep) We always zero *all* high bits, even though this isn't how the actual instruction works. The code generator also seems to rely on this behaviour and it's faster to execute on many cpus as well so for now I'm just documenting the fact.

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

AVX bitwise logical XOR operation

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

FMA3 fused multiply-add operations.

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

X86 call instruction

Fields

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

SSE2 unaligned move of floating-point vectors

VMOVU Format Operand Operand

AVX unaligned move of floating-point vectors

MOVL Format Operand Operand

SSE2 move between memory and low-part of an xmm register

MOVH Format Operand Operand

SSE move between memory and high-part of an xmm register

MOVDQU Format Operand Operand

SSE2 unaligned move of integer vectors

VMOVDQU Format Operand Operand

AVX unaligned move of integer vectors

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

Move two 32-bit floats from the high part of an xmm register to the low part of another xmm register.

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 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 :: 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.

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.

data MinOrMax Source #

MIN or MAX

Constructors

Min 
Max 

Instances

Instances details
Show MinOrMax Source # 
Instance details

Defined in GHC.CmmToAsm.X86.Instr

Eq MinOrMax Source # 
Instance details

Defined in GHC.CmmToAsm.X86.Instr

data MinMaxType Source #

What kind of minmax operation: signed or unsigned vector integer minmax, or (scalar or vector) floating point min/max?

Constructors

IntVecMinMax 

Fields

FloatMinMax 

Instances

Instances details
Show MinMaxType Source # 
Instance details

Defined in GHC.CmmToAsm.X86.Instr

Eq MinMaxType Source # 
Instance details

Defined in GHC.CmmToAsm.X86.Instr