[Haskell] stack overflow - nonobvious thunks?

Dean Herington heringtonlacey at mindspring.com
Thu Jul 28 02:27:13 EDT 2005


The following version seems to do the trick (and still remain quite 
readable).  It worked for 100000000 as well.

import Data.Map as Map
import System.Random
import Data.List (foldl')

table :: (Ord a) => [a] -> [(a,Int)]
table xs = Map.assocs $! foldl' f Map.empty xs
     where f m x = let  m' = Map.insertWith (+) x 1 m
                        Just v = Map.lookup x m'
                   in v `seq` m'

unif :: [Int]
unif = randomRs (1,10) $ mkStdGen 1

f :: Int -> [(Int, Int)]
f n = table $ take n unif

main = print $ f 10000000

- Dean


At 2:19 PM -0700 7/27/05, Scherrer, Chad wrote:
>Adrian, Does your AVL library have an "insertWith'"-type function
>mentioned by Udo?
>
>If I lookup and insert into the table separately, forcing evaluation at
>each step, I can do
>
>table' :: (Ord a) => [a] -> [(a, Int)]
>table' xs = Map.assocs $! foldl' f Map.empty xs
>     where
>     f m x = (Map.insert x $! 1 + Map.findWithDefault 0 x m) $! m
>
>This helps with the stack overflow problem, but now I'm hitting a
>different wall:
>
>*Main> table $ take 10000000 unif
>[(1,999662),(2,1000220),(3,998800),(4,1000965),(5,999314),(6,1001819),(7
>,1000997),(8,999450),(9,999877),(10,998896)]
>
>*Main> table $ take 100000000 unif
><interactive>: out of memory (requested 1048576 bytes)
>
>I thought I may have found a good approach using an idea from one of
>Amanda Clare's pages
>http://users.aber.ac.uk/afc/stricthaskell.html
>
>If I write
>
>eqSeq x y = if x==x then y else y
>
>this forces evaluation of x further than seq alone. Then I can write
>
>table :: (Ord a) => [a] -> [(a, Int)]
>table xs = Map.assocs $! foldl' f Map.empty xs
>     where
>     f m x = m `eqSeq` Map.insertWith (+) x 1 m
>
>Same result as Udo's suggestion - out of memory.
>
>I still don't see why this function should need any more than a few
>kilobytes, even for very large n like this.
>
>-Chad
>
>-----Original Message-----
>From: u.stenzel at web.de [mailto:u.stenzel at web.de]
>Sent: Wednesday, July 27, 2005 11:02 AM
>To: Scherrer, Chad
>Cc: haskell at haskell.org
>Subject: Re: [Haskell] stack overflow - nonobvious thunks?
>
>Scherrer, Chad wrote:
>
>>      f m x = Map.insertWith (+) x 1 m
>
>insertWith is inserting the "nonobvious thunks".  Internally it applies
>(+) to the old value and the new one, producing a thunk.  There is no
>place you could put a seq or something to force the result.  You
>basically need insertWith', which isn't there.
>
>I think, your best best is to manually lookup the old value, combine
>with the new, force the result, then insert that, overwriting the old
>value.
>
>On top of that you still need foldl' to avoid building long chains of
>Map.insert.
>
>
>Udo.
>--
>The Second Law of Thermodynamics:
>         If you think things are in a mess now, just wait!
>	                -- Jim Warner
>_______________________________________________
>Haskell mailing list
>Haskell at haskell.org
>http://www.haskell.org/mailman/listinfo/haskell
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org//pipermail/haskell/attachments/20050728/2f14c588/attachment.htm


More information about the Haskell mailing list