| Safe Haskell | None |
|---|
AWS.CloudWatch
Contents
- type CloudWatch m a = AWS AWSContext m a
- runCloudWatch :: MonadIO m => Credential -> CloudWatch m a -> m a
- runCloudWatchwithManager :: Monad m => Manager -> Credential -> CloudWatch m a -> m a
- setRegion :: (MonadBaseControl IO m, MonadResource m) => Text -> CloudWatch m ()
- apiVersion :: ByteString
- listMetrics :: (MonadBaseControl IO m, MonadResource m) => [DimensionFilter] -> Maybe Text -> Maybe Text -> Maybe Text -> CloudWatch m ([Metric], Maybe Text)
- getMetricStatistics :: (MonadBaseControl IO m, MonadResource m) => [DimensionFilter] -> UTCTime -> UTCTime -> Text -> Text -> Int -> [Statistic] -> Maybe Text -> CloudWatch m ([Datapoint], Text)
- putMetricData :: (MonadBaseControl IO m, MonadResource m) => [MetricDatum] -> Text -> CloudWatch m ()
- describeAlarms :: (MonadBaseControl IO m, MonadResource m) => Maybe Text -> AlarmNameSpec -> Maybe Int -> Maybe Text -> Maybe StateValue -> CloudWatch m ([MetricAlarm], Maybe Text)
- describeAlarmsForMetric :: (MonadBaseControl IO m, MonadResource m) => [Dimension] -> Text -> Text -> Int -> Statistic -> Maybe Text -> CloudWatch m [MetricAlarm]
- putMetricAlarm :: (MonadBaseControl IO m, MonadResource m) => PutMetricAlarmRequest -> CloudWatch m ()
- deleteAlarms :: (MonadBaseControl IO m, MonadResource m) => [Text] -> CloudWatch m ()
- describeAlarmHistory :: (MonadBaseControl IO m, MonadResource m) => Maybe Text -> Maybe UTCTime -> Maybe HistoryType -> Maybe Int -> Maybe Text -> Maybe UTCTime -> CloudWatch m ([AlarmHistory], Maybe Text)
- enableAlarmActions :: (MonadBaseControl IO m, MonadResource m) => [Text] -> CloudWatch m ()
- disableAlarmActions :: (MonadBaseControl IO m, MonadResource m) => [Text] -> CloudWatch m ()
- setAlarmState :: (MonadBaseControl IO m, MonadResource m) => Text -> Text -> Text -> StateValue -> CloudWatch m ()
CloudWatch Environment
type CloudWatch m a = AWS AWSContext m aSource
runCloudWatch :: MonadIO m => Credential -> CloudWatch m a -> m aSource
runCloudWatchwithManager :: Monad m => Manager -> Credential -> CloudWatch m a -> m aSource
setRegion :: (MonadBaseControl IO m, MonadResource m) => Text -> CloudWatch m ()Source
apiVersion :: ByteStringSource
Ver.2010-08-01
Metric
Arguments
| :: (MonadBaseControl IO m, MonadResource m) | |
| => [DimensionFilter] | Dimensions |
| -> Maybe Text | MetricName |
| -> Maybe Text | Namespace |
| -> Maybe Text | NextToken |
| -> CloudWatch m ([Metric], Maybe Text) |
Arguments
| :: (MonadBaseControl IO m, MonadResource m) | |
| => [DimensionFilter] | |
| -> UTCTime | StartTime |
| -> UTCTime | EndTime |
| -> Text | MetricName |
| -> Text | Namespace |
| -> Int | Period |
| -> [Statistic] | Statistics |
| -> Maybe Text | Unit |
| -> CloudWatch m ([Datapoint], Text) | Datapoints and Label |
Arguments
| :: (MonadBaseControl IO m, MonadResource m) | |
| => [MetricDatum] | A list of data describing the metric. |
| -> Text | The namespace for the metric data. |
| -> CloudWatch m () |
Arguments
| :: (MonadBaseControl IO m, MonadResource m) | |
| => Maybe Text | The action name prefix. |
| -> AlarmNameSpec | The alarm name prefix or a list of alarm names to retrieve information for. |
| -> Maybe Int | The maximum number of alarm descriptions to retrieve. |
| -> Maybe Text | The token returned by a previous call to indicate that there is more data available. |
| -> Maybe StateValue | The state value to be used in matching alarms. |
| -> CloudWatch m ([MetricAlarm], Maybe Text) | A list of information for the specified alarms and NextToken. |
Arguments
| :: (MonadBaseControl IO m, MonadResource m) | |
| => [Dimension] | The list of dimensions associated with the metric. |
| -> Text | The name of the metric. |
| -> Text | The namespace of the metric. |
| -> Int | The period in seconds over which the statistic is applied. |
| -> Statistic | The statistic for the metric. |
| -> Maybe Text | The unit for the metric. |
| -> CloudWatch m [MetricAlarm] |
putMetricAlarm :: (MonadBaseControl IO m, MonadResource m) => PutMetricAlarmRequest -> CloudWatch m ()Source
Arguments
| :: (MonadBaseControl IO m, MonadResource m) | |
| => [Text] | A list of alarms to be deleted. |
| -> CloudWatch m () |
Arguments
| :: (MonadBaseControl IO m, MonadResource m) | |
| => Maybe Text | The name of the alarm. |
| -> Maybe UTCTime | The ending date to retrieve alarm history. |
| -> Maybe HistoryType | The type of alarm histories to retrieve. |
| -> Maybe Int | The maximum number of alarm history records to retrieve. |
| -> Maybe Text | The token returned by a previous call to indicate that there is more data available. |
| -> Maybe UTCTime | The starting date to retrieve alarm history. |
| -> CloudWatch m ([AlarmHistory], Maybe Text) |
Arguments
| :: (MonadBaseControl IO m, MonadResource m) | |
| => [Text] | The names of the alarms to enable actions for. |
| -> CloudWatch m () |
Arguments
| :: (MonadBaseControl IO m, MonadResource m) | |
| => [Text] | The names of the alarms to enable actions for. |
| -> CloudWatch m () |
Arguments
| :: (MonadBaseControl IO m, MonadResource m) | |
| => Text | The name for the alarm. |
| -> Text | The reason that this alarm is set to this specific state (in human-readable text format) |
| -> Text | The reason that this alarm is set to this specific state (in machine-readable JSON format) |
| -> StateValue | The value of the state. |
| -> CloudWatch m () |