base-4.7.0.0: Basic libraries

Copyright(c) The University of Glasgow, CWI 2001--2011
LicenseBSD-style (see the file libraries/base/LICENSE)
Safe HaskellUnsafe
LanguageHaskell2010

Data.OldTypeable.Internal

Description

Deprecated: Use Data.Typeable.Internal instead

The representations of the types TyCon and TypeRep, and the function mkTyCon which is used by derived instances of Typeable to construct a TyCon.

Since: 4.7.0.0

Synopsis

Documentation

data TypeRepSource

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

Constructors

TypeRep !Fingerprint TyCon [TypeRep] 

data TyConSource

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

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.

typeRepTyCon :: TypeRep -> TyConSource

Observe the type constructor of a type representation

typeOfDefault :: forall t a. (Typeable1 t, Typeable a) => t a -> TypeRepSource

For defining a Typeable instance from any Typeable1 instance.

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

For defining a Typeable1 instance from any Typeable2 instance.

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

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

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

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

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

For defining a Typeable6 instance from any Typeable7 instance.

class Typeable a whereSource

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

Methods

typeOf :: a -> TypeRepSource

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.

class Typeable1 t whereSource

Variant for unary type constructors

Methods

typeOf1 :: t a -> TypeRepSource

Instances

class Typeable2 t whereSource

Variant for binary type constructors

Methods

typeOf2 :: t a b -> TypeRepSource

Instances

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

One Typeable2 instance for all Typeable3 instances

class Typeable3 t whereSource

Variant for 3-ary type constructors

Methods

typeOf3 :: t a b c -> TypeRepSource

Instances

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

One Typeable3 instance for all Typeable4 instances

class Typeable4 t whereSource

Variant for 4-ary type constructors

Methods

typeOf4 :: t a b c d -> TypeRepSource

Instances

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

One Typeable4 instance for all Typeable5 instances

class Typeable5 t whereSource

Variant for 5-ary type constructors

Methods

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

Instances

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

One Typeable5 instance for all Typeable6 instances

class Typeable6 t whereSource

Variant for 6-ary type constructors

Methods

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

Instances

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

One Typeable6 instance for all Typeable7 instances

class Typeable7 t whereSource

Variant for 7-ary type constructors

Methods

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

Instances

mkFunTy :: TypeRep -> TypeRep -> TypeRepSource

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

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.

typeRepArgs :: TypeRep -> [TypeRep]Source

Observe the argument types of a type representation

tyConString :: TyCon -> StringSource

Observe string encoding of a type representation