| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.OpenWitness.Typeable
Description
This is an approximate re-implementation of Data.Typeable using open witnesses.
- class Typeable a where
 - type Fun = (->)
 - cast :: forall a b. (Typeable a, Typeable b) => a -> Maybe b
 - gcast :: forall k a b c. (Typeable a, Typeable b) => c a -> Maybe (c b)
 - mkFunTy :: TypeRep a -> TypeRep b -> TypeRep (a -> b)
 - funResultTy :: TypeRep (a -> b) -> TypeRep a -> Maybe (TypeRep b)
 - mkAppTy :: forall k1 k2 f a. TypeRep f -> TypeRep a -> TypeRep (f a)
 
Documentation
class Typeable a where Source #
types of kind * with a representation
Minimal complete definition
Instances
| (Typeable (k1 -> k2) f, Typeable k1 a) => Typeable k2 (f a) Source # | |
| Typeable * Bool Source # | |
| Typeable * Char Source # | |
| Typeable * Int Source # | |
| Typeable * Type Source # | |
| Typeable * Constraint Source # | |
| Typeable * () Source # | |
| Typeable (* -> * -> *) (->) Source # | |
| Typeable (* -> * -> *) Either Source # | |
| Typeable (* -> * -> *) (,) Source # | |
| Typeable (* -> *) [] Source # | |
| Typeable (* -> *) Maybe Source # | |
| Typeable (k -> Constraint) (Typeable k) Source # | |
| Typeable (k -> *) (TypeRep k) Source # | |
mkFunTy :: TypeRep a -> TypeRep b -> TypeRep (a -> b) Source #
given representations of a and b, make a representation of a -> b