|
1 | 1 | {-# LANGUAGE LambdaCase #-}
|
2 | 2 | {-# 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. |
3 | 8 | module System.Metrics.Dimensional where
|
4 | 9 |
|
5 | 10 | import qualified System.Metrics.Counter as Counter
|
6 | 11 | import qualified System.Metrics.Distribution as Distribution
|
7 | 12 | import qualified System.Metrics.Gauge as Gauge
|
8 | 13 | import qualified System.Metrics.Label as Label
|
9 | 14 |
|
10 |
| -import Prelude hiding (lookup) |
11 |
| -import GHC.Exception (Exception) |
12 | 15 | import Control.Exception (throwIO)
|
13 |
| -import Data.Text (Text) |
14 |
| -import Data.IORef (IORef, atomicModifyIORef', newIORef, readIORef) |
15 | 16 | import Data.HashMap.Strict (HashMap, empty)
|
16 | 17 | 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) |
17 | 22 |
|
18 | 23 | type Name = Text
|
| 24 | + |
19 | 25 | type Explanation = Text
|
| 26 | + |
20 | 27 | type Dimensions = [Text]
|
| 28 | + |
21 | 29 | type Point = [Text]
|
22 | 30 |
|
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)) |
29 | 38 | }
|
30 | 39 |
|
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) |
32 | 43 | newDimensional new name explanation dimensions =
|
33 |
| - Dimensional new name explanation dimensions <$> newIORef empty |
| 44 | + Dimensional new name explanation dimensions <$> newIORef empty |
34 | 45 |
|
35 |
| -data DimensionError |
36 |
| - = DimensionError !Name !Dimensions !Point |
| 46 | +data DimensionError = |
| 47 | + DimensionError !Name |
| 48 | + !Dimensions |
| 49 | + !Point |
37 | 50 | deriving (Show, Ord, Eq)
|
| 51 | + |
38 | 52 | instance Exception DimensionError
|
39 | 53 |
|
40 | 54 | data LookupFailure
|
41 | 55 | = UnmatchedDimensions DimensionError
|
42 | 56 | | NotFound
|
43 | 57 | deriving (Show, Ord, Eq)
|
44 | 58 |
|
| 59 | +-- | Returns dimensional metric with specified labels |
45 | 60 | lookup :: Dimensional a -> Point -> IO (Either LookupFailure a)
|
46 | 61 | lookup d pt
|
47 |
| - | not $ matchDimensions (_dimensions d) pt = pure $ Left (UnmatchedDimensions err) |
| 62 | + | not $ matchDimensions (dimensionalDimensions d) pt = |
| 63 | + pure $ Left (UnmatchedDimensions err) |
48 | 64 | | otherwise = do
|
49 |
| - toLookupResult . HashMap.lookup pt <$> readIORef (_points d) |
| 65 | + toLookupResult . HashMap.lookup pt <$> readIORef (dimensionalPoints d) |
50 | 66 | where
|
51 | 67 | err :: DimensionError
|
52 |
| - err = DimensionError (_name d) (_dimensions d) pt |
53 |
| - |
| 68 | + err = DimensionError (dimensionalName d) (dimensionalDimensions d) pt |
54 | 69 | toLookupResult Nothing = Left NotFound
|
55 | 70 | toLookupResult (Just x) = Right x
|
56 | 71 |
|
57 | 72 | matchDimensions :: Dimensions -> Point -> Bool
|
58 | 73 | matchDimensions ds ps = length ds == length ps
|
59 | 74 |
|
| 75 | +-- | Initialize a new empty dimensional metric with specified labels |
60 | 76 | create :: Dimensional a -> Point -> IO a
|
61 | 77 | create d pt
|
62 |
| - | not $ matchDimensions (_dimensions d) pt = throwIO err |
| 78 | + | not $ matchDimensions (dimensionalDimensions d) pt = throwIO err |
63 | 79 | | 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 |
67 | 85 | where
|
68 | 86 | err :: DimensionError
|
69 |
| - err = DimensionError (_name d) (_dimensions d) pt |
| 87 | + err = DimensionError (dimensionalName d) (dimensionalDimensions d) pt |
70 | 88 |
|
| 89 | +-- | Returns dimensional metric with specified labels, creating it if not exists |
71 | 90 | lookupOrCreate :: Dimensional a -> Point -> IO a
|
72 |
| -lookupOrCreate d pt = lookup d pt >>= \case |
| 91 | +lookupOrCreate d pt = |
| 92 | + lookup d pt >>= \case |
73 | 93 | Left NotFound -> create d pt
|
74 | 94 | Left (UnmatchedDimensions err) -> throwIO err
|
75 | 95 | Right x -> return x
|
76 | 96 |
|
77 | 97 | type Counter = Dimensional Counter.Counter
|
| 98 | + |
78 | 99 | type Gauge = Dimensional Gauge.Gauge
|
| 100 | + |
79 | 101 | type Label = Dimensional Label.Label
|
80 |
| -type Distribution = Dimensional Distribution.Distribution |
81 | 102 |
|
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 |
0 commit comments