Skip to content

Commit

Permalink
trace-resources: restore the ResourceStats HKD
Browse files Browse the repository at this point in the history
  • Loading branch information
deepfire committed Oct 5, 2021
1 parent c9daebd commit ef3fd9b
Show file tree
Hide file tree
Showing 5 changed files with 69 additions and 22 deletions.
4 changes: 2 additions & 2 deletions trace-resources/src/Cardano/Logging/Resources.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
{-# LANGUAGE CPP #-}

module Cardano.Logging.Resources
(
ResourceStats(..)
( Resources(..)
, ResourceStats
, readResourceStats
) where

Expand Down
3 changes: 2 additions & 1 deletion trace-resources/src/Cardano/Logging/Resources/Darwin.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,7 @@ readRessoureStatsInternal = getProcessID >>= \pid -> do
rts <- GhcStats.getRTSStats
mem <- getMemoryInfo pid
pure . Just $
ResourceStats
Resources
{ rCentiCpu = timeValToCenti (_user_time cpu)
+ timeValToCenti (_system_time cpu)
, rCentiGC = nsToCenti $ GhcStats.gc_cpu_ns rts
Expand All @@ -97,6 +97,7 @@ readRessoureStatsInternal = getProcessID >>= \pid -> do
, rGcsMinor = fromIntegral $ GhcStats.gcs rts - GhcStats.major_gcs rts
, rAlloc = GhcStats.allocated_bytes rts
, rLive = GhcStats.gcdetails_live_bytes $ GhcStats.gc rts
, rHeap = GhcStats.gcdetails_mem_in_use_bytes $ GhcStats.gc rts
, rRSS = _resident_size mem
, rCentiBlkIO = 0
, rThreads = 0
Expand Down
3 changes: 2 additions & 1 deletion trace-resources/src/Cardano/Logging/Resources/Linux.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,14 +28,15 @@ readRessoureStatsInternal = do
:_:_:_:rss:_:_:_:_:_:_ -- 20-29
:_:_:_:_:_:_:_:_:_:_ -- 30-39
:_:blkio:_rest) = -- 40-42
Just $ ResourceStats
Just $ Resources
{ rCentiCpu = user + sys
, rCentiGC = nsToCenti $ GhcStats.gc_cpu_ns rts
, rCentiMut = nsToCenti $ GhcStats.mutator_cpu_ns rts
, rGcsMajor = fromIntegral $ GhcStats.major_gcs rts
, rGcsMinor = fromIntegral $ GhcStats.gcs rts - GhcStats.major_gcs rts
, rAlloc = GhcStats.allocated_bytes rts
, rLive = GhcStats.gcdetails_live_bytes $ GhcStats.gc rts
, rHeap = GhcStats.gcdetails_mem_in_use_bytes $ GhcStats.gc rts
, rRSS = rss * 4096 -- TODO: this is really PAGE_SIZE.
, rCentiBlkIO = blkio
, rThreads = threads
Expand Down
78 changes: 61 additions & 17 deletions trace-resources/src/Cardano/Logging/Resources/Types.hs
Original file line number Diff line number Diff line change
@@ -1,37 +1,81 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}

module Cardano.Logging.Resources.Types
(
ResourceStats(..)
( Resources(..)
, ResourceStats
, docResourceStats
) where


import Cardano.Logging.Types
import Data.Aeson (Value (Number, String), (.=))
import Data.Aeson
import Data.Text (pack)
import Data.Word
import GHC.Generics (Generic)

-- | Struct for resources used by the process
data ResourceStats
= ResourceStats
{ rCentiCpu :: !Word64
, rCentiGC :: !Word64
, rCentiMut :: !Word64
, rGcsMajor :: !Word64
, rGcsMinor :: !Word64
, rAlloc :: !Word64
, rLive :: !Word64
, rRSS :: !Word64
, rCentiBlkIO :: !Word64
, rThreads :: !Word64
type ResourceStats = Resources Word64

-- * HKD for resources used by the process.
--
data Resources a
= Resources
{ rCentiCpu :: !a
, rCentiGC :: !a
, rCentiMut :: !a
, rGcsMajor :: !a
, rGcsMinor :: !a
, rAlloc :: !a
, rLive :: !a
, rHeap :: !a
, rRSS :: !a
, rCentiBlkIO :: !a
, rThreads :: !a
}
deriving (Show)
deriving (Functor, Generic, Show)

instance Applicative Resources where
pure a = Resources a a a a a a a a a a a
f <*> x =
Resources
{ rCentiCpu = rCentiCpu f (rCentiCpu x)
, rCentiGC = rCentiGC f (rCentiGC x)
, rCentiMut = rCentiMut f (rCentiMut x)
, rGcsMajor = rGcsMajor f (rGcsMajor x)
, rGcsMinor = rGcsMinor f (rGcsMinor x)
, rAlloc = rAlloc f (rAlloc x)
, rLive = rLive f (rLive x)
, rHeap = rHeap f (rHeap x)
, rRSS = rRSS f (rRSS x)
, rCentiBlkIO = rCentiBlkIO f (rCentiBlkIO x)
, rThreads = rThreads f (rThreads x)
}

instance FromJSON a => FromJSON (Resources a) where
parseJSON = genericParseJSON jsonEncodingOptions

instance ToJSON a => ToJSON (Resources a) where
toJSON = genericToJSON jsonEncodingOptions
toEncoding = genericToEncoding jsonEncodingOptions

jsonEncodingOptions :: Options
jsonEncodingOptions = defaultOptions
{ fieldLabelModifier = drop 1
, tagSingleConstructors = True
, sumEncoding =
TaggedObject
{ tagFieldName = "kind"
, contentsFieldName = "contents"
}
}

docResourceStats :: Documented ResourceStats
docResourceStats = Documented [
DocMsg
(ResourceStats 1 1 1 1 1 1 1 1 1 1)
(pure 0)
[("Stat.Cputicks", "Reports the CPU ticks, sice the process was started")
,("Mem.Resident", "TODO JNF")
,("RTS.GcLiveBytes", "TODO JNF")
Expand Down
3 changes: 2 additions & 1 deletion trace-resources/src/Cardano/Logging/Resources/Windows.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -143,14 +143,15 @@ readRessoureStatsInternal = getCurrentProcessId >>= \pid -> do
mem <- getMemoryInfo pid
rts <- GhcStats.getRTSStats
pure . Just $
ResourceStats
Resources
{ rCentiCpu = usecsToCenti $ usertime cpu + systime cpu
, rCentiGC = nsToCenti $ GhcStats.gc_cpu_ns rts
, rCentiMut = nsToCenti $ GhcStats.mutator_cpu_ns rts
, rGcsMajor = fromIntegral $ GhcStats.major_gcs rts
, rGcsMinor = fromIntegral $ GhcStats.gcs rts - GhcStats.major_gcs rts
, rAlloc = GhcStats.allocated_bytes rts
, rLive = GhcStats.gcdetails_live_bytes $ GhcStats.gc rts
, rHeap = GhcStats.gcdetails_mem_in_use_bytes $ GhcStats.gc rts
, rRSS = fromIntegral (_workingSetSize mem)
, rCentiBlkIO = 0
, rThreads = 0
Expand Down

0 comments on commit ef3fd9b

Please sign in to comment.