ridley-0.3.3.0: Quick metrics to grow your app strong.
Safe HaskellNone
LanguageHaskell2010

System.Metrics.Prometheus.Ridley.Types

Synopsis

Documentation

newtype RidleyT t a Source #

Constructors

Ridley (ReaderT RidleyOptions t a) 

Instances

Instances details
KatipContext Ridley Source # 
Instance details

Defined in System.Metrics.Prometheus.Ridley.Types

Katip Ridley Source # 
Instance details

Defined in System.Metrics.Prometheus.Ridley.Types

MonadTrans RidleyT Source # 
Instance details

Defined in System.Metrics.Prometheus.Ridley.Types

Methods

lift :: Monad m => m a -> RidleyT m a #

Monad t => MonadReader RidleyOptions (RidleyT t) Source # 
Instance details

Defined in System.Metrics.Prometheus.Ridley.Types

Monad t => Monad (RidleyT t) Source # 
Instance details

Defined in System.Metrics.Prometheus.Ridley.Types

Methods

(>>=) :: RidleyT t a -> (a -> RidleyT t b) -> RidleyT t b #

(>>) :: RidleyT t a -> RidleyT t b -> RidleyT t b #

return :: a -> RidleyT t a #

Functor t => Functor (RidleyT t) Source # 
Instance details

Defined in System.Metrics.Prometheus.Ridley.Types

Methods

fmap :: (a -> b) -> RidleyT t a -> RidleyT t b #

(<$) :: a -> RidleyT t b -> RidleyT t a #

Applicative t => Applicative (RidleyT t) Source # 
Instance details

Defined in System.Metrics.Prometheus.Ridley.Types

Methods

pure :: a -> RidleyT t a #

(<*>) :: RidleyT t (a -> b) -> RidleyT t a -> RidleyT t b #

liftA2 :: (a -> b -> c) -> RidleyT t a -> RidleyT t b -> RidleyT t c #

(*>) :: RidleyT t a -> RidleyT t b -> RidleyT t b #

(<*) :: RidleyT t a -> RidleyT t b -> RidleyT t a #

MonadIO t => MonadIO (RidleyT t) Source # 
Instance details

Defined in System.Metrics.Prometheus.Ridley.Types

Methods

liftIO :: IO a -> RidleyT t a #

type Port = Int Source #

data RidleyMetric Source #

Constructors

ProcessMemory 
CPULoad 
GHCConc

Tap into the metrics exposed by GHC.Conc

Network 
Wai 
DiskUsage

Gets stats about Disk usage (free space, etc)

CustomMetric 

Fields

  • !Text

    The name of the metric

  • !(Maybe Int)

    An optional timeout, in microseconds, that regulates how often the metric is actually updated. If Nothing, the metric will be updated using Ridley top-level setting, if Just the underlying IO action will be run only every n seconds, or cached otherwise.

  • (forall m. MonadIO m => RidleyOptions -> RegistryT m RidleyMetricHandler)

    An action to generate the handler. ^ A user-defined metric, identified by a name.

data RidleyOptions Source #

Instances

Instances details
Monad t => MonadReader RidleyOptions (RidleyT t) Source # 
Instance details

Defined in System.Metrics.Prometheus.Ridley.Types

metric :: RidleyMetricHandler -> c Source #

An opaque metric

updateMetric :: RidleyMetricHandler -> c -> Bool -> IO () Source #

An IO action used to update the metric

flush :: RidleyMetricHandler -> Bool Source #

Whether or not to flush this Metric

label :: RidleyMetricHandler -> Text Source #

A user-friendly label, used to report errors

mkRidleyMetricHandler :: forall c. HasCallStack => Text -> c -> (c -> Bool -> IO ()) -> Bool -> RidleyMetricHandler Source #