{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
#if __GLASGOW_HASKELL__ >= 801
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
#endif
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE PolyKinds #-}
#endif
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Data.Some.Newtype (
#if __GLASGOW_HASKELL__ >= 801
Some(Some),
#else
Some,
#endif
mkSome,
withSome,
mapSome,
foldSome,
traverseSome,
) where
import Control.Applicative (Applicative (..))
import Control.DeepSeq (NFData (..))
import Data.Monoid (Monoid (..))
import Data.Semigroup (Semigroup (..))
import GHC.Exts (Any)
import Unsafe.Coerce (unsafeCoerce)
import Data.GADT.Compare
import Data.GADT.DeepSeq
import Data.GADT.Show
newtype Some tag = UnsafeSome (tag Any)
#if __GLASGOW_HASKELL__ >= 801
{-# COMPLETE Some #-}
pattern Some :: tag a -> Some tag
pattern Some x <- UnsafeSome ((unsafeCoerce :: tag Any -> tag a) -> x)
where Some x = UnsafeSome ((unsafeCoerce :: tag a -> tag Any) x)
#endif
mkSome :: tag a -> Some tag
mkSome = \x -> UnsafeSome (unsafeCoerce x)
withSome :: Some tag -> (forall a. tag a -> b) -> b
withSome (UnsafeSome thing) some = some (unsafeCoerce thing)
foldSome :: (forall a. tag a -> b) -> Some tag -> b
foldSome some (UnsafeSome thing) = some (unsafeCoerce thing)
mapSome :: (forall t. f t -> g t) -> Some f -> Some g
mapSome f (UnsafeSome x) = UnsafeSome (unsafeCoerce f x)
traverseSome :: Functor m => (forall a. f a -> m (g a)) -> Some f -> m (Some g)
traverseSome f x = withSome x $ \x' -> fmap mkSome (f x')
instance GShow tag => Show (Some tag) where
showsPrec p some = withSome 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 mkSome, rest')
| (con, rest) <- lex s
, con == "Some" || con == "mkSome"
, (withTag, rest') <- greadsPrec 11 rest
]
instance GEq tag => Eq (Some tag) where
x == y =
withSome x $ \x' ->
withSome y $ \y' -> defaultEq x' y'
instance GCompare tag => Ord (Some tag) where
compare x y =
withSome x $ \x' ->
withSome y $ \y' -> defaultCompare x' y'
instance GNFData tag => NFData (Some tag) where
rnf x = withSome x grnf
instance Control.Applicative.Applicative m => Data.Semigroup.Semigroup (Some m) where
m <> n =
withSome m $ \m' ->
withSome n $ \n' ->
mkSome (m' *> n')
instance Applicative m => Data.Monoid.Monoid (Some m) where
mempty = mkSome (pure ())
mappend = (<>)