module Data.Repa.Scalar.Option
(
Option (..)
, fromOption, toOption
, Option2 (..)
, fromOption2, toOption2
, Option3 (..)
, fromOption3, toOption3
, Option4 (..)
, fromOption4, toOption4)
where
data Option a
= Some !a
| None
deriving (Eq, Ord, Show)
toOption :: Maybe a -> Option a
toOption Nothing = None
toOption (Just x) = Some x
{-# INLINE toOption #-}
fromOption :: Option a -> Maybe a
fromOption None = Nothing
fromOption (Some x) = Just x
{-# INLINE fromOption #-}
instance Functor Option where
fmap _ None = None
fmap f (Some x) = Some (f x)
{-# INLINE fmap #-}
data Option2 a b
= Some2 !a !b
| None2
deriving (Eq, Ord, Show)
toOption2 :: Maybe (a, b) -> Option2 a b
toOption2 Nothing = None2
toOption2 (Just (x, y)) = Some2 x y
{-# INLINE toOption2 #-}
fromOption2 :: Option2 a b -> Maybe (a, b)
fromOption2 None2 = Nothing
fromOption2 (Some2 x y) = Just (x, y)
{-# INLINE fromOption2 #-}
instance Functor (Option2 a) where
fmap _ None2 = None2
fmap f (Some2 x y) = Some2 x (f y)
{-# INLINE fmap #-}
data Option3 a b c
= Some3 !a !b !c
| None3
deriving (Eq, Ord, Show)
toOption3 :: Maybe (a, b, c) -> Option3 a b c
toOption3 Nothing = None3
toOption3 (Just (x, y, z)) = Some3 x y z
{-# INLINE toOption3 #-}
fromOption3 :: Option3 a b c -> Maybe (a, b, c)
fromOption3 None3 = Nothing
fromOption3 (Some3 x y z) = Just (x, y, z)
{-# INLINE fromOption3 #-}
instance Functor (Option3 a b) where
fmap _ None3 = None3
fmap f (Some3 x y z) = Some3 x y (f z)
{-# INLINE fmap #-}
data Option4 a b c d
= Some4 !a !b !c !d
| None4
deriving (Eq, Ord, Show)
toOption4 :: Maybe (a, b, c, d) -> Option4 a b c d
toOption4 Nothing = None4
toOption4 (Just (x1, x2, x3, x4)) = Some4 x1 x2 x3 x4
{-# INLINE toOption4 #-}
fromOption4 :: Option4 a b c d -> Maybe (a, b, c, d)
fromOption4 None4 = Nothing
fromOption4 (Some4 x1 x2 x3 x4) = Just (x1, x2, x3, x4)
{-# INLINE fromOption4 #-}
instance Functor (Option4 a b c) where
fmap _ None4 = None4
fmap f (Some4 x y z a) = Some4 x y z (f a)
{-# INLINE fmap #-}