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.Typeable.Internal

Description

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

Synopsis

Documentation

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 ★ s) 
Typeable (k → ★) (Proxy k) 
type Rep (Proxy k t) 

data TypeRep Source

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

Constructors

TypeRep !Fingerprint TyCon [TypeRep] 

typeOf ∷ ∀ a. Typeable a ⇒ a → TypeRep Source

typeOf1 ∷ ∀ t a. Typeable t ⇒ t a → TypeRep Source

typeOf2 ∷ ∀ t a b. Typeable t ⇒ t a b → TypeRep Source

typeOf3 ∷ ∀ t a b c. Typeable t ⇒ t a b c → TypeRep Source

typeOf4 ∷ ∀ t a b c d. Typeable t ⇒ t a b c d → TypeRep Source

typeOf5 ∷ ∀ t a b c d e. Typeable t ⇒ t a b c d e → TypeRep Source

typeOf6 ∷ ∀ t a b c d e f. Typeable t ⇒ t a b c d e f → TypeRep Source

typeOf7 ∷ ∀ t a b c d e f g. Typeable t ⇒ t a b c d e f g → TypeRep Source

type Typeable1 a = Typeable a Source

Deprecated: renamed to Typeable

type Typeable2 a = Typeable a Source

Deprecated: renamed to Typeable

type Typeable3 a = Typeable a Source

Deprecated: renamed to Typeable

type Typeable4 a = Typeable a Source

Deprecated: renamed to Typeable

type Typeable5 a = Typeable a Source

Deprecated: renamed to Typeable

type Typeable6 a = Typeable a Source

Deprecated: renamed to Typeable

type Typeable7 a = Typeable a Source

Deprecated: renamed to Typeable

data TyCon Source

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

Constructors

TyCon 

Fields

tyConHash ∷ !Fingerprint
 
tyConPackageString

Since: 4.5.0.0

tyConModuleString

Since: 4.5.0.0

tyConNameString

Since: 4.5.0.0

Instances

typeRep ∷ ∀ proxy a. Typeable a ⇒ proxy a → TypeRep Source

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

Since: 4.7.0.0

mkTyConWord#Word#StringStringStringTyCon Source

mkTyCon3 Source

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'

mkTyConAppTyCon → [TypeRep] → TypeRep Source

Applies a type constructor to a sequence of types

mkAppTyTypeRepTypeRepTypeRep Source

Adds a TypeRep argument to a TypeRep.

typeRepTyConTypeRepTyCon Source

Observe the type constructor of a type representation

class Typeable a where Source

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

Methods

typeRep#Proxy# a → TypeRep Source

Instances

TypeableBool 
TypeableChar 
TypeableDouble 
TypeableFloat 
TypeableInt 
TypeableInt8 
TypeableInt16 
TypeableInt32 
TypeableInt64 
TypeableInteger 
TypeableOrdering 
TypeableRealWorld 
TypeableWord 
TypeableWord8 
TypeableWord16 
TypeableWord32 
TypeableWord64 
Typeable ★ () 
TypeableSomeException 
TypeableTyCon 
TypeableTypeRep 
TypeableArithException 
TypeableErrorCall 
TypeableIOException 
TypeableDynamic 
TypeableCUIntMax 
TypeableCIntMax 
TypeableCUIntPtr 
TypeableCIntPtr 
TypeableCSUSeconds 
TypeableCUSeconds 
TypeableCTime 
TypeableCClock 
TypeableCSigAtomic 
TypeableCWchar 
TypeableCSize 
TypeableCPtrdiff 
TypeableCDouble 
TypeableCFloat 
TypeableCULLong 
TypeableCLLong 
TypeableCULong 
TypeableCLong 
TypeableCUInt 
TypeableCInt 
TypeableCUShort 
TypeableCShort 
TypeableCUChar 
TypeableCSChar 
TypeableCChar 
TypeableIntPtr 
TypeableWordPtr 
TypeableHandle 
TypeableExitCode 
TypeableArrayException 
TypeableAsyncException 
TypeableSomeAsyncException 
TypeableAssertionFailed 
TypeableDeadlock 
TypeableBlockedIndefinitelyOnSTM 
TypeableBlockedIndefinitelyOnMVar 
TypeableFd 
TypeableCRLim 
TypeableCTcflag 
TypeableCSpeed 
TypeableCCc 
TypeableCUid 
TypeableCNlink 
TypeableCGid 
TypeableCSsize 
TypeableCPid 
TypeableCOff 
TypeableCMode 
TypeableCIno 
TypeableCDev 
TypeableThreadId 
TypeableNestedAtomically 
TypeableNonTermination 
TypeableNoMethodError 
TypeableRecUpdError 
TypeableRecConError 
TypeableRecSelError 
TypeablePatternMatchFail 
TypeableQSemN 
TypeableVersion 
TypeableE12 
TypeableE9 
TypeableE6 
TypeableE3 
TypeableE2 
TypeableE1 
TypeableE0 
TypeableUnique 
TypeableSpecConstrAnnotation 
(Typeable (k1 → k) s, Typeable k1 a) ⇒ Typeable k (s a)

Kind-polymorphic Typeable instance for type application

Typeable ((★ → ★) → Constraint) Alternative 
Typeable ((★ → ★) → Constraint) Applicative 
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 (★ → Constraint) Monoid 
Typeable (k → k → ★) (Coercion k) 
Typeable (k → k → ★) ((:~:) k) 
Typeable (k → ★) (Proxy k) 

mkFunTyTypeRepTypeRepTypeRep Source

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

splitTyConAppTypeRep → (TyCon, [TypeRep]) Source

Splits a type constructor application

funResultTyTypeRepTypeRepMaybe TypeRep Source

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.

typeRepArgsTypeRep → [TypeRep] Source

Observe the argument types of a type representation

tyConStringTyConString Source

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

Observe string encoding of a type representation