#5705: getGCStats only works with +RTS -s
------------------------------+---------------------------------------------
Reporter: tibbe | Owner:
Type: bug | Status: new
Priority: normal | Component: Runtime System
Version: 7.2.1 | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Testcase:
Blockedby: | Blocking:
Related: |
------------------------------+---------------------------------------------
Description changed by tibbe:
Old description:
> As the below program shows, `GHC.Stats.getGCStats` only returns non-zero
> values for e.g. `gc_wall_time` if the program is run with `+RTS -s`. I
> guess that's because the stats aren't tracked by the GC unless you
> specify `+RTS -s`. Are the stats expensive to maintain? If not could we
> always update these counters?
>
> {{{
> module Main where
>
> import GHC.Stats
> import System.Mem
>
> main = do
> print $ let xs = [1..1000000] -- allocation
> in fromIntegral (sum xs) / fromIntegral (length xs)
> performGC
> stats <- getGCStats
> putStrLn $ show stats
> }}}
>
> {{{
> $ ./Repro
> 500000.5
> GCStats {bytesAllocated = 0, numGcs = 184, maxBytesUsed = 0,
> numByteUsageSamples = 0, cumulativeBytesUsed = 0, bytesCopied = 0,
> currentBytesUsed = 0, currentBytesSlop = 0, maxBytesSlop = 0,
> peakMegabytesAllocated = 63, mutatorCpuSeconds = 9.6468e-2,
> mutatorWallSeconds = 0.115874, gcCpuSeconds = 0.0,
> gcWallSeconds = 0.0, cpuSeconds = 9.7045e-2, wallSeconds = 0.115874,
> parAvgBytesCopied = 0, parMaxBytesCopied = 0}
> }}}
>
> {{{
> 500000.5
> GCStats {bytesAllocated = 96086504, numGcs = 184, maxBytesUsed =
> 27442272,
> numByteUsageSamples = 7, cumulativeBytesUsed = 52228768, bytesCopied =
> 90580024,
> currentBytesUsed = 74336, currentBytesSlop = 0, maxBytesSlop = 6803872,
> peakMegabytesAllocated = 63, mutatorCpuSeconds = 2.523e-2,
> mutatorWallSeconds = 2.5739e-2, gcCpuSeconds = 7.1919e-2,
> gcWallSeconds = 9.126e-2, cpuSeconds = 9.7729e-2, wallSeconds = 0.116999,
> parAvgBytesCopied = 0, parMaxBytesCopied = 0}
> ...
> }}}
New description:
As the below program shows, `GHC.Stats.getGCStats` only returns non-zero
values for e.g. `gc_wall_time` if the program is run with `+RTS -s`. I
guess that's because the stats aren't tracked by the GC unless you specify
`+RTS -s`. Are the stats expensive to maintain? If not could we always
update these counters?
{{{
module Main where
import GHC.Stats
import System.Mem
main = do
print $ let xs = [1..1000000] -- allocation
in fromIntegral (sum xs) / fromIntegral (length xs)
performGC
stats <- getGCStats
putStrLn $ show stats
}}}
{{{
$ ./Repro
500000.5
GCStats {bytesAllocated = 0, numGcs = 184, maxBytesUsed = 0,
numByteUsageSamples = 0, cumulativeBytesUsed = 0, bytesCopied = 0,
currentBytesUsed = 0, currentBytesSlop = 0, maxBytesSlop = 0,
peakMegabytesAllocated = 63, mutatorCpuSeconds = 9.6468e-2,
mutatorWallSeconds = 0.115874, gcCpuSeconds = 0.0,
gcWallSeconds = 0.0, cpuSeconds = 9.7045e-2, wallSeconds = 0.115874,
parAvgBytesCopied = 0, parMaxBytesCopied = 0}
}}}
{{{
$ ./Repro +RTS -s
500000.5
GCStats {bytesAllocated = 96086504, numGcs = 184, maxBytesUsed = 27442272,
numByteUsageSamples = 7, cumulativeBytesUsed = 52228768, bytesCopied =
90580024,
currentBytesUsed = 74336, currentBytesSlop = 0, maxBytesSlop = 6803872,
peakMegabytesAllocated = 63, mutatorCpuSeconds = 2.523e-2,
mutatorWallSeconds = 2.5739e-2, gcCpuSeconds = 7.1919e-2,
gcWallSeconds = 9.126e-2, cpuSeconds = 9.7729e-2, wallSeconds = 0.116999,
parAvgBytesCopied = 0, parMaxBytesCopied = 0}
...
}}}
--
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5705#comment:1>
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