Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data DogStatsSettings = DogStatsSettings {}
- defaultSettings :: DogStatsSettings
- createStatsClient :: MonadIO m => DogStatsSettings -> MetricName -> [Tag] -> m StatsClient
- closeStatsClient :: MonadIO m => StatsClient -> m ()
- send :: (MonadIO m, ToStatsD v, HasType MetricName v, HasType [Tag] v) => StatsClient -> v -> m ()
- sendSampled :: (MonadIO m, ToStatsD v, HasType SampleRate v, HasType MetricName v, HasType [Tag] v) => StatsClient -> v -> m ()
- sendEvt :: MonadIO m => StatsClient -> Event -> m ()
- metric :: ToMetricValue a => MetricName -> MetricType -> a -> Metric
- data Metric
- data MetricName
- data MetricType
- event :: Text -> Text -> Event
- data Event
- serviceCheck :: Text -> ServiceCheckStatus -> ServiceCheck
- data ServiceCheck
- data ServiceCheckStatus
- class ToStatsD a
- data Tag
- envTag :: EnvVarName -> TagKey -> IO (Maybe Tag)
- tag :: Text -> Text -> Tag
- tagged :: HasType [Tag] v => (a -> v) -> (a -> [Tag]) -> a -> v
- sampled :: HasType SampleRate v => (a -> v) -> SampleRate -> a -> v
- sampled' :: HasType SampleRate v => (a -> v) -> (a -> SampleRate) -> a -> v
- incCounter :: MetricName -> Metric
- addCounter :: MetricName -> (a -> Int) -> a -> Metric
- gauge :: ToMetricValue v => MetricName -> (a -> v) -> a -> Metric
- timer :: ToMetricValue v => MetricName -> (a -> v) -> a -> Metric
- histogram :: ToMetricValue v => MetricName -> (a -> v) -> a -> Metric
- class ToMetricValue a where
- value :: ToMetricValue a => Setter Metric Metric (Utf8Builder ()) a
- data SampleRate
- data Priority
- data AlertType
- data StatsClient = Dummy
Client interface
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))) |
createStatsClient :: MonadIO m => DogStatsSettings -> MetricName -> [Tag] -> m StatsClient Source #
closeStatsClient :: MonadIO m => StatsClient -> m () Source #
send :: (MonadIO m, ToStatsD v, HasType MetricName v, HasType [Tag] v) => StatsClient -> v -> m () Source #
sendSampled :: (MonadIO m, ToStatsD v, HasType SampleRate 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.
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
]
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]))))) |
data 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 #
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 :: * -> *)))) |
event :: Text -> Text -> Event Source #
Smart Event
constructor. Use the lens functions to set the optional fields.
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
:: Text | name |
-> ServiceCheckStatus | |
-> ServiceCheck |
data ServiceCheck Source #
The fields accessible through corresponding lenses are:
Instances
data ServiceCheckStatus Source #
Instances
Convert an Event
, Metric
, or StatusCheck
to their wire format.
toStatsD
Instances
ToStatsD ServiceCheck Source # | |
Defined in Arbor.Network.StatsD.Datadog toStatsD :: ServiceCheck -> Utf8Builder () | |
ToStatsD Event Source # | |
Defined in Arbor.Network.StatsD.Datadog toStatsD :: Event -> Utf8Builder () | |
ToStatsD Metric Source # | |
Defined in Arbor.Network.StatsD.Datadog toStatsD :: Metric -> Utf8Builder () |
Optional fields
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 # | |
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 ())))) |
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 #
incCounter :: MetricName -> Metric 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.
encodeValue :: a -> Utf8Builder () Source #
Instances
ToMetricValue Double Source # | |
Defined in Arbor.Network.StatsD.Datadog encodeValue :: Double -> Utf8Builder () Source # | |
ToMetricValue Int Source # | |
Defined in Arbor.Network.StatsD.Datadog encodeValue :: Int -> Utf8Builder () Source # |
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
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 :: * -> *))) |
Dummy client
data StatsClient Source #
Note that Dummy is not the only constructor, just the only publicly available one.
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 :: * -> *)) |