some-1.0.0.2: Existential type: Some

Safe HaskellSafe
LanguageHaskell2010

Data.Some.GADT

Synopsis

Documentation

data Some tag where Source #

Existential. This is type is useful to hide GADTs' parameters.

>>> data Tag :: * -> * where TagInt :: Tag Int; TagBool :: Tag Bool
>>> instance GShow Tag where gshowsPrec _ TagInt = showString "TagInt"; gshowsPrec _ TagBool = showString "TagBool"
>>> classify s = case s of "TagInt" -> [mkGReadResult TagInt]; "TagBool" -> [mkGReadResult TagBool]; _ -> []
>>> instance GRead Tag where greadsPrec _ s = [ (r, rest) | (con, rest) <-  lex s, r <- classify con ]

You can either use constructor:

>>> let x = Some TagInt
>>> x
Some TagInt
>>> case x of { Some TagInt -> "I"; Some TagBool -> "B" } :: String
"I"

or you can use functions

>>> let y = mkSome TagBool
>>> y
Some TagBool
>>> withSome y $ \y' -> case y' of { TagInt -> "I"; TagBool -> "B" } :: String
"B"

The implementation of mapSome is safe.

>>> let f :: Tag a -> Tag a; f TagInt = TagInt; f TagBool = TagBool
>>> mapSome f y
Some TagBool

but you can also use:

>>> withSome y (mkSome . f)
Some TagBool
>>> read "Some TagBool" :: Some Tag
Some TagBool
>>> read "mkSome TagInt" :: Some Tag
Some TagInt

Constructors

Some :: tag a -> Some tag 
Instances
GEq tag => Eq (Some tag) Source # 
Instance details

Defined in Data.Some.GADT

Methods

(==) :: Some tag -> Some tag -> Bool #

(/=) :: Some tag -> Some tag -> Bool #

GCompare tag => Ord (Some tag) Source # 
Instance details

Defined in Data.Some.GADT

Methods

compare :: Some tag -> Some tag -> Ordering #

(<) :: Some tag -> Some tag -> Bool #

(<=) :: Some tag -> Some tag -> Bool #

(>) :: Some tag -> Some tag -> Bool #

(>=) :: Some tag -> Some tag -> Bool #

max :: Some tag -> Some tag -> Some tag #

min :: Some tag -> Some tag -> Some tag #

GRead f => Read (Some f) Source # 
Instance details

Defined in Data.Some.GADT

GShow tag => Show (Some tag) Source # 
Instance details

Defined in Data.Some.GADT

Methods

showsPrec :: Int -> Some tag -> ShowS #

show :: Some tag -> String #

showList :: [Some tag] -> ShowS #

Applicative m => Semigroup (Some m) Source # 
Instance details

Defined in Data.Some.GADT

Methods

(<>) :: Some m -> Some m -> Some m #

sconcat :: NonEmpty (Some m) -> Some m #

stimes :: Integral b => b -> Some m -> Some m #

Applicative m => Monoid (Some m) Source # 
Instance details

Defined in Data.Some.GADT

Methods

mempty :: Some m #

mappend :: Some m -> Some m -> Some m #

mconcat :: [Some m] -> Some m #

GNFData tag => NFData (Some tag) Source # 
Instance details

Defined in Data.Some.GADT

Methods

rnf :: Some tag -> () #

mkSome :: tag a -> Some tag Source #

Constructor.

withSome :: Some tag -> (forall a. tag a -> b) -> b Source #

Eliminator.

mapSome :: (forall x. f x -> g x) -> Some f -> Some g Source #

Map over argument.

foldSome :: (forall a. tag a -> b) -> Some tag -> b Source #

traverseSome :: Functor m => (forall a. f a -> m (g a)) -> Some f -> m (Some g) Source #

Traverse over argument.