magicbane-0.3.0: A web framework that integrates Servant, RIO, EKG, fast-logger, wai-cli…

Safe HaskellNone
LanguageHaskell2010

Magicbane.Metrics

Contents

Description

Provides metrics via monad-metrics/EKG in a Magicbane app context. Also reexports Wai metrics middleware.

Synopsis

Documentation

newtype ModMetrics Source #

Constructors

ModMetrics Metrics 

newMetricsWith :: Store -> IO ModMetrics Source #

Creates a metrics module with a particular Store. The Store should come from the backend you want to use for storing the metrics. For development, a simple backend that shows metrics on a web page is ekg-wai, reexported here.

registerGcMetrics :: Store -> IO () #

Register a number of metrics related to garbage collector behavior.

To enable GC statistics collection, either run your program with

+RTS -T

or compile it with

-with-rtsopts=-T

The runtime overhead of -T is very small so it's safe to always leave it enabled.

Registered counters:

rts.gc.bytes_allocated
Total number of bytes allocated
rts.gc.num_gcs
Number of garbage collections performed
rts.gc.num_bytes_usage_samples
Number of byte usage samples taken
rts.gc.cumulative_bytes_used
Sum of all byte usage samples, can be used with numByteUsageSamples to calculate averages with arbitrary weighting (if you are sampling this record multiple times).
rts.gc.bytes_copied
Number of bytes copied during GC
rts.gc.mutator_cpu_ms
CPU time spent running mutator threads, in milliseconds. This does not include any profiling overhead or initialization.
rts.gc.mutator_wall_ms
Wall clock time spent running mutator threads, in milliseconds. This does not include initialization.
rts.gc.gc_cpu_ms
CPU time spent running GC, in milliseconds.
rts.gc.gc_wall_ms
Wall clock time spent running GC, in milliseconds.
rts.gc.cpu_ms
Total CPU time elapsed since program start, in milliseconds.
rts.gc.wall_ms
Total wall clock time elapsed since start, in milliseconds.

Registered gauges:

rts.gc.max_bytes_used
Maximum number of live bytes seen so far
rts.gc.current_bytes_used
Current number of live bytes
rts.gc.current_bytes_slop
Current number of bytes lost to slop
rts.gc.max_bytes_slop
Maximum number of bytes lost to slop at any one time so far
rts.gc.peak_megabytes_allocated
Maximum number of megabytes allocated
rts.gc.par_tot_bytes_copied
Number of bytes copied during GC, minus space held by mutable lists held by the capabilities. Can be used with parMaxBytesCopied to determine how well parallel GC utilized all cores.
rts.gc.par_avg_bytes_copied
Deprecated alias for par_tot_bytes_copied.
rts.gc.par_max_bytes_copied
Sum of number of bytes copied each GC by the most active GC thread each GC. The ratio of par_tot_bytes_copied divided by par_max_bytes_copied approaches 1 for a maximally sequential run and approaches the number of threads (set by the RTS flag -N) for a maximally parallel run.

data Store #

A mutable metric store.

serverMetricStore :: Server -> Store #

The metric store associated with the server. If you want to add metric to the default store created by forkServer you need to use this function to retrieve it.

label' :: (MonadIO m, MonadMetrics m, Show a) => Text -> a -> m () #

Set the Label to the Shown value of whatever you pass in.

  • Since v0.1.0.0

label :: (MonadIO m, MonadMetrics m) => Text -> Text -> m () #

Set the Label to the given Text value.

  • Since v0.1.0.0

timed :: (MonadIO m, MonadMetrics m, MonadMask m) => Text -> m a -> m a #

Record the time of executing the given action in seconds. Defers to timed'.

  • Since v0.1.0.0

timedList :: (MonadIO m, MonadMetrics m, MonadMask m) => Resolution -> [Text] -> m a -> m a #

Record the time taken to perform the action, under several names at once. The number is stored in a Distribution and is converted to the specified Resolution.

This is useful to store the same durations data sectioned by different criteria, e.g.:

timedList Seconds ["request.byUser." <> userName, "request.byType." <> requestType] $ do
    ...

So you will have "request.byUser.someuser" storing duration distribution for requests of user "someuser" of any type; and "request.byType.sometype" storing duration distribution for requests of type "sometype" from any user.

timed' :: (MonadIO m, MonadMetrics m, MonadMask m) => Resolution -> Text -> m a -> m a #

Record the time taken to perform the named action. The number is stored in a Distribution and is converted to the specified Resolution.

  • Since v0.1.0.0

gauge :: (MonadIO m, MonadMetrics m) => Text -> Int -> m () #

A type specialized version of gauge' to avoid ambiguous types.

  • Since v0.1.0.0

gauge' :: (MonadIO m, MonadMetrics m, Integral int) => Text -> int -> m () #

Set the value of the named Gauge.

  • Since v0.1.0.0

distribution :: (MonadIO m, MonadMetrics m) => Text -> Double -> m () #

Add the value to the named Distribution.

  • Since v0.1.0.0

counter :: (MonadIO m, MonadMetrics m) => Text -> Int -> m () #

A type specialized version of counter' to avoid ambiguous type errors.

  • Since v0.1.0.0

counter' :: (MonadIO m, MonadMetrics m, Integral int) => Text -> int -> m () #

Adds the value to the named Counter.

  • Since v0.1.0.0

increment :: (MonadIO m, MonadMetrics m) => Text -> m () #

Increment the named counter by 1.

  • Since v0.1.0.0

class Monad m => MonadMetrics (m :: * -> *) where #

A type can be an instance of MonadMetrics if it can provide a Metrics somehow. Commonly, this will be implemented as a ReaderT where some field in the environment is the Metrics data.

  • Since v0.1.0.0

Minimal complete definition

getMetrics

Methods

getMetrics :: m Metrics #

Instances
(Has ModMetrics α, Monad μ, MonadReader α μ) => MonadMetrics μ # 
Instance details

Defined in Magicbane.Metrics

Methods

getMetrics :: μ Metrics #

(MonadMetrics m, MonadTrans t, Monad (t m)) => MonadMetrics (t m) 
Instance details

Defined in Control.Monad.Metrics

Methods

getMetrics :: t m Metrics #

Monad m => MonadMetrics (ReaderT Metrics m) 
Instance details

Defined in Control.Monad.Metrics

metricsStore :: Lens' Metrics Store #

A lens into the Store provided by the Metrics.

  • Since v0.1.0.0

metricsLabels :: Lens' Metrics (IORef (HashMap Text Label)) #

A lens into the Labels provided by the Metrics.

  • Since v0.1.0.0

metricsGauges :: Lens' Metrics (IORef (HashMap Text Gauge)) #

A lens into the Gauges provided by the Metrics.

  • Since v0.1.0.0

metricsCounters :: Lens' Metrics (IORef (HashMap Text Counter)) #

A lens into the Counters provided by the Metrics.

  • Since v0.1.0.0

data Metrics #

A container for metrics used by the MonadMetrics class.

  • Since v0.1.0.0
Instances
Monad m => MonadMetrics (ReaderT Metrics m) 
Instance details

Defined in Control.Monad.Metrics

metrics :: WaiMetrics -> Middleware #

Create a middleware to be added to a WAI-based webserver.

registerNamedWaiMetrics :: Text -> Store -> IO WaiMetrics #

Register in EKG a number of metrics related to web server activity with a namespace.

registerWaiMetrics :: Store -> IO WaiMetrics #

Register in EKG a number of metrics related to web server activity using empty namespace.

  • wai.request_count
  • wai.response_status_1xx
  • wai.response_status_2xx
  • wai.response_status_3xx
  • wai.response_status_4xx
  • wai.response_status_5xx
  • wai.latency_distribution

Orphan instances

(Has ModMetrics α, Monad μ, MonadReader α μ) => MonadMetrics μ Source # 
Instance details

Methods

getMetrics :: μ Metrics #