monad-metrics-extensible-0.1.1.0: An extensible and type-safe wrapper around EKG metrics
Safe HaskellNone
LanguageHaskell2010

System.Metrics.Extensible

Synopsis

Documentation

data Counter #

A mutable, integer-valued counter.

Instances

Instances details
TrackerLike Counter Source # 
Instance details

Defined in System.Metrics.TrackerInstances

Associated Types

type TrackAction Counter m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric Counter name)) => metric Counter name -> TrackAction Counter m Source #

createTracker :: Text -> Store -> IO Counter Source #

type TrackAction Counter m Source # 
Instance details

Defined in System.Metrics.TrackerInstances

type TrackAction Counter m = m ()

data Gauge #

A mutable, integer-valued gauge.

Instances

Instances details
TrackerLike Gauge Source # 
Instance details

Defined in System.Metrics.TrackerInstances

Associated Types

type TrackAction Gauge m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric Gauge name)) => metric Gauge name -> TrackAction Gauge m Source #

createTracker :: Text -> Store -> IO Gauge Source #

type TrackAction Gauge m Source # 
Instance details

Defined in System.Metrics.TrackerInstances

type TrackAction Gauge m = Int64 -> m ()

data Label #

A mutable, text-valued label.

Instances

Instances details
TrackerLike Label Source # 
Instance details

Defined in System.Metrics.TrackerInstances

Associated Types

type TrackAction Label m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric Label name)) => metric Label name -> TrackAction Label m Source #

createTracker :: Text -> Store -> IO Label Source #

type TrackAction Label m Source # 
Instance details

Defined in System.Metrics.TrackerInstances

type TrackAction Label m = Text -> m ()

data Distribution #

An metric for tracking events.

Instances

Instances details
TrackerLike Distribution Source # 
Instance details

Defined in System.Metrics.TrackerInstances

Associated Types

type TrackAction Distribution m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric Distribution name)) => metric Distribution name -> TrackAction Distribution m Source #

createTracker :: Text -> Store -> IO Distribution Source #

type TrackAction Distribution m Source # 
Instance details

Defined in System.Metrics.TrackerInstances

class MonadIO m => MonadMetrics m where Source #

Methods

getTracker :: (TrackerLike tracker, KnownSymbol name, Typeable metric, Ord (metric tracker name)) => metric tracker name -> m tracker Source #

Instances

Instances details
MonadIO m => MonadMetrics (MetricsT m) Source # 
Instance details

Defined in System.Metrics.Monad

Methods

getTracker :: forall tracker (name :: Symbol) metric. (TrackerLike tracker, KnownSymbol name, Typeable metric, Ord (metric tracker name)) => metric tracker name -> MetricsT m tracker Source #

class Typeable tracker => TrackerLike tracker where Source #

Associated Types

type TrackAction tracker (m :: * -> *) = r | r -> m Source #

Methods

track :: (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric tracker name)) => metric tracker name -> TrackAction tracker m Source #

createTracker :: Text -> Store -> IO tracker Source #

Instances

Instances details
TrackerLike Counter Source # 
Instance details

Defined in System.Metrics.TrackerInstances

Associated Types

type TrackAction Counter m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric Counter name)) => metric Counter name -> TrackAction Counter m Source #

createTracker :: Text -> Store -> IO Counter Source #

TrackerLike Gauge Source # 
Instance details

Defined in System.Metrics.TrackerInstances

Associated Types

type TrackAction Gauge m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric Gauge name)) => metric Gauge name -> TrackAction Gauge m Source #

createTracker :: Text -> Store -> IO Gauge Source #

TrackerLike Label Source # 
Instance details

Defined in System.Metrics.TrackerInstances

Associated Types

type TrackAction Label m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric Label name)) => metric Label name -> TrackAction Label m Source #

createTracker :: Text -> Store -> IO Label Source #

TrackerLike Distribution Source # 
Instance details

Defined in System.Metrics.TrackerInstances

Associated Types

type TrackAction Distribution m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric Distribution name)) => metric Distribution name -> TrackAction Distribution m Source #

createTracker :: Text -> Store -> IO Distribution Source #

TrackerLike DistrGauge Source # 
Instance details

Defined in System.Metrics.TrackerInstances

Associated Types

type TrackAction DistrGauge m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric DistrGauge name)) => metric DistrGauge name -> TrackAction DistrGauge m Source #

createTracker :: Text -> Store -> IO DistrGauge Source #

TrackerLike Timestamp Source # 
Instance details

Defined in System.Metrics.ExtraTrackers

Associated Types

type TrackAction Timestamp m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric Timestamp name)) => metric Timestamp name -> TrackAction Timestamp m Source #

createTracker :: Text -> Store -> IO Timestamp Source #

(Typeable magn, MagnitudeOps magn) => TrackerLike (Timer magn) Source # 
Instance details

Defined in System.Metrics.ExtraTrackers

Associated Types

type TrackAction (Timer magn) m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric (Timer magn) name)) => metric (Timer magn) name -> TrackAction (Timer magn) m Source #

createTracker :: Text -> Store -> IO (Timer magn) Source #

withMetricsStore :: (MonadIO m, MonadMask m) => Server -> (MetricsStore -> m a) -> m a Source #

getMetricFromStore :: (TrackerLike tracker, KnownSymbol name, Typeable metric, Ord (metric tracker name)) => MetricsStore -> metric tracker name -> IO tracker Source #

data MetricsT (m :: k -> *) (a :: k) Source #

Instances

Instances details
MonadReader r m => MonadReader r (MetricsT m) Source # 
Instance details

Defined in System.Metrics.Monad

Methods

ask :: MetricsT m r #

local :: (r -> r) -> MetricsT m a -> MetricsT m a #

reader :: (r -> a) -> MetricsT m a #

MonadTrans (MetricsT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in System.Metrics.Monad

Methods

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

Monad m => Monad (MetricsT m) Source # 
Instance details

Defined in System.Metrics.Monad

Methods

(>>=) :: MetricsT m a -> (a -> MetricsT m b) -> MetricsT m b #

(>>) :: MetricsT m a -> MetricsT m b -> MetricsT m b #

return :: a -> MetricsT m a #

Functor m => Functor (MetricsT m) Source # 
Instance details

Defined in System.Metrics.Monad

Methods

fmap :: (a -> b) -> MetricsT m a -> MetricsT m b #

(<$) :: a -> MetricsT m b -> MetricsT m a #

Applicative m => Applicative (MetricsT m) Source # 
Instance details

Defined in System.Metrics.Monad

Methods

pure :: a -> MetricsT m a #

(<*>) :: MetricsT m (a -> b) -> MetricsT m a -> MetricsT m b #

liftA2 :: (a -> b -> c) -> MetricsT m a -> MetricsT m b -> MetricsT m c #

(*>) :: MetricsT m a -> MetricsT m b -> MetricsT m b #

(<*) :: MetricsT m a -> MetricsT m b -> MetricsT m a #

MonadIO m => MonadIO (MetricsT m) Source # 
Instance details

Defined in System.Metrics.Monad

Methods

liftIO :: IO a -> MetricsT m a #

MonadThrow m => MonadThrow (MetricsT m) Source # 
Instance details

Defined in System.Metrics.Monad

Methods

throwM :: Exception e => e -> MetricsT m a #

MonadCatch m => MonadCatch (MetricsT m) Source # 
Instance details

Defined in System.Metrics.Monad

Methods

catch :: Exception e => MetricsT m a -> (e -> MetricsT m a) -> MetricsT m a #

MonadIO m => MonadMetrics (MetricsT m) Source # 
Instance details

Defined in System.Metrics.Monad

Methods

getTracker :: forall tracker (name :: Symbol) metric. (TrackerLike tracker, KnownSymbol name, Typeable metric, Ord (metric tracker name)) => metric tracker name -> MetricsT m tracker Source #

newtype DistrGauge Source #

Constructors

DistrGauge (Distribution, Gauge) 

Instances

Instances details
TrackerLike DistrGauge Source # 
Instance details

Defined in System.Metrics.TrackerInstances

Associated Types

type TrackAction DistrGauge m = (r :: Type) Source #

Methods

track :: forall (m :: Type -> Type) (name :: Symbol) metric. (MonadMetrics m, KnownSymbol name, Typeable metric, Ord (metric DistrGauge name)) => metric DistrGauge name -> TrackAction DistrGauge m Source #

createTracker :: Text -> Store -> IO DistrGauge Source #

type TrackAction DistrGauge m Source # 
Instance details

Defined in System.Metrics.TrackerInstances

type TrackAction DistrGauge m = Int64 -> m ()