| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.StatsD.Datadog
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
- data DogStatsSettings = DogStatsSettings {}
 - defaultSettings :: DogStatsSettings
 - withDogStatsD :: MonadUnliftIO m => DogStatsSettings -> (StatsClient -> m a) -> m a
 - mkStatsClient :: MonadIO m => DogStatsSettings -> m StatsClient
 - finalizeStatsClient :: MonadIO m => StatsClient -> m ()
 - send :: (MonadIO m, ToStatsD v) => StatsClient -> v -> m ()
 - metric :: ToMetricValue a => MetricName -> MetricType -> a -> Metric
 - data Metric
 - newtype MetricName = MetricName {}
 - data MetricType
 - event :: Text -> Text -> Event
 - data Event
 - serviceCheck :: Text -> ServiceCheckStatus -> ServiceCheck
 - data ServiceCheck
 - data ServiceCheckStatus
 - class ToStatsD a
 - data Tag
 - tag :: Text -> Text -> Tag
 - class ToMetricValue a where
- encodeValue :: a -> Utf8Builder ()
 
 - value :: ToMetricValue a => Setter Metric Metric (Utf8Builder ()) a
 - data Priority
 - data AlertType
 - class HasName s a | s -> a where
 - class HasSampleRate s a | s -> a where
- sampleRate :: Lens' s a
 
 - class HasType' s a | s -> a where
 - class HasTags s a | s -> a where
 - class HasTitle s a | s -> a where
 - class HasText s a | s -> a where
 - class HasDateHappened s a | s -> a where
- dateHappened :: Lens' s a
 
 - class HasHostname s a | s -> a where
 - class HasAggregationKey s a | s -> a where
- aggregationKey :: Lens' s a
 
 - class HasPriority s a | s -> a where
 - class HasSourceTypeName s a | s -> a where
- sourceTypeName :: Lens' s a
 
 - class HasAlertType s a | s -> a where
 - class HasHost s a | s -> a where
 - class HasPort s a | s -> a where
 - class HasBufferSize s a | s -> a where
- bufferSize :: Lens' s a
 
 - class HasMaxDelay s a | s -> a where
 - class HasOnException s a | s -> a where
- onException :: Lens' s a
 
 - class HasStatus s a | s -> a where
 - class HasMessage s a | s -> a where
 - data StatsClient = Dummy
 
Client interface
data DogStatsSettings Source #
Constructors
| DogStatsSettings | |
Fields 
  | |
Instances
| HasPort DogStatsSettings Int Source # | |
Defined in Network.StatsD.Datadog  | |
| HasMaxDelay DogStatsSettings Int Source # | |
Defined in Network.StatsD.Datadog  | |
| HasHost DogStatsSettings HostName Source # | |
Defined in Network.StatsD.Datadog  | |
| HasBufferSize DogStatsSettings Int Source # | |
Defined in Network.StatsD.Datadog Methods  | |
| HasOnException DogStatsSettings (SomeException -> Seq ByteString -> IO (Seq ByteString -> Seq ByteString)) Source # | |
Defined in Network.StatsD.Datadog Methods onException :: Lens' DogStatsSettings (SomeException -> Seq ByteString -> IO (Seq ByteString -> Seq ByteString)) Source #  | |
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.
The fields accessible through corresponding lenses are:
name::MetricNamesampleRate::Doubletype'::MetricTypevalue::ToMetricValuea => atags::[Tag]
Instances
| ToStatsD Metric Source # | |
Defined in Network.StatsD.Datadog Methods toStatsD :: Metric -> Utf8Builder ()  | |
| HasType' Metric MetricType Source # | |
Defined in Network.StatsD.Datadog  | |
| HasSampleRate Metric Double Source # | |
Defined in Network.StatsD.Datadog  | |
| HasName Metric MetricName Source # | |
Defined in Network.StatsD.Datadog  | |
| HasTags Metric [Tag] Source # | |
newtype MetricName Source #
Constructors
| MetricName | |
Fields  | |
Instances
| HasName Metric MetricName Source # | |
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 # | |
Defined in Network.StatsD.Datadog  | |
event :: Text -> Text -> Event Source #
Smart Event constructor. Use the lens functions to set the optional fields.
The fields accessible through corresponding lenses are:
Instances
| ToStatsD Event Source # | |
Defined in Network.StatsD.Datadog Methods toStatsD :: Event -> Utf8Builder ()  | |
| HasTitle Event Text Source # | |
| HasText Event Text Source # | |
| HasTags Event [Tag] Source # | |
| HasSourceTypeName Event (Maybe Text) Source # | |
Defined in Network.StatsD.Datadog  | |
| HasPriority Event (Maybe Priority) Source # | |
| HasHostname Event (Maybe Text) Source # | |
| HasDateHappened Event (Maybe UTCTime) Source # | |
Defined in Network.StatsD.Datadog  | |
| HasAlertType Event (Maybe AlertType) Source # | |
| HasAggregationKey Event (Maybe Text) Source # | |
Defined in Network.StatsD.Datadog  | |
Arguments
| :: Text | name  | 
| -> ServiceCheckStatus | |
| -> ServiceCheck | 
data ServiceCheck Source #
The fields accessible through corresponding lenses are:
Instances
| ToStatsD ServiceCheck Source # | |
Defined in Network.StatsD.Datadog Methods toStatsD :: ServiceCheck -> Utf8Builder ()  | |
| HasName ServiceCheck Text Source # | |
Defined in Network.StatsD.Datadog  | |
| HasStatus ServiceCheck ServiceCheckStatus Source # | |
Defined in Network.StatsD.Datadog Methods  | |
| HasTags ServiceCheck [Tag] Source # | |
Defined in Network.StatsD.Datadog  | |
| HasHostname ServiceCheck (Maybe Text) Source # | |
Defined in Network.StatsD.Datadog  | |
| HasDateHappened ServiceCheck (Maybe UTCTime) Source # | |
Defined in Network.StatsD.Datadog Methods  | |
| HasMessage ServiceCheck (Maybe Text) Source # | |
Defined in Network.StatsD.Datadog  | |
data ServiceCheckStatus Source #
Constructors
| ServiceOk | |
| ServiceWarning | |
| ServiceCritical | |
| ServiceUnknown | 
Instances
Minimal complete definition
toStatsD
Instances
| ToStatsD Metric Source # | |
Defined in Network.StatsD.Datadog Methods toStatsD :: Metric -> Utf8Builder ()  | |
| ToStatsD Event Source # | |
Defined in Network.StatsD.Datadog Methods toStatsD :: Event -> Utf8Builder ()  | |
| ToStatsD ServiceCheck Source # | |
Defined in Network.StatsD.Datadog Methods toStatsD :: ServiceCheck -> 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.
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 # | |
Defined in Network.StatsD.Datadog Methods encodeValue :: Double -> Utf8Builder () Source #  | |
| ToMetricValue Int Source # | |
Defined in Network.StatsD.Datadog Methods 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)class HasName s a | s -> a where Source #
Instances
| HasName Metric MetricName Source # | |
Defined in Network.StatsD.Datadog  | |
| HasName ServiceCheck Text Source # | |
Defined in Network.StatsD.Datadog  | |
class HasSampleRate s a | s -> a where Source #
Methods
sampleRate :: Lens' s a Source #
Instances
| HasSampleRate Metric Double Source # | |
Defined in Network.StatsD.Datadog  | |
class HasType' s a | s -> a where Source #
Instances
| HasType' Metric MetricType Source # | |
Defined in Network.StatsD.Datadog  | |
class HasDateHappened s a | s -> a where Source #
Methods
dateHappened :: Lens' s a Source #
Instances
| HasDateHappened Event (Maybe UTCTime) Source # | |
Defined in Network.StatsD.Datadog  | |
| HasDateHappened ServiceCheck (Maybe UTCTime) Source # | |
Defined in Network.StatsD.Datadog Methods  | |
class HasHostname s a | s -> a where Source #
Instances
| HasHostname Event (Maybe Text) Source # | |
| HasHostname ServiceCheck (Maybe Text) Source # | |
Defined in Network.StatsD.Datadog  | |
class HasAggregationKey s a | s -> a where Source #
Methods
aggregationKey :: Lens' s a Source #
Instances
| HasAggregationKey Event (Maybe Text) Source # | |
Defined in Network.StatsD.Datadog  | |
class HasPriority s a | s -> a where Source #
class HasSourceTypeName s a | s -> a where Source #
Methods
sourceTypeName :: Lens' s a Source #
Instances
| HasSourceTypeName Event (Maybe Text) Source # | |
Defined in Network.StatsD.Datadog  | |
class HasAlertType s a | s -> a where Source #
class HasHost s a | s -> a where Source #
Instances
| HasHost DogStatsSettings HostName Source # | |
Defined in Network.StatsD.Datadog  | |
class HasPort s a | s -> a where Source #
Instances
| HasPort DogStatsSettings Int Source # | |
Defined in Network.StatsD.Datadog  | |
class HasBufferSize s a | s -> a where Source #
Methods
bufferSize :: Lens' s a Source #
Instances
| HasBufferSize DogStatsSettings Int Source # | |
Defined in Network.StatsD.Datadog Methods  | |
class HasMaxDelay s a | s -> a where Source #
Instances
| HasMaxDelay DogStatsSettings Int Source # | |
Defined in Network.StatsD.Datadog  | |
class HasOnException s a | s -> a where Source #
Methods
onException :: Lens' s a Source #
Instances
| HasOnException DogStatsSettings (SomeException -> Seq ByteString -> IO (Seq ByteString -> Seq ByteString)) Source # | |
Defined in Network.StatsD.Datadog Methods onException :: Lens' DogStatsSettings (SomeException -> Seq ByteString -> IO (Seq ByteString -> Seq ByteString)) Source #  | |
class HasStatus s a | s -> a where Source #
Instances
| HasStatus ServiceCheck ServiceCheckStatus Source # | |
Defined in Network.StatsD.Datadog Methods  | |
class HasMessage s a | s -> a where Source #
Instances
| HasMessage ServiceCheck (Maybe Text) Source # | |
Defined in Network.StatsD.Datadog  | |
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.  |