Copyright | (c) The University of Glasgow CWI 2001--2004 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | stable |
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.10, all types automatically have Typeable
instances derived.
This is in contrast to previous releases where Typeable
had to be
explicitly derived using the DeriveDataTypeable
language extension.
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
Synopsis
- class Typeable (a :: k)
- typeOf :: Typeable a => a -> TypeRep
- typeRep :: forall {k} proxy (a :: k). Typeable a => proxy a -> TypeRep
- data (a :: k) :~: (b :: k) where
- data (a :: k1) :~~: (b :: k2) where
- cast :: (Typeable a, Typeable b) => a -> Maybe b
- eqT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b)
- heqT :: forall {k1} {k2} (a :: k1) (b :: k2). (Typeable a, Typeable b) => Maybe (a :~~: b)
- decT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Either ((a :~: b) -> Void) (a :~: b)
- hdecT :: forall {k1} {k2} (a :: k1) (b :: k2). (Typeable a, Typeable b) => Either ((a :~~: b) -> Void) (a :~~: b)
- gcast :: forall {k} (a :: k) (b :: k) c. (Typeable a, Typeable b) => c a -> Maybe (c b)
- gcast1 :: forall {k1} {k2} c (t :: k2 -> k1) (t' :: k2 -> k1) (a :: k2). (Typeable t, Typeable t') => c (t a) -> Maybe (c (t' a))
- gcast2 :: forall {k1} {k2} {k3} c (t :: k2 -> k3 -> k1) (t' :: k2 -> k3 -> k1) (a :: k2) (b :: k3). (Typeable t, Typeable t') => c (t a b) -> Maybe (c (t' a b))
- data Proxy (t :: k) = 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 :: Typeable t => t a -> TypeRep
- typeOf2 :: Typeable t => t a b -> TypeRep
- typeOf3 :: Typeable t => t a b c -> TypeRep
- typeOf4 :: Typeable t => t a b c d -> TypeRep
- typeOf5 :: Typeable t => t a b c d e -> TypeRep
- typeOf6 :: Typeable t => t a b c d e f -> TypeRep
- typeOf7 :: Typeable t => t a b c d e f g -> TypeRep
- trLiftedRep :: TypeRep LiftedRep
The Typeable class
class Typeable (a :: k) Source #
The class Typeable
allows a concrete representation of a type to
be calculated.
typeRep#
typeRep :: forall {k} proxy (a :: k). Typeable a => proxy a -> TypeRep Source #
Takes a value of type a
and returns a concrete representation
of that type.
Since: base-4.7.0.0
Propositional equality
data (a :: k) :~: (b :: k) 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: base-4.7.0.0
Instances
Category ((:~:) :: k -> k -> Type) Source # | Since: base-4.7.0.0 |
TestCoercion ((:~:) a :: k -> Type) Source # | Since: base-4.7.0.0 |
Defined in Data.Type.Coercion | |
TestEquality ((:~:) a :: k -> Type) Source # | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
(a ~ b, Data a) => Data (a :~: b) Source # | Since: base-4.7.0.0 |
Defined in Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~: b) -> c (a :~: b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~: b) Source # toConstr :: (a :~: b) -> Constr Source # dataTypeOf :: (a :~: b) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~: b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~: b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~: b) -> a :~: b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (a :~: b) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~: b) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) Source # | |
a ~ b => Bounded (a :~: b) Source # | Since: base-4.7.0.0 |
a ~ b => Enum (a :~: b) Source # | Since: base-4.7.0.0 |
Defined in Data.Type.Equality succ :: (a :~: b) -> a :~: b Source # pred :: (a :~: b) -> a :~: b Source # toEnum :: Int -> a :~: b Source # fromEnum :: (a :~: b) -> Int Source # enumFrom :: (a :~: b) -> [a :~: b] Source # enumFromThen :: (a :~: b) -> (a :~: b) -> [a :~: b] Source # enumFromTo :: (a :~: b) -> (a :~: b) -> [a :~: b] Source # enumFromThenTo :: (a :~: b) -> (a :~: b) -> (a :~: b) -> [a :~: b] Source # | |
a ~ b => Read (a :~: b) Source # | Since: base-4.7.0.0 |
Show (a :~: b) Source # | Since: base-4.7.0.0 |
Eq (a :~: b) Source # | Since: base-4.7.0.0 |
Ord (a :~: b) Source # | Since: base-4.7.0.0 |
Defined in Data.Type.Equality |
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: base-4.10.0.0
Instances
Category ((:~~:) :: k -> k -> Type) Source # | Since: base-4.10.0.0 |
TestCoercion ((:~~:) a :: k -> Type) Source # | Since: base-4.10.0.0 |
Defined in Data.Type.Coercion | |
TestEquality ((:~~:) a :: k -> Type) Source # | Since: base-4.10.0.0 |
Defined in Data.Type.Equality | |
(Typeable i, Typeable j, Typeable a, Typeable b, a ~~ b) => Data (a :~~: b) Source # | Since: base-4.10.0.0 |
Defined in Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~~: b) -> c (a :~~: b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~~: b) Source # toConstr :: (a :~~: b) -> Constr Source # dataTypeOf :: (a :~~: b) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~~: b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~~: b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~~: b) -> a :~~: b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~~: b) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~~: b) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (a :~~: b) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~~: b) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~~: b) -> m (a :~~: b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~~: b) -> m (a :~~: b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~~: b) -> m (a :~~: b) Source # | |
a ~~ b => Bounded (a :~~: b) Source # | Since: base-4.10.0.0 |
a ~~ b => Enum (a :~~: b) Source # | Since: base-4.10.0.0 |
Defined in Data.Type.Equality succ :: (a :~~: b) -> a :~~: b Source # pred :: (a :~~: b) -> a :~~: b Source # toEnum :: Int -> a :~~: b Source # fromEnum :: (a :~~: b) -> Int Source # enumFrom :: (a :~~: b) -> [a :~~: b] Source # enumFromThen :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] Source # enumFromTo :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] Source # enumFromThenTo :: (a :~~: b) -> (a :~~: b) -> (a :~~: b) -> [a :~~: b] Source # | |
a ~~ b => Read (a :~~: b) Source # | Since: base-4.10.0.0 |
Show (a :~~: b) Source # | Since: base-4.10.0.0 |
Eq (a :~~: b) Source # | Since: base-4.10.0.0 |
Ord (a :~~: b) Source # | Since: base-4.10.0.0 |
Defined in Data.Type.Equality compare :: (a :~~: b) -> (a :~~: b) -> Ordering Source # (<) :: (a :~~: b) -> (a :~~: b) -> Bool Source # (<=) :: (a :~~: b) -> (a :~~: b) -> Bool Source # (>) :: (a :~~: b) -> (a :~~: b) -> Bool Source # (>=) :: (a :~~: b) -> (a :~~: b) -> Bool Source # |
Type-safe cast
eqT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) Source #
Extract a witness of equality of two types
Since: base-4.7.0.0
heqT :: forall {k1} {k2} (a :: k1) (b :: k2). (Typeable a, Typeable b) => Maybe (a :~~: b) Source #
Extract a witness of heterogeneous equality of two types
Since: base-4.18.0.0
decT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Either ((a :~: b) -> Void) (a :~: b) Source #
Decide an equality of two types
Since: base-4.19.0.0
hdecT :: forall {k1} {k2} (a :: k1) (b :: k2). (Typeable a, Typeable b) => Either ((a :~~: b) -> Void) (a :~~: b) Source #
Decide heterogeneous equality of two types.
Since: base-4.19.0.0
gcast :: forall {k} (a :: k) (b :: k) 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 {k1} {k2} c (t :: k2 -> k1) (t' :: k2 -> k1) (a :: k2). (Typeable t, Typeable t') => c (t a) -> Maybe (c (t' a)) Source #
Cast over k1 -> k2
gcast2 :: forall {k1} {k2} {k3} c (t :: k2 -> k3 -> k1) (t' :: k2 -> k3 -> k1) (a :: k2) (b :: k3). (Typeable t, Typeable t') => c (t a b) -> Maybe (c (t' a b)) Source #
Cast over k1 -> k2 -> k3
A canonical proxy type
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a
idiom.undefined
:: a
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Instances
Generic1 (Proxy :: k -> Type) Source # | |
Defined in GHC.Generics | |
MonadZip (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
Foldable (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Proxy m -> m Source # foldMap :: Monoid m => (a -> m) -> Proxy a -> m Source # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m Source # foldr :: (a -> b -> b) -> b -> Proxy a -> b Source # foldr' :: (a -> b -> b) -> b -> Proxy a -> b Source # foldl :: (b -> a -> b) -> b -> Proxy a -> b Source # foldl' :: (b -> a -> b) -> b -> Proxy a -> b Source # foldr1 :: (a -> a -> a) -> Proxy a -> a Source # foldl1 :: (a -> a -> a) -> Proxy a -> a Source # toList :: Proxy a -> [a] Source # null :: Proxy a -> Bool Source # length :: Proxy a -> Int Source # elem :: Eq a => a -> Proxy a -> Bool Source # maximum :: Ord a => Proxy a -> a Source # minimum :: Ord a => Proxy a -> a Source # | |
Eq1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
Ord1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] Source # | |
Show1 (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
Contravariant (Proxy :: Type -> Type) Source # | |
Traversable (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 |
Alternative (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
Applicative (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 |
Monad (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 |
MonadPlus (Proxy :: Type -> Type) Source # | Since: base-4.9.0.0 |
Data t => Data (Proxy t) Source # | Since: base-4.7.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) Source # toConstr :: Proxy t -> Constr Source # dataTypeOf :: Proxy t -> DataType Source # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) Source # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) Source # gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) Source # | |
Monoid (Proxy s) Source # | Since: base-4.7.0.0 |
Semigroup (Proxy s) Source # | Since: base-4.9.0.0 |
Bounded (Proxy t) Source # | Since: base-4.7.0.0 |
Enum (Proxy s) Source # | Since: base-4.7.0.0 |
Defined in Data.Proxy succ :: Proxy s -> Proxy s Source # pred :: Proxy s -> Proxy s Source # toEnum :: Int -> Proxy s Source # fromEnum :: Proxy s -> Int Source # enumFrom :: Proxy s -> [Proxy s] Source # enumFromThen :: Proxy s -> Proxy s -> [Proxy s] Source # enumFromTo :: Proxy s -> Proxy s -> [Proxy s] Source # enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] Source # | |
Generic (Proxy t) Source # | |
Defined in GHC.Generics | |
Ix (Proxy s) Source # | Since: base-4.7.0.0 |
Read (Proxy t) Source # | Since: base-4.7.0.0 |
Show (Proxy s) Source # | Since: base-4.7.0.0 |
Eq (Proxy s) Source # | Since: base-4.7.0.0 |
Ord (Proxy s) Source # | Since: base-4.7.0.0 |
type Rep1 (Proxy :: k -> Type) Source # | Since: base-4.6.0.0 |
type Rep (Proxy t) Source # | Since: base-4.6.0.0 |
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: base-4.7.0.0
Type constructors
tyConPackage :: TyCon -> String Source #
tyConModule :: TyCon -> String Source #
tyConFingerprint :: TyCon -> Fingerprint Source #