GHC-HEAD 19.Aug.2010, llvm, threaded [Memory Exhaustion]
Simon Marlow
marlowsd at gmail.com
Mon Aug 23 06:50:18 EDT 2010
On 20/08/2010 20:13, Christian Höner zu Siederdissen wrote:
> Hi,
>
> using:
> http://www.haskell.org/ghc/dist/current/dist/ghc-6.13.20100819-x86_64-unknown-linux.tar.bz2
> parallel-3.1.0.0
>
> and the most-common test program ... ever:
>
> module Main where
> import Control.Parallel.Strategies
>
> fib :: Int -> Int
> fib n
> | n< 1 = error "n< 1"
> | n == 1 = 1
> | n == 2 = 1
> | otherwise = fib (n-1) + fib(n-2)
>
> fibs = parMap rdeepseq fib $ [1..100]
> main = do
> mapM_ (putStrLn . show) $ zip [1..] fibs
>
>
> ghc -fllvm -threaded -rtsopts -O2 Prog.hs
>
> ./Prog -- runs slowly through 1..100 [OK]
> ./Prog +RTS -N2 -RTS -- requests all available memory [NOT OK]
>
> ghc -fllvm -threaded -rtsopts Prog.hs
>
> ./Prog +RTS -N2 -RTS -- slowly but [OK]
>
>
>
> Can anybody confirm this?
Yes, and many thanks for reporting this. I was about to reply and say
that I couldn't reproduce it, but then I noticed that it only happened
sometimes and more often with larger -N values. I tracked it down to a
bug where the RTS was looping allocating some objects when it should
have been blocking the current thread. It was a simple missing test in
some code that handles blocking on black hole objects.
I'm testing the fix now. Thanks again for the report!
Cheers,
Simon
More information about the Glasgow-haskell-users
mailing list