> On Friday 07 January 2005 12:03, Ketil Malde wrote:
> > Naive use of foldl.  I tend to think the default foldl should be
> > strict (ie. replaced by foldl') -- are there important cases where it
> > needs to be lazy?
>
> Hi,
> One simple example would be,
> > reverse = foldl (flip (:)) []

A better example would be building some other "lazy structure" that is strict 
on it's elements...
J.A.

-----------------------------------------------
module Test where
import Data.List 

data L = E | !Int :+: L deriving Show

-- my head
h (x:+:xs) = x 
h E        = error "ops"

-- 
rev1 = foldl  (flip (:+:)) E
rev2 = foldl' (flip (:+:)) E

l    = [error "", error "", 1::Int]
----------------------------------------------

*Test> h (rev1 l)
1
(0.00 secs, 264560 bytes)
*Test> h (rev2 l)
*** Exception:
(0.01 secs, 264524 bytes)

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to