instrument-0.6.1.0: Easy stats/metrics instrumentation for Haskell programs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Instrument.Client

Synopsis

Documentation

data Instrument Source #

Instances

Instances details
Monad m => HasInstrument (ReaderT Instrument m) Source # 
Instance details

Defined in Instrument.ClientClass

initInstrument Source #

Arguments

:: ConnectInfo

Redis connection info

-> InstrumentConfig

Instrument configuration. Use "def" if you don't have specific needs

-> IO Instrument 

Initialize an instrument for measurement and feeding data into the system.

The resulting opaque Instrument is meant to be threaded around in your application to be later used in conjunction with sample and time.

sampleI :: MonadIO m => MetricName -> HostDimensionPolicy -> Dimensions -> Double -> Instrument -> m () Source #

Record given measurement under the given label.

Instrument will automatically capture useful stats like min, max, count, avg, stdev and percentiles within a single flush interval.

Say we check our upload queue size every minute and record something like:

>>> sampleI \"uploadQueue\" 27 inst

timeI :: MonadIO m => MetricName -> HostDimensionPolicy -> Dimensions -> Instrument -> m a -> m a Source #

Run a monadic action while measuring its runtime. Push the measurement into the instrument system.

>>> timeI \"fileUploadTime\" policy dims instr $ uploadFile file

timeI' :: MonadIO m => (a -> m (Maybe (MetricName, HostDimensionPolicy, Dimensions))) -> Instrument -> m a -> m a Source #

like timeI but with maximum flexibility: it uses the result and can use the monad to determine the metric name, host dimension policy, and dimensions or even not emit a timing at all. Some use cases include:

  • Emit different metrics or suppress metrics on error
  • Fetch some dimension info from the environment

timeExI :: (MonadIO m, MonadCatch m) => (Either SomeException a -> (MetricName, HostDimensionPolicy, Dimensions)) -> Instrument -> m a -> m a Source #

Run a monadic action while measuring its runtime. Push the measurement into the instrument system. rethrows exceptions and sends a different Metric on failure

>>> timeExI \"fileUploadTimeError\" \"fileUploadTime\" policy dims instr $ uploadFile file

time :: MonadIO m => m a -> m (Double, a) Source #

Measure how long action took, in seconds along with its result

timeEx :: (MonadCatch m, MonadIO m) => m a -> m (Double, Either SomeException a) Source #

Measure how long action took, even if they fail

submitTime Source #

Arguments

:: MonadIO m 
=> MetricName 
-> HostDimensionPolicy 
-> Dimensions 
-> Double

Time in seconds

-> Instrument 
-> m () 

Sometimes dimensions are determined within a code block that you're measuring. In that case, you can use time to measure it and when you're ready to submit, use submitTime.

Also, you may be pulling time details from some external source that you can't measure with timeI yourself.

Note: for legacy purposes, metric name will have "time." prepended to it.

incrementI :: MonadIO m => MetricName -> HostDimensionPolicy -> Dimensions -> Instrument -> m () Source #

Increment a counter by one. Same as calling countI with 1.

>>> incrementI \"uploadedFiles\" instr

countI :: MonadIO m => MetricName -> HostDimensionPolicy -> Dimensions -> Int -> Instrument -> m () Source #

Increment a counter by n.

>>> countI \"uploadedFiles\" 1 instr

packetsKey :: ByteString Source #

A key pointing to a SET of keys with _sq_ prefix, which contain data packets. These are processed by worker.