base-4.10.1.0: Basic libraries

Copyright(c) The University of Glasgow CWI 2001--2017
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilitynon-portable (requires GADTs and compiler support)
Safe HaskellTrustworthy
LanguageHaskell2010

Type.Reflection

Contents

Description

This provides a type-indexed type representation mechanism, similar to that described by,

  • Simon Peyton-Jones, Stephanie Weirich, Richard Eisenberg, Dimitrios Vytiniotis. "A reflection on types." /Proc. Philip Wadler's 60th birthday Festschrift/, Edinburgh (April 2016).

The interface provides TypeRep, a type representation which can be safely decomposed and composed. See Data.Dynamic for an example of this.

Since: 4.10.0.0

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#

withTypeable :: forall a r. TypeRep a -> (Typeable a => r) -> r #

Use a TypeRep as Typeable evidence.

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 representations

Type-Indexed

data TypeRep (a :: k) #

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

Instances

TestEquality k (TypeRep k) # 

Methods

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

Eq (TypeRep k a) #

Since: 2.1

Methods

(==) :: TypeRep k a -> TypeRep k a -> Bool Source #

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

Ord (TypeRep k a) #

Since: 4.4.0.0

Methods

compare :: TypeRep k a -> TypeRep k a -> Ordering Source #

(<) :: TypeRep k a -> TypeRep k a -> Bool Source #

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

(>) :: TypeRep k a -> TypeRep k a -> Bool Source #

(>=) :: TypeRep k a -> TypeRep k a -> Bool Source #

max :: TypeRep k a -> TypeRep k a -> TypeRep k a Source #

min :: TypeRep k a -> TypeRep k a -> TypeRep k a Source #

Show (TypeRep k a) # 

Methods

showsPrec :: Int -> TypeRep k a -> ShowS #

show :: TypeRep k a -> String #

showList :: [TypeRep k a] -> ShowS #

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

pattern App :: forall k2 (t :: k2). forall k1 (a :: k1 -> k2) (b :: k1). t ~ a b => TypeRep a -> TypeRep b -> TypeRep t #

A type application.

For instance, typeRep @(Maybe Int) === App (typeRep @Maybe) (typeRep @Int) Note that this will never match a function type (e.g. Int -> Char).

pattern Con :: forall k (a :: k). TyCon -> TypeRep a #

Pattern match on a type constructor

pattern Con' :: forall k (a :: k). TyCon -> [SomeTypeRep] -> TypeRep a #

Pattern match on a type constructor including its instantiated kind variables.

For instance, App (Con' proxyTyCon ks) intRep = typeRep (Proxy @Int) will bring into scope, proxyTyCon :: TyCon ks == [someTypeRep Type] :: [SomeTypeRep] intRep == typeRep Int @

pattern Fun :: forall k (fun :: k). forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (arg :: TYPE r1) (res :: TYPE r2). (k ~ Type, fun ~~ (arg -> res)) => TypeRep arg -> TypeRep res -> TypeRep fun #

The function type constructor.

For instance, typeRep @(Int -> Char) === Fun (typeRep @Int) (typeRep @Char)

typeRepTyCon :: TypeRep a -> TyCon #

Observe the type constructor of a type representation

rnfTypeRep :: TypeRep a -> () #

Helper to fully evaluate TypeRep for use as NFData(rnf) implementation

Since: 4.8.0.0

eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> Maybe (a :~~: b) #

Type equality

Since: 4.10

typeRepKind :: TypeRep (a :: k) -> TypeRep k #

Observe the kind of a type.

Quantified

someTypeRep :: forall proxy a. Typeable a => proxy a -> SomeTypeRep #

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

Since: 4.7.0.0

someTypeRepTyCon :: SomeTypeRep -> TyCon #

Observe the type constructor of a quantified type representation.

rnfSomeTypeRep :: SomeTypeRep -> () #

Helper to fully evaluate SomeTypeRep for use as NFData(rnf) implementation

Since: 4.10.0.0

Type constructors

data TyCon :: * Source #

Instances

rnfTyCon :: TyCon -> () #

Module names

data Module :: * Source #

Instances

Eq Module 
Show Module #

Since: 4.9.0.0

rnfModule :: Module -> () #

Helper to fully evaluate TyCon for use as NFData(rnf) implementation

Since: 4.8.0.0