reflection-2.1.6: 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
KnownNat n => Reifies (n :: Nat) Integer Source # 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> Integer Source #

KnownSymbol n => Reifies (n :: Symbol) String Source # 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> String Source #

Reifies Z Int Source # 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy Z -> Int Source #

Reifies n Int => Reifies (PD n :: Type) Int Source # 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (PD n) -> Int Source #

Reifies n Int => Reifies (SD n :: Type) Int Source # 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (SD n) -> Int Source #

Reifies n Int => Reifies (D n :: Type) Int Source # 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (D n) -> Int Source #

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 :: Nat). 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.

Attemping to pass a negative Integer as an argument will result in an Underflow exception.

Available only on GHC 7.8+

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

reifySymbol :: forall r. String -> (forall (n :: Symbol). 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 #

0

Instances
Reifies Z Int Source # 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy Z -> Int Source #

data D (n :: *) Source #

2n

Instances
Reifies n Int => Reifies (D n :: Type) Int Source # 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (D n) -> Int Source #

data SD (n :: *) Source #

2n + 1

Instances
Reifies n Int => Reifies (SD n :: Type) Int Source # 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (SD n) -> Int Source #

data PD (n :: *) Source #

2n - 1

Instances
Reifies n Int => Reifies (PD n :: Type) Int Source # 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (PD n) -> Int Source #

Reified Monoids

data ReifiedMonoid a Source #

Constructors

ReifiedMonoid 

Fields

newtype ReflectedMonoid a s Source #

Constructors

ReflectedMonoid a 

reifyMonoid :: (a -> a -> a) -> a -> (forall (s :: *). Reifies s (ReifiedMonoid a) => t -> ReflectedMonoid a s) -> t -> a Source #

foldMapBy :: Foldable t => (r -> r -> r) -> r -> (a -> r) -> t a -> r Source #

Fold a value using its Foldable instance using explicitly provided Monoid operations. This is like foldMap where the Monoid instance can be manually specified.

foldMapBy mappend memptyfoldMap
>>> foldMapBy (+) 0 length ["hello","world"]
10

foldBy :: Foldable t => (a -> a -> a) -> a -> t a -> a Source #

Fold a value using its Foldable instance using explicitly provided Monoid operations. This is like fold where the Monoid instance can be manually specified.

foldBy mappend memptyfold
>>> foldBy (++) [] ["hello","world"]
"helloworld"

Reified Applicatives

data ReifiedApplicative f Source #

Constructors

ReifiedApplicative 

Fields

reifyApplicative :: (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (forall (s :: *). Reifies s (ReifiedApplicative f) => t -> ReflectedApplicative f s a) -> t -> f a Source #

traverseBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> t a -> f (t b) Source #

Traverse a container using its Traversable instance using explicitly provided Applicative operations. This is like traverse where the Applicative instance can be manually specified.

sequenceBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> t (f a) -> f (t a) Source #

Sequence a container using its Traversable instance using explicitly provided Applicative operations. This is like sequence where the Applicative instance can be manually specified.

Orphan instances

Num Exp Source #

This permits the use of $(5) as an expression splice, which stands for Proxy :: Proxy $(5)

Instance details

Methods

(+) :: Exp -> Exp -> Exp #

(-) :: Exp -> Exp -> Exp #

(*) :: Exp -> Exp -> Exp #

negate :: Exp -> Exp #

abs :: Exp -> Exp #

signum :: Exp -> Exp #

fromInteger :: Integer -> Exp #

Num Type Source #

This permits the use of $(5) as a type splice.

Instance details

Methods

(+) :: Type -> Type -> Type #

(-) :: Type -> Type -> Type #

(*) :: Type -> Type -> Type #

negate :: Type -> Type #

abs :: Type -> Type #

signum :: Type -> Type #

fromInteger :: Integer -> Type #

Fractional a => Fractional (Q a) Source # 
Instance details

Methods

(/) :: Q a -> Q a -> Q a #

recip :: Q a -> Q a #

fromRational :: Rational -> Q a #

Num a => Num (Q a) Source # 
Instance details

Methods

(+) :: Q a -> Q a -> Q a #

(-) :: Q a -> Q a -> Q a #

(*) :: Q a -> Q a -> Q a #

negate :: Q a -> Q a #

abs :: Q a -> Q a #

signum :: Q a -> Q a #

fromInteger :: Integer -> Q a #