[Haskell-cafe] Profiling/cost centre question
Sebastian Reese
str at holumbus.org
Thu Jun 18 06:35:39 EDT 2009
Hi there,
I mailed to this list in May
(http://www.haskell.org/pipermail/haskell-cafe/2009-May/062126.html)
with no answer at all. So I wrote a smaller program to demonstrate my
problem/question. Maybe now someone can help me now.
I wrote a small program that does nothing but listening on a TCP port.
After connection is done it simply terminates.
#> cat Test.hs
module Main where
import Network
main :: IO ()
main =
(do
servSock <- {-# SCC "cc1" #-}listenOn . PortNumber $ 10000
(handle, host, port) <- {-# SCC "cc2" #-}accept servSock
return ()
)`catch` (putStrLn . show)
#>
I compile, run (connection from elsewhere, so program terminates) and
watch the .prof output
#> ghc --make -threaded -O2 -prof -caf-all -auto-all Test.hs
Linking Test ...
#> ./Test +RTS -p
#> cat Test.prof
Thu Jun 18 12:24 2009 Time and Allocation Profiling Report (Final)
Test +RTS -p -RTS
total time = 0.32 secs (16 ticks @ 20 ms)
total alloc = 32,384 bytes (excludes profiling overheads)
COST CENTRE MODULE %time %alloc
MAIN MAIN 100.0 7.8
CAF GHC.Conc 0.0 4.0
CAF GHC.Handle 0.0 26.8
cc1 Main 0.0 3.8
cc2 Main 0.0 55.8
... snip ...
#>
My actual question is, where does the 100% individual time from MAIN
come from, how can I debug that in other programs and where does this
MAIN cost centre come from?
thanks for your help
Sebastian
----------------------------------------------------------------
This message was sent using IMP, the Internet Messaging Program.
More information about the Haskell-Cafe
mailing list