base-4.5.1.0: Basic libraries

Portabilityportable
Stabilityexperimental
Maintainerlibraries@haskell.org
Safe HaskellTrustworthy

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.

Synopsis

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 Bool 
Typeable Char 
Typeable Double 
Typeable Float 
Typeable Int 
Typeable Int8 
Typeable Int16 
Typeable Int32 
Typeable Int64 
Typeable Integer 
Typeable Ordering 
Typeable RealWorld 
Typeable Word 
Typeable Word8 
Typeable Word16 
Typeable Word32 
Typeable Word64 
Typeable () 
Typeable TyCon 
Typeable TypeRep 
Typeable ArithException 
Typeable ErrorCall 
Typeable SomeException 
Typeable IOException 
Typeable CUIntMax 
Typeable CIntMax 
Typeable CUIntPtr 
Typeable CIntPtr 
Typeable CSUSeconds 
Typeable CUSeconds 
Typeable CTime 
Typeable CClock 
Typeable CSigAtomic 
Typeable CWchar 
Typeable CSize 
Typeable CPtrdiff 
Typeable CDouble 
Typeable CFloat 
Typeable CULLong 
Typeable CLLong 
Typeable CULong 
Typeable CLong 
Typeable CUInt 
Typeable CInt 
Typeable CUShort 
Typeable CShort 
Typeable CUChar 
Typeable CSChar 
Typeable CChar 
Typeable Dynamic 
Typeable IntPtr 
Typeable WordPtr 
Typeable Handle__ 
Typeable Handle 
Typeable ExitCode 
Typeable ArrayException 
Typeable AsyncException 
Typeable AssertionFailed 
Typeable Deadlock 
Typeable BlockedIndefinitelyOnSTM 
Typeable BlockedIndefinitelyOnMVar 
Typeable ThreadId 
Typeable NestedAtomically 
Typeable NonTermination 
Typeable NoMethodError 
Typeable RecUpdError 
Typeable RecConError 
Typeable RecSelError 
Typeable PatternMatchFail 
Typeable Fd 
Typeable CRLim 
Typeable CTcflag 
Typeable CSpeed 
Typeable CCc 
Typeable CUid 
Typeable CNlink 
Typeable CGid 
Typeable CSsize 
Typeable CPid 
Typeable COff 
Typeable CMode 
Typeable CIno 
Typeable CDev 
Typeable FD 
Typeable Exception 
Typeable SpecConstrAnnotation 
Typeable BlockedIndefinitely 
Typeable BlockedOnDeadMVar 
Typeable Unique 
Typeable QSem 
Typeable QSemN 
Typeable Timeout 
Typeable E12 
Typeable E9 
Typeable E6 
Typeable E3 
Typeable E2 
Typeable E1 
Typeable E0 
Typeable Version 
(Typeable1 s, Typeable a) => Typeable (s a)

One Typeable instance for all Typeable1 instances

Type-safe cast

cast :: (Typeable a, Typeable b) => a -> Maybe b

The type-safe cast operation

gcast :: (Typeable a, Typeable b) => c a -> Maybe (c b)

A flexible variation parameterised in a type constructor

Type representations

data TypeRep

A concrete representation of a (monomorphic) type. TypeRep supports reasonably efficient equality.

data TyCon

An abstract representation of a type constructor. TyCon objects can be built using mkTyCon.

tyConString :: TyCon -> String

Observe string encoding of a type representation

Construction of type representations

mkTyCon

Arguments

:: String

unique string

-> TyCon

A unique TyCon object

Deprecated: either derive Typeable, or use mkTyCon3 instead

Backwards-compatible API

mkTyCon3

Arguments

:: String

package name

-> String

module name

-> String

the name of the type constructor

-> TyCon

A unique TyCon object

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] -> TypeRep

Applies a type constructor to a sequence of types

mkAppTy :: TypeRep -> TypeRep -> TypeRep

Adds a TypeRep argument to a TypeRep.

mkFunTy :: TypeRep -> TypeRep -> TypeRep

A special case of mkTyConApp, which applies the function type constructor to a pair of types.

Observation of type representations

splitTyConApp :: TypeRep -> (TyCon, [TypeRep])

Splits a type constructor application

funResultTy :: 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.

typeRepTyCon :: TypeRep -> TyCon

Observe the type constructor of a type representation

typeRepArgs :: TypeRep -> [TypeRep]

Observe the argument types of a type representation

typeRepKey :: TypeRep -> IO TypeRepKey

Deprecated: TypeRep itself is now an instance of Ord

(DEPRECATED) Returns a unique key associated with a TypeRep. This function is deprecated because TypeRep itself is now an instance of Ord, so mappings can be made directly with TypeRep as the key.

The other Typeable classes

Note: The general instances are provided for GHC only.

class Typeable2 t where

Variant for binary type constructors

Methods

typeOf2 :: t a b -> TypeRep

Instances

Typeable2 (->) 
Typeable2 Either 
Typeable2 (,) 
Typeable2 ST 
Typeable2 Array 
Typeable2 IOArray 
Typeable2 STRef 
(Typeable3 s, Typeable a) => Typeable2 (s a)

One Typeable2 instance for all Typeable3 instances

class Typeable3 t where

Variant for 3-ary type constructors

Methods

typeOf3 :: t a b c -> TypeRep

Instances

Typeable3 (,,) 
Typeable3 STArray 
(Typeable4 s, Typeable a) => Typeable3 (s a)

One Typeable3 instance for all Typeable4 instances

class Typeable4 t where

Variant for 4-ary type constructors

Methods

typeOf4 :: t a b c d -> TypeRep

Instances

Typeable4 (,,,) 
(Typeable5 s, Typeable a) => Typeable4 (s a)

One Typeable4 instance for all Typeable5 instances

class Typeable5 t where

Variant for 5-ary type constructors

Methods

typeOf5 :: t a b c d e -> TypeRep

Instances

Typeable5 (,,,,) 
(Typeable6 s, Typeable a) => Typeable5 (s a)

One Typeable5 instance for all Typeable6 instances

class Typeable6 t where

Variant for 6-ary type constructors

Methods

typeOf6 :: t a b c d e f -> TypeRep

Instances

Typeable6 (,,,,,) 
(Typeable7 s, Typeable a) => Typeable6 (s a)

One Typeable6 instance for all Typeable7 instances

class Typeable7 t where

Variant for 7-ary type constructors

Methods

typeOf7 :: t a b c d e f g -> TypeRep

Instances

gcast1 :: (Typeable1 t, Typeable1 t') => c (t a) -> Maybe (c (t' a))

Cast for * -> *

gcast2 :: (Typeable2 t, Typeable2 t') => c (t a b) -> Maybe (c (t' a b))

Cast for * -> * -> *

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 -> TypeRep

For defining a Typeable instance from any Typeable1 instance.

typeOf1Default :: forall t a b. (Typeable2 t, Typeable a) => t a b -> TypeRep

For defining a Typeable1 instance from any Typeable2 instance.

typeOf2Default :: forall t a b c. (Typeable3 t, Typeable a) => t a b c -> TypeRep

For defining a Typeable2 instance from any Typeable3 instance.

typeOf3Default :: forall t a b c d. (Typeable4 t, Typeable a) => t a b c d -> TypeRep

For defining a Typeable3 instance from any Typeable4 instance.

typeOf4Default :: forall t a b c d e. (Typeable5 t, Typeable a) => t a b c d e -> TypeRep

For defining a Typeable4 instance from any Typeable5 instance.

typeOf5Default :: forall t a b c d e f. (Typeable6 t, Typeable a) => t a b c d e f -> TypeRep

For defining a Typeable5 instance from any Typeable6 instance.

typeOf6Default :: forall t a b c d e f g. (Typeable7 t, Typeable a) => t a b c d e f g -> TypeRep

For defining a Typeable6 instance from any Typeable7 instance.