[GHC] #11645: Heap profiling - hp2ps: samples out of sequence

#11645: Heap profiling - hp2ps: samples out of sequence -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.0.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #664 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- `make TEST=hpc_fork WAY=prof` is failing, but it has nothing to do with `hpc`. {{{ hp2ps: hpc_fork.hp, line 9, samples out of sequence hp2ps error when processing heap profile for hpc_fork }}} hpc_fork.hs: {{{ module main where import system.posix.process import control.concurrent main = do pid1 <- forkprocess $ do threaddelay 100000 pid2 <- forkprocess $ do threaddelay 100000 print () }}} To reproduce: {{{ $ ghc-8.0.1 hpc_fork.hs -fforce-recomp -prof $ ./hpc_fork +RTS -hc $ hp2ps hpc_fork.hp }}} Example hpc_fork.hp: {{{ JOB "hpc_fork +RTS -hc" DATE "Thu Feb 25 22:37 2016" SAMPLE_UNIT "seconds" VALUE_UNIT "bytes" BEGIN_SAMPLE 0.000000 END_SAMPLE 0.000000 BEGIN_SAMPLE 0.005672 END_SAMPLE 0.005672 BEGIN_SAMPLE 0.003167 END_SAMPLE 0.003167 BEGIN_SAMPLE 0.003311 END_SAMPLE 0.003311 }}} This is a regression from 7.10.3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11645 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11645: Heap profiling - hp2ps: samples out of sequence -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | libraries/hpc/tests/fork/hpc_fork Blocked By: | Blocking: Related Tickets: #664 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => libraries/hpc/tests/fork/hpc_fork -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11645#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11645: Heap profiling - hp2ps: samples out of sequence
-------------------------------------+-------------------------------------
Reporter: thomie | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Profiling | Version: 8.0.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| libraries/hpc/tests/fork/hpc_fork
Blocked By: | Blocking:
Related Tickets: #664 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Thomas Miedema

#11645: Heap profiling - hp2ps: samples out of sequence
-------------------------------------+-------------------------------------
Reporter: thomie | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Profiling | Version: 8.0.1-rc2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| libraries/hpc/tests/fork/hpc_fork
Blocked By: | Blocking:
Related Tickets: #664 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11645: Heap profiling - hp2ps: samples out of sequence -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | libraries/hpc/tests/fork/hpc_fork Blocked By: | Blocking: Related Tickets: #664 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by jme): The problem is that the profiler doesn't work with `forkProcess` (''e.g.'', see #8862). In this particular case, the issue is that the elapsed ''per-process'' time is being reported for each sample. Since the parent spends more time performing the forks than each child does executing `threadDelay`, its elapsed time is the largest. But the parent outputs its sample before either child, and so the samples appear out of order. The reason this behavior does not cause a problem when using 7.10.3 is that the sample times used to only be reported in hundredths of a second (and so were all 0.00). As of 1da3bbd2bd82ea11f8a1d760385df84708bbea63, they are being reported with full precision. One possible way to work around this is to simply increase the `threadDelay` intervals for each child (400000 for the first and 800000 for the second worked for me). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11645#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11645: Heap profiling - hp2ps: samples out of sequence -------------------------------------+------------------------------------- Reporter: thomie | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | libraries/hpc/tests/fork/hpc_fork Blocked By: | Blocking: Related Tickets: #664 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by angerman): * cc: angerman (added) Comment: I'm still seeing this with a profiling ghc. The `ghc-stage2.prof` can't be read. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11645#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11645: Heap profiling - hp2ps: samples out of sequence -------------------------------------+------------------------------------- Reporter: thomie | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | libraries/hpc/tests/fork/hpc_fork Blocked By: | Blocking: Related Tickets: #664 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): David also reported seeing this while profiling GHC (#14006). However, I think we should keep this ticket to describe the incompatibility with `forkProcess`. Perhaps comment on #14006 instead. It might be helpful if you could include the `hp` file as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11645#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11645: Heap profiling - hp2ps: samples out of sequence -------------------------------------+------------------------------------- Reporter: thomie | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | libraries/hpc/tests/fork/hpc_fork Blocked By: | Blocking: Related Tickets: #664 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by angerman): I don't have the `.hp` anymore :( It's been basically a `prof` stage2, compiling a module e.g. Dynflags with `-fllvmng`. Due to the time building ghc takes, I won't be able to reproduce this right away. Eventually I'll probably have to again, when testing the `llvmng` backend. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11645#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11645: Heap profiling - hp2ps: samples out of sequence -------------------------------------+------------------------------------- Reporter: thomie | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | libraries/hpc/tests/fork/hpc_fork Blocked By: | Blocking: Related Tickets: #664 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Fuuzetsu): I hit this today on 8.2.1. This is on a proprietary project so I am unable to provide any substantial code to aid debugging this. Below is a highly inefficient program which re-sequences .hp so that you can at least use the data. {{{#!hs {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} module Main (main) where import Control.Monad (guard) import Data.Attoparsec.Combinator as P import Data.Attoparsec.Text as P import Data.List (sort) import Data.Monoid ((<>)) import Data.Text as T import qualified Data.Text.IO as T import System.Environment (getArgs) import System.Exit (exitFailure) import System.IO (hPutStrLn, stderr) data Sample = Sample !Double ![Text] deriving (Eq) instance Ord Sample where compare (Sample x _) (Sample y _) = compare x y data F = F ![Text] ![Sample] parseF :: Parser F parseF = do ls <- P.manyTill (P.takeTill isEndOfLine <* endOfLine) (P.lookAhead "BEGIN_SAMPLE") s <- P.many' parseSample pure $! F ls s parseSample :: Parser Sample parseSample = do s <- "BEGIN_SAMPLE " *> double <* endOfLine let endSample = do es <- "END_SAMPLE " *> double <* endOfLine guard (es == s) l = P.takeTill isEndOfLine <* endOfLine ls <- P.manyTill l endSample pure $! Sample s ls renderSample :: Sample -> Text renderSample (Sample d ls) = T.unlines $ ("BEGIN_SAMPLE " <> T.pack (show d)) : ls ++ [ "END_SAMPLE " <> T.pack (show d) ] main :: IO () main = getArgs >>= \case [input, output] -> do c <- T.readFile input case parseOnly parseF c of Left err -> do hPutStrLn stderr ("Parse failed: " <> err) exitFailure Right (F startLines samples) -> do let s' = T.concat . Prelude.map renderSample $ sort samples T.writeFile output (T.unlines startLines <> s') _ -> do hPutStrLn stderr "usage: fix-hp inputFile outputFile" exitFailure }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11645#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11645: Heap profiling - hp2ps: samples out of sequence -------------------------------------+------------------------------------- Reporter: thomie | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | libraries/hpc/tests/fork/hpc_fork Blocked By: | Blocking: Related Tickets: #664 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by angerman): Ohh, i'm super sorry, not to have attached my reorder script. {{{#!haskell {-# LANGUAGE LambdaCase #-} import System.Environment (getArgs) import Data.List (mapAccumL, isPrefixOf) import GHC.Exts (sortWith) main :: IO () main = getArgs >>= \case [f] -> readFile f >>= pure . unlines . reorder . lines >>= putStr _ -> putStrLn $ "only one input" reorder :: [String] -> [String] reorder = map snd . sortWith fst . snd . mapAccumL f (-1.0) where g :: (Double, String) -> (Double, (Double, String)) g (x,y) = (x,(x,y)) f :: Double -> String -> (Double, (Double, String)) f acc line | "BEGIN_SAMPLE " `isPrefixOf` line = g (read $ drop 13 line, line) | "END_SAMPLE " `isPrefixOf` line && (read $ drop 11 line) /= acc = error "BEING/END missmatch" | otherwise = g (acc, line) }}} Could have saved someone else some time :( However, the generated output still looks rather garbled. [[Image(https://dl.dropbox.com/s/yz5d5ug656mziun/Screenshot%202017-10-03%2017.15.58....)]] did you observe the same Fuuzetsu? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11645#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11645: Heap profiling - hp2ps: samples out of sequence -------------------------------------+------------------------------------- Reporter: thomie | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | libraries/hpc/tests/fork/hpc_fork Blocked By: | Blocking: Related Tickets: #664, #14257 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: #664 => #664, #14257 Comment: I was looking at a similar issue, #14257, and thought I had a theory. Unfortunately it fell apart. I'll try to get back to this soon. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11645#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11645: Heap profiling - hp2ps: samples out of sequence -------------------------------------+------------------------------------- Reporter: thomie | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.0.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | libraries/hpc/tests/fork/hpc_fork Blocked By: | Blocking: Related Tickets: #664, #14257 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mnislaih): * cc: mnislaih (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11645#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11645: Heap profiling - hp2ps: samples out of sequence -------------------------------------+------------------------------------- Reporter: thomie | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Profiling | Version: 8.0.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | libraries/hpc/tests/fork/hpc_fork Blocked By: | Blocking: Related Tickets: #664, #14257 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.4.1 Comment: I believe this is another manifestation of #14257. I have verified that this can no longer be reproduced on `master`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11645#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC