[Haskell] best way to do generic programming?

Mirko Rahn rahn at ira.uka.de
Fri Jul 1 06:42:41 EDT 2005


> data Expr = Const Int | Var String | Add Expr Expr

> 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.

A one minute solution using the "Scrap your boilerplate" approach is:

{-# OPTIONS -fglasgow-exts #-}

import Data.Generics

data Expr = Const Int
	  | Var String
	  | Add Expr Expr
	    deriving ( Data , Typeable , Show )

optimize :: Expr -> Expr
optimize (Add x (Const 0)) = x
optimize (Add (Const 0) x) = x
optimize x                 = x

data Stmt = Assign String Expr
	  | Seq Stmt Stmt
	    deriving ( Data , Typeable , Show )

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


Now:

*Main> everywhere (mkT optimize) stmt
Seq (Assign "y" (Var "x")) (Assign "z" (Var "y"))

as wanted. The work to do is to just import the Data.Genrics module and 
to add the deriving (Data,Typeable) clausel to the data definitions. I 
think this is easy. The SYB3 paper also describes how to implement 
functions that are extensible with new type-specific cases.

Have fun,

-- 
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---


More information about the Haskell mailing list