[Haskell-beginners] folds -- help!

Peter Verswyvelen bugfact at gmail.com
Mon Mar 9 13:24:14 EDT 2009


Maybe it helps to visualize it like this. Instead of computing the sum by
using a fold with (+), we just construct data:
data Expr = N Int
          | Expr :+: Expr
          deriving Show

ns :: [Expr]
ns = map N [1..3]

lf :: Expr
lf = foldl1 (:+:) ns

rf :: Expr
rf = foldr1 (:+:) ns

For simplicity Iused foldl1 and foldr1, which only work on non-empty lists.

(regarding the weird :+: well in Haskell, you can use operators for data
constructors when they start with a colon)

Run this with GHCi, and evaluate lf and rf. You should get

*Main> lf
(N 1 :+: N 2) :+: N 3
*Main> rf
N 1 :+: (N 2 :+: N 3)

So really, foldl "folds on the left", because the parentheses are on the
left side. Similarly for foldr.

Does this help?

On Mon, Mar 9, 2009 at 5:46 PM, 7stud <bbxx789_05ss at yahoo.com> wrote:

> This is an example that shows how foldl and foldr work (from RWH p.93-94):
>
> foldl (+) 0 (1:2:3:[])
>   == foldl (+) (0 + 1)             (2:3:[])
>   == foldl (+) ((0 + 1) + 2)       (3:[])
>   == foldl (+) (((0 + 1) + 2) + 3) []
>   ==           (((0 + 1) + 2) + 3)
>
>
> foldr (+) 0 (1:2:3:[])
>   ==  1 +           foldr (+) 0 (2:3:[])
>   ==  1 + (2 +      foldr (+) 0 (3:[])
>   ==  1 + (2 + (3 + foldr (+) 0 []))
>   ==  1 + (2 + (3 + 0))
>
> The book says on p.94:
>
> -----
> The difference between foldl and foldr should be clear from looking at
> where
> the parentheses and the empty list elements show up.  With foldl, the empty
> list element is on the left, and all the parentheses group to the left.
> With foldr, the zero value is on the right, and the parentheses group to
> the
> right.
> ----
>
> Huh?  With foldl, the only empty list element I see is on the right.
>
> Initially, it looked to me ike they did the same thing, and that the only
> difference was the way they called step.  I think "step" is a horrible,
> non-descriptive name, so I'm going to use "accFunc" instead:
>
> foldl calls: accFunc acc x
>
> foldr calls: accFunc x acc
>
> So it looks like you can define a function using either one and get the
> same result.  Here is a test:
>
> --I am going to use odd for pfunc and [1, 2, 3] for xs:
>
> myFilter1 pfunc xs = foldl accFunc [] xs
>    where accFunc acc x
>            | pfunc x       = acc ++ [x]
>            | otherwise     = acc
>
> myFilter2 pfunc xs = foldr accFunc [] xs
>    where accFunc x acc
>            | pfunc x       = acc ++ [x]
>            | otherwise     = acc
>
>
> *Main> myFilter1 odd [1, 2, 3]
> [1,3]
> *Main> myFilter2 odd [1, 2, 3]
> [3,1]
>
> Hmmm.  So there is a difference.  foldr appears to grab elements from
> the end of the list.  Therefore, to get the same result from the function
> that uses foldr, I did this:
>
>
> myFilter3 pfunc xs = foldr accFunc [] xs
>    where accFunc x acc
>            | pfunc x       = x : acc
>            | otherwise     = acc
>
>
> *Main> myFilter3 odd [1, 2, 3]
> [1,3]
>
> But then RWH explains that you would never use foldl in practice because it
> thunks the result, which for large lists can overwhelm the maximum memory
> alloted for a thunk.  But it appears to me the same thunk problem would
> occur with foldr.  So why is foldr used in practice but not foldl?
>
>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20090309/add4f687/attachment.htm


More information about the Beginners mailing list