Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
An existential type.
The constructor is exported only on GHC-8 and later.
Documentation
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 PatternSynonyms
(available with GHC >= 8.0)
>>>
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
Instances
GEq tag => Eq (Some tag) Source # | |
GCompare tag => Ord (Some tag) Source # | |
Defined in Data.Some.Newtype | |
GRead f => Read (Some f) Source # | |
GShow tag => Show (Some tag) Source # | |
Applicative m => Semigroup (Some m) Source # | |
Applicative m => Monoid (Some m) Source # | |
GNFData tag => NFData (Some tag) Source # | |
Defined in Data.Some.Newtype |