Você está na página 1de 36

Haskell Templates

Prelude
When Im read thorough first paper on Template Haskell (Template metaprogramming for Haskell), I cant understand it. I see the tricky [|...| and !(...) e"pressions, #ut cant figure $hen I should use first construct, $hen to use second and ho$ they must #e com#ined together. %nly after reading last sections $ith &technical details', I disco(ered for myself ho$ this actually $orks and could understand all pre(ious &high)le(el' stuff. I try to read another papers on TH, #ut they $as no more helpful. *o I decided to $rite my o$n TH tutorial + such one, $hich gi(es to reader full understanding of $hat he does on each step of education. It is the result. ,eel free to edit this $ikipage, especially if you see my misusing of -nglish (Im not nati(e speaker, after all ). I use curly #races to cite Haskell code in te"t.

Lesson 1: low-level TH
Template Haskell is macro preprocessor for Haskell, $hose macros are $ritten in Haskell itself, and is .ust ordinary functions. /acros are called (spliced) $ith synta" !macro or ! (macro params...), for e"ample0

1ip 2 !mk3ip fst4 2 !(cnst 5 &result')

In this e"ample, mk3ip and (cnst 5 &result') are *67I8- -96:-**I%;*. That means $hat they $ill #e e(aluated at 8%/6I7- TI/- and returned (alue $ill #e con(erted to ordinary Haskell code and su#stituted instead of splice construction. ,unctions used in splice e"pressions must #e defined in another module, imported #y current one, #ecause at the moment of this preprocessing functions defined in current module are not e(en compiled.

The $hole splice e"pression must ha(e type <= -"p>, so in this e"ample appropriate type for function cnst may #e0 cnst 00 Int )? *tring )? = -"p

Type = represents =uotation /onad. I $ill e"plain its role in ne"t lesson, no$ $e $ill .ust use <return> to lift the (alues of type <-"p> into type <= -"p>. Type -"p is Template Haskells representation of Haskell e"pressions. Its not a *tring, as you can suppose, #ecause @

such simple representation $ould create pro#lems for code generation and especially for code transformations. Instead, its a recursi(e structure, representing AB*T:A8T *C;TA9 T:-- of e"pression. *uch representations are usually resulted from syntactic parsing of Haskell programs in compliers, program transformation tools and so on. Here it is used for diametrically opposite goal + to create a right piece of Haskell code.

Dalue of type -"p can #e con(erted to string containing actual Haskell code #y function pprint (Want to kno$ moreE Template Haskell itself uses this function to insert generated code #ack to source files). /oreo(er, Fuotation #rackets [| ... | performs the opposite transition + they parse ordinary Haskell code and returns -"p structure representing itG *o, #efore $riting any programs $e can play a little $ith it0

80HHaskell? ghci +fth ghci? 0m I7anguage.Haskell.TH

Here, $e use &)fth' to ena#le support of Fuotation #rackets, and import module 7anguage.Haskell.TH, $hich contains definition of =, -"p, pprint and all other TH stuff. 7ets continue0

ghci? run= [| @ | ??2 print 7it- (Integer7 @)

ghci? run= [| H" J )? " | ??2 print 7am- [Dar6 "JK,Wild6 (Dar- "JK)

ghci? run= [| H" J )? " | ??2 put*tr7n.pprint H"JK J )? "JK

We are use <print> to print the structures #uilt #y [|...| and <put*tr7n.pprint> to con(ert these structures #ack to strings $ith actual Haskell code. As you can see from last call, it really prints the same code + modulo renaming of (aria#les. *o, $e disco(ered e"cellent TH de#ugging tools + you can use <run= [| 8%L- | ??2 print> to see the structure that must #e 5

returned to generate some 8%L-, and <run= (macro params...) ??2 put*tr7n.pprint> to print out the code that !(macro params...) $ill generate.

Cou can find definitions of types, used in TH to represent Haskell code, in the module 7anguage.Haskell.TH.*ynta", and I partially cite these definitions here0

data -"p 2 Dar- ;ame | 7it- 7it | App- -"p -"p | 7am- [6at -"p | Tup- [-"p

)) represents Haskell e"pressions )) < " > )) < M or NcN> )) < f " > )) < H p@ p5 )? e > )) < (e@,e5) > )) < if e@ then e5 else e4 >

| 8ond- -"p -"p -"p | 7ist- [-"p | ...

)) < [@,5,4 >

data 6at 2 7it6 7it | Dar6 ;ame | Tup6 [6at | Wild6 | ...

)) represents Haskell patterns )) < M or NcN > )) < " > )) < (p@,p5) > )) < J >

data 7it 2 8har7 8har | *tring7 *tring

)) represents Haskell literals )) Oa )) &string'

| Integer7 Integer

)) @54

| Lou#le6rim7 :ational )) @5.4 | ...

data ;ame 2 ... )) represents Haskell sym#ols (identifiers and operators) data Type 2 ... )) represents Haskell datatypes

As you can see, e"pressions are composed from other e"pressions, literals, (aria#les, patterns and so on, in the strict compliance $ith the Haskell synta" rules.

Petting all this kno$ledge, you can easily $rite almost any macro, #ut lets start from the simplest one0 lets define macro &cnst', so that splice !(cnst n str) $ill generate function (lam#da form) $hich accepts <n> (unused) parameters and returns .ust <str>. *e(eral e"amples of code, $hich should #e generated #y this macro0

!(cnst @ &"')

22? (HJ )? &"')

!(cnst 5 &str') 22? (HJ J )? &str') !(cnst 4 &hey') 22? (HJ J J )? &hey')

We can start from printing (alues, $hat should #e generated #y our function0

ghci? run= [| HJ )? Q"Q | ??2 print 7am- [Wild6 (7it- (*tring7 Q"Q))

ghci? run= [| HJ J )? QstrQ | ??2 print 7am- [Wild6,Wild6 (7it- (*tring7 QstrQ))

ghci? run= [| HJ J J )? QheyQ | ??2 print 7am- [Wild6,Wild6,Wild6 (7it- (*tring7 QheyQ))

At this moment, I hope, you can compare printed (alues $ith definition of type -"p and check that these (alues are really representations of code in Fuotation #rackets [|...| . Writing actual code should #e tri(ial, please does it yourself and compare results $ith my module (remem#er to use <return> to lift result into = monadG)0

module Test $here import 7anguage.Haskell.TH

cnst 00 Int )? *tring )? = -"p cnst n s 2 return (7am- (replicate n Wild6) (7it- (*tring7 s)))

;o$ $e can test our macro #y loading it into ghci (I assume that you put te"t of module Test in file test.hs)0

80HHaskell? ghci +fth test.hs

ghci? run= (cnst @ Q"Q) ??2 print 7am- [Wild6 (7it- (*tring7 Q"Q))

ghci? run= (cnst @ Q"Q) ??2 put*tr7n.pprint HJ )? Q"Q

ghci? run= (cnst 5 QstrQ) ??2 put*tr7n.pprint HJ J )? QstrQ

It really $orksGGG ;o$ lets try to use this macro to actually define ne$ functions0

ghci? let cnst@ 2 !(cnst @ Q"Q) ghci? 0t cnst@ cnst@ 00 t )? [8har ghci? cnst@ 5@ Q"Q

ghci? let cnst5 2 !(cnst 5 QstrQ) ghci? 0t cnst5 cnst5 00 t )? t@ )? [8har ghci? cnst5 5@ 4R QstrQ

ghci? let cnst5K 2 !(cnst 5K QstrQ) ghci? 0t cnst5K cnst5K 00 t )? t@ )? ... )? t@S )? [8har

And it $orks tooG As home$ork, try to define (ariant of <cnst>, $hich can return any literal constant + #e it a *tring, 8har or Lou#le. To do it, you should import module 7anguage.Haskell.TH.*ynta", $hich contains function <lift>. This function con(erts Ints, *trings and so on to appropriate (alues of type 7it.

At the end of this lesson, I $ill gi(e e"ample of module, $hich uses our macro to define functions and also prints structure of generated e"pressions. Cou can use such modules instead of ghci to de#ug and test your code0

<)U %6TI%;*JPH8 )fglasgo$)e"ts )fth U)> module /ain $here

import 7anguage.Haskell.TH import Test

cnst@ 2 !(cnst @ Q"Q) cnst5 2 !(cnst 5 QstrQ) cnst5K 2 !(cnst 5K QfooQ)

main 2 do print (cnst@ @@) print (cnst5 @@ @5) run=(cnst @ Q"Q) ??2 print run=(cnst 5 QstrQ) ??2 print run=(cnst 5K QfooQ) ??2 print run=(cnst @ Q"Q) ??2 put*tr7n.pprint run=(cnst 5 QstrQ) ??2 put*tr7n.pprint run=(cnst 5K QfooQ) ??2 put*tr7n.pprint

Lesson 2: generation of unique names and dynamic variables


V

If you actually tried to $rite your o$n TH macros after completing first lesson, you are pro#a#ly noticed that I dont e"plain ho$ to create (alues of type ;ame. These (alues represent (aria#les + #oth in patterns and e"pressions. We cant use .ust *tring to represent them #ecause that cannot gi(e guarantees that (aria#les created in different parts of programs, $ill not use the same name. /oreo(er, e(en se(eral calls to one function creating (aria#le $ith fi"ed name, can raise pro#lems. 6ro#lems $ith o(erlapping (aria#le names so seriously #eat other macro preprocessors that TH proposed an ultimate solution in this area + =uotation /onad, named =. This monad supports special operation for generating uniFue (aria#le names0

ne$;ame 00 *tring )? = ;ame

Argument to ne$;ame $ill #e used as prefi" for generated name, follo$ed #y &J' and uniFue num#er. It should #e used to gi(e to generated (aria#les more mnemonic names, #ut e(en $ith the same arguments each call to ne$;ame $ill generate ne$, uniFue (aria#le name. As $ith any other monad, you can use <do> notation to e"ecute monad operations0

somemacro 2 do (ar@ W) ne$;ame &"' (ar5 W) ne$;ame &y' return (...)

;o$ $e are ready to define more interesting macro0 !(sel n m) should generate a lam#da form, $hich gets m)component tuple as argument and returns its nth component, so0

!(sel @ 4) should generate code, eFui(alent to H( ",J, J) )? " !(sel 5 R) should generate code, eFui(alent to H(J,",J,J) )? "

7ets start from looking at -"ps $e must return0

80HHaskell? ghci +fth

ghci? run= [| H(",J,J) )? " | ??2 print 7am- [Tup6 [Dar6 "JK,Wild6,Wild6 (Dar- "JK)

ghci? run= [| H(J,",J,J) )? " | ??2 print 7am- [Tup6 [Wild6,Dar6 "J@,Wild6,Wild6 (Dar- "J@)

Here $e see our old friends, 7am- and Wild6, together $ith ne$ ones0 "JK and "J@ represents (alues of type ;ame, $hich $e should generate $ith help of ne$;ame, Dar6YDar- incorporate these ;ames into patterns and e"pressions, respecti(ely, and Tup6 creates pattern matching a tuple from list of patterns for indi(idual tuple elements. 6lease dra$ attention to the follo$ing + if you need to refer to the same (aria#le in different parts of generated code, you must generate its ;ame once #y using ne$;ame and then use returned (alue. Lifferent calls to ne$;ame, e(en $ith the same argument, $ill gi(e you different (aria#lesG Lont try to generate (aria#les for your code in <let> or <$here> clausesG

sel 00 Int )? Int )? = -"p sel n m 2 do " W) ne$;ame &"' let $ilds 2 replicate m Wild6 return (7am- (replaceAt (n)@) $ilds (Dar6 ")) (Dar- "))

)) |:eplace nNth element (counted from K) in Z"sZ to Z"Z replaceAt n "s " 2 take n "s II " 0 drop (nI@) "s

There are rare cases $hen $e dont need to generate (aria#les $ith uniFue names + on the contrary, $e need to specify the e"act identifier name $hich must #e used in generated code. ,or such cases, there is a function mk;ame, $hich generates identifier $ith e"act gi(en name. This property can #e used to refer to identifiers in outer, hand)$ritten code or to link together independently generated parts of code. This function, like ne$;ame, returns (alue of type ;ame, $hich then can #e used to construct e"pressions, patterns or declarations. But mk;ame, unlike ne$;ame, dont run in = monad, its a pure function0

mk;ame 00 *tring )? ;ame

In order to directly compare these functions, try to run the follo$ing ghci session0

80HHaskell? ghci +fth ghci? 0m I7anguage.Haskell.TH

ghci? run= (return! Dar- (mk;ame &"')) ??2 put*tr7n.pprint "

$hen $e need to control e"act (aria#le names that $ill #e used in generated code, for e"ample to refer to identifiers in the outer hand)$ritten code or $hen $e use our o$n schemes of (aria#le names generation. ,or such cases, there is a possi#ility to create (aria#le $hich $ill ha(e in generated code the e"act name you specified using function dyn0

80HHaskell? ghci +fth ghci? 0m I7anguage.Haskell.TH

ghci? run= (return! Dar- (mk;ame &"')) ??2 put*tr7n.pprint "

ghci? run= (tup- [dyn Q"Q, dyn &"' ) ??2 put*tr7n.pprint (",")

@K

This e"ample also use ne$ function tup-. What is difference #et$een this function and constructor Tup-E 7ets see its definition in module 7anguage.Haskell.TH.7i#0

tup- 00 [-"p= )? -"p= tup- es 2 do < es@ W) seFuence es[ return (Tup- es@)>

As you can see

Lesson : ot!er monadic activities


Besides ne$;ame, there are a num#er of other TH utilities $hose results depend on the en(ironment $here TH function $as e"ecuted. It includes error reporting and returning information a#out place $here higher)le(el TH splice $as called0

report 00 Bool ? *tring ? = () :eport something to the user. If the Bool is True, the something is treated as an error, other$ise it is simply displayed. In #oth cases, though, e"ecution continues. The difference #et$een the t$o is seen #y reco(er[ if there is no enclosing reco(er, compilation fails.

gi(e\p 00 = a *top e"ecution[ find the enclosing reco(er.

reco(er 00 = a ? = a ? = a The call (reco(er h F) runs F. If F e"ecutes gi(e\p, e"ecution resumes $ith h. If F runs to completion, #ut has made some calls to report True, the result is discarded and h is run. If F @@

runs to completion $ith no error report, h is ignored, and FNs result is the result of the call to reco(er.

current/odule 00 = *tring :eturns the name of the module #eing compiled.

current7oc 00 = (,ile6ath, Int) :eturns the location of the tople(el splice #eing e"ecuted.

The last t$o functions may #e useful for constructing error messages.

/oreo(er, #ecause top)le(el TH functions must return (alues in = monad, there are a num#er of helper functions, $hich lifts constructors of -"pY7itY6at datatypes into the = monad0 lit-, (ar-, app-, (ar6 and so on. Their declarations also use lifted atatypes0 -"p= 2 = -"p, 7it= 2 = 7it, 6at= 2 = 6at... (you can find all these lifted functions and types in module 7anguage.Haskell.TH.7i#). \sing these functions allo$ to decrease num#er of cases $here &do' construct is needed.

Lesson ": add sugar to your taste


-"plicit creation of code $ith -"pY6at constructors is much more complicated than $riting Haskell code itself. Hopefully, there is a method to translate Haskell code into appropriate e"pression, $hich $ould return (alue of type -"p. And you already kno$ this method + using Fuotation #rackets [|...| G 7ets see ho$ the sel function can #e defined $ith them0

sel @ 5 2 [| H(",J) )? " | sel 5 5 2 [| H(J,") )? " | sel @ 4 2 [| H(",J,J) )? " | ...

@5

=uotation #rackets [|...| compiles as the e"pression of the type <= -"p>, $hich upon e"ecution in monad = $ould return -"p, representing Haskell code inside #rackets + and that it e"actly $hat $e need to define selG We already used Fuotation #rackets to see $hich e"pressions $e should generate to represent some Haskell code. ;o$ $e are using them to directly represent the -"ps $e should return for each com#ination of sel arguments. %f course, that is not (ery interesting. The key to real usage of Fuotation #rackets to define macro functions is their a#ility to include splice e"pressionsG *ee, for e"ample, the follo$ing recursi(e cnst definition0

cnst K str 2 lift str cnst n str 2 do e W) cnst (n)@) str [| HJ )? !e |

Here, cnst called recursi(e and e recei(es result of this call + constant function $ith (n)@) arguments. This (alue used to #uild function $ith n arguments + .ust #y using it in lam#da form $ith one more argument. :esult of this recursi(e calculation for (cnst 4 &foo') $ould #e <HJ )? (HJ )? (HJ )? &foo'))> $hat is fully eFui(alent to pre(ious definition.

*pliced e"pression !" or !(f ...) inside Fuotation #rackets also should #e of type <= -"p>. Its (alue is computed, con(erted to string $ith Haskell code #y using function <pprint> and inserted at the place of call. After e(aluating all splice calls inside Fuotation #rackets, the $hole Haskell code they contains con(erted #ack to the (alue of type <= -"p>. There is also another interpretation of this process + that Fuotation #rackets are con(erted to Haskell e"pression constructing appropriate -"p, $here splice e"pressions are replaced to using of appropriate (aria#les. We can simplify our definition0

cnst K str 2 [| str | cnst n str 2 [| HJ )? !(cnst (n)@) str) |

I replaced <lift str> $ith [| str | 0 (aria#les not #ound inside Fuotation #rackets are #ound to outside (aria#les. But #ecause compile)time (aria#les is run)time constants(G) these outside) #ound (aria#les turns into literals of appropriate type + and that is eFui(alent to con(erting them (ia <lift> function. Also I replaced computation of <e> and splicing its (alue inside Fuotation #rackets $ith computation of the same (alue in the splice call itself. %ur ne$ definition doesnt contain any details related to -"p and 6at types, #ut ne(ertheless it $orksG And $hat is great + in many cases you can create macros $ithout e(er thinking a#out comple" synta" trees they generateG =uotation #rackets also hide details of using Fuotation @4

monad = + spliced e"pressions inside #rackets can ha(e type <-"p> or <= -"p>, and (aria#les created inside #rackets get its o$n, uniFue names.

The splice call !(...) and Fuotation #rackets [|...| does the opposite things + former e"ecutes computation of type <= -"p>, and con(erts its result to Haskell code using function <pprint 00 -"p )? *tring>, $hile later gets Haskell code as ordinal *tring and con(erts this string into e"pression of type <= -"p>, corresponding to this code. Therefore, !( [| 999 | ) as $ell as [| !999 | can #e replaced $ith .ust 999. \sing this rule, $e can e"plore splicing of macros $ithout going do$n to details of generated -"ps. 7ets consider the follo$ing usage of cnst0

cnst4 2 !(cnst 4 &"')

We can replace call to cnst $ith right side of the appropriate definition0

cnst4 2 !( [|HJ )? !(cnst (4)@) &"') | )

8om#ination of !(...) and [|...| disappears, so this eFui(alent to0

cnst4 2 HJ )? !(cnst 5 &"')

*plice !(cnst 5 &"') in turn can #e replaced $ith result of this call, and so on. !(cnst K &"') $ill #e replaced $ith !([| &"' | ) $hich is eFui(alent to &"', and the final result $ill #e0

cnst4 2 HJ )? ( HJ )? ( HJ )? &"' )))

That is really looks like macro e"pansion, you agreeE But for those cases $here e"pression cant #e #uilt $ith .ust splicing and Fuotation #rackets, the $hole po$er of e"plicit -"p construction ready at your ser(ice. ,or e"ample, definition of sel in pre(ious lesson cannot #e repeated in #racket synta", #ecause there is no $ay to create tuple $ith (aria#le num#er of elements.

@R

#ore comple$ e$ample: %ipn


useful to see $hat mk3ip generates for a particular n in understanding ho$ it $orks. When applied to 4, and the o#.ect (aria#le((ar QffQ) it generates a (alue in the -"pr type. 6retty) printing that (alue as concrete synta" $e get0

\ y1 y2 y3 > case (y1,y2,y3) of (x1:xs1,x2:xs2,x3:xs3) > (x1,x2,x3) : ff xs1 xs2 xs3 (_,_,_) > []

mkZip :: Int > Expr > Expr mkZip n name $%ere (p&s, e&s) (p"s, e"s) (p&*s,e&*s) pcons x xs m1 m2 'en(E )x) n 'en(E )y) n 'en(E )xs) n [p+ ,x : ,xs +] !am p"s (caseE (t#p e"s) [m1,m2])

[+ ,(t#p e&s) : ,(apps(name : e&*s)) +] simp!e. (pt#p (/ip0it% pcons p&s p&*s)) simp!e. (pt#p (copies n p$i!1)) (con )[]))

#ore comple$ e$ample: printf &eneration of declarations and identifiers reification

@M

\ntil this moment, $e only considered using of TH for generation of some Haskell e"pressions. But TH has more po$er + it can also create declarations0 ne$ functions, ne$ data types, class instances and so on. Leclarations in TH represented #y type Lec. In order to generate declarations, you must place splice call in the module place $here declarations allo$ed and make this splice to return (alue of type = [Lec . *uch splice call may return any num#er of declarations $hich then $ill #e su#stituted instead of splice call.

#ore comple$ e$ample: deriving '!ow

@T

(not!er tutorial:
Template Haskell is a Haskell e"tension that supports compiletime metaprogramming. The purpose of the system is to support the algorithmic construction of programs at compiletime. The a#ility to generate code at compile time allo$s the programmer to use programming techniFues not a(aila#le in Haskell itself, such as macrolike e"pansion, user directed optimi1ation (such as inlining), polytypic programs, generation of supporting data structures and functions from e"isting data structures and functions. ,or e"ample, the code
ye!! fi!e !ine fai! (,(printf )Error in fi!e 2s !ine 21)) fi!e !ine)

may #e translated #y TH to
ye!! fi!e !ine fi!e !ine) fai! ((\x1 x2 3> )Error in fi!e )44x144) !ine )44s%o$ x2)

As another e"ample, the code


1ata 5 6 Int *trin' + 7 Inte'er + 8

,(1eri9e*%o$ ::5)

may #e translated to
1ata 5 6 Int *trin' + 7 Inte'er + 8

instance *%o$ 5 s%o$ (6 x1 x2) s%o$ (7 x1) s%o$ 8 )6 )44s%o$ x144) )44s%o$ x2 )7 )44s%o$ x1 )8)

(if you are interested, you can find definitions of printf and 1eri9e*%o$ at the end of this documentation).

In TH, Haskell code generated .ust #y ordinary Haskell functions. In order to use TH, you must learn 4 things0 Ho$ Haskell code represented in TH functions Ho$ Fuotation monad used to supply uniFue names Ho$ TH)generated code inserted in the module

There are also se(eral more ad(anced topics0

@V

=uotation monad =uotation #rackets :eification -rror reporting and reco(ery Le#ugging

I also included some e"amples of using TH0 printf deri(e*ho$

How Haskell code represented in TH functions


In Template Haskell, ordinary algebraic data types represent Haskell program fragments. These types modeled after Haskell language synta" and represents A*T (a#stract synta" tree) of corresponding Haskell code. There is an Exp type to represent Haskell e"pressions, (at + for patterns, ;it + for literals, <ec + for declarations, 5ype + for data types and so on. Cou can see definitions of all these types in the module ;an'#a'e=>aske!!=5>=*yntax. These types refer to each other according to rules of Haskell synta", so using them you can construct (alues representing any possi#le Haskell program fragments. ]ust some simple e"amples0
9arx patx ?arE (mk@ame )x)) ?ar( (mk@ame )x))

represents e"pression x, i.e. simple (aria#le &"' represents pattern x, i.e. the same (aria#le &"' used in represents constant e"pression )str) represents tuple e"pression (x,)str))

pattern
str ;itE (*trin'; )str)) t#p!e

5#pE [9arx, str]

;amE [patx] t#p!e

represents lam#da form (\x 3> (x,)str)))

To make our life easier, all constructors of Exp type ha(e names ending $ith &-', of (at type + ending $ith &6' and so on. ,unction mk@ame, used here, creates (alue of type @ame (representing identifier) from *trin' $ith name of this identifier. *o, to generate some Haskell code, TH function must .ust create and return (alue of type Exp, $hich ser(e as representation for this chunk of code. Cou dont e(en need to thoroughly learn Exp and other types definitions in order to kno$ ho$ to represent Haskell code you need + in the section Le#ugging I $ill say ho$ you can print TH representation of any Haskell code chunk.

@X

How quotation monad used to supply unique names


But TH functions are not pure functions returning (alues of type Exp. Instead, they are computations e"ecuted in special monad = (called &Fuotation monad'), $hich allo$s to automatically generate uniFue names for (aria#les using monadic operation ne$@ame::*trin'3>A @ame. This operation on each call generates uniFue name $ith gi(en prefi". This name then may #e used as part of pattern (#y using constructor ?ar(::@ame3 >(at) and e"pressions ((ia ?arE::@ame3>Exp). 7ets $rite simple TH e"ample + TH function t#p!eBep!icate, $hich $hen used as &, (t#p!eBep!icate n) x' $ill return n)element tuple containing " in all positions (.ust like rep!icate does for lists). 6lease dra$ attention that &n' is an argument of TH function, $hile &"' is an argument to anonymous function (lam#da form) it generatesG I pro(ide the $hole module containing this function definition (module ;an'#a'e=>aske!!=5> is an &e"ternal interface' to TH + it pro(ides all the data types and functions $hich are used to $rite TH programs)0
mo1#!e 5#p!eBep!icate $%ere import ;an'#a'e=>aske!!=5> t#p!eBep!icate :: Int 3> A Exp t#p!eBep!icate n 1o i1 C3 ne$@ame )x) ret#rn , ;amE (?ar( i1) (5#pE , rep!icate n , ?arE i1)

,or e"ample, call &t#p!eBep!icate 3D returns Exp eFui(alent to Haskell e"pression &(\x 3> (x,x,x))'.

How TH-generated code inserted in the module


A splice is written $x, where x is an identifier, or $(...), where the "..." is an arbitrary expression. There must be no space between the "$" and the identifier or parenthesis. This use of "$" overrides its meaning as an infix operator, just as "M.x" overrides the meaning of "." as an infix operator. f you want the infix operator, put spaces around it. A splice can occur in place of an e"pression[ the spliced e"pression must ha(e type A Exp a list of top)le(el declarations[ the spliced e"pression must ha(e type A [<ec]. Leclarations, generated #y splice, ha(e access only to identifiers, $hose declarations are te"tually precede them ($hich is contro(ersial to usual Haskell practice of glo#al access to all declarations placed in current module) a type[ the spliced e"pression must ha(e type A 5ype

Also you must kno$ that Cou must use compiler flag Eft% to ena#le splices synta"

@S

Cou can only run a function at compile time if it is imported from another module. That is, you canNt define a function in a module, and call it from $ithin a splice in the same module. If you are #uilding PH8 from source, you need at least a stage)5 #ootstrap compiler to run Template Haskell. A stage)@ compiler $ill re.ect the TH constructs.

-"ample of module $hich uses our t#p!eBep!icate function0


F3G H(5IH@*_I>8 3ft% G3J mo1#!e 5est $%ere import 5#p!eBep!icate main 1o print (,(t#p!eBep!icate 2) 1) print (,(t#p!eBep!icate K) )x)) 33 prints (1,1) 33 prints ()x),)x),)x),)x),)x))

Quotation monad
!ecause top"level T# functions must return values in $ monad, there are a number of helper functions, which lifts constructors of %xp&'it&(at data types into the $ monad) lam% *lifted 'am%+, var%, app%, var( and so on. Their declarations also use lifted data types) %xp$ , $ %xp, 'it$ , $ 'it, (at$ , $ (at... *you can find all these lifted functions and types in module Language.Haskell.TH.Lib+. -sing these functions allow to decrease number of cases where do statement is needed. There is also function lift, which converts any value, which has literal representation, to value of type Exp which represents this literal. n some rare cases you don.t need uni/ue variable name to be generated0 instead, you need to specify the exact name of variable which must be generated in output code. 1or these cases, there is a *pure+ function mkName::String->Name. There is also corresponding helper function 2d n!s!"!return!(#arE!(mkName!s))3, which returns Exp representing variable with exact the given name.

Quotation brackets
While the Exp can represent any Haskell e"pression, programmatic #uilding of Exp (alues is not so easy $ork. In order to address this pro#lem, Template Haskell supports /uotation brac4ets, $hich is a $ay to con(ert literal Haskell code to data (alue representing it. There are four types of Fuotation #rackets0
[+ === +],

$here the Q...Q is an e"pression[ the Fuotation has type A Exp $here the Q...Q is a pattern[ the Fuotation has type A (at $here the Q...Q is a list of top)le(el declarations[ the Fuotation has type $here the Q...Q is a type[ the Fuotation has type A 5ype

[p+ === +], [1+ === +], A [<ec] [t+ === +],

5K

,or e"ample, [+ \_ 3> L +] $ill #e translated to (ret#rn , ;amE [0i!1(] (;itE (Inte'er; L))). The Fuotation has type A Exp (rather than .ust Exp), so that it need to #e e"ecuted in = monad to return appropriate Exp. This e"ecution stage allo$s Template Haskell to replace all identifiers, introduced inside Fuotation #rackets, #y uniFue ones, generated internally $ith help of ne$@ame. ,or e"ample, Fuotation [+ \x 3> x +] $ill #e translated to the follo$ing code0
(1o i1 C3 ne$@ame )x)M ret#rn , ;amE [?ar( i1] (?arE i1))

/oreo(er, inside Fuotation #rackets $e can again use splices, making TH some form of macro preprocessor, $here a part of code $ritten literally and part of code generated programmatically. ,or e"ample, the Fuotation [+ 1 4 ,(f x) +] $ill e"ecute (f x) + $hich must ha(e type A Exp, translate returned Exp (alue to literal Haskell code, su#stitute it instead of splice call, and then recon(ert the full e"pression inside #rackets into the code $hich #uilds the appropriate Exp. Thanks to automatic renaming of internally used identifiers, the different Fuotations and e(en different in(ocations of the same Fuotation $ill ne(er refer to the each others local (aria#les. 8onsider the follo$ing definition0
s#mm n s#mm: n [+ L +] s#mm: L co1e co1e s#mm: n co1e [+ \x 3> ,(s#mm: (n31) [+,co1e4x+] ) +]

This definition generates lam#da form $ith n parameters $hich sums up all its arguments, for e"ample ,(s#mm 3) 3> (\x1 3> \x2 3> \x3 3> L4x14x24x3). 6lease dra$ attention that generated code uses three different names for lam#da parameters despite the fact that they all $ere generated #y the same Fuotation. As you can see in this fragment, depth of Fuotation and splicing #rackets can #e ar#itrary, the only rule is that they must interchange + no Fuotations inside Fuotations, and no splices inside splices.

The FuasiFuote notation is a con(enient shorthand for representing Haskell programs, and as such it is le"ically scoped. /ore precisely0 e(ery occurrence of a (aria#le is #ound to the (alue that is le"ically in scope at the occurrence site in the original source program, #efore any template e"pansion. This rule has 4 cases0 =uotation #rackets pre(ent &capturing' of local (aria#les, declared in one Fuotation, #y another (like the usual Haskell pre(ents capturing of local (aria#les, used in closures). I already descri#ed ho$ that is accomplished #y automatic renaming of all locally introduced identifiers. %nly [p+ === +] Fuotation doesnt rename (aria#les this pattern introduces. Instead, TH pro(ides function 'enpat, $hich generates uniFue pattern from the gi(en one. Plo#al identifiers, referred inside Fuotation, &capture' the identifiers a(aila#le in the en(ironment $here this Fuotation is defined (again, like usual Haskell), so you can pass $ithout any pro#lems (alue of Fuotation to functions in other modules, $hich dont ha(e these definitions or e(en ha(e another definitions for the same names. This rule uses internal PH8 mechanism of references to sym#ols in another modules, for

5@

e"ample Fuotation [+ map +] may #e translated to reference to sym#ol &<ata=;ist=map' or &44' operation, used in Fuotation, may #e translated to reference to &I>8=7ase=44D= If you need to use identifiers, a(aila#le at place of splicing call, use the ,(1yn )str)) form. Also inside Fuotation #rackets you can use local (aria#les of currently e"ecuted functions. These compile)time (aria#les are run)time constants, so on translating #rackets contents TH .ust su#stitute current (alues of these (aria#les as literals. *o, in this case [+=== x ===+] is con(erted to [+ === ,(!ift x) === +].

*plicing and Fuoting is opposite operations + one translates Exp to Haskell code, another + Haskell code to Exp, so their co)usage is disappear + ,([+ === +]) is eFui(alent to (===), and so [+ ,(===) +]. This has inimita#le (alue for de(elopment of TH programs + in many cases $e can think entirely in terms of Haskell code generated, and dont #other a#out Exp (alues it internally uses. ,or e"ample, consider the e"ecution of splice ,(s#mm 3). ]ust replace this call $ith its #ody0
,(s#mm 3) 3> ,(s#mm: 3 [+ L +]) 3> ,([+ \x 3> ,(s#mm: (331) [+ ,([+L+]) 4 x +] ) +]) 3>

;o$, $e can kill occurrences of the !([| ... | ) and [| !(...) | , at the same time replacing &"' $ith uniFue identifier0
\x1 3> ,(s#mm: (331) [+L4x1+]) 3>

Again replace call to s#mm: $ith its #ody0


\x1 3> ,([+ \x 3> ,(s#mm: (231) [+ ,([+L4x1+]) 4 x +] ) +]) 3>

And repeat the last t$o steps until the end0


\x1 \x1 \x1 \x1 \x1 3> 3> 3> 3> 3> \x2 \x2 \x2 \x2 \x2 3> 3> 3> 3> 3> ,(s#mm: (231) [+ L4x14x2 +]) 3> ,([+ \x 3> ,(s#mm: (131) [+ ,([+L4x14x2+]) 4 x +] ) +]) 3> \x3 3> ,(s#mm: (131) [+ L4x14x24x3 +]) 3> \x3 3> ,([+ L4x14x24x3 +]) 3> \x3 3> L4x14x24x3

It is interesting, that in this definition left side of lam#da form (\xL 3> \x1===) is #uild recursi(ely right on the stack of calls, $hile the right side (L4x14===) is accumulated in the co1e (aria#le. The same techniFue is used to implement -"ample0 printf

Reification
:eification is a Template Haskells $ay of allo$ing the programmer to Fuery the state of the compilers internal (sym#ol) ta#le. The monadic operation &reify::@ame3>A Info' returns information a#out gi(en name0 if its a glo#al identifier (function, constant, constructor) + you can get its type, if its a type or class + you can get its structure. By using reify you are 55

get &entry point' to sym#ols ta#le, $hich then can #e used to find information a#out other types, constructors, classes related to this identifier. Cou can find definition of type Info in the module ;an'#a'e=>aske!!=5>=*yntax. To get a @ame, corresponding to identifier you are interested, you can, theoretically, use function mk@ame, #ut this solution is unsafe, #ecause mk@ame returns unFualified name, $hich interpretation may #e changed depending on conte"t. %n the other side, code &?arE i1 C3 [+ name +]' is safe, #ecause i1 $ill #e linked to Fualified name (like &.y=H$n=.o1#!e=name'), #ut too (er#ose and need monadic conte"t to run. *o, Template Haskell supports another light$eight form of Fuotation0 :i1entifier returns @ame, corresponding to i1entifier[ &!et i1 :name' is fully eFui(alent to &?arE i1 C3 [+ name +]'. 6lease note that this synta" construction has type @ame (not A Exp, nor A @ame), so it can #e used in conte"ts $here monadic computations are impossi#le, for e"ample0
f :: Exp > Exp f (6pp (?ar m) e) + m :map ===

This ne$ form is still a Fuotation construct, .ust like [+ 9 +], and follo$s the same rules as Fuotation #rackets. ,or e"ample, one cannot Fuote inside Fuotes, so this is illegal0 [+ :9 +]. The more important, that it is resol(ed statically, and returns fully Fualified @ame, $hose meaning $ill #e persistent. HaskellNs namespaces make things .ust slightly more complicated. The Fuotation [+ ( +] $ould mean the data constructor 6, $hereas [t+ ( +] $ould mean the type constructor 6. *o $e need the same distinction for light$eight Fuoting. We use t$o single)Fuotes to distinguish the type conte"t0
:9 means N5%e name 9 interprete1 in an expression contextD ::9 means N5%e name 9 interprete1 in an type contextD

*o ::a means the type (aria#le a, for e"ample. Cou can find e"ample of using light$eight Fuoting and reification to automatically generate *%o$ instances in section -"ample0 deri(e*ho$.

The reify function can #e used to get structure of type, #ut it cannot #e used to get Exp representing the #ody of already defined function. If you need to reify function #ody + put declaration of this function in Fuotation #rackets and e"plore returned result, like this0
,(optimi/e [1+ fi==== +])

or
fi,(optimi/e [+ ==== +])

54

Error reporting and recovery


The = monad makes it possi#le to report errors, and reco(er from failures gracefully. Here is the interface0
report :: 7oo! > *trin' > A ()

:eport something to the user. If the Bool is True, the something is treated as an error, other$ise it is simply displayed. In #oth cases, though, e"ecution continues. The difference #et$een the t$o is seen #y reco(er[ if there is no enclosing reco(er, compilation fails.
'i9eOp :: A a

*top e"ecution[ find the enclosing reco(er.


reco9er :: A a > A a > A a

The call (reco9er % P) runs F. If F e"ecutes gi(e\p, e"ecution resumes $ith h. If F runs to completion, #ut has made some calls to report True, the result is discarded and h is run. If F runs to completion $ith no error report, h is ignored, and FNs result is the result of the call to reco(er.
c#rrent.o1#!e :: A *trin'

:eturns the name of the module #eing compiled.


c#rrent;oc :: A (Qi!e(at%, Int)

:eturns the location of the top)le(el splice #eing e"ecuted.

Debugging
In order to make de#ugging Template Haskell programs easier, compiler supports flag 311#mp3sp!ices, $hich sho$s the e"pansion of all top)le(el splices as they happen. Also, you can run computations in = monad programmatically $ith help of &r#nA::A a3>IH a' and print their results either in form of A*T in order to kno$ ho$ you must #uild such e"pression0

8:\>aske!!> '%ci Eft% '%ci> :m 4;an'#a'e=>aske!!=5>

'%ci> r#nA [+ \x _ 3> x +] >>

print

;amE [?ar( x_L,0i!1(] (?arE x_L)

5R

=== or in t%e form of >aske!! co1e to see $%at t%e co1e $i!! -e 'enerate1 -y some sp!ice ca!!: 8:\>aske!!> '%ci '%ci> :m 4;an'#a'e=>aske!!=5> '%ci> :m 48nst

'%ci> r#nA(cnst 2 )str)) >> \_ _ 3> )str)

p#t*tr;n=pprint

This techniFue can #e also used in modules $hich imports appropriate definitions of functions, $ritten in TH, #ut then print results of calls (ia print and pprint instead of splicing them0
F3G H(5IH@*_I>8 3f'!as'o$3exts 3ft% G3J mo1#!e .ain $%ere import ;an'#a'e=>aske!!=5> import 8nst 33 mo1#!e 8nst 1efines f#nction RcnstR, $%ic% can -e #se1 in sp!ices: cnst1 cnst2 cnst2L ,(cnst 1 )x)) ,(cnst 2 )str)) ,(cnst 2L )foo))

33 === -#t $e can a!so r#n RcnstR 9ia r#nA to see %o$ it $orks: main 1o r#nA(cnst 1 )x)) >> print r#nA(cnst 2 )str)) >> print r#nA(cnst 2L )foo)) >> print r#nA(cnst 1 )x)) >> p#t*tr;n=pprint r#nA(cnst 2 )str)) >> p#t*tr;n=pprint r#nA(cnst 2L )foo)) >> p#t*tr;n=pprint

This is the module 8nst, used in these e"amples0


mo1#!e 8nst $%ere import ;an'#a'e=>aske!!=5> cnst :: Int 3> *trin' 3> A Exp cnst n s ret#rn (;amE (rep!icate n 0i!1() (;itE (*trin'; s)))

E ample! printf
That is the definition of function printf, mentioned earlier, together $ith /ain module $hat uses it. 8ompile $ith Q'%c 3ft% 33make .ain=%s'
F3 .ain=%s 3J mo1#!e .ain $%ere

5M

33 Import o#r temp!ate )printf) import (rintf (printf) 33 5%e sp!ice operator , takes t%e >aske!! so#rce co1e 33 'enerate1 at compi!e time -y )printf) an1 sp!ices it into 33 t%e ar'#ment of )p#t*tr;n)= main p#t*tr;n ( ,(printf )Error in fi!e 2s !ine 21: 2s)) )io=cpp) 32K )printer not fo#n1) )

F3 (rintf=%s 3J mo1#!e (rintf $%ere 33 Import 5emp!ate >aske!! interfaces import ;an'#a'e=>aske!!=5> 33 <escri-e a format strin' 1ata Qormat < 33 represents )21) + * 33 represents )2s) + ; *trin' 33 represents ot%er parts of format strin', printe1 !itera!!y 33 (arse a format strin'= parse :: *trin' 3> *trin' 3> [Qormat] parse (:2:::s::xs) rest ; rest : * : parse xs )) parse (:2:::1::xs) rest ; rest : < : parse xs )) parse )) rest [; rest] parse (x:xs) rest parse xs (rest44[x]) 33 Ienerate >aske!! so#rce co1e from a parse1 representation 33 of t%e format strin'= 5%is co1e $i!! -e sp!ice1 into 33 t%e mo1#!e $%ic% ca!!s )printf), at compi!e time= 'en :: [Qormat] 3> ExpA 3> ExpA 'en [] co1e co1e 'en (< : xs) co1e [+ \x3> ,('en xs [+ ,co1e44s%o$ x +]) +] 'en (* : xs) co1e [+ \x3> ,('en xs [+ ,co1e44x +]) +] 'en (; s : xs) co1e 'en xs [+ ,co1e44s +] 33 >ere $e 'enerate t%e >aske!! co1e for t%e sp!ice 33 from an inp#t format strin'= printf :: *trin' 3> ExpA printf s 'en (parse s ))) [+ )) +]

E ample! derive"how
This is the minimal e"ample $hich sho$s ho$ TH can #e used to automatically generate class instances. It uses ::type notation and reify function to generate *%o$ instance for gi(en data type. To simplify code, I dont handle here parametric types, types $ith named fields and other &comple"' types.

F3 .ain=%s 3J

5T

mo1#!e .ain $%ere import <eri9e

1ata 5

6 Int *trin' + 7 Inte'er + 8

,(1eri9e*%o$ ::5)

main

print [6 1 )s), 7 2, 8]

33 prints exact!y CC[6 1 )s),7 2,8]>>

F3 <eri9e=%s 3J mo1#!e <eri9e $%ere

import ;an'#a'e=>aske!!=5> import 8ontro!=.ona1

1ata 51 1ata 52 a

51 52 a

1eri9e*%o$ t

1o

33 Iet !ist of constr#ctors for type t 5y8onI (<ata< _ _ _ constr#ctors _) C3 reify t

33 .ake Rs%o$R c!a#se for one constr#ctor: 33 s%o$ (6 x1 x2) )6 )44s%o$ x144) )44s%o$ x2 1o

!et s%o$8!a#se (@orma!8 name fie!1s)

33 @ame of constr#ctor, i=e= )6)= 0i!! -ecome strin' !itera! in 'enerate1 co1e !et constr#ctor@ame name7ase name

5V

33 Iet 9aria-!es for !eft an1 ri'%t si1e of f#nction 1efinition (pats,9ars) C3 'en(E (!en't% fie!1s) 33 Bec#rsi9e!y -#i!1 () )44s%o$ x144===44))) expression from [x1===] 9aria-!es !ist !et f [] f (9:9ars) [+ )) +] [+ ) ) 44 s%o$ ,9 44 ,(f 9ars) +]

33 Ienerate f#nction c!a#se for one constr#ctor c!a#se [con( name pats] 33 (6 x1

x2)

(norma!7 [+ constr#ctor@ame 44 ,(f 9ars) +]) [] 4s%o$ x144) )44s%o$ x2

33 )6 )4

33 .ake -o1y for f#nction Rs%o$R: 33 33 33 s%o$ (6 x1 x2) s%o$ (7 x1) s%o$ 8 )6 )44s%o$ x144) )44s%o$ x2 )7 )44s%o$ x1 )8)

s%o$-o1y C3 map. s%o$8!a#se constr#ctors

33 Ienerate temp!ate instance 1ec!aration an1 t%en rep!ace 33 type name (51) an1 f#nction -o1y (\x 3> )text)) $it% o#r 1ata

1 C3 [1+ instance *%o$ 51 $%ere s%o$ x +] !et [Instance< [] (6pp5 s%o$t (8on5 _51)) [Q#n< s%o$f _text]] )) [Q#n< s%o$f s%o$-o1y]] 1 )text)

ret#rn [Instance< [] (6pp5 s%o$t (8on5 t

33 Ienerate n #niP#e 9aria-!es an1 ret#rn t%em in form of patterns an1 expressions

5X

'en(E n

1o

i1s C3 rep!icate. n (ne$@ame )x)) ret#rn (map 9ar( i1s, map 9arE i1s)

5S

#$%$ Template Haskell


Template Haskell allo$s you to do compile)time meta)programming in Haskell. The #ackground to the main technical inno(ations is discussed in Q Template /eta)programming for HaskellQ (6roc Haskell Workshop 5KK5). There is a Wiki page a#out Template Haskell at http0YY$$$.haskell.orgYhaskell$ikiYTemplateJHaskell, and that is the #est place to look for further details. Cou may also consult the online Haskell li#rary reference material (look for module ;an'#a'e=>aske!!=5>). /any changes to the original design are descri#ed in ;otes on Template Haskell (ersion 5. ;ot all of these changes are in PH8, ho$e(er. The first e"ample from that paper is set out #elo$ (*ection V.S.4, & A Template Haskell Worked -"ample ') as a $orked e"ample to help get you started. The documentation here descri#es the realisation of Template Haskell in PH8. It is not detailed enough to understand Template Haskell[ see the Wiki page.

7.9.1. Syntax
Template Haskell has the follo$ing ne$ syntactic constructions. Cou need to use the flag 3&5emp!ate>aske!! to s$itch these syntactic e"tensions on (3&5emp!ate>aske!! is no longer implied #y 3f'!as'o$3exts).

A splice is $ritten ,x, $here x is an identifier, or ,(===), $here the Q...Q is an ar#itrary e"pression. There must #e no space #et$een the Q!Q and the identifier or parenthesis. This use of Q!Q o(errides its meaning as an infi" operator, .ust as Q/."Q o(errides the meaning of Q.Q as an infi" operator. If you $ant the infi" operator, put spaces around it. A splice can occur in place of
o o o

an e"pression[ the spliced e"pression must ha(e type A Exp an type[ the spliced e"pression must ha(e type A 5yp a list of top)le(el declarations[ the spliced e"pression must ha(e type A [<ec]

;ote that pattern splices are not supported. Inside a splice you can can only call functions defined in imported modules, not functions defined else$here in the same module.

A e"pression Fuotation is $ritten in %"ford #rackets, thus0 o [+ === +], or [e+ === +], $here the Q...Q is an e"pression[ the Fuotation has type A Exp.
o [1+ === +], $here the has type A [<ec].

Q...Q is a list of top)le(el declarations[ the Fuotation

4K

o o

[t+ === +], [p+ === +],

$here the Q...Q is a type[ the Fuotation has type A 5ype. $here the Q...Q is a pattern[ the Fuotation has type A (at.

A Fuasi)Fuotation can appear in either a pattern conte"t or an e"pression conte"t and is also $ritten in %"ford #rackets0
o [$arid+ === +],

$here the Q...Q is an ar#itrary string[ a full description of the Fuasi)Fuotation facility is gi(en in *ection V.S.M, & Template Haskell =uasi) Fuotation '.

A name can #e Fuoted $ith either one or t$o prefi" single Fuotes0
o

has type @ame, and names the function f. *imilarly :8 has type @ame and names the data constructor 8. In general :t%ing interprets t%ing in an e"pression conte"t.
:f

has type @ame, and names the type constructor 5. That is, ::t%ing interprets t%ing in a type conte"t.
::5

These @ames can #e used to construct Template Haskell e"pressions, patterns, declarations etc. They may also #e gi(en as an argument to the reify function.

Cou may omit the ,(===) in a top)le(el declaration splice. *imply $riting an e"pression (rather than a declaration) implies a splice. ,or e"ample, you can $rite
mo1#!e Qoo $%ere import 7ar f x x 33 Oses t%e ,(===) notation

,(1eri9e*t#ff :f) ' y y41

1eri9e*t#ff :' % / /31

33 Hmits t%e ,(===)

This a##re(iation makes top)le(el declaration slices Fuieter and less intimidating. (8ompared to the original paper, there are many differences of detail. The synta" for a declaration splice uses Q,Q not Qsp!iceQ. The type of the enclosed e"pression must #e A [<ec], not [A <ec]. 6attern splices and Fuotations are not implemented.)

7.9.2. Using Template Haskell

The data types and monadic constructor functions for Template Haskell are in the li#rary ;an'#a'e=>aske!!=5>*yntax.

4@

Cou can only run a function at compile time if it is imported from another module. That is, you canNt define a function in a module, and call it from $ithin a splice in the same module. (It $ould make sense to do so, #ut itNs hard to implement.) Cou can only run a function at compile time if it is imported from another module that is not part of a mutually"recursive group of modules that includes the module currently being compiled. ,urthermore, all of the modules of the mutually)recursi(e group must #e reacha#le #y non)*%\:8- imports from the module $here the splice is to #e run. ,or e"ample, $hen compiling module A, you can only run Template Haskell functions imported from B if B does not import A (directly or indirectly). The reason should #e clear0 to run B $e must compile and run A, #ut $e are currently type) checking A.

The flag 311#mp3sp!ices sho$s the e"pansion of all top)le(el splices as they happen. If you are #uilding PH8 from source, you need at least a stage)5 #ootstrap compiler to run Template Haskell. A stage)@ compiler $ill re.ect the TH constructs. :eason0 TH compiles and runs a program, and then looks at the result. *o itNs important that the program it compiles produces results $hose representations are identical to those of the compiler itself.

Template Haskell $orks in any mode (33make, 33interacti9e, or file)at)a)time). There used to #e a restriction to the former t$o, #ut that restriction has #een lifted.

7.9.3. A Template Haskell Worked Example


To help you get o(er the confidence #arrier, try out this skeletal $orked e"ample. ,irst cut and paste the t$o modules #elo$ into Q/ain.hsQ and Q6rintf.hsQ0
F3 .ain=%s 3J mo1#!e .ain $%ere 33 Import o#r temp!ate )pr) import (rintf ( pr ) 33 5%e sp!ice operator , takes t%e >aske!! so#rce co1e 33 'enerate1 at compi!e time -y )pr) an1 sp!ices it into 33 t%e ar'#ment of )p#t*tr;n)= main p#t*tr;n ( ,(pr )>e!!o)) ) F3 (rintf=%s 3J mo1#!e (rintf $%ere 33 *ke!eta! printf from t%e paper= 33 It nee1s to -e in a separate mo1#!e to t%e one $%ere 33 yo# inten1 to #se it= 33 Import some 5emp!ate >aske!! syntax import ;an'#a'e=>aske!!=5>

45

33 <escri-e a format strin' 1ata Qormat < + * + ; *trin' 33 (arse a format strin'= 5%is is !eft !ar'e!y to yo# 33 as $e are %ere intereste1 in -#i!1in' o#r first e9er 33 5emp!ate >aske!! pro'ram an1 not in -#i!1in' printf= parse :: *trin' 3> [Qormat] parse s [ ; s ] 33 Ienerate >aske!! so#rce co1e from a parse1 representation 33 of t%e format strin'= 5%is co1e $i!! -e sp!ice1 into 33 t%e mo1#!e $%ic% ca!!s )pr), at compi!e time= 'en :: [Qormat] 3> A Exp 'en [<] [+ \n 3> s%o$ n +] 'en [*] [+ \s 3> s +] 'en [; s] strin'E s 33 33 pr pr >ere $e 'enerate t%e >aske!! co1e for t%e sp!ice from an inp#t format strin'= :: *trin' 3> A Exp s 'en (parse s)

;o$ run the compiler (here $e are a 8yg$in prompt on Windo$s)0


, '%c 33make 3&5emp!ate>aske!! main=%s 3o main=exe

:un Qmain.e"eQ and here is your output0


, =Smain >e!!o

7.9.4. Using Template Haskell

it! "ro#iling

Template Haskell relies on PH8Ns #uilt)in #ytecode compiler and interpreter to run the splice e"pressions. The #ytecode interpreter runs the compiled e"pression on top of the same runtime on $hich PH8 itself is running[ this means that the compiled code referred to #y the interpreted e"pression must #e compati#le $ith this runtime, and in particular this means that o#.ect code that is compiled for profiling cannot #e loaded and used #y a splice e"pression, #ecause profiled o#.ect code is only compati#le $ith the profiling (ersion of the runtime. This causes difficulties if you ha(e a multi)module program containing Template Haskell code and you need to compile it for profiling, #ecause PH8 cannot load the profiled o#.ect code and use it $hen e"ecuting the splices. ,ortunately PH8 pro(ides a $orkaround. The #asic idea is to compile the program t$ice0 @. 8ompile the program or li#rary first the normal $ay, $ithout 3prof. 5. Then compile it again $ith 3prof, and additionally use 3os#f p_o to name the o#.ect files differently (you can choose any suffi" that isnNt the normal o#.ect suffi" here). PH8 $ill automatically load the o#.ect files #uilt in the first step $hen e"ecuting splice e"pressions. If you omit the 3os#f flag $hen #uilding $ith 3prof and Template Haskell is used, PH8 $ill emit an error message.

44

7.9.$. Template Haskell %&asi'(&otation


=uasi)Fuotation allo$s patterns and e"pressions to #e $ritten using programmer)defined concrete synta"[ the moti(ation #ehind the e"tension and se(eral e"amples are documented in QWhy ItNs ;ice to #e =uoted0 =uasiFuoting for HaskellQ (6roc Haskell Workshop 5KKV). The e"ample #elo$ sho$s ho$ to $rite a FuasiFuoter for a simple e"pression language. Here are the salient features

A Fuasi)Fuote has the form [&uoter+ string +]. o The &uoter must #e the (unFualified) name of an imported Fuoter[ it cannot #e an ar#itrary e"pression.
o

The &uoter cannot #e QeQ, QtQ, Q1Q, or QpQ, since those o(erlap $ith Template Haskell Fuotations. There must #e no spaces in the token [&uoter+. The Fuoted string can #e ar#itrary, and may contain ne$lines.

o o

A FuasiFuote may appear in place of


o o o o

An e"pression A pattern A type A top)le(el declaration

(%nly the first t$o are descri#ed in the paper.)


A Fuoter is a (alue of type ;an'#a'e=>aske!!=5>=A#ote=A#asiA#oter, $hich is defined thus0


1ata A#asiA#oter A#asiA#oter F P#oteExp P#ote(at P#ote5ype P#ote<ec :: :: :: :: *trin' *trin' *trin' *trin' 3> 3> 3> 3> A A A A Exp, (at, 5ype, [<ec] J

That is, a Fuoter is a tuple of four parsers, one for each of the conte"ts in $hich a Fuasi)Fuote can occur.

A Fuasi)Fuote is e"panded #y applying the appropriate parser to the string enclosed #y the %"ford #rackets. The conte"t of the Fuasi)Fuote (e"pression, pattern, type, declaration) determines $hich of the parsers is called.

The e"ample #elo$ sho$s Fuasi)Fuotation in action. The Fuoter expr is #ound to a (alue of type A#asiA#oter defined in module Expr. The e"ample makes use of an antiFuoted (aria#le n, indicated #y the synta" :int:n (this synta" for anti)Fuotation $as defined #y the parserNs author, not #y PH8). This #inds n to the integer (alue argument of the constructor IntExpr 4R

$hen pattern matching. 6lease see the referenced paper for further details regarding anti) Fuotation as $ell as the description of a techniFue that uses *CB to le(erage a single parser of type *trin' 3> a to generate #oth an e"pression parser that returns a (alue of type A Exp and a pattern parser that returns a (alue of type A (at. =uasiFuoters must o#ey the same stage restrictions as Template Haskell, e.g., in the e"ample, expr cannot #e defined in .ain=%s $here it is used, #ut must #e imported.
F3 3333333333333 fi!e .ain=%s 333333333333333 3J mo1#!e .ain $%ere import Expr main :: IH () main 1o F print , e9a! [expr+1 4 2+] M case IntExpr 1 of F [expr+:int:n+] 3> print n M _ 3> ret#rn () J J F3 3333333333333 fi!e Expr=%s 333333333333333 3J mo1#!e Expr $%ere import P#a!ifie1 ;an'#a'e=>aske!!=5> as 5> import ;an'#a'e=>aske!!=5>=A#ote 1ata Expr IntExpr Inte'er + 6ntiIntExpr *trin' + 7inopExpr 7inHp Expr Expr + 6ntiExpr *trin' 1eri9in'(*%o$, 5ypea-!e, <ata) 611Hp + *#-Hp + .#!Hp + <i9Hp 1eri9in'(*%o$, 5ypea-!e, <ata) n (op5oQ#n op) (e9a! x) (e9a! y)

1ata 7inHp

e9a! :: Expr 3> Inte'er e9a! (IntExpr n) e9a! (7inopExpr op x y) $%ere op5oQ#n 611Hp (4) op5oQ#n *#-Hp (3) op5oQ#n .#!Hp (T) op5oQ#n <i9Hp 1i9 expr 33 33 33 33 33

A#asiA#oter F P#oteExp

parseExprExp, P#ote(at

parseExpr(at J

(arse an Expr, ret#rnin' its representation as eit%er a A Exp or a A (at= *ee t%e reference1 paper for %o$ to #se *"7 to 1o t%is -y $ritin' a sin'!e parser of type *trin' 3> Expr instea1 of t$o separate parsers=

parseExprExp :: *trin' 3> A Exp parseExprExp ===

4M

parseExpr(at :: *trin' 3> A (at parseExpr(at ===

;o$ run the compiler0


, '%c 33make 3&A#asiA#otes .ain=%s 3o main

:un QmainQ and here is your output0


, =Smain 3 1

4T

Você também pode gostar