A Template Haskell Adventure
Oh no! Evil forces from the Intergalactic Federation for the Advancement of Finite Heterogeneous Data Structures of Length No More Than Sixty-Two have captured us! They want us to rewrite some basic list functions from Haskell’s Prelude to work on tuples instead of lists.
Begrudgingly, we learn the strange layouts of their alien keyboards (is that Colemak?!) and get to typing:
head (Unit x1) = x1
head (x1, x2) = x1
head (x1, x2, x3) = x1
head (x1, x2, x3, x4) = x1
head (x1, x2, x3, x4, x5) = x1
Luckily, we’ve remembered that GHC.Tuple
exports Unit
(defined as data Unit = Unit a
), so we don’t miss the 1
case and anger our captors. It’s also nice that we don’t have to error out on an empty list, since we can just leave head ()
undefined. However, the work is very slow going. How many of these are we going to have to write? It seems tuples are defined up to length 62, which we can verify with ghci.
λ :t (1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,51,52,53,54,55,56,57,58,59,60,61,62,63)
<interactive>:1:1: error:
A 63-tuple is too large for GHC
(max size is 62)
Workaround: use nested tuples or define a data type
That’s a lot of tuple typing. After lengthy negotiations, we finally convince the Federation forces to let us use Template Haskell to reduce the amount of redundant boilerplate. We also decide to call Template Haskell “TH” to reduce the amount of redundant boilerplate.
Because TH bubbles up a stage restriction error otherwise, we know we’ll need a separate module to import from. Let’s name it after what we wish we had in this situation: Helpers
.
{-# LANGUAGE TemplateHaskell #-}
module Helpers where
import Language.Haskell.TH
import Control.Monad
Splices (which look like $( ... )
) will go in Main
and everything else in Helpers
.
Now, let’s get back to defining head
. We want to be able to vary the tuple length across several functions, so we’ll take an Int
argument. Since we’re defining an expression, we’ll use the Exp
type.
Exp
gives us various options to choose from. We’re trying to build a function here, so let’s use LamE
, the lambda constructor. LamE
takes a list of patterns to match against, and an expression to run.
The expression is relatively straightforward. Assuming we name the first element of our tuples x1
, as above, we just need to pass back a single-variable expression. VarE
does this, taking a Name
. For now, let’s create that name via mkName "x1"
.
We still need the pattern match argument to LamE
. Just as we had VarE
construct an x1
variable expression, we can use VarP
to construct an x1
variable pattern match. Once we have our variable patterns from x1
to xN
, we can combine them with TupP
. Because it seems likely we’ll want to keep naming tuples, let’s build helper functions to do all this.
names :: Int -> Int -> [Name]
names a b = map (mkName . ('x':) . show) [a..b]
namedTupleP :: Int -> Pat
namedTupleP n = TupP . map VarP $ names 1 n
Then, we can test that names
properly builds names from x1
to xN
, and that namedTupleP
produces the equivalent of a (x1, x2, x3...)
pattern match in ghci.
λ names 1 10
[x1,x2,x3,x4,x5,x6,x7,x8,x9,x10]
λ namedTupleP 5
TupP [VarP x1,VarP x2,VarP x3,VarP x4,VarP x5]
Coming back to defining headN
, we now have a complete Exp
.
To actually use this, though, we’ll want to write a splice like $(headN 3) (1, 2, 3)
. These splices expect things wrapped up in the Q
monad, though. We could use pure
directly, as in $(pure $ headN 3) (1, 2, 3)
. Alternatively, we can alter the definition of headN
just a little a bit, and continue to use $(headN 3) (1, 2, 3)
.
The Federation representatives seem less angry than before, but are discussing something earnestly….
“Not good enough” is the verdict. Alien programmers don’t want to use such a…human-looking language, with strange $(headN 3)
syntax everywhere. They’d much rather call functions like head3
directly. For this, we need some code that uses code that writes code to write code.
We know head
is only viable on tuples of size 1 or greater, but there are other functions that might take a size-zero tuple ()
, so let’s pass a startingTupleSize
argument. Passing a name prefix (the head
in head3
) lets us name our functions, and we have headN :: Int -> Q Exp
, to pass as the third argument. rangeOverTuples
gives us back a list of declarations—the functions head1
to headN
.
rangeOverTuples :: Int -> String -> (Int -> Q Exp) -> Q [Dec]
rangeOverTuples startingTupleSize funcName funcForTupleSize =
undefined
Usage of this will look like
To be able to see what code TH is actually generating, from now on we’ll dump splices via ghc Main -ddump-splices
. For now, let’s set maxTupleSize
to 5
to keep dumped splices easier to read, with the intention of bumping it back up to 62 once we’re done fiddling with definitions.
We can begin to fill out the body of rangeOverTuples
by mapping over tuple sizes from the start to the max.
Grab the Exp
from our funcForTupleSize :: Int -> Q Exp
And also make a name, like head5
With these pieces in place, we can construct a function declaration with FunD
. It takes a Name
and a list of Clause
s. Looking at Clause [Pat] Body [Dec]
we see we can pass in a list of patterns, but we’ve actually already done that in headN
’s LamE
. To keep things simple, stick with the lambda’s pattern match for now. We also don’t have any extra declarations here, since the lambda does everything we need it to do. We do need a Body
. Because there are no guards, we can use NormalB
(rather than GuardedB
) and our existing currentFunc
.
Putting it all together, we get
rangeOverTuples :: Int -> String -> (Int -> Q Exp) -> Q [Dec]
rangeOverTuples startingTupleSize funcName funcForTupleSize =
forM [startingTupleSize..maxTupleSize] $ \tupleSize -> do
currentFunc <- funcForTupleSize tupleSize
let name = mkName $ funcName ++ show tupleSize
pure $ FunD name [Clause [] (NormalB currentFunc) []]
Now, when we splice this in:
…we get all the functions head1
through head5
in scope. After some tiny formatting liberties are taken, we can read the generated code fairly easily:
head1 = \ Unit x1 -> x1
head2 = \ (x1, x2) -> x1
head3 = \ (x1, x2, x3) -> x1
head4 = \ (x1, x2, x3, x4) -> x1
head5 = \ (x1, x2, x3, x4, x5) -> x1
We’ve built up quite the toolkit for replacing just one Prelude function! Let’s get started on a few more.
After head
, tail
is fairly natural. The trickiest part is that now instead of a single VarE
, we have to return a TupE
. We can hijack names
to get the correct list of names for this, but will need to write our own tupleE
.
tupleE
gets a list of names, turns them into VarE
, and turns the list into a tuple via TupE
. There’s really just one catch here, which is that TupE
acts on a list of Maybe Exp
as of TH 2.16.0, but acted directly on lists of Exp
before then. (It was changed to support tuple sections.)
If needed, we could use the CPP extension to conditionally support this behavior based on TH version. However, for simplicity, I’ll just assume we’re both on a recent enough version.
#if MIN_VERSION_template_haskell(2,16,0)
preTupE :: a -> Maybe a
preTupE = Just
#else
preTupE :: a -> a
preTupE = id
#endif
Like head
, tail
is partial on empty lists. So, we only generate tailN
where N
is 1 or greater. That’s all there is to it!
The generated code looks good to me:
tail1 = \ Unit x1 -> ()
tail2 = \ (x1, x2) -> Unit x2
tail3 = \ (x1, x2, x3) -> (x2, x3)
tail4 = \ (x1, x2, x3, x4) -> (x2, x3, x4)
tail5 = \ (x1, x2, x3, x4, x5) -> (x2, x3, x4, x5)
I’m going to take a minute to look around and see if there’s some way to escape this place. Do you mind writing initN
and lastN
?
Hey, I’m back. While I was looking around, some big ugly alien jailer came by and yelled at me in some language I could barely tell was a language, let alone decipher. I think we might be here a while. Do you mind if we work on something weirdly easy? Let’s write lengthN
.
It’s not quite as easy as lengthN n = n
, but it’s really not too bad. Our generated function can totally ignore its argument, so let’s just use a _
pattern match there. We can use LitE
to create some literal expression. Since we obviously have n
, just give back the integer literal form of n
.
length
can of course work on structures of length 0:
That’s actually kind of pretty.
length0 = \ _ -> 0
length1 = \ _ -> 1
length2 = \ _ -> 2
length3 = \ _ -> 3
length4 = \ _ -> 4
length5 = \ _ -> 5
I think we’re really getting the hang of things. After length
, null
shouldn’t be too bad.
Try writing nullN
. You’ll want to know ConE
, which helps you write constructors.
That looks good, but I do have a suggestion. TH gives us multiple ways to create Name
s. So far, we’ve just been using mkName
, but we can also construct names directly based on what’s currently in scope. Use ''
for types, and '
for values. For example, if I wanted to use ConT
, I could write ''Bool
to get the name. If you like, take a look at the docs for more explanation.
Because True
and False
are values, and they’re in scope, we can get those names with a single tick '
nullN :: Int -> Q Exp
nullN n =
pure . LamE [namedTupleP n] . ConE $
if n == 0
then 'True
else 'False
It looks like nullN
works
null0 = \ () -> True
null1 = \ Unitx1 -> False
null2 = \ (x1, x2) -> False
null3 = \ (x1, x2, x3) -> False
null4 = \ (x1, x2, x3, x4) -> False
null5 = \ (x1, x2, x3, x4, x5) -> False
An alien steps in and informs us that we only have to write one more function! Additionally, because tuples can have different types in different slots, we’re now allowed to assume homogenously typed tuples (t2 :: (a, a)
, t3 :: (a, a, a)
, etc.). The last function we need to come up with is mapN
. It would be possible to build a multimap
that maps different functions over different types, but we’re only here to replace functions on lists.
As ever, let’s start with the basics.
Peeking at the list definition map :: (a -> b) -> [a] -> [b]
shows us we now have two arguments. Let’s call the first one (the function) f
:
We still have namedTupleP n
as part of our pattern match, but we also want to grab f
there as well. The overall pattern match will look something like f (x1, x2, x3)
in the end.
The Exp
way to apply some expression to another is AppE
. We can use this to actually apply f
to each of the x
s.
Then, we construct a new tuple with the function applied to each element.
Putting it all together…
mapN :: Int -> Q Exp
mapN n = do
let f = mkName "f"
args = [VarP f, namedTupleP n]
applyFunc x = AppE (VarE f) (VarE x)
pure $ LamE args $ TupE . map (Just . applyFunc) $ names 1 n
The generated code looks like it does what was expected
map0 = \ f () -> ()
map1 = \ f Unitx1 -> Unit f x1
map2 = \ f (x1, x2) -> (f x1, f x2)
map3 = \ f (x1, x2, x3) -> (f x1, f x2, f x3)
map4 = \ f (x1, x2, x3, x4) -> (f x1, f x2, f x3, f x4)
map5 = \ f (x1, x2, x3, x4, x5) -> (f x1, f x2, f x3, f x4, f x5)
Satisfied, we set maxTupleSize
back to 62
.
The jailer returns, swinging open the creaky door of our oddly comfortable coding cell. As we exit the hallway, starshine streams in through a large window. We board a nondescript craft and return to earth, satisfied with the job we’ve done, but somewhat worried about the fate of humanity.
On the way back we discuss what a silly, contrived, ridiculous thing it is to want a Tuple Prelude. In the end though, whether using recursion to operate on a list, or using TH metaprogramming to generate functions on tuples, it’s all just ranging over data structures. There’s a sort of beautiful simplicity to this deep connectedness of alien and human programming styles, even with very different surfaces.
In the interest of furthering human-alien relations, it might be worthwhile to convert a few more functions. Potentially interesting ones include:
(!!)
foldr
(++)
In the last case, you’re combining pairs of two tuple sizes, so you’ll need to do more work than just mapping over tuple sizes once.
Aliens might also appreciate more thorough use of FunD
rather than LamE
everywhere.
As we disembark, I promise you I’ll put everything we’ve learned in a github repo for easier reference.