base-4.10.1.0: Basic libraries

Copyright(c) The University of Glasgow CWI 2001--2004
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

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.

Compatibility Notes

Since GHC 8.2, GHC has supported type-indexed type representations. Data.Typeable provides type representations which are qualified over this index, providing an interface very similar to the Typeable notion seen in previous releases. For the type-indexed interface, see Type.Reflection.

Since GHC 7.8, Typeable is poly-kinded. The changes required for this might break some old programs involving Typeable. More details on this, including how to fix your code, can be found on the PolyTypeable wiki page

Synopsis

The Typeable class

class Typeable (a :: k) #

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

Minimal complete definition

typeRep#

typeOf :: forall a. Typeable a => a -> TypeRep #

Observe a type representation for the type of a value.

typeRep :: forall proxy a. Typeable a => proxy a -> TypeRep #

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

Since: 4.7.0.0

Propositional equality

data a :~: b where infix 4 #

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.

Since: 4.7.0.0

Constructors

Refl :: a :~: a 

Instances

Category k ((:~:) k) #

Since: 4.7.0.0

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

TestEquality k ((:~:) k a) #

Since: 4.7.0.0

Methods

testEquality :: f a -> f b -> Maybe (((k :~: a) :~: a) b) #

TestCoercion k ((:~:) k a) #

Since: 4.7.0.0

Methods

testCoercion :: f a -> f b -> Maybe (Coercion (k :~: a) a b) #

(~) k a b => Bounded ((:~:) k a b) #

Since: 4.7.0.0

Methods

minBound :: (k :~: a) b #

maxBound :: (k :~: a) b #

(~) k a b => Enum ((:~:) k a b) #

Since: 4.7.0.0

Methods

succ :: (k :~: a) b -> (k :~: a) b #

pred :: (k :~: a) b -> (k :~: a) b #

toEnum :: Int -> (k :~: a) b #

fromEnum :: (k :~: a) b -> Int #

enumFrom :: (k :~: a) b -> [(k :~: a) b] #

enumFromThen :: (k :~: a) b -> (k :~: a) b -> [(k :~: a) b] #

enumFromTo :: (k :~: a) b -> (k :~: a) b -> [(k :~: a) b] #

enumFromThenTo :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b -> [(k :~: a) b] #

Eq ((:~:) k a b) # 

Methods

(==) :: (k :~: a) b -> (k :~: a) b -> Bool Source #

(/=) :: (k :~: a) b -> (k :~: a) b -> Bool Source #

((~) * a b, Data a) => Data ((:~:) * a b) #

Since: 4.7.0.0

Methods

gfoldl :: (forall d c. Data d => c (d -> c) -> d -> c c) -> (forall g. g -> c g) -> (* :~: a) b -> c ((* :~: a) b) #

gunfold :: (forall c r. Data c => c (c -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((* :~: a) b) #

toConstr :: (* :~: a) b -> Constr #

dataTypeOf :: (* :~: a) b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ((* :~: a) b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((* :~: a) b)) #

gmapT :: (forall c. Data c => c -> c) -> (* :~: a) b -> (* :~: a) b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (* :~: a) b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (* :~: a) b -> r #

gmapQ :: (forall d. Data d => d -> u) -> (* :~: a) b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> (* :~: a) b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (* :~: a) b -> m ((* :~: a) b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (* :~: a) b -> m ((* :~: a) b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (* :~: a) b -> m ((* :~: a) b) #

Ord ((:~:) k a b) # 

Methods

compare :: (k :~: a) b -> (k :~: a) b -> Ordering Source #

(<) :: (k :~: a) b -> (k :~: a) b -> Bool Source #

(<=) :: (k :~: a) b -> (k :~: a) b -> Bool Source #

(>) :: (k :~: a) b -> (k :~: a) b -> Bool Source #

(>=) :: (k :~: a) b -> (k :~: a) b -> Bool Source #

max :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b Source #

min :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b Source #

(~) k a b => Read ((:~:) k a b) #

Since: 4.7.0.0

Methods

readsPrec :: Int -> ReadS ((k :~: a) b) #

readList :: ReadS [(k :~: a) b] #

readPrec :: ReadPrec ((k :~: a) b) #

readListPrec :: ReadPrec [(k :~: a) b] #

Show ((:~:) k a b) # 

Methods

showsPrec :: Int -> (k :~: a) b -> ShowS #

show :: (k :~: a) b -> String #

showList :: [(k :~: a) b] -> ShowS #

data (a :: k1) :~~: (b :: k2) where infix 4 #

Kind heterogeneous propositional equality. Like '(:~:)', a :~~: b is inhabited by a terminating value if and only if a is the same type as b.

Since: 4.10.0.0

Constructors

HRefl :: a :~~: a 

Instances

Category k ((:~~:) k k) #

Since: 4.10.0.0

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

TestEquality k ((:~~:) k1 k a) #

Since: 4.10.0.0

Methods

testEquality :: f a -> f b -> Maybe (((k1 :~~: k) a :~: a) b) #

TestCoercion k ((:~~:) k1 k a) #

Since: 4.10.0.0

Methods

testCoercion :: f a -> f b -> Maybe (Coercion ((k1 :~~: k) a) a b) #

(~~) k1 k2 a b => Bounded ((:~~:) k1 k2 a b) #

Since: 4.10.0.0

Methods

minBound :: (k1 :~~: k2) a b #

maxBound :: (k1 :~~: k2) a b #

(~~) k1 k2 a b => Enum ((:~~:) k1 k2 a b) #

Since: 4.10.0.0

Methods

succ :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b #

pred :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b #

toEnum :: Int -> (k1 :~~: k2) a b #

fromEnum :: (k1 :~~: k2) a b -> Int #

enumFrom :: (k1 :~~: k2) a b -> [(k1 :~~: k2) a b] #

enumFromThen :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> [(k1 :~~: k2) a b] #

enumFromTo :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> [(k1 :~~: k2) a b] #

enumFromThenTo :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> [(k1 :~~: k2) a b] #

Eq ((:~~:) k1 k2 a b) #

Since: 4.10.0.0

Methods

(==) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool Source #

(/=) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool Source #

(Typeable * i2, Typeable * j2, Typeable i2 a, Typeable j2 b, (~~) i2 j2 a b) => Data ((:~~:) i2 j2 a b) #

Since: 4.10.0.0

Methods

gfoldl :: (forall d c. Data d => c (d -> c) -> d -> c c) -> (forall g. g -> c g) -> (i2 :~~: j2) a b -> c ((i2 :~~: j2) a b) #

gunfold :: (forall c r. Data c => c (c -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ((i2 :~~: j2) a b) #

toConstr :: (i2 :~~: j2) a b -> Constr #

dataTypeOf :: (i2 :~~: j2) a b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ((i2 :~~: j2) a b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ((i2 :~~: j2) a b)) #

gmapT :: (forall c. Data c => c -> c) -> (i2 :~~: j2) a b -> (i2 :~~: j2) a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (i2 :~~: j2) a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (i2 :~~: j2) a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> (i2 :~~: j2) a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> (i2 :~~: j2) a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (i2 :~~: j2) a b -> m ((i2 :~~: j2) a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (i2 :~~: j2) a b -> m ((i2 :~~: j2) a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (i2 :~~: j2) a b -> m ((i2 :~~: j2) a b) #

Ord ((:~~:) k1 k2 a b) #

Since: 4.10.0.0

Methods

compare :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Ordering Source #

(<) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool Source #

(<=) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool Source #

(>) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool Source #

(>=) :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> Bool Source #

max :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> (k1 :~~: k2) a b Source #

min :: (k1 :~~: k2) a b -> (k1 :~~: k2) a b -> (k1 :~~: k2) a b Source #

(~~) k1 k2 a b => Read ((:~~:) k1 k2 a b) #

Since: 4.10.0.0

Methods

readsPrec :: Int -> ReadS ((k1 :~~: k2) a b) #

readList :: ReadS [(k1 :~~: k2) a b] #

readPrec :: ReadPrec ((k1 :~~: k2) a b) #

readListPrec :: ReadPrec [(k1 :~~: k2) a b] #

Show ((:~~:) k1 k2 a b) #

Since: 4.10.0.0

Methods

showsPrec :: Int -> (k1 :~~: k2) a b -> ShowS #

show :: (k1 :~~: k2) a b -> String #

showList :: [(k1 :~~: k2) a b] -> ShowS #

Type-safe cast

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

The type-safe cast operation

eqT :: forall a b. (Typeable a, Typeable b) => Maybe (a :~: b) #

Extract a witness of equality of two types

Since: 4.7.0.0

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

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)) #

Cast over k1 -> k2

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

Cast over k1 -> k2 -> k3

A canonical proxy type

data Proxy t #

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Generic1 k (Proxy k) # 

Associated Types

type Rep1 (Proxy k) (f :: Proxy k -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Proxy k) f a #

to1 :: Rep1 (Proxy k) f a -> f a #

Monad (Proxy *) #

Since: 4.7.0.0

Methods

(>>=) :: Proxy * a -> (a -> Proxy * b) -> Proxy * b #

(>>) :: Proxy * a -> Proxy * b -> Proxy * b #

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Functor (Proxy *) #

Since: 4.7.0.0

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b #

(<$) :: a -> Proxy * b -> Proxy * a #

Applicative (Proxy *) #

Since: 4.7.0.0

Methods

pure :: a -> Proxy * a #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b #

liftA2 :: (a -> b -> c) -> Proxy * a -> Proxy * b -> Proxy * c #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a #

Foldable (Proxy *) #

Since: 4.7.0.0

Methods

fold :: Monoid m => Proxy * m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy * a -> m #

foldr :: (a -> b -> b) -> b -> Proxy * a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy * a -> b #

foldl :: (b -> a -> b) -> b -> Proxy * a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy * a -> b #

foldr1 :: (a -> a -> a) -> Proxy * a -> a #

foldl1 :: (a -> a -> a) -> Proxy * a -> a #

toList :: Proxy * a -> [a] #

null :: Proxy * a -> Bool #

length :: Proxy * a -> Int #

elem :: Eq a => a -> Proxy * a -> Bool #

maximum :: Ord a => Proxy * a -> a #

minimum :: Ord a => Proxy * a -> a #

sum :: Num a => Proxy * a -> a #

product :: Num a => Proxy * a -> a #

Traversable (Proxy *) #

Since: 4.7.0.0

Methods

traverse :: Applicative f => (a -> f b) -> Proxy * a -> f (Proxy * b) #

sequenceA :: Applicative f => Proxy * (f a) -> f (Proxy * a) #

mapM :: Monad m => (a -> m b) -> Proxy * a -> m (Proxy * b) #

sequence :: Monad m => Proxy * (m a) -> m (Proxy * a) #

MonadPlus (Proxy *) #

Since: 4.9.0.0

Methods

mzero :: Proxy * a #

mplus :: Proxy * a -> Proxy * a -> Proxy * a #

Alternative (Proxy *) #

Since: 4.9.0.0

Methods

empty :: Proxy * a #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a #

some :: Proxy * a -> Proxy * [a] #

many :: Proxy * a -> Proxy * [a] #

MonadZip (Proxy *) #

Since: 4.9.0.0

Methods

mzip :: Proxy * a -> Proxy * b -> Proxy * (a, b) #

mzipWith :: (a -> b -> c) -> Proxy * a -> Proxy * b -> Proxy * c #

munzip :: Proxy * (a, b) -> (Proxy * a, Proxy * b) #

Show1 (Proxy *) #

Since: 4.9.0.0

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy * a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy * a] -> ShowS #

Read1 (Proxy *) #

Since: 4.9.0.0

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy * a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy * a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy * a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy * a] #

Ord1 (Proxy *) #

Since: 4.9.0.0

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy * a -> Proxy * b -> Ordering #

Eq1 (Proxy *) #

Since: 4.9.0.0

Methods

liftEq :: (a -> b -> Bool) -> Proxy * a -> Proxy * b -> Bool #

Bounded (Proxy k t) # 

Methods

minBound :: Proxy k t #

maxBound :: Proxy k t #

Enum (Proxy k s) #

Since: 4.7.0.0

Methods

succ :: Proxy k s -> Proxy k s #

pred :: Proxy k s -> Proxy k s #

toEnum :: Int -> Proxy k s #

fromEnum :: Proxy k s -> Int #

enumFrom :: Proxy k s -> [Proxy k s] #

enumFromThen :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromTo :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromThenTo :: Proxy k s -> Proxy k s -> Proxy k s -> [Proxy k s] #

Eq (Proxy k s) #

Since: 4.7.0.0

Methods

(==) :: Proxy k s -> Proxy k s -> Bool Source #

(/=) :: Proxy k s -> Proxy k s -> Bool Source #

Data t => Data (Proxy * t) #

Since: 4.7.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy * t -> c (Proxy * t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy * t) #

toConstr :: Proxy * t -> Constr #

dataTypeOf :: Proxy * t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Proxy * t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Proxy * t)) #

gmapT :: (forall b. Data b => b -> b) -> Proxy * t -> Proxy * t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy * t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy * t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Proxy * t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy * t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy * t -> m (Proxy * t) #

Ord (Proxy k s) #

Since: 4.7.0.0

Methods

compare :: Proxy k s -> Proxy k s -> Ordering Source #

(<) :: Proxy k s -> Proxy k s -> Bool Source #

(<=) :: Proxy k s -> Proxy k s -> Bool Source #

(>) :: Proxy k s -> Proxy k s -> Bool Source #

(>=) :: Proxy k s -> Proxy k s -> Bool Source #

max :: Proxy k s -> Proxy k s -> Proxy k s Source #

min :: Proxy k s -> Proxy k s -> Proxy k s Source #

Read (Proxy k s) #

Since: 4.7.0.0

Show (Proxy k s) #

Since: 4.7.0.0

Methods

showsPrec :: Int -> Proxy k s -> ShowS #

show :: Proxy k s -> String #

showList :: [Proxy k s] -> ShowS #

Ix (Proxy k s) #

Since: 4.7.0.0

Methods

range :: (Proxy k s, Proxy k s) -> [Proxy k s] #

index :: (Proxy k s, Proxy k s) -> Proxy k s -> Int #

unsafeIndex :: (Proxy k s, Proxy k s) -> Proxy k s -> Int

inRange :: (Proxy k s, Proxy k s) -> Proxy k s -> Bool #

rangeSize :: (Proxy k s, Proxy k s) -> Int #

unsafeRangeSize :: (Proxy k s, Proxy k s) -> Int

Generic (Proxy k t) # 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Semigroup (Proxy k s) #

Since: 4.9.0.0

Methods

(<>) :: Proxy k s -> Proxy k s -> Proxy k s #

sconcat :: NonEmpty (Proxy k s) -> Proxy k s #

stimes :: Integral b => b -> Proxy k s -> Proxy k s #

Monoid (Proxy k s) #

Since: 4.7.0.0

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

type Rep1 k (Proxy k) # 
type Rep1 k (Proxy k) = D1 k (MetaData "Proxy" "Data.Proxy" "base" False) (C1 k (MetaCons "Proxy" PrefixI False) (U1 k))
type Rep (Proxy k t) # 
type Rep (Proxy k t) = D1 * (MetaData "Proxy" "Data.Proxy" "base" False) (C1 * (MetaCons "Proxy" PrefixI False) (U1 *))

Type representations

type TypeRep = SomeTypeRep #

A quantified type representation.

rnfTypeRep :: TypeRep -> () #

Force a TypeRep to normal form.

showsTypeRep :: TypeRep -> ShowS #

Show a type representation

mkFunTy :: TypeRep -> TypeRep -> TypeRep #

Build a function type.

Observing type representations

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.

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

Splits a type constructor application. Note that if the type constructor is polymorphic, this will not return the kinds that were used.

typeRepArgs :: TypeRep -> [TypeRep] #

Observe the argument types of a type representation

typeRepTyCon :: TypeRep -> TyCon #

Observe the type constructor of a quantified type representation.

typeRepFingerprint :: TypeRep -> Fingerprint #

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

Since: 4.7.0.0

Type constructors

data TyCon :: * Source #

Instances

rnfTyCon :: TyCon -> () #

For backwards compatibility

typeOf1 :: forall t (a :: *). Typeable t => t a -> TypeRep #

typeOf2 :: forall t (a :: *) (b :: *). Typeable t => t a b -> TypeRep #

typeOf3 :: forall t (a :: *) (b :: *) (c :: *). Typeable t => t a b c -> TypeRep #

typeOf4 :: forall t (a :: *) (b :: *) (c :: *) (d :: *). Typeable t => t a b c d -> TypeRep #

typeOf5 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *). Typeable t => t a b c d e -> TypeRep #

typeOf6 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *). Typeable t => t a b c d e f -> TypeRep #

typeOf7 :: forall t (a :: *) (b :: *) (c :: *) (d :: *) (e :: *) (f :: *) (g :: *). Typeable t => t a b c d e f g -> TypeRep #

type Typeable1 (a :: * -> *) = Typeable a #

Deprecated: renamed to Typeable

type Typeable2 (a :: * -> * -> *) = Typeable a #

Deprecated: renamed to Typeable

type Typeable3 (a :: * -> * -> * -> *) = Typeable a #

Deprecated: renamed to Typeable

type Typeable4 (a :: * -> * -> * -> * -> *) = Typeable a #

Deprecated: renamed to Typeable

type Typeable5 (a :: * -> * -> * -> * -> * -> *) = Typeable a #

Deprecated: renamed to Typeable

type Typeable6 (a :: * -> * -> * -> * -> * -> * -> *) = Typeable a #

Deprecated: renamed to Typeable

type Typeable7 (a :: * -> * -> * -> * -> * -> * -> * -> *) = Typeable a #

Deprecated: renamed to Typeable