Haskell Templates

Embed Size (px)

Citation preview

  • 8/12/2019 Haskell Templates

    1/36

    Haskell Templates

    PreludeWhen Im read thorough first paper on Template Haskell ( Template metaprogramming forHaskell ), 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#inedtogether. %nly after reading last sections $ith &technical details', I disco ered for myselfho$ this actually $orks and could understand all pre ious &high le el' stuff. I try to readanother papers on TH, #ut they $as no more helpful. *o I decided to $rite my o$n THtutorial + such one, $hich gi es to reader full understanding of $hat he does on each step ofeducation. 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 THTemplate Haskell is macro preprocessor for Haskell, $hose macros are $ritten in Haskellitself, 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 $hatthey $ill #e e aluated at 8%/6I7- TI/- and returned alue $ill #e con erted to ordinaryHaskell code and su#stituted instead of splice construction. unctions used in splicee"pressions must #e defined in another module, imported #y current one, #ecause at themoment of this preprocessing functions defined in current module are not e en compiled.

    The $hole splice e"pression must ha e type into type

  • 8/12/2019 Haskell Templates

    2/36

    such simple representation $ould create pro#lems for code generation and especially for codetransformations. Instead, its a recursi e structure, representing AB*T:A8T *C;TA9T:-- of e"pression. *uch representations are usually resulted from syntactic parsing ofHaskell programs in compliers, program transformation tools and so on. Here it is used fordiametrically 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 generatedcode #ack to source files). /oreo er, Fuotation #rackets [| ... | performs the oppositetransition + they parse ordinary Haskell code and returns -"p structure representing itG *o,

    #efore $riting any programs $e can play a little $ith it0

    80 Haskell? ghci +fth

    ghci? 0m 7anguage.Haskell.TH

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

    ghci? run= [| @ | ??2 print

    7it- (Integer7 @)

    ghci? run= [| " J ? " | ??2 print

    7am- [Dar6 "JK,Wild6 (Dar- "JK)

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

    "JK J ? "JK

    We are use to print the structures #uilt #y [|...| and to con ert thesestructures #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 THde#ugging tools + you can use to see the structure that must #e

    5

  • 8/12/2019 Haskell Templates

    3/36

    returned to generate some 8%L-, and to printout the code that !(macro params...) $ill generate.

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

    data -"p represents Haskell e"pressions

    2 Dar- ;ame < " >

    | 7it- 7it < M or NcN>

    | App- -"p -"p < f " >

    | 7am- [6at -"p < p@ p5 ? e >

    | Tup- [-"p < (e@,e5) >

    | 8ond- -"p -"p -"p < if e@ then e5 else e4 >

    | 7ist- [-"p < [@,5,4 >

    | ...

    data 6at represents Haskell patterns

    2 7it6 7it < M or NcN >

    | Dar6 ;ame < " >

    | Tup6 [6at < (p@,p5) >

    | Wild6 < J >

    | ...

    data 7it represents Haskell literals

    2 8har7 8har Oa

    | *tring7 *tring &string'

    4

  • 8/12/2019 Haskell Templates

    4/36

    | 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, patternsand 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 thesimplest one0 lets define macro &cnst', so that splice !(cnst n str) $ill generate function(lam#da form) $hich accepts (unused) parameters and returns ust . *e erale"amples of code, $hich should #e generated #y this macro0

    !(cnst @ &"') 22? ( J ? &"')

    !(cnst 5 &str') 22? ( J J ? &str')

    !(cnst 4 &hey') 22? ( J J J ? &hey')

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

    ghci? run= [| J ? Q"Q | ??2 print

    7am- [Wild6 (7it- (*tring7 Q"Q))

    ghci? run= [| J J ? QstrQ | ??2 print

    7am- [Wild6,Wild6 (7it- (*tring7 QstrQ))

    R

  • 8/12/2019 Haskell Templates

    5/36

    ghci? run= [| J 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 andcheck that these alues are really representations of code in Fuotation #rackets [|...| . Writingactual code should #e tri ial, please does it yourself and compare results $ith my module(remem#er to use 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 Testin file test.hs)0

    80 Haskell? 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

    J ? Q"Q

    M

  • 8/12/2019 Haskell Templates

    6/36

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

    J 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 , $hich can return any literalconstant + #e it a *tring, 8har or Lou#le. To do it, you should import module7anguage.Haskell.TH.*ynta", $hich contains function . This function con erts Ints,*trings and so on to appropriate alues of type 7it.

  • 8/12/2019 Haskell Templates

    7/36

    At the end of this lesson, I $ill gi e e"ample of module, $hich uses our macro to definefunctions and also prints structure of generated e"pressions. Cou can use such modulesinstead 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 anddynamic variables

    V

  • 8/12/2019 Haskell Templates

    8/36

    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 aluesrepresent aria#les + #oth in patterns and e"pressions. We cant use ust *tring to representthem #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#lenames0

    ne$;ame 00 *tring ? = ;ame

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

    somemacro 2 do ar@ ne$;ame &"'

    ar5 ne$;ame &y'

    return (...)

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

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

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

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

    80 Haskell? ghci +fth

    X

  • 8/12/2019 Haskell Templates

    9/36

    ghci? run= [| (",J,J) ? " | ??2 print

    7am- [Tup6 [Dar6 "JK,Wild6,Wild6 (Dar- "JK)

    ghci? run= [| (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 Tup6creates pattern matching a tuple from list of patterns for indi idual tuple elements. 6leasedra$ attention to the follo$ing + if you need to refer to the same aria#le in different parts ofgenerated code, you must generate its ;ame once #y using ne$;ame and then use returnedalue. Lifferent calls to ne$;ame, e en $ith the same argument, $ill gi e you differentaria#lesG Lont try to generate aria#les for your code in or clausesG

    sel 00 Int ? Int ? = -"p

    sel n m 2 do " 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 " 0 drop (n @) "s

    There are rare cases $hen $e dont need to generate aria#les $ith uniFue names + on thecontrary, $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 enname. This property can #e used to refer to identifiers in outer, hand $ritten code or to linktogether independently generated parts of code. This function, like ne$;ame, returns alueof type ;ame, $hich then can #e used to construct e"pressions, patterns or declarations. Butmk;ame, unlike ne$;ame, dont run in = monad, its a pure function0

    S

  • 8/12/2019 Haskell Templates

    10/36

    mk;ame 00 *tring ? ;ame

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

    80 Haskell? ghci +fth

    ghci? 0m 7anguage.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, fore"ample to refer to identifiers in the outer hand $ritten code or $hen $e use our o$nschemes 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

    80 Haskell? ghci +fth

    ghci? 0m 7anguage.Haskell.TH

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

    "

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

    (",")

    @K

  • 8/12/2019 Haskell Templates

    11/36

    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@ 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 theen ironment $here TH function $as e"ecuted. It includes error reporting and returninginformation 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 tocompletion, #ut has made some calls to report True, the result is discarded and h is run. If F

    @@

  • 8/12/2019 Haskell Templates

    12/36

    runs to completion $ith no error report, h is ignored, and FNs result is the result of the call toreco 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#erof 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 module7anguage.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 $ritingHaskell code itself. Hopefully, there is a method to translate Haskell code into appropriatee"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 [| (",J) ? " |

    sel 5 5 2 [| (J,") ? " |

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

    ...

    @5

  • 8/12/2019 Haskell Templates

    13/36

    =uotation #rackets [|...| compiles as the e"pression of the type $hat is fully eFui alent to pre ious definition.

    *pliced e"pression !" or !(f ...) inside Fuotation #rackets also should #e of type . There is alsoanother interpretation of this process + that Fuotation #rackets are con erted to Haskelle"pression constructing appropriate -"p, $here splice e"pressions are replaced to using ofappropriate aria#les. We can simplify our definition0

    cnst K str 2 [| str |

    cnst n str 2 [| J ? !(cnst (n @) str) |

    I replaced $ith [| str | 0 aria#les not #ound inside Fuotation #rackets are #ound tooutside 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 ertingthem ia function. Also I replaced computation of and splicing its alue insideFuotation #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 $orksGAnd $hat is great + in many cases you can create macros $ithout e er thinking a#outcomple" synta" trees they generateG =uotation #rackets also hide details of using Fuotation

    @4

  • 8/12/2019 Haskell Templates

    14/36

    monad = + spliced e"pressions inside #rackets can ha e type , andaria#les created inside #rackets get its o$n, uniFue names.

    The splice call !(...) and Fuotation #rackets [|...| does the opposite things + former e"ecutescomputation of type , $hile later gets Haskell code as ordinal *tring and con erts this string intoe"pression of type

  • 8/12/2019 Haskell Templates

    15/36

    #ore comple$ e$ample: %ipnuseful to see $hat mk3ip generates for a particular n in understanding ho$ it $orks. Whenapplied 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 !am p"s (caseE (t#p e"s) [m1,m2])

    $%ere

    (p&s, e&s) 'en E x n

    (p"s, e"s) 'en E y n

    (p&*s,e&*s) 'en E xs n

    pcons x xs [p+ x : xs +]

    - [+ (t#p e&s) : (apps(name : e&*s)) +]

    m1 simp!e. (pt#p (/ip0it% pcons p&s p&*s)) -

    m2 simp!e. (pt#p (copies n p$i! )) (con [] )

    #ore comple$ e$ample: printf

    &eneration of declarations and identifiersreification

    @M

  • 8/12/2019 Haskell Templates

    16/36

    \ntil this moment, $e only considered using of TH for generation of some Haskelle"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 togenerate declarations, you must place splice call in the module place $here declarationsallo$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

    @

  • 8/12/2019 Haskell Templates

    17/36

    (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 programmingtechniFues not a aila#le in Haskell itself, such as macrolike e"pansion, user directedoptimi1ation (such as inlining), polytypic programs, generation of supporting data structuresand functions from e"isting data structures and functions. or e"ample, the code

    ye!! fi!e !ine fai! ( (printf Error in fi!e s !ine ) fi!e !ine)

    may #e translated #y TH to

    ye!! fi!e !ine fai! ((\x1 x2 > Error in fi!e 44x144 !ine 44s%o$ x2)

    fi!e !ine)

    As another e"ample, the code

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

    ( eri9e*%o$ 5)

    may #e translated to

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

    instance *%o$ 5

    s%o$ (6 x1 x2) 6 44s%o$ x144 44s%o$ x2

    s%o$ (7 x1) 7 44s%o$ x1

    s%o$ 8 8

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

    In TH, Haskell code generated ust #y ordinary Haskell functions. In order to use TH, youmust 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

  • 8/12/2019 Haskell Templates

    18/36

    =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,

  • 8/12/2019 Haskell Templates

    19/36

    How quotation monad used to supply unique names

    But TH functions are not pure functions returning alues of type Exp . Instead, they arecomputations e"ecuted in special monad = (called &Fuotation monad'), $hich allo$s toautomatically generate uniFue names for aria#les using monadic operationne$@ame::*trin' >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 ::@ame> at ) and e"pressions ( ia ?arE::@ame >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 likerep!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)0mo #!e 5#p!eBep!icate $%ere import ;an'#a'e= aske!!=5 t#p!eBep!icate :: Int > A Expt#p!eBep!icate n o i C ne$@ame x ret#rn ;amE (?ar i ) (5#pE rep!icate n ?arE i )

    or e"ample, call & t#p!eBep!icate 3D returns Exp eFui alent to Haskell e"pression & (\x> (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 arbitraryexpression. There must be no space between the "$" and the identifier or parenthesis. Thisuse 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 [

  • 8/12/2019 Haskell Templates

    20/36

    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 thesame module.

    If you are #uilding PH8 from source, you need at least a stage 5 #ootstrap compilerto run Template Haskell. A stage @ compiler $ill re ect the TH constructs.

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

    F G H 5IH@*_ 8 ft% G Jmo #!e 5est $%ere import 5#p!eBep!icate main o print ( (t#p!eBep!icate 2) 1) prints (1,1) print ( (t#p!eBep!icate K) x ) 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 inmodule Language.Haskell.TH.Lib +. -sing these functions allow to decrease number ofcases 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 needto specify the exact name of variable which must be generated in output code. 1or thesecases, there is a *pure+ function mkName::String->Name . There is also corresponding helper

    function 2 d n s " return (#arE (mkName s)) 3, which returns Exp representing variablewith exact the given name.

    Quotation brackets

    While the Exp can represent any Haskell e"pression, programmatic #uilding of Exp alues isnot so easy $ork. In order to address this pro#lem, Template Haskell supports /uotationbrac4ets , $hich is a $ay to con ert literal Haskell code to data alue representing it. Thereare four types of Fuotation #rackets0

    [+ === +] , $here the Q...Q is an e"pression the Fuotation has type A Exp

    [p+ === +] , $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 A [

  • 8/12/2019 Haskell Templates

    21/36

  • 8/12/2019 Haskell Templates

    22/36

    e"ample Fuotation [+ map +] may #e translated to reference to sym#ol&

  • 8/12/2019 Haskell Templates

    23/36

    get &entry point' to sym#ols ta#le, $hich then can #e used to find information a#out othertypes, constructors, classes related to this identifier. Cou can find definition of type Info inthe module ;an'#a'e= aske!!=5 =*yntax .

    To get a @ame, corresponding to identifier you are interested, you can, theoretically, usefunction mk@ame, #ut this solution is unsafe, #ecause mk@ame returns unFualified name, $hichinterpretation may #e changed depending on conte"t. %n the other side, code & ?arE i C[+ name +] ' is safe, #ecause i $ill #e linked to Fualified name (like&.y=H$n=.o #!e=name '), #ut too er#ose and need monadic conte"t to run. *o, TemplateHaskell supports another light$eight form of Fuotation0 i entifier returns @ame,corresponding to i entifier &!et i name ' is fully eFui alent to & ?arE i C [+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 > Expf (6pp (?ar m) e) + m map ===

    This ne$ form is still a Fuotation construct, ust like [+ 9 +] , and follo$s the same rules asFuotation #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, $hosemeaning $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 distinguishthe type conte"t0

    9 means N5%e name 9 interprete in an expression contextD9 means N5%e name 9 interprete 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 + putdeclaration of this function in Fuotation #rackets and e"plore returned result, like this0

    (optimi/e [ + fi- ==== +])

    or

    fi- (optimi/e [+ ==== +])

    54

    https://doc-0s-9c-docs.googleusercontent.com/docs/securesc/ha0ro937gcuc7l7deffksulhg5h7mbp1/hle6udvh1h09fukrs4mipsqdf2udf7m5/1337659200000/10578434965449041783/*/0B4BgTwf_ng_TM2MxZjJjZjctMTQ0OS00YzcwLWE5N2QtMDI0YzE4NGUwZDM3#_Example:_deriveShowhttps://doc-0s-9c-docs.googleusercontent.com/docs/securesc/ha0ro937gcuc7l7deffksulhg5h7mbp1/hle6udvh1h09fukrs4mipsqdf2udf7m5/1337659200000/10578434965449041783/*/0B4BgTwf_ng_TM2MxZjJjZjctMTQ0OS00YzcwLWE5N2QtMDI0YzE4NGUwZDM3#_Example:_deriveShow
  • 8/12/2019 Haskell Templates

    24/36

  • 8/12/2019 Haskell Templates

    25/36

    === or in t%e form of aske!! co e to see $%at t%e co e $i!! -e 'enerate-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 ) >> p#t*tr;n=pprint

    \_ _ > str

    This techniFue can #e also used in modules $hich imports appropriate definitions offunctions, $ritten in TH, #ut then print results of calls ia print and pprint instead of

    splicing them0

    F G H 5IH@*_ 8 f'!as'o$ exts ft% G Jmo #!e .ain $%ere import ;an'#a'e= aske!!=5import 8nst mo #!e 8nst efines f#nction RcnstR, $%ic% can -e #se in sp!ices:

    cnst1 (cnst 1 x )cnst2 (cnst 2 str )cnst2L (cnst 2L foo ) === -#t $e can a!so r#n RcnstR 9ia r#nA to see %o$ it $orks:

    main o 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

    mo #!e 8nst $%ere

    import ;an'#a'e= aske!!=5 cnst :: Int > *trin' > A Expcnst n s ret#rn (;amE (rep!icate n 0i! ) (;itE (*trin'; s)))

    E ample! printf

    That is the definition of function printf , mentioned earlier, together $ith /ain module $hatuses it. 8ompile $ith Q '%c ft% make .ain=%s '

    F .ain=%s Jmo #!e .ain $%ere

    5M

  • 8/12/2019 Haskell Templates

    26/36

    Import o#r temp!ate printf

    import rintf (printf) 5%e sp!ice operator takes t%e aske!! so#rce co e 'enerate at compi!e time -y printf an sp!ices it into

    t%e ar'#ment of p#t*tr;n =main p#t*tr;n ( (printf Error in fi!e s !ine : s ) io=cpp 32Kprinter not fo#n )

    F rintf=%s Jmo #!e rintf $%ere Import 5emp!ate aske!! interfaces

    import ;an'#a'e= aske!!=5

    [Qormat]parse ( : s :xs) rest ; rest : * : parse xs parse ( : :xs) rest ; rest : < : parse xs parse rest [; rest]parse (x:xs) rest parse xs (rest44[x]) enerate aske!! so#rce co e from a parse representation of t%e format strin'= 5%is co e $i!! -e sp!ice into t%e mo #!e $%ic% ca!!s printf , at compi!e time=

    'en :: [Qormat] > ExpA > ExpA'en [] co e co e'en (< : xs) co e [+ \x > ('en xs [+ co e44s%o$ x +]) +]'en (* : xs) co e [+ \x > ('en xs [+ co e44x +]) +]'en (; s : xs) co e 'en xs [+ co e44s +] ere $e 'enerate t%e aske!! co e for t%e sp!ice from an inp#t format strin'=

    printf :: *trin' > ExpAprintf s 'en (parse s ) [+ +]

    E ample! derive"how

    This is the minimal e"ample $hich sho$s ho$ TH can #e used to automatically generateclass instances. It uses type notation and reify function to generate *%o$ instance forgi en data type. To simplify code, I dont handle here parametric types, types $ith namedfields and other &comple"' types.

    F .ain=%s J

    5

  • 8/12/2019 Haskell Templates

    27/36

    mo #!e .ain $%ere

    import >

    F

  • 8/12/2019 Haskell Templates

    28/36

    et 9aria-!es for !eft an ri'%t si e of f#nction efinition

    (pats,9ars) C 'en E (!en't% fie! s)

    Bec#rsi9e!y -#i! ( 44s%o$ x144===44 ) expression from[x1===] 9aria-!es !ist

    !et f [] [+ +]

    f (9:9ars) [+ 44 s%o$ 9 44 (f 9ars) +]

    enerate f#nction c!a#se for one constr#ctor

    c!a#se [con name pats] (6 x1x2)

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

    .ake -o y for f#nction Rs%o$R:

    s%o$ (6 x1 x2) 6 44s%o$ x144 44s%o$ x2

    s%o$ (7 x1) 7 44s%o$ x1

    s%o$ 8 8

    s%o$-o y C map. s%o$8!a#se constr#ctors

    enerate temp!ate instance ec!aration an t%en rep!ace

    type name (51) an f#nction -o y (\x > text ) $it% o#r ata

    C [ + instance *%o$ 51 $%ere

    s%o$ x text

    +]

    !et [Instance< [] (6pp5 s%o$t (8on5 _51)) [Q#n< s%o$f _text]]

    ret#rn [Instance< [] (6pp5 s%o$t (8on5 t )) [Q#n< s%o$f s%o$-o y]]

    enerate n #niP#e 9aria-!es an ret#rn t%em in form of patterns anexpressions

    5X

  • 8/12/2019 Haskell Templates

    29/36

    'en E n o

    i s C rep!icate. n (ne$@ame x )

    ret#rn (map 9ar i s, map 9arE i s)

    5S

  • 8/12/2019 Haskell Templates

    30/36

    #$%$ 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 Haskell Q (6roc Haskell Workshop 5KK5).

    There is a Wiki page a#out Template Haskell athttp0YY$$$.haskell.orgYhaskell$ikiYTemplateJHaskell , and that is the #est place to look forfurther details. Cou may also consult the online Haskell li#rary reference material (look formodule ;an'#a'e= aske!!=5 ). /any changes to the original design are descri#ed in ;oteson 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 HaskellWorked -"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 notdetailed 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&5emp!ate aske!! to s$itch these syntactic e"tensions on ( &5emp!ate aske!! is nolonger implied #y f'!as'o$ exts ).

    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/."Qo errides the meaning of Q.Q as an infi" operator. If you $ant the infi" operator, putspaces around it.

    A splice can occur in place of

    o an e"pression the spliced e"pression must ha e type A Expo an type the spliced e"pression must ha e type A 5yp

    o a list of top le el declarations the spliced e"pression must ha e type A [

  • 8/12/2019 Haskell Templates

    31/36

    o [t+ === +] , $here the Q...Q is a type the Fuotation has type A 5ype .

    o [p+ === +] , $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 andis also $ritten in %"ford #rackets0

    o [ arid + === +] , $here the Q...Q is an ar#itrary string a full description of theFuasi Fuotation facility is gi en in *ection V.S.M, & Template Haskell =uasiFuotation ' .

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

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

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

    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 ane"pression (rather than a declaration) implies a splice. or e"ample, you can $rite

    mo #!e Qoo $%ere

    import 7ar

    f x x

    ( eri9e*t#ff f) Oses t%e (===) notation

    ' y y41

    eri9e*t#ff ' Hmits t%e (===)

    % / / 1

    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 adeclaration splice uses Q Q not Qsp!ice Q. The type of the enclosed e"pression must #e A[

  • 8/12/2019 Haskell Templates

    32/36

    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 thesame 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 modulecurrently being compiled . urthermore, all of the modules of the mutually recursi egroup must #e reacha#le #y non *%\:8- imports from the module $here the spliceis to #e run.

    or e"ample, $hen compiling module A, you can only run Template Haskellfunctions imported from B if B does not import A (directly or indirectly). The reasonshould #e clear0 to run B $e must compile and run A, #ut $e are currently typechecking A.

    The flag #mp sp!ices sho$s the e"pansion of all top le el splices as theyhappen.

    If you are #uilding PH8 from source, you need at least a stage 5 #ootstrap compilerto run Template Haskell. A stage @ compiler $ill re ect the TH constructs. :eason0TH compiles and runs a program, and then looks at the result. *o itNs important thatthe program it compiles produces results $hose representations are identical to thoseof the compiler itself.

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

    7.9.3. A Template Haskell Worked ExampleTo help you get o er the confidence #arrier, try out this skeletal $orked e"ample. irst cutand paste the t$o modules #elo$ into Q/ain.hsQ and Q6rintf.hsQ0

    F .ain=%s Jmo #!e .ain $%ere

    Import o#r temp!ate primport rintf ( pr )

    5%e sp!ice operator takes t%e aske!! so#rce co e 'enerate at compi!e time -y pr an sp!ices it into t%e ar'#ment of p#t*tr;n =

    main p#t*tr;n ( (pr e!!o ) )

    F rintf=%s Jmo #!e rintf $%ere

    *ke!eta! printf from t%e paper= It nee s to -e in a separate mo #!e to t%e one $%ere yo# inten to #se it=

    Import some 5emp!ate aske!! syntaximport ;an'#a'e= aske!!=5

    45

  • 8/12/2019 Haskell Templates

    33/36

    [Qormat]parse s [ ; s ]

    enerate aske!! so#rce co e from a parse representation of t%e format strin'= 5%is co e $i!! -e sp!ice into t%e mo #!e $%ic% ca!!s pr , at compi!e time=

    'en :: [Qormat] > A Exp'en [ s%o$ n +]'en [*] [+ \s > s +]'en [; s] strin'E s

    ere $e 'enerate t%e aske!! co e for t%e sp!ice from an inp#t format strin'=

    pr :: *trin' > A Exppr s 'en (parse s)

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

    '%c make &5emp!ate aske!! main=%s o main=exe

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

    =Smaine!!o

    7.9.4. Using Template Haskell it! "ro#iling

    Template Haskell relies on PH8Ns #uilt in #ytecode compiler and interpreter to run the splicee"pressions. The #ytecode interpreter runs the compiled e"pression on top of the sameruntime on $hich PH8 itself is running this means that the compiled code referred to #y theinterpreted e"pression must #e compati#le $ith this runtime, and in particular this means thato# 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 Haskellcode and you need to compile it for profiling, #ecause PH8 cannot load the profiled o# ectcode 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 prof .

    5. Then compile it again $ith prof , and additionally use os#f p_o to name the o# ectfiles 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"ecutingsplice e"pressions. If you omit the os#f flag $hen #uilding $ith prof andTemplate Haskell is used, PH8 $ill emit an error message.

    44

  • 8/12/2019 Haskell Templates

    34/36

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

    =uasi Fuotation allo$s patterns and e"pressions to #e $ritten using programmer definedconcrete synta" the moti ation #ehind the e"tension and se eral e"amples are documented inQWhy ItNs ;ice to #e =uoted0 =uasiFuoting for Haskell Q (6roc Haskell Workshop 5KKV). Thee"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 Qe Q, Qt Q, QQ, or QpQ, since those o erlap $ith TemplateHaskell Fuotations.

    o There must #e no spaces in the token [ &uoter +.

    o The Fuoted string can #e ar#itrary, and may contain ne$lines.

    A FuasiFuote may appear in place of

    o An e"pression

    o A pattern

    o A type

    o 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 isdefined thus0

    ata A#asiA#oter A#asiA#oter F P#oteExp :: *trin' > A Exp, P#ote at :: *trin' > A at, P#ote5ype :: *trin' > A 5ype, P#ote

  • 8/12/2019 Haskell Templates

    35/36

    $hen pattern matching. 6lease see the referenced paper for further details regarding antiFuotation as $ell as the description of a techniFue that uses *CB to le erage a single parserof type *trin' > 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.

    F fi!e .ain=%s Jmo #!e .ain $%ere

    import Expr

    main :: IH ()main o F print e9a! [expr+1 4 2+] M case IntExpr 1 of F [expr+ int:n+] > print n

    M _ > ret#rn () J J

    F fi!e Expr=%s Jmo #!e Expr $%ere

    import P#a!ifie ;an'#a'e= aske!!=5 as 5import ;an'#a'e= aske!!=5 =A#ote

    ata Expr IntExpr Inte'er + 6ntiIntExpr *trin' + 7inopExpr 7inHp Expr Expr + 6ntiExpr *trin' eri9in'(*%o$, 5ypea-!e,

  • 8/12/2019 Haskell Templates

    36/36

    parseExpr at :: *trin' > A atparseExpr at ===

    ;o$ run the compiler0

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

    :un QmainQ and here is your output0

    =Smain31