{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE PolyKinds #-}
#endif
#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Safe #-}
#elif __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Data.Some.GADT (
Some(Some),
mkSome,
withSome,
withSomeM,
mapSome,
foldSome,
traverseSome,
) where
import Control.Applicative (Applicative (..))
import Control.DeepSeq (NFData (..))
import Data.Monoid (Monoid (..))
import Data.Semigroup (Semigroup (..))
import Data.GADT.Compare
import Data.GADT.DeepSeq
import Data.GADT.Show
data Some tag where
Some :: tag a -> Some tag
mkSome :: tag a -> Some tag
mkSome = Some
withSome :: Some tag -> (forall a. tag a -> b) -> b
withSome (Some thing) some = some thing
withSomeM :: Monad m => m (Some tag) -> (forall a. tag a -> m r) -> m r
withSomeM m k = m >>= \s -> withSome s k
foldSome :: (forall a. tag a -> b) -> Some tag -> b
foldSome some (Some thing) = some thing
mapSome :: (forall x. f x -> g x) -> Some f -> Some g
mapSome nt (Some fx) = Some (nt fx)
traverseSome :: Functor m => (forall a. f a -> m (g a)) -> Some f -> m (Some g)
traverseSome f (Some x) = fmap Some (f x)
instance GShow tag => Show (Some tag) where
showsPrec p (Some thing) = showParen (p > 10)
$ showString "Some "
. gshowsPrec 11 thing
instance GRead f => Read (Some f) where
readsPrec p = readParen (p>10) $ \s ->
[ (getGReadResult withTag Some, rest')
| (con, rest) <- lex s
, con == "Some" || con == "mkSome"
, (withTag, rest') <- greadsPrec 11 rest
]
instance GEq tag => Eq (Some tag) where
Some x == Some y = defaultEq x y
instance GCompare tag => Ord (Some tag) where
compare (Some x) (Some y) = defaultCompare x y
instance GNFData tag => NFData (Some tag) where
rnf (Some x) = grnf x
instance Control.Applicative.Applicative m => Data.Semigroup.Semigroup (Some m) where
Some m <> Some n = Some (m *> n)
instance Applicative m => Data.Monoid.Monoid (Some m) where
mempty = Some (pure ())
mappend = (<>)