{-# LANGUAGE MagicHash, UnboxedTuples, TypeSynonymInstances, FlexibleInstances #-}
{-# LANGUAGE DefaultSignatures, FlexibleContexts, TypeOperators #-}
module Data.Array.Repa.Eval.Elt
(Elt (..))
where
import GHC.Prim
import GHC.Exts
import GHC.Types
import GHC.Word
import GHC.Int
import GHC.Generics
class Elt a where
touch :: a -> IO ()
default touch :: (Generic a, GElt (Rep a)) => a -> IO ()
touch = Rep a Any -> IO ()
forall (f :: * -> *) a. GElt f => f a -> IO ()
gtouch (Rep a Any -> IO ()) -> (a -> Rep a Any) -> a -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep a Any
forall a x. Generic a => a -> Rep a x
from
{-# INLINE touch #-}
zero :: a
default zero :: (Generic a, GElt (Rep a)) => a
zero = Rep a Any -> a
forall a x. Generic a => Rep a x -> a
to Rep a Any
forall (f :: * -> *) a. GElt f => f a
gzero
{-# INLINE zero #-}
one :: a
default one :: (Generic a, GElt (Rep a)) => a
one = Rep a Any -> a
forall a x. Generic a => Rep a x -> a
to Rep a Any
forall (f :: * -> *) a. GElt f => f a
gone
{-# INLINE one #-}
class GElt f where
gtouch :: f a -> IO ()
gzero :: f a
gone :: f a
instance GElt U1 where
gtouch :: U1 a -> IO ()
gtouch U1 a
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# INLINE gtouch #-}
gzero :: U1 a
gzero = U1 a
forall k (p :: k). U1 p
U1
{-# INLINE gzero #-}
gone :: U1 a
gone = U1 a
forall k (p :: k). U1 p
U1
{-# INLINE gone #-}
instance (GElt a, GElt b) => GElt (a :*: b) where
gtouch :: (:*:) a b a -> IO ()
gtouch (a a
x :*: b a
y) = a a -> IO ()
forall (f :: * -> *) a. GElt f => f a -> IO ()
gtouch a a
x IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> b a -> IO ()
forall (f :: * -> *) a. GElt f => f a -> IO ()
gtouch b a
y
{-# INLINE gtouch #-}
gzero :: (:*:) a b a
gzero = a a
forall (f :: * -> *) a. GElt f => f a
gzero a a -> b a -> (:*:) a b a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: b a
forall (f :: * -> *) a. GElt f => f a
gzero
{-# INLINE gzero #-}
gone :: (:*:) a b a
gone = a a
forall (f :: * -> *) a. GElt f => f a
gone a a -> b a -> (:*:) a b a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: b a
forall (f :: * -> *) a. GElt f => f a
gone
{-# INLINE gone #-}
instance (GElt a, GElt b) => GElt (a :+: b) where
gtouch :: (:+:) a b a -> IO ()
gtouch (L1 a a
x) = a a -> IO ()
forall (f :: * -> *) a. GElt f => f a -> IO ()
gtouch a a
x
gtouch (R1 b a
x) = b a -> IO ()
forall (f :: * -> *) a. GElt f => f a -> IO ()
gtouch b a
x
{-# INLINE gtouch #-}
gzero :: (:+:) a b a
gzero = a a -> (:+:) a b a
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 a a
forall (f :: * -> *) a. GElt f => f a
gzero
{-# INLINE gzero #-}
gone :: (:+:) a b a
gone = b a -> (:+:) a b a
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 b a
forall (f :: * -> *) a. GElt f => f a
gone
{-# INLINE gone #-}
instance (GElt a) => GElt (M1 i c a) where
gtouch :: M1 i c a a -> IO ()
gtouch (M1 a a
x) = a a -> IO ()
forall (f :: * -> *) a. GElt f => f a -> IO ()
gtouch a a
x
{-# INLINE gtouch #-}
gzero :: M1 i c a a
gzero = a a -> M1 i c a a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 a a
forall (f :: * -> *) a. GElt f => f a
gzero
{-# INLINE gzero #-}
gone :: M1 i c a a
gone = a a -> M1 i c a a
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 a a
forall (f :: * -> *) a. GElt f => f a
gone
{-# INLINE gone #-}
instance (Elt a) => GElt (K1 i a) where
gtouch :: K1 i a a -> IO ()
gtouch (K1 a
x) = a -> IO ()
forall a. Elt a => a -> IO ()
touch a
x
{-# INLINE gtouch #-}
gzero :: K1 i a a
gzero = a -> K1 i a a
forall k i c (p :: k). c -> K1 i c p
K1 a
forall a. Elt a => a
zero
{-# INLINE gzero #-}
gone :: K1 i a a
gone = a -> K1 i a a
forall k i c (p :: k). c -> K1 i c p
K1 a
forall a. Elt a => a
one
{-# INLINE gone #-}
instance Elt Bool where
{-# INLINE touch #-}
touch :: Bool -> IO ()
touch Bool
b
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Bool -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Bool
b State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Bool
zero = Bool
False
{-# INLINE one #-}
one :: Bool
one = Bool
True
instance Elt Float where
{-# INLINE touch #-}
touch :: Float -> IO ()
touch (F# Float#
f)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Float# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Float#
f State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Float
zero = Float
0
{-# INLINE one #-}
one :: Float
one = Float
1
instance Elt Double where
{-# INLINE touch #-}
touch :: Double -> IO ()
touch (D# Double#
d)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Double# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Double#
d State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Double
zero = Double
0
{-# INLINE one #-}
one :: Double
one = Double
1
instance Elt Int where
{-# INLINE touch #-}
touch :: Int -> IO ()
touch (I# Int#
i)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Int# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Int#
i State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Int
zero = Int
0
{-# INLINE one #-}
one :: Int
one = Int
1
instance Elt Int8 where
{-# INLINE touch #-}
touch :: Int8 -> IO ()
touch (I8# Int#
w)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Int# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Int#
w State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Int8
zero = Int8
0
{-# INLINE one #-}
one :: Int8
one = Int8
1
instance Elt Int16 where
{-# INLINE touch #-}
touch :: Int16 -> IO ()
touch (I16# Int#
w)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Int# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Int#
w State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Int16
zero = Int16
0
{-# INLINE one #-}
one :: Int16
one = Int16
1
instance Elt Int32 where
{-# INLINE touch #-}
touch :: Int32 -> IO ()
touch (I32# Int#
w)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Int# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Int#
w State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Int32
zero = Int32
0
{-# INLINE one #-}
one :: Int32
one = Int32
1
instance Elt Int64 where
{-# INLINE touch #-}
touch :: Int64 -> IO ()
touch (I64# Int#
w)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Int# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Int#
w State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Int64
zero = Int64
0
{-# INLINE one #-}
one :: Int64
one = Int64
1
instance Elt Word where
{-# INLINE touch #-}
touch :: Word -> IO ()
touch (W# Word#
i)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Word# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Word#
i State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Word
zero = Word
0
{-# INLINE one #-}
one :: Word
one = Word
1
instance Elt Word8 where
{-# INLINE touch #-}
touch :: Word8 -> IO ()
touch (W8# Word#
w)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Word# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Word#
w State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Word8
zero = Word8
0
{-# INLINE one #-}
one :: Word8
one = Word8
1
instance Elt Word16 where
{-# INLINE touch #-}
touch :: Word16 -> IO ()
touch (W16# Word#
w)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Word# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Word#
w State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Word16
zero = Word16
0
{-# INLINE one #-}
one :: Word16
one = Word16
1
instance Elt Word32 where
{-# INLINE touch #-}
touch :: Word32 -> IO ()
touch (W32# Word#
w)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Word# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Word#
w State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Word32
zero = Word32
0
{-# INLINE one #-}
one :: Word32
one = Word32
1
instance Elt Word64 where
{-# INLINE touch #-}
touch :: Word64 -> IO ()
touch (W64# Word#
w)
= (State# RealWorld -> (# State# RealWorld, () #)) -> IO ()
forall a. (State# RealWorld -> (# State# RealWorld, a #)) -> IO a
IO (\State# RealWorld
state -> case Word# -> State# RealWorld -> State# RealWorld
forall a. a -> State# RealWorld -> State# RealWorld
touch# Word#
w State# RealWorld
state of
State# RealWorld
state' -> (# State# RealWorld
state', () #))
{-# INLINE zero #-}
zero :: Word64
zero = Word64
0
{-# INLINE one #-}
one :: Word64
one = Word64
1
instance (Elt a, Elt b) => Elt (a, b) where
{-# INLINE touch #-}
touch :: (a, b) -> IO ()
touch (a
a, b
b)
= do a -> IO ()
forall a. Elt a => a -> IO ()
touch a
a
b -> IO ()
forall a. Elt a => a -> IO ()
touch b
b
{-# INLINE zero #-}
zero :: (a, b)
zero = (a
forall a. Elt a => a
zero, b
forall a. Elt a => a
zero)
{-# INLINE one #-}
one :: (a, b)
one = (a
forall a. Elt a => a
one, b
forall a. Elt a => a
one)
instance (Elt a, Elt b, Elt c) => Elt (a, b, c) where
{-# INLINE touch #-}
touch :: (a, b, c) -> IO ()
touch (a
a, b
b, c
c)
= do a -> IO ()
forall a. Elt a => a -> IO ()
touch a
a
b -> IO ()
forall a. Elt a => a -> IO ()
touch b
b
c -> IO ()
forall a. Elt a => a -> IO ()
touch c
c
{-# INLINE zero #-}
zero :: (a, b, c)
zero = (a
forall a. Elt a => a
zero, b
forall a. Elt a => a
zero, c
forall a. Elt a => a
zero)
{-# INLINE one #-}
one :: (a, b, c)
one = (a
forall a. Elt a => a
one, b
forall a. Elt a => a
one, c
forall a. Elt a => a
one)
instance (Elt a, Elt b, Elt c, Elt d) => Elt (a, b, c, d) where
{-# INLINE touch #-}
touch :: (a, b, c, d) -> IO ()
touch (a
a, b
b, c
c, d
d)
= do a -> IO ()
forall a. Elt a => a -> IO ()
touch a
a
b -> IO ()
forall a. Elt a => a -> IO ()
touch b
b
c -> IO ()
forall a. Elt a => a -> IO ()
touch c
c
d -> IO ()
forall a. Elt a => a -> IO ()
touch d
d
{-# INLINE zero #-}
zero :: (a, b, c, d)
zero = (a
forall a. Elt a => a
zero, b
forall a. Elt a => a
zero, c
forall a. Elt a => a
zero, d
forall a. Elt a => a
zero)
{-# INLINE one #-}
one :: (a, b, c, d)
one = (a
forall a. Elt a => a
one, b
forall a. Elt a => a
one, c
forall a. Elt a => a
one, d
forall a. Elt a => a
one)
instance (Elt a, Elt b, Elt c, Elt d, Elt e) => Elt (a, b, c, d, e) where
{-# INLINE touch #-}
touch :: (a, b, c, d, e) -> IO ()
touch (a
a, b
b, c
c, d
d, e
e)
= do a -> IO ()
forall a. Elt a => a -> IO ()
touch a
a
b -> IO ()
forall a. Elt a => a -> IO ()
touch b
b
c -> IO ()
forall a. Elt a => a -> IO ()
touch c
c
d -> IO ()
forall a. Elt a => a -> IO ()
touch d
d
e -> IO ()
forall a. Elt a => a -> IO ()
touch e
e
{-# INLINE zero #-}
zero :: (a, b, c, d, e)
zero = (a
forall a. Elt a => a
zero, b
forall a. Elt a => a
zero, c
forall a. Elt a => a
zero, d
forall a. Elt a => a
zero, e
forall a. Elt a => a
zero)
{-# INLINE one #-}
one :: (a, b, c, d, e)
one = (a
forall a. Elt a => a
one, b
forall a. Elt a => a
one, c
forall a. Elt a => a
one, d
forall a. Elt a => a
one, e
forall a. Elt a => a
one)
instance (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Elt (a, b, c, d, e, f) where
{-# INLINE touch #-}
touch :: (a, b, c, d, e, f) -> IO ()
touch (a
a, b
b, c
c, d
d, e
e, f
f)
= do a -> IO ()
forall a. Elt a => a -> IO ()
touch a
a
b -> IO ()
forall a. Elt a => a -> IO ()
touch b
b
c -> IO ()
forall a. Elt a => a -> IO ()
touch c
c
d -> IO ()
forall a. Elt a => a -> IO ()
touch d
d
e -> IO ()
forall a. Elt a => a -> IO ()
touch e
e
f -> IO ()
forall a. Elt a => a -> IO ()
touch f
f
{-# INLINE zero #-}
zero :: (a, b, c, d, e, f)
zero = (a
forall a. Elt a => a
zero, b
forall a. Elt a => a
zero, c
forall a. Elt a => a
zero, d
forall a. Elt a => a
zero, e
forall a. Elt a => a
zero, f
forall a. Elt a => a
zero)
{-# INLINE one #-}
one :: (a, b, c, d, e, f)
one = (a
forall a. Elt a => a
one, b
forall a. Elt a => a
one, c
forall a. Elt a => a
one, d
forall a. Elt a => a
one, e
forall a. Elt a => a
one, f
forall a. Elt a => a
one)