{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

module GHC.Cmm.MachOp
    ( MachOp(..)
    , pprMachOp, isCommutableMachOp, isAssociativeMachOp
    , isComparisonMachOp, maybeIntComparison, machOpResultType
    , machOpArgReps, maybeInvertComparison, isFloatComparison

    -- MachOp builders
    , mo_wordAdd, mo_wordSub, mo_wordEq, mo_wordNe,mo_wordMul, mo_wordSQuot
    , mo_wordSRem, mo_wordSNeg, mo_wordUQuot, mo_wordURem
    , mo_wordSGe, mo_wordSLe, mo_wordSGt, mo_wordSLt, mo_wordUGe
    , mo_wordULe, mo_wordUGt, mo_wordULt
    , mo_wordAnd, mo_wordOr, mo_wordXor, mo_wordNot
    , mo_wordShl, mo_wordSShr, mo_wordUShr
    , mo_u_8To32, mo_s_8To32, mo_u_16To32, mo_s_16To32
    , mo_u_8ToWord, mo_s_8ToWord, mo_u_16ToWord, mo_s_16ToWord
    , mo_u_32ToWord, mo_s_32ToWord
    , mo_32To8, mo_32To16, mo_WordTo8, mo_WordTo16, mo_WordTo32, mo_WordTo64

    -- CallishMachOp
    , CallishMachOp(..), callishMachOpHints
    , pprCallishMachOp
    , machOpMemcpyishAlign

    -- Atomic read-modify-write
    , AtomicMachOp(..)
   )
where

import GHC.Prelude

import GHC.Platform
import GHC.Cmm.Type
import GHC.Utils.Outputable

-----------------------------------------------------------------------------
--              MachOp
-----------------------------------------------------------------------------

{- |
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.
-}

data MachOp
  -- Integer operations (insensitive to signed/unsigned)
  = MO_Add Width
  | MO_Sub Width
  | MO_Eq  Width
  | MO_Ne  Width
  | MO_Mul Width                -- low word of multiply

  -- Signed multiply/divide
  | MO_S_MulMayOflo Width       -- nonzero if signed multiply overflows
  | MO_S_Quot Width             -- signed / (same semantics as IntQuotOp)
  | MO_S_Rem  Width             -- signed % (same semantics as IntRemOp)
  | MO_S_Neg  Width             -- unary -

  -- Unsigned multiply/divide
  | MO_U_MulMayOflo Width       -- nonzero if unsigned multiply overflows
  | MO_U_Quot Width             -- unsigned / (same semantics as WordQuotOp)
  | MO_U_Rem  Width             -- unsigned % (same semantics as WordRemOp)

  -- Signed comparisons
  | MO_S_Ge Width
  | MO_S_Le Width
  | MO_S_Gt Width
  | MO_S_Lt Width

  -- Unsigned comparisons
  | MO_U_Ge Width
  | MO_U_Le Width
  | MO_U_Gt Width
  | MO_U_Lt Width

  -- Floating point arithmetic
  | MO_F_Add  Width
  | MO_F_Sub  Width
  | MO_F_Neg  Width             -- unary -
  | MO_F_Mul  Width
  | MO_F_Quot Width

  -- Floating point comparison
  | MO_F_Eq Width
  | MO_F_Ne Width
  | MO_F_Ge Width
  | MO_F_Le Width
  | MO_F_Gt Width
  | MO_F_Lt Width

  -- Bitwise operations.  Not all of these may be supported
  -- at all sizes, and only integral Widths are valid.
  | MO_And   Width
  | MO_Or    Width
  | MO_Xor   Width
  | MO_Not   Width
  | MO_Shl   Width
  | MO_U_Shr Width      -- unsigned shift right
  | MO_S_Shr Width      -- signed shift right

  -- Conversions.  Some of these will be NOPs.
  -- Floating-point conversions use the signed variant.
  | MO_SF_Conv Width Width      -- Signed int -> Float
  | MO_FS_Conv Width Width      -- Float -> Signed int
  | MO_SS_Conv Width Width      -- Signed int -> Signed int
  | MO_UU_Conv Width Width      -- unsigned int -> unsigned int
  | MO_XX_Conv Width Width      -- int -> int; puts no requirements on the
                                -- contents of upper bits when extending;
                                -- narrowing is simply truncation; the only
                                -- expectation is that we can recover the
                                -- original value by applying the opposite
                                -- MO_XX_Conv, e.g.,
                                --   MO_XX_CONV W64 W8 (MO_XX_CONV W8 W64 x)
                                -- is equivalent to just x.
  | MO_FF_Conv Width Width      -- Float -> Float

  -- Vector element insertion and extraction operations
  | MO_V_Insert  Length Width   -- Insert scalar into vector
  | MO_V_Extract Length Width   -- Extract scalar from vector

  -- Integer vector operations
  | MO_V_Add Length Width
  | MO_V_Sub Length Width
  | MO_V_Mul Length Width

  -- Signed vector multiply/divide
  | MO_VS_Quot Length Width
  | MO_VS_Rem  Length Width
  | MO_VS_Neg  Length Width

  -- Unsigned vector multiply/divide
  | MO_VU_Quot Length Width
  | MO_VU_Rem  Length Width

  -- Floating point vector element insertion and extraction operations
  | MO_VF_Insert  Length Width   -- Insert scalar into vector
  | MO_VF_Extract Length Width   -- Extract scalar from vector

  -- Floating point vector operations
  | MO_VF_Add  Length Width
  | MO_VF_Sub  Length Width
  | MO_VF_Neg  Length Width      -- unary negation
  | MO_VF_Mul  Length Width
  | MO_VF_Quot Length Width

  -- Alignment check (for -falignment-sanitisation)
  | MO_AlignmentCheck Int Width
  deriving (MachOp -> MachOp -> Bool
(MachOp -> MachOp -> Bool)
-> (MachOp -> MachOp -> Bool) -> Eq MachOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MachOp -> MachOp -> Bool
$c/= :: MachOp -> MachOp -> Bool
== :: MachOp -> MachOp -> Bool
$c== :: MachOp -> MachOp -> Bool
Eq, Length -> MachOp -> ShowS
[MachOp] -> ShowS
MachOp -> String
(Length -> MachOp -> ShowS)
-> (MachOp -> String) -> ([MachOp] -> ShowS) -> Show MachOp
forall a.
(Length -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MachOp] -> ShowS
$cshowList :: [MachOp] -> ShowS
show :: MachOp -> String
$cshow :: MachOp -> String
showsPrec :: Length -> MachOp -> ShowS
$cshowsPrec :: Length -> MachOp -> ShowS
Show)

pprMachOp :: MachOp -> SDoc
pprMachOp :: MachOp -> SDoc
pprMachOp MachOp
mo = String -> SDoc
text (MachOp -> String
forall a. Show a => a -> String
show MachOp
mo)



-- -----------------------------------------------------------------------------
-- Some common MachReps

-- A 'wordRep' is a machine word on the target architecture
-- Specifically, it is the size of an Int#, Word#, Addr#
-- and the unit of allocation on the stack and the heap
-- Any pointer is also guaranteed to be a wordRep.

mo_wordAdd, mo_wordSub, mo_wordEq, mo_wordNe,mo_wordMul, mo_wordSQuot
    , mo_wordSRem, mo_wordSNeg, mo_wordUQuot, mo_wordURem
    , mo_wordSGe, mo_wordSLe, mo_wordSGt, mo_wordSLt, mo_wordUGe
    , mo_wordULe, mo_wordUGt, mo_wordULt
    , mo_wordAnd, mo_wordOr, mo_wordXor, mo_wordNot, mo_wordShl, mo_wordSShr, mo_wordUShr
    , mo_u_8ToWord, mo_s_8ToWord, mo_u_16ToWord, mo_s_16ToWord, mo_u_32ToWord, mo_s_32ToWord
    , mo_WordTo8, mo_WordTo16, mo_WordTo32, mo_WordTo64
    :: Platform -> MachOp

mo_u_8To32, mo_s_8To32, mo_u_16To32, mo_s_16To32
    , mo_32To8, mo_32To16
    :: MachOp

mo_wordAdd :: Platform -> MachOp
mo_wordAdd      Platform
platform = Width -> MachOp
MO_Add (Platform -> Width
wordWidth Platform
platform)
mo_wordSub :: Platform -> MachOp
mo_wordSub      Platform
platform = Width -> MachOp
MO_Sub (Platform -> Width
wordWidth Platform
platform)
mo_wordEq :: Platform -> MachOp
mo_wordEq       Platform
platform = Width -> MachOp
MO_Eq  (Platform -> Width
wordWidth Platform
platform)
mo_wordNe :: Platform -> MachOp
mo_wordNe       Platform
platform = Width -> MachOp
MO_Ne  (Platform -> Width
wordWidth Platform
platform)
mo_wordMul :: Platform -> MachOp
mo_wordMul      Platform
platform = Width -> MachOp
MO_Mul (Platform -> Width
wordWidth Platform
platform)
mo_wordSQuot :: Platform -> MachOp
mo_wordSQuot    Platform
platform = Width -> MachOp
MO_S_Quot (Platform -> Width
wordWidth Platform
platform)
mo_wordSRem :: Platform -> MachOp
mo_wordSRem     Platform
platform = Width -> MachOp
MO_S_Rem (Platform -> Width
wordWidth Platform
platform)
mo_wordSNeg :: Platform -> MachOp
mo_wordSNeg     Platform
platform = Width -> MachOp
MO_S_Neg (Platform -> Width
wordWidth Platform
platform)
mo_wordUQuot :: Platform -> MachOp
mo_wordUQuot    Platform
platform = Width -> MachOp
MO_U_Quot (Platform -> Width
wordWidth Platform
platform)
mo_wordURem :: Platform -> MachOp
mo_wordURem     Platform
platform = Width -> MachOp
MO_U_Rem (Platform -> Width
wordWidth Platform
platform)

mo_wordSGe :: Platform -> MachOp
mo_wordSGe      Platform
platform = Width -> MachOp
MO_S_Ge  (Platform -> Width
wordWidth Platform
platform)
mo_wordSLe :: Platform -> MachOp
mo_wordSLe      Platform
platform = Width -> MachOp
MO_S_Le  (Platform -> Width
wordWidth Platform
platform)
mo_wordSGt :: Platform -> MachOp
mo_wordSGt      Platform
platform = Width -> MachOp
MO_S_Gt  (Platform -> Width
wordWidth Platform
platform)
mo_wordSLt :: Platform -> MachOp
mo_wordSLt      Platform
platform = Width -> MachOp
MO_S_Lt  (Platform -> Width
wordWidth Platform
platform)

mo_wordUGe :: Platform -> MachOp
mo_wordUGe      Platform
platform = Width -> MachOp
MO_U_Ge  (Platform -> Width
wordWidth Platform
platform)
mo_wordULe :: Platform -> MachOp
mo_wordULe      Platform
platform = Width -> MachOp
MO_U_Le  (Platform -> Width
wordWidth Platform
platform)
mo_wordUGt :: Platform -> MachOp
mo_wordUGt      Platform
platform = Width -> MachOp
MO_U_Gt  (Platform -> Width
wordWidth Platform
platform)
mo_wordULt :: Platform -> MachOp
mo_wordULt      Platform
platform = Width -> MachOp
MO_U_Lt  (Platform -> Width
wordWidth Platform
platform)

mo_wordAnd :: Platform -> MachOp
mo_wordAnd      Platform
platform = Width -> MachOp
MO_And (Platform -> Width
wordWidth Platform
platform)
mo_wordOr :: Platform -> MachOp
mo_wordOr       Platform
platform = Width -> MachOp
MO_Or  (Platform -> Width
wordWidth Platform
platform)
mo_wordXor :: Platform -> MachOp
mo_wordXor      Platform
platform = Width -> MachOp
MO_Xor (Platform -> Width
wordWidth Platform
platform)
mo_wordNot :: Platform -> MachOp
mo_wordNot      Platform
platform = Width -> MachOp
MO_Not (Platform -> Width
wordWidth Platform
platform)
mo_wordShl :: Platform -> MachOp
mo_wordShl      Platform
platform = Width -> MachOp
MO_Shl (Platform -> Width
wordWidth Platform
platform)
mo_wordSShr :: Platform -> MachOp
mo_wordSShr     Platform
platform = Width -> MachOp
MO_S_Shr (Platform -> Width
wordWidth Platform
platform)
mo_wordUShr :: Platform -> MachOp
mo_wordUShr     Platform
platform = Width -> MachOp
MO_U_Shr (Platform -> Width
wordWidth Platform
platform)

mo_u_8To32 :: MachOp
mo_u_8To32               = Width -> Width -> MachOp
MO_UU_Conv Width
W8 Width
W32
mo_s_8To32 :: MachOp
mo_s_8To32               = Width -> Width -> MachOp
MO_SS_Conv Width
W8 Width
W32
mo_u_16To32 :: MachOp
mo_u_16To32              = Width -> Width -> MachOp
MO_UU_Conv Width
W16 Width
W32
mo_s_16To32 :: MachOp
mo_s_16To32              = Width -> Width -> MachOp
MO_SS_Conv Width
W16 Width
W32

mo_u_8ToWord :: Platform -> MachOp
mo_u_8ToWord    Platform
platform = Width -> Width -> MachOp
MO_UU_Conv Width
W8  (Platform -> Width
wordWidth Platform
platform)
mo_s_8ToWord :: Platform -> MachOp
mo_s_8ToWord    Platform
platform = Width -> Width -> MachOp
MO_SS_Conv Width
W8  (Platform -> Width
wordWidth Platform
platform)
mo_u_16ToWord :: Platform -> MachOp
mo_u_16ToWord   Platform
platform = Width -> Width -> MachOp
MO_UU_Conv Width
W16 (Platform -> Width
wordWidth Platform
platform)
mo_s_16ToWord :: Platform -> MachOp
mo_s_16ToWord   Platform
platform = Width -> Width -> MachOp
MO_SS_Conv Width
W16 (Platform -> Width
wordWidth Platform
platform)
mo_s_32ToWord :: Platform -> MachOp
mo_s_32ToWord   Platform
platform = Width -> Width -> MachOp
MO_SS_Conv Width
W32 (Platform -> Width
wordWidth Platform
platform)
mo_u_32ToWord :: Platform -> MachOp
mo_u_32ToWord   Platform
platform = Width -> Width -> MachOp
MO_UU_Conv Width
W32 (Platform -> Width
wordWidth Platform
platform)

mo_WordTo8 :: Platform -> MachOp
mo_WordTo8      Platform
platform = Width -> Width -> MachOp
MO_UU_Conv (Platform -> Width
wordWidth Platform
platform) Width
W8
mo_WordTo16 :: Platform -> MachOp
mo_WordTo16     Platform
platform = Width -> Width -> MachOp
MO_UU_Conv (Platform -> Width
wordWidth Platform
platform) Width
W16
mo_WordTo32 :: Platform -> MachOp
mo_WordTo32     Platform
platform = Width -> Width -> MachOp
MO_UU_Conv (Platform -> Width
wordWidth Platform
platform) Width
W32
mo_WordTo64 :: Platform -> MachOp
mo_WordTo64     Platform
platform = Width -> Width -> MachOp
MO_UU_Conv (Platform -> Width
wordWidth Platform
platform) Width
W64

mo_32To8 :: MachOp
mo_32To8                 = Width -> Width -> MachOp
MO_UU_Conv Width
W32 Width
W8
mo_32To16 :: MachOp
mo_32To16                = Width -> Width -> MachOp
MO_UU_Conv Width
W32 Width
W16


-- ----------------------------------------------------------------------------
-- isCommutableMachOp

{- |
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.
-}
isCommutableMachOp :: MachOp -> Bool
isCommutableMachOp :: MachOp -> Bool
isCommutableMachOp MachOp
mop =
  case MachOp
mop of
        MO_Add Width
_                -> Bool
True
        MO_Eq Width
_                 -> Bool
True
        MO_Ne Width
_                 -> Bool
True
        MO_Mul Width
_                -> Bool
True
        MO_S_MulMayOflo Width
_       -> Bool
True
        MO_U_MulMayOflo Width
_       -> Bool
True
        MO_And Width
_                -> Bool
True
        MO_Or Width
_                 -> Bool
True
        MO_Xor Width
_                -> Bool
True
        MO_F_Add Width
_              -> Bool
True
        MO_F_Mul Width
_              -> Bool
True
        MachOp
_other                  -> Bool
False

-- ----------------------------------------------------------------------------
-- isAssociativeMachOp

{- |
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.
-}
isAssociativeMachOp :: MachOp -> Bool
isAssociativeMachOp :: MachOp -> Bool
isAssociativeMachOp MachOp
mop =
  case MachOp
mop of
        MO_Add {} -> Bool
True       -- NB: does not include
        MO_Mul {} -> Bool
True --     floatint point!
        MO_And {} -> Bool
True
        MO_Or  {} -> Bool
True
        MO_Xor {} -> Bool
True
        MachOp
_other    -> Bool
False


-- ----------------------------------------------------------------------------
-- isComparisonMachOp

{- |
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.
-}
isComparisonMachOp :: MachOp -> Bool
isComparisonMachOp :: MachOp -> Bool
isComparisonMachOp MachOp
mop =
  case MachOp
mop of
    MO_Eq   Width
_  -> Bool
True
    MO_Ne   Width
_  -> Bool
True
    MO_S_Ge Width
_  -> Bool
True
    MO_S_Le Width
_  -> Bool
True
    MO_S_Gt Width
_  -> Bool
True
    MO_S_Lt Width
_  -> Bool
True
    MO_U_Ge Width
_  -> Bool
True
    MO_U_Le Width
_  -> Bool
True
    MO_U_Gt Width
_  -> Bool
True
    MO_U_Lt Width
_  -> Bool
True
    MO_F_Eq {} -> Bool
True
    MO_F_Ne {} -> Bool
True
    MO_F_Ge {} -> Bool
True
    MO_F_Le {} -> Bool
True
    MO_F_Gt {} -> Bool
True
    MO_F_Lt {} -> Bool
True
    MachOp
_other     -> Bool
False

{- |
Returns @Just w@ if the operation is an integer comparison with width
@w@, or @Nothing@ otherwise.
-}
maybeIntComparison :: MachOp -> Maybe Width
maybeIntComparison :: MachOp -> Maybe Width
maybeIntComparison MachOp
mop =
  case MachOp
mop of
    MO_Eq   Width
w  -> Width -> Maybe Width
forall a. a -> Maybe a
Just Width
w
    MO_Ne   Width
w  -> Width -> Maybe Width
forall a. a -> Maybe a
Just Width
w
    MO_S_Ge Width
w  -> Width -> Maybe Width
forall a. a -> Maybe a
Just Width
w
    MO_S_Le Width
w  -> Width -> Maybe Width
forall a. a -> Maybe a
Just Width
w
    MO_S_Gt Width
w  -> Width -> Maybe Width
forall a. a -> Maybe a
Just Width
w
    MO_S_Lt Width
w  -> Width -> Maybe Width
forall a. a -> Maybe a
Just Width
w
    MO_U_Ge Width
w  -> Width -> Maybe Width
forall a. a -> Maybe a
Just Width
w
    MO_U_Le Width
w  -> Width -> Maybe Width
forall a. a -> Maybe a
Just Width
w
    MO_U_Gt Width
w  -> Width -> Maybe Width
forall a. a -> Maybe a
Just Width
w
    MO_U_Lt Width
w  -> Width -> Maybe Width
forall a. a -> Maybe a
Just Width
w
    MachOp
_ -> Maybe Width
forall a. Maybe a
Nothing

isFloatComparison :: MachOp -> Bool
isFloatComparison :: MachOp -> Bool
isFloatComparison MachOp
mop =
  case MachOp
mop of
    MO_F_Eq {} -> Bool
True
    MO_F_Ne {} -> Bool
True
    MO_F_Ge {} -> Bool
True
    MO_F_Le {} -> Bool
True
    MO_F_Gt {} -> Bool
True
    MO_F_Lt {} -> Bool
True
    MachOp
_other     -> Bool
False

-- -----------------------------------------------------------------------------
-- Inverting conditions

-- Sometimes it's useful to be able to invert the sense of a
-- condition.  Not all conditional tests are invertible: in
-- particular, floating point conditionals cannot be inverted, because
-- there exist floating-point values which return False for both senses
-- of a condition (eg. !(NaN > NaN) && !(NaN /<= NaN)).

maybeInvertComparison :: MachOp -> Maybe MachOp
maybeInvertComparison :: MachOp -> Maybe MachOp
maybeInvertComparison MachOp
op
  = case MachOp
op of  -- None of these Just cases include floating point
        MO_Eq Width
r   -> MachOp -> Maybe MachOp
forall a. a -> Maybe a
Just (Width -> MachOp
MO_Ne Width
r)
        MO_Ne Width
r   -> MachOp -> Maybe MachOp
forall a. a -> Maybe a
Just (Width -> MachOp
MO_Eq Width
r)
        MO_U_Lt Width
r -> MachOp -> Maybe MachOp
forall a. a -> Maybe a
Just (Width -> MachOp
MO_U_Ge Width
r)
        MO_U_Gt Width
r -> MachOp -> Maybe MachOp
forall a. a -> Maybe a
Just (Width -> MachOp
MO_U_Le Width
r)
        MO_U_Le Width
r -> MachOp -> Maybe MachOp
forall a. a -> Maybe a
Just (Width -> MachOp
MO_U_Gt Width
r)
        MO_U_Ge Width
r -> MachOp -> Maybe MachOp
forall a. a -> Maybe a
Just (Width -> MachOp
MO_U_Lt Width
r)
        MO_S_Lt Width
r -> MachOp -> Maybe MachOp
forall a. a -> Maybe a
Just (Width -> MachOp
MO_S_Ge Width
r)
        MO_S_Gt Width
r -> MachOp -> Maybe MachOp
forall a. a -> Maybe a
Just (Width -> MachOp
MO_S_Le Width
r)
        MO_S_Le Width
r -> MachOp -> Maybe MachOp
forall a. a -> Maybe a
Just (Width -> MachOp
MO_S_Gt Width
r)
        MO_S_Ge Width
r -> MachOp -> Maybe MachOp
forall a. a -> Maybe a
Just (Width -> MachOp
MO_S_Lt Width
r)
        MachOp
_other    -> Maybe MachOp
forall a. Maybe a
Nothing

-- ----------------------------------------------------------------------------
-- machOpResultType

{- |
Returns the MachRep of the result of a MachOp.
-}
machOpResultType :: Platform -> MachOp -> [CmmType] -> CmmType
machOpResultType :: Platform -> MachOp -> [CmmType] -> CmmType
machOpResultType Platform
platform MachOp
mop [CmmType]
tys =
  case MachOp
mop of
    MO_Add {}           -> CmmType
ty1  -- Preserve GC-ptr-hood
    MO_Sub {}           -> CmmType
ty1  -- of first arg
    MO_Mul    Width
r         -> Width -> CmmType
cmmBits Width
r
    MO_S_MulMayOflo Width
r   -> Width -> CmmType
cmmBits Width
r
    MO_S_Quot Width
r         -> Width -> CmmType
cmmBits Width
r
    MO_S_Rem  Width
r         -> Width -> CmmType
cmmBits Width
r
    MO_S_Neg  Width
r         -> Width -> CmmType
cmmBits Width
r
    MO_U_MulMayOflo Width
r   -> Width -> CmmType
cmmBits Width
r
    MO_U_Quot Width
r         -> Width -> CmmType
cmmBits Width
r
    MO_U_Rem  Width
r         -> Width -> CmmType
cmmBits Width
r

    MO_Eq {}            -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_Ne {}            -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_S_Ge {}          -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_S_Le {}          -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_S_Gt {}          -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_S_Lt {}          -> Platform -> CmmType
comparisonResultRep Platform
platform

    MO_U_Ge {}          -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_U_Le {}          -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_U_Gt {}          -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_U_Lt {}          -> Platform -> CmmType
comparisonResultRep Platform
platform

    MO_F_Add Width
r          -> Width -> CmmType
cmmFloat Width
r
    MO_F_Sub Width
r          -> Width -> CmmType
cmmFloat Width
r
    MO_F_Mul Width
r          -> Width -> CmmType
cmmFloat Width
r
    MO_F_Quot Width
r         -> Width -> CmmType
cmmFloat Width
r
    MO_F_Neg Width
r          -> Width -> CmmType
cmmFloat Width
r
    MO_F_Eq  {}         -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_F_Ne  {}         -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_F_Ge  {}         -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_F_Le  {}         -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_F_Gt  {}         -> Platform -> CmmType
comparisonResultRep Platform
platform
    MO_F_Lt  {}         -> Platform -> CmmType
comparisonResultRep Platform
platform

    MO_And {}           -> CmmType
ty1  -- Used for pointer masking
    MO_Or {}            -> CmmType
ty1
    MO_Xor {}           -> CmmType
ty1
    MO_Not   Width
r          -> Width -> CmmType
cmmBits Width
r
    MO_Shl   Width
r          -> Width -> CmmType
cmmBits Width
r
    MO_U_Shr Width
r          -> Width -> CmmType
cmmBits Width
r
    MO_S_Shr Width
r          -> Width -> CmmType
cmmBits Width
r

    MO_SS_Conv Width
_ Width
to     -> Width -> CmmType
cmmBits Width
to
    MO_UU_Conv Width
_ Width
to     -> Width -> CmmType
cmmBits Width
to
    MO_XX_Conv Width
_ Width
to     -> Width -> CmmType
cmmBits Width
to
    MO_FS_Conv Width
_ Width
to     -> Width -> CmmType
cmmBits Width
to
    MO_SF_Conv Width
_ Width
to     -> Width -> CmmType
cmmFloat Width
to
    MO_FF_Conv Width
_ Width
to     -> Width -> CmmType
cmmFloat Width
to

    MO_V_Insert  Length
l Width
w    -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmBits Width
w)
    MO_V_Extract Length
_ Width
w    -> Width -> CmmType
cmmBits Width
w

    MO_V_Add Length
l Width
w        -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmBits Width
w)
    MO_V_Sub Length
l Width
w        -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmBits Width
w)
    MO_V_Mul Length
l Width
w        -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmBits Width
w)

    MO_VS_Quot Length
l Width
w      -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmBits Width
w)
    MO_VS_Rem  Length
l Width
w      -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmBits Width
w)
    MO_VS_Neg  Length
l Width
w      -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmBits Width
w)

    MO_VU_Quot Length
l Width
w      -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmBits Width
w)
    MO_VU_Rem  Length
l Width
w      -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmBits Width
w)

    MO_VF_Insert  Length
l Width
w   -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmFloat Width
w)
    MO_VF_Extract Length
_ Width
w   -> Width -> CmmType
cmmFloat Width
w

    MO_VF_Add  Length
l Width
w      -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmFloat Width
w)
    MO_VF_Sub  Length
l Width
w      -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmFloat Width
w)
    MO_VF_Mul  Length
l Width
w      -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmFloat Width
w)
    MO_VF_Quot Length
l Width
w      -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmFloat Width
w)
    MO_VF_Neg  Length
l Width
w      -> Length -> CmmType -> CmmType
cmmVec Length
l (Width -> CmmType
cmmFloat Width
w)

    MO_AlignmentCheck Length
_ Width
_ -> CmmType
ty1
  where
    (CmmType
ty1:[CmmType]
_) = [CmmType]
tys

comparisonResultRep :: Platform -> CmmType
comparisonResultRep :: Platform -> CmmType
comparisonResultRep = Platform -> CmmType
bWord  -- is it?


-- -----------------------------------------------------------------------------
-- machOpArgReps

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

machOpArgReps :: Platform -> MachOp -> [Width]
machOpArgReps :: Platform -> MachOp -> [Width]
machOpArgReps Platform
platform MachOp
op =
  case MachOp
op of
    MO_Add    Width
r         -> [Width
r,Width
r]
    MO_Sub    Width
r         -> [Width
r,Width
r]
    MO_Eq     Width
r         -> [Width
r,Width
r]
    MO_Ne     Width
r         -> [Width
r,Width
r]
    MO_Mul    Width
r         -> [Width
r,Width
r]
    MO_S_MulMayOflo Width
r   -> [Width
r,Width
r]
    MO_S_Quot Width
r         -> [Width
r,Width
r]
    MO_S_Rem  Width
r         -> [Width
r,Width
r]
    MO_S_Neg  Width
r         -> [Width
r]
    MO_U_MulMayOflo Width
r   -> [Width
r,Width
r]
    MO_U_Quot Width
r         -> [Width
r,Width
r]
    MO_U_Rem  Width
r         -> [Width
r,Width
r]

    MO_S_Ge Width
r           -> [Width
r,Width
r]
    MO_S_Le Width
r           -> [Width
r,Width
r]
    MO_S_Gt Width
r           -> [Width
r,Width
r]
    MO_S_Lt Width
r           -> [Width
r,Width
r]

    MO_U_Ge Width
r           -> [Width
r,Width
r]
    MO_U_Le Width
r           -> [Width
r,Width
r]
    MO_U_Gt Width
r           -> [Width
r,Width
r]
    MO_U_Lt Width
r           -> [Width
r,Width
r]

    MO_F_Add Width
r          -> [Width
r,Width
r]
    MO_F_Sub Width
r          -> [Width
r,Width
r]
    MO_F_Mul Width
r          -> [Width
r,Width
r]
    MO_F_Quot Width
r         -> [Width
r,Width
r]
    MO_F_Neg Width
r          -> [Width
r]
    MO_F_Eq  Width
r          -> [Width
r,Width
r]
    MO_F_Ne  Width
r          -> [Width
r,Width
r]
    MO_F_Ge  Width
r          -> [Width
r,Width
r]
    MO_F_Le  Width
r          -> [Width
r,Width
r]
    MO_F_Gt  Width
r          -> [Width
r,Width
r]
    MO_F_Lt  Width
r          -> [Width
r,Width
r]

    MO_And   Width
r          -> [Width
r,Width
r]
    MO_Or    Width
r          -> [Width
r,Width
r]
    MO_Xor   Width
r          -> [Width
r,Width
r]
    MO_Not   Width
r          -> [Width
r]
    MO_Shl   Width
r          -> [Width
r, Platform -> Width
wordWidth Platform
platform]
    MO_U_Shr Width
r          -> [Width
r, Platform -> Width
wordWidth Platform
platform]
    MO_S_Shr Width
r          -> [Width
r, Platform -> Width
wordWidth Platform
platform]

    MO_SS_Conv Width
from Width
_   -> [Width
from]
    MO_UU_Conv Width
from Width
_   -> [Width
from]
    MO_XX_Conv Width
from Width
_   -> [Width
from]
    MO_SF_Conv Width
from Width
_   -> [Width
from]
    MO_FS_Conv Width
from Width
_   -> [Width
from]
    MO_FF_Conv Width
from Width
_   -> [Width
from]

    MO_V_Insert  Length
l Width
r    -> [CmmType -> Width
typeWidth (Length -> CmmType -> CmmType
vec Length
l (Width -> CmmType
cmmBits Width
r)),Width
r,Platform -> Width
wordWidth Platform
platform]
    MO_V_Extract Length
l Width
r    -> [CmmType -> Width
typeWidth (Length -> CmmType -> CmmType
vec Length
l (Width -> CmmType
cmmBits Width
r)),Platform -> Width
wordWidth Platform
platform]

    MO_V_Add Length
_ Width
r        -> [Width
r,Width
r]
    MO_V_Sub Length
_ Width
r        -> [Width
r,Width
r]
    MO_V_Mul Length
_ Width
r        -> [Width
r,Width
r]

    MO_VS_Quot Length
_ Width
r      -> [Width
r,Width
r]
    MO_VS_Rem  Length
_ Width
r      -> [Width
r,Width
r]
    MO_VS_Neg  Length
_ Width
r      -> [Width
r]

    MO_VU_Quot Length
_ Width
r      -> [Width
r,Width
r]
    MO_VU_Rem  Length
_ Width
r      -> [Width
r,Width
r]

    MO_VF_Insert  Length
l Width
r   -> [CmmType -> Width
typeWidth (Length -> CmmType -> CmmType
vec Length
l (Width -> CmmType
cmmFloat Width
r)),Width
r,Platform -> Width
wordWidth Platform
platform]
    MO_VF_Extract Length
l Width
r   -> [CmmType -> Width
typeWidth (Length -> CmmType -> CmmType
vec Length
l (Width -> CmmType
cmmFloat Width
r)),Platform -> Width
wordWidth Platform
platform]

    MO_VF_Add  Length
_ Width
r      -> [Width
r,Width
r]
    MO_VF_Sub  Length
_ Width
r      -> [Width
r,Width
r]
    MO_VF_Mul  Length
_ Width
r      -> [Width
r,Width
r]
    MO_VF_Quot Length
_ Width
r      -> [Width
r,Width
r]
    MO_VF_Neg  Length
_ Width
r      -> [Width
r]

    MO_AlignmentCheck Length
_ Width
r -> [Width
r]

-----------------------------------------------------------------------------
-- CallishMachOp
-----------------------------------------------------------------------------

-- CallishMachOps tend to be implemented by foreign calls in some backends,
-- so we separate them out.  In Cmm, these can only occur in a
-- statement position, in contrast to an ordinary MachOp which can occur
-- anywhere in an expression.
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_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_ReadBarrier
  | MO_WriteBarrier
  | MO_Touch         -- Keep variables live (when using interior pointers)

  -- Prefetch
  | MO_Prefetch_Data Int -- Prefetch hint. May change program performance but not
                     -- program behavior.
                     -- the Int can be 0-3. Needs to be known at compile time
                     -- to interact with code generation correctly.
                     --  TODO: add support for prefetch WRITES,
                     --  currently only exposes prefetch reads, which
                     -- would the majority of use cases in ghc anyways


  -- These three MachOps are parameterised by the known alignment
  -- of the destination and source (for memcpy/memmove) pointers.
  -- This information may be used for optimisation in backends.
  | 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

  -- Atomic read-modify-write.
  | MO_AtomicRMW Width AtomicMachOp
  | MO_AtomicRead Width
  | MO_AtomicWrite Width
  | MO_Cmpxchg Width
  -- Should be an AtomicRMW variant eventually.
  -- Sequential consistent.
  | MO_Xchg Width
  deriving (CallishMachOp -> CallishMachOp -> Bool
(CallishMachOp -> CallishMachOp -> Bool)
-> (CallishMachOp -> CallishMachOp -> Bool) -> Eq CallishMachOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallishMachOp -> CallishMachOp -> Bool
$c/= :: CallishMachOp -> CallishMachOp -> Bool
== :: CallishMachOp -> CallishMachOp -> Bool
$c== :: CallishMachOp -> CallishMachOp -> Bool
Eq, Length -> CallishMachOp -> ShowS
[CallishMachOp] -> ShowS
CallishMachOp -> String
(Length -> CallishMachOp -> ShowS)
-> (CallishMachOp -> String)
-> ([CallishMachOp] -> ShowS)
-> Show CallishMachOp
forall a.
(Length -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallishMachOp] -> ShowS
$cshowList :: [CallishMachOp] -> ShowS
show :: CallishMachOp -> String
$cshow :: CallishMachOp -> String
showsPrec :: Length -> CallishMachOp -> ShowS
$cshowsPrec :: Length -> CallishMachOp -> ShowS
Show)

-- | The operation to perform atomically.
data AtomicMachOp =
      AMO_Add
    | AMO_Sub
    | AMO_And
    | AMO_Nand
    | AMO_Or
    | AMO_Xor
      deriving (AtomicMachOp -> AtomicMachOp -> Bool
(AtomicMachOp -> AtomicMachOp -> Bool)
-> (AtomicMachOp -> AtomicMachOp -> Bool) -> Eq AtomicMachOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AtomicMachOp -> AtomicMachOp -> Bool
$c/= :: AtomicMachOp -> AtomicMachOp -> Bool
== :: AtomicMachOp -> AtomicMachOp -> Bool
$c== :: AtomicMachOp -> AtomicMachOp -> Bool
Eq, Length -> AtomicMachOp -> ShowS
[AtomicMachOp] -> ShowS
AtomicMachOp -> String
(Length -> AtomicMachOp -> ShowS)
-> (AtomicMachOp -> String)
-> ([AtomicMachOp] -> ShowS)
-> Show AtomicMachOp
forall a.
(Length -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AtomicMachOp] -> ShowS
$cshowList :: [AtomicMachOp] -> ShowS
show :: AtomicMachOp -> String
$cshow :: AtomicMachOp -> String
showsPrec :: Length -> AtomicMachOp -> ShowS
$cshowsPrec :: Length -> AtomicMachOp -> ShowS
Show)

pprCallishMachOp :: CallishMachOp -> SDoc
pprCallishMachOp :: CallishMachOp -> SDoc
pprCallishMachOp CallishMachOp
mo = String -> SDoc
text (CallishMachOp -> String
forall a. Show a => a -> String
show CallishMachOp
mo)

callishMachOpHints :: CallishMachOp -> ([ForeignHint], [ForeignHint])
callishMachOpHints :: CallishMachOp -> ([ForeignHint], [ForeignHint])
callishMachOpHints CallishMachOp
op = case CallishMachOp
op of
  MO_Memcpy Length
_  -> ([], [ForeignHint
AddrHint,ForeignHint
AddrHint,ForeignHint
NoHint])
  MO_Memset Length
_  -> ([], [ForeignHint
AddrHint,ForeignHint
NoHint,ForeignHint
NoHint])
  MO_Memmove Length
_ -> ([], [ForeignHint
AddrHint,ForeignHint
AddrHint,ForeignHint
NoHint])
  MO_Memcmp Length
_  -> ([], [ForeignHint
AddrHint, ForeignHint
AddrHint, ForeignHint
NoHint])
  CallishMachOp
_            -> ([],[])
  -- empty lists indicate NoHint

-- | The alignment of a 'memcpy'-ish operation.
machOpMemcpyishAlign :: CallishMachOp -> Maybe Int
machOpMemcpyishAlign :: CallishMachOp -> Maybe Length
machOpMemcpyishAlign CallishMachOp
op = case CallishMachOp
op of
  MO_Memcpy  Length
align -> Length -> Maybe Length
forall a. a -> Maybe a
Just Length
align
  MO_Memset  Length
align -> Length -> Maybe Length
forall a. a -> Maybe a
Just Length
align
  MO_Memmove Length
align -> Length -> Maybe Length
forall a. a -> Maybe a
Just Length
align
  MO_Memcmp  Length
align -> Length -> Maybe Length
forall a. a -> Maybe a
Just Length
align
  CallishMachOp
_                -> Maybe Length
forall a. Maybe a
Nothing