[GHC] #8453: segfault/assertion failure with multi-threaded profiling
GHC
ghc-devs at haskell.org
Thu Oct 17 11:19:45 UTC 2013
#8453: segfault/assertion failure with multi-threaded profiling
----------------------------------+----------------------------------
Reporter: akio | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Profiling | Version: 7.7
Keywords: | Operating System: Linux
Architecture: x86_64 (amd64) | Type of failure: Runtime crash
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
----------------------------------+----------------------------------
Steps to reproduce:
{{{
ghc-stage2 selector_thunks.hs -rtsopts -fforce-recomp -prof -threaded
-debug -O2
./selector_thunk +RTS -N4
}}}
In a few seconds, it either segfaults or dies with the following error
message:
{{{
selector_thunks: internal error: ASSERTION FAILED: file
rts/dist/build/sm/Evac_thr.c, line 778
(GHC version 7.7.20131002 for x86_64_unknown_linux)
Please report this as a GHC bug:
http://www.haskell.org/ghc/reportabug
}}}
selector_thunks.hs:
{{{
import Control.Monad
import Control.Concurrent
import Data.IORef
main = do
gref <- newIORef [return ()]
forM_ [0::Int ..10] $ \_ -> forkIO $ do
ref <- newIORef [return ()]
forever $ do
list <- readIORef gref
writeIORef ref $! reverse list
acts <- readIORef ref
last acts
forM_ [1..100000099] $ \i ->
writeIORef gref $! reverse $
concatMap (replicate 10) $
mapfst $ foldr (\x y -> seq x (x : y)) [] $
map f [1..10+ (div i 1000000)]
mapfst :: [(a, b)] -> [a]
mapfst [] = []
mapfst (x:xs) = (case x of (a, _) -> a) : mapfst xs
f :: Int -> (IO (), Int)
f x = (x `seq` return (), x)
}}}
I only tested the code with a recent HEAD, but I have seen a similar
assertion failure with GHC 7.6.3, in a non-contrived application program.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8453>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list