ghc-9.12: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Cmm.MachOp

Synopsis

Documentation

data MachOp Source #

Machine-level primops; ones which we can reasonably delegate to the native code generators to handle.

Most operations are parameterised by the Width that they operate on. Some operations have separate signed and unsigned versions, and float and integer versions.

Note that there are variety of places in the native code generator where we assume that the code produced for a MachOp does not introduce new blocks.

Constructors

MO_Add Width 
MO_Sub Width 
MO_Eq Width 
MO_Ne Width 
MO_Mul Width 
MO_S_MulMayOflo Width 
MO_S_Quot Width 
MO_S_Rem Width 
MO_S_Neg Width 
MO_U_Quot Width 
MO_U_Rem Width 
MO_S_Ge Width 
MO_S_Le Width 
MO_S_Gt Width 
MO_S_Lt Width 
MO_U_Ge Width 
MO_U_Le Width 
MO_U_Gt Width 
MO_U_Lt Width 
MO_F_Add Width 
MO_F_Sub Width 
MO_F_Neg Width 
MO_F_Mul Width 
MO_F_Quot Width 
MO_FMA FMASign Length Width

Fused multiply-add, see FMASign.

MO_F_Eq Width 
MO_F_Ne Width 
MO_F_Ge Width 
MO_F_Le Width 
MO_F_Gt Width 
MO_F_Lt Width 
MO_F_Min Width 
MO_F_Max Width 
MO_And Width 
MO_Or Width 
MO_Xor Width 
MO_Not Width 
MO_Shl Width 
MO_U_Shr Width 
MO_S_Shr Width 
MO_SF_Round Width Width 
MO_FS_Truncate Width Width 
MO_SS_Conv Width Width 
MO_UU_Conv Width Width 
MO_XX_Conv Width Width 
MO_FF_Conv Width Width 
MO_WF_Bitcast Width 
MO_FW_Bitcast Width 
MO_V_Broadcast Length Width 
MO_V_Insert Length Width 
MO_V_Extract Length Width 
MO_V_Add Length Width 
MO_V_Sub Length Width 
MO_V_Mul Length Width 
MO_VS_Quot Length Width 
MO_VS_Rem Length Width 
MO_VS_Neg Length Width 
MO_VU_Quot Length Width 
MO_VU_Rem Length Width 
MO_V_Shuffle Length Width [Int] 
MO_VF_Shuffle Length Width [Int] 
MO_VF_Broadcast Length Width 
MO_VF_Insert Length Width 
MO_VF_Extract Length Width 
MO_VF_Add Length Width 
MO_VF_Sub Length Width 
MO_VF_Neg Length Width 
MO_VF_Mul Length Width 
MO_VF_Quot Length Width 
MO_VS_Min Length Width 
MO_VS_Max Length Width 
MO_VU_Min Length Width 
MO_VU_Max Length Width 
MO_VF_Min Length Width 
MO_VF_Max Length Width 
MO_RelaxedRead Width

An atomic read with no memory ordering. Address msut be naturally aligned.

MO_AlignmentCheck Int Width 

Instances

Instances details
Show MachOp Source # 
Instance details

Defined in GHC.Cmm.MachOp

Eq MachOp Source # 
Instance details

Defined in GHC.Cmm.MachOp

Methods

(==) :: MachOp -> MachOp -> Bool #

(/=) :: MachOp -> MachOp -> Bool #

isCommutableMachOp :: MachOp -> Bool Source #

Returns True if the MachOp has commutable arguments. This is used in the platform-independent Cmm optimisations.

If in doubt, return False. This generates worse code on the native routes, but is otherwise harmless.

isAssociativeMachOp :: MachOp -> Bool Source #

Returns True if the MachOp is associative (i.e. (x+y)+z == x+(y+z)) This is used in the platform-independent Cmm optimisations.

If in doubt, return False. This generates worse code on the native routes, but is otherwise harmless.

isComparisonMachOp :: MachOp -> Bool Source #

Returns True if the MachOp is a comparison.

If in doubt, return False. This generates worse code on the native routes, but is otherwise harmless.

maybeIntComparison :: MachOp -> Maybe Width Source #

Returns Just w if the operation is an integer comparison with width w, or Nothing otherwise.

machOpResultType :: Platform -> MachOp -> [CmmType] -> CmmType Source #

Returns the MachRep of the result of a MachOp.

machOpArgReps :: Platform -> MachOp -> [Width] Source #

This function is used for debugging only: we can check whether an application of a MachOp is "type-correct" by checking that the MachReps of its arguments are the same as the MachOp expects. This is used when linting a CmmExpr.

data CallishMachOp Source #

Constructors

MO_F64_Pwr 
MO_F64_Sin 
MO_F64_Cos 
MO_F64_Tan 
MO_F64_Sinh 
MO_F64_Cosh 
MO_F64_Tanh 
MO_F64_Asin 
MO_F64_Acos 
MO_F64_Atan 
MO_F64_Asinh 
MO_F64_Acosh 
MO_F64_Atanh 
MO_F64_Log 
MO_F64_Log1P 
MO_F64_Exp 
MO_F64_ExpM1 
MO_F64_Fabs 
MO_F64_Sqrt 
MO_F32_Pwr 
MO_F32_Sin 
MO_F32_Cos 
MO_F32_Tan 
MO_F32_Sinh 
MO_F32_Cosh 
MO_F32_Tanh 
MO_F32_Asin 
MO_F32_Acos 
MO_F32_Atan 
MO_F32_Asinh 
MO_F32_Acosh 
MO_F32_Atanh 
MO_F32_Log 
MO_F32_Log1P 
MO_F32_Exp 
MO_F32_ExpM1 
MO_F32_Fabs 
MO_F32_Sqrt 
MO_I64_ToI 
MO_I64_FromI 
MO_W64_ToW 
MO_W64_FromW 
MO_x64_Neg 
MO_x64_Add 
MO_x64_Sub 
MO_x64_Mul 
MO_I64_Quot 
MO_I64_Rem 
MO_W64_Quot 
MO_W64_Rem 
MO_x64_And 
MO_x64_Or 
MO_x64_Xor 
MO_x64_Not 
MO_x64_Shl 
MO_I64_Shr 
MO_W64_Shr 
MO_x64_Eq 
MO_x64_Ne 
MO_I64_Ge 
MO_I64_Gt 
MO_I64_Le 
MO_I64_Lt 
MO_W64_Ge 
MO_W64_Gt 
MO_W64_Le 
MO_W64_Lt 
MO_UF_Conv Width 
MO_S_Mul2 Width 
MO_S_QuotRem Width 
MO_U_QuotRem Width 
MO_U_QuotRem2 Width 
MO_Add2 Width 
MO_AddWordC Width 
MO_SubWordC Width 
MO_AddIntC Width 
MO_SubIntC Width 
MO_U_Mul2 Width 
MO_Touch 
MO_Prefetch_Data Int 
MO_Memcpy Int 
MO_Memset Int 
MO_Memmove Int 
MO_Memcmp Int 
MO_PopCnt Width 
MO_Pdep Width 
MO_Pext Width 
MO_Clz Width 
MO_Ctz Width 
MO_BSwap Width 
MO_BRev Width 
MO_AcquireFence 
MO_ReleaseFence 
MO_SeqCstFence 
MO_AtomicRMW Width AtomicMachOp

Atomic read-modify-write. Arguments are [dest, n].

MO_AtomicRead Width MemoryOrdering

Atomic read. Arguments are [addr].

MO_AtomicWrite Width MemoryOrdering

Atomic write. Arguments are [addr, value].

MO_Cmpxchg Width

Atomic compare-and-swap. Arguments are [dest, expected, new]. Sequentially consistent. Possible future refactoring: should this be anMO_AtomicRMW variant?

MO_Xchg Width

Atomic swap. Arguments are [dest, new]

MO_SuspendThread 
MO_ResumeThread 

Instances

Instances details
Show CallishMachOp Source # 
Instance details

Defined in GHC.Cmm.MachOp

Eq CallishMachOp Source # 
Instance details

Defined in GHC.Cmm.MachOp

callishMachOpHints :: CallishMachOp -> ([ForeignHint], [ForeignHint]) Source #

Return (results_hints,args_hints)

machOpMemcpyishAlign :: CallishMachOp -> Maybe Int Source #

The alignment of a memcpy-ish operation.

data AtomicMachOp Source #

The operation to perform atomically.

Instances

Instances details
Show AtomicMachOp Source # 
Instance details

Defined in GHC.Cmm.MachOp

Eq AtomicMachOp Source # 
Instance details

Defined in GHC.Cmm.MachOp

data FMASign Source #

Where are the signs in a fused multiply-add instruction?

x*y + z vs x*y - z vs -x*y+z vs -x*y-z.

Warning: the signs aren't consistent across architectures (X86, PowerPC, AArch64). The user-facing implementation uses the X86 convention, while the relevant backends use their corresponding conventions.

Constructors

FMAdd

Fused multiply-add x*y + z.

FMSub

Fused multiply-subtract. On X86: x*y - z.

FNMAdd

Fused multiply-add. On X86: -x*y + z.

FNMSub

Fused multiply-subtract. On X86: -x*y - z.

Instances

Instances details
Show FMASign Source # 
Instance details

Defined in GHC.Cmm.MachOp

Eq FMASign Source # 
Instance details

Defined in GHC.Cmm.MachOp

Methods

(==) :: FMASign -> FMASign -> Bool #

(/=) :: FMASign -> FMASign -> Bool #

pprFMASign :: IsLine doc => FMASign -> doc Source #