| 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 |
Data.Typeable
Contents
Description
TheTypeable 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 moduleData.Dynamic uses Typeable for an implementation of dynamics. The moduleData.Data uses Typeable and type-safe cast (but not dynamics) to support the "Scrap your boilerplate" style of generic programming.
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 theTypeable notion seen in previous releases. For the type-indexed interface, seeType.Reflection.
Since GHC 7.8,Typeable is poly-kinded. The changes required for this might break some old programs involvingTypeable. More details on this, including how to fix your code, can be found on thePolyTypeable wiki page
The classTypeable allows a concrete representation of a type to be calculated.
Minimal complete definition
typeRep#
typeOf ::forall a.Typeable a => a ->TypeRepSource#
Observe a type representation for the type of a value.
typeRep ::forall proxy a.Typeable a => proxy a ->TypeRepSource#
Takes a value of typea and returns a concrete representation of that type.
Since: 4.7.0.0
data a:~: bwhereinfix 4Source#
Propositional equality. Ifa :~: b is inhabited by some terminating value, then the typea is the same as the typeb. To use this equality in practice, pattern-match on thea :~: b to get out theRefl constructor; in the body of the pattern-match, the compiler knows thata ~ b.
Since: 4.7.0.0
| Category ((:~:) :: k -> k ->Type)Source# | Since: 4.7.0.0 |
| TestEquality ((:~:) a :: k ->Type)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Type.Equality | |
| TestCoercion ((:~:) a :: k ->Type)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Type.Coercion | |
| a ~ b =>Bounded (a:~: b)Source# | Since: 4.7.0.0 |
| a ~ b =>Enum (a:~: b)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Type.Equality Methods succ :: (a:~: b) -> a:~: bSource# pred :: (a:~: b) -> a:~: bSource# fromEnum :: (a:~: b) ->IntSource# 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# | |
| Eq (a:~: b)Source# | Since: 4.7.0.0 |
| (a ~ b,Data a) =>Data (a:~: b)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Data Methods 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) ->ConstrSource# dataTypeOf :: (a:~: b) ->DataTypeSource# 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:~: bSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> (a:~: b) -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> (a:~: b) -> rSource# gmapQ :: (forall d.Data d => d -> u) -> (a:~: b) -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) -> (a:~: b) -> uSource# 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# | |
| Ord (a:~: b)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Type.Equality | |
| a ~ b =>Read (a:~: b)Source# | Since: 4.7.0.0 |
| Show (a:~: b)Source# | Since: 4.7.0.0 |
data (a :: k1):~~: (b :: k2)whereinfix 4Source#
Kind heterogeneous propositional equality. Like:~:,a :~~: b is inhabited by a terminating value if and only ifa is the same type asb.
Since: 4.10.0.0
| Category ((:~~:) :: k -> k ->Type)Source# | Since: 4.10.0.0 |
| TestEquality ((:~~:) a :: k ->Type)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Type.Equality | |
| TestCoercion ((:~~:) a :: k ->Type)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Type.Coercion | |
| a~~ b =>Bounded (a:~~: b)Source# | Since: 4.10.0.0 |
| a~~ b =>Enum (a:~~: b)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Type.Equality Methods succ :: (a:~~: b) -> a:~~: bSource# pred :: (a:~~: b) -> a:~~: bSource# toEnum ::Int -> a:~~: bSource# fromEnum :: (a:~~: b) ->IntSource# 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# | |
| Eq (a:~~: b)Source# | Since: 4.10.0.0 |
| (Typeable i,Typeable j,Typeable a,Typeable b, a~~ b) =>Data (a:~~: b)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Data Methods 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) ->ConstrSource# dataTypeOf :: (a:~~: b) ->DataTypeSource# 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:~~: bSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') -> (a:~~: b) -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') -> (a:~~: b) -> rSource# gmapQ :: (forall d.Data d => d -> u) -> (a:~~: b) -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) -> (a:~~: b) -> uSource# 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# | |
| Ord (a:~~: b)Source# | Since: 4.10.0.0 |
Instance detailsDefined inData.Type.Equality | |
| a~~ b =>Read (a:~~: b)Source# | Since: 4.10.0.0 |
| Show (a:~~: b)Source# | Since: 4.10.0.0 |
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
gcast1 ::forall c t t' a. (Typeable t,Typeable t') => c (t a) ->Maybe (c (t' a))Source#
Cast overk1 -> k2
gcast2 ::forall c t t' a b. (Typeable t,Typeable t') => c (t a b) ->Maybe (c (t' a b))Source#
Cast overk1 -> k2 -> k3
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 theProxy ::Proxy a'undefined :: a' idiom.
>>>Proxy :: Proxy (Void, Int -> Int)Proxy
Proxy can even hold types of higher kinds,
>>>Proxy :: Proxy EitherProxy
>>>Proxy :: Proxy FunctorProxy
>>>Proxy :: Proxy complicatedStructureProxy
Constructors
| Proxy |
| Generic1 (Proxy :: k ->Type)Source# | |
| Monad (Proxy ::Type ->Type)Source# | Since: 4.7.0.0 |
| Functor (Proxy ::Type ->Type)Source# | Since: 4.7.0.0 |
| Applicative (Proxy ::Type ->Type)Source# | Since: 4.7.0.0 |
| Foldable (Proxy ::Type ->Type)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Proxy m -> mSource# foldMap ::Monoid m => (a -> m) ->Proxy a -> mSource# foldr :: (a -> b -> b) -> b ->Proxy a -> bSource# foldr' :: (a -> b -> b) -> b ->Proxy a -> bSource# foldl :: (b -> a -> b) -> b ->Proxy a -> bSource# foldl' :: (b -> a -> b) -> b ->Proxy a -> bSource# foldr1 :: (a -> a -> a) ->Proxy a -> aSource# foldl1 :: (a -> a -> a) ->Proxy a -> aSource# toList ::Proxy a -> [a]Source# elem ::Eq a => a ->Proxy a ->BoolSource# maximum ::Ord a =>Proxy a -> aSource# minimum ::Ord a =>Proxy a -> aSource# | |
| Traversable (Proxy ::Type ->Type)Source# | Since: 4.7.0.0 |
| MonadPlus (Proxy ::Type ->Type)Source# | Since: 4.9.0.0 |
| Alternative (Proxy ::Type ->Type)Source# | Since: 4.9.0.0 |
| MonadZip (Proxy ::Type ->Type)Source# | Since: 4.9.0.0 |
| Show1 (Proxy ::Type ->Type)Source# | Since: 4.9.0.0 |
| Read1 (Proxy ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| Ord1 (Proxy ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| Eq1 (Proxy ::Type ->Type)Source# | Since: 4.9.0.0 |
| Contravariant (Proxy ::Type ->Type)Source# | |
| Bounded (Proxy t)Source# | Since: 4.7.0.0 |
| Enum (Proxy s)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Proxy Methods succ ::Proxy s ->Proxy sSource# pred ::Proxy s ->Proxy sSource# fromEnum ::Proxy s ->IntSource# 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# | |
| Eq (Proxy s)Source# | Since: 4.7.0.0 |
| Data t =>Data (Proxy t)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Data Methods 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 ->ConstrSource# dataTypeOf ::Proxy t ->DataTypeSource# 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 tSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Proxy t -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Proxy t -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Proxy t -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Proxy t -> uSource# 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# | |
| Ord (Proxy s)Source# | Since: 4.7.0.0 |
| Read (Proxy t)Source# | Since: 4.7.0.0 |
| Show (Proxy s)Source# | Since: 4.7.0.0 |
| Ix (Proxy s)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Proxy | |
| Generic (Proxy t)Source# | |
| Semigroup (Proxy s)Source# | Since: 4.9.0.0 |
| Monoid (Proxy s)Source# | Since: 4.7.0.0 |
| typeRep1 (Proxy :: k ->Type)Source# | Since: 4.6.0.0 |
| typeRep (Proxy t)Source# | Since: 4.6.0.0 |
typeTypeRep =SomeTypeRepSource#
A quantified type representation.
rnfTypeRep ::TypeRep -> ()Source#
Force aTypeRep to normal form.
showsTypeRep ::TypeRep ->ShowSSource#
Show a type representation
funResultTy ::TypeRep ->TypeRep ->MaybeTypeRepSource#
Applies a type to a function type. Returns:Just u if the first argument represents a function of typet -> u and the second argument represents a function of typet. Otherwise, returnsNothing.
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 ->TyConSource#
Observe the type constructor of a quantified type representation.
typeRepFingerprint ::TypeRep ->FingerprintSource#
Takes a value of typea and returns a concrete representation of that type.
Since: 4.7.0.0
typeOf4 ::forall t (a ::Type) (b ::Type) (c ::Type) (d ::Type).Typeable t => t a b c d ->TypeRepSource#
typeOf5 ::forall t (a ::Type) (b ::Type) (c ::Type) (d ::Type) (e ::Type).Typeable t => t a b c d e ->TypeRepSource#
Produced byHaddock version 2.20.0