Skip to content

Commit

Permalink
CAD-2069 process metrics: add GC time
Browse files Browse the repository at this point in the history
  • Loading branch information
deepfire committed Oct 21, 2020
1 parent 03586ad commit da25603
Show file tree
Hide file tree
Showing 4 changed files with 28 additions and 9 deletions.
5 changes: 5 additions & 0 deletions iohk-monitoring/src/Cardano/BM/Counters/Darwin.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ import Foreign.C.Types
import Foreign.Marshal.Alloc
import Foreign.Ptr
import Foreign.Storable
import qualified GHC.Stats as GhcStats
import System.Posix.Process (getProcessID)
import System.Posix.Types (ProcessID)

Expand Down Expand Up @@ -405,14 +406,18 @@ getMemoryInfo pid =
readProcessStats :: IO (Maybe ProcessStats)
readProcessStats = getProcessID >>= \pid -> do
cpu <- getCpuTimes pid
rts <- GhcStats.getRTSStats
mem <- getMemoryInfo pid
pure . Just $
ProcessStatsDarwin
{ psCentiSecsCpu = timeValToCenti (_user_time cpu)
+ timeValToCenti (_system_time cpu)
, psCentiSecsGC = nsToCenti $ GhcStats.gc_cpu_ns rts
, psRSS = fromIntegral (_resident_size mem)
}
where
nsToCenti :: GhcStats.RtsTime -> Word
nsToCenti = fromIntegral . (/ 10000000)
timeValToCenti :: TIME_VALUE_T -> Word
timeValToCenti = fromIntegral . ceiling . (/ 10000) . usFromTimeValue

Expand Down
24 changes: 15 additions & 9 deletions iohk-monitoring/src/Cardano/BM/Counters/Linux.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module Cardano.BM.Counters.Linux
import Data.Foldable (foldrM)
import Data.Maybe (catMaybes)
import Data.Text (Text, pack)
import qualified GHC.Stats as GhcStats
import System.FilePath.Posix ((</>))
import System.Posix.Files (getFileStatus,fileMode,ownerReadMode,
intersectFileModes)
Expand All @@ -42,22 +43,27 @@ import Cardano.BM.Data.SubTrace
\begin{code}
readProcessStats :: IO (Maybe ProcessStats)
readProcessStats =
parseProcStats . fmap fromIntegral <$> readProcList "/proc/self/stat"
readProcessStats = do
rts <- GhcStats.getRTSStats
mkProcStats rts . fmap fromIntegral <$> readProcList "/proc/self/stat"
where
parseProcStats :: [Word] -> Maybe ProcessStats
parseProcStats (_:_:_:_:_:_:_:_:_:_ -- 00-09
:_:_:_:user:sys:_:_:_:_:threads -- 10-19
:_:_:_:rss:_:_:_:_:_:_ -- 20-29
:_:_:_:_:_:_:_:_:_:_ -- 30-39
:_:blkio:_rest) = -- 40-42
mkProcStats :: GhcStats.RTSStats -> [Word] -> Maybe ProcessStats
mkProcStats rts
(_:_:_:_:_:_:_:_:_:_ -- 00-09
:_:_:_:user:sys:_:_:_:_:threads -- 10-19
:_:_:_:rss:_:_:_:_:_:_ -- 20-29
:_:_:_:_:_:_:_:_:_:_ -- 30-39
:_:blkio:_rest) = -- 40-42
Just $ ProcessStatsLinux
{ psCentiSecsCpu = user + sys
, psCentiSecsGC = nsToCenti $ GhcStats.gc_cpu_ns rts
, psRSS = rss
, psCentiSecsIOWait = blkio
, psThreads = threads
}
parseProcStats _ = Nothing
mkProcStats _ _ = Nothing
nsToCenti :: GhcStats.RtsTime -> Word
nsToCenti = floor . (/ (10000000 :: Double)) . fromIntegral
readCounters :: SubTrace -> IO [Counter]
readCounters NoTrace = return []
Expand Down
5 changes: 5 additions & 0 deletions iohk-monitoring/src/Cardano/BM/Counters/Windows.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ import Foreign.C.Types
import Foreign.Marshal.Alloc
import Foreign.Ptr
import Foreign.Storable
import qualified GHC.Stats as GhcStats
import System.Win32.Process (ProcessId, getCurrentProcessId)
import System.Win32.Types

Expand Down Expand Up @@ -310,14 +311,18 @@ readProcessStats :: IO (Maybe ProcessStats)
readProcessStats = getCurrentProcessId >>= \pid -> do
cpu <- getCpuTimes pid
mem <- getMemoryInfo pid
rts <- GhcStats.getRTSStats
pure . Just $
ProcessStatsWindows
{ psCentiSecsCpu = usecsToCenti $ usertime cpu + systime cpu
, psCentiSecsGC = nsToCenti $ GhcStats.gc_cpu_ns rts
, psRSS = fromIntegral (_workingSetSize mem)
}
where
usecsToCenti :: ULONGLONG -> Word
usecsToCenti = ceiling . (/ 10000)
nsToCenti :: GhcStats.RtsTime -> Word
nsToCenti = fromIntegral . (/ 10000000)

readProcStats :: ProcessId -> IO [Counter]
readProcStats pid = do
Expand Down
3 changes: 3 additions & 0 deletions iohk-monitoring/src/Cardano/BM/Stats/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,19 +5,22 @@ where
data ProcessStats
= ProcessStatsDarwin
{ psCentiSecsCpu :: !Word
, psCentiSecsGC :: !Word
, psRSS :: !Word
}
| ProcessStatsDummy
{
}
| ProcessStatsLinux
{ psCentiSecsCpu :: !Word
, psCentiSecsGC :: !Word
, psRSS :: !Word
, psCentiSecsIOWait :: !Word
, psThreads :: !Word
}
| ProcessStatsWindows
{ psCentiSecsCpu :: !Word
, psCentiSecsGC :: !Word
, psRSS :: !Word
}
deriving Show

0 comments on commit da25603

Please sign in to comment.