freckle-app-1.0.3.0: Haskell application toolkit used at Freckle
Safe HaskellNone
LanguageHaskell2010

Freckle.App.Datadog

Description

Datadog access for your App

Synopsis

Reader environment interface

class HasDogStatsClient app where Source #

Instances

Instances details
HasDogStatsClient site => HasDogStatsClient (HandlerData child site) Source # 
Instance details

Defined in Freckle.App.Datadog

class HasDogStatsTags app where Source #

Methods

getDogStatsTags :: app -> [Tag] Source #

Instances

Instances details
HasDogStatsTags site => HasDogStatsTags (HandlerData child site) Source # 
Instance details

Defined in Freckle.App.Datadog

Methods

getDogStatsTags :: HandlerData child site -> [Tag] Source #

data StatsClient #

Note that Dummy is not the only constructor, just the only publicly available one.

data Tag #

Tags are a Datadog specific extension to StatsD. They allow you to tag a metric with a dimension that’s meaningful to you and slice and dice along that dimension in your graphs. For example, if you wanted to measure the performance of two video rendering algorithms, you could tag the rendering time metric with the version of the algorithm you used.

Instances

Instances details
Eq Tag 
Instance details

Defined in Network.StatsD.Datadog

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Show Tag 
Instance details

Defined in Network.StatsD.Datadog

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

HasTags ServiceCheck [Tag] 
Instance details

Defined in Network.StatsD.Datadog

HasTags Event [Tag] 
Instance details

Defined in Network.StatsD.Datadog

Methods

tags :: Lens' Event [Tag] #

HasTags Metric [Tag] 
Instance details

Defined in Network.StatsD.Datadog

Methods

tags :: Lens' Metric [Tag] #

Lower-level operations

Higher-level operations

Reading settings at startup

data DogStatsSettings #

Constructors

DogStatsSettings 

Fields

  • dogStatsSettingsHost :: HostName

    The hostname or IP of the DogStatsD server (default: 127.0.0.1)

  • dogStatsSettingsPort :: !Int

    The port that the DogStatsD server is listening on (default: 8125)

  • dogStatsSettingsBufferSize :: !Int

    Maximum buffer size. Stats are sent over UDP, so the maximum possible value is 65507 bytes per packet. In some scenarios, however, you may wish to send smaller packets. (default: 65507)

  • dogStatsSettingsMaxDelay :: !Int

    Maximum amount of time (in microseconds) between having no stats to send locally and when new stats will be sent to the statsd server. (default: 1 second)

  • dogStatsSettingsOnException :: SomeException -> Seq ByteString -> IO (Seq ByteString -> Seq ByteString)

    Handler to recover from exceptions thrown while sending stats to the server. Caution: Throwing an exception from this handler will shut down the worker that sends stats to the server, but is not able to prevent you from enqueuing stats via the client. Default: print the exception and throw away any accumulated stats.

mkStatsClient :: MonadIO m => DogStatsSettings -> m StatsClient #

Create a stats client. Be sure to close it with finalizeStatsClient in order to send any pending stats and close the underlying handle when done using it. Alternatively, use withDogStatsD to finalize it automatically.

To be removed in next major bump

guage :: (MonadUnliftIO m, MonadReader env m, HasDogStatsClient env, HasDogStatsTags env) => Text -> [(Text, Text)] -> Double -> m () Source #

Deprecated: Use gauge instead

Deprecated typo version of gauge