[Template-haskell] Module THTraverse

Sean Seefried sseefried at cse.unsw.edu.au
Fri Nov 14 15:12:41 EST 2003


A common task when using Template Haskell is to write some sort of
transformation pass over a THSyntax data type.  It will typically have
the form:

thPass :: <data-type> -> Q <data-type>

where data-type is any one of Dec, Exp, Typ etc.

In fact, writing a pass usually involves writing functions for more
than one of the data types, since the data types are heavily
interrelated. This presents a little bit of a conundrum for
programmers.  The interesting work of the pass may well only be on
expressions (the Exp data type), but you may want to call the pass on
declarations (Dec).  But this means one has to write a whole bunch of
cases that do nothing but call the pass recursively on the
substructures of declarations. Worse still, it is necessary to write
functions to traverse these substructures since they may not be
expressions, but contain expressions.

I could see this task being repeated over and over again, so I did
what any good programmer would do and wrote a module to relieve the
burden of writing the recursive cases, which I have called
THTraverse.

I will show how to use the module through an example. Say we wish to
write a pass that does just one thing: it traverses through
declarations and changes all sub-expressions which use infix function
application to prefix form. For example, the following expression:

InfixE (Just (VarE "x")) (VarE "fun") (Just (VarE "y"))

becomes

AppE (AppE (VarE "fun") (VarE "x")) (VarE "y")


First, I'm going to throw you all in the deep end by showing the full
definition of this function using the THTraverse module.  Then, once
you begun to drown in the definition, I'll throw in some floatation
devices (i.e. explanation and clarification) to help you swim again.

Here is the full definition of infixToPrefixDec

-------------------------

infixToPrefixFuns :: THTraverseFuns Q
infixToPrefixFuns =
   (THTraverseFuns i i i i i i i i i i i i i i i i i i i i i i)
   { tDec = infixToPrefixDec,
     tExp = infixToPrefixExp }
   where
     i item = thTraverse infixToPrefixFuns item

infixToPrefixDec dec =
   thTraverse infixToPrefixFuns dec

infixToPrefixExp (InfixE (Just e1) e2 (Just e3)) =
   do e1' <- thTraverse infixToPrefixFuns e1
      e2' <- thTraverse infixToPrefixFuns e2
      e3' <- thTraverse infixToPrefixFuns e3
      return $ AppE (AppE e1' e2') e3'
   where
infixToPrefixExp exp = thTraverse infixToPrefixFuns exp

-------------------------

I hope you will agree that this constitutes a lot less
programming. Now for the explanation of how it all works.  The heart
of the module is the function thTraverse which is defined using type
classes.

class THTraverse a where
   thTraverse ::  Monad m => THTraverseFuns m -> a -> m a

(Usually the monad will be the Q monad but this does not have to be
the case. I often find myself using the Identity monad.)  An instance
of the class has been defined for all the data types declared in
THSyntax.

The function, thTraverse, has one very simple purpose; to take an
instance of the THTraverseFuns data structure, and an instance of a
THSyntax data structure (call it "d"), and to call the appropriate
functions recursively on the sub-structures of "d".  The appropriate
functions are contained within an instance of THTraverseFuns. Its
definition is:

data THTraverseFuns m =
    THTraverseFuns { tLit :: Lit -> m Lit,
                     tPat :: Pat -> m Pat,
                     tFieldPat :: FieldPat -> m FieldPat,
                     tMatch :: Match -> m Match,
                     tClause :: Clause -> m Clause,
                     tGuardedExp :: (Exp, Exp) -> m (Exp,Exp),
                     tExp :: Exp -> m Exp,
                     tFieldExp :: FieldExp -> m FieldExp,
                     tBody :: Body -> m Body,
                     tStmt :: Stmt -> m Stmt,
                     tRange :: Range -> m Range,
                     tDec :: Dec -> m Dec,
                     tForeign :: Foreign -> m Foreign,
                     tCallconv :: Callconv -> m Callconv,
                     tSafety :: Safety -> m Safety,
                     tCxt :: Cxt -> m Cxt,
                     tStrict :: Strict -> m Strict,
                     tCon :: Con -> m Con,
                     tStrictType :: StrictType -> m StrictType,
                     tVarStrictType :: VarStrictType -> m VarStrictType,
                     tModule :: Module -> m Module,
		    tType :: Type -> m Type
		  }

When defining a traversal function, thTraverse should be used as a
catch-all case once the cases that actually do useful work have been
written.  As such, a call to thTraverse should be the last case of any
traversal function definition. You can see this in the function
definitions for infixToPrefixDec and infixToPrefixExp above.

When writing a function in which all you want to do is recursively
call the pass on the sub-structures the thTraverse case will be the
only case.

If we now to return to the example, we can see that for the most part
infixToPrefixFuns is defined in terms of 'i', which just calls
thTraverse on sub-structures. (Note the recursive nature of its
definition; thTraverse is applied to infixToPrefixFuns.) This saves
much of the work of writing out tedious functions which contain only
one case.

There is now only one thing to clarify. Why did I define
infixToPrefixDec if it only contains the thTraverse case? Why, so I
had a name to refer to it.  Nothing else.

-------------------------

Summary.

To write your own pass follow this simple recipe:

1. Declare a function

<name>Funs =
   (THTraverseFuns i i i i i i i i i i i i i i i i i i i i i i)
   {
     < functions you defined in step 2 will go here >
   }
   where
     i item = thTraverse infixToPrefixFuns item

2.  Write the functions of the pass that actually do interesting
     work.  Ensure that the last case is a call to thTraverse of the
     form.

     <pass function> x = thTraverse <name>Funs x

3. Back substitute the names of these pass functions back into the
    definition of 1.

-------------------------

I realise acutely that it may be possible to write the THTraverse
module.  For instance, I find that the necessity of a THTraverseFuns
data structure annoying.  I would have preferred to define the
function thTraverse without its use.  I thought that it might be
possible to do this through the use of type classes but I was unable
to do this.

I urge the more zealous hackers out there to have a look at my module
and see if they can do better.


-------------- next part --------------
A non-text attachment was scrubbed...
Name: THTraverse.hs
Type: application/octet-stream
Size: 10064 bytes
Desc: not available
Url : http://haskell.org/pipermail/template-haskell/attachments/20031114/c21bb0b5/THTraverse.obj


More information about the template-haskell mailing list