[Haskell-cafe] how to break foldl' ?

Daniel Fischer daniel.is.fischer at web.de
Fri Sep 30 14:15:05 EDT 2005


Am Freitag, 30. September 2005 17:14 schrieb Henning Thielemann:
> On Fri, 30 Sep 2005, gary ng wrote:
> > Once again, many thanks to all who taught me about
> > this small little problem. Don't even know there is
> > init/last and thought there is only head/tail.
>
> http://www.haskell.org/ghc/docs/6.4/html/libraries/base/Data.List.html
>
> > But just for my curiosity, would the takeWhile still
> > store the intermediate result till my result is
> > reached ? If so, and my list is really very long(and I
> > need to go to 1/2 of its length), I would still use a
> > lot more memory than imperative method or even the
> > foldl one(where in both case, I just take one element)
> > ?
>
> If you don't trust the compiler you can at least test if the rest of the
> list is ignored: Run with an infinite list.
>
> E.g.
>   last (takeWhile (<10) (scanl (+) 0 (repeat 1)))

I think Gary wanted to know whether the initial part of scanl's result is 
stored. I think, it shouldn't, because of the 'last'.

However, when profiling your versions versus

testFoldl :: (a -> Bool) -> (a -> b -> a) -> a -> [b] -> a
testFoldl _ _ z [] = z
testFoldl p _ z _ | p z = z
testFoldl p f z (x:xs) = testFoldl p f (f z x) xs,

I found that your 
head (dropWhile ... )
took about twice as long and allocated roughly 2.6 times as much memory as 
mine
and 
last (takeWhile ... )
was a bit worse.
Still, it didn't use near enough memory to store
takeWhile (<= 5*10^7) (scanl (+) 0 (repeat 1)),
all three used (if I interpret the profiling graphs [-hc, -hb] correctly) 
about 16.5 k of memory for practically the complete runtime.

Besides, 
head (dropWhile (<10) (scanl (+) 0 (replicate 9 1)))
will raise an error, as will
last (takeWhile ...)
if the starting value satisfies the break-condition.

Cheers,
Daniel


More information about the Haskell-Cafe mailing list