#5282: Bizarre results from -P profiler on OS X
-------------------------------+--------------------------------------------
Reporter: bos | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.2.1
Component: Runtime System | Version: 7.0.3
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: MacOS X | Blocking:
Architecture: x86_64 (amd64) | Failure: Incorrect result at runtime
-------------------------------+--------------------------------------------
Changes (by dmp):
* cc: dmp@… (added)
Comment:
I'm seeing the odd profiling results, but only with the single threaded
runtime. If I compile with `-threaded`, then the profiling results look
correct.
For the non-threaded runtime, it looks like all of the profiling ticks are
going to the SYSTEM cost center. Since these ticks are not included in the
profiling summary, it makes it look like there are very few actual ticks
that get logged. To see where the ticks are going, I did some simple
printf debugging by adding a statement to the `handleProfTick` function
that prints out the cost center.
{{{
if (do_prof_ticks) {
printf("%s\n", CCCS->root->label);
CCCS->time_ticks++;
}
}}}
When running with the threaded runtime it prints mostly "CAF" and the
profiling output looks good. When running with the non-threaded runtime it
prints mostly "SYSTEM" and the profiling summary looks bad.
I looked around, but couldn't see anything obviously wrong that would
cause all the ticks to go to the SYSTEM entry. I'm at a dead end, but
could do some more if there are some suggestions on where to look.
I'm using a simplified version of bos's benchmark that just does a busy
loop
{{{
{-# LANGUAGE BangPatterns, OverloadedStrings #-}
--module Main (main) where
import Control.Monad
import System.Environment
import Data.Time.Clock
import System.IO
counting :: Int -> (Int -> () -> IO ()) -> IO ()
counting count act = loop 0
where loop !i | i < count = act i () >> loop (i+1)
| otherwise = return ()
{-# NOINLINE counting #-}
idle count = counting count $ \_ x -> return ()
main = do
args <- getArgs
let count = case args of
(_:x:_) -> read x
_ -> 100000
let bm = case args of
("idle":_) -> idle
_ -> error "wut?"
start <- getCurrentTime
bm count
elapsed <- (`diffUTCTime` start) `fmap` getCurrentTime
putStrLn (show elapsed)
}}}
and running with
{{{
$ ./Simple idle 10000000 +RTS -P -RTS
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5282#comment:8>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs