Skip to content

Commit e86c5d9

Browse files
lucasdicioccioMatthieu Morel
authored andcommitted
Add Dimensional wrapper for metrics.
Breaking change: the Sample type now holds dimensions as key-value pairs.
1 parent 398d6b6 commit e86c5d9

File tree

3 files changed

+168
-11
lines changed

3 files changed

+168
-11
lines changed

System/Metrics.hs

Lines changed: 79 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -49,13 +49,18 @@ module System.Metrics
4949
, registerLabel
5050
, registerDistribution
5151
, registerGroup
52+
, registerDimensional
5253

5354
-- ** Convenience functions
5455
-- $convenience
5556
, createCounter
5657
, createGauge
5758
, createLabel
5859
, createDistribution
60+
, createDimensionalCounter
61+
, createDimensionalGauge
62+
, createDimensionalLabel
63+
, createDimensionalDistribution
5964

6065
-- ** Predefined metrics
6166
-- $predefined
@@ -70,7 +75,9 @@ module System.Metrics
7075

7176
import Control.Applicative ((<$>))
7277
import Control.Monad (forM)
78+
import Data.Either (partitionEithers)
7379
import Data.Int (Int64)
80+
import Data.Monoid ((<>))
7481
import qualified Data.IntMap.Strict as IM
7582
import Data.IORef (IORef, atomicModifyIORef, newIORef, readIORef)
7683
import qualified Data.HashMap.Strict as M
@@ -86,6 +93,8 @@ import System.Metrics.Gauge (Gauge)
8693
import qualified System.Metrics.Gauge as Gauge
8794
import System.Metrics.Label (Label)
8895
import qualified System.Metrics.Label as Label
96+
import System.Metrics.Dimensional (Dimensional)
97+
import qualified System.Metrics.Dimensional as Dimensional
8998

9099
-- $naming
91100
-- Compound metric names should be separated using underscores.
@@ -137,6 +146,7 @@ data MetricSampler = CounterS !(IO Int64)
137146
| GaugeS !(IO Int64)
138147
| LabelS !(IO T.Text)
139148
| DistributionS !(IO Distribution.Stats)
149+
| DimensionalS !Dimensional.Dimensions !(IO (M.HashMap Dimensional.Point Value))
140150

141151
-- | Create a new, empty metric store.
142152
newStore :: IO Store
@@ -192,6 +202,16 @@ registerDistribution
192202
registerDistribution name sample store =
193203
register name (DistributionS sample) store
194204

205+
-- | Registers a dimensional metric.
206+
registerDimensional
207+
:: Dimensional a
208+
-> (a -> IO Value) -- ^ Function to sample the dimensional metric to a Value.
209+
-> Store -- ^ Metric store
210+
-> IO ()
211+
registerDimensional d f store =
212+
let x = readIORef (Dimensional._points d) >>= traverse f in
213+
register (Dimensional._name d) (DimensionalS (Dimensional._dimensions d) x) store
214+
195215
register :: T.Text
196216
-> MetricSampler
197217
-> Store
@@ -323,6 +343,48 @@ createDistribution name store = do
323343
registerDistribution name (Distribution.read event) store
324344
return event
325345

346+
-- | Create and register a zero-initialized dimensional counter.
347+
createDimensionalCounter :: T.Text -- ^ Counter name
348+
-> Store -- ^ Metric store
349+
-> Dimensional.Dimensions -- ^ Dimension names.
350+
-> IO (Dimensional Counter)
351+
createDimensionalCounter name store dims = do
352+
counter <- Dimensional.newDimensional Counter.new name "" dims
353+
registerDimensional counter (fmap Counter . Counter.read) store
354+
return counter
355+
356+
-- | Create and register a zero-initialized dimensional gauge.
357+
createDimensionalGauge :: T.Text -- ^ Gauge name
358+
-> Store -- ^ Metric store
359+
-> Dimensional.Dimensions -- ^ Dimension names.
360+
-> IO (Dimensional Gauge)
361+
createDimensionalGauge name store dims = do
362+
gauge <- Dimensional.newDimensional Gauge.new name "" dims
363+
registerDimensional gauge (fmap Gauge . Gauge.read) store
364+
return gauge
365+
366+
-- | Create and register a zero-initialized dimensional label.
367+
createDimensionalLabel :: T.Text -- ^ Label name
368+
-> Store -- ^ Metric store
369+
-> Dimensional.Dimensions -- ^ Dimension names.
370+
-> IO (Dimensional Label)
371+
createDimensionalLabel name store dims = do
372+
label <- Dimensional.newDimensional Label.new name "" dims
373+
registerDimensional label (fmap Label . Label.read) store
374+
return label
375+
376+
-- | Create and register a zero-initialized dimensional distribution.
377+
createDimensionalDistribution :: T.Text -- ^ Distribution name
378+
-> Store -- ^ Metric store
379+
-> Dimensional.Dimensions -- ^ Dimension names.
380+
-> IO (Dimensional Distribution)
381+
createDimensionalDistribution name store dims = do
382+
distribution <- Dimensional.newDimensional Distribution.new name "" dims
383+
registerDimensional distribution (fmap Distribution . Distribution.read) store
384+
return distribution
385+
386+
387+
326388
------------------------------------------------------------------------
327389
-- * Predefined metrics
328390

@@ -590,7 +652,7 @@ gcParTotBytesCopied = Stats.parAvgBytesCopied
590652
-- metrics atomically.
591653

592654
-- | A sample of some metrics.
593-
type Sample = M.HashMap T.Text Value
655+
type Sample = M.HashMap (T.Text, [(T.Text, T.Text)]) Value
594656

595657
-- | Sample all metrics. Sampling is /not/ atomic in the sense that
596658
-- some metrics might have been mutated before they're sampled but
@@ -601,9 +663,10 @@ sampleAll store = do
601663
let metrics = stateMetrics state
602664
groups = stateGroups state
603665
cbSample <- sampleGroups $ IM.elems groups
604-
sample <- readAllRefs metrics
605-
let allSamples = sample ++ cbSample
606-
return $! M.fromList allSamples
666+
(dimSamples, sample) <- partitionEithers <$> readAllRefs metrics
667+
let noDimSamples = [((k,[]),v) | (k,v) <- sample ++ cbSample]
668+
let flatDimSamples = [ ((k,zip ds dvs),v) | (k, ds, pointVals) <- dimSamples, (dvs,v) <- pointVals]
669+
return $! M.fromList (noDimSamples ++ flatDimSamples)
607670

608671
-- | Sample all metric groups.
609672
sampleGroups :: [GroupSampler] -> IO [(T.Text, Value)]
@@ -621,17 +684,22 @@ data Value = Counter {-# UNPACK #-} !Int64
621684
| Distribution !Distribution.Stats
622685
deriving (Eq, Show)
623686

624-
sampleOne :: MetricSampler -> IO Value
625-
sampleOne (CounterS m) = Counter <$> m
626-
sampleOne (GaugeS m) = Gauge <$> m
627-
sampleOne (LabelS m) = Label <$> m
628-
sampleOne (DistributionS m) = Distribution <$> m
687+
type Value2 = Either (Dimensional.Dimensions, [(Dimensional.Point, Value)]) Value
688+
689+
sampleOne :: MetricSampler -> IO Value2
690+
sampleOne (CounterS m) = Right . Counter <$> m
691+
sampleOne (GaugeS m) = Right . Gauge <$> m
692+
sampleOne (LabelS m) = Right . Label <$> m
693+
sampleOne (DistributionS m) = Right . Distribution <$> m
694+
sampleOne (DimensionalS dims m) = Left . (\pairs -> (dims, pairs)) . M.toList <$> m
629695

630696
-- | Get a snapshot of all values. Note that we're not guaranteed to
631697
-- see a consistent snapshot of the whole map.
632698
readAllRefs :: M.HashMap T.Text (Either MetricSampler GroupId)
633-
-> IO [(T.Text, Value)]
699+
-> IO [Either (T.Text, Dimensional.Dimensions, [(Dimensional.Point, Value)]) (T.Text, Value)]
634700
readAllRefs m = do
635701
forM ([(name, ref) | (name, Left ref) <- M.toList m]) $ \ (name, ref) -> do
636702
val <- sampleOne ref
637-
return (name, val)
703+
return $ case val of
704+
Left (dims, pairs) -> Left (name, dims, pairs)
705+
Right v -> Right (name, v)

System/Metrics/Dimensional.hs

Lines changed: 88 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,88 @@
1+
{-# LANGUAGE LambdaCase #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
module System.Metrics.Dimensional where
4+
5+
import qualified System.Metrics.Counter as Counter
6+
import qualified System.Metrics.Distribution as Distribution
7+
import qualified System.Metrics.Gauge as Gauge
8+
import qualified System.Metrics.Label as Label
9+
10+
import Prelude hiding (lookup)
11+
import GHC.Exception (Exception)
12+
import Control.Exception (throwIO)
13+
import Data.Text (Text)
14+
import Data.IORef (IORef, atomicModifyIORef', newIORef, readIORef)
15+
import Data.HashMap.Strict (HashMap, empty)
16+
import qualified Data.HashMap.Strict as HashMap
17+
18+
type Name = Text
19+
type Explanation = Text
20+
type Dimensions = [Text]
21+
type Point = [Text]
22+
23+
data Dimensional a = Dimensional {
24+
_create :: !(IO a)
25+
, _name :: !Name
26+
, _explanation :: !Explanation
27+
, _dimensions :: !Dimensions
28+
, _points :: !(IORef (HashMap Point a))
29+
}
30+
31+
newDimensional :: IO a -> Name -> Explanation -> Dimensions -> IO (Dimensional a)
32+
newDimensional new name explanation dimensions =
33+
Dimensional new name explanation dimensions <$> newIORef empty
34+
35+
data DimensionError
36+
= DimensionError !Name !Dimensions !Point
37+
deriving (Show, Ord, Eq)
38+
instance Exception DimensionError
39+
40+
data LookupFailure
41+
= UnmatchedDimensions DimensionError
42+
| NotFound
43+
deriving (Show, Ord, Eq)
44+
45+
lookup :: Dimensional a -> Point -> IO (Either LookupFailure a)
46+
lookup d pt
47+
| not $ matchDimensions (_dimensions d) pt = pure $ Left (UnmatchedDimensions err)
48+
| otherwise = do
49+
toLookupResult . HashMap.lookup pt <$> readIORef (_points d)
50+
where
51+
err :: DimensionError
52+
err = DimensionError (_name d) (_dimensions d) pt
53+
54+
toLookupResult Nothing = Left NotFound
55+
toLookupResult (Just x) = Right x
56+
57+
matchDimensions :: Dimensions -> Point -> Bool
58+
matchDimensions ds ps = length ds == length ps
59+
60+
create :: Dimensional a -> Point -> IO a
61+
create d pt
62+
| not $ matchDimensions (_dimensions d) pt = throwIO err
63+
| otherwise = do
64+
v <- _create d
65+
atomicModifyIORef' (_points d) (\store -> (HashMap.insert pt v store, ()))
66+
return v
67+
where
68+
err :: DimensionError
69+
err = DimensionError (_name d) (_dimensions d) pt
70+
71+
lookupOrCreate :: Dimensional a -> Point -> IO a
72+
lookupOrCreate d pt = lookup d pt >>= \case
73+
Left NotFound -> create d pt
74+
Left (UnmatchedDimensions err) -> throwIO err
75+
Right x -> return x
76+
77+
type Counter = Dimensional Counter.Counter
78+
type Gauge = Dimensional Gauge.Gauge
79+
type Label = Dimensional Label.Label
80+
type Distribution = Dimensional Distribution.Distribution
81+
82+
example :: IO ()
83+
example = do
84+
c <- newDimensional Counter.new "foo" "a foo" ["url", "status"]
85+
let url = "/hello"
86+
let status = "200"
87+
x <- lookupOrCreate c [url, status]
88+
Counter.inc x

ekg-core.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ library
2222
exposed-modules:
2323
System.Metrics
2424
System.Metrics.Counter
25+
System.Metrics.Dimensional
2526
System.Metrics.Distribution
2627
System.Metrics.Distribution.Internal
2728
System.Metrics.Gauge

0 commit comments

Comments
 (0)