
You can use a general fold and unfold, without any type-specific programming if you re-express Expr as the least fixed point of its underlying "base functor":
data ExprF a = Add a a | Sub a a | Mul a a | Eq a a | B Bool | I Int deriving (Show,Functor)
data Expr = Fix ExprF
Then use the standard definitions:
newtype Fix f = Roll { unRoll :: f (Fix f) }
fold :: Functor f => (f b -> b) -> (Fix f -> b) fold h = h . fmap (fold h) . unRoll
unfold :: Functor f => (a -> f a) -> (a -> Fix f) unfold g = Roll . fmap (unfold g) . g
Also handy:
hylo :: Functor f => (f b -> b) -> (a -> f a) -> (a -> b) hylo h g = fold h . unfold g
For details, see Jeremy Gibbons's paper "Calculating functional programs".
There are probably easier sources as well.
-- Conal
On Sat, Mar 30, 2013 at 11:45 AM, J. J. W.
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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe