base-4.12.0.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) Source #

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

Minimal complete definition

typeRep#

withTypeable :: forall k (a :: k) rep (r :: TYPE rep). TypeRep a -> (Typeable a => r) -> r Source #

Use a TypeRep as Typeable evidence.

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

Constructors

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

Since: 4.7.0.0

Instance details

Defined in Control.Category

Methods

id :: a :~: a Source #

(.) :: (b :~: c) -> (a :~: b) -> a :~: c Source #

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

Since: 4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

testEquality :: (a :~: a0) -> (a :~: b) -> Maybe (a0 :~: b) Source #

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

Since: 4.7.0.0

Instance details

Defined in Data.Type.Coercion

Methods

testCoercion :: (a :~: a0) -> (a :~: b) -> Maybe (Coercion a0 b) Source #

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

Since: 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) Source #

Since: 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) Source #

Since: 4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

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

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

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

Since: 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 :: (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) Source #

Since: 4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

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

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

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

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

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

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

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

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

Since: 4.7.0.0

Instance details

Defined in Data.Type.Equality

Show (a :~: b) Source #

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

Constructors

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

Since: 4.10.0.0

Instance details

Defined in Control.Category

Methods

id :: a :~~: a Source #

(.) :: (b :~~: c) -> (a :~~: b) -> a :~~: c Source #

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

Since: 4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

testEquality :: (a :~~: a0) -> (a :~~: b) -> Maybe (a0 :~: b) Source #

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

Since: 4.10.0.0

Instance details

Defined in Data.Type.Coercion

Methods

testCoercion :: (a :~~: a0) -> (a :~~: b) -> Maybe (Coercion a0 b) Source #

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

Since: 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) Source #

Since: 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) Source #

Since: 4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

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

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

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

Since: 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 :: (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) Source #

Since: 4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

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

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

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

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

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

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

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

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

Since: 4.10.0.0

Instance details

Defined in Data.Type.Equality

Show (a :~~: b) Source #

Since: 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 representations

Type-Indexed

data TypeRep (a :: k) Source #

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

Instances
TestEquality (TypeRep :: k -> Type) Source # 
Instance details

Defined in Data.Typeable.Internal

Methods

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

Eq (TypeRep a) Source #

Since: 2.1

Instance details

Defined in Data.Typeable.Internal

Methods

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

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

Ord (TypeRep a) Source #

Since: 4.4.0.0

Instance details

Defined in Data.Typeable.Internal

Methods

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

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

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

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

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

max :: TypeRep a -> TypeRep a -> TypeRep a #

min :: TypeRep a -> TypeRep a -> TypeRep a #

Show (TypeRep a) Source # 
Instance details

Defined in Data.Typeable.Internal

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

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

A type application.

For instance,

typeRep @(Maybe Int) === App (typeRep @Maybe) (typeRep @Int)

Note that this will also match a function type,

typeRep @(Int# -> Char)
  ===
App (App arrow (typeRep @Int#)) (typeRep @Char)

where arrow :: TypeRep ((->) :: TYPE IntRep -> Type -> Type).

pattern Con :: forall k (a :: k). () => IsApplication a ~ "" => TyCon -> TypeRep a Source #

Pattern match on a type constructor

pattern Con' :: forall k (a :: k). () => IsApplication a ~ "" => TyCon -> [SomeTypeRep] -> TypeRep a Source #

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

The function type constructor.

For instance,

typeRep @(Int -> Char) === Fun (typeRep @Int) (typeRep @Char)

typeRepTyCon :: TypeRep a -> TyCon Source #

Observe the type constructor of a type representation

rnfTypeRep :: TypeRep a -> () Source #

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

Type equality

Since: 4.10

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

Observe the kind of a type.

Quantified

data SomeTypeRep where Source #

A non-indexed type representation.

Constructors

SomeTypeRep :: forall k (a :: k). !(TypeRep a) -> SomeTypeRep 

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

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

Since: 4.7.0.0

someTypeRepTyCon :: SomeTypeRep -> TyCon Source #

Observe the type constructor of a quantified type representation.

rnfSomeTypeRep :: SomeTypeRep -> () Source #

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

Since: 4.10.0.0

Type constructors

data TyCon #

Instances
Eq TyCon 
Instance details

Defined in GHC.Classes

Methods

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

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

Ord TyCon 
Instance details

Defined in GHC.Classes

Methods

compare :: TyCon -> TyCon -> Ordering #

(<) :: TyCon -> TyCon -> Bool #

(<=) :: TyCon -> TyCon -> Bool #

(>) :: TyCon -> TyCon -> Bool #

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

max :: TyCon -> TyCon -> TyCon #

min :: TyCon -> TyCon -> TyCon #

Show TyCon Source #

Since: 2.1

Instance details

Defined in GHC.Show

Module names

data Module #

Instances
Eq Module 
Instance details

Defined in GHC.Classes

Methods

(==) :: Module -> Module -> Bool #

(/=) :: Module -> Module -> Bool #

Show Module Source #

Since: 4.9.0.0

Instance details

Defined in GHC.Show

rnfModule :: Module -> () Source #

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

Since: 4.8.0.0