Safe Haskell | None |
---|---|
Language | Haskell2010 |
Reify an Haskell value using type-directed normalisation-by-evaluation (NBE).
Synopsis
- data ReifyReflect repr meta a = ReifyReflect {}
- base :: ReifyReflect repr (repr a) a
- (-->) :: Abstractable repr => ReifyReflect repr m1 o1 -> ReifyReflect repr m2 o2 -> ReifyReflect repr (m1 -> m2) (o1 -> o2)
- reifyTH :: Name -> Q Exp
Documentation
data ReifyReflect repr meta a Source #
ReifyReflect
witnesses the duality between meta
and (repr a)
.
It indicates which type variables in a
are not to be instantiated
with the arrow type, and instantiates them to (repr _)
in meta
.
This is directly taken from: http://okmij.org/ftp/tagless-final/course/TDPE.hs
meta
instantiates polymorphic types of the original Haskell expression with(repr _)
types, according to howReifyReflect
is constructed usingbase
and(
. This is obviously not possible if the orignal expression uses monomorphic types (like-->
)Int
), but remains possible with constrained polymorphic types (like(Num i => i)
), because(i)
can still be inferred to(repr _)
, whereas the finally chosen(repr)
(eg.E
, orIdentity
, orCodeQ
, or ...) can have aNum
instance.(repr a)
is the symantic type as it would have been, had the expression been written with explicitlam
s instead of bare haskell functions. DOC: http://okmij.org/ftp/tagless-final/cookbook.html#TDPE DOC: http://okmij.org/ftp/tagless-final/NBE.html DOC: https://www.dicosmo.org/Articles/2004-BalatDiCosmoFiore-Popl.pdf
base :: ReifyReflect repr (repr a) a Source #
The base of induction : placeholder for a type which is not the arrow type.
(-->) :: Abstractable repr => ReifyReflect repr m1 o1 -> ReifyReflect repr m2 o2 -> ReifyReflect repr (m1 -> m2) (o1 -> o2) infixr 8 Source #
The inductive case : the arrow type.