Template Haskell

Template haskell has been one of those things that I have always wanted to learn, but every time I opened a wiki page I lost the will to live with confusion. Each document and tutorial would go on and on about monadic functions to manipulate the raw abstract syntax tree of my haskell document, it all seemed very… un-haskly. But it turns out, if you keep google, eventually you will find some sources that give you the easy option. In this article I will go through template haskell and, unliek the other sources I could easily find, it will be both typed and look like haskell code and not gibberish! All credit should go to this youtube video.

First Steps

To begin with, lets look at the following function:

power5 :: Int -> Int
power5 k = k * k * k * k * k

It is pretty self-explanatory, $power5 : x \mapsto x^5$. It isn’t very general though. I could write the following to make it general:

power 0 k = 1
power n k = k * power (n - 1) k

but this function is far less optimal. Can I make a general version of the one above? Yes! With template haskell! Template haskell is a way of writing haskell code whoch is run at compile time. Here we will use it to generate our general haskell function:

{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH

power :: Int -> ExpQ
power 0 = [| \k -> 1 |]
power n = [| \k -> k * $(power (n - 1)) k |]

power5 = $(power 5)

A lot is going on here. The first thing to note is that we had to enable the template haskell language extention. We have introduced two new bits of syntax, [| |] and $() The first is used to take haskell code and turn it into a code form. The second runs the code form. From this you should be able to work out how it works. “But it isn’t typed!” I hear you cry. Don’t worry! There is a typed version too:

{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH

power :: Int -> TExpQ Int
power 0 = [|| \k -> 1 ||]
power n = [|| \k -> k * $$(power (n - 1)) k ||]

power5 = $$(power 5)

And thats basically it! A typed template haskell! So lets take this to the next level.

QuasiQuotes

I will introduce you to another part of template haskell called QuasiQuotations. It is used in a number of libraries in super cool ways. inline-c allows you to write c code inside your haskell source, massively simplifying the ffi. The example they provide on hackage is:

{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}

import qualified Language.C.Inline as C

C.include "<math.h>"

main :: IO ()
main = do
  x <- [C.exp| double{ cos(1) } |]
  print x

Pretty damn cool if you ask me! In normal template haskell, haskell code is parsed by splicing, but that need not be the case. In this library, we have a parser, C.exp that parses c code.

We will make a quasiquote that adds numbers separated by spaces: [adder| 1 2 3 |] => 6. Yeah… not quite as cool as inline-c but you have to start somewhere! We have to make a new haskell file, for some reason, QuasiQuotatins requires the quoter thingy to be defined in another file so I have made one called Adder.hs. The file will begin in the usual way with certain language extensions and imports:

{-# LANGUAGE TemplateHaskell #-}

module Adder (adder) where

import Language.Haskell.TH
import Language.Haskell.TH.Quote

To make a quoter, we have to write the following:

adder = QuasiQuoter { quoteExp = quoteE, quotePat = quoteP,
                                 quoteType = quoteT, quoteDec = quoteD }

I’m not going to go into what quotePat, quoteType and quoteDec mean… we will just ignore them and put up with the warnings.

We have to define a function, quoteE :: String -> ExpQ. It is basically a compiler from string input to the haskell syntax tree representation.

toCode :: [Int] -> TExpQ Int
toCode []     = [|| 0 ||]
toCode (x:xs) = [|| x + $$(toCode xs) ||]

parser' :: String -> TExpQ Int
parser' = toCode . map (read :: String -> Int) . words 

parser s = parser' s >>= return . unType

adder = QuasiQuoter { quoteExp = parser }

parser takes out string and split it into a list of integers and sends that off to toCode. This function changes it to a typed template of the code that adds those integers. We then use unType to make the types all match up and that’s about it! Job done! in Main.hs we can now user adder, pointlessly, to add integers!

It may have been a useless example, but I hope it shows you what you need to build some really cool haskell libraries with eDSLs and other fun things!

James