
Although it's already been solved, I'd like to point out here that
foldl is (or may be) getting tail optimised, but that the stack
overflow isn't from the foldl itself, but from the evaluation of the
huge expression which that foldl builds. Evaluating the left
associative expression involves immediately pushing 1000000 items on
the stack.
Note that:
foldl (flip (:)) [] (replicate 1000000 1)
works fine after a short pause, due to the fact that the result can be
lazily evaluated and printed one piece at a time, whereas
foldl (+) 0 (replicate 1000000 1)
causes a stack overflow.
As was mentioned, the solution is to use the stricter foldl' to keep
the accumulated expression small.
- Cale
On 28/12/05, David Roundy
Hi all,
I've got a problem that I'm seeing using either Data.Map or Data.IntMap.
module Main where import Data.List import qualified Data.IntMap as Map
stats elems = foldl add_elem Map.empty elems add_elem m x = Map.insertWith (+) x 1 m
main = print $ stats $ take 1000000 $ repeat 1
This program has a space leak and runs out of stack space. I'm guessing that I'm being bit here by an unnatural amount of laziness in Map.insertWith, but I can't see how to fix this. :( I'm sure it's something elementary...
I tried defining
add_elem m x = let m' = Map.insertWith (+) x 1 m Just num = Map.lookup x m' in seq num m' to force the (+) to be evaluated strictly, but that didn't help. -- David Roundy http://www.darcs.net _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe