[GHC] #14841: Inconsistent allocation stats

GHC ghc-devs at haskell.org
Thu Feb 22 18:56:01 UTC 2018


#14841: Inconsistent allocation stats
-------------------------------------+-------------------------------------
           Reporter:  patrickdoc     |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Runtime        |           Version:
  System                             |
           Keywords:  GCStats,       |  Operating System:  Unknown/Multiple
  RTSStats                           |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 I'm looking at Criterion internals, and seeing an inconsistency in the
 allocations reported by `GCStats` and `RTSStats`. Here is a small
 reproduction:

 {{{#!hs
 {-# LANGUAGE CPP #-}
 module Main where

 import GHC.Stats
 import System.Mem (performGC)

 main :: IO ()
 main = do
     runOldThing 1000
 #if __GLASGOW_HASKELL__ >= 802
     putStrLn "Running new:"
     runThing 1000
 #endif

 runOldThing :: Int -> IO ()
 runOldThing n = loop n 0 >> return ()
   where
     loop 0 _ = return 0
     loop count x = do
       performGC
       stats <- getGCStats
       putStrLn $ show (count `mod` 15) ++ ": " ++ show (bytesAllocated
 stats - x) ++ " num: " ++ show (numGcs stats)
       loop (count-1) (bytesAllocated stats)

 #if __GLASGOW_HASKELL__ >= 802
 runThing :: Int -> IO ()
 runThing = loop
   where
     loop 0 = return ()
     loop n = do
       performGC
       stats <- getRTSStats
       putStrLn $ show (n `mod` 15) ++ ": " ++ show
 (gcdetails_allocated_bytes (gc stats)) ++ " num: " ++ show (gcs stats)
       loop (n-1)
 #endif
 }}}

 This code just performs a garbage collection and then prints the stats in
 a loop. Here is a snippet of the output.

 {{{
 ...
 4: 8840 num: 1967
 3: 4880 num: 1968
 2: 4880 num: 1969
 1: 4880 num: 1970
 0: 4880 num: 1971
 14: 4880 num: 1972
 13: 4976 num: 1973
 12: 4976 num: 1974
 11: 4976 num: 1975
 10: 4976 num: 1976
 9: 4976 num: 1977
 8: 4880 num: 1978
 7: 4880 num: 1979
 6: 4880 num: 1980
 5: 4880 num: 1981
 4: 8840 num: 1982
 3: 4880 num: 1983
 2: 4880 num: 1984
 1: 4880 num: 1985
 0: 4880 num: 1986
 14: 4880 num: 1987
 13: 4976 num: 1988
 12: 4976 num: 1989
 11: 4976 num: 1990
 10: 4976 num: 1991
 9: 4976 num: 1992
 8: 4880 num: 1993
 7: 4880 num: 1994
 6: 4880 num: 1995
 5: 4880 num: 1996
 4: 8840 num: 1997
 3: 4880 num: 1998
 2: 4880 num: 1999
 1: 4880 num: 2000
 }}}

 On the left, I've included the gc number `mod` 15 to show that exactly
 every 15 gcs, there is an extra 4k bytes reported. This output was made
 with 8.2.1.
 On 7.8.4, 7.10.3, and 8.0.2 it's every 23. And on 8.4.0.20180204 it's
 every 9.

 I've played around with extra allocations between garbage collections, but
 the interval remained constant. I tried poking around the rts, but I've
 been unable to determine if this is a bug or just unavoidable noise.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14841>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list