base-4.7.0.0: Basic libraries

Copyright(c) The University of Glasgow, CWI 2001--2004
License(c) The University of Glasgow, CWI 2001--2004
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
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

A proxy type

data Proxy t Source

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (Proxy *) 
Functor (Proxy *) 
Applicative (Proxy *) 
Foldable (Proxy *) 
Traversable (Proxy *) 
Bounded (Proxy k s) 
Enum (Proxy k s) 
Eq (Proxy k s) 
Data t => Data (Proxy * t) 
Ord (Proxy k s) 
Read (Proxy k s) 
Show (Proxy k s) 
Ix (Proxy k s) 
Generic (Proxy * t) 
Monoid (Proxy k s) 
Typeable (k -> *) (Proxy k) 

The Typeable class

class Typeable a whereSource

The class Typeable allows a concrete representation of a type to be calculated.

Methods

typeRep :: proxy a -> TypeRepSource

Takes a value of type a and returns a concrete representation of that type.

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 * SomeException 
Typeable * TyCon 
Typeable * TypeRep 
Typeable * ArithException 
Typeable * ErrorCall 
Typeable * IOException 
Typeable * Dynamic 
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 * IntPtr 
Typeable * WordPtr 
Typeable * Handle 
Typeable * ExitCode 
Typeable * ArrayException 
Typeable * AsyncException 
Typeable * SomeAsyncException 
Typeable * AssertionFailed 
Typeable * Deadlock 
Typeable * BlockedIndefinitelyOnSTM 
Typeable * BlockedIndefinitelyOnMVar 
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 * ThreadId 
Typeable * NestedAtomically 
Typeable * NonTermination 
Typeable * NoMethodError 
Typeable * RecUpdError 
Typeable * RecConError 
Typeable * RecSelError 
Typeable * PatternMatchFail 
Typeable * QSemN 
Typeable * E12 
Typeable * E9 
Typeable * E6 
Typeable * E3 
Typeable * E2 
Typeable * E1 
Typeable * E0 
Typeable * Unique 
Typeable * Version 
Typeable * SpecConstrAnnotation 
(Typeable (k1 -> k) s, Typeable k1 a) => Typeable k (s a)

Kind-polymorphic Typeable instance for type application

Typeable (* -> * -> * -> * -> * -> * -> * -> *) (,,,,,,) 
Typeable (* -> * -> * -> * -> * -> * -> *) (,,,,,) 
Typeable (* -> * -> * -> * -> * -> *) (,,,,) 
Typeable (* -> * -> * -> * -> *) (,,,) 
Typeable (* -> * -> * -> *) (,,) 
Typeable (* -> * -> *) (->) 
Typeable (* -> * -> *) Either 
Typeable (* -> * -> *) (,) 
Typeable (* -> * -> *) ST 
Typeable (* -> * -> *) STRef 
Typeable (* -> *) [] 
Typeable (* -> *) Ratio 
Typeable (* -> *) StablePtr 
Typeable (* -> *) IO 
Typeable (* -> *) Ptr 
Typeable (* -> *) FunPtr 
Typeable (* -> *) Maybe 
Typeable (* -> *) IORef 
Typeable (* -> *) MVar 
Typeable (* -> *) Weak 
Typeable (* -> *) ForeignPtr 
Typeable (* -> *) TVar 
Typeable (* -> *) STM 
Typeable (* -> *) Chan 
Typeable (* -> *) Complex 
Typeable (* -> *) Fixed 
Typeable (* -> *) StableName 
Typeable (k -> k -> *) (:=: k) 
Typeable (k -> *) (Proxy k) 

Propositional equality

data a :=: b whereSource

Propositional equality. If a :=: b is inhabited by some terminating value, then the type a is the same as the type b. To use this equality in practice, pattern-match on the a :=: b to get out the Refl constructor; in the body of the pattern-match, the compiler knows that a ~ b.

Constructors

Refl :: a :=: a 

Instances

Category k (:=: k) 
EqualityT k (:=: k a) 
Typeable (k -> k -> *) (:=: k) 
Bounded (:=: k a a) 
Enum (:=: k a a) 
Eq (:=: k a b) 
(Typeable * a, Data a) => Data (:=: * a a) 
Ord (:=: k a b) 
Read (:=: k a a) 
Show (:=: k a b) 

For backwards compatibility

typeOf :: forall a. Typeable a => a -> TypeRepSource

typeOf1 :: forall t a. Typeable t => t a -> TypeRepSource

typeOf2 :: forall t a b. Typeable t => t a b -> TypeRepSource

typeOf3 :: forall t a b c. Typeable t => t a b c -> TypeRepSource

typeOf4 :: forall t a b c d. Typeable t => t a b c d -> TypeRepSource

typeOf5 :: forall t a b c d e. Typeable t => t a b c d e -> TypeRepSource

typeOf6 :: forall t a b c d e f. Typeable t => t a b c d e f -> TypeRepSource

typeOf7 :: forall t a b c d e f g. Typeable t => t a b c d e f g -> TypeRepSource

Type-safe cast

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

The type-safe cast operation

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

A flexible variation parameterised in a type constructor

Generalized casts for higher-order kinds

gcast1 :: forall c t t' a. (Typeable t, Typeable t') => c (t a) -> Maybe (c (t' a))Source

Cast over k1 -> k2

gcast2 :: forall c t t' a b. (Typeable t, Typeable t') => c (t a b) -> Maybe (c (t' a b))Source

Cast over k1 -> k2 -> k3

Type representations

data TypeRep Source

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

data TyCon Source

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

tyConString :: TyCon -> StringSource

Deprecated: renamed to tyConName; tyConModule and tyConPackage are also available.

Observe string encoding of a type representation

Construction of type representations

mkTyCon3Source

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

Applies a type constructor to a sequence of types

mkAppTy :: TypeRep -> TypeRep -> TypeRepSource

Adds a TypeRep argument to a TypeRep.

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

funResultTy :: TypeRep -> TypeRep -> Maybe TypeRepSource

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

Observe the type constructor of a type representation

typeRepArgs :: TypeRep -> [TypeRep]Source

Observe the argument types of a type representation

Type-level reasoning with Typeable