| 
| Data.Typeable | | Portability | portable |  | Stability | experimental |  | Maintainer | libraries@haskell.org |  
  |  
  | 
 | 
 | 
 | 
| 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.
 | 
 | 
| Synopsis | 
 | 
| class  Typeable a  where |   |   |  | cast :: (Typeable a, Typeable b) => a -> Maybe b |   |  | gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b) |   |  | data  TypeRep  |   |  | data  TyCon  |   |  | showsTypeRep :: TypeRep -> ShowS |   |  | mkTyCon :: 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] |   |  | tyConString :: TyCon -> String |   |  | typeRepKey :: TypeRep -> IO Int |   |  | 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 :: (Typeable1 t, Typeable a) => t a -> TypeRep |   |  | typeOf1Default :: (Typeable2 t, Typeable a) => t a b -> TypeRep |   |  | typeOf2Default :: (Typeable3 t, Typeable a) => t a b c -> TypeRep |   |  | typeOf3Default :: (Typeable4 t, Typeable a) => t a b c d -> TypeRep |   |  | typeOf4Default :: (Typeable5 t, Typeable a) => t a b c d e -> TypeRep |   |  | typeOf5Default :: (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep |   |  | typeOf6Default :: (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 |   |  | Takes a value of type a and returns a concrete representation
 of that type.  The value of the argument should be ignored by
 any instance of Typeable, so that it is safe to pass undefined as
 the argument.
 |  
  |   |    Instances |   |  
  | 
 | 
| Type-safe cast
 | 
 | 
 | 
| The type-safe cast operation
 | 
 | 
 | 
| A flexible variation parameterised in a type constructor
 | 
 | 
| Type representations
 | 
 | 
 | 
| A concrete representation of a (monomorphic) type.  TypeRep
 supports reasonably efficient equality.
 |    Instances |   |  
  | 
 | 
 | 
| An abstract representation of a type constructor.  TyCon objects can
 be built using mkTyCon.
 |    Instances |   |  
  | 
 | 
 | 
 | 
| Construction of type representations
 | 
 | 
 | 
| :: String | the name of the type constructor (should be unique
 in the program, so it might be wise to use the
 fully qualified name).
 |  | -> TyCon | A unique TyCon object
 |  Builds a TyCon object representing a type constructor.  An
 implementation of Data.Typeable should ensure that the following holds:
   mkTyCon "a" == mkTyCon "a"
  |  
  | 
 | 
 | 
| Applies a type constructor to a sequence of types
 | 
 | 
 | 
| Adds a TypeRep argument to a TypeRep.
 | 
 | 
 | 
| A special case of mkTyConApp, which applies the function 
 type constructor to a pair of types.
 | 
 | 
| Observation of type representations
 | 
 | 
 | 
| Splits a type constructor application
 | 
 | 
 | 
| 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.
 | 
 | 
 | 
| Observe the type constructor of a type representation
 | 
 | 
 | 
| Observe the argument types of a type representation
 | 
 | 
 | 
| Observe string encoding of a type representation
 | 
 | 
 | 
Returns a unique integer associated with a TypeRep.  This can
 be used for making a mapping with TypeReps
 as the keys, for example.  It is guaranteed that t1 == t2 if and only if
 typeRepKey t1 == typeRepKey t2.
 It is in the IO monad because the actual value of the key may
 vary from run to run of the program.  You should only rely on
 the equality property, not any actual key value.  The relative ordering
 of keys has no meaning either.
  | 
 | 
| The other Typeable classes
 | 
 | 
| Note: The general instances are provided for GHC only.
 | 
 | 
 | 
| Variant for unary type constructors
 |   |  | Methods |   |   |    Instances |   |  
  | 
 | 
 | 
| Variant for binary type constructors
 |   |  | Methods |   |   |    Instances |   |  
  | 
 | 
 | 
| Variant for 3-ary type constructors
 |   |  | Methods |   |   |    Instances |   |  
  | 
 | 
 | 
| Variant for 4-ary type constructors
 |   |  | Methods |   |   |    Instances |   |  
  | 
 | 
 | 
| Variant for 5-ary type constructors
 |   |  | Methods |   |   |    Instances |   |  
  | 
 | 
 | 
| Variant for 6-ary type constructors
 |   |  | Methods |   |   |    Instances |   |  
  | 
 | 
 | 
| Variant for 7-ary type constructors
 |   |  | Methods |   |   |    Instances |   |  
  | 
 | 
 | 
| Cast for * -> *
 | 
 | 
 | 
| Cast for * -> * -> *
 | 
 | 
| Default instances
 | 
 | 
| Note: These are not needed by GHC, for which these instances
 are generated by general instance declarations.
 | 
 | 
 | 
| For defining a Typeable instance from any Typeable1 instance.
 | 
 | 
 | 
| For defining a Typeable1 instance from any Typeable2 instance.
 | 
 | 
 | 
| For defining a Typeable2 instance from any Typeable3 instance.
 | 
 | 
 | 
| For defining a Typeable3 instance from any Typeable4 instance.
 | 
 | 
 | 
| For defining a Typeable4 instance from any Typeable5 instance.
 | 
 | 
 | 
| For defining a Typeable5 instance from any Typeable6 instance.
 | 
 | 
 | 
| For defining a Typeable6 instance from any Typeable7 instance.
 | 
 | 
| Produced by Haddock version 2.6.0 |