[Haskell] best way to do generic programming?

johanj at cs.uu.nl johanj at cs.uu.nl
Fri Jul 1 07:36:02 EDT 2005


Here is a solution to your problem in Generic Haskell, see
www.generic-haskell.org.

You use gmap to traverse the structure, and
have a special case for the type Expr, which does the
optimization.

I'm surprised the `real world' is this easy :-)

---------------------------------------------
module Optimize where

import GH.Library.Map

data Expr = Const Int | Var String | Add Expr Expr deriving Show

data Stm = Assign String Expr | Seq Stm Stm deriving Show

stmt :: Stm
stmt = Seq (Assign "y" (Add (Var "x") (Const 0)))
           (Assign "z" (Add (Const 0) (Var "y")))

optimize {| t :: * |} :: (optimize{|t|}) => t -> t
optimize extends gmap
optimize {|Expr|} e =
  case e of
    Add x (Const 0) -> x
    Add (Const 0) x -> x
    e'              -> e'

mymain = optimize{|Stm|} stmt
------------------------------------------

-- Johan

> I'm playing with generic programming. At the moment I'm interested in
> reusable transformations on data types. Provided for example a toy
> datatype Expr like this:
>
> data Expr = Const Int | Var String | Add Expr Expr
>
> Plus a function "optimize" that optimizes a pattern "x + 0" into "x":
>
> optimize (Add x (Const 0)) = x
>
> You would now want this to be this generic, so the function should be
> recursive for all other constructors *and* other data types. For
> example, suppose that Expr is included in other datatype:
>
> data Stm = Assign String Expr | Seq Stm Stm
>
> I now want the "optimize" transformation to work on Stm, like
> this:
>
> x = optimize (Seq (Assign (Add (Var "x") (Const 0))) blah blah)
>
> For sure, I don't want to write specific code for type Stm. The thing
> I want is to generically walk through values of those types into Expr
> where it can apply the pattern.
>
> Haskell does not seem to have an easy way to do this.  After looking
> through some papers I found lots of things that *might* handle this,
> like Generic Haskell, "scrap your boilerplate", Drift, etc. Now I'm
> not sure what works best for real world, bread and butter programming.
> None of them seem ideal. I know it's trivial in Scheme (my usual
> language). Vast amounts of the research literature concerns itself
> only with toy problems. Extensibility (i.e., reuse) however seems not
> to be a big concern. Really, this shouldn't be so hard. So I even
> asked a Haskell programming friend of mine, and he could not come up
> with a sensible solution in an hour, while I can do this in two
> minutes in Scheme. After all, writing compilers is supposed to be a
> *strong* point of Haskell. Real world is knocking on your door, guys!
>
> Yours truly,
>
> Arka.




More information about the Haskell mailing list