{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module System.Metrics
(
Store
, newStore
, registerCounter
, registerGauge
, registerLabel
, registerDistribution
, registerGroup
, createCounter
, createGauge
, createLabel
, createDistribution
, registerGcMetrics
, Sample
, sampleAll
, Value(..)
) where
import Control.Applicative ((<$>))
import Control.Monad (forM)
import Data.Int (Int64)
import qualified Data.IntMap.Strict as IM
import Data.IORef (IORef, atomicModifyIORef, newIORef, readIORef)
import qualified Data.HashMap.Strict as M
import qualified Data.Text as T
import qualified GHC.Stats as Stats
import Prelude hiding (read)
import System.Metrics.Counter (Counter)
import qualified System.Metrics.Counter as Counter
import System.Metrics.Distribution (Distribution)
import qualified System.Metrics.Distribution as Distribution
import System.Metrics.Gauge (Gauge)
import qualified System.Metrics.Gauge as Gauge
import System.Metrics.Label (Label)
import qualified System.Metrics.Label as Label
newtype Store = Store { storeState :: IORef State }
type GroupId = Int
data State = State
{ stateMetrics :: !(M.HashMap T.Text (Either MetricSampler GroupId))
, stateGroups :: !(IM.IntMap GroupSampler)
, stateNextId :: {-# UNPACK #-} !Int
}
data GroupSampler = forall a. GroupSampler
{ groupSampleAction :: !(IO a)
, groupSamplerMetrics :: !(M.HashMap T.Text (a -> Value))
}
data MetricSampler = CounterS !(IO Int64)
| GaugeS !(IO Int64)
| LabelS !(IO T.Text)
| DistributionS !(IO Distribution.Stats)
newStore :: IO Store
newStore = do
state <- newIORef $ State M.empty IM.empty 0
return $ Store state
registerCounter :: T.Text
-> IO Int64
-> Store
-> IO ()
registerCounter name sample store =
register name (CounterS sample) store
registerGauge :: T.Text
-> IO Int64
-> Store
-> IO ()
registerGauge name sample store =
register name (GaugeS sample) store
registerLabel :: T.Text
-> IO T.Text
-> Store
-> IO ()
registerLabel name sample store =
register name (LabelS sample) store
registerDistribution
:: T.Text
-> IO Distribution.Stats
-> Store
-> IO ()
registerDistribution name sample store =
register name (DistributionS sample) store
register :: T.Text
-> MetricSampler
-> Store
-> IO ()
register name sample store = do
atomicModifyIORef (storeState store) $ \ state@State{..} ->
case M.member name stateMetrics of
False -> let !state' = state {
stateMetrics = M.insert name
(Left sample)
stateMetrics
}
in (state', ())
True -> alreadyInUseError name
alreadyInUseError :: T.Text -> a
alreadyInUseError name =
error $ "The name \"" ++ show name ++ "\" is already taken " ++
"by a metric."
registerGroup
:: M.HashMap T.Text
(a -> Value)
-> IO a
-> Store
-> IO ()
registerGroup getters cb store = do
atomicModifyIORef (storeState store) $ \ State{..} ->
let !state' = State
{ stateMetrics = M.foldlWithKey' (register_ stateNextId)
stateMetrics getters
, stateGroups = IM.insert stateNextId
(GroupSampler cb getters)
stateGroups
, stateNextId = stateNextId + 1
}
in (state', ())
where
register_ groupId metrics name _ = case M.lookup name metrics of
Nothing -> M.insert name (Right groupId) metrics
Just _ -> alreadyInUseError name
createCounter :: T.Text
-> Store
-> IO Counter
createCounter name store = do
counter <- Counter.new
registerCounter name (Counter.read counter) store
return counter
createGauge :: T.Text
-> Store
-> IO Gauge
createGauge name store = do
gauge <- Gauge.new
registerGauge name (Gauge.read gauge) store
return gauge
createLabel :: T.Text
-> Store
-> IO Label
createLabel name store = do
label <- Label.new
registerLabel name (Label.read label) store
return label
createDistribution :: T.Text
-> Store
-> IO Distribution
createDistribution name store = do
event <- Distribution.new
registerDistribution name (Distribution.read event) store
return event
#if MIN_VERSION_base(4,10,0)
nsToMs :: Int64 -> Int64
nsToMs s = round (realToFrac s / (1000000.0 :: Double))
#else
sToMs :: Double -> Int64
sToMs s = round (s * 1000.0)
#endif
registerGcMetrics :: Store -> IO ()
registerGcMetrics store =
registerGroup
#if MIN_VERSION_base(4,10,0)
(M.fromList
[ ("rts.gc.bytes_allocated" , Counter . fromIntegral . Stats.allocated_bytes)
, ("rts.gc.num_gcs" , Counter . fromIntegral . Stats.gcs)
, ("rts.gc.num_bytes_usage_samples" , Counter . fromIntegral . Stats.major_gcs)
, ("rts.gc.cumulative_bytes_used" , Counter . fromIntegral . Stats.cumulative_live_bytes)
, ("rts.gc.bytes_copied" , Counter . fromIntegral . Stats.copied_bytes)
#if MIN_VERSION_base(4,12,0)
, ("rts.gc.init_cpu_ms" , Counter . nsToMs . Stats.init_cpu_ns)
, ("rts.gc.init_wall_ms" , Counter . nsToMs . Stats.init_elapsed_ns)
#endif
, ("rts.gc.mutator_cpu_ms" , Counter . nsToMs . Stats.mutator_cpu_ns)
, ("rts.gc.mutator_wall_ms" , Counter . nsToMs . Stats.mutator_elapsed_ns)
, ("rts.gc.gc_cpu_ms" , Counter . nsToMs . Stats.gc_cpu_ns)
, ("rts.gc.gc_wall_ms" , Counter . nsToMs . Stats.gc_elapsed_ns)
, ("rts.gc.cpu_ms" , Counter . nsToMs . Stats.cpu_ns)
, ("rts.gc.wall_ms" , Counter . nsToMs . Stats.elapsed_ns)
, ("rts.gc.max_bytes_used" , Gauge . fromIntegral . Stats.max_live_bytes)
, ("rts.gc.current_bytes_used" , Gauge . fromIntegral . Stats.gcdetails_live_bytes . Stats.gc)
, ("rts.gc.current_bytes_slop" , Gauge . fromIntegral . Stats.gcdetails_slop_bytes . Stats.gc)
, ("rts.gc.max_bytes_slop" , Gauge . fromIntegral . Stats.max_slop_bytes)
, ("rts.gc.peak_megabytes_allocated" , Gauge . fromIntegral . (`quot` (1024*1024)) . Stats.max_mem_in_use_bytes)
, ("rts.gc.par_tot_bytes_copied" , Gauge . fromIntegral . Stats.par_copied_bytes)
, ("rts.gc.par_avg_bytes_copied" , Gauge . fromIntegral . Stats.par_copied_bytes)
, ("rts.gc.par_max_bytes_copied" , Gauge . fromIntegral . Stats.cumulative_par_max_copied_bytes)
])
getRTSStats
#else
(M.fromList
[ ("rts.gc.bytes_allocated" , Counter . Stats.bytesAllocated)
, ("rts.gc.num_gcs" , Counter . Stats.numGcs)
, ("rts.gc.num_bytes_usage_samples" , Counter . Stats.numByteUsageSamples)
, ("rts.gc.cumulative_bytes_used" , Counter . Stats.cumulativeBytesUsed)
, ("rts.gc.bytes_copied" , Counter . Stats.bytesCopied)
, ("rts.gc.mutator_cpu_ms" , Counter . sToMs . Stats.mutatorCpuSeconds)
, ("rts.gc.mutator_wall_ms" , Counter . sToMs . Stats.mutatorWallSeconds)
, ("rts.gc.gc_cpu_ms" , Counter . sToMs . Stats.gcCpuSeconds)
, ("rts.gc.gc_wall_ms" , Counter . sToMs . Stats.gcWallSeconds)
, ("rts.gc.cpu_ms" , Counter . sToMs . Stats.cpuSeconds)
, ("rts.gc.wall_ms" , Counter . sToMs . Stats.wallSeconds)
, ("rts.gc.max_bytes_used" , Gauge . Stats.maxBytesUsed)
, ("rts.gc.current_bytes_used" , Gauge . Stats.currentBytesUsed)
, ("rts.gc.current_bytes_slop" , Gauge . Stats.currentBytesSlop)
, ("rts.gc.max_bytes_slop" , Gauge . Stats.maxBytesSlop)
, ("rts.gc.peak_megabytes_allocated" , Gauge . Stats.peakMegabytesAllocated)
, ("rts.gc.par_tot_bytes_copied" , Gauge . gcParTotBytesCopied)
, ("rts.gc.par_avg_bytes_copied" , Gauge . gcParTotBytesCopied)
, ("rts.gc.par_max_bytes_copied" , Gauge . Stats.parMaxBytesCopied)
])
getGcStats
#endif
store
#if MIN_VERSION_base(4,10,0)
getRTSStats :: IO Stats.RTSStats
getRTSStats = do
enabled <- Stats.getRTSStatsEnabled
if enabled
then Stats.getRTSStats
else return emptyRTSStats
emptyRTSStats :: Stats.RTSStats
emptyRTSStats = Stats.RTSStats
{ gcs = 0
, major_gcs = 0
, allocated_bytes = 0
, max_live_bytes = 0
, max_large_objects_bytes = 0
, max_compact_bytes = 0
, max_slop_bytes = 0
, max_mem_in_use_bytes = 0
, cumulative_live_bytes = 0
, copied_bytes = 0
, par_copied_bytes = 0
, cumulative_par_max_copied_bytes = 0
# if MIN_VERSION_base(4,11,0)
, cumulative_par_balanced_copied_bytes = 0
# if MIN_VERSION_base(4,12,0)
, init_cpu_ns = 0
, init_elapsed_ns = 0
# endif
# endif
, mutator_cpu_ns = 0
, mutator_elapsed_ns = 0
, gc_cpu_ns = 0
, gc_elapsed_ns = 0
, cpu_ns = 0
, elapsed_ns = 0
, gc = emptyGCDetails
}
emptyGCDetails :: Stats.GCDetails
emptyGCDetails = Stats.GCDetails
{ gcdetails_gen = 0
, gcdetails_threads = 0
, gcdetails_allocated_bytes = 0
, gcdetails_live_bytes = 0
, gcdetails_large_objects_bytes = 0
, gcdetails_compact_bytes = 0
, gcdetails_slop_bytes = 0
, gcdetails_mem_in_use_bytes = 0
, gcdetails_copied_bytes = 0
, gcdetails_par_max_copied_bytes = 0
# if MIN_VERSION_base(4,11,0)
, gcdetails_par_balanced_copied_bytes = 0
# endif
, gcdetails_sync_elapsed_ns = 0
, gcdetails_cpu_ns = 0
, gcdetails_elapsed_ns = 0
}
#else
getGcStats :: IO Stats.GCStats
# if MIN_VERSION_base(4,6,0)
getGcStats = do
enabled <- Stats.getGCStatsEnabled
if enabled
then Stats.getGCStats
else return emptyGCStats
emptyGCStats :: Stats.GCStats
emptyGCStats = Stats.GCStats
{ bytesAllocated = 0
, numGcs = 0
, maxBytesUsed = 0
, numByteUsageSamples = 0
, cumulativeBytesUsed = 0
, bytesCopied = 0
, currentBytesUsed = 0
, currentBytesSlop = 0
, maxBytesSlop = 0
, peakMegabytesAllocated = 0
, mutatorCpuSeconds = 0
, mutatorWallSeconds = 0
, gcCpuSeconds = 0
, gcWallSeconds = 0
, cpuSeconds = 0
, wallSeconds = 0
, parTotBytesCopied = 0
, parMaxBytesCopied = 0
}
# else
getGcStats = Stats.getGCStats
# endif
gcParTotBytesCopied :: Stats.GCStats -> Int64
# if MIN_VERSION_base(4,6,0)
gcParTotBytesCopied = Stats.parTotBytesCopied
# else
gcParTotBytesCopied = Stats.parAvgBytesCopied
# endif
#endif
type Sample = M.HashMap T.Text Value
sampleAll :: Store -> IO Sample
sampleAll store = do
state <- readIORef (storeState store)
let metrics = stateMetrics state
groups = stateGroups state
cbSample <- sampleGroups $ IM.elems groups
sample <- readAllRefs metrics
let allSamples = sample ++ cbSample
return $! M.fromList allSamples
sampleGroups :: [GroupSampler] -> IO [(T.Text, Value)]
sampleGroups cbSamplers = concat `fmap` sequence (map runOne cbSamplers)
where
runOne :: GroupSampler -> IO [(T.Text, Value)]
runOne GroupSampler{..} = do
a <- groupSampleAction
return $! map (\ (n, f) -> (n, f a)) (M.toList groupSamplerMetrics)
data Value = Counter {-# UNPACK #-} !Int64
| Gauge {-# UNPACK #-} !Int64
| Label {-# UNPACK #-} !T.Text
| Distribution !Distribution.Stats
deriving (Eq, Show)
sampleOne :: MetricSampler -> IO Value
sampleOne (CounterS m) = Counter <$> m
sampleOne (GaugeS m) = Gauge <$> m
sampleOne (LabelS m) = Label <$> m
sampleOne (DistributionS m) = Distribution <$> m
readAllRefs :: M.HashMap T.Text (Either MetricSampler GroupId)
-> IO [(T.Text, Value)]
readAllRefs m = do
forM ([(name, ref) | (name, Left ref) <- M.toList m]) $ \ (name, ref) -> do
val <- sampleOne ref
return (name, val)