[GHC] #11645: Heap profiling - hp2ps: samples out of sequence
GHC
ghc-devs at haskell.org
Tue Oct 17 13:29:50 UTC 2017
#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.png)]]
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
More information about the ghc-tickets
mailing list