arbor-datadog-0.0.0.1: Datadog client for Haskell.

Safe HaskellNone
LanguageHaskell2010

Arbor.Network.StatsD.Type

Synopsis

Documentation

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

Constructors

Tag 

Fields

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 ()))))

newtype SampleRate Source #

Constructors

SampleRate Double 
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)))

newtype MetricName Source #

Constructors

MetricName 

Fields

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 #

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
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 :: * -> *))))

data Metric Source #

Metric

The fields accessible through corresponding lenses are:

Constructors

Metric 

Fields

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 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 :: * -> *)))

data Event 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 :: * -> *)))

data ServiceCheck Source #

Constructors

ServiceCheck 

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)))

data StatsClient Source #

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

Constructors

StatsClient 
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 :: * -> *))