[Haskell-cafe] strange stack overflow with Data.Map

David Roundy droundy at darcs.net
Wed Dec 28 19:42:05 EST 2005


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


More information about the Haskell-Cafe mailing list