[Haskell-cafe] STM, newArray, and a stack overflow?

Bas van Dijk v.dijk.bas at gmail.com
Wed Mar 23 19:42:54 CET 2011


On 23 March 2011 18:42, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
> On 23 March 2011 17:19, Jake McArthur <jake.mcarthur at gmail.com> wrote:
>> On 03/23/2011 10:34 AM, Ketil Malde wrote:
>>>
>>> It works (calling the same function) from GHCi, but breaks when
>>> compiled.  Also when compiling with -O0.
>>
>> Confirmed for GHC 7.0.2. Works fine in GHCi, but compiling it (in my case,
>> with -O) and running the executable causes a stack overflow unless I run it
>> with +RTS -K16m, and even then it spends 90% of its time in GC. This looks
>> like it is probably a bug, to me. Maybe it should be reported in GHC's Trac?
>
> It looks like a bug indeed.
>
> The problem can be reduced to just:
>
> atomically $ replicateM 1000000 (newTVar undefined)
>
> or even simpler:
>
> replicateM 1000000 (newIORef undefined)
>
> Bas
>

Maybe it's not really a bug:

For example the following very similar program also overflows the
stack: (note that: replicateM n x = sequence (replicate n x))

main = sequence $ replicate 1000000 $ (randomIO :: IO Int)

This happens because sequence is defined using a right fold:

sequence ms = foldr k (return []) ms
    where
      k m m' = do
        x <- m
        xs <- m'
        return (x:xs)

What happens is that sequence repeatedly pushes an x onto the stack
then continues with m' until your stack overflows.

The stack overflow disappears when you use a left fold:

sequencel xs = foldl k (\r -> return $ r []) xs id
    where
      k g m = \r -> do
        x <- m
        g (r . (x:))

or written with explicit recursion:

sequencel xs = go xs id
    where
      go []     r = return $ r []
      go (m:ms) r = do x <- m
                       go ms (r . (x:))

Note that I used a difference list to keep the list in the right
order. Alternatively you can use a normal list (x:r) and reverse it
when done. I'm not sure what's more efficient.

I'm surprised I haven't encountered this problem with sequence before.
Does this suggest we need the left folded sequencel?

Regards,

Bas



More information about the Haskell-Cafe mailing list