Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Tag = Tag {
- builder :: Utf8Builder ()
- newtype SampleRate = SampleRate Double
- newtype MetricName = MetricName {}
- data MetricType
- data Metric = Metric {
- name :: !MetricName
- sampleRate :: !SampleRate
- type_ :: !MetricType
- value :: !(Utf8Builder ())
- tags :: ![Tag]
- data Priority
- data AlertType
- data Event = Event {}
- data ServiceCheckStatus
- data ServiceCheck = ServiceCheck {}
- data DogStatsSettings = DogStatsSettings {}
- data StatsClient
- = StatsClient {
- handle :: !Handle
- reaper :: Reaper (Maybe (Utf8Builder ())) (Utf8Builder ())
- aspect :: MetricName
- tags :: [Tag]
- | Dummy
- = StatsClient {
- type EnvVarName = String
- type TagKey = Text
Documentation
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.
Tag | |
|
Instances
Generic Tag Source # | |
type Rep Tag Source # | |
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 #
Instances
newtype MetricName Source #
Instances
Eq MetricName Source # | |
Defined in Arbor.Network.StatsD.Type (==) :: MetricName -> MetricName -> Bool # (/=) :: MetricName -> MetricName -> Bool # | |
Show MetricName Source # | |
Defined in Arbor.Network.StatsD.Type showsPrec :: Int -> MetricName -> ShowS # show :: MetricName -> String # showList :: [MetricName] -> ShowS # | |
Generic MetricName Source # | |
Defined in Arbor.Network.StatsD.Type type Rep MetricName :: * -> * # from :: MetricName -> Rep MetricName x # to :: Rep MetricName x -> MetricName # | |
type Rep MetricName Source # | |
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 #
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 # | |
Defined in Arbor.Network.StatsD.Type (==) :: MetricType -> MetricType -> Bool # (/=) :: MetricType -> MetricType -> Bool # | |
Show MetricType Source # | |
Defined in Arbor.Network.StatsD.Type showsPrec :: Int -> MetricType -> ShowS # show :: MetricType -> String # showList :: [MetricType] -> ShowS # | |
Generic MetricType Source # | |
Defined in Arbor.Network.StatsD.Type type Rep MetricType :: * -> * # from :: MetricType -> Rep MetricType x # to :: Rep MetricType x -> MetricType # | |
type Rep MetricType Source # | |
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 :: * -> *)))) |
The fields accessible through corresponding lenses are:
$sel:name:Metric
::
MetricName
$sel:sampleRate:Metric
::
Double
type'
::
MetricType
$sel:value:Metric
::
ToMetricValue
a => a
$sel:tags:ServiceCheck
::
[
Tag
]
Metric | |
|
Instances
Generic Metric Source # | |
ToStatsD Metric Source # | |
Defined in Arbor.Network.StatsD.Datadog toStatsD :: Metric -> Utf8Builder () | |
type Rep Metric Source # | |
Defined in Arbor.Network.StatsD.Type type Rep Metric = D1 (MetaData "Metric" "Arbor.Network.StatsD.Type" "arbor-datadog-0.0.0.1-GEqpenS6RJZ6iFSpptPIZ6" False) (C1 (MetaCons "Metric" PrefixI True) ((S1 (MetaSel (Just "name") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MetricName) :*: S1 (MetaSel (Just "sampleRate") SourceUnpack SourceStrict DecidedStrict) (Rec0 SampleRate)) :*: (S1 (MetaSel (Just "type_") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MetricType) :*: (S1 (MetaSel (Just "value") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Utf8Builder ())) :*: S1 (MetaSel (Just "tags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Tag]))))) |
Instances
Generic AlertType Source # | |
type Rep AlertType Source # | |
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 :: * -> *))) |
The fields accessible through corresponding lenses are:
$sel:title:Event
::
Text
$sel:text:MetricName
::
Text
$sel:dateHappened:Event
::
Maybe
UTCTime
$sel:hostname:Event
::
Maybe
Text
$sel:aggregationKey:Event
::
Maybe
Text
$sel:priority:Event
::
Maybe
Priority
$sel:sourceTypeName:Event
::
Maybe
Text
$sel:alertType:Event
::
Maybe
AlertType
$sel:tags:ServiceCheck
::
[
Tag
]
Instances
data ServiceCheckStatus Source #
Instances
data ServiceCheck Source #
The fields accessible through corresponding lenses are:
Instances
data DogStatsSettings Source #
Instances
Generic DogStatsSettings Source # | |
Defined in Arbor.Network.StatsD.Type type Rep DogStatsSettings :: * -> * # from :: DogStatsSettings -> Rep DogStatsSettings x # to :: Rep DogStatsSettings x -> DogStatsSettings # | |
type Rep DogStatsSettings Source # | |
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.
StatsClient | |
| |
Dummy | Just drops all stats. |
Instances
Generic StatsClient Source # | |
Defined in Arbor.Network.StatsD.Type type Rep StatsClient :: * -> * # from :: StatsClient -> Rep StatsClient x # to :: Rep StatsClient x -> StatsClient # | |
type Rep StatsClient Source # | |
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 :: * -> *)) |
type EnvVarName = String Source #