Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/41138fd97a9944850b79488196b617597a0fe0c4

>---------------------------------------------------------------

commit 41138fd97a9944850b79488196b617597a0fe0c4
Author: Johan Tibell <[email protected]>
Date:   Tue Oct 25 17:12:06 2011 -0700

    GHC.Stats: Use camelCase in public APIs

>---------------------------------------------------------------

 GHC/Stats.hsc |  110 ++++++++++++++++++++++++++++----------------------------
 1 files changed, 55 insertions(+), 55 deletions(-)

diff --git a/GHC/Stats.hsc b/GHC/Stats.hsc
index 9755f2b..92b33e2 100644
--- a/GHC/Stats.hsc
+++ b/GHC/Stats.hsc
@@ -22,76 +22,76 @@ foreign import ccall "getGCStats"    getGCStats_    :: Ptr 
() -> IO ()
 
 -- | Global garbage collection and memory statistics.
 data GCStats = GCStats
-    { bytes_allocated :: !Int64 -- ^ Total number of bytes allocated
-    , num_gcs :: !Int64 -- ^ Number of garbage collections performed
-    , max_bytes_used :: !Int64 -- ^ Maximum number of live bytes seen so far
-    , num_byte_usage_samples :: !Int64 -- ^ Number of byte usage samples taken
+    { bytesAllocated :: !Int64 -- ^ Total number of bytes allocated
+    , numGcs :: !Int64 -- ^ Number of garbage collections performed
+    , maxBytesUsed :: !Int64 -- ^ Maximum number of live bytes seen so far
+    , numByteUsageSamples :: !Int64 -- ^ Number of byte usage samples taken
     -- | Sum of all byte usage samples, can be used with
-    -- 'num_byte_usage_samples' to calculate averages with
+    -- 'numByteUsageSamples' to calculate averages with
     -- arbitrary weighting (if you are sampling this record multiple
     -- times).
-    , cumulative_bytes_used :: !Int64
-    , bytes_copied :: !Int64 -- ^ Number of bytes copied during GC
-    , current_bytes_used :: !Int64 -- ^ Current number of live bytes
-    , current_bytes_slop :: !Int64 -- ^ Current number of bytes lost to slop
-    , max_bytes_slop :: !Int64 -- ^ Maximum number of bytes lost to slop at 
any one time so far
-    , peak_megabytes_allocated :: !Int64 -- ^ Maximum number of megabytes 
allocated
+    , cumulativeBytesUsed :: !Int64
+    , bytesCopied :: !Int64 -- ^ Number of bytes copied during GC
+    , currentBytesUsed :: !Int64 -- ^ Current number of live bytes
+    , currentBytesSlop :: !Int64 -- ^ Current number of bytes lost to slop
+    , maxBytesSlop :: !Int64 -- ^ Maximum number of bytes lost to slop at any 
one time so far
+    , peakMegabytesAllocated :: !Int64 -- ^ Maximum number of megabytes 
allocated
     -- | CPU time spent running mutator threads.  This does not include
     -- any profiling overhead or initialization.
-    , mutator_cpu_seconds :: !Double
+    , mutatorCpuSeconds :: !Double
     -- | Wall clock time spent running mutator threads.  This does not
     -- include initialization.
-    , mutator_wall_seconds :: !Double
-    , gc_cpu_seconds :: !Double -- ^ CPU time spent running GC
-    , gc_wall_seconds :: !Double -- ^ Wall clock time spent running GC
-    , cpu_seconds :: !Double -- ^ Total CPU time elapsed since program start
-    , wall_seconds :: !Double -- ^ Total wall clock time elapsed since start
+    , mutatorWallSeconds :: !Double
+    , gcCpuSeconds :: !Double -- ^ CPU time spent running GC
+    , gcWallSeconds :: !Double -- ^ Wall clock time spent running GC
+    , cpuSeconds :: !Double -- ^ Total CPU time elapsed since program start
+    , wallSeconds :: !Double -- ^ Total wall clock time elapsed since start
     -- | Number of bytes copied during GC, minus space held by mutable
     -- lists held by the capabilities.  Can be used with
-    -- 'par_max_bytes_copied' to determine how well parallel GC utilized
+    -- 'parMaxBytesCopied' to determine how well parallel GC utilized
     -- all cores.
-    , par_avg_bytes_copied :: !Int64
+    , parAvgBytesCopied :: !Int64
     -- | Sum of number of bytes copied each GC by the most active GC
-    -- thread each GC.  The ratio of 'par_avg_bytes_copied' divided by
-    -- 'par_max_bytes_copied' approaches 1 for a maximally sequential
+    -- thread each GC.  The ratio of 'parAvgBytesCopied' divided by
+    -- 'parMaxBytesCopied' approaches 1 for a maximally sequential
     -- run and approaches the number of threads (set by the RTS flag
     -- @-N@) for a maximally parallel run.
-    , par_max_bytes_copied :: !Int64
+    , parMaxBytesCopied :: !Int64
     } deriving (Show, Read)
 
     {-
-    , g_init_cpu_seconds :: !Double
-    , g_init_wall_seconds :: !Double
+    , initCpuSeconds :: !Double
+    , initWallSeconds :: !Double
     -}
 
 -- | Retrieves garbage collection and memory statistics as of the last
 -- garbage collection.  If you would like your statistics as recent as
--- possible, first run a 'performGC' from "System.Mem".
+-- possible, first run a 'System.Mem.performGC'.
 getGCStats :: IO GCStats
 getGCStats = allocaBytes (#size GCStats) $ \p -> do
     getGCStats_ p
-    bytes_allocated <- (# peek GCStats, bytes_allocated) p
-    num_gcs <- (# peek GCStats, num_gcs ) p
-    num_byte_usage_samples <- (# peek GCStats, num_byte_usage_samples ) p
-    max_bytes_used <- (# peek GCStats, max_bytes_used ) p
-    cumulative_bytes_used <- (# peek GCStats, cumulative_bytes_used ) p
-    bytes_copied <- (# peek GCStats, bytes_copied ) p
-    current_bytes_used <- (# peek GCStats, current_bytes_used ) p
-    current_bytes_slop <- (# peek GCStats, current_bytes_slop) p
-    max_bytes_slop <- (# peek GCStats, max_bytes_slop) p
-    peak_megabytes_allocated <- (# peek GCStats, peak_megabytes_allocated ) p
+    bytesAllocated <- (# peek GCStats, bytes_allocated) p
+    numGcs <- (# peek GCStats, num_gcs ) p
+    numByteUsageSamples <- (# peek GCStats, num_byte_usage_samples ) p
+    maxBytesUsed <- (# peek GCStats, max_bytes_used ) p
+    cumulativeBytesUsed <- (# peek GCStats, cumulative_bytes_used ) p
+    bytesCopied <- (# peek GCStats, bytes_copied ) p
+    currentBytesUsed <- (# peek GCStats, current_bytes_used ) p
+    currentBytesSlop <- (# peek GCStats, current_bytes_slop) p
+    maxBytesSlop <- (# peek GCStats, max_bytes_slop) p
+    peakMegabytesAllocated <- (# peek GCStats, peak_megabytes_allocated ) p
     {-
-    init_cpu_seconds <- (# peek GCStats, init_cpu_seconds) p
-    init_wall_seconds <- (# peek GCStats, init_wall_seconds) p
+    initCpuSeconds <- (# peek GCStats, init_cpu_seconds) p
+    initWallSeconds <- (# peek GCStats, init_wall_seconds) p
     -}
-    mutator_cpu_seconds <- (# peek GCStats, mutator_cpu_seconds) p
-    mutator_wall_seconds <- (# peek GCStats, mutator_wall_seconds) p
-    gc_cpu_seconds <- (# peek GCStats, gc_cpu_seconds) p
-    gc_wall_seconds <- (# peek GCStats, gc_wall_seconds) p
-    cpu_seconds <- (# peek GCStats, cpu_seconds) p
-    wall_seconds <- (# peek GCStats, wall_seconds) p
-    par_avg_bytes_copied <- (# peek GCStats, par_avg_bytes_copied) p
-    par_max_bytes_copied <- (# peek GCStats, par_max_bytes_copied) p
+    mutatorCpuSeconds <- (# peek GCStats, mutator_cpu_seconds) p
+    mutatorWallSeconds <- (# peek GCStats, mutator_wall_seconds) p
+    gcCpuSeconds <- (# peek GCStats, gc_cpu_seconds) p
+    gcWallSeconds <- (# peek GCStats, gc_wall_seconds) p
+    cpuSeconds <- (# peek GCStats, cpu_seconds) p
+    wallSeconds <- (# peek GCStats, wall_seconds) p
+    parAvgBytesCopied <- (# peek GCStats, par_avg_bytes_copied) p
+    parMaxBytesCopied <- (# peek GCStats, par_max_bytes_copied) p
     return GCStats { .. }
 
 {-
@@ -101,19 +101,19 @@ getGCStats = allocaBytes (#size GCStats) $ \p -> do
 -- but that needs a new rts/ header.
 
 data TaskStats = TaskStats
-    { task_mut_cpu_seconds :: Int64
-    , task_mut_wall_seconds :: Int64
-    , task_gc_cpu_seconds :: Int64
-    , task_gc_wall_seconds :: Int64
+    { taskMutCpuSeconds :: Int64
+    , taskMutWallSeconds :: Int64
+    , taskGcCpuSeconds :: Int64
+    , taskGcWallSeconds :: Int64
     } deriving (Show, Read)
 
 data SparkStats = SparkStats
-    { sparks_created :: Int64
-    , sparks_dud :: Int64
-    , sparks_overflowed :: Int64
-    , sparks_converted :: Int64
-    , sparks_gcd :: Int64
-    , sparks_fizzled :: Int64
+    { sparksCreated :: Int64
+    , sparksDud :: Int64
+    , sparksOverflowed :: Int64
+    , sparksConverted :: Int64
+    , sparksGcd :: Int64
+    , sparksFizzled :: Int64
     } deriving (Show, Read)
 
 -- We also could get per-generation stats, which requires a



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to