Haskell Hierarchical Libraries (base package)ContentsIndex
Data.Typeable
Portability portable
Stability experimental
Maintainer libraries@haskell.org
Contents
The Typeable class
Type-safe cast
Type representations
Construction of type representations
Observation of type representations
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.Generics uses Typeable and type-safe cast (but not dynamics) to support the "Scrap your boilerplate" style of generic programming.
Synopsis
class Typeable a where
typeOf :: a -> TypeRep
cast :: (Typeable a, Typeable b) => a -> Maybe b
castss :: (Typeable a, Typeable b) => t a -> Maybe (t b)
castarr :: (Typeable a, Typeable b, Typeable c, Typeable d) => (a -> t b) -> Maybe (c -> t d)
data TypeRep
data TyCon
mkTyCon :: String -> TyCon
mkAppTy :: TyCon -> [TypeRep] -> TypeRep
mkFunTy :: TypeRep -> TypeRep -> TypeRep
applyTy :: TypeRep -> TypeRep -> Maybe TypeRep
typerepTyCon :: TypeRep -> TyCon
typerepArgs :: TypeRep -> [TypeRep]
tyconString :: TyCon -> String
The Typeable class
class Typeable a where
The class Typeable allows a concrete representation of a type to be calculated.
Methods
typeOf :: a -> TypeRep
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
Typeable Exception
Typeable IOException
Typeable ArithException
Typeable ArrayException
Typeable AsyncException
(Typeable a, Typeable b) => Typeable (ST a b)
(Typeable a, Typeable b) => Typeable (Array a b)
(Typeable a, Typeable b) => Typeable (UArray a b)
(Typeable a, Typeable b, Typeable c) => Typeable (STArray a b c)
(Typeable a, Typeable b, Typeable c) => Typeable (STUArray a b c)
(Typeable a, Typeable b) => Typeable (IOArray a b)
(Typeable a, Typeable b) => Typeable (IOUArray a b)
Typeable a => Typeable (Complex a)
Typeable Dynamic
Typeable Constr
Typeable PackedString
(Typeable a, Typeable b) => Typeable (STRef a b)
Typeable a => Typeable [a]
Typeable ()
(Typeable a, Typeable b) => Typeable (a, b)
(Typeable a, Typeable b, Typeable c) => Typeable (a, b, c)
(Typeable a, Typeable b, Typeable c, Typeable d) => Typeable (a, b, c, d)
(Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable (a, b, c, d, e)
(Typeable a, Typeable b) => Typeable (a -> b)
Typeable Bool
Typeable Char
Typeable Float
Typeable Double
Typeable Int
Typeable Integer
Typeable a => Typeable (Ratio a)
(Typeable a, Typeable b) => Typeable (Either a b)
Typeable a => Typeable (IO a)
Typeable a => Typeable (Maybe a)
Typeable Ordering
Typeable Handle
Typeable a => Typeable (Ptr a)
Typeable a => Typeable (StablePtr a)
Typeable Int8
Typeable Int16
Typeable Int32
Typeable Int64
Typeable Word8
Typeable Word16
Typeable Word32
Typeable Word64
Typeable TyCon
Typeable TypeRep
Typeable a => Typeable (IORef a)
Typeable CChar
Typeable CSChar
Typeable CUChar
Typeable CShort
Typeable CUShort
Typeable CInt
Typeable CUInt
Typeable CLong
Typeable CULong
Typeable CLLong
Typeable CULLong
Typeable CFloat
Typeable CDouble
Typeable CLDouble
Typeable CPtrdiff
Typeable CSize
Typeable CWchar
Typeable CSigAtomic
Typeable CClock
Typeable CTime
Typeable a => Typeable (ForeignPtr a)
Typeable a => Typeable (StableName a)
Typeable a => Typeable (Weak a)
Typeable CDev
Typeable CIno
Typeable CMode
Typeable COff
Typeable CPid
Typeable CSsize
Typeable CGid
Typeable CNlink
Typeable CUid
Typeable CCc
Typeable CSpeed
Typeable CTcflag
Typeable CRLim
Typeable Fd
Type-safe cast
cast :: (Typeable a, Typeable b) => a -> Maybe b
The type-safe cast operation
castss :: (Typeable a, Typeable b) => t a -> Maybe (t b)
A convenient variation for kind * -> *
castarr :: (Typeable a, Typeable b, Typeable c, Typeable d) => (a -> t b) -> Maybe (c -> t d)
Another variation
Type representations
data TypeRep
A concrete representation of a (monomorphic) type. TypeRep supports reasonably efficient equality.
Instances
Eq TypeRep
Show TypeRep
Typeable TypeRep
data TyCon
An abstract representation of a type constructor. TyCon objects can be built using mkTyCon.
Instances
Eq TyCon
Show TyCon
Typeable TyCon
Construction of type representations
mkTyCon
:: Stringthe name of the type constructor (should be unique in the program, so it might be wise to use the fully qualified name).
-> TyConA 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"
mkAppTy :: TyCon -> [TypeRep] -> TypeRep
Applies a type constructor to a sequence of types
mkFunTy :: TypeRep -> TypeRep -> TypeRep
A special case of mkAppTy, which applies the function type constructor to a pair of types.
applyTy :: TypeRep -> TypeRep -> Maybe TypeRep
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.
Observation of type representations
typerepTyCon :: TypeRep -> TyCon
Observe the type constructor of a type representation
typerepArgs :: TypeRep -> [TypeRep]
Observe the argument types of a type representation
tyconString :: TyCon -> String
Observe string encoding of a type representation
Produced by Haddock version 0.6