| Copyright | (c) The University of Glasgow CWI 2001--2017 | 
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Stability | experimental | 
| Portability | non-portable (requires GADTs and compiler support) | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Type.Reflection
Contents
Description
This provides a type-indexed type representation mechanism, similar to that described by,
- Simon Peyton-Jones, Stephanie Weirich, Richard Eisenberg, Dimitrios Vytiniotis. "A reflection on types." /Proc. Philip Wadler's 60th birthday Festschrift/, Edinburgh (April 2016).
 
The interface provides TypeRep, a type representation which can
 be safely decomposed and composed. See Data.Dynamic for an example of this.
Since: 4.10.0.0
- class Typeable (a :: k)
 - typeRep :: Typeable a => TypeRep a
 - withTypeable :: forall a r. TypeRep a -> (Typeable a => r) -> r
 - data a :~: b where
 - data (a :: k1) :~~: (b :: k2) where
 - data TypeRep (a :: k)
 - typeOf :: Typeable a => a -> TypeRep a
 - pattern App :: forall k2 (t :: k2). forall k1 (a :: k1 -> k2) (b :: k1). t ~ a b => TypeRep a -> TypeRep b -> TypeRep t
 - pattern Con :: forall k (a :: k). TyCon -> TypeRep a
 - pattern Con' :: forall k (a :: k). TyCon -> [SomeTypeRep] -> TypeRep a
 - pattern Fun :: forall k (fun :: k). forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (arg :: TYPE r1) (res :: TYPE r2). (k ~ Type, fun ~~ (arg -> res)) => TypeRep arg -> TypeRep res -> TypeRep fun
 - typeRepTyCon :: TypeRep a -> TyCon
 - rnfTypeRep :: TypeRep a -> ()
 - eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> Maybe (a :~~: b)
 - typeRepKind :: TypeRep (a :: k) -> TypeRep k
 - splitApps :: TypeRep a -> (TyCon, [SomeTypeRep])
 - data SomeTypeRep where
- SomeTypeRep :: forall k (a :: k). !(TypeRep a) -> SomeTypeRep
 
 - someTypeRep :: forall proxy a. Typeable a => proxy a -> SomeTypeRep
 - someTypeRepTyCon :: SomeTypeRep -> TyCon
 - rnfSomeTypeRep :: SomeTypeRep -> ()
 - data TyCon :: *
 - tyConPackage :: TyCon -> String
 - tyConModule :: TyCon -> String
 - tyConName :: TyCon -> String
 - rnfTyCon :: TyCon -> ()
 - data Module :: *
 - moduleName :: Module -> String
 - modulePackage :: Module -> String
 - rnfModule :: Module -> ()
 
The Typeable class
class Typeable (a :: k) Source #
The class Typeable allows a concrete representation of a type to
 be calculated.
Minimal complete definition
typeRep#
withTypeable :: forall a r. TypeRep a -> (Typeable a => r) -> r Source #
Propositional equality
data a :~: b where infix 4 Source #
Propositional equality. If a :~: b is inhabited by some terminating
 value, then the type a is the same as the type b. To use this equality
 in practice, pattern-match on the a :~: b to get out the Refl constructor;
 in the body of the pattern-match, the compiler knows that a ~ b.
Since: 4.7.0.0
Instances
| Category k ((:~:) k) Source # | Since: 4.7.0.0  | 
| TestEquality k ((:~:) k a) Source # | Since: 4.7.0.0  | 
| TestCoercion k ((:~:) k a) Source # | Since: 4.7.0.0  | 
| (~) k a b => Bounded ((:~:) k a b) Source # | Since: 4.7.0.0  | 
| (~) k a b => Enum ((:~:) k a b) Source # | Since: 4.7.0.0  | 
| Eq ((:~:) k a b) Source # | |
| ((~) * a b, Data a) => Data ((:~:) * a b) Source # | Since: 4.7.0.0  | 
| Ord ((:~:) k a b) Source # | |
| (~) k a b => Read ((:~:) k a b) Source # | Since: 4.7.0.0  | 
| Show ((:~:) k a b) Source # | |
data (a :: k1) :~~: (b :: k2) where infix 4 Source #
Kind heterogeneous propositional equality. Like '(:~:)', a :~~: b is
 inhabited by a terminating value if and only if a is the same type as b.
Since: 4.10.0.0
Instances
| Category k ((:~~:) k k) Source # | Since: 4.10.0.0  | 
| TestEquality k ((:~~:) k1 k a) Source # | Since: 4.10.0.0  | 
| TestCoercion k ((:~~:) k1 k a) Source # | Since: 4.10.0.0  | 
| (~~) k1 k2 a b => Bounded ((:~~:) k1 k2 a b) Source # | Since: 4.10.0.0  | 
| (~~) k1 k2 a b => Enum ((:~~:) k1 k2 a b) Source # | Since: 4.10.0.0  | 
| Eq ((:~~:) k1 k2 a b) Source # | Since: 4.10.0.0  | 
| (Typeable * i2, Typeable * j2, Typeable i2 a, Typeable j2 b, (~~) i2 j2 a b) => Data ((:~~:) i2 j2 a b) Source # | Since: 4.10.0.0  | 
| Ord ((:~~:) k1 k2 a b) Source # | Since: 4.10.0.0  | 
| (~~) k1 k2 a b => Read ((:~~:) k1 k2 a b) Source # | Since: 4.10.0.0  | 
| Show ((:~~:) k1 k2 a b) Source # | Since: 4.10.0.0  | 
Type representations
Type-Indexed
data TypeRep (a :: k) Source #
A concrete representation of a (monomorphic) type.
 TypeRep supports reasonably efficient equality.
pattern App :: forall k2 (t :: k2). forall k1 (a :: k1 -> k2) (b :: k1). t ~ a b => TypeRep a -> TypeRep b -> TypeRep t Source #
Pattern match on a type application
pattern Con' :: forall k (a :: k). TyCon -> [SomeTypeRep] -> TypeRep a Source #
Pattern match on a type constructor including its instantiated kind variables.
pattern Fun :: forall k (fun :: k). forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (arg :: TYPE r1) (res :: TYPE r2). (k ~ Type, fun ~~ (arg -> res)) => TypeRep arg -> TypeRep res -> TypeRep fun Source #
typeRepTyCon :: TypeRep a -> TyCon Source #
Observe the type constructor of a type representation
rnfTypeRep :: TypeRep a -> () Source #
Helper to fully evaluate TypeRep for use as NFData(rnf) implementation
Since: 4.8.0.0
eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> Maybe (a :~~: b) Source #
Type equality
Since: 4.10
typeRepKind :: TypeRep (a :: k) -> TypeRep k Source #
Observe the kind of a type.
Quantified
data SomeTypeRep where Source #
A non-indexed type representation.
Constructors
| SomeTypeRep :: forall k (a :: k). !(TypeRep a) -> SomeTypeRep | 
Instances
| Eq SomeTypeRep Source # | |
| Ord SomeTypeRep Source # | |
| Show SomeTypeRep Source # | Since: 4.10.0.0  | 
someTypeRep :: forall proxy a. Typeable a => proxy a -> SomeTypeRep Source #
Takes a value of type a and returns a concrete representation
 of that type.
Since: 4.7.0.0
someTypeRepTyCon :: SomeTypeRep -> TyCon Source #
Observe the type constructor of a quantified type representation.
rnfSomeTypeRep :: SomeTypeRep -> () Source #
Helper to fully evaluate SomeTypeRep for use as NFData(rnf)
 implementation
Since: 4.10.0.0
Type constructors
tyConPackage :: TyCon -> String Source #
tyConModule :: TyCon -> String Source #
Module names
moduleName :: Module -> String Source #
modulePackage :: Module -> String Source #