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/th/, and that is the best place to look for further details. You may also consult the online Haskell library reference material (search for the type ExpQ). [Temporary: many changes to the original design are described in "http://research.microsoft.com/~simonpj/tmp/notes2.ps". Not all of these changes are in GHC 6.6.]
The first example from that paper is set out below as a worked example to help get you started.
The documentation here describes the realisation in GHC. (It's rather sketchy just now; Tim Sheard is going to expand it.)
Template Haskell has the following new syntactic
constructions. You need to use the flag
-fth
to switch these syntactic extensions on
(-fth
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 list of top-level declarations; ; the spliced expression must have type Q [Dec]
[Planned, but not implemented yet.] a
type; the spliced expression must have type Q Typ
.
(Note that the syntax for a declaration splice uses "$
" not "splice
" as in
the paper. Also the type of the enclosed expression must be Q [Dec]
, not [Q Dec]
as in the paper.)
A expression quotation is written in Oxford brackets, thus:
[| ... |]
, where the "..." is an expression;
the quotation has type Expr
.
[d| ... |]
, where the "..." is a list of top-level declarations;
the quotation has type Q [Dec]
.
[Planned, but not implemented yet.] [t| ... |]
, where the "..." is a type;
the quotation has type Type
.
Reification is written thus:
reifyDecl T
, where T
is a type constructor; this expression
has type Dec
.
reifyDecl C
, where C
is a class; has type Dec
.
reifyType f
, where f
is an identifier; has type Typ
.
Still to come: fixities
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.)
Furthermore, 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. 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.
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] -> ExpQ 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 -> ExpQ pr s = gen (parse s)
Now run the compiler (here we are a Cygwin prompt on Windows):
$ ghc --make -fth main.hs -o main.exe
Run "main.exe" and here is your output:
$ ./main Hello
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:
Compile the program or library first the normal way, without
-prof
.
Then compile it again with -prof
, and
additionally use -osuf
p_o
to name the object files differentliy (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.