| Portability | portable | 
|---|---|
| Stability | experimental | 
| Maintainer | libraries@haskell.org | 
| Safe Haskell | Trustworthy | 
Data.Typeable
Contents
Description
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.
- class Typeable a where
 - cast :: (Typeable a, Typeable b) => a -> Maybe b
 - gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b)
 - data TypeRep
 - showsTypeRep :: TypeRep -> ShowS
 - data TyCon
 - tyConString :: TyCon -> String
 - tyConPackage :: TyCon -> String
 - tyConModule :: TyCon -> String
 - tyConName :: TyCon -> String
 - mkTyCon :: String -> TyCon
 - mkTyCon3 :: String -> String -> String -> TyCon
 - mkTyConApp :: TyCon -> [TypeRep] -> TypeRep
 - mkAppTy :: TypeRep -> TypeRep -> TypeRep
 - mkFunTy :: TypeRep -> TypeRep -> TypeRep
 - splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
 - funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep
 - typeRepTyCon :: TypeRep -> TyCon
 - typeRepArgs :: TypeRep -> [TypeRep]
 - typeRepKey :: TypeRep -> IO TypeRepKey
 - data TypeRepKey
 - class Typeable1 t where
 - class Typeable2 t where
 - class Typeable3 t where
 - class Typeable4 t where
 - class Typeable5 t where
 - class Typeable6 t where
 - class Typeable7 t where
 - gcast1 :: (Typeable1 t, Typeable1 t') => c (t a) -> Maybe (c (t' a))
 - gcast2 :: (Typeable2 t, Typeable2 t') => c (t a b) -> Maybe (c (t' a b))
 - typeOfDefault :: forall t a. (Typeable1 t, Typeable a) => t a -> TypeRep
 - typeOf1Default :: forall t a b. (Typeable2 t, Typeable a) => t a b -> TypeRep
 - typeOf2Default :: forall t a b c. (Typeable3 t, Typeable a) => t a b c -> TypeRep
 - typeOf3Default :: forall t a b c d. (Typeable4 t, Typeable a) => t a b c d -> TypeRep
 - typeOf4Default :: forall t a b c d e. (Typeable5 t, Typeable a) => t a b c d e -> TypeRep
 - typeOf5Default :: forall t a b c d e f. (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep
 - typeOf6Default :: forall t a b c d e f g. (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep
 
The Typeable class
The class Typeable allows a concrete representation of a type to
 be calculated.
Methods
Instances
Type-safe cast
gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b)Source
A flexible variation parameterised in a type constructor
Type representations
A concrete representation of a (monomorphic) type.  TypeRep
 supports reasonably efficient equality.
showsTypeRep :: TypeRep -> ShowSSource
tyConString :: TyCon -> StringSource
Observe string encoding of a type representation
tyConPackage :: TyCon -> StringSource
tyConModule :: TyCon -> StringSource
Construction of type representations
Arguments
| :: String | package name  | 
| -> String | module name  | 
| -> String | the name of the type constructor  | 
| -> TyCon | A unique   | 
Builds a TyCon object representing a type constructor.  An
 implementation of Data.Typeable should ensure that the following holds:
A==A' ^ B==B' ^ C==C' ==> mkTyCon A B C == mkTyCon A' B' C'
mkTyConApp :: TyCon -> [TypeRep] -> TypeRepSource
Applies a type constructor to a sequence of types
mkFunTy :: TypeRep -> TypeRep -> TypeRepSource
A special case of mkTyConApp, which applies the function 
 type constructor to a pair of types.
Observation of type representations
splitTyConApp :: TypeRep -> (TyCon, [TypeRep])Source
Splits a type constructor application
typeRepTyCon :: TypeRep -> TyConSource
Observe the type constructor of a type representation
typeRepArgs :: TypeRep -> [TypeRep]Source
Observe the argument types of a type representation
typeRepKey :: TypeRep -> IO TypeRepKeySource
data TypeRepKey Source
Instances
The other Typeable classes
Note: The general instances are provided for GHC only.
Variant for unary type constructors
Instances
| Typeable1 [] | |
| Typeable1 Ratio | |
| Typeable1 StablePtr | |
| Typeable1 IO | |
| Typeable1 Ptr | |
| Typeable1 FunPtr | |
| Typeable1 Maybe | |
| Typeable1 MVar | |
| Typeable1 IORef | |
| Typeable1 ForeignPtr | |
| Typeable1 Weak | |
| Typeable1 TVar | |
| Typeable1 STM | |
| Typeable1 Chan | |
| Typeable1 SampleVar | |
| Typeable1 Complex | |
| Typeable1 Fixed | |
| Typeable1 StableName | |
| (Typeable2 s, Typeable a) => Typeable1 (s a) | One Typeable1 instance for all Typeable2 instances  | 
Variant for binary type constructors
Variant for 3-ary type constructors
Variant for 4-ary type constructors
Variant for 5-ary type constructors
Variant for 6-ary type constructors
Variant for 7-ary type constructors
Default instances
Note: These are not needed by GHC, for which these instances are generated by general instance declarations.
typeOfDefault :: forall t a. (Typeable1 t, Typeable a) => t a -> TypeRepSource
typeOf1Default :: forall t a b. (Typeable2 t, Typeable a) => t a b -> TypeRepSource
typeOf2Default :: forall t a b c. (Typeable3 t, Typeable a) => t a b c -> TypeRepSource
typeOf3Default :: forall t a b c d. (Typeable4 t, Typeable a) => t a b c d -> TypeRepSource
typeOf4Default :: forall t a b c d e. (Typeable5 t, Typeable a) => t a b c d e -> TypeRepSource
typeOf5Default :: forall t a b c d e f. (Typeable6 t, Typeable a) => t a b c d e f -> TypeRepSource