[GHC] #9384: setNumCapabilities call breaks eventlog events

#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

#9384: setNumCapabilities call breaks eventlog events -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 7.8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Changes (by gintas): * cc: gintas (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9384#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9384: setNumCapabilities call breaks eventlog events -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 7.8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by gintas): FWIW I also ran into this bug while trying to profile ghc itself. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9384#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9384: setNumCapabilities call breaks eventlog events -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Profiling | Version: 7.8.3 Resolution: | 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: | -------------------------------------+------------------------------------- Changes (by MikolajKonarski): * priority: normal => high * milestone: => 7.10.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9384#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9384: setNumCapabilities call breaks eventlog events -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Profiling | Version: 7.8.3 Resolution: | 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: D592 | -------------------------------------+------------------------------------- Changes (by qnikst): * cc: qnikst (added) * differential: => D592 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9384#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9384: setNumCapabilities call breaks eventlog events -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: patch Priority: high | Milestone: 7.10.1 Component: Profiling | Version: 7.8.3 Resolution: | 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: D592 | -------------------------------------+------------------------------------- Changes (by slyfox): * status: new => patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9384#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9384: setNumCapabilities call breaks eventlog events -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: patch Priority: high | Milestone: 7.10.1 Component: Profiling | Version: 7.8.3 Resolution: | 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: Phab:D592 | -------------------------------------+------------------------------------- Changes (by thoughtpolice): * differential: D592 => Phab:D592 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9384#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9384: setNumCapabilities call breaks eventlog events
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: patch
Priority: high | Milestone: 7.10.1
Component: Profiling | Version: 7.8.3
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64
Type of failure: Incorrect result | (amd64)
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions: Phab:D592
-------------------------------------+-------------------------------------
Comment (by Sergei Trofimovich

#9384: setNumCapabilities call breaks eventlog events -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.10.1 Component: Profiling | Version: 7.8.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D592 -------------------------------------+------------------------------------- Changes (by slyfox): * status: patch => merge Comment: Tested manually on sample attached: works fine with threadscope-0.2.6 \o/ -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9384#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9384: setNumCapabilities call breaks eventlog events -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.10.1 Component: Profiling | Version: 7.8.3 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D592 -------------------------------------+------------------------------------- Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-7.10`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9384#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC