Safe Haskell | None |
---|---|
Language | Haskell2010 |
Open type representations and dynamic types
- module Data.Constraint
- module Data.Proxy
- module Language.Syntactic
- class Typeable t a
- data TypeRep t a
- typeRep :: Typeable t a => TypeRep t a
- class Render t => TypeEq t u
- typeEqM :: (TypeEq t t, MonadError String m) => TypeRep t a -> TypeRep t b -> m (Dict (a ~ b))
- typeEq :: TypeEq t t => TypeRep t a -> TypeRep t b -> Maybe (Dict (a ~ b))
- matchCon :: TypeRep t c -> [E (TypeRep t)]
- matchConM :: Monad m => TypeRep t c -> m [E (TypeRep t)]
- class Witness p t u
- class (ShowClass p, Render t) => PWitness p t u
- wit :: forall p t a. Witness p t t => Proxy p -> TypeRep t a -> Dict (p a)
- pwit :: forall p t m a. (PWitness p t t, MonadError String m) => Proxy p -> TypeRep t a -> m (Dict (p a))
- witTypeable :: Witness (Typeable t) t t => TypeRep t a -> Dict (Typeable t a)
- pwitTypeable :: PWitness (Typeable t) t t => TypeRep t a -> Either String (Dict (Typeable t a))
- cast :: forall t a b. (Typeable t a, Typeable t b, TypeEq t t) => Proxy t -> a -> Either String b
- gcast :: forall t a b c. (Typeable t a, Typeable t b, TypeEq t t) => Proxy t -> c a -> Either String (c b)
- data Dynamic t where
- toDyn :: Typeable t a => a -> Dynamic t
- fromDyn :: forall t a. (Typeable t a, TypeEq t t) => Dynamic t -> Either String a
- class Any a
- class ShowClass p where
- pAny :: Proxy Any
- pDataTypeable :: Proxy Typeable
- pEq :: Proxy Eq
- pOrd :: Proxy Ord
- pShow :: Proxy Show
- pNum :: Proxy Num
- pIntegral :: Proxy Integral
- class SubUniverse sub sup where
- weakenUniverse :: TypeRep sub a -> TypeRep sup a
Helper types
module Data.Constraint
module Data.Proxy
module Language.Syntactic
Type representations
This class provides reification of type a
in a universe t
.
means that Typeable
t aa
is in the type universe represented by t
.
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.
); see
Typeable
t awitTypeable
.
class Render t => TypeEq t u Source
Equality on type representations
TypeEq Empty t Source | |
TypeEq IntWordType t Source | |
TypeEq t t => TypeEq FunType t Source | |
TypeEq t t => TypeEq ListType t Source | |
TypeEq DoubleType t Source | |
TypeEq FloatType t Source | |
TypeEq IntType t Source | |
TypeEq CharType t Source | |
TypeEq BoolType t Source | |
TypeEq t t => TypeEq TupleType t Source | |
(TypeEq t1 t, TypeEq t2 t) => TypeEq ((:+:) t1 t2) t Source |
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
Witness a type constraint for a reified type
class (ShowClass p, Render t) => PWitness p t u Source
Partially witness a type constraint for a reified type
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
)
Dynamic type parameterized on a type universe
Misc.
The universal class
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
weakenUniverse :: TypeRep sub a -> TypeRep sup a Source
Cast a type representation to a larger universe
(SubUniverse sub sup', (~) (* -> *) sup ((:+:) t sup')) => SubUniverse sub sup Source | |
SubUniverse t t Source |