| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Data.GADT.Show
Synopsis
- class GShow t where
- gshowsPrec :: Int -> t a -> ShowS
 
 - gshows :: GShow t => t a -> ShowS
 - gshow :: GShow t => t a -> String
 - class GRead t where
- greadsPrec :: Int -> GReadS t
 
 - type GReadS t = String -> [(Some t, String)]
 - greads :: GRead t => GReadS t
 - gread :: GRead t => String -> (forall a. t a -> b) -> b
 - greadMaybe :: GRead t => String -> (forall a. t a -> b) -> Maybe b
 - getGReadResult :: Some tag -> (forall a. tag a -> b) -> b
 - mkGReadResult :: tag a -> Some tag
 
Showing
Show-like class for 1-type-parameter GADTs.  GShow t => ... is equivalent to something
 like (forall a. Show (t a)) => ....  The easiest way to create instances would probably be
 to write (or derive) an instance Show (T a), and then simply say:
instance GShow t where gshowsPrec = showsPrec
Methods
gshowsPrec :: Int -> t a -> ShowS Source #
Instances
| GShow (TypeRep :: k -> Type) Source # | |
Defined in Data.GADT.Internal  | |
| GShow ((:~:) a :: k -> Type) Source # | |
Defined in Data.GADT.Internal  | |
| GShow (GOrdering a :: k -> Type) Source # | |
Defined in Data.GADT.Internal  | |
| (GShow a, GShow b) => GShow (Product a b :: k -> Type) Source # | 
  | 
Defined in Data.GADT.Internal  | |
| (GShow a, GShow b) => GShow (Sum a b :: k -> Type) Source # | 
  | 
Defined in Data.GADT.Internal  | |
Reading
Read-like class for 1-type-parameter GADTs.  Unlike GShow, this one cannot be
 mechanically derived from a Read instance because greadsPrec must choose the phantom
 type based on the String being parsed.
Methods
greadsPrec :: Int -> GReadS t Source #
type GReadS t = String -> [(Some t, String)] Source #
GReadS t is equivalent to ReadS (forall b. (forall a. t a -> b) -> b), which is
 in turn equivalent to ReadS (Exists t) (with data Exists t where Exists :: t a -> Exists t)
greadMaybe :: GRead t => String -> (forall a. t a -> b) -> Maybe b Source #
>>>greadMaybe "InL Refl" mkSome :: Maybe (Some (Sum ((:~:) Int) ((:~:) Bool)))Just (mkSome (InL Refl))
>>>greadMaybe "garbage" mkSome :: Maybe (Some ((:~:) Int))Nothing
getGReadResult :: Some tag -> (forall a. tag a -> b) -> b Source #
mkGReadResult :: tag a -> Some tag Source #