module Data.Array.Parallel.Base.Rebox (
Rebox(..), Box(..)
) where
import Data.Array.Parallel.Base.Hyperstrict
import GHC.Base (Int(..), Char(..))
import GHC.Float (Float(..), Double(..))
class Rebox a where
rebox :: a -> a
dseq :: a -> b -> b
instance Rebox () where
rebox () = ()
dseq = seq
instance Rebox Bool where
rebox True = True
rebox False = False
dseq = seq
instance Rebox Char where
rebox (C# c#) = id (C# c#)
dseq = seq
instance Rebox Int where
rebox (I# i#) = id (I# i#)
dseq = seq
instance Rebox Float where
rebox (F# f#) = F# f#
dseq = seq
instance Rebox Double where
rebox (D# d#) = D# d#
dseq = seq
instance (Rebox a, Rebox b) => Rebox (a :*: b) where
rebox (x :*: y) = rebox x :*: rebox y
dseq (x :*: y) z = dseq x (dseq y z)
instance (Rebox a, Rebox b) => Rebox (EitherS a b) where
rebox (LeftS x) = LeftS (rebox x)
rebox (RightS y) = RightS (rebox y)
dseq (LeftS x) z = dseq x z
dseq (RightS y) z = dseq y z
instance Rebox a => Rebox (MaybeS a) where
rebox NothingS = NothingS
rebox (JustS x) = JustS (rebox x)
dseq NothingS y = y
dseq (JustS x) y = dseq x y
data Box a = Box a
instance Rebox (Box a) where
rebox (Box a) = Box a
dseq (Box a) x = x
instance Rebox (Lazy a) where
rebox (Lazy a) = Lazy a
dseq (Lazy a) x = x