G'day.
Quoting Jeremy Shaw <[EMAIL PROTECTED]>:
I have an expression data-type:
data Expr
= Quotient Expr Expr
| Product Expr Expr
| Sum Expr Expr
| Difference Expr Expr
| Lit Double
| Var Char
deriving (Eq, Ord, Data, Typeable, Read, Show)
And I want to write a function that will take an expression and
automatically apply the identity laws to simplify the expression.
[...]
I would also be interested in alternative approaches besides the ones
I outlined.
A low-tech alternative that would work here is to use smart
constructors. This approach avoids non-termination, and allows for
quite general transformations.
Example:
sum :: Expr -> Expr -> Expr
sum (Lit 0) y = y
sum x (Lit 0) = x
sum (Lit x) (Lit y) = lit (x+y) -- Call smart constructors recursively
sum (Var v1) (Var v2) | v1 == v2 = product (Lit 2) (Var v1) -- Guards are OK
sum x y@(Sum _ _)
= foldl1 sum x . getTerms y $ []
-- So is complex stuff.
-- This is a simple version, but it's also not too hard to write
-- something which rewrites (x + 1) + (y + 2) to (x + y) + 3, say.
-- Applying the Risch structure theorem is left as an exercise.
where
getTerms (Sum x y) = getTerms x . getTerms y
getTerms e = (e:)
sum x y = Sum x y -- And here's the default case
lit :: Double -> Expr
lit = Lit -- Some constructors are trivial. Include them anyway.
You can now either aggressively replace instances of data constructors
with smart ones (except within the smart constructors themselves!) or
write a single traversal which rewrites an expression:
simplify :: Expr -> Expr
simplify (Sum x y) = sum (simplify x) (simplify y)
simplify (Lit x) = lit x
-- etc etc
Cheers,
Andrew Bromage
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe