datadog-0.2.5.0: Datadog client for Haskell. Supports both the HTTP API and StatsD.

Safe HaskellNone
LanguageHaskell2010

Network.StatsD.Datadog

Contents

Description

DogStatsD accepts custom application metrics points over UDP, and then periodically aggregates and forwards the metrics to Datadog, where they can be graphed on dashboards. The data is sent by using a client library such as this one that communicates with a DogStatsD server.

Synopsis

Client interface

data DogStatsSettings Source #

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.

withDogStatsD :: MonadUnliftIO m => DogStatsSettings -> (StatsClient -> m a) -> m a Source #

Create a StatsClient and provide it to the provided function. The StatsClient will be finalized as soon as the inner block is exited, whether normally or via an exception.

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

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.

finalizeStatsClient :: MonadIO m => StatsClient -> m () Source #

Send all pending unsent events and close the connection to the specified statsd server.

send :: (MonadIO m, ToStatsD v) => StatsClient -> v -> m () Source #

Send a Metric, Event, or StatusCheck to the DogStatsD server.

Since UDP is used to send the events, there is no ack that sent values are successfully dealt with.

withDogStatsD defaultSettings $ \client -> do
  send client $ event "Wombat attack" "A host of mighty wombats has breached the gates"
  send client $ metric "wombat.force_count" Gauge (9001 :: Int)
  send client $ serviceCheck "Wombat Radar" ServiceOk

Data supported by DogStatsD

metric :: ToMetricValue a => MetricName -> MetricType -> a -> Metric Source #

Smart Metric constructor. Use the lens functions to set the optional fields.

data Metric Source #

Metric

The fields accessible through corresponding lenses are:

Instances
ToStatsD Metric Source # 
Instance details

Defined in Network.StatsD.Datadog

Methods

toStatsD :: Metric -> Utf8Builder ()

HasType' Metric MetricType Source # 
Instance details

Defined in Network.StatsD.Datadog

HasSampleRate Metric Double Source # 
Instance details

Defined in Network.StatsD.Datadog

HasName Metric MetricName Source # 
Instance details

Defined in Network.StatsD.Datadog

HasTags Metric [Tag] Source # 
Instance details

Defined in Network.StatsD.Datadog

Methods

tags :: Lens' Metric [Tag] Source #

newtype MetricName Source #

Constructors

MetricName 

Fields

Instances
HasName Metric MetricName Source # 
Instance details

Defined in Network.StatsD.Datadog

data MetricType Source #

Constructors

Gauge

Gauges measure the value of a particular thing at a particular time, like the amount of fuel in a car’s gas tank or the number of users connected to a system.

Counter

Counters track how many times something happened per second, like the number of database requests or page views.

Timer

StatsD only supports histograms for timing, not generic values (like the size of uploaded files or the number of rows returned from a query). Timers are essentially a special case of histograms, so they are treated in the same manner by DogStatsD for backwards compatibility.

Histogram

Histograms track the statistical distribution of a set of values, like the duration of a number of database queries or the size of files uploaded by users. Each histogram will track the average, the minimum, the maximum, the median and the 95th percentile.

Set

Sets are used to count the number of unique elements in a group. If you want to track the number of unique visitor to your site, sets are a great way to do that.

Instances
HasType' Metric MetricType Source # 
Instance details

Defined in Network.StatsD.Datadog

event :: Text -> Text -> Event Source #

Smart Event constructor. Use the lens functions to set the optional fields.

data Event Source #

data ServiceCheckStatus Source #

Instances
Enum ServiceCheckStatus Source # 
Instance details

Defined in Network.StatsD.Datadog

Eq ServiceCheckStatus Source # 
Instance details

Defined in Network.StatsD.Datadog

Ord ServiceCheckStatus Source # 
Instance details

Defined in Network.StatsD.Datadog

Read ServiceCheckStatus Source # 
Instance details

Defined in Network.StatsD.Datadog

Show ServiceCheckStatus Source # 
Instance details

Defined in Network.StatsD.Datadog

HasStatus ServiceCheck ServiceCheckStatus Source # 
Instance details

Defined in Network.StatsD.Datadog

class ToStatsD a Source #

Convert an Event, Metric, or StatusCheck to their wire format.

Minimal complete definition

toStatsD

Instances
ToStatsD Metric Source # 
Instance details

Defined in Network.StatsD.Datadog

Methods

toStatsD :: Metric -> Utf8Builder ()

ToStatsD Event Source # 
Instance details

Defined in Network.StatsD.Datadog

Methods

toStatsD :: Event -> Utf8Builder ()

ToStatsD ServiceCheck Source # 
Instance details

Defined in Network.StatsD.Datadog

Optional fields

data Tag Source #

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
Eq Tag Source # 
Instance details

Defined in Network.StatsD.Datadog

Methods

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

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

Show Tag Source # 
Instance details

Defined in Network.StatsD.Datadog

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

HasTags Metric [Tag] Source # 
Instance details

Defined in Network.StatsD.Datadog

Methods

tags :: Lens' Metric [Tag] Source #

HasTags Event [Tag] Source # 
Instance details

Defined in Network.StatsD.Datadog

Methods

tags :: Lens' Event [Tag] Source #

HasTags ServiceCheck [Tag] Source # 
Instance details

Defined in Network.StatsD.Datadog

tag :: Text -> Text -> Tag Source #

Create a tag from a key-value pair. Useful for slicing and dicing events in Datadog.

Key and value text values are normalized by converting ":"s, "|"s, and "@"s to underscores ("_").

class ToMetricValue a where Source #

Converts a supported numeric type to the format understood by DogStatsD. Currently limited by BufferBuilder encoding options.

Methods

encodeValue :: a -> Utf8Builder () Source #

Instances
ToMetricValue Double Source # 
Instance details

Defined in Network.StatsD.Datadog

ToMetricValue Int Source # 
Instance details

Defined in Network.StatsD.Datadog

value :: ToMetricValue a => Setter Metric Metric (Utf8Builder ()) a Source #

Special setter to update the value of a Metric.

metric ("foo"" :: Text) Counter (1 :: Int) & value .~ (5 :: Double)

data Priority Source #

Constructors

Low 
Normal 
Instances
HasPriority Event (Maybe Priority) Source # 
Instance details

Defined in Network.StatsD.Datadog

class HasName s a | s -> a where Source #

Methods

name :: Lens' s a Source #

class HasSampleRate s a | s -> a where Source #

Methods

sampleRate :: Lens' s a Source #

Instances
HasSampleRate Metric Double Source # 
Instance details

Defined in Network.StatsD.Datadog

class HasType' s a | s -> a where Source #

Methods

type' :: Lens' s a Source #

Instances
HasType' Metric MetricType Source # 
Instance details

Defined in Network.StatsD.Datadog

class HasTags s a | s -> a where Source #

Methods

tags :: Lens' s a Source #

Instances
HasTags Metric [Tag] Source # 
Instance details

Defined in Network.StatsD.Datadog

Methods

tags :: Lens' Metric [Tag] Source #

HasTags Event [Tag] Source # 
Instance details

Defined in Network.StatsD.Datadog

Methods

tags :: Lens' Event [Tag] Source #

HasTags ServiceCheck [Tag] Source # 
Instance details

Defined in Network.StatsD.Datadog

class HasTitle s a | s -> a where Source #

Methods

title :: Lens' s a Source #

Instances
HasTitle Event Text Source # 
Instance details

Defined in Network.StatsD.Datadog

class HasText s a | s -> a where Source #

Methods

text :: Lens' s a Source #

Instances
HasText Event Text Source # 
Instance details

Defined in Network.StatsD.Datadog

class HasHostname s a | s -> a where Source #

Methods

hostname :: Lens' s a Source #

class HasAggregationKey s a | s -> a where Source #

class HasPriority s a | s -> a where Source #

Methods

priority :: Lens' s a Source #

Instances
HasPriority Event (Maybe Priority) Source # 
Instance details

Defined in Network.StatsD.Datadog

class HasSourceTypeName s a | s -> a where Source #

class HasAlertType s a | s -> a where Source #

Methods

alertType :: Lens' s a Source #

class HasHost s a | s -> a where Source #

Methods

host :: Lens' s a Source #

class HasPort s a | s -> a where Source #

Methods

port :: Lens' s a Source #

class HasBufferSize s a | s -> a where Source #

Methods

bufferSize :: Lens' s a Source #

class HasMaxDelay s a | s -> a where Source #

Methods

maxDelay :: Lens' s a Source #

class HasStatus s a | s -> a where Source #

Methods

status :: Lens' s a Source #

class HasMessage s a | s -> a where Source #

Methods

message :: Lens' s a Source #

Dummy client

data StatsClient Source #

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

Constructors

Dummy

Just drops all stats.