Copyright | (c) The University of Glasgow CWI 2001--2004 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
The Typeable
class reifies types to some extent by associating type
representations to types. These type representations can be compared,
and one can in turn define a type-safe cast operation. To this end,
an unsafe cast is guarded by a test for type (representation)
equivalence. The module Data.Dynamic uses Typeable for an
implementation of dynamics. The module Data.Data uses Typeable
and type-safe cast (but not dynamics) to support the "Scrap your
boilerplate" style of generic programming.
Compatibility Notes
Since GHC 8.2, GHC has supported type-indexed type representations. Data.Typeable provides type representations which are qualified over this index, providing an interface very similar to the Typeable notion seen in previous releases. For the type-indexed interface, see Type.Reflection.
Since GHC 7.8, Typeable
is poly-kinded. The changes required for this might
break some old programs involving Typeable
. More details on this, including
how to fix your code, can be found on the
PolyTypeable wiki page
- class Typeable (a :: k)
- typeOf :: forall a. Typeable a => a -> TypeRep
- typeRep :: forall proxy a. Typeable a => proxy a -> TypeRep
- data a :~: b where
- data (a :: k1) :~~: (b :: k2) where
- cast :: forall a b. (Typeable a, Typeable b) => a -> Maybe b
- eqT :: forall a b. (Typeable a, Typeable b) => Maybe (a :~: b)
- gcast :: forall a b c. (Typeable a, Typeable b) => c a -> Maybe (c b)
- gcast1 :: forall c t t' a. (Typeable t, Typeable t') => c (t a) -> Maybe (c (t' a))
- gcast2 :: forall c t t' a b. (Typeable t, Typeable t') => c (t a b) -> Maybe (c (t' a b))
- data Proxy t = Proxy
- type TypeRep = SomeTypeRep
- rnfTypeRep :: TypeRep -> ()
- showsTypeRep :: TypeRep -> ShowS
- mkFunTy :: TypeRep -> TypeRep -> TypeRep
- funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep
- splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
- typeRepArgs :: TypeRep -> [TypeRep]
- typeRepTyCon :: TypeRep -> TyCon
- typeRepFingerprint :: TypeRep -> Fingerprint
- data TyCon :: *
- tyConPackage :: TyCon -> String
- tyConModule :: TyCon -> String
- tyConName :: TyCon -> String
- rnfTyCon :: TyCon -> ()
- tyConFingerprint :: TyCon -> Fingerprint
- typeOf1 :: forall t (a :: *). Typeable t => t a -> TypeRep
- typeOf2 :: forall t (a :: *) (b :: *). Typeable t => t a b -> TypeRep
- typeOf3 :: forall t (a :: *) (b :: *) (c :: *). Typeable t => t a b c -> TypeRep
- typeOf4 :: forall t (a :: *) (b :: *) (c :: *) (d :: *). Typeable t => t a b c d -> TypeRep
- typeOf5 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *). Typeable t => t a b c d e -> TypeRep
- typeOf6 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *). Typeable t => t a b c d e f -> TypeRep
- typeOf7 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *) (g :: *). Typeable t => t a b c d e f g -> TypeRep
- type Typeable1 (a :: * -> *) = Typeable a
- type Typeable2 (a :: * -> * -> *) = Typeable a
- type Typeable3 (a :: * -> * -> * -> *) = Typeable a
- type Typeable4 (a :: * -> * -> * -> * -> *) = Typeable a
- type Typeable5 (a :: * -> * -> * -> * -> * -> *) = Typeable a
- type Typeable6 (a :: * -> * -> * -> * -> * -> * -> *) = Typeable a
- type Typeable7 (a :: * -> * -> * -> * -> * -> * -> * -> *) = Typeable a
The Typeable class
class Typeable (a :: k) Source #
The class Typeable
allows a concrete representation of a type to
be calculated.
typeRep#
typeOf :: forall a. Typeable a => a -> TypeRep Source #
Observe a type representation for the type of a value.
typeRep :: forall proxy a. Typeable a => proxy a -> TypeRep Source #
Takes a value of type a
and returns a concrete representation
of that type.
Since: 4.7.0.0
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
Category k ((:~:) k) # | Since: 4.7.0.0 |
TestEquality k ((:~:) k a) # | Since: 4.7.0.0 |
TestCoercion k ((:~:) k a) # | Since: 4.7.0.0 |
(~) k a b => Bounded ((:~:) k a b) # | Since: 4.7.0.0 |
(~) k a b => Enum ((:~:) k a b) # | Since: 4.7.0.0 |
Eq ((:~:) k a b) # | |
((~) * a b, Data a) => Data ((:~:) * a b) # | Since: 4.7.0.0 |
Ord ((:~:) k a b) # | |
(~) k a b => Read ((:~:) k a b) # | Since: 4.7.0.0 |
Show ((:~:) k a b) # | |
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
Category k ((:~~:) k k) # | Since: 4.10.0.0 |
TestEquality k ((:~~:) k1 k a) # | Since: 4.10.0.0 |
TestCoercion k ((:~~:) k1 k a) # | Since: 4.10.0.0 |
(~~) k1 k2 a b => Bounded ((:~~:) k1 k2 a b) # | Since: 4.10.0.0 |
(~~) k1 k2 a b => Enum ((:~~:) k1 k2 a b) # | Since: 4.10.0.0 |
Eq ((:~~:) k1 k2 a b) # | Since: 4.10.0.0 |
(Typeable * i2, Typeable * j2, Typeable i2 a, Typeable j2 b, (~~) i2 j2 a b) => Data ((:~~:) i2 j2 a b) # | Since: 4.10.0.0 |
Ord ((:~~:) k1 k2 a b) # | Since: 4.10.0.0 |
(~~) k1 k2 a b => Read ((:~~:) k1 k2 a b) # | Since: 4.10.0.0 |
Show ((:~~:) k1 k2 a b) # | Since: 4.10.0.0 |
Type-safe cast
eqT :: forall a b. (Typeable a, Typeable b) => Maybe (a :~: b) Source #
Extract a witness of equality of two types
Since: 4.7.0.0
gcast :: forall a b c. (Typeable a, Typeable b) => c a -> Maybe (c b) Source #
A flexible variation parameterised in a type constructor
Generalized casts for higher-order kinds
gcast1 :: forall c t t' a. (Typeable t, Typeable t') => c (t a) -> Maybe (c (t' a)) Source #
Cast over k1 -> k2
gcast2 :: forall c t t' a b. (Typeable t, Typeable t') => c (t a b) -> Maybe (c (t' a b)) Source #
Cast over k1 -> k2 -> k3
A canonical proxy type
A concrete, poly-kinded proxy type
Generic1 k (Proxy k) # | |
Monad (Proxy *) # | Since: 4.7.0.0 |
Functor (Proxy *) # | Since: 4.7.0.0 |
Applicative (Proxy *) # | Since: 4.7.0.0 |
Foldable (Proxy *) # | Since: 4.7.0.0 |
Traversable (Proxy *) # | Since: 4.7.0.0 |
MonadPlus (Proxy *) # | Since: 4.9.0.0 |
Alternative (Proxy *) # | Since: 4.9.0.0 |
MonadZip (Proxy *) # | Since: 4.9.0.0 |
Show1 (Proxy *) # | Since: 4.9.0.0 |
Read1 (Proxy *) # | Since: 4.9.0.0 |
Ord1 (Proxy *) # | Since: 4.9.0.0 |
Eq1 (Proxy *) # | Since: 4.9.0.0 |
Bounded (Proxy k t) # | |
Enum (Proxy k s) # | Since: 4.7.0.0 |
Eq (Proxy k s) # | Since: 4.7.0.0 |
Data t => Data (Proxy * t) # | Since: 4.7.0.0 |
Ord (Proxy k s) # | Since: 4.7.0.0 |
Read (Proxy k s) # | Since: 4.7.0.0 |
Show (Proxy k s) # | Since: 4.7.0.0 |
Ix (Proxy k s) # | Since: 4.7.0.0 |
Generic (Proxy k t) # | |
Semigroup (Proxy k s) # | Since: 4.9.0.0 |
Monoid (Proxy k s) # | Since: 4.7.0.0 |
type Rep1 k (Proxy k) # | |
type Rep (Proxy k t) # | |
Type representations
type TypeRep = SomeTypeRep Source #
A quantified type representation.
rnfTypeRep :: TypeRep -> () Source #
Force a TypeRep
to normal form.
showsTypeRep :: TypeRep -> ShowS Source #
Show a type representation
Observing type representations
funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep Source #
Applies a type to a function type. Returns: Just u
if the first argument
represents a function of type t -> u
and the second argument represents a
function of type t
. Otherwise, returns Nothing
.
splitTyConApp :: TypeRep -> (TyCon, [TypeRep]) Source #
Splits a type constructor application. Note that if the type constructor is polymorphic, this will not return the kinds that were used.
typeRepArgs :: TypeRep -> [TypeRep] Source #
Observe the argument types of a type representation
typeRepTyCon :: TypeRep -> TyCon Source #
Observe the type constructor of a quantified type representation.
typeRepFingerprint :: TypeRep -> Fingerprint Source #
Takes a value of type a
and returns a concrete representation
of that type.
Since: 4.7.0.0
Type constructors
tyConPackage :: TyCon -> String Source #
tyConModule :: TyCon -> String Source #
tyConFingerprint :: TyCon -> Fingerprint Source #
For backwards compatibility
typeOf4 :: forall t (a :: *) (b :: *) (c :: *) (d :: *). Typeable t => t a b c d -> TypeRep Source #
typeOf5 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *). Typeable t => t a b c d e -> TypeRep Source #
typeOf6 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *). Typeable t => t a b c d e f -> TypeRep Source #
typeOf7 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *) (g :: *). Typeable t => t a b c d e f g -> TypeRep Source #
type Typeable5 (a :: * -> * -> * -> * -> * -> *) = Typeable a Source #
Deprecated: renamed to Typeable