freckle-app-1.15.2.0: Haskell application toolkit used at Freckle
Safe HaskellSafe-Inferred
LanguageHaskell2010

Freckle.App.Stats

Description

An intentionally-leaky StatsD interface to Datadog

Synopsis

Documentation

Usage

  data AppSettings = AppSettings
   { -- ...
   , appStatsSettings :: StatsSettings
   }

  loadSettings :: IO AppSettings
  loadSettings = Env.parse id $ AppSettings
    $ -- ...
    * envParseStatsSettings
  

This will read,

  • DOGSTATSD_ENABLED=x
  • DOGSTATSD_HOST=127.0.0.1
  • DOGSTATSD_PORT=8125
  • DOGSTATSD_TAGS=[key:value,...]
  • Optionally DD_ENV, DD_SERVICE, and DD_VERSION
  • Give your App a HasStatsClient instance
  data App = App
    { -- ...
    , appStatsClient :: StatsClient
    }

  instance HasStatsClient App where
    statsClientL = lens appStatsClient $ x y -> { appStatsClient = y }
  
  • Use withStatsClient to build and store a client on your App when you run it
  withStatsClient appStatsSettings $ client -> do
    app <- App
      $ ...
      * pure client

    runApp app $ ...
  
  • Throughout your application code, emit metrics as desired
  import qualified Freckle.App.Stats as Stats

  myFunction :: (MonadIO m, MonadReader env m, HasStatsClient env) => m ()
  myFunction = do
    start <- liftIO getCurrentTime
    result <- myAction

    Stats.increment "action.attempt"
    Stats.histogramSinceMs "action.duration" start

    case result of
      Left err -> do
        Stats.increment "action.failure"
        -- ...
      Right x -. do
        Stats.increment "action.success"
        -- ...
  

Client

data StatsClient Source #

Instances

Instances details
HasStatsClient StatsClient Source # 
Instance details

Defined in Freckle.App.Stats

class HasStatsClient env where Source #

Instances

Instances details
HasStatsClient StatsClient Source # 
Instance details

Defined in Freckle.App.Stats

HasStatsClient site => HasStatsClient (HandlerData child site) Source # 
Instance details

Defined in Freckle.App.Stats

Gauges

withGauge :: (MonadReader app m, HasStatsClient app, MonadUnliftIO m) => (Gauges -> Gauge) -> m a -> m a Source #

Reporting

tagged :: (MonadReader env m, HasStatsClient env) => [(Text, Text)] -> m a -> m a Source #

Include the given tags on all metrics emitted from a block

increment :: (MonadUnliftIO m, MonadReader env m, HasStatsClient env) => Text -> m () Source #

Synonym for counter 1

counter :: (MonadUnliftIO m, MonadReader env m, HasStatsClient env) => Text -> Int -> m () Source #

gauge :: (MonadUnliftIO m, MonadReader env m, HasStatsClient env) => Text -> Double -> m () Source #

histogram :: (MonadUnliftIO m, MonadReader env m, HasStatsClient env, ToMetricValue n) => Text -> n -> m () Source #

Emit an elapsed duration (which Datadog calls a histogram)

The ToMetricValue constraint can be satisfied by most numeric types and is assumed to be seconds.