Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides the basics for instrumenting Haskell executables for use with the Prometheus monitoring system.
Synopsis
- registerIO :: MonadIO m => m (Metric s) -> m s
- register :: MonadIO m => Metric s -> m s
- unsafeRegisterIO :: IO (Metric s) -> s
- unsafeRegister :: Metric s -> s
- unregisterAll :: MonadIO m => m ()
- collectMetrics :: MonadIO m => m [SampleGroup]
- exportMetricsAsText :: MonadIO m => m ByteString
- data Counter
- counter :: Info -> Metric Counter
- incCounter :: MonadMonitor m => Counter -> m ()
- addCounter :: MonadMonitor m => Counter -> Double -> m Bool
- unsafeAddCounter :: MonadMonitor m => Counter -> Double -> m ()
- addDurationToCounter :: (MonadIO m, MonadMonitor m) => Counter -> m a -> m a
- countExceptions :: (MonadCatch m, MonadMonitor m) => Counter -> m a -> m a
- getCounter :: MonadIO m => Counter -> m Double
- data Gauge
- gauge :: Info -> Metric Gauge
- incGauge :: MonadMonitor m => Gauge -> m ()
- decGauge :: MonadMonitor m => Gauge -> m ()
- addGauge :: MonadMonitor m => Gauge -> Double -> m ()
- subGauge :: MonadMonitor m => Gauge -> Double -> m ()
- setGauge :: MonadMonitor m => Gauge -> Double -> m ()
- setGaugeToDuration :: (MonadIO m, MonadMonitor m) => Gauge -> m a -> m a
- getGauge :: MonadIO m => Gauge -> m Double
- class Observer metric where
- observeDuration :: (Observer metric, MonadIO m, MonadMonitor m) => metric -> m a -> m a
- data Summary
- type Quantile = (Rational, Rational)
- summary :: Info -> [Quantile] -> Metric Summary
- defaultQuantiles :: [Quantile]
- getSummary :: MonadIO m => Summary -> m [(Rational, Double)]
- data Histogram
- histogram :: Info -> [Bucket] -> Metric Histogram
- defaultBuckets :: [Double]
- exponentialBuckets :: Bucket -> Double -> Int -> [Bucket]
- linearBuckets :: Bucket -> Double -> Int -> [Bucket]
- getHistogram :: MonadIO m => Histogram -> m (Map Bucket Int)
- data Vector l m
- vector :: Label l => l -> Metric m -> Metric (Vector l m)
- withLabel :: (Label label, MonadMonitor m) => Vector label metric -> label -> (metric -> IO ()) -> m ()
- removeLabel :: (Label label, MonadMonitor m) => Vector label metric -> label -> m ()
- clearLabels :: (Label label, MonadMonitor m) => Vector label metric -> m ()
- getVectorWith :: Vector label metric -> (metric -> IO a) -> IO [(label, a)]
- class Ord l => Label l where
- type LabelPairs = [(Text, Text)]
- type Label0 = ()
- type Label1 = Text
- type Label2 = (Text, Text)
- type Label3 = (Text, Text, Text)
- type Label4 = (Text, Text, Text, Text)
- type Label5 = (Text, Text, Text, Text, Text)
- type Label6 = (Text, Text, Text, Text, Text, Text)
- type Label7 = (Text, Text, Text, Text, Text, Text, Text)
- type Label8 = (Text, Text, Text, Text, Text, Text, Text, Text)
- type Label9 = (Text, Text, Text, Text, Text, Text, Text, Text, Text)
- class Monad m => MonadMonitor m where
- type Monitor a = MonitorT Identity a
- runMonitor :: Monitor a -> (a, IO ())
- data MonitorT m a
- runMonitorT :: Monad m => MonitorT m a -> m (a, IO ())
- data Info = Info {
- metricName :: Text
- metricHelp :: Text
- newtype Metric s = Metric {
- construct :: IO (s, IO [SampleGroup])
- data Sample = Sample Text LabelPairs ByteString
- data SampleGroup = SampleGroup Info SampleType [Sample]
- data SampleType
Registry
registerIO :: MonadIO m => m (Metric s) -> m s Source #
Registers a metric with the global metric registry.
register :: MonadIO m => Metric s -> m s Source #
Registers a metric with the global metric registry.
unsafeRegisterIO :: IO (Metric s) -> s Source #
Registers a metric with the global metric registry.
IMPORTANT: This method should only be used to register metrics as top level symbols, it should not be run from other pure code.
For example,
>>>
:{
{-# NOINLINE c #-} let c = unsafeRegisterIO $ counter (Info "my_counter" "An example metric") :} ...
unsafeRegister :: Metric s -> s Source #
Registers a metric with the global metric registry.
IMPORTANT: This method should only be used to register metrics as top level symbols, it should not be run from other pure code.
unregisterAll :: MonadIO m => m () Source #
Removes all currently registered metrics from the registry.
collectMetrics :: MonadIO m => m [SampleGroup] Source #
Collect samples from all currently registered metrics. In typical use cases
there is no reason to use this function, instead you should use
exportMetricsAsText
or a convenience library.
This function is likely only of interest if you wish to export metrics in a non-supported format for use with another monitoring service.
Exporting
exportMetricsAsText :: MonadIO m => m ByteString Source #
Export all registered metrics in the Prometheus 0.0.4 text exposition format.
For the full specification of the format, see the official Prometheus documentation.
>>>
:m +Data.ByteString
>>>
myCounter <- register $ counter (Info "my_counter" "Example counter")
>>>
incCounter myCounter
>>>
exportMetricsAsText >>= Data.ByteString.Lazy.putStr
# HELP my_counter Example counter # TYPE my_counter counter my_counter 1.0
Metrics
A metric represents a single value that is being monitored. For example a metric could be the number of open files, the current CPU temperature, the elapsed time of execution, and the latency of HTTP requests.
This module provides 4 built-in metric types: counters, gauges, summaries, and metric vectors. These types of metrics should cover most typical use cases. However, for more specialized use cases it is also possible to write custom metrics.
Counter
A counter models a monotonically increasing value. It is the simplest type of metric provided by this library.
A Counter is typically used to count requests served, tasks completed, errors occurred, etc.
>>>
myCounter <- register $ counter (Info "my_counter" "An example counter")
>>>
replicateM_ 47 (incCounter myCounter)
>>>
getCounter myCounter
47.0>>>
void $ addCounter myCounter 10
>>>
getCounter myCounter
57.0
counter :: Info -> Metric Counter Source #
Creates a new counter metric with a given name and help string.
incCounter :: MonadMonitor m => Counter -> m () Source #
Increments the value of a counter metric by 1.
addCounter :: MonadMonitor m => Counter -> Double -> m Bool Source #
Add the given value to the counter, if it is zero or more.
unsafeAddCounter :: MonadMonitor m => Counter -> Double -> m () Source #
Add the given value to the counter. Panic if it is less than zero.
addDurationToCounter :: (MonadIO m, MonadMonitor m) => Counter -> m a -> m a Source #
Add the duration of an IO action (in seconds) to a counter.
If the IO action throws, no duration is added.
countExceptions :: (MonadCatch m, MonadMonitor m) => Counter -> m a -> m a Source #
Count the amount of times an action throws any synchronous exception.
>>>
exceptions <- register $ counter (Info "exceptions_total" "Total amount of exceptions thrown")
>>>
countExceptions exceptions $ return ()
>>>
getCounter exceptions
0.0>>>
countExceptions exceptions (error "Oh no!") `catch` (\SomeException{} -> return ())
>>>
getCounter exceptions
1.0
It's important to note that this will count *all* synchronous exceptions. If
you want more granular counting of exceptions, you will need to write custom
code using incCounter
.
getCounter :: MonadIO m => Counter -> m Double Source #
Retrieves the current value of a counter metric.
Gauge
A gauge models an arbitrary floating point value. There are operations to set the value of a gauge as well as add and subtract arbitrary values.
>>>
myGauge <- register $ gauge (Info "my_gauge" "An example gauge")
>>>
setGauge myGauge 100
>>>
addGauge myGauge 50
>>>
subGauge myGauge 25
>>>
getGauge myGauge
125.0
incGauge :: MonadMonitor m => Gauge -> m () Source #
Increments a gauge metric by 1.
decGauge :: MonadMonitor m => Gauge -> m () Source #
Decrements a gauge metric by 1.
subGauge :: MonadMonitor m => Gauge -> Double -> m () Source #
Subtracts a value from a gauge metric.
setGauge :: MonadMonitor m => Gauge -> Double -> m () Source #
Sets a gauge metric to a specific value.
setGaugeToDuration :: (MonadIO m, MonadMonitor m) => Gauge -> m a -> m a Source #
Sets a gauge metric to the duration in seconds of an IO action.
Summaries and histograms
An Observer
is a generic metric that captures observations of a
floating point value over time. Different implementations can store
and summarise these value in different ways.
The two main observers are summaries and histograms. A Summary
allows you
to get a precise estimate of a particular quantile, but cannot be meaningfully
aggregated across processes. A Histogram
packs requests into user-supplied
buckets, which can be aggregated meaningfully, but provide much less precise
information on particular quantiles.
class Observer metric where Source #
Interface shared by Summary
and Histogram
.
observe :: MonadMonitor m => metric -> Double -> m () Source #
Observe that a particular floating point value has occurred. For example, observe that this request took 0.23s.
observeDuration :: (Observer metric, MonadIO m, MonadMonitor m) => metric -> m a -> m a Source #
Adds the duration in seconds of an IO action as an observation to an observer metric.
If the IO action throws an exception no duration will be observed.
Summary
A summary is an Observer
that summarizes the observations as a count,
sum, and rank estimations. A typical use case for summaries is measuring
HTTP request latency.
>>>
mySummary <- register $ summary (Info "my_summary" "") defaultQuantiles
>>>
observe mySummary 0
>>>
getSummary mySummary
[(1 % 2,0.0),(9 % 10,0.0),(99 % 100,0.0)]
type Quantile = (Rational, Rational) Source #
A quantile is a pair of a quantile value and an associated acceptable error value.
summary :: Info -> [Quantile] -> Metric Summary Source #
Creates a new summary metric with a given name, help string, and a list of
quantiles. A reasonable set set of quantiles is provided by
defaultQuantiles
.
defaultQuantiles :: [Quantile] Source #
getSummary :: MonadIO m => Summary -> m [(Rational, Double)] Source #
Retrieves a list of tuples containing a quantile and its associated value.
Histogram
A histogram captures observations of a floating point value over time and stores those observations in a user-supplied histogram. A typical use case for histograms is measuring HTTP request latency. Histograms are unlike summaries in that they can be meaningfully aggregated across processes.
>>>
myHistogram <- register $ histogram (Info "my_histogram" "") defaultBuckets
>>>
observe myHistogram 0
>>>
getHistogram myHistogram
fromList [(5.0e-3,1),(1.0e-2,0),(2.5e-2,0),(5.0e-2,0),(0.1,0),(0.25,0),(0.5,0),(1.0,0),(2.5,0),(5.0,0),(10.0,0)]
A histogram. Counts the number of observations that fall within the specified buckets.
histogram :: Info -> [Bucket] -> Metric Histogram Source #
Create a new Histogram
metric with a given name, help string, and
list of buckets. Panics if the list of buckets is not strictly increasing.
A good default list of buckets is defaultBuckets
. You can also create
buckets with linearBuckets
or exponentialBuckets
.
defaultBuckets :: [Double] Source #
The default Histogram buckets. These are tailored to measure the response time (in seconds) of a network service. You will almost certainly need to customize them for your particular use case.
exponentialBuckets :: Bucket -> Double -> Int -> [Bucket] Source #
Create count
buckets, where the lowest bucket has an upper bound of start
and each bucket's upper bound is factor
times the previous bucket's upper bound.
Use this to create buckets for histogram
.
linearBuckets :: Bucket -> Double -> Int -> [Bucket] Source #
Create count
buckets, each width
wide, where the lowest bucket has an
upper bound of start
. Use this to create buckets for histogram
.
getHistogram :: MonadIO m => Histogram -> m (Map Bucket Int) Source #
Retries a map of upper bounds to counts of values observed that are less-than-or-equal-to that upper bound, but greater than any other upper bound in the map.
Vector
A vector models a collection of metrics that share the same name but are partitioned across a set of dimensions.
>>>
myVector <- register $ vector ("method", "code") $ counter (Info "http_requests" "")
>>>
withLabel myVector ("GET", "200") incCounter
>>>
withLabel myVector ("GET", "200") incCounter
>>>
withLabel myVector ("GET", "404") incCounter
>>>
withLabel myVector ("POST", "200") incCounter
>>>
getVectorWith myVector getCounter
[(("GET","200"),2.0),(("GET","404"),1.0),(("POST","200"),1.0)]>>>
exportMetricsAsText >>= Data.ByteString.Lazy.putStr
# HELP http_requests # TYPE http_requests counter http_requests{method="GET",code="200"} 2.0 http_requests{method="GET",code="404"} 1.0 http_requests{method="POST",code="200"} 1.0
vector :: Label l => l -> Metric m -> Metric (Vector l m) Source #
Creates a new vector of metrics given a label.
withLabel :: (Label label, MonadMonitor m) => Vector label metric -> label -> (metric -> IO ()) -> m () Source #
Given a label, applies an operation to the corresponding metric in the vector.
removeLabel :: (Label label, MonadMonitor m) => Vector label metric -> label -> m () Source #
Removes a label from a vector.
clearLabels :: (Label label, MonadMonitor m) => Vector label metric -> m () Source #
Removes all labels from a vector.
Labels
The labels of a vector metric are types of the class Label. This module defines all n-tupes of Strings for n <= 9 to be Labels. Additionally, the type aliases LabelN is defined for each of these tuple types to make specifying the types of vectors more concise.
>>>
:{
>>>
let myVector :: Metric (Vector Label3 Counter);
>>>
myVector = vector ("a", "b", "c") $ counter (Info "some_counter" "")
>>>
:}
class Ord l => Label l where Source #
Label describes a class of types that can be used to as the label of a vector.
labelPairs :: l -> l -> LabelPairs Source #
Instances
Label () Source # | |
Defined in Prometheus.Label labelPairs :: () -> () -> LabelPairs Source # | |
Label Text Source # | |
Defined in Prometheus.Label labelPairs :: Text -> Text -> LabelPairs Source # | |
(a ~ Text, b ~ a) => Label (a, b) Source # | |
Defined in Prometheus.Label labelPairs :: (a, b) -> (a, b) -> LabelPairs Source # | |
(a ~ Text, b ~ a, c ~ a) => Label (a, b, c) Source # | |
Defined in Prometheus.Label labelPairs :: (a, b, c) -> (a, b, c) -> LabelPairs Source # | |
(a ~ Text, b ~ a, c ~ a, d ~ a) => Label (a, b, c, d) Source # | |
Defined in Prometheus.Label labelPairs :: (a, b, c, d) -> (a, b, c, d) -> LabelPairs Source # | |
(a ~ Text, b ~ a, c ~ a, d ~ a, e ~ a) => Label (a, b, c, d, e) Source # | |
Defined in Prometheus.Label labelPairs :: (a, b, c, d, e) -> (a, b, c, d, e) -> LabelPairs Source # | |
(a ~ Text, b ~ a, c ~ a, d ~ a, e ~ a, f ~ a) => Label (a, b, c, d, e, f) Source # | |
Defined in Prometheus.Label labelPairs :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> LabelPairs Source # | |
(a ~ Text, b ~ a, c ~ a, d ~ a, e ~ a, f ~ a, g ~ a) => Label (a, b, c, d, e, f, g) Source # | |
Defined in Prometheus.Label labelPairs :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> LabelPairs Source # | |
(a ~ Text, b ~ a, c ~ a, d ~ a, e ~ a, f ~ a, g ~ a, h ~ a) => Label (a, b, c, d, e, f, g, h) Source # | |
Defined in Prometheus.Label labelPairs :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> LabelPairs Source # | |
(a ~ Text, b ~ a, c ~ a, d ~ a, e ~ a, f ~ a, g ~ a, h ~ a, i ~ a) => Label (a, b, c, d, e, f, g, h, i) Source # | |
Defined in Prometheus.Label labelPairs :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> LabelPairs Source # |
type LabelPairs = [(Text, Text)] Source #
A list of tuples where the first value is the label and the second is the value of that label.
Custom metrics
Custom metrics can be created by directly creating a new Metric
type. There
are two parts of any metric, the handle and the collect method.
The handle is a value embedded in the metric that is intended to allow for communication with the metric from instrumented code. For example, all of the metrics provided by this library use a newtype wrapped TVar of some underlying data type as their handle. When defining a new metric, it is recommended that you use a newtype wrapper around your handle type as it will allow users of your metric to succinctly identify your metric in type signatures.
The collect method is responsible for serializing the current value of
a metric into a list of SampleGroup
s.
The following is an example of a custom metric that models the current CPU time. It uses a newtype wrapped unit as the handler type since it doesn't need to maintain any state.
>>>
:m +System.CPUTime
>>>
:m +Data.ByteString.UTF8
>>>
newtype CPUTime = MkCPUTime ()
>>>
let info = Info "cpu_time" "The current CPU time"
>>>
let toValue = Data.ByteString.UTF8.fromString . show
>>>
let toSample = Sample "cpu_time" [] . toValue
>>>
let toSampleGroup = (:[]) . SampleGroup info GaugeType . (:[]) . toSample
>>>
let collectCPUTime = fmap toSampleGroup getCPUTime
>>>
let cpuTimeMetric = Metric (return (MkCPUTime (), collectCPUTime))
>>>
register cpuTimeMetric
>>>
exportMetricsAsText >>= Data.ByteString.Lazy.putStr
# HELP cpu_time The current CPU time # TYPE cpu_time gauge cpu_time ...
Instrumenting pure code
Pure code can be instrumented through the use of the Monitor
monad and
MonitorT
monad transformer. These constructs work by queueing all
operations on metrics. In order for the operations to actually be performed,
the queue must be evaluated within the IO monad.
The following is a contrived example that defines an add function that records the number of times it was invoked.
add :: Int -> Int -> Monitor Int
Note that the changes to numAdds are not reflected until the updateMetrics value has been evaluated in the IO monad.
>>>
numAdds <- register $ counter (Info "num_adds" "The number of additions")
>>>
let add x y = incCounter numAdds >> return (x + y)
>>>
let (3, updateMetrics) = runMonitor $ (add 1 1) >>= (add 1)
>>>
getCounter numAdds
0.0>>>
updateMetrics
>>>
getCounter numAdds
2.0
class Monad m => MonadMonitor m where Source #
MonadMonitor describes a class of Monads that are capable of performing asynchronous IO operations.
doIO :: IO () -> m () Source #
doIO :: (MonadTrans t, MonadMonitor n, m ~ t n) => IO () -> m () Source #
Instances
MonadMonitor IO Source # | |
MonadMonitor m => MonadMonitor (MaybeT m) Source # | |
Monad m => MonadMonitor (MonitorT m) Source # | |
MonadMonitor m => MonadMonitor (ExceptT e m) Source # | |
MonadMonitor m => MonadMonitor (IdentityT m) Source # | |
(Error e, MonadMonitor m) => MonadMonitor (ErrorT e m) Source # | |
MonadMonitor m => MonadMonitor (StateT s m) Source # | |
MonadMonitor m => MonadMonitor (StateT s m) Source # | |
(MonadMonitor m, Monoid w) => MonadMonitor (WriterT w m) Source # | |
(MonadMonitor m, Monoid w) => MonadMonitor (WriterT w m) Source # | |
MonadMonitor m => MonadMonitor (ReaderT r m) Source # | |
(MonadMonitor m, Monoid w) => MonadMonitor (RWST r w s m) Source # | |
(MonadMonitor m, Monoid w) => MonadMonitor (RWST r w s m) Source # | |
type Monitor a = MonitorT Identity a Source #
Monitor allows the use of Prometheus metrics in pure code. When using Monitor, all of the metric operations will be collected and queued into a single IO () value that can be run from impure code.
Because all of the operations are performed asynchronously use of this class is not recommended for use with metrics that are time sensitive (e.g. for measuring latency).
runMonitor :: Monitor a -> (a, IO ()) Source #
Extract a value and the corresponding monitor update value from the Monitor
monad. For an example use see Monitor
.
MonitorT is the monad transformer analog of Monitor and allows for monitoring pure monad transformer stacks.
Instances
MonadTrans MonitorT Source # | |
Defined in Prometheus.MonadMonitor | |
Monad m => Monad (MonitorT m) Source # | |
Functor m => Functor (MonitorT m) Source # | |
Applicative m => Applicative (MonitorT m) Source # | |
Defined in Prometheus.MonadMonitor | |
Monad m => MonadMonitor (MonitorT m) Source # | |
runMonitorT :: Monad m => MonitorT m a -> m (a, IO ()) Source #
Extract a value and the corresponding monitor update value from the MonitorT monad transformer.
Base data types
Meta data about a metric including its name and a help string that describes the value that the metric is measuring.
Info | |
|
A metric represents a single value that is being monitored. It is comprised of a handle value and a collect method. The handle value is typically a new type wrapped value that provides access to the internal state of the metric. The collect method samples the current value of the metric.
Metric | |
|
A single value recorded at a moment in time. The sample type contains the name of the sample, a list of labels and their values, and the value encoded as a ByteString.
data SampleGroup Source #
A Sample group is a list of samples that is tagged with meta data including the name, help string, and type of the sample.
Instances
Show SampleGroup Source # | |
Defined in Prometheus.Metric showsPrec :: Int -> SampleGroup -> ShowS # show :: SampleGroup -> String # showList :: [SampleGroup] -> ShowS # |
data SampleType Source #
The type of a sample. This corresponds to the 5 types of metrics supported by Prometheus.
Instances
Show SampleType Source # | |
Defined in Prometheus.Metric showsPrec :: Int -> SampleType -> ShowS # show :: SampleType -> String # showList :: [SampleType] -> ShowS # |