open-typerep-0.5: Open type representations and dynamic types

Safe HaskellNone
LanguageHaskell2010

Data.TypeRep

Contents

Description

Open type representations and dynamic types

Synopsis

Helper types

module Data.Proxy

Type representations

class Typeable t a Source

This class provides reification of type a in a universe t. Typeable t a means that a is in the type universe represented by t.

Minimal complete definition

typeRep'

Instances

data TypeRep t a Source

Representation of type a in a type universe t

This type can also be seen as a witness that a is a member of t (i.e. Typeable t a); see witTypeable.

Instances

Render t => Show (TypeRep t a) Source 
Syntactic (TypeRep t a) Source 
type Internal (TypeRep t a) = a Source 
type Domain (TypeRep t a) = t Source 

typeRep :: Typeable t a => TypeRep t a Source

Reification of type a in a type universe t

class Render t => TypeEq t u Source

Equality on type representations

Minimal complete definition

typeEqSym

typeEqM :: (TypeEq t t, MonadError String m) => TypeRep t a -> TypeRep t b -> m (Dict (a ~ b)) Source

Equality on type representations

typeEq :: TypeEq t t => TypeRep t a -> TypeRep t b -> Maybe (Dict (a ~ b)) Source

Equality on type representations

matchCon :: TypeRep t c -> [E (TypeRep t)] Source

Type constructor matching. This function makes it possible to match on type representations without dealing with the underlying AST representation.

For example, to check that a TypeRep represents the type a -> Int for some a:

is_atoi :: (TypeEq t t, IntType :<: t) => TypeRep t a -> Bool
is_atoi t
    | [E ta, E tb] <- matchCon t
    , Just _       <- typeEq ta intType = True
    | otherwise                         = False

matchConM :: Monad m => TypeRep t c -> m [E (TypeRep t)] Source

Monadic version of matchCon

matchConM = return . matchCon

matchConM is convenient when matching types in a monad, e.g.:

do ...
   [E ta, E tb] <- matchConM t
   Dict         <- typeEq ta tb
   ...

class Witness p t u Source

Witness a type constraint for a reified type

Minimal complete definition

witSym

Instances

Witness Eq IntWordType t Source 
Witness Eq t t => Witness Eq ListType t Source 
Witness Eq DoubleType t Source 
Witness Eq FloatType t Source 
Witness Eq IntType t Source 
Witness Eq CharType t Source 
Witness Eq BoolType t Source 
Witness Eq t t => Witness Eq TupleType t Source 
Witness Integral IntWordType t Source 
Witness Integral IntType t Source 
Witness Num IntWordType t Source 
Witness Num DoubleType t Source 
Witness Num FloatType t Source 
Witness Num IntType t Source 
Witness Ord IntWordType t Source 
Witness Ord t t => Witness Ord ListType t Source 
Witness Ord DoubleType t Source 
Witness Ord FloatType t Source 
Witness Ord IntType t Source 
Witness Ord CharType t Source 
Witness Ord BoolType t Source 
Witness Ord t t => Witness Ord TupleType t Source 
Witness Show IntWordType t Source 
Witness Show t t => Witness Show ListType t Source 
Witness Show DoubleType t Source 
Witness Show FloatType t Source 
Witness Show IntType t Source 
Witness Show CharType t Source 
Witness Show BoolType t Source 
Witness Show t t => Witness Show TupleType t Source 
Witness Any IntWordType t Source 
Witness Any FunType t Source 
Witness Any ListType t Source 
Witness Any DoubleType t Source 
Witness Any FloatType t Source 
Witness Any IntType t Source 
Witness Any CharType t Source 
Witness Any BoolType t Source 
Witness Any TupleType t Source 
Witness p t t => Witness p (AST t) t Source 
(Witness p t1 t, Witness p t2 t) => Witness p ((:+:) t1 t2) t Source 
Witness (Typeable *) IntWordType t Source 
Witness (Typeable *) t t => Witness (Typeable *) FunType t Source 
Witness (Typeable *) t t => Witness (Typeable *) ListType t Source 
Witness (Typeable *) DoubleType t Source 
Witness (Typeable *) FloatType t Source 
Witness (Typeable *) IntType t Source 
Witness (Typeable *) CharType t Source 
Witness (Typeable *) BoolType t Source 
Witness (Typeable *) t t => Witness (Typeable *) TupleType t Source 

class (ShowClass p, Render t) => PWitness p t u Source

Partially witness a type constraint for a reified type

Instances

PWitness Eq IntWordType t Source 
PWitness Eq FunType t Source 
PWitness Eq t t => PWitness Eq ListType t Source 
PWitness Eq DoubleType t Source 
PWitness Eq FloatType t Source 
PWitness Eq IntType t Source 
PWitness Eq CharType t Source 
PWitness Eq BoolType t Source 
PWitness Eq t t => PWitness Eq TupleType t Source 
PWitness Integral IntWordType t Source 
PWitness Integral FunType t Source 
PWitness Integral ListType t Source 
PWitness Integral DoubleType t Source 
PWitness Integral FloatType t Source 
PWitness Integral IntType t Source 
PWitness Integral CharType t Source 
PWitness Integral BoolType t Source 
PWitness Integral TupleType t Source 
PWitness Num IntWordType t Source 
PWitness Num FunType t Source 
PWitness Num ListType t Source 
PWitness Num DoubleType t Source 
PWitness Num FloatType t Source 
PWitness Num IntType t Source 
PWitness Num CharType t Source 
PWitness Num BoolType t Source 
PWitness Num TupleType t Source 
PWitness Ord IntWordType t Source 
PWitness Ord FunType t Source 
PWitness Ord t t => PWitness Ord ListType t Source 
PWitness Ord DoubleType t Source 
PWitness Ord FloatType t Source 
PWitness Ord IntType t Source 
PWitness Ord CharType t Source 
PWitness Ord BoolType t Source 
PWitness Ord t t => PWitness Ord TupleType t Source 
PWitness Show IntWordType t Source 
PWitness Show FunType t Source 
PWitness Show t t => PWitness Show ListType t Source 
PWitness Show DoubleType t Source 
PWitness Show FloatType t Source 
PWitness Show IntType t Source 
PWitness Show CharType t Source 
PWitness Show BoolType t Source 
PWitness Show t t => PWitness Show TupleType t Source 
PWitness Any IntWordType t Source 
PWitness Any FunType t Source 
PWitness Any ListType t Source 
PWitness Any DoubleType t Source 
PWitness Any FloatType t Source 
PWitness Any IntType t Source 
PWitness Any CharType t Source 
PWitness Any BoolType t Source 
PWitness Any TupleType t Source 
(PWitness p t1 t, PWitness p t2 t) => PWitness p ((:+:) t1 t2) t Source 
PWitness (Typeable *) IntWordType t Source 
PWitness (Typeable *) t t => PWitness (Typeable *) FunType t Source 
PWitness (Typeable *) t t => PWitness (Typeable *) ListType t Source 
PWitness (Typeable *) DoubleType t Source 
PWitness (Typeable *) FloatType t Source 
PWitness (Typeable *) IntType t Source 
PWitness (Typeable *) CharType t Source 
PWitness (Typeable *) BoolType t Source 
PWitness (Typeable *) t t => PWitness (Typeable *) TupleType t Source 

wit :: forall p t a. Witness p t t => Proxy p -> TypeRep t a -> Dict (p a) Source

Witness a type constraint for a reified type

pwit :: forall p t m a. (PWitness p t t, MonadError String m) => Proxy p -> TypeRep t a -> m (Dict (p a)) Source

Partially witness a type constraint for a reified type

witTypeable :: Witness (Typeable t) t t => TypeRep t a -> Dict (Typeable t a) Source

Witness a Typeable constraint for a reified type

pwitTypeable :: PWitness (Typeable t) t t => TypeRep t a -> Either String (Dict (Typeable t a)) Source

Partially witness a Typeable constraint for a reified type

Dynamic types

cast :: forall t a b. (Typeable t a, Typeable t b, TypeEq t t) => Proxy t -> a -> Either String b Source

Safe cast (does not use unsafeCoerce)

gcast :: forall t a b c. (Typeable t a, Typeable t b, TypeEq t t) => Proxy t -> c a -> Either String (c b) Source

Safe generalized cast (does not use unsafeCoerce)

data Dynamic t where Source

Dynamic type parameterized on a type universe

Constructors

Dyn :: TypeRep t a -> a -> Dynamic t 

Instances

(TypeEq t t, Witness Eq t t) => Eq (Dynamic t) Source 
Witness Show t t => Show (Dynamic t) Source 

toDyn :: Typeable t a => a -> Dynamic t Source

fromDyn :: forall t a. (Typeable t a, TypeEq t t) => Dynamic t -> Either String a Source

Misc.

class ShowClass p where Source

Show the name of type classes

Methods

showClass :: Proxy p -> String Source

Show the name of a type class

pAny :: Proxy Any Source

Proxy of Any class. Can be passed to wit and pwit.

pDataTypeable :: Proxy Typeable Source

Proxy of Typeable class (from the base library). Can be passed to wit and pwit.

pEq :: Proxy Eq Source

Proxy of Eq class. Can be passed to wit and pwit.

pOrd :: Proxy Ord Source

Proxy of Ord class. Can be passed to wit and pwit.

pShow :: Proxy Show Source

Proxy of Show class. Can be passed to wit and pwit.

pNum :: Proxy Num Source

Proxy of Num class. Can be passed to wit and pwit.

pIntegral :: Proxy Integral Source

Proxy of Integral class. Can be passed to wit and pwit.

Sub-universes

class SubUniverse sub sup where Source

Sub-universe relation

In general, a universe t is a sub-universe of u if u has the form

t1 :+: t2 :+: ... :+: t

Methods

weakenUniverse :: TypeRep sub a -> TypeRep sup a Source

Cast a type representation to a larger universe

Instances

(SubUniverse sub sup', (~) (* -> *) sup ((:+:) t sup')) => SubUniverse sub sup Source 
SubUniverse t t Source