Skip to content

Commit

Permalink
CAD-2069 Cardano.BM.Stats.readProcessStats: minimal, aggregated proce…
Browse files Browse the repository at this point in the history
…ss stats
  • Loading branch information
deepfire committed Oct 19, 2020
1 parent 7a7b0b6 commit 03586ad
Show file tree
Hide file tree
Showing 7 changed files with 131 additions and 34 deletions.
3 changes: 3 additions & 0 deletions iohk-monitoring/iohk-monitoring.cabal
Expand Up @@ -37,6 +37,9 @@ library
Cardano.BM.Counters.Common
Cardano.BM.Counters.Dummy

Cardano.BM.Stats
Cardano.BM.Stats.Types

Cardano.BM.Data.Aggregated
Cardano.BM.Data.AggregatedKind
Cardano.BM.Data.Backend
Expand Down
19 changes: 17 additions & 2 deletions iohk-monitoring/src/Cardano/BM/Counters/Darwin.hsc
Expand Up @@ -3,8 +3,8 @@
{-# LANGUAGE ForeignFunctionInterface #-}

module Cardano.BM.Counters.Darwin
(
readCounters
( readCounters
, readProcessStats
, DiskInfo (..)
) where

Expand All @@ -22,6 +22,7 @@ import System.Posix.Types (ProcessID)
import Cardano.BM.Counters.Common (getMonoClock, readRTSStats)
import Cardano.BM.Data.Observable
import Cardano.BM.Data.Aggregated (Measurable(..))
import Cardano.BM.Stats.Types (ProcessStats(..))
#endif
import Cardano.BM.Data.Counter
import Cardano.BM.Data.SubTrace
Expand Down Expand Up @@ -401,6 +402,20 @@ getMemoryInfo pid =


#ifdef ENABLE_OBSERVABLES
readProcessStats :: IO (Maybe ProcessStats)
readProcessStats = getProcessID >>= \pid -> do
cpu <- getCpuTimes pid
mem <- getMemoryInfo pid
pure . Just $
ProcessStatsDarwin
{ psCentiSecsCpu = timeValToCenti (_user_time cpu)
+ timeValToCenti (_system_time cpu)
, psRSS = fromIntegral (_resident_size mem)
}
where
timeValToCenti :: TIME_VALUE_T -> Word
timeValToCenti = fromIntegral . ceiling . (/ 10000) . usFromTimeValue

readSysStats :: ProcessID -> IO [Counter]
readSysStats _pid = do
-- sysinfo <- getSysInfo
Expand Down
8 changes: 6 additions & 2 deletions iohk-monitoring/src/Cardano/BM/Counters/Dummy.lhs
Expand Up @@ -11,13 +11,14 @@ The only supported measurements are monotonic clock time and RTS statistics for
\begin{code}
{-# LANGUAGE CPP #-}
module Cardano.BM.Counters.Dummy
(
readCounters
( readCounters
, readProcessStats
) where
#ifdef ENABLE_OBSERVABLES
import Cardano.BM.Counters.Common (getMonoClock, readRTSStats)
import Cardano.BM.Data.Observable
import Cardano.BM.Stats.Types (ProcessStats(..))
#endif
import Cardano.BM.Data.Aggregated (Measurable(..))
import Cardano.BM.Data.Counter
Expand All @@ -27,6 +28,9 @@ import Cardano.BM.Data.SubTrace

\label{code:Dummy.readCounters}\index{Counters!Dummy!readCounters}
\begin{code}
readProcessStats :: IO (Maybe ProcessStats)
readProcessStats = pure . Just $ ProcessStatsDummy
readCounters :: SubTrace -> IO [Counter]
readCounters NoTrace = return []
readCounters Neutral = return []
Expand Down
24 changes: 22 additions & 2 deletions iohk-monitoring/src/Cardano/BM/Counters/Linux.lhs
Expand Up @@ -5,10 +5,11 @@
%if style == newcode
\begin{code}
{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
module Cardano.BM.Counters.Linux
(
readCounters
( readCounters
, readProcessStats
) where
#ifdef ENABLE_OBSERVABLES
Expand All @@ -27,6 +28,7 @@ import Text.Read (readMaybe)
import Cardano.BM.Counters.Common (getMonoClock, readRTSStats)
import Cardano.BM.Data.Observable
import Cardano.BM.Data.Aggregated (Measurable(..))
import Cardano.BM.Stats.Types (ProcessStats(..))
#endif
import Cardano.BM.Data.Counter
import Cardano.BM.Data.SubTrace
Expand All @@ -39,6 +41,24 @@ import Cardano.BM.Data.SubTrace
\label{code:Linux.readCounters}\index{Counters!Linux!readCounters}
\begin{code}
readProcessStats :: IO (Maybe ProcessStats)
readProcessStats =
parseProcStats . 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
Just $ ProcessStatsLinux
{ psCentiSecsCpu = user + sys
, psRSS = rss
, psCentiSecsIOWait = blkio
, psThreads = threads
}
parseProcStats _ = Nothing
readCounters :: SubTrace -> IO [Counter]
readCounters NoTrace = return []
readCounters Neutral = return []
Expand Down
70 changes: 42 additions & 28 deletions iohk-monitoring/src/Cardano/BM/Counters/Windows.hsc
Expand Up @@ -4,8 +4,8 @@
{-# LANGUAGE TypeApplications #-}

module Cardano.BM.Counters.Windows
(
readCounters
( readCounters
, readProcessStats
) where

#ifdef ENABLE_OBSERVABLES
Expand All @@ -22,6 +22,7 @@ import System.Win32.Types
import Cardano.BM.Counters.Common (getMonoClock, readRTSStats)
import Cardano.BM.Data.Observable
import Cardano.BM.Data.Aggregated (Measurable(..))
import Cardano.BM.Stats.Types (ProcessStats(..))
#endif
import Cardano.BM.Data.Counter
import Cardano.BM.Data.SubTrace
Expand Down Expand Up @@ -121,7 +122,7 @@ foreign import ccall unsafe c_get_io_counters :: Ptr IOCounters -> CInt -> IO CI


{- system information -}
{-
{-
typedef struct _SYSTEM_INFO {
union {
DWORD dwOemId; // Obsolete field...do not use
Expand Down Expand Up @@ -231,7 +232,7 @@ readCounters (ObservableTrace _ _) = return []
#ifdef ENABLE_OBSERVABLES
readProcMem :: ProcessId -> IO [Counter]
readProcMem pid = do
meminfo <- getMemoryInfo
meminfo <- getMemoryInfo pid
return [ Counter MemoryCounter "Pid" (PureI $ fromIntegral pid)
, Counter MemoryCounter "WorkingSetSize" (PureI $ fromIntegral (_workingSetSize meminfo))
, Counter MemoryCounter "PeakWorkingSetSize" (PureI $ fromIntegral (_peakWorkingSetSize meminfo))
Expand All @@ -243,25 +244,25 @@ readProcMem pid = do
, Counter MemoryCounter "PeakPagefileUsage" (PureI $ fromIntegral (_peakPagefileUsage meminfo))
, Counter MemoryCounter "PageFaultCount" (PureI $ fromIntegral (_pageFaultCount meminfo))
]
where
getMemoryInfo :: IO ProcessMemoryCounters
getMemoryInfo =
allocaBytes 128 $ \ptr -> do
res <- c_get_process_memory_info ptr (fromIntegral pid)
if res <= 0
then do
putStrLn $ "c_get_process_memory_info: failure returned: " ++ (show res)
return $ ProcessMemoryCounters 0 0 0 0 0 0 0 0 0 0
else
peek ptr

getMemoryInfo :: ProcessId -> IO ProcessMemoryCounters
getMemoryInfo pid =
allocaBytes 128 $ \ptr -> do
res <- c_get_process_memory_info ptr (fromIntegral pid)
if res <= 0
then do
putStrLn $ "c_get_process_memory_info: failure returned: " ++ (show res)
return $ ProcessMemoryCounters 0 0 0 0 0 0 0 0 0 0
else
peek ptr
#endif


#ifdef ENABLE_OBSERVABLES
readSysStats :: ProcessId -> IO [Counter]
readSysStats pid = do
sysinfo <- getSysInfo
cputimes <- getCpuTimes
cputimes <- getCpuTimes pid
winbits <- getWinBits
return [ Counter SysInfo "Pid" (PureI $ fromIntegral pid)
, Counter SysInfo "Platform" (PureI $ fromIntegral $ fromEnum Windows)
Expand All @@ -275,7 +276,7 @@ readSysStats pid = do
, Counter SysInfo "KernelTime" (Microseconds $ systime cputimes)
, Counter SysInfo "CPUTime" (Microseconds $ (systime cputimes + usertime cputimes))
, Counter SysInfo "IdleTime" (Microseconds $ idletime cputimes)
, Counter SysInfo "WindowsPlatformBits" (PureI $ fromIntegral winbits)
, Counter SysInfo "WindowsPlatformBits" (PureI $ fromIntegral winbits)
]
where
getWinBits :: IO CInt
Expand Down Expand Up @@ -305,6 +306,19 @@ readSysStats pid = do


#ifdef ENABLE_OBSERVABLES
readProcessStats :: IO (Maybe ProcessStats)
readProcessStats = getCurrentProcessId >>= \pid -> do
cpu <- getCpuTimes pid
mem <- getMemoryInfo pid
pure . Just $
ProcessStatsWindows
{ psCentiSecsCpu = usecsToCenti $ usertime cpu + systime cpu
, psRSS = fromIntegral (_workingSetSize mem)
}
where
usecsToCenti :: ULONGLONG -> Word
usecsToCenti = ceiling . (/ 10000)

readProcStats :: ProcessId -> IO [Counter]
readProcStats pid = do
cputimes <- getCpuTimes
Expand All @@ -314,17 +328,17 @@ readProcStats pid = do
, Counter StatInfo "StartTime" (Microseconds $ idletime cputimes)
, Counter StatInfo "CPUTime" (Microseconds $ (systime cputimes + usertime cputimes))
]
where
getCpuTimes :: IO CpuTimes
getCpuTimes =
allocaBytes 128 $ \ptr -> do
res <- c_get_proc_cpu_times ptr (fromIntegral pid)
if res <= 0
then do
putStrLn $ "c_get_proc_cpu_times: failure returned: " ++ (show res)
return $ CpuTimes 0 0 0
else
peek ptr

getCpuTimes :: ProcessId -> IO CpuTimes
getCpuTimes pid =
allocaBytes 128 $ \ptr -> do
res <- c_get_proc_cpu_times ptr (fromIntegral pid)
if res <= 0
then do
putStrLn $ "c_get_proc_cpu_times: failure returned: " ++ (show res)
return $ CpuTimes 0 0 0
else
peek ptr

#endif

Expand Down
18 changes: 18 additions & 0 deletions iohk-monitoring/src/Cardano/BM/Stats.hs
@@ -0,0 +1,18 @@
{-# LANGUAGE CPP #-}
module Cardano.BM.Stats
( ProcessStats(..)
, Platform.readProcessStats
)
where

import Cardano.BM.Stats.Types (ProcessStats(..))

#if defined(linux_HOST_OS)
import qualified Cardano.BM.Counters.Linux as Platform
#elif defined(mingw32_HOST_OS)
import qualified Cardano.BM.Counters.Windows as Platform
#elif defined(darwin_HOST_OS)
import qualified Cardano.BM.Counters.Darwin as Platform
#else
import qualified Cardano.BM.Counters.Dummy as Platform
#endif
23 changes: 23 additions & 0 deletions iohk-monitoring/src/Cardano/BM/Stats/Types.hs
@@ -0,0 +1,23 @@
module Cardano.BM.Stats.Types
(ProcessStats(..))
where

data ProcessStats
= ProcessStatsDarwin
{ psCentiSecsCpu :: !Word
, psRSS :: !Word
}
| ProcessStatsDummy
{
}
| ProcessStatsLinux
{ psCentiSecsCpu :: !Word
, psRSS :: !Word
, psCentiSecsIOWait :: !Word
, psThreads :: !Word
}
| ProcessStatsWindows
{ psCentiSecsCpu :: !Word
, psRSS :: !Word
}
deriving Show

0 comments on commit 03586ad

Please sign in to comment.