reflection-2: Reifies arbitrary terms into types that can be reflected back into terms

Copyright2009-2015 Edward Kmett, 2012 Elliott Hird, 2004 Oleg Kiselyov and Chung-chieh Shan
LicenseBSD3
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell98

Data.Reflection

Contents

Description

Reifies arbitrary terms at the type level. Based on the Functional Pearl: Implicit Configurations paper by Oleg Kiselyov and Chung-chieh Shan.

http://okmij.org/ftp/Haskell/tr-15-04.pdf

The approach from the paper was modified to work with Data.Proxy and to cheat by using knowledge of GHC's internal representations by Edward Kmett and Elliott Hird.

Usage comes down to two combinators, reify and reflect.

>>> reify 6 (\p -> reflect p + reflect p)
12

The argument passed along by reify is just a data Proxy t = Proxy, so all of the information needed to reconstruct your value has been moved to the type level. This enables it to be used when constructing instances (see examples/Monoid.hs).

In addition, a simpler API is offered for working with singleton values such as a system configuration, etc.

Synopsis

Reflection

class Reifies s a | s -> a where Source

Methods

reflect :: proxy s -> a Source

Recover a value inside a reify context, given a proxy for its reified type.

Instances

reify :: forall a r. a -> (forall s. Reifies s a => Proxy s -> r) -> r Source

Reify a value at the type level, to be recovered with reflect.

reifyNat :: forall r. Integer -> (forall n. KnownNat n => Proxy n -> r) -> r Source

This upgraded version of reify can be used to generate a KnownNat suitable for use with other APIs.

Available only on GHC 7.8+

>>> reifyNat 4 natVal
4
>>> reifyNat 4 reflect
4

reifySymbol :: forall r. String -> (forall n. KnownSymbol n => Proxy n -> r) -> r Source

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"

reifyTypeable :: Typeable a => a -> (forall s. (Typeable s, Reifies s a) => Proxy s -> r) -> r Source

Reify a value at the type level in a Typeable-compatible fashion, to be recovered with reflect.

This can be necessary to work around the changes to Data.Typeable in GHC HEAD.

Given

class Given a where Source

This is a version of Reifies that allows for only a single value.

This is easier to work with than Reifies and permits extended defaulting, but it only offers a single reflected value of a given type at a time.

Methods

given :: a Source

Recover the value of a given type previously encoded with give.

give :: forall a r. a -> (Given a => r) -> r Source

Reify a value into an instance to be recovered with given.

You should only give a single value for each type. If multiple instances are in scope, then the behavior is implementation defined.

Template Haskell reflection

int :: Int -> TypeQ Source

This can be used to generate a template haskell splice for a type level version of a given int.

This does not use GHC TypeLits, instead it generates a numeric type by hand similar to the ones used in the "Functional Pearl: Implicit Configurations" paper by Oleg Kiselyov and Chung-Chieh Shan.

instance Num (Q Exp) provided in this package allows writing $(3) instead of $(int 3). Sometimes the two will produce the same representation (if compiled without the -DUSE_TYPE_LITS preprocessor directive).

nat :: Int -> TypeQ Source

This is a restricted version of int that can only generate natural numbers. Attempting to generate a negative number results in a compile time error. Also the resulting sequence will consist entirely of Z, D, and SD constructors representing the number in zeroless binary.

Useful compile time naturals

data Z Source

Instances

data D n Source

Instances

Reifies * n Int => Reifies * (D n) Int 

data SD n Source

Instances

Reifies * n Int => Reifies * (SD n) Int 

data PD n Source

Instances

Reifies * n Int => Reifies * (PD n) Int