7.5. Template Haskell

Template Haskell allows you to do compile-time meta-programming in Haskell. There is a "home page" for Template Haskell at http://www.haskell.org/th/, while the background to the main technical innovations is discussed in "Template Meta-programming for Haskell" (Proc Haskell Workshop 2002).

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.)

7.5.1. Syntax

Template Haskell has the following new syntactic constructions. You need to use the flag -fthto switch these syntactic extensions on (-fth is currently implied by -fglasgow-exts, but you are encouraged to specify it explicitly).

7.5.2. Using Template Haskell

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.5.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.THSyntax

-- 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] -> Expr
gen [D]   = [| \n -> show n |]
gen [S]   = [| \s -> s |]
gen [L s] = string s

-- Here we generate the Haskell code for the splice
-- from an input format string.
pr :: String -> Expr
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