(original) (raw)
{-# LINE 1 "GHC/Stats.hsc" #-} {-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE RecordWildCards #-} {-# OPTIONS_GHC -funbox-strict-fields #-}
module GHC.Stats (
RTSStats(..), GCDetails(..), RtsTime
, getRTSStats
, getRTSStatsEnabled
) where
import Control.Monad import Data.Int import Data.Word import GHC.Base import GHC.Read ( Read ) import GHC.Show ( Show ) import GHC.IO.Exception import Foreign.Marshal.Alloc import Foreign.Storable import Foreign.Ptr
foreign import ccall "getRTSStats" getRTSStats_ :: Ptr () -> IO ()
foreign import ccall "getRTSStatsEnabled" getRTSStatsEnabled :: IO Bool
data RTSStats = RTSStats {
gcs :: Word32
, major_gcs :: Word32
, allocated_bytes :: Word64
, max_live_bytes :: Word64
, max_large_objects_bytes :: Word64
, max_compact_bytes :: Word64
, max_slop_bytes :: Word64
, max_mem_in_use_bytes :: Word64
, cumulative_live_bytes :: Word64
, copied_bytes :: Word64
, par_copied_bytes :: Word64
, cumulative_par_max_copied_bytes :: Word64
, cumulative_par_balanced_copied_bytes :: Word64
, init_cpu_ns :: RtsTime
, init_elapsed_ns :: RtsTime
, mutator_cpu_ns :: RtsTime
, mutator_elapsed_ns :: RtsTime
, gc_cpu_ns :: RtsTime
, gc_elapsed_ns :: RtsTime
, cpu_ns :: RtsTime
, elapsed_ns :: RtsTime
, gc :: GCDetails } deriving ( Read , Show )
data GCDetails = GCDetails {
gcdetails_gen :: Word32
, gcdetails_threads :: Word32
, gcdetails_allocated_bytes :: Word64
, gcdetails_live_bytes :: Word64
, gcdetails_large_objects_bytes :: Word64
, gcdetails_compact_bytes :: Word64
, gcdetails_slop_bytes :: Word64
, gcdetails_mem_in_use_bytes :: Word64
, gcdetails_copied_bytes :: Word64
, gcdetails_par_max_copied_bytes :: Word64
, gcdetails_par_balanced_copied_bytes :: Word64
, gcdetails_sync_elapsed_ns :: RtsTime
, gcdetails_cpu_ns :: RtsTime
, gcdetails_elapsed_ns :: RtsTime } deriving ( Read , Show )
type RtsTime = Int64
getRTSStats :: IO RTSStats
getRTSStats = do
statsEnabled <- getRTSStatsEnabled
unless statsEnabled . ioError $ IOError
Nothing
UnsupportedOperation
""
"GHC.Stats.getRTSStats: GC stats not enabled. Use +RTS -T -RTS' to enable them." Nothing Nothing allocaBytes ((320)) $ \p -> do {-# LINE 171 "GHC/Stats.hsc" #-} getRTSStats_ p gcs <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) p {-# LINE 173 "GHC/Stats.hsc" #-} major_gcs <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) p {-# LINE 174 "GHC/Stats.hsc" #-} allocated_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) p {-# LINE 175 "GHC/Stats.hsc" #-} max_live_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 16)) p {-# LINE 176 "GHC/Stats.hsc" #-} max_large_objects_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 24)) p {-# LINE 177 "GHC/Stats.hsc" #-} max_compact_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 32)) p {-# LINE 178 "GHC/Stats.hsc" #-} max_slop_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 40)) p {-# LINE 179 "GHC/Stats.hsc" #-} max_mem_in_use_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 48)) p {-# LINE 180 "GHC/Stats.hsc" #-} cumulative_live_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 56)) p {-# LINE 181 "GHC/Stats.hsc" #-} copied_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 64)) p {-# LINE 182 "GHC/Stats.hsc" #-} par_copied_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 72)) p {-# LINE 183 "GHC/Stats.hsc" #-} cumulative_par_max_copied_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 80)) p {-# LINE 185 "GHC/Stats.hsc" #-} cumulative_par_balanced_copied_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 88)) p {-# LINE 187 "GHC/Stats.hsc" #-} init_cpu_ns <- ((\hsc_ptr -> peekByteOff hsc_ptr 96)) p {-# LINE 188 "GHC/Stats.hsc" #-} init_elapsed_ns <- ((\hsc_ptr -> peekByteOff hsc_ptr 104)) p {-# LINE 189 "GHC/Stats.hsc" #-} mutator_cpu_ns <- ((\hsc_ptr -> peekByteOff hsc_ptr 112)) p {-# LINE 190 "GHC/Stats.hsc" #-} mutator_elapsed_ns <- ((\hsc_ptr -> peekByteOff hsc_ptr 120)) p {-# LINE 191 "GHC/Stats.hsc" #-} gc_cpu_ns <- ((\hsc_ptr -> peekByteOff hsc_ptr 128)) p {-# LINE 192 "GHC/Stats.hsc" #-} gc_elapsed_ns <- ((\hsc_ptr -> peekByteOff hsc_ptr 136)) p {-# LINE 193 "GHC/Stats.hsc" #-} cpu_ns <- ((\hsc_ptr -> peekByteOff hsc_ptr 144)) p {-# LINE 194 "GHC/Stats.hsc" #-} elapsed_ns <- ((\hsc_ptr -> peekByteOff hsc_ptr 152)) p {-# LINE 195 "GHC/Stats.hsc" #-} let pgc = ((\hsc_ptr -> hsc_ptr
plusPtr` 160)) p
{-# LINE 196 "GHC/Stats.hsc" #-}
gc <- do
gcdetails_gen <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) pgc
{-# LINE 198 "GHC/Stats.hsc" #-}
gcdetails_threads <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) pgc
{-# LINE 199 "GHC/Stats.hsc" #-}
gcdetails_allocated_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) pgc
{-# LINE 200 "GHC/Stats.hsc" #-}
gcdetails_live_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 16)) pgc
{-# LINE 201 "GHC/Stats.hsc" #-}
gcdetails_large_objects_bytes <-
((\hsc_ptr -> peekByteOff hsc_ptr 24)) pgc
{-# LINE 203 "GHC/Stats.hsc" #-}
gcdetails_compact_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 32)) pgc
{-# LINE 204 "GHC/Stats.hsc" #-}
gcdetails_slop_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 40)) pgc
{-# LINE 205 "GHC/Stats.hsc" #-}
gcdetails_mem_in_use_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 48)) pgc
{-# LINE 206 "GHC/Stats.hsc" #-}
gcdetails_copied_bytes <- ((\hsc_ptr -> peekByteOff hsc_ptr 56)) pgc
{-# LINE 207 "GHC/Stats.hsc" #-}
gcdetails_par_max_copied_bytes <-
((\hsc_ptr -> peekByteOff hsc_ptr 64)) pgc
{-# LINE 209 "GHC/Stats.hsc" #-}
gcdetails_par_balanced_copied_bytes <-
((\hsc_ptr -> peekByteOff hsc_ptr 72)) pgc
{-# LINE 211 "GHC/Stats.hsc" #-}
gcdetails_sync_elapsed_ns <- ((\hsc_ptr -> peekByteOff hsc_ptr 80)) pgc
{-# LINE 212 "GHC/Stats.hsc" #-}
gcdetails_cpu_ns <- ((\hsc_ptr -> peekByteOff hsc_ptr 88)) pgc
{-# LINE 213 "GHC/Stats.hsc" #-}
gcdetails_elapsed_ns <- ((\hsc_ptr -> peekByteOff hsc_ptr 96)) pgc
{-# LINE 214 "GHC/Stats.hsc" #-}
return GCDetails{..}
return RTSStats{..}