[Template-haskell] Template Haskell and Hydra

John O'Donnell jtod@dcs.gla.ac.uk
20 Jan 2003 16:15:21 +0000


Hi Simon,

I have a possible application for template Haskell, but am not sure
whether it will work out.

The application is Hydra, where function definitions need to be
transformed.  I can see three approaches:

1. Do the transformation by hand.  This is acceptable only as an
interim approach, although I've been doing it for quite some time.

2. Use Template Haskell.  Actually, my application is typical of the
kind of thing that Scheme macros are good for.

3. Write a parser for Hydra (which would be a subset of Haskell), turn
it into a syntax tree, and do the transformation there.

I recently started working on (3), which is flexible but a pretty
heavyweight approach.  But if (2) were flexible enough, it would be
preferable.

Here's an example of the kind of transformation I'd like to perform:
Given this original program...

f1 :: Clocked a => a -> a -> (a,a)
f1 a b = (x, z)
  where (x,y) = (f2 a y, f3 b x)
        z = f4 a (f5 x y) z

transform it to...

f1 :: (Clocked a, Structural a) => a -> a -> (a,a)
f1 a b = (x', z')
  where
-- These equations are similar to the original ones:
        (x,y) = (f2 a' y', f3 b' x')
        z =  f4 a' (f5 x' y') z'
-- These new equations specify the names and structure
-- of the definition:
        p = glob1
              "f1"
              [sgl a', sgl b']
              (pair (sgl x') (sgl z'))
              [x',y',z']
        a' = glob2 p a "a" (Input 1 Sgl)
        b' = glob2 p b "b" (Input 2 Sgl)
        x' = glob2 p x "x" (Equation 1 (Pair 1 Sgl))
        y' = glob2 p y "y" (Equation 1 (Pair 2 Sgl))
        z' = glob2 p z "z" (Equation 2 Sgl)

The details of the transformation aren't too important, and are likely
to change, but the salient points are:

-- The transformed definition follows the structure of the original
one --- the equations in the original appear in similar form in the
final version --- but there are some extra definitions.

-- The names used in the original definition appear as literal strings
in the transformed one.  This is analogous to what's often needed for
debugging, although Hydra uses this information for more than just
debugging.  This is similar to what Sean Seefried requested in an
earlier email, where he wanted to be able to show the name of a
function defined at the top level.

-- The structure of the original definition (e.g. which equation
within the `where' clause contains the definition of a name) is made
explicit in the transformed version.

-- Some globally defined functions (glob1 etc) are introduced in the
transformation; these are imported from another module.

-- Functions f2, ... used within the original definition of f1 are
used also in the transformed version of f1.  These need to have
definitions with types compatible with their use in the transformed
f1, but it is not the responsibility of the transformation to ensure
this.

Apparently Template Haskell can't implement such a transformation now,
since it can't reify top level functions.  It might be possible to
implement the transformation partially, with enough $ and [|...|]
embedded in the original definition, but I suspect that this would
introduce too much syntactic noise in the definition, and it would be
better just to use the explicit heavyweight parser/transformer.

To support this kind of transformation, it would be necessary to allow
top level definitions to be reified, but I think it might be best to go
farther, and allow an entire module to be reified.

Simon P J made the following points about problems with top level
function reification; here are some comments in the context of my
application...

> a) Inconvenience (it's a little tiresome to implement)

I can believe this!  It probably comes down to a tradeoff between
difficulty of implementation and usefulness.  Hydra is a potential
application which really needs a top-level reification; the only
alternative I can see is the separate parser and transformer.

> b) It would be particularly difficult to get the definition of a
> function defined in another module (because we'd have to read that
> entire module too).  This is not true of data type declarations, which
> travel in interface files, so there is no ugly cross-module issue to
> worry about.  

Right.  And that would be needed for some purposes, such as
optimisations based on global transformations across functions.

However, for Hydra, it isn't necessary to get the definition of any
other function; all that matters is its type.  And the transformation
doesn't even need to know the type of any other function; the
typechecking of the final source program will be sufficient.

> c) I'm not quite clear what you'd expect to get.  If we have
> 
>         f = ...f...
> 
> it's easy enough.  If you have mutual recursion
> 
>         f = ...g...
>         g = ...f...
> 
> do you get just f's definition, or g's too?  If it's a pattern binding
> 
>         (f,g) = ...
> 
> you can't avoid getting both.  
> 
> And even if it's a simple, non-recursive defn
> 
>         f = ....g....
> 
> (where g is defined earlier), I wonder whether there should be some way
> to get at g's definition too. 

Cases like
>         f = ...g...
>         g = ...f...
are typical in Hydra.  However, to transform the definition of f, we
don't need the definition of g.  Any application of the form (g a b c)
appearing in f will just be transformed into (g a' b' c').

Naturally, a global optimisation might require the definitions of all
the functions that are used, but I don't need such things (yet).

I think the point here is that any transformation of f that requires
the definition of g should require g to be defined in the same module
as f.  If it were possible to reify an entire module, then it would be
possible to do some very general inter-function transformations, but
these wouldn't be able to cross module boundaries for the reasons
Simon gives.  I think that is a reasonable restriction, and this kind
of flexibility might be worthwhile.

For my own current purposes, all that's really needed is the ability
to reify every top level definition.  It seems to me that if the ghc
team is willing to implement that, it would likely be worth while
going all the way for complete module reification.

Where would you introduce a reify application for a complete module?
Instead of writing Template Haskell notations in the module, what
about the following idea: introduce a ghc/ghci switch, so that

   ghc -... -ftransform-module-with Foo M.hs

would run Foo.Main on the reification of the complete module M, and
compile the result.  This would make it possible to compile M without
the switch (so you get the original definitions in M.hs), as well as
with the switch (so you get the transformed definitions).  I'm not
sure how best to distinguish between the two versions of the
definitions in M; perhaps as M.f1 vs.  M.Foo.f1, or with "import M"
vs. "import M.Foo", or something like that.

There still could be some advantages to using a separate parser and
transformer, rather than Template Haskell.  One thing I'd like to
experiment with is a slightly enhanced typechecking algorithm, for
example.  But it might even be possible to do that using reified types
obtained from Template Haskell.  If that were workable, it would be
simpler and more elegant than doing a complete typechecker from
scratch.  But these typing issues are not the main story for me right
now, they are for the future.

Would it be feasible to do something like this?  Do you forsee any
tricky problems with it?  Would it be worthwhile?  (to anybody besides
me :-)

Cheers,
John O'Donnell