arbor-datadog-0.0.0.1: Datadog client for Haskell.

Safe HaskellNone
LanguageHaskell2010

Arbor.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

  • host :: HostName

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

  • port :: Int

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

Instances
Generic DogStatsSettings Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Associated Types

type Rep DogStatsSettings :: * -> * #

type Rep DogStatsSettings Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

type Rep DogStatsSettings = D1 (MetaData "DogStatsSettings" "Arbor.Network.StatsD.Type" "arbor-datadog-0.0.0.1-GEqpenS6RJZ6iFSpptPIZ6" False) (C1 (MetaCons "DogStatsSettings" PrefixI True) (S1 (MetaSel (Just "host") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HostName) :*: S1 (MetaSel (Just "port") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

send :: (MonadIO m, ToStatsD v, HasType MetricName v, HasType [Tag] v) => StatsClient -> v -> m () Source #

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
Generic Metric Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Associated Types

type Rep Metric :: * -> * #

Methods

from :: Metric -> Rep Metric x #

to :: Rep Metric x -> Metric #

ToStatsD Metric Source # 
Instance details

Defined in Arbor.Network.StatsD.Datadog

Methods

toStatsD :: Metric -> Utf8Builder ()

type Rep Metric Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

data MetricName Source #

Instances
Eq MetricName Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Show MetricName Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Generic MetricName Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Associated Types

type Rep MetricName :: * -> * #

type Rep MetricName Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

type Rep MetricName = D1 (MetaData "MetricName" "Arbor.Network.StatsD.Type" "arbor-datadog-0.0.0.1-GEqpenS6RJZ6iFSpptPIZ6" True) (C1 (MetaCons "MetricName" PrefixI True) (S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data MetricType Source #

Instances
Eq MetricType Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Show MetricType Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Generic MetricType Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Associated Types

type Rep MetricType :: * -> * #

type Rep MetricType Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

type Rep MetricType = D1 (MetaData "MetricType" "Arbor.Network.StatsD.Type" "arbor-datadog-0.0.0.1-GEqpenS6RJZ6iFSpptPIZ6" False) ((C1 (MetaCons "Gauge" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Counter" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Timer" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Histogram" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Set" PrefixI False) (U1 :: * -> *))))

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

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

data Event Source #

data ServiceCheck Source #

data ServiceCheckStatus Source #

Instances
Enum ServiceCheckStatus Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Eq ServiceCheckStatus Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Ord ServiceCheckStatus Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Read ServiceCheckStatus Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Show ServiceCheckStatus Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Generic ServiceCheckStatus Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Associated Types

type Rep ServiceCheckStatus :: * -> * #

type Rep ServiceCheckStatus Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

type Rep ServiceCheckStatus = D1 (MetaData "ServiceCheckStatus" "Arbor.Network.StatsD.Type" "arbor-datadog-0.0.0.1-GEqpenS6RJZ6iFSpptPIZ6" False) ((C1 (MetaCons "ServiceOk" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ServiceWarning" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "ServiceCritical" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ServiceUnknown" PrefixI False) (U1 :: * -> *)))

class ToStatsD a Source #

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

Minimal complete definition

toStatsD

Instances
ToStatsD ServiceCheck Source # 
Instance details

Defined in Arbor.Network.StatsD.Datadog

ToStatsD Event Source # 
Instance details

Defined in Arbor.Network.StatsD.Datadog

Methods

toStatsD :: Event -> Utf8Builder ()

ToStatsD Metric Source # 
Instance details

Defined in Arbor.Network.StatsD.Datadog

Methods

toStatsD :: Metric -> Utf8Builder ()

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

Defined in Arbor.Network.StatsD.Type

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

type Rep Tag Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

type Rep Tag = D1 (MetaData "Tag" "Arbor.Network.StatsD.Type" "arbor-datadog-0.0.0.1-GEqpenS6RJZ6iFSpptPIZ6" True) (C1 (MetaCons "Tag" PrefixI True) (S1 (MetaSel (Just "builder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Utf8Builder ()))))

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 ("_").

tagged :: HasType [Tag] v => (a -> v) -> (a -> [Tag]) -> a -> v 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

send :: (MonadBase IO m, ToStatsD v) => Z.StatsClient -> v -> m () send Dummy _ = return () send (StatsClient _ r) v = liftBase $ reaperAdd r (toStatsD v >> appendChar7 '\n') {--}

sampled :: HasType SampleRate v => (a -> v) -> SampleRate -> a -> v Source #

sampled' :: HasType SampleRate v => (a -> v) -> (a -> SampleRate) -> a -> v Source #

addCounter :: MetricName -> (a -> Int) -> a -> Metric Source #

gauge :: ToMetricValue v => MetricName -> (a -> v) -> a -> Metric Source #

timer :: ToMetricValue v => MetricName -> (a -> v) -> a -> Metric Source #

histogram :: ToMetricValue v => MetricName -> (a -> v) -> a -> Metric Source #

class ToMetricValue a where Source #

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

Minimal complete definition

encodeValue

Methods

encodeValue :: a -> Utf8Builder () Source #

Instances
ToMetricValue Double Source # 
Instance details

Defined in Arbor.Network.StatsD.Datadog

ToMetricValue Int Source # 
Instance details

Defined in Arbor.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 SampleRate Source #

Instances
Eq SampleRate Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Ord SampleRate Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Show SampleRate Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Generic SampleRate Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Associated Types

type Rep SampleRate :: * -> * #

type Rep SampleRate Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

type Rep SampleRate = D1 (MetaData "SampleRate" "Arbor.Network.StatsD.Type" "arbor-datadog-0.0.0.1-GEqpenS6RJZ6iFSpptPIZ6" True) (C1 (MetaCons "SampleRate" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))

data Priority Source #

Constructors

Low 
Normal 
Instances
Generic Priority Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Associated Types

type Rep Priority :: * -> * #

Methods

from :: Priority -> Rep Priority x #

to :: Rep Priority x -> Priority #

type Rep Priority Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

type Rep Priority = D1 (MetaData "Priority" "Arbor.Network.StatsD.Type" "arbor-datadog-0.0.0.1-GEqpenS6RJZ6iFSpptPIZ6" False) (C1 (MetaCons "Low" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Normal" PrefixI False) (U1 :: * -> *))

data AlertType Source #

Constructors

Error 
Warning 
Info 
Success 
Instances
Generic AlertType Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Associated Types

type Rep AlertType :: * -> * #

type Rep AlertType Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

type Rep AlertType = D1 (MetaData "AlertType" "Arbor.Network.StatsD.Type" "arbor-datadog-0.0.0.1-GEqpenS6RJZ6iFSpptPIZ6" False) ((C1 (MetaCons "Error" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Warning" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Info" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Success" PrefixI False) (U1 :: * -> *)))

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.

Instances
Generic StatsClient Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

Associated Types

type Rep StatsClient :: * -> * #

type Rep StatsClient Source # 
Instance details

Defined in Arbor.Network.StatsD.Type

type Rep StatsClient = D1 (MetaData "StatsClient" "Arbor.Network.StatsD.Type" "arbor-datadog-0.0.0.1-GEqpenS6RJZ6iFSpptPIZ6" False) (C1 (MetaCons "StatsClient" PrefixI True) ((S1 (MetaSel (Just "handle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Handle) :*: S1 (MetaSel (Just "reaper") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Reaper (Maybe (Utf8Builder ())) (Utf8Builder ())))) :*: (S1 (MetaSel (Just "aspect") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MetricName) :*: S1 (MetaSel (Just "tags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Tag]))) :+: C1 (MetaCons "Dummy" PrefixI False) (U1 :: * -> *))