Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data MachOp
- = 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
- | 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
- | MO_AlignmentCheck Int Width
- pprMachOp :: MachOp -> SDoc
- isCommutableMachOp :: MachOp -> Bool
- isAssociativeMachOp :: MachOp -> Bool
- isComparisonMachOp :: MachOp -> Bool
- maybeIntComparison :: MachOp -> Maybe Width
- machOpResultType :: Platform -> MachOp -> [CmmType] -> CmmType
- machOpArgReps :: Platform -> MachOp -> [Width]
- maybeInvertComparison :: MachOp -> Maybe MachOp
- isFloatComparison :: MachOp -> Bool
- isCommutableCallishMachOp :: CallishMachOp -> Bool
- mo_wordAdd :: Platform -> MachOp
- mo_wordSub :: Platform -> MachOp
- mo_wordEq :: Platform -> MachOp
- mo_wordNe :: Platform -> MachOp
- mo_wordMul :: Platform -> MachOp
- mo_wordSQuot :: Platform -> MachOp
- mo_wordSRem :: Platform -> MachOp
- mo_wordSNeg :: Platform -> MachOp
- mo_wordUQuot :: Platform -> MachOp
- mo_wordURem :: Platform -> MachOp
- mo_wordSGe :: Platform -> MachOp
- mo_wordSLe :: Platform -> MachOp
- mo_wordSGt :: Platform -> MachOp
- mo_wordSLt :: Platform -> MachOp
- mo_wordUGe :: Platform -> MachOp
- mo_wordULe :: Platform -> MachOp
- mo_wordUGt :: Platform -> MachOp
- mo_wordULt :: Platform -> MachOp
- mo_wordAnd :: Platform -> MachOp
- mo_wordOr :: Platform -> MachOp
- mo_wordXor :: Platform -> MachOp
- mo_wordNot :: Platform -> MachOp
- mo_wordShl :: Platform -> MachOp
- mo_wordSShr :: Platform -> MachOp
- mo_wordUShr :: Platform -> MachOp
- mo_u_8To32 :: MachOp
- mo_s_8To32 :: MachOp
- mo_u_16To32 :: MachOp
- mo_s_16To32 :: MachOp
- mo_u_8ToWord :: Platform -> MachOp
- mo_s_8ToWord :: Platform -> MachOp
- mo_u_16ToWord :: Platform -> MachOp
- mo_s_16ToWord :: Platform -> MachOp
- mo_u_32ToWord :: Platform -> MachOp
- mo_s_32ToWord :: Platform -> MachOp
- mo_32To8 :: MachOp
- mo_32To16 :: MachOp
- mo_WordTo8 :: Platform -> MachOp
- mo_WordTo16 :: Platform -> MachOp
- mo_WordTo32 :: Platform -> MachOp
- mo_WordTo64 :: Platform -> MachOp
- data CallishMachOp
- = 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
- | MO_AtomicRead Width MemoryOrdering
- | MO_AtomicWrite Width MemoryOrdering
- | MO_Cmpxchg Width
- | MO_Xchg Width
- | MO_SuspendThread
- | MO_ResumeThread
- callishMachOpHints :: CallishMachOp -> ([ForeignHint], [ForeignHint])
- pprCallishMachOp :: CallishMachOp -> SDoc
- machOpMemcpyishAlign :: CallishMachOp -> Maybe Int
- data MemoryOrdering
- data AtomicMachOp
- data FMASign
- pprFMASign :: IsLine doc => FMASign -> doc
Documentation
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.
isCommutableMachOp :: MachOp -> Bool Source #
isAssociativeMachOp :: MachOp -> Bool Source #
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.
isFloatComparison :: MachOp -> Bool Source #
mo_wordAdd :: Platform -> MachOp Source #
mo_wordSub :: Platform -> MachOp Source #
mo_wordMul :: Platform -> MachOp Source #
mo_wordSQuot :: Platform -> MachOp Source #
mo_wordSRem :: Platform -> MachOp Source #
mo_wordSNeg :: Platform -> MachOp Source #
mo_wordUQuot :: Platform -> MachOp Source #
mo_wordURem :: Platform -> MachOp Source #
mo_wordSGe :: Platform -> MachOp Source #
mo_wordSLe :: Platform -> MachOp Source #
mo_wordSGt :: Platform -> MachOp Source #
mo_wordSLt :: Platform -> MachOp Source #
mo_wordUGe :: Platform -> MachOp Source #
mo_wordULe :: Platform -> MachOp Source #
mo_wordUGt :: Platform -> MachOp Source #
mo_wordULt :: Platform -> MachOp Source #
mo_wordAnd :: Platform -> MachOp Source #
mo_wordXor :: Platform -> MachOp Source #
mo_wordNot :: Platform -> MachOp Source #
mo_wordShl :: Platform -> MachOp Source #
mo_wordSShr :: Platform -> MachOp Source #
mo_wordUShr :: Platform -> MachOp Source #
mo_u_8To32 :: MachOp Source #
mo_s_8To32 :: MachOp Source #
mo_u_16To32 :: MachOp Source #
mo_s_16To32 :: MachOp Source #
mo_u_8ToWord :: Platform -> MachOp Source #
mo_s_8ToWord :: Platform -> MachOp Source #
mo_u_16ToWord :: Platform -> MachOp Source #
mo_s_16ToWord :: Platform -> MachOp Source #
mo_u_32ToWord :: Platform -> MachOp Source #
mo_s_32ToWord :: Platform -> MachOp Source #
mo_WordTo8 :: Platform -> MachOp Source #
mo_WordTo16 :: Platform -> MachOp Source #
mo_WordTo32 :: Platform -> MachOp Source #
mo_WordTo64 :: Platform -> MachOp Source #
data CallishMachOp Source #
Instances
Show CallishMachOp Source # | |
Defined in GHC.Cmm.MachOp showsPrec :: Int -> CallishMachOp -> ShowS # show :: CallishMachOp -> String # showList :: [CallishMachOp] -> ShowS # | |
Eq CallishMachOp Source # | |
Defined in GHC.Cmm.MachOp (==) :: CallishMachOp -> CallishMachOp -> Bool # (/=) :: CallishMachOp -> CallishMachOp -> Bool # |
callishMachOpHints :: CallishMachOp -> ([ForeignHint], [ForeignHint]) Source #
Return (results_hints,args_hints)
pprCallishMachOp :: CallishMachOp -> SDoc Source #
machOpMemcpyishAlign :: CallishMachOp -> Maybe Int Source #
The alignment of a memcpy
-ish operation.
data MemoryOrdering Source #
C11 memory ordering semantics.
MemOrderRelaxed | relaxed ordering |
MemOrderAcquire | acquire ordering |
MemOrderRelease | release ordering |
MemOrderSeqCst | sequentially consistent |
Instances
Show MemoryOrdering Source # | |
Defined in GHC.Cmm.MachOp showsPrec :: Int -> MemoryOrdering -> ShowS # show :: MemoryOrdering -> String # showList :: [MemoryOrdering] -> ShowS # | |
Eq MemoryOrdering Source # | |
Defined in GHC.Cmm.MachOp (==) :: MemoryOrdering -> MemoryOrdering -> Bool # (/=) :: MemoryOrdering -> MemoryOrdering -> Bool # | |
Ord MemoryOrdering Source # | |
Defined in GHC.Cmm.MachOp compare :: MemoryOrdering -> MemoryOrdering -> Ordering # (<) :: MemoryOrdering -> MemoryOrdering -> Bool # (<=) :: MemoryOrdering -> MemoryOrdering -> Bool # (>) :: MemoryOrdering -> MemoryOrdering -> Bool # (>=) :: MemoryOrdering -> MemoryOrdering -> Bool # max :: MemoryOrdering -> MemoryOrdering -> MemoryOrdering # min :: MemoryOrdering -> MemoryOrdering -> MemoryOrdering # |
data AtomicMachOp Source #
The operation to perform atomically.
Instances
Show AtomicMachOp Source # | |
Defined in GHC.Cmm.MachOp showsPrec :: Int -> AtomicMachOp -> ShowS # show :: AtomicMachOp -> String # showList :: [AtomicMachOp] -> ShowS # | |
Eq AtomicMachOp Source # | |
Defined in GHC.Cmm.MachOp (==) :: AtomicMachOp -> AtomicMachOp -> Bool # (/=) :: AtomicMachOp -> AtomicMachOp -> Bool # |
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.
pprFMASign :: IsLine doc => FMASign -> doc Source #