[[project @ 2002-11-09 09:31:36 by chak] chak**20021109093137 Some documentation covering the extra desugaring that is needed for Template Haskell. ] { addfile ./ghc/docs/comm/exts/th.html hunk ./ghc/docs/comm/exts/th.html 1 + + +
+ ++ The Template Haskell (TH) extension to GHC adds a meta-programming + facility in which all meta-level code is executed at compile time. The + design of this extension is detailed in "Template Meta-programming for + Haskell", Tim Sheard and Simon Peyton Jones, ACM + SIGPLAN 2002 Haskell Workshop, 2002. However, some of the details + changed after the paper was published. +
+ +
+ The extra syntax of TH (quasi-quote brackets, splices, and reification)
+ is handled in the module DsMeta
.
+ In particular, the function dsBracket
desugars the four
+ types of quasi-quote brackets ([|...|]
,
+ [p|...|]
, [d|...|]
, and [t|...|]
)
+ and dsReify
desugars the three types of reification
+ operations (reifyType
, reifyDecl
, and
+ reifyFixity
).
+
+ A term in quasi-quote brackets needs to be translated into Core code
+ that, when executed, yields a representation of that term in
+ the form of the abstract syntax trees defined in Language.Haskell.THSyntax
.
+ Within DsMeta
, this is achieved by four functions
+ corresponding to the four types of quasi-quote brackets:
+ repE
(for [|...|]
), repP
(for
+ [p|...|]
), repTy
(for [t|...|]
),
+ and repTopDs
(for [d|...|]
). All four of
+ these functions receive as an argument the GHC-internal Haskell AST of
+ the syntactic form that they quote (i.e., arguments of type HsExpr
.HsExpr
+ Name
, HsPat
.HsPat Name
,
+ HsType
.HsType
+ Name
, and HsDecls
.HsGroup
+ Name
, respectively).
+
+ To increase the static type safety in DsMeta
, the functions
+ constructing representations do not just return plain values of type CoreSyn
+ .CoreExpr
; instead, DsMeta
introduces a
+ parametrised type Core
whose dummy type parameter indicates
+ the source-level type of the value computed by the corresponding Core
+ expression. All construction of Core fragments in DsMeta
+ is performed by smart constructors whose type signatures use the dummy
+ type parameter to constrain the contexts in which they are applicable.
+ For example, a function that builds a Core expression that evaluates to
+ a TH type representation, which has type
+ Language.Haskell.THSyntax.Type
, would return a value of
+ type
+
++ ++Core Language.Haskell.THSyntax.Type+
+ The TH paper introduces four reification operators:
+ reifyType
, reifyDecl
,
+ reifyFixity
, and reifyLocn
. Of these,
+ currently (= 9 Nov 2002), only the former two are implemented.
+
+ The operator reifyType
receives the name of a function or
+ data constructor as its argument and yields a representation of this
+ entity's type in the form of a value of type
+ THSyntax.Type
. Similarly, reifyDecl
receives
+ the name of a type and yields a representation of the type's declaration
+ as a value of type THSyntax.Decl
. The name of the reified
+ entity is mapped to the GHC-internal representation of the entity by
+ using the function lookupOcc
on the name.
+
+ Name lookups in the meta environment of the desugarer use two functions
+ with slightly different behaviour, namely DsMeta.lookupOcc
+ and lookupBinder
. The module DsMeta
contains
+ the following explanation as to the difference of these functions:
+
+++When we desugar [d| data T = MkT |] +we want to get + Data "T" [] [Con "MkT" []] [] +and *not* + Data "Foo:T" [] [Con "Foo:MkT" []] [] +That is, the new data decl should fit into whatever new module it is +asked to fit in. We do *not* clone, though; no need for this: + Data "T79" .... + +But if we see this: + data T = MkT + foo = reifyDecl T + +then we must desugar to + foo = Data "Foo:T" [] [Con "Foo:MkT" []] [] + +So in repTopDs we bring the binders into scope with mkGenSyms and addBinds, +but in dsReify we do not. And we use lookupOcc, rather than lookupBinder +in repTyClD and repC.+
+ This implies that lookupOcc
, when it does not find the name
+ in the meta environment, uses the function DsMeta.globalVar
+ to construct the original name of the entity. This name
+ uniquely identifies the entity in the whole program and is in scope
+ independent of whether the user name of the same entity is in
+ scope or not (i.e., it may be defined in a different module without
+ being explicitly imported). NB: Incidentally, the
+ current implementation of this mechanisms facilitates breaking any
+ abstraction barrier.
+
+ During the construction of representations, the desugarer needs to use a
+ large number of functions defined in the library
+ Language.Haskell.THSyntax
. The names of these functions
+ need to be made available to the compiler in the way outlined Primitives and the Prelude.
+ Unfortunately, any change to PrelNames
+ triggers a significant amount of recompilation. Hence, the names needed
+ for TH are defined in DsMeta
instead (at the end of the
+ module).
+
+ +Last modified: Sat Nov 9 20:27:46 EST 2002 + + + + hunk ./ghc/docs/comm/index.html 9 -