[Haskell-cafe] Optimizing Fold Expressions

J. J. W. bsc.j.j.w at gmail.com
Sat Mar 30 19:45:35 CET 2013


Dear all,

I was wondering whether it was possible to write fold expressions more
elegantly. Suppose I have the following
datastructure:

data Expr = Add Expr Expr
          | Sub Expr Expr
          | Mul Expr Expr
          | Eq  Expr Expr
          | B Bool
          | I Int
          deriving Show

type ExprAlgebra r = (r -> r -> r, -- Add
                      r -> r -> r, -- Sub
                      r -> r -> r, -- Mul
                      r -> r -> r, -- Eq
                      Bool   -> r, -- Bool
                      Int -> r     -- Int
                      )

foldAlgebra :: ExprAlgebra r -> Expr -> r
foldAlgebra alg@(a, b, c ,d, e, f) (Add x y) = a (foldAlgebra alg x)
(foldAlgebra alg y)
foldAlgebra alg@(a, b, c ,d, e, f) (Sub x y) = b (foldAlgebra alg x)
(foldAlgebra alg y)
foldAlgebra alg@(a, b, c ,d, e, f) (Mul x y) = c (foldAlgebra alg x)
(foldAlgebra alg y)
foldAlgebra alg@(a, b, c ,d, e, f) (Eq  x y) = d (foldAlgebra alg x)
(foldAlgebra alg y)
foldAlgebra alg@(a, b, c ,d, e, f) (B b')    = e b'
foldAlgebra alg@(a, b, c ,d, e, f) (I i)     = f i

If I am correct, this works, however if we for example would like to
replace all Int's by booleans (note: this is to illustrate my problem):

replaceIntByBool = foldAlgebra (Add, Sub, Mul, Eq, B, \x -> if x == 0 then
B False else B True)

As you can see, a lot of "useless" identity code. Can I somehow optimize
this? Can someone give me some pointers how I can write this more clearly
(or with less code?) So I constantly don't have to write Add, Sub, Mul, for
those things that I just want an "identity function"?

Thanks in advance!

Jun Jie
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130330/91f7f7bc/attachment.htm>


More information about the Haskell-Cafe mailing list