base-4.8.0.0: Basic libraries

Copyright(c) The University of Glasgow, CWI 2001--2011
LicenseBSD-style (see the file libraries/base/LICENSE)
Safe HaskellTrustworthy
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 k 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 :: forall a. Typeable a => a -> TypeRep Source

typeOf1 :: forall t a. Typeable t => t a -> TypeRep Source

typeOf2 :: forall t a b. Typeable t => t a b -> TypeRep Source

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

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

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

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

typeOf7 :: forall 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
 
tyConPackage :: String

Since: 4.5.0.0

tyConModule :: String

Since: 4.5.0.0

tyConName :: String

Since: 4.5.0.0

typeRep :: forall 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

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'

mkTyConApp :: TyCon -> [TypeRep] -> TypeRep Source

Applies a type constructor to a sequence of types

mkAppTy :: TypeRep -> TypeRep -> TypeRep Source

Adds a TypeRep argument to a TypeRep.

typeRepTyCon :: TypeRep -> TyCon 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

Typeable Bool False 
Typeable Bool True 
Typeable Ordering LT 
Typeable Ordering EQ 
Typeable Ordering GT 
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 * Number 
Typeable * Lexeme 
Typeable * Fingerprint 
Typeable * TyCon 
Typeable * TypeRep 
Typeable * Any 
Typeable * All 
Typeable * CUIntMax 
Typeable * CIntMax 
Typeable * CUIntPtr 
Typeable * CIntPtr 
Typeable * CJmpBuf 
Typeable * CFpos 
Typeable * CFile 
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 * ArithException 
Typeable * ErrorCall 
Typeable * IOException 
Typeable * Dynamic 
Typeable * IntPtr 
Typeable * WordPtr 
Typeable * NewlineMode 
Typeable * Newline 
Typeable * BufferMode 
Typeable * Handle 
Typeable * IOErrorType 
Typeable * ExitCode 
Typeable * ArrayException 
Typeable * AsyncException 
Typeable * SomeAsyncException 
Typeable * AssertionFailed 
Typeable * AllocationLimitExceeded 
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 * Version 
Typeable * Fixity 
Typeable * ConstrRep 
Typeable * DataRep 
Typeable * Constr 
Typeable * DataType 
Typeable * Natural 
Typeable * SpecConstrAnnotation 
Typeable * StaticPtrInfo 
Typeable * QSem 
Typeable * QSemN 
Typeable * E12 
Typeable * E9 
Typeable * E6 
Typeable * E3 
Typeable * E2 
Typeable * E1 
Typeable * E0 
Typeable * Unique 
Typeable * Void 
KnownNat n => Typeable Nat n 
KnownSymbol s => Typeable Symbol s 
Typeable () () 
Typeable ArithException Overflow 
Typeable ArithException Underflow 
Typeable ArithException LossOfPrecision 
Typeable ArithException DivideByZero 
Typeable ArithException Denormal 
Typeable ArithException RatioZeroDenominator 
Typeable Newline LF 
Typeable Newline CRLF 
Typeable AsyncException StackOverflow 
Typeable AsyncException HeapOverflow 
Typeable AsyncException ThreadKilled 
Typeable AsyncException UserInterrupt 
Typeable AllocationLimitExceeded AllocationLimitExceeded 
Typeable Deadlock Deadlock 
Typeable BlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM 
Typeable BlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar 
Typeable NestedAtomically NestedAtomically 
Typeable NonTermination NonTermination 
Typeable Fixity Prefix 
Typeable Fixity Infix 
Typeable SpecConstrAnnotation NoSpecConstr 
Typeable SpecConstrAnnotation ForceSpecConstr 
(Typeable (k1 -> k) s, Typeable k1 a) => Typeable k (s a)

Kind-polymorphic Typeable instance for type application

Typeable [a] ([] a) 
Typeable (Maybe a) (Nothing a) 
Typeable (KProxy t) (KProxy t) 
Typeable (Bool -> Any) Any 
Typeable (Bool -> All) All 
Typeable ((* -> * -> *) -> * -> * -> *) WrappedArrow 
Typeable ((* -> *) -> * -> *) WrappedMonad 
Typeable ((* -> *) -> Constraint) Monad 
Typeable ((* -> *) -> Constraint) Functor 
Typeable ((* -> *) -> Constraint) Applicative 
Typeable ((* -> *) -> Constraint) MonadPlus 
Typeable ((* -> *) -> Constraint) Alternative 
Typeable (* -> * -> * -> * -> * -> * -> * -> *) (,,,,,,) 
Typeable (* -> * -> * -> * -> * -> * -> *) (,,,,,) 
Typeable (* -> * -> * -> * -> * -> *) (,,,,) 
Typeable (* -> * -> * -> * -> *) (,,,) 
Typeable (* -> * -> * -> *) (,,) 
Typeable (* -> * -> *) (->) 
Typeable (* -> * -> *) Either 
Typeable (* -> * -> *) (,) 
Typeable (* -> * -> *) ST 
Typeable (* -> * -> *) STRef 
Typeable (* -> * -> *) Const 
Typeable (* -> *) [] 
Typeable (* -> *) Ratio 
Typeable (* -> *) StablePtr 
Typeable (* -> *) IO 
Typeable (* -> *) Ptr 
Typeable (* -> *) FunPtr 
Typeable (* -> *) StaticPtr 
Typeable (* -> *) Maybe 
Typeable (* -> *) ReadP 
Typeable (* -> *) ReadPrec 
Typeable (* -> *) KProxy 
Typeable (* -> *) Last 
Typeable (* -> *) First 
Typeable (* -> *) Product 
Typeable (* -> *) Sum 
Typeable (* -> *) Endo 
Typeable (* -> *) Dual 
Typeable (* -> *) MVar 
Typeable (* -> *) Weak 
Typeable (* -> *) IORef 
Typeable (* -> *) ForeignPtr 
Typeable (* -> *) TVar 
Typeable (* -> *) STM 
Typeable (* -> *) ZipList 
Typeable (* -> *) Chan 
Typeable (* -> *) Complex 
Typeable (* -> *) Fixed 
Typeable (* -> *) Identity 
Typeable (* -> *) StableName 
Typeable (* -> Constraint) IsList 
Typeable (* -> Constraint) Bounded 
Typeable (* -> Constraint) Enum 
Typeable (* -> Constraint) Eq 
Typeable (* -> Constraint) Floating 
Typeable (* -> Constraint) Fractional 
Typeable (* -> Constraint) Integral 
Typeable (* -> Constraint) Data 
Typeable (* -> Constraint) Num 
Typeable (* -> Constraint) Ord 
Typeable (* -> Constraint) Read 
Typeable (* -> Constraint) Real 
Typeable (* -> Constraint) RealFloat 
Typeable (* -> Constraint) RealFrac 
Typeable (* -> Constraint) Show 
Typeable (* -> Constraint) Ix 
Typeable (* -> Constraint) Monoid 
Typeable (* -> Constraint) FiniteBits 
Typeable (* -> Constraint) Bits 
Typeable (* -> Constraint) HasResolution 
Typeable (Newline -> Newline -> NewlineMode) NewlineMode 
Typeable ((k -> *) -> Constraint) (TestCoercion k) 
Typeable ((k -> *) -> Constraint) (TestEquality k) 
Typeable ((a -> a) -> Endo a) (Endo a) 
Typeable ((k -> *) -> k -> *) (Alt k) 
Typeable ([a] -> ZipList a) (ZipList a) 
Typeable (k -> Constraint) (Typeable k) 
Typeable (k -> k -> Constraint) (Coercible k) 
Typeable (k -> k -> Constraint) ((~) k) 
Typeable (k -> k -> *) (Coercion k) 
Typeable (k -> k -> *) ((:~:) k) 
Typeable (k -> *) (Proxy k) 
Typeable (a -> Maybe a) (Just a) 
Typeable (a -> [a] -> [a]) ((:) a) 
Typeable (a -> Dual a) (Dual a) 
Typeable (a -> Sum a) (Sum a) 
Typeable (a -> Product a) (Product a) 
Typeable (a -> a -> Complex a) ((:+) a) 
Typeable (a -> Identity a) (Identity a) 
Typeable (Maybe a -> First a) (First a) 
Typeable (Maybe a -> Last a) (Last a) 
Typeable (a -> b -> (,) a b) ((,) a b) 
Typeable (a -> Either a b) (Left a b) 
Typeable (b -> Either a b) (Right a b) 
Typeable (a -> Const a b) (Const a b) 
Typeable (a -> b -> c -> (,,) a b c) ((,,) a b c) 
Typeable (a -> b -> c -> d -> (,,,) a b c d) ((,,,) a b c d) 
Typeable (a -> b -> c -> d -> e -> (,,,,) a b c d e) ((,,,,) a b c d e) 
Typeable (a -> b -> c -> d -> e -> f -> (,,,,,) a b c d e f) ((,,,,,) a b c d e f) 
Typeable (a -> b -> c -> d -> e -> f -> g -> (,,,,,,) a b c d e f g) ((,,,,,,) a b c d e f g) 

mkFunTy :: TypeRep -> TypeRep -> TypeRep Source

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

typeRepArgs :: TypeRep -> [TypeRep] Source

Observe the argument types of a type representation

tyConString :: TyCon -> String Source

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

Observe string encoding of a type representation