| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Reflection
Synopsis
- class Reifies (s :: k) a | s -> a where
- reify :: a -> (forall s. Reifies s a => Proxy s -> r) -> r
- reifyNat :: Integer -> (forall (n :: Nat). KnownNat n => Proxy n -> r) -> r
- reifySymbol :: String -> (forall (n :: Symbol). KnownSymbol n => Proxy n -> r) -> r
- reifyTypeable :: Typeable a => a -> (forall s. (Typeable s, Reifies s a) => Proxy s -> r) -> r
Documentation
class Reifies (s :: k) a | s -> a where #
Minimal complete definition
Methods
Recover a value inside a reify context, given a proxy for its
reified type.
Instances
| KnownNat n => Reifies (n :: Nat) Integer | |
Defined in Data.Reflection | |
| KnownSymbol n => Reifies (n :: Symbol) String | |
Defined in Data.Reflection | |
| Reifies Z Int | |
Defined in Data.Reflection | |
| Reifies n Int => Reifies (D n :: *) Int | |
Defined in Data.Reflection | |
| Reifies n Int => Reifies (SD n :: *) Int | |
Defined in Data.Reflection | |
| Reifies n Int => Reifies (PD n :: *) Int | |
Defined in Data.Reflection | |
| (B b0, B b1, B b2, B b3, B b4, B b5, B b6, B b7, w0 ~ W b0 b1 b2 b3, w1 ~ W b4 b5 b6 b7) => Reifies (Stable w0 w1 a :: *) a | |
Defined in Data.Reflection | |
reify :: a -> (forall s. Reifies s a => Proxy s -> r) -> r #
Reify a value at the type level, to be recovered with reflect.
reifySymbol :: String -> (forall (n :: Symbol). KnownSymbol n => Proxy n -> r) -> r #
This upgraded version of reify can be used to generate a KnownSymbol suitable for use with other APIs.
Available only on GHC 7.8+
>>>reifySymbol "hello" symbolVal"hello"
>>>reifySymbol "hello" reflect"hello"