W3cubDocs

/Haskell 8

Data.Typeable

Copyright (c) The University of Glasgow CWI 2001--2004
License BSD-style (see the file libraries/base/LICENSE)
Maintainer [email protected]
Stability experimental
Portability portable
Safe Haskell Trustworthy
Language Haskell2010

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

The Typeable class

class Typeable (a :: k) Source

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

Minimal complete definition

typeRep#

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

Observe a type representation for the type of a value.

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: base-4.7.0.0

Propositional equality

data a :~: b where infix 4 Source

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: base-4.7.0.0

Constructors

Refl :: a :~: a
Instances
Instances details
Category ((:~:) :: k -> k -> Type)

Since: base-4.7.0.0

Instance details

Defined in Control.Category

Methods

id :: forall (a :: k0). a :~: a Source

(.) :: forall (b :: k0) (c :: k0) (a :: k0). (b :~: c) -> (a :~: b) -> a :~: c Source

TestEquality ((:~:) a :: k -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

testEquality :: forall (a0 :: k0) (b :: k0). (a :~: a0) -> (a :~: b) -> Maybe (a0 :~: b) Source

TestCoercion ((:~:) a :: k -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Coercion

Methods

testCoercion :: forall (a0 :: k0) (b :: k0). (a :~: a0) -> (a :~: b) -> Maybe (Coercion a0 b) Source

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

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

minBound :: a :~: b Source

maxBound :: a :~: b Source

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

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

succ :: (a :~: b) -> a :~: b Source

pred :: (a :~: b) -> a :~: b Source

toEnum :: Int -> a :~: b Source

fromEnum :: (a :~: b) -> Int Source

enumFrom :: (a :~: b) -> [a :~: b] Source

enumFromThen :: (a :~: b) -> (a :~: b) -> [a :~: b] Source

enumFromTo :: (a :~: b) -> (a :~: b) -> [a :~: b] Source

enumFromThenTo :: (a :~: b) -> (a :~: b) -> (a :~: b) -> [a :~: b] Source

Eq (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

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

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

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

Since: base-4.7.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: (a :~: b) -> Constr Source

dataTypeOf :: (a :~: b) -> DataType Source

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

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

gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~: b) -> a :~: b Source

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

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

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

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

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

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

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

Ord (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

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

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

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

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

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

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

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

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

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Show (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~: b) -> ShowS Source

show :: (a :~: b) -> String Source

showList :: [a :~: b] -> ShowS Source

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

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: base-4.10.0.0

Constructors

HRefl :: a :~~: a
Instances
Instances details
Category ((:~~:) :: k -> k -> Type)

Since: base-4.10.0.0

Instance details

Defined in Control.Category

Methods

id :: forall (a :: k0). a :~~: a Source

(.) :: forall (b :: k0) (c :: k0) (a :: k0). (b :~~: c) -> (a :~~: b) -> a :~~: c Source

TestEquality ((:~~:) a :: k -> Type)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

testEquality :: forall (a0 :: k0) (b :: k0). (a :~~: a0) -> (a :~~: b) -> Maybe (a0 :~: b) Source

TestCoercion ((:~~:) a :: k -> Type)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Coercion

Methods

testCoercion :: forall (a0 :: k0) (b :: k0). (a :~~: a0) -> (a :~~: b) -> Maybe (Coercion a0 b) Source

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

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

minBound :: a :~~: b Source

maxBound :: a :~~: b Source

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

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

succ :: (a :~~: b) -> a :~~: b Source

pred :: (a :~~: b) -> a :~~: b Source

toEnum :: Int -> a :~~: b Source

fromEnum :: (a :~~: b) -> Int Source

enumFrom :: (a :~~: b) -> [a :~~: b] Source

enumFromThen :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] Source

enumFromTo :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] Source

enumFromThenTo :: (a :~~: b) -> (a :~~: b) -> (a :~~: b) -> [a :~~: b] Source

Eq (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

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

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

(Typeable i, Typeable j, Typeable a, Typeable b, a ~~ b) => Data (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: (a :~~: b) -> Constr Source

dataTypeOf :: (a :~~: b) -> DataType Source

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

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

gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~~: b) -> a :~~: b Source

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

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

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

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

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

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

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

Ord (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

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

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

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

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

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

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

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

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

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

Show (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~~: b) -> ShowS Source

show :: (a :~~: b) -> String Source

showList :: [a :~~: b] -> ShowS Source

Type-safe cast

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

The type-safe cast operation

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

Extract a witness of equality of two types

Since: base-4.7.0.0

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

A canonical proxy type

data Proxy t Source

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy
Instances
Instances details
Generic1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type Source

Methods

from1 :: forall (a :: k0). Proxy a -> Rep1 Proxy a Source

to1 :: forall (a :: k0). Rep1 Proxy a -> Proxy a Source

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b Source

(>>) :: Proxy a -> Proxy b -> Proxy b Source

return :: a -> Proxy a Source

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b Source

(<$) :: a -> Proxy b -> Proxy a Source

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a Source

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

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c Source

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

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

Foldable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Proxy m -> m Source

foldMap :: Monoid m => (a -> m) -> Proxy a -> m Source

foldMap' :: Monoid m => (a -> m) -> Proxy a -> m Source

foldr :: (a -> b -> b) -> b -> Proxy a -> b Source

foldr' :: (a -> b -> b) -> b -> Proxy a -> b Source

foldl :: (b -> a -> b) -> b -> Proxy a -> b Source

foldl' :: (b -> a -> b) -> b -> Proxy a -> b Source

foldr1 :: (a -> a -> a) -> Proxy a -> a Source

foldl1 :: (a -> a -> a) -> Proxy a -> a Source

toList :: Proxy a -> [a] Source

null :: Proxy a -> Bool Source

length :: Proxy a -> Int Source

elem :: Eq a => a -> Proxy a -> Bool Source

maximum :: Ord a => Proxy a -> a Source

minimum :: Ord a => Proxy a -> a Source

sum :: Num a => Proxy a -> a Source

product :: Num a => Proxy a -> a Source

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) Source

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

sequence :: Monad m => Proxy (m a) -> m (Proxy a) Source

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a Source

mplus :: Proxy a -> Proxy a -> Proxy a Source

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a Source

(<|>) :: Proxy a -> Proxy a -> Proxy a Source

some :: Proxy a -> Proxy [a] Source

many :: Proxy a -> Proxy [a] Source

MonadZip (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Proxy a -> Proxy b -> Proxy (a, b) Source

mzipWith :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c Source

munzip :: Proxy (a, b) -> (Proxy a, Proxy b) Source

Show1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Read1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) Source

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] Source

Ord1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering Source

Eq1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool Source

Contravariant (Proxy :: Type -> Type)
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Proxy b -> Proxy a Source

(>$) :: b -> Proxy b -> Proxy a Source

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s Source

pred :: Proxy s -> Proxy s Source

toEnum :: Int -> Proxy s Source

fromEnum :: Proxy s -> Int Source

enumFrom :: Proxy s -> [Proxy s] Source

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] Source

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] Source

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] Source

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

Data t => Data (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Proxy t -> Constr Source

dataTypeOf :: Proxy t -> DataType Source

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

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

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

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

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

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

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

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

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

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

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

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

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

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

max :: Proxy s -> Proxy s -> Proxy s Source

min :: Proxy s -> Proxy s -> Proxy s Source

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS Source

show :: Proxy s -> String Source

showList :: [Proxy s] -> ShowS Source

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] Source

index :: (Proxy s, Proxy s) -> Proxy s -> Int Source

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

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool Source

rangeSize :: (Proxy s, Proxy s) -> Int Source

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

Generic (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type Source

Methods

from :: Proxy t -> Rep (Proxy t) x Source

to :: Rep (Proxy t) x -> Proxy t Source

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s Source

sconcat :: NonEmpty (Proxy s) -> Proxy s Source

stimes :: Integral b => b -> Proxy s -> Proxy s Source

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s Source

mappend :: Proxy s -> Proxy s -> Proxy s Source

mconcat :: [Proxy s] -> Proxy s Source

type Rep1 (Proxy :: k -> Type)
Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type Rep (Proxy t)
Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))

Type representations

type TypeRep = SomeTypeRep Source

A quantified type representation.

rnfTypeRep :: TypeRep -> () Source

Force a TypeRep to normal form.

showsTypeRep :: TypeRep -> ShowS Source

Show a type representation

mkFunTy :: TypeRep -> TypeRep -> TypeRep Source

Build a function type.

Observing type representations

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.

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

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

Observe the argument types of a type representation

typeRepTyCon :: TypeRep -> TyCon Source

Observe the type constructor of a quantified type representation.

typeRepFingerprint :: TypeRep -> Fingerprint Source

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

Since: base-4.7.0.0

Type constructors

data TyCon Source

Instances
Instances details
Eq TyCon
Instance details

Defined in GHC.Classes

Methods

(==) :: TyCon -> TyCon -> Bool Source

(/=) :: TyCon -> TyCon -> Bool Source

Ord TyCon
Instance details

Defined in GHC.Classes

Show TyCon

Since: base-2.1

Instance details

Defined in GHC.Show

tyConPackage :: TyCon -> String Source

tyConModule :: TyCon -> String Source

tyConName :: TyCon -> String Source

rnfTyCon :: TyCon -> () Source

tyConFingerprint :: TyCon -> Fingerprint Source

For backwards compatibility

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

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

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

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

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

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

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

© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/8.8.3/docs/html/libraries/base-4.13.0.0/Data-Typeable.html