[GHC] #9384: setNumCapabilities call breaks eventlog events
GHC
ghc-devs at haskell.org
Wed Jul 30 15:27:03 UTC 2014
#9384: setNumCapabilities call breaks eventlog events
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Profiling | Version: 7.8.3
Keywords: | Operating System: Linux
Architecture: x86_64 (amd64) | Type of failure: Incorrect
Difficulty: Unknown | result at runtime
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
The problem was found when i tried to eventlog '''ghc --make''' itself.
I've missinterpreted is as a threadscope bug:
https://github.com/haskell/ThreadScope/issues/37
Here is small program to reliably reproduce the bug:
{{{#!hs
module Main where
import qualified Data.List as L
import qualified System.Environment as E
import Control.Monad
import qualified Control.Concurrent as CC
import qualified Control.Concurrent.MVar as CC
slow_and_silly :: Int -> IO Int
slow_and_silly i = return $ length $ L.foldl' (\a v -> a ++ [v]) [] [1..i]
-- build as:
-- $ ghc --make a -O2 -threaded -eventlog
-- valid eventlog:
-- $ ./a 2 7000 +RTS -ls -N2
-- $ ghc-events validate threads a.eventlog
-- Valid eventlog:
-- ...
-- invalid eventlog
-- $ ./a 2 7000 +RTS -ls
-- $ ghc-events validate threads a.eventlog
-- Invalid eventlog:
-- ...
main = do
[caps, count] <- E.getArgs
let n_caps :: Int
n_caps = read caps
max_n :: Int
max_n = read count
CC.setNumCapabilities n_caps
waits <- replicateM n_caps $ CC.newEmptyMVar
forM_ waits $ \w -> CC.forkIO $ do
slow_and_silly max_n >>= print
CC.putMVar w ()
forM_ waits $ \w -> CC.takeMVar w
}}}
How to reproduce (comments have '''ghc-events''' version):
{{{
$ ghc --make a -O2 -threaded -eventlog
$ ./a 2 7000 +RTS -ls -N2
$ threadscope a.eventlog # works
$ ./a 2 7000 +RTS -ls
$ threadscope a.eventlog # crashes
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9384>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list