datadog-0.2.0.0: Datadog client for Haskell. Supports both the HTTP API and StatsD.

Safe HaskellNone
LanguageHaskell2010

Network.Datadog.Monitor

Description

Monitoring all of your infrastructure in one place wouldn’t be complete without the ability to know when critical changes are occurring. Datadog gives you the ability to create monitors that will actively check metrics, integration availability, network endpoints and more. Once a monitor is created, you will be notified when its conditions are met.

A simple way to get started with monitors:

main = do
  env <- createEnvironment =<< loadKeysFromEnv
  -- Check if the average bytes received in the last five minutes is >100 on host0
  let query = "avg(last_5m):sum:system.net.bytes_rcvd{host:host0} > 100"
  let mspec = minimalMonitorSpec MetricAlert query
  monitor <- createMonitor env mspec
  print $ mId monitor

Synopsis

Documentation

data MonitorSpec Source #

A representation of a monitor's configuration, from which a monitor could be rebuilt.

Constructors

MonitorSpec 

Fields

data MonitorType Source #

Each monitor is of a specific type, which determines what sort of check the monitor performs.

Constructors

MetricAlert

Watches a (combination of) metric(s), alerting when it crosses some threshold.

ServiceCheck

Watches a service and alerts when the service enters a failing state.

EventAlert

Checks the event stream for events meeting certain criteria.

data MonitorOptions Source #

Advanced configuration parameters for a monitor.

getSilencedMonitorScopes :: MonitorOptions -> [(Text, Maybe UTCTime)] Source #

Provide a list of the silenced scopes for this monitor and the time at which the silencer will expire (may be indefinite). The monitor "*" refers to the monitor at large (un-scoped).

silenceMonitorScope :: Text -> Maybe UTCTime -> MonitorOptions -> MonitorOptions Source #

Silence a given scope until some time (or indefinitely), replacing the current silencer on the given scope if one already exists.

unsilenceMonitorScope :: Text -> MonitorOptions -> MonitorOptions Source #

Remove the silencer from a given scope, if the scope is currently silenced.

unsilenceAllMonitorScope :: MonitorOptions -> MonitorOptions Source #

Unsilence every scope in the monitor, including the global scope.

doesNotifyOnNoMonitorData :: MonitorOptions -> Maybe NominalDiffTime Source #

Determine how long without data a monitor will go before notifying to such, providing Nothing if the monitor will never notify on lack of data.

notifyOnNoMonitorData :: NominalDiffTime -> MonitorOptions -> MonitorOptions Source #

Have the monitor notify when it does not receive data for some given amount of time (rounded down to the nearest minute).

noNotifyOnNoMonitorData :: MonitorOptions -> MonitorOptions Source #

Prevent the monitor from notifying when it is missing data.

getMonitorTimeout :: MonitorOptions -> Maybe NominalDiffTime Source #

Determine after how long the monitor will stop alerting after it is triggered, providing Nothing if the monitor will never stop alerting.

setMonitorTimeout :: NominalDiffTime -> MonitorOptions -> MonitorOptions Source #

Have the monitor stop alerting some time after it is triggered (rounded up to the nearest hour).

clearMonitorTimeout :: MonitorOptions -> MonitorOptions Source #

Prevent the monitor from timing out after it is triggered.

doesRenotifyMonitor :: MonitorOptions -> Maybe (NominalDiffTime, Maybe Text) Source #

Determine after how long after being triggered the monitor will re-notify, and what message it will include in the re-notification (if any), providing Nothing if the monitor will never re-notify.

renotifyMonitor :: NominalDiffTime -> Maybe Text -> MonitorOptions -> MonitorOptions Source #

Have the monitor re-notify some amount of time after the most recent notification (rounded down to the nearest minute) and optionally what text it will include in the re-notification.

noRenotifyMonitor :: MonitorOptions -> MonitorOptions Source #

Prevent the monitor from re-notifying after it triggers an un-resolved notification.

doesNotifyOnAudit :: MonitorOptions -> Bool Source #

Determine if the monitor triggers a notification when it is modified.

notifyOnAudit :: MonitorOptions -> MonitorOptions Source #

Have the monitor trigger a notification when it is modified.

noNotifyOnAudit :: MonitorOptions -> MonitorOptions Source #

Prevent the monitor from triggering a notification when it is modified.

data Monitor Source #

A Datadog monitor. These monitors actively check multiple different types of data within Datadog against user-provided conditions, triggering notifications when condition(s) are met.

Constructors

Monitor 

Fields

type MonitorId = Int Source #

Datadog's internal reference to a specific monitor.

minimalMonitorSpec :: MonitorType -> Text -> MonitorSpec Source #

Creates the most basic specification required by a monitor, containing the type of monitor and the query string used to detect the monitor's state.

This uses defaultMonitorOptions to set the options (see that function for disclaimer(s)).

createMonitor :: Environment -> MonitorSpec -> IO Monitor Source #

Create a new monitor in Datadog matching a specification.

updateMonitor :: Environment -> MonitorId -> MonitorSpec -> IO Monitor Source #

Sync a monitor with Datadog.

This must be called on any active monitors to apply the changes with Datadog itself; merely modifying a monitor locally is not enough to store the changes.

Beware: If a monitor has changed on the Datadog remote endpoint between the time it was copied locally and when this function is called, those changes already made remotely will be overwritten by this change.

deleteMonitor :: Environment -> MonitorId -> IO () Source #

Delete a monitor from Datadog.

Note that once a monitor is deleted, it cannot be used locally anymore, however you can always create a new monitor using the deleted monitor's specification.

loadMonitor :: Environment -> MonitorId -> IO Monitor Source #

Load a monitor from Datadog by its ID.

loadMonitors Source #

Arguments

:: Environment 
-> [Tag]

Tags on which to filter the results

-> IO [Monitor] 

Load monitors from Datadog.

This function takes a filter list argument, which should contain any tags the user wishes to filter on. If the filter list is left empty, no filters will be applied. The list of tags is ANDed together; if you specify more than one filter tag, only metrics which match all filter tags will be provided.

muteAllMonitors :: Environment -> IO () Source #

Prevent all monitors from notifying indefinitely.

unmuteAllMonitors :: Environment -> IO () Source #

Allow all monitors to notify.

class HasId' s a | s -> a where Source #

Minimal complete definition

id'

Methods

id' :: Lens' s a Source #

class HasSpec s a | s -> a where Source #

Minimal complete definition

spec

Methods

spec :: Lens' s a Source #

class HasType' s a | s -> a where Source #

Minimal complete definition

type'

Methods

type' :: Lens' s a Source #

class HasQuery s a | s -> a where Source #

Minimal complete definition

query

Methods

query :: Lens' s a Source #

class HasOptions s a | s -> a where Source #

Minimal complete definition

options

Methods

options :: Lens' s a Source #

class HasName s a | s -> a where Source #

Minimal complete definition

name

Methods

name :: Lens' s a Source #

class HasNotifyNoData s a | s -> a where Source #

Minimal complete definition

notifyNoData

Methods

notifyNoData :: Lens' s a Source #

class HasTimeoutH s a | s -> a where Source #

Minimal complete definition

timeoutH

Methods

timeoutH :: Lens' s a Source #

class HasSilenced s a | s -> a where Source #

Minimal complete definition

silenced

Methods

silenced :: Lens' s a Source #