Safe Haskell | None |
---|---|
Language | Haskell98 |
- 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_MulMayOflo 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_F_Eq Width
- | MO_F_Ne Width
- | MO_F_Ge Width
- | MO_F_Le Width
- | MO_F_Gt Width
- | MO_F_Lt 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_Conv Width Width
- | MO_FS_Conv Width Width
- | MO_SS_Conv Width Width
- | MO_UU_Conv Width Width
- | MO_FF_Conv Width 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_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
- pprMachOp :: MachOp -> SDoc
- isCommutableMachOp :: MachOp -> Bool
- isAssociativeMachOp :: MachOp -> Bool
- isComparisonMachOp :: MachOp -> Bool
- machOpResultType :: DynFlags -> MachOp -> [CmmType] -> CmmType
- machOpArgReps :: DynFlags -> MachOp -> [Width]
- maybeInvertComparison :: MachOp -> Maybe MachOp
- mo_wordAdd :: DynFlags -> MachOp
- mo_wordSub :: DynFlags -> MachOp
- mo_wordEq :: DynFlags -> MachOp
- mo_wordNe :: DynFlags -> MachOp
- mo_wordMul :: DynFlags -> MachOp
- mo_wordSQuot :: DynFlags -> MachOp
- mo_wordSRem :: DynFlags -> MachOp
- mo_wordSNeg :: DynFlags -> MachOp
- mo_wordUQuot :: DynFlags -> MachOp
- mo_wordURem :: DynFlags -> MachOp
- mo_wordSGe :: DynFlags -> MachOp
- mo_wordSLe :: DynFlags -> MachOp
- mo_wordSGt :: DynFlags -> MachOp
- mo_wordSLt :: DynFlags -> MachOp
- mo_wordUGe :: DynFlags -> MachOp
- mo_wordULe :: DynFlags -> MachOp
- mo_wordUGt :: DynFlags -> MachOp
- mo_wordULt :: DynFlags -> MachOp
- mo_wordAnd :: DynFlags -> MachOp
- mo_wordOr :: DynFlags -> MachOp
- mo_wordXor :: DynFlags -> MachOp
- mo_wordNot :: DynFlags -> MachOp
- mo_wordShl :: DynFlags -> MachOp
- mo_wordSShr :: DynFlags -> MachOp
- mo_wordUShr :: DynFlags -> MachOp
- mo_u_8To32 :: MachOp
- mo_s_8To32 :: MachOp
- mo_u_16To32 :: MachOp
- mo_s_16To32 :: MachOp
- mo_u_8ToWord :: DynFlags -> MachOp
- mo_s_8ToWord :: DynFlags -> MachOp
- mo_u_16ToWord :: DynFlags -> MachOp
- mo_s_16ToWord :: DynFlags -> MachOp
- mo_u_32ToWord :: DynFlags -> MachOp
- mo_s_32ToWord :: DynFlags -> MachOp
- mo_32To8 :: MachOp
- mo_32To16 :: MachOp
- mo_WordTo8 :: DynFlags -> MachOp
- mo_WordTo16 :: DynFlags -> MachOp
- mo_WordTo32 :: DynFlags -> MachOp
- mo_WordTo64 :: DynFlags -> 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_Log
- | MO_F64_Exp
- | 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_Log
- | MO_F32_Exp
- | MO_F32_Sqrt
- | MO_UF_Conv Width
- | MO_S_QuotRem Width
- | MO_U_QuotRem Width
- | MO_U_QuotRem2 Width
- | MO_Add2 Width
- | MO_U_Mul2 Width
- | MO_WriteBarrier
- | MO_Touch
- | MO_Prefetch_Data Int
- | MO_Memcpy
- | MO_Memset
- | MO_Memmove
- | MO_PopCnt Width
- | MO_BSwap Width
- callishMachOpHints :: CallishMachOp -> ([ForeignHint], [ForeignHint])
- pprCallishMachOp :: CallishMachOp -> SDoc
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.
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.
machOpResultType :: DynFlags -> MachOp -> [CmmType] -> CmmType Source
Returns the MachRep of the result of a MachOp.
machOpArgReps :: DynFlags -> 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.
mo_wordAdd :: DynFlags -> MachOp Source
mo_wordSub :: DynFlags -> MachOp Source
mo_wordMul :: DynFlags -> MachOp Source
mo_wordSQuot :: DynFlags -> MachOp Source
mo_wordSRem :: DynFlags -> MachOp Source
mo_wordSNeg :: DynFlags -> MachOp Source
mo_wordUQuot :: DynFlags -> MachOp Source
mo_wordURem :: DynFlags -> MachOp Source
mo_wordSGe :: DynFlags -> MachOp Source
mo_wordSLe :: DynFlags -> MachOp Source
mo_wordSGt :: DynFlags -> MachOp Source
mo_wordSLt :: DynFlags -> MachOp Source
mo_wordUGe :: DynFlags -> MachOp Source
mo_wordULe :: DynFlags -> MachOp Source
mo_wordUGt :: DynFlags -> MachOp Source
mo_wordULt :: DynFlags -> MachOp Source
mo_wordAnd :: DynFlags -> MachOp Source
mo_wordXor :: DynFlags -> MachOp Source
mo_wordNot :: DynFlags -> MachOp Source
mo_wordShl :: DynFlags -> MachOp Source
mo_wordSShr :: DynFlags -> MachOp Source
mo_wordUShr :: DynFlags -> MachOp Source
mo_u_8ToWord :: DynFlags -> MachOp Source
mo_s_8ToWord :: DynFlags -> MachOp Source
mo_u_16ToWord :: DynFlags -> MachOp Source
mo_s_16ToWord :: DynFlags -> MachOp Source
mo_u_32ToWord :: DynFlags -> MachOp Source
mo_s_32ToWord :: DynFlags -> MachOp Source
mo_WordTo8 :: DynFlags -> MachOp Source
mo_WordTo16 :: DynFlags -> MachOp Source
mo_WordTo32 :: DynFlags -> MachOp Source
mo_WordTo64 :: DynFlags -> MachOp Source
data CallishMachOp Source
callishMachOpHints :: CallishMachOp -> ([ForeignHint], [ForeignHint]) Source