Skip to content

Commit 3ab47b6

Browse files
author
Matthieu Morel
committed
add documentation and cosmetic changes
1 parent 09e8a44 commit 3ab47b6

File tree

3 files changed

+64
-34
lines changed

3 files changed

+64
-34
lines changed

System/Metrics.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -209,8 +209,8 @@ registerDimensional
209209
-> Store -- ^ Metric store
210210
-> IO ()
211211
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
212+
let x = readIORef (Dimensional.dimensionalPoints d) >>= traverse f in
213+
register (Dimensional.dimensionalName d) (DimensionalS (Dimensional.dimensionalDimensions d) x) store
214214

215215
register :: T.Text
216216
-> MetricSampler

System/Metrics/Dimensional.hs

Lines changed: 47 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -1,88 +1,103 @@
11
{-# LANGUAGE LambdaCase #-}
22
{-# LANGUAGE OverloadedStrings #-}
3+
4+
-- | This module defines a type for mutable dimensional string-valued label.
5+
-- Dimensional label are variable values and can be used to track e.g. the
6+
-- current number of call to an api endpoint by its http return code.
7+
-- All operations on Dimensional label are thread-safe.
38
module System.Metrics.Dimensional where
49

510
import qualified System.Metrics.Counter as Counter
611
import qualified System.Metrics.Distribution as Distribution
712
import qualified System.Metrics.Gauge as Gauge
813
import qualified System.Metrics.Label as Label
914

10-
import Prelude hiding (lookup)
11-
import GHC.Exception (Exception)
1215
import Control.Exception (throwIO)
13-
import Data.Text (Text)
14-
import Data.IORef (IORef, atomicModifyIORef', newIORef, readIORef)
1516
import Data.HashMap.Strict (HashMap, empty)
1617
import qualified Data.HashMap.Strict as HashMap
18+
import Data.IORef (IORef, atomicModifyIORef', newIORef, readIORef)
19+
import Data.Text (Text)
20+
import GHC.Exception (Exception)
21+
import Prelude hiding (lookup)
1722

1823
type Name = Text
24+
1925
type Explanation = Text
26+
2027
type Dimensions = [Text]
28+
2129
type Point = [Text]
2230

23-
data Dimensional a = Dimensional {
24-
_create :: !(IO a)
25-
, _name :: !Name
26-
, _explanation :: !Explanation
27-
, _dimensions :: !Dimensions
28-
, _points :: !(IORef (HashMap Point a))
31+
-- | Dimensional metrics storage
32+
data Dimensional a = Dimensional
33+
{ dimensionalCreate :: !(IO a)
34+
, dimensionalName :: !Name
35+
, dimensionalExplanation :: !Explanation
36+
, dimensionalDimensions :: !Dimensions
37+
, dimensionalPoints :: !(IORef (HashMap Point a))
2938
}
3039

31-
newDimensional :: IO a -> Name -> Explanation -> Dimensions -> IO (Dimensional a)
40+
-- | Create a new empty dimensional metrics
41+
newDimensional ::
42+
IO a -> Name -> Explanation -> Dimensions -> IO (Dimensional a)
3243
newDimensional new name explanation dimensions =
33-
Dimensional new name explanation dimensions <$> newIORef empty
44+
Dimensional new name explanation dimensions <$> newIORef empty
3445

35-
data DimensionError
36-
= DimensionError !Name !Dimensions !Point
46+
data DimensionError =
47+
DimensionError !Name
48+
!Dimensions
49+
!Point
3750
deriving (Show, Ord, Eq)
51+
3852
instance Exception DimensionError
3953

4054
data LookupFailure
4155
= UnmatchedDimensions DimensionError
4256
| NotFound
4357
deriving (Show, Ord, Eq)
4458

59+
-- | Returns dimensional metric with specified labels
4560
lookup :: Dimensional a -> Point -> IO (Either LookupFailure a)
4661
lookup d pt
47-
| not $ matchDimensions (_dimensions d) pt = pure $ Left (UnmatchedDimensions err)
62+
| not $ matchDimensions (dimensionalDimensions d) pt =
63+
pure $ Left (UnmatchedDimensions err)
4864
| otherwise = do
49-
toLookupResult . HashMap.lookup pt <$> readIORef (_points d)
65+
toLookupResult . HashMap.lookup pt <$> readIORef (dimensionalPoints d)
5066
where
5167
err :: DimensionError
52-
err = DimensionError (_name d) (_dimensions d) pt
53-
68+
err = DimensionError (dimensionalName d) (dimensionalDimensions d) pt
5469
toLookupResult Nothing = Left NotFound
5570
toLookupResult (Just x) = Right x
5671

5772
matchDimensions :: Dimensions -> Point -> Bool
5873
matchDimensions ds ps = length ds == length ps
5974

75+
-- | Initialize a new empty dimensional metric with specified labels
6076
create :: Dimensional a -> Point -> IO a
6177
create d pt
62-
| not $ matchDimensions (_dimensions d) pt = throwIO err
78+
| not $ matchDimensions (dimensionalDimensions d) pt = throwIO err
6379
| otherwise = do
64-
v <- _create d
65-
atomicModifyIORef' (_points d) (\store -> (HashMap.insert pt v store, ()))
66-
return v
80+
v <- dimensionalCreate d
81+
atomicModifyIORef'
82+
(dimensionalPoints d)
83+
(\store -> (HashMap.insert pt v store, ()))
84+
return v
6785
where
6886
err :: DimensionError
69-
err = DimensionError (_name d) (_dimensions d) pt
87+
err = DimensionError (dimensionalName d) (dimensionalDimensions d) pt
7088

89+
-- | Returns dimensional metric with specified labels, creating it if not exists
7190
lookupOrCreate :: Dimensional a -> Point -> IO a
72-
lookupOrCreate d pt = lookup d pt >>= \case
91+
lookupOrCreate d pt =
92+
lookup d pt >>= \case
7393
Left NotFound -> create d pt
7494
Left (UnmatchedDimensions err) -> throwIO err
7595
Right x -> return x
7696

7797
type Counter = Dimensional Counter.Counter
98+
7899
type Gauge = Dimensional Gauge.Gauge
100+
79101
type Label = Dimensional Label.Label
80-
type Distribution = Dimensional Distribution.Distribution
81102

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
103+
type Distribution = Dimensional Distribution.Distribution

examples/Dimensional.hs

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
import qualified System.Metrics.Counter as Counter
2+
import System.Metrics.Dimensional
3+
4+
main :: IO ()
5+
main = do
6+
c <-
7+
newDimensional
8+
Counter.new
9+
"wai.response"
10+
"endpoints status response"
11+
["url", "status"]
12+
let url = "/hello"
13+
let status = "200"
14+
x <- lookupOrCreate c [url, status]
15+
Counter.inc x

0 commit comments

Comments
 (0)