7.15. Template Haskell

Template Haskell allows you to do compile-time meta-programming in Haskell. The background to the main technical innovations is discussed in " Template Meta-programming for Haskell" (Proc Haskell Workshop 2002).

There is a Wiki page about Template Haskell at http://www.haskell.org/haskellwiki/Template_Haskell, and that is the best place to look for further details. You may also consult the online Haskell library reference material (look for module Language.Haskell.TH). Many changes to the original design are described in Notes on Template Haskell version 2. Not all of these changes are in GHC, however.

The first example from that paper is set out below (Section 7.15.3, “ A Template Haskell Worked Example ”) as a worked example to help get you started.

The documentation here describes the realisation of Template Haskell in GHC. It is not detailed enough to understand Template Haskell; see the Wiki page.

7.15.1. Syntax

Template Haskell has the following new syntactic constructions. You need to use the flag -XTemplateHaskell to switch these syntactic extensions on (-XTemplateHaskell is no longer implied by -fglasgow-exts).

  • 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. If you want the infix operator, put spaces around it.

    A splice can occur in place of

    • an expression; the spliced expression must have type Q Exp

    • a pattern; the spliced pattern must have type Q Pat

    • a type; the spliced expression must have type Q Type

    • a list of declarations; the spliced expression must have type Q [Dec]

    Inside a splice you can only call functions defined in imported modules, not functions defined elsewhere in the same module.

  • A expression quotation is written in Oxford brackets, thus:

    • [| ... |], or [e| ... |], where the "..." is an expression; the quotation has type Q Exp.

    • [d| ... |], where the "..." is a list of top-level declarations; the quotation has type Q [Dec].

    • [t| ... |], where the "..." is a type; the quotation has type Q Type.

    • [p| ... |], where the "..." is a pattern; the quotation has type Q Pat.

  • A typed expression splice is written $$x, where x is an identifier, or $$(...), where the "..." is an arbitrary expression.

    A typed expression splice can occur in place of an expression; the spliced expression must have type Q (TExp a)

  • A typed expression quotation is written as [|| ... ||], or [e|| ... ||], where the "..." is an expression; if the "..." expression has type a, then the quotation has type Q (TExp a).

    Values of type TExp a may be converted to values of type Exp using the function unType :: TExp a -> Exp.

  • A quasi-quotation can appear in either a pattern context or an expression context and is also written in Oxford brackets:

  • A name can be quoted with either one or two prefix single quotes:

    • 'f has type Name, and names the function f. Similarly 'C has type Name and names the data constructor C. In general 'thing interprets thing in an expression context.

      A name whose second character is a single quote (sadly) cannot be quoted in this way, because it will be parsed instead as a quoted character. For example, if the function is called f'7 (which is a legal Haskell identifier), an attempt to quote it as 'f'7 would be parsed as the character literal 'f' followed by the numeric literal 7. There is no current escape mechanism in this (unusual) situation.

    • ''T has type Name, and names the type constructor T. That is, ''thing interprets thing in a type context.

    These Names can be used to construct Template Haskell expressions, patterns, declarations etc. They may also be given as an argument to the reify function.

  • You may omit the $(...) in a top-level declaration splice. Simply writing an expression (rather than a declaration) implies a splice. For example, you can write

    module Foo where
    import Bar
    
    f x = x
    
    $(deriveStuff 'f)   -- Uses the $(...) notation
    
    g y = y+1
    
    deriveStuff 'g      -- Omits the $(...)
    
    h z = z-1
    

    This abbreviation makes top-level declaration slices quieter and less intimidating.

  • Binders are lexically scoped. For example, consider the following code, where a value g of type Bool -> Q Pat is in scope, having been imported from another module

    y :: Int
    y = 7
    
    f :: Int -> Int -> Int
    f n = \ $(g True) -> y+n
    

    The y in the right-hand side of f refers to the top-level y = 7, even if the pattern splice $(g n) also generates a binder y.

    Note that a pattern quasiquoter may generate binders that scope over the right-hand side of a definition because these binders are in scope lexically. For example, given a quasiquoter haskell that parses Haskell, in the following code, the y in the right-hand side of f refers to the y bound by the haskell pattern quasiquoter, not the top-level y = 7.

    y :: Int
    y = 7
    
    f :: Int -> Int -> Int
    f n = \ [haskell|y|] -> y+n
    

  • The type environment seen by reify includes all the top-level declaration up to the end of the immediately preceding declaration group, but no more.

    A declaration group is the group of declarations created by a top-level declaration splice, plus those following it, down to but not including the next top-level declaration splice. The first declaration group in a module includes all top-level definitions down to but not including the first top-level declaration splice.

    Concretely, consider the following code

    module M where
       import ...
       f x = x
       $(th1 4)
       h y = k y y $(blah1)
       $(th2 10)
       w z = $(blah2)
    

    In this example

    1. A reify inside the splice $(th1 ..) would see the definition of f.

    2. A reify inside the splice $(blah1) would see the definition of f, but would not see the definition of h.

    3. A reify inside the splice $(th2..) would see the definition of f, all the bindings created by $(th1..), and the definition of h.

    4. A reify inside the splice $(blah2) would see the same definitions as the splice $(th2...).

(Compared to the original paper, there are many differences of detail. The syntax for a declaration splice uses "$" not "splice". The type of the enclosed expression must be Q [Dec], not [Q Dec]. Typed expression splices and quotations are supported.)

7.15.2.  Using Template Haskell

  • The data types and monadic constructor functions for Template Haskell are in the library Language.Haskell.THSyntax.

  • You can only run a function at compile time if it is imported from another module. That is, you can't define a function in a module, and call it from within a splice in the same module. (It would make sense to do so, but it's hard to implement.)

  • You 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. Furthermore, all of the modules of the mutually-recursive group must be reachable by non-SOURCE imports from the module where the splice is to be run.

    For example, when 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 be clear: to run B we must compile and run A, but we are currently type-checking A.

  • The flag -ddump-splices shows the expansion of all top-level splices as they happen.

  • If you are building GHC from source, you need at least a stage-2 bootstrap compiler to run Template Haskell. A stage-1 compiler will reject the TH constructs. Reason: TH compiles and runs a program, and then looks at the result. So it's important that the program it compiles produces results whose representations are identical to those of the compiler itself.

Template Haskell works in any mode (--make, --interactive, or file-at-a-time). There used to be a restriction to the former two, but that restriction has been lifted.

7.15.3.  A Template Haskell Worked Example

To help you get over the confidence barrier, try out this skeletal worked example. First cut and paste the two modules below into "Main.hs" and "Printf.hs":


{- Main.hs -}
module Main where

-- Import our template "pr"
import Printf ( pr )

-- The splice operator $ takes the Haskell source code
-- generated at compile time by "pr" and splices it into
-- the argument of "putStrLn".
main = putStrLn ( $(pr "Hello") )


{- Printf.hs -}
module Printf where

-- Skeletal printf from the paper.
-- It needs to be in a separate module to the one where
-- you intend to use it.

-- Import some Template Haskell syntax
import Language.Haskell.TH

-- Describe a format string
data Format = D | S | L String

-- Parse a format string.  This is left largely to you
-- as we are here interested in building our first ever
-- Template Haskell program and not in building printf.
parse :: String -> [Format]
parse s   = [ L s ]

-- Generate Haskell source code from a parsed representation
-- of the format string.  This code will be spliced into
-- the module which calls "pr", at compile time.
gen :: [Format] -> Q Exp
gen [D]   = [| \n -> show n |]
gen [S]   = [| \s -> s |]
gen [L s] = stringE s

-- Here we generate the Haskell code for the splice
-- from an input format string.
pr :: String -> Q Exp
pr s = gen (parse s)

Now run the compiler (here we are a Cygwin prompt on Windows):

$ ghc --make -XTemplateHaskell main.hs -o main.exe

Run "main.exe" and here is your output:

$ ./main
Hello

7.15.4. Using Template Haskell with Profiling

Template Haskell relies on GHC's built-in bytecode compiler and interpreter to run the splice expressions. The bytecode interpreter runs the compiled expression on top of the same runtime on which GHC itself is running; this means that the compiled code referred to by the interpreted expression must be compatible with this runtime, and in particular this means that object code that is compiled for profiling cannot be loaded and used by a splice expression, because profiled object code is only compatible with the profiling version of the runtime.

This causes difficulties if you have a multi-module program containing Template Haskell code and you need to compile it for profiling, because GHC cannot load the profiled object code and use it when executing the splices. Fortunately GHC provides a workaround. The basic idea is to compile the program twice:

  1. Compile the program or library first the normal way, without -prof.

  2. Then compile it again with -prof, and additionally use -osuf p_o to name the object files differently (you can choose any suffix that isn't the normal object suffix here). GHC will automatically load the object files built in the first step when executing splice expressions. If you omit the -osuf flag when building with -prof and Template Haskell is used, GHC will emit an error message.

7.15.5.  Template Haskell Quasi-quotation

Quasi-quotation allows patterns and expressions to be written using programmer-defined concrete syntax; the motivation behind the extension and several examples are documented in "Why It's Nice to be Quoted: Quasiquoting for Haskell" (Proc Haskell Workshop 2007). The example below shows how to write a quasiquoter for a simple expression language.

Here are the salient features

  • A quasi-quote has the form [quoter| string |].

    • The quoter must be the (unqualified) name of an imported quoter; it cannot be an arbitrary expression.

    • The quoter cannot be "e", "t", "d", or "p", since those overlap with Template Haskell quotations.

    • There must be no spaces in the token [quoter|.

    • The quoted string can be arbitrary, and may contain newlines.

    • The quoted string finishes at the first occurrence of the two-character sequence "|]". Absolutely no escaping is performed. If you want to embed that character sequence in the string, you must invent your own escape convention (such as, say, using the string "|~]" instead), and make your quoter function interpret "|~]" as "|]". One way to implement this is to compose your quoter with a pre-processing pass to perform your escape conversion. See the discussion in Trac for details.

  • A quasiquote may appear in place of

    • An expression

    • A pattern

    • A type

    • A top-level declaration

    (Only the first two are described in the paper.)

  • A quoter is a value of type Language.Haskell.TH.Quote.QuasiQuoter, which is defined thus:

    data QuasiQuoter = QuasiQuoter { quoteExp  :: String -> Q Exp,
                                     quotePat  :: String -> Q Pat,
                                     quoteType :: String -> Q Type,
                                     quoteDec  :: String -> Q [Dec] }
    

    That is, a quoter is a tuple of four parsers, one for each of the contexts in which a quasi-quote can occur.

  • A quasi-quote is expanded by applying the appropriate parser to the string enclosed by the Oxford brackets. The context of the quasi-quote (expression, pattern, type, declaration) determines which of the parsers is called.

The example below shows quasi-quotation in action. The quoter expr is bound to a value of type QuasiQuoter defined in module Expr. The example makes use of an antiquoted variable n, indicated by the syntax 'int:n (this syntax for anti-quotation was defined by the parser's author, not by GHC). This binds n to the integer value argument of the constructor IntExpr when pattern matching. Please see the referenced paper for further details regarding anti-quotation as well as the description of a technique that uses SYB to leverage a single parser of type String -> a to generate both an expression parser that returns a value of type Q Exp and a pattern parser that returns a value of type Q Pat.

Quasiquoters must obey the same stage restrictions as Template Haskell, e.g., in the example, expr cannot be defined in Main.hs where it is used, but must be imported.

{- ------------- file Main.hs --------------- -}
module Main where

import Expr

main :: IO ()
main = do { print $ eval [expr|1 + 2|]
          ; case IntExpr 1 of
              { [expr|'int:n|] -> print n
              ;  _              -> return ()
              }
          }


{- ------------- file Expr.hs --------------- -}
module Expr where

import qualified Language.Haskell.TH as TH
import Language.Haskell.TH.Quote

data Expr  =  IntExpr Integer
           |  AntiIntExpr String
           |  BinopExpr BinOp Expr Expr
           |  AntiExpr String
    deriving(Show, Typeable, Data)

data BinOp  =  AddOp
            |  SubOp
            |  MulOp
            |  DivOp
    deriving(Show, Typeable, Data)

eval :: Expr -> Integer
eval (IntExpr n)        = n
eval (BinopExpr op x y) = (opToFun op) (eval x) (eval y)
  where
    opToFun AddOp = (+)
    opToFun SubOp = (-)
    opToFun MulOp = (*)
    opToFun DivOp = div

expr = QuasiQuoter { quoteExp = parseExprExp, quotePat =  parseExprPat }

-- Parse an Expr, returning its representation as
-- either a Q Exp or a Q Pat. See the referenced paper
-- for how to use SYB to do this by writing a single
-- parser of type String -> Expr instead of two
-- separate parsers.

parseExprExp :: String -> Q Exp
parseExprExp ...

parseExprPat :: String -> Q Pat
parseExprPat ...

Now run the compiler:

$ ghc --make -XQuasiQuotes Main.hs -o main

Run "main" and here is your output:

$ ./main
3
1