amazonka-cloudwatch-1.6.1: Amazon CloudWatch SDK.

Copyright(c) 2013-2018 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay+amazonka@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS.CloudWatch

Contents

Description

Amazon CloudWatch monitors your Amazon Web Services (AWS) resources and the applications you run on AWS in real time. You can use CloudWatch to collect and track metrics, which are the variables you want to measure for your resources and applications.

CloudWatch alarms send notifications or automatically change the resources you are monitoring based on rules that you define. For example, you can monitor the CPU usage and disk reads and writes of your Amazon EC2 instances. Then, use this data to determine whether you should launch additional instances to handle increased load. You can also use this data to stop under-used instances to save money.

In addition to monitoring the built-in metrics that come with AWS, you can monitor your own custom metrics. With CloudWatch, you gain system-wide visibility into resource utilization, application performance, and operational health.

Synopsis

Service Configuration

cloudWatch :: Service Source #

API version 2010-08-01 of the Amazon CloudWatch SDK configuration.

Errors

Error matchers are designed for use with the functions provided by Control.Exception.Lens. This allows catching (and rethrowing) service specific errors returned by CloudWatch.

LimitExceededFault

_LimitExceededFault :: AsError a => Getting (First ServiceError) a ServiceError Source #

The quota for alarms for this customer has already been reached.

DashboardNotFoundError

_DashboardNotFoundError :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified dashboard does not exist.

InvalidNextToken

_InvalidNextToken :: AsError a => Getting (First ServiceError) a ServiceError Source #

The next token specified is invalid.

InternalServiceFault

_InternalServiceFault :: AsError a => Getting (First ServiceError) a ServiceError Source #

Request processing has failed due to some unknown error, exception, or failure.

DashboardInvalidInputError

_DashboardInvalidInputError :: AsError a => Getting (First ServiceError) a ServiceError Source #

Some part of the dashboard data is invalid.

InvalidParameterValueException

_InvalidParameterValueException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The value of an input parameter is bad or out-of-range.

InvalidFormatFault

_InvalidFormatFault :: AsError a => Getting (First ServiceError) a ServiceError Source #

Data was not syntactically valid JSON.

MissingRequiredParameterException

_MissingRequiredParameterException :: AsError a => Getting (First ServiceError) a ServiceError Source #

An input parameter that is required is missing.

InvalidParameterCombinationException

_InvalidParameterCombinationException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Parameters were used together that cannot be used together.

ResourceNotFound

_ResourceNotFound :: AsError a => Getting (First ServiceError) a ServiceError Source #

The named resource does not exist.

Waiters

Waiters poll by repeatedly sending a request until some remote success condition configured by the Wait specification is fulfilled. The Wait specification determines how many attempts should be made, in addition to delay and retry strategies.

AlarmExists

alarmExists :: Wait DescribeAlarms Source #

Polls DescribeAlarms every 5 seconds until a successful state is reached. An error is returned after 40 failed checks.

Operations

Some AWS operations return results that are incomplete and require subsequent requests in order to obtain the entire result set. The process of sending subsequent requests to continue where a previous request left off is called pagination. For example, the ListObjects operation of Amazon S3 returns up to 1000 objects at a time, and you must send subsequent requests with the appropriate Marker in order to retrieve the next page of results.

Operations that have an AWSPager instance can transparently perform subsequent requests, correctly setting Markers and other request facets to iterate through the entire result set of a truncated API operation. Operations which support this have an additional note in the documentation.

Many operations have the ability to filter results on the server side. See the individual operation parameters for details.

EnableAlarmActions

GetDashboard

GetMetricData

PutMetricData

ListDashboards (Paginated)

DescribeAlarms (Paginated)

ListMetrics (Paginated)

DeleteDashboards

DeleteAlarms

DescribeAlarmHistory (Paginated)

GetMetricStatistics

DescribeAlarmsForMetric

DisableAlarmActions

PutDashboard

PutMetricAlarm

SetAlarmState

Types

ComparisonOperator

data ComparisonOperator Source #

Instances
Bounded ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Enum ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Eq ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Data ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ComparisonOperator -> c ComparisonOperator #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ComparisonOperator #

toConstr :: ComparisonOperator -> Constr #

dataTypeOf :: ComparisonOperator -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ComparisonOperator) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ComparisonOperator) #

gmapT :: (forall b. Data b => b -> b) -> ComparisonOperator -> ComparisonOperator #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ComparisonOperator -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ComparisonOperator -> r #

gmapQ :: (forall d. Data d => d -> u) -> ComparisonOperator -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ComparisonOperator -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ComparisonOperator -> m ComparisonOperator #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ComparisonOperator -> m ComparisonOperator #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ComparisonOperator -> m ComparisonOperator #

Ord ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Read ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Show ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Generic ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Associated Types

type Rep ComparisonOperator :: Type -> Type #

Hashable ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

FromXML ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToHeader ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToQuery ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToByteString ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

FromText ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToText ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

NFData ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

rnf :: ComparisonOperator -> () #

type Rep ComparisonOperator Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

type Rep ComparisonOperator = D1 (MetaData "ComparisonOperator" "Network.AWS.CloudWatch.Types.Sum" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) ((C1 (MetaCons "GreaterThanOrEqualToThreshold" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GreaterThanThreshold" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LessThanOrEqualToThreshold" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LessThanThreshold" PrefixI False) (U1 :: Type -> Type)))

HistoryItemType

data HistoryItemType Source #

Instances
Bounded HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Enum HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Eq HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Data HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HistoryItemType -> c HistoryItemType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HistoryItemType #

toConstr :: HistoryItemType -> Constr #

dataTypeOf :: HistoryItemType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HistoryItemType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HistoryItemType) #

gmapT :: (forall b. Data b => b -> b) -> HistoryItemType -> HistoryItemType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HistoryItemType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HistoryItemType -> r #

gmapQ :: (forall d. Data d => d -> u) -> HistoryItemType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HistoryItemType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HistoryItemType -> m HistoryItemType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HistoryItemType -> m HistoryItemType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HistoryItemType -> m HistoryItemType #

Ord HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Read HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Show HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Generic HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Associated Types

type Rep HistoryItemType :: Type -> Type #

Hashable HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

FromXML HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToHeader HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToQuery HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToByteString HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

FromText HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToText HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

NFData HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

rnf :: HistoryItemType -> () #

type Rep HistoryItemType Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

type Rep HistoryItemType = D1 (MetaData "HistoryItemType" "Network.AWS.CloudWatch.Types.Sum" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "Action" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ConfigurationUpdate" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StateUpdate" PrefixI False) (U1 :: Type -> Type)))

ScanBy

data ScanBy Source #

Instances
Bounded ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Enum ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Eq ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

(==) :: ScanBy -> ScanBy -> Bool #

(/=) :: ScanBy -> ScanBy -> Bool #

Data ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScanBy -> c ScanBy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScanBy #

toConstr :: ScanBy -> Constr #

dataTypeOf :: ScanBy -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ScanBy) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScanBy) #

gmapT :: (forall b. Data b => b -> b) -> ScanBy -> ScanBy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScanBy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScanBy -> r #

gmapQ :: (forall d. Data d => d -> u) -> ScanBy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScanBy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScanBy -> m ScanBy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScanBy -> m ScanBy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScanBy -> m ScanBy #

Ord ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Read ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Show ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Generic ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Associated Types

type Rep ScanBy :: Type -> Type #

Methods

from :: ScanBy -> Rep ScanBy x #

to :: Rep ScanBy x -> ScanBy #

Hashable ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

hashWithSalt :: Int -> ScanBy -> Int #

hash :: ScanBy -> Int #

ToHeader ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

toHeader :: HeaderName -> ScanBy -> [Header] #

ToQuery ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToByteString ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

toBS :: ScanBy -> ByteString #

FromText ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

parser :: Parser ScanBy #

ToText ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

toText :: ScanBy -> Text #

NFData ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

rnf :: ScanBy -> () #

type Rep ScanBy Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

type Rep ScanBy = D1 (MetaData "ScanBy" "Network.AWS.CloudWatch.Types.Sum" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "TimestampAscending" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TimestampDescending" PrefixI False) (U1 :: Type -> Type))

StandardUnit

data StandardUnit Source #

Instances
Bounded StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Enum StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Eq StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Data StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StandardUnit -> c StandardUnit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StandardUnit #

toConstr :: StandardUnit -> Constr #

dataTypeOf :: StandardUnit -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StandardUnit) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StandardUnit) #

gmapT :: (forall b. Data b => b -> b) -> StandardUnit -> StandardUnit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StandardUnit -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StandardUnit -> r #

gmapQ :: (forall d. Data d => d -> u) -> StandardUnit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StandardUnit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StandardUnit -> m StandardUnit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StandardUnit -> m StandardUnit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StandardUnit -> m StandardUnit #

Ord StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Read StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Show StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Generic StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Associated Types

type Rep StandardUnit :: Type -> Type #

Hashable StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

FromXML StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToHeader StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToQuery StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToByteString StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

FromText StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToText StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

toText :: StandardUnit -> Text #

NFData StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

rnf :: StandardUnit -> () #

type Rep StandardUnit Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

type Rep StandardUnit = D1 (MetaData "StandardUnit" "Network.AWS.CloudWatch.Types.Sum" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) ((((C1 (MetaCons "Bits" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "BitsSecond" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Bytes" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "BytesSecond" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Count" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CountSecond" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Gigabits" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GigabitsSecond" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Gigabytes" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "GigabytesSecond" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Kilobits" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "KilobitsSecond" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Kilobytes" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "KilobytesSecond" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Megabits" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MegabitsSecond" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Megabytes" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MegabytesSecond" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Microseconds" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Milliseconds" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "None" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Percent" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Seconds" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Terabits" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TerabitsSecond" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Terabytes" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TerabytesSecond" PrefixI False) (U1 :: Type -> Type))))))

StateValue

data StateValue Source #

Constructors

Alarm 
InsufficientData 
OK 
Instances
Bounded StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Enum StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Eq StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Data StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StateValue -> c StateValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StateValue #

toConstr :: StateValue -> Constr #

dataTypeOf :: StateValue -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StateValue) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StateValue) #

gmapT :: (forall b. Data b => b -> b) -> StateValue -> StateValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StateValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StateValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> StateValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StateValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StateValue -> m StateValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StateValue -> m StateValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StateValue -> m StateValue #

Ord StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Read StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Show StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Generic StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Associated Types

type Rep StateValue :: Type -> Type #

Hashable StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

FromXML StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToHeader StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToQuery StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToByteString StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

FromText StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToText StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

toText :: StateValue -> Text #

NFData StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

rnf :: StateValue -> () #

type Rep StateValue Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

type Rep StateValue = D1 (MetaData "StateValue" "Network.AWS.CloudWatch.Types.Sum" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "Alarm" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "InsufficientData" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OK" PrefixI False) (U1 :: Type -> Type)))

Statistic

data Statistic Source #

Instances
Bounded Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Enum Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Eq Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Data Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Statistic -> c Statistic #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Statistic #

toConstr :: Statistic -> Constr #

dataTypeOf :: Statistic -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Statistic) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Statistic) #

gmapT :: (forall b. Data b => b -> b) -> Statistic -> Statistic #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Statistic -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Statistic -> r #

gmapQ :: (forall d. Data d => d -> u) -> Statistic -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Statistic -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Statistic -> m Statistic #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Statistic -> m Statistic #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Statistic -> m Statistic #

Ord Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Read Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Show Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Generic Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Associated Types

type Rep Statistic :: Type -> Type #

Hashable Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

FromXML Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToHeader Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToQuery Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToByteString Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

toBS :: Statistic -> ByteString #

FromText Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToText Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

toText :: Statistic -> Text #

NFData Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

rnf :: Statistic -> () #

type Rep Statistic Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

type Rep Statistic = D1 (MetaData "Statistic" "Network.AWS.CloudWatch.Types.Sum" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) ((C1 (MetaCons "Average" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Maximum" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Minimum" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SampleCount" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Sum" PrefixI False) (U1 :: Type -> Type))))

StatusCode

data StatusCode Source #

Instances
Bounded StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Enum StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Eq StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Data StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StatusCode -> c StatusCode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StatusCode #

toConstr :: StatusCode -> Constr #

dataTypeOf :: StatusCode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StatusCode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StatusCode) #

gmapT :: (forall b. Data b => b -> b) -> StatusCode -> StatusCode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StatusCode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StatusCode -> r #

gmapQ :: (forall d. Data d => d -> u) -> StatusCode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StatusCode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StatusCode -> m StatusCode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StatusCode -> m StatusCode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StatusCode -> m StatusCode #

Ord StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Read StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Show StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Generic StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Associated Types

type Rep StatusCode :: Type -> Type #

Hashable StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

FromXML StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToHeader StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToQuery StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToByteString StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

FromText StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

ToText StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

toText :: StatusCode -> Text #

NFData StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

Methods

rnf :: StatusCode -> () #

type Rep StatusCode Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Sum

type Rep StatusCode = D1 (MetaData "StatusCode" "Network.AWS.CloudWatch.Types.Sum" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "Complete" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "InternalError" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PartialData" PrefixI False) (U1 :: Type -> Type)))

AlarmHistoryItem

data AlarmHistoryItem Source #

Represents the history of a specific alarm.

See: alarmHistoryItem smart constructor.

Instances
Eq AlarmHistoryItem Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data AlarmHistoryItem Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AlarmHistoryItem -> c AlarmHistoryItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AlarmHistoryItem #

toConstr :: AlarmHistoryItem -> Constr #

dataTypeOf :: AlarmHistoryItem -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AlarmHistoryItem) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AlarmHistoryItem) #

gmapT :: (forall b. Data b => b -> b) -> AlarmHistoryItem -> AlarmHistoryItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AlarmHistoryItem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AlarmHistoryItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> AlarmHistoryItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AlarmHistoryItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AlarmHistoryItem -> m AlarmHistoryItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AlarmHistoryItem -> m AlarmHistoryItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AlarmHistoryItem -> m AlarmHistoryItem #

Read AlarmHistoryItem Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show AlarmHistoryItem Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic AlarmHistoryItem Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep AlarmHistoryItem :: Type -> Type #

Hashable AlarmHistoryItem Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

FromXML AlarmHistoryItem Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData AlarmHistoryItem Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: AlarmHistoryItem -> () #

type Rep AlarmHistoryItem Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep AlarmHistoryItem = D1 (MetaData "AlarmHistoryItem" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "AlarmHistoryItem'" PrefixI True) ((S1 (MetaSel (Just "_ahiAlarmName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ahiHistoryItemType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HistoryItemType))) :*: (S1 (MetaSel (Just "_ahiHistoryData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_ahiHistorySummary") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ahiTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601))))))

alarmHistoryItem :: AlarmHistoryItem Source #

Creates a value of AlarmHistoryItem with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ahiAlarmName :: Lens' AlarmHistoryItem (Maybe Text) Source #

The descriptive name for the alarm.

ahiHistoryData :: Lens' AlarmHistoryItem (Maybe Text) Source #

Data about the alarm, in JSON format.

ahiHistorySummary :: Lens' AlarmHistoryItem (Maybe Text) Source #

A summary of the alarm history, in text format.

ahiTimestamp :: Lens' AlarmHistoryItem (Maybe UTCTime) Source #

The time stamp for the alarm history item.

DashboardEntry

data DashboardEntry Source #

Represents a specific dashboard.

See: dashboardEntry smart constructor.

Instances
Eq DashboardEntry Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data DashboardEntry Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DashboardEntry -> c DashboardEntry #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DashboardEntry #

toConstr :: DashboardEntry -> Constr #

dataTypeOf :: DashboardEntry -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DashboardEntry) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DashboardEntry) #

gmapT :: (forall b. Data b => b -> b) -> DashboardEntry -> DashboardEntry #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DashboardEntry -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DashboardEntry -> r #

gmapQ :: (forall d. Data d => d -> u) -> DashboardEntry -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DashboardEntry -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DashboardEntry -> m DashboardEntry #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DashboardEntry -> m DashboardEntry #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DashboardEntry -> m DashboardEntry #

Read DashboardEntry Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show DashboardEntry Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic DashboardEntry Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep DashboardEntry :: Type -> Type #

Hashable DashboardEntry Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

FromXML DashboardEntry Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData DashboardEntry Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: DashboardEntry -> () #

type Rep DashboardEntry Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep DashboardEntry = D1 (MetaData "DashboardEntry" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "DashboardEntry'" PrefixI True) ((S1 (MetaSel (Just "_deSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Integer)) :*: S1 (MetaSel (Just "_deDashboardName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_deLastModified") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601)) :*: S1 (MetaSel (Just "_deDashboardARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

dashboardEntry :: DashboardEntry Source #

Creates a value of DashboardEntry with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • deSize - The size of the dashboard, in bytes.
  • deDashboardName - The name of the dashboard.
  • deLastModified - The time stamp of when the dashboard was last modified, either by an API call or through the console. This number is expressed as the number of milliseconds since Jan 1, 1970 00:00:00 UTC.
  • deDashboardARN - The Amazon Resource Name (ARN) of the dashboard.

deSize :: Lens' DashboardEntry (Maybe Integer) Source #

The size of the dashboard, in bytes.

deDashboardName :: Lens' DashboardEntry (Maybe Text) Source #

The name of the dashboard.

deLastModified :: Lens' DashboardEntry (Maybe UTCTime) Source #

The time stamp of when the dashboard was last modified, either by an API call or through the console. This number is expressed as the number of milliseconds since Jan 1, 1970 00:00:00 UTC.

deDashboardARN :: Lens' DashboardEntry (Maybe Text) Source #

The Amazon Resource Name (ARN) of the dashboard.

DashboardValidationMessage

data DashboardValidationMessage Source #

An error or warning for the operation.

See: dashboardValidationMessage smart constructor.

Instances
Eq DashboardValidationMessage Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data DashboardValidationMessage Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DashboardValidationMessage -> c DashboardValidationMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DashboardValidationMessage #

toConstr :: DashboardValidationMessage -> Constr #

dataTypeOf :: DashboardValidationMessage -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DashboardValidationMessage) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DashboardValidationMessage) #

gmapT :: (forall b. Data b => b -> b) -> DashboardValidationMessage -> DashboardValidationMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DashboardValidationMessage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DashboardValidationMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> DashboardValidationMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DashboardValidationMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DashboardValidationMessage -> m DashboardValidationMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DashboardValidationMessage -> m DashboardValidationMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DashboardValidationMessage -> m DashboardValidationMessage #

Read DashboardValidationMessage Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show DashboardValidationMessage Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic DashboardValidationMessage Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep DashboardValidationMessage :: Type -> Type #

Hashable DashboardValidationMessage Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

FromXML DashboardValidationMessage Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData DashboardValidationMessage Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep DashboardValidationMessage Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep DashboardValidationMessage = D1 (MetaData "DashboardValidationMessage" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "DashboardValidationMessage'" PrefixI True) (S1 (MetaSel (Just "_dvmDataPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_dvmMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

dashboardValidationMessage :: DashboardValidationMessage Source #

Creates a value of DashboardValidationMessage with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dvmDataPath - The data path related to the message.
  • dvmMessage - A message describing the error or warning.

dvmDataPath :: Lens' DashboardValidationMessage (Maybe Text) Source #

The data path related to the message.

dvmMessage :: Lens' DashboardValidationMessage (Maybe Text) Source #

A message describing the error or warning.

Datapoint

data Datapoint Source #

Encapsulates the statistical data that CloudWatch computes from metric data.

See: datapoint smart constructor.

Instances
Eq Datapoint Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data Datapoint Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Datapoint -> c Datapoint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Datapoint #

toConstr :: Datapoint -> Constr #

dataTypeOf :: Datapoint -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Datapoint) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Datapoint) #

gmapT :: (forall b. Data b => b -> b) -> Datapoint -> Datapoint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Datapoint -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Datapoint -> r #

gmapQ :: (forall d. Data d => d -> u) -> Datapoint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Datapoint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Datapoint -> m Datapoint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Datapoint -> m Datapoint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Datapoint -> m Datapoint #

Read Datapoint Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show Datapoint Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic Datapoint Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep Datapoint :: Type -> Type #

Hashable Datapoint Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

FromXML Datapoint Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData Datapoint Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: Datapoint -> () #

type Rep Datapoint Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

datapoint :: Datapoint Source #

Creates a value of Datapoint with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dSampleCount - The number of metric values that contributed to the aggregate value of this data point.
  • dMaximum - The maximum metric value for the data point.
  • dAverage - The average of the metric values that correspond to the data point.
  • dMinimum - The minimum metric value for the data point.
  • dExtendedStatistics - The percentile statistic for the data point.
  • dSum - The sum of the metric values for the data point.
  • dUnit - The standard unit for the data point.
  • dTimestamp - The time stamp used for the data point.

dSampleCount :: Lens' Datapoint (Maybe Double) Source #

The number of metric values that contributed to the aggregate value of this data point.

dMaximum :: Lens' Datapoint (Maybe Double) Source #

The maximum metric value for the data point.

dAverage :: Lens' Datapoint (Maybe Double) Source #

The average of the metric values that correspond to the data point.

dMinimum :: Lens' Datapoint (Maybe Double) Source #

The minimum metric value for the data point.

dExtendedStatistics :: Lens' Datapoint (HashMap Text Double) Source #

The percentile statistic for the data point.

dSum :: Lens' Datapoint (Maybe Double) Source #

The sum of the metric values for the data point.

dUnit :: Lens' Datapoint (Maybe StandardUnit) Source #

The standard unit for the data point.

dTimestamp :: Lens' Datapoint (Maybe UTCTime) Source #

The time stamp used for the data point.

Dimension

data Dimension Source #

Expands the identity of a metric.

See: dimension smart constructor.

Instances
Eq Dimension Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data Dimension Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dimension -> c Dimension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dimension #

toConstr :: Dimension -> Constr #

dataTypeOf :: Dimension -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dimension) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dimension) #

gmapT :: (forall b. Data b => b -> b) -> Dimension -> Dimension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dimension -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dimension -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dimension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dimension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dimension -> m Dimension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dimension -> m Dimension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dimension -> m Dimension #

Read Dimension Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show Dimension Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic Dimension Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep Dimension :: Type -> Type #

Hashable Dimension Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

FromXML Dimension Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

ToQuery Dimension Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData Dimension Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: Dimension -> () #

type Rep Dimension Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep Dimension = D1 (MetaData "Dimension" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "Dimension'" PrefixI True) (S1 (MetaSel (Just "_dName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_dValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

dimension Source #

Arguments

:: Text

dName

-> Text

dValue

-> Dimension 

Creates a value of Dimension with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dName - The name of the dimension.
  • dValue - The value representing the dimension measurement.

dName :: Lens' Dimension Text Source #

The name of the dimension.

dValue :: Lens' Dimension Text Source #

The value representing the dimension measurement.

DimensionFilter

data DimensionFilter Source #

Represents filters for a dimension.

See: dimensionFilter smart constructor.

Instances
Eq DimensionFilter Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data DimensionFilter Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DimensionFilter -> c DimensionFilter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DimensionFilter #

toConstr :: DimensionFilter -> Constr #

dataTypeOf :: DimensionFilter -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DimensionFilter) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DimensionFilter) #

gmapT :: (forall b. Data b => b -> b) -> DimensionFilter -> DimensionFilter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DimensionFilter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DimensionFilter -> r #

gmapQ :: (forall d. Data d => d -> u) -> DimensionFilter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DimensionFilter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DimensionFilter -> m DimensionFilter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionFilter -> m DimensionFilter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionFilter -> m DimensionFilter #

Read DimensionFilter Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show DimensionFilter Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic DimensionFilter Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep DimensionFilter :: Type -> Type #

Hashable DimensionFilter Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

ToQuery DimensionFilter Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData DimensionFilter Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: DimensionFilter -> () #

type Rep DimensionFilter Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep DimensionFilter = D1 (MetaData "DimensionFilter" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "DimensionFilter'" PrefixI True) (S1 (MetaSel (Just "_dfValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_dfName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

dimensionFilter Source #

Arguments

:: Text

dfName

-> DimensionFilter 

Creates a value of DimensionFilter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dfValue - The value of the dimension to be matched.
  • dfName - The dimension name to be matched.

dfValue :: Lens' DimensionFilter (Maybe Text) Source #

The value of the dimension to be matched.

dfName :: Lens' DimensionFilter Text Source #

The dimension name to be matched.

MessageData

data MessageData Source #

A message returned by the GetMetricData API, including a code and a description.

See: messageData smart constructor.

Instances
Eq MessageData Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data MessageData Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageData -> c MessageData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageData #

toConstr :: MessageData -> Constr #

dataTypeOf :: MessageData -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MessageData) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageData) #

gmapT :: (forall b. Data b => b -> b) -> MessageData -> MessageData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageData -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageData -> m MessageData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageData -> m MessageData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageData -> m MessageData #

Read MessageData Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show MessageData Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic MessageData Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep MessageData :: Type -> Type #

Hashable MessageData Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

FromXML MessageData Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData MessageData Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: MessageData -> () #

type Rep MessageData Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep MessageData = D1 (MetaData "MessageData" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "MessageData'" PrefixI True) (S1 (MetaSel (Just "_mValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_mCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

messageData :: MessageData Source #

Creates a value of MessageData with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • mValue - The message text.
  • mCode - The error code or status code associated with the message.

mValue :: Lens' MessageData (Maybe Text) Source #

The message text.

mCode :: Lens' MessageData (Maybe Text) Source #

The error code or status code associated with the message.

Metric

data Metric Source #

Represents a specific metric.

See: metric smart constructor.

Instances
Eq Metric Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

(==) :: Metric -> Metric -> Bool #

(/=) :: Metric -> Metric -> Bool #

Data Metric Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Metric -> c Metric #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Metric #

toConstr :: Metric -> Constr #

dataTypeOf :: Metric -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Metric) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Metric) #

gmapT :: (forall b. Data b => b -> b) -> Metric -> Metric #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Metric -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Metric -> r #

gmapQ :: (forall d. Data d => d -> u) -> Metric -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Metric -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Metric -> m Metric #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Metric -> m Metric #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Metric -> m Metric #

Read Metric Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show Metric Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic Metric Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep Metric :: Type -> Type #

Methods

from :: Metric -> Rep Metric x #

to :: Rep Metric x -> Metric #

Hashable Metric Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

hashWithSalt :: Int -> Metric -> Int #

hash :: Metric -> Int #

FromXML Metric Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

ToQuery Metric Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData Metric Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: Metric -> () #

type Rep Metric Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep Metric = D1 (MetaData "Metric" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "Metric'" PrefixI True) (S1 (MetaSel (Just "_mMetricName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_mNamespace") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_mDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension])))))

metric :: Metric Source #

Creates a value of Metric with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mMetricName :: Lens' Metric (Maybe Text) Source #

The name of the metric.

mNamespace :: Lens' Metric (Maybe Text) Source #

The namespace of the metric.

mDimensions :: Lens' Metric [Dimension] Source #

The dimensions for the metric.

MetricAlarm

data MetricAlarm Source #

Represents an alarm.

See: metricAlarm smart constructor.

Instances
Eq MetricAlarm Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data MetricAlarm Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetricAlarm -> c MetricAlarm #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetricAlarm #

toConstr :: MetricAlarm -> Constr #

dataTypeOf :: MetricAlarm -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetricAlarm) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetricAlarm) #

gmapT :: (forall b. Data b => b -> b) -> MetricAlarm -> MetricAlarm #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetricAlarm -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetricAlarm -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetricAlarm -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetricAlarm -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetricAlarm -> m MetricAlarm #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricAlarm -> m MetricAlarm #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricAlarm -> m MetricAlarm #

Read MetricAlarm Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show MetricAlarm Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic MetricAlarm Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep MetricAlarm :: Type -> Type #

Hashable MetricAlarm Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

FromXML MetricAlarm Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData MetricAlarm Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: MetricAlarm -> () #

type Rep MetricAlarm Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep MetricAlarm = D1 (MetaData "MetricAlarm" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "MetricAlarm'" PrefixI True) ((((S1 (MetaSel (Just "_maAlarmName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_maStateUpdatedTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601)) :*: S1 (MetaSel (Just "_maTreatMissingData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_maPeriod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat)) :*: (S1 (MetaSel (Just "_maAlarmDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_maEvaluationPeriods") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))))) :*: ((S1 (MetaSel (Just "_maMetricName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_maNamespace") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_maComparisonOperator") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ComparisonOperator)))) :*: (S1 (MetaSel (Just "_maOKActions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: (S1 (MetaSel (Just "_maEvaluateLowSampleCountPercentile") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_maStateValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe StateValue)))))) :*: (((S1 (MetaSel (Just "_maDatapointsToAlarm") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat)) :*: (S1 (MetaSel (Just "_maThreshold") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Double)) :*: S1 (MetaSel (Just "_maAlarmConfigurationUpdatedTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601)))) :*: (S1 (MetaSel (Just "_maActionsEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 (MetaSel (Just "_maInsufficientDataActions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_maStateReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) :*: ((S1 (MetaSel (Just "_maStateReasonData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_maDimensions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Dimension])) :*: S1 (MetaSel (Just "_maAlarmARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_maAlarmActions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])) :*: S1 (MetaSel (Just "_maUnit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe StandardUnit))) :*: (S1 (MetaSel (Just "_maStatistic") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Statistic)) :*: S1 (MetaSel (Just "_maExtendedStatistic") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))))

metricAlarm :: MetricAlarm Source #

Creates a value of MetricAlarm with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • maAlarmName - The name of the alarm.
  • maStateUpdatedTimestamp - The time stamp of the last update to the alarm state.
  • maTreatMissingData - Sets how this alarm is to handle missing data points. If this parameter is omitted, the default behavior of missing is used.
  • maPeriod - The period, in seconds, over which the statistic is applied.
  • maAlarmDescription - The description of the alarm.
  • maEvaluationPeriods - The number of periods over which data is compared to the specified threshold.
  • maMetricName - The name of the metric associated with the alarm.
  • maNamespace - The namespace of the metric associated with the alarm.
  • maComparisonOperator - The arithmetic operation to use when comparing the specified statistic and threshold. The specified statistic value is used as the first operand.
  • maOKActions - The actions to execute when this alarm transitions to the OK state from any other state. Each action is specified as an Amazon Resource Name (ARN).
  • maEvaluateLowSampleCountPercentile - Used only for alarms based on percentiles. If ignore , the alarm state does not change during periods with too few data points to be statistically significant. If evaluate or this parameter is not used, the alarm is always evaluated and possibly changes state no matter how many data points are available.
  • maStateValue - The state value for the alarm.
  • maDatapointsToAlarm - The number of datapoints that must be breaching to trigger the alarm.
  • maThreshold - The value to compare with the specified statistic.
  • maAlarmConfigurationUpdatedTimestamp - The time stamp of the last update to the alarm configuration.
  • maActionsEnabled - Indicates whether actions should be executed during any changes to the alarm state.
  • maInsufficientDataActions - The actions to execute when this alarm transitions to the INSUFFICIENT_DATA state from any other state. Each action is specified as an Amazon Resource Name (ARN).
  • maStateReason - An explanation for the alarm state, in text format.
  • maStateReasonData - An explanation for the alarm state, in JSON format.
  • maDimensions - The dimensions for the metric associated with the alarm.
  • maAlarmARN - The Amazon Resource Name (ARN) of the alarm.
  • maAlarmActions - The actions to execute when this alarm transitions to the ALARM state from any other state. Each action is specified as an Amazon Resource Name (ARN).
  • maUnit - The unit of the metric associated with the alarm.
  • maStatistic - The statistic for the metric associated with the alarm, other than percentile. For percentile statistics, use ExtendedStatistic .
  • maExtendedStatistic - The percentile statistic for the metric associated with the alarm. Specify a value between p0.0 and p100.

maAlarmName :: Lens' MetricAlarm (Maybe Text) Source #

The name of the alarm.

maStateUpdatedTimestamp :: Lens' MetricAlarm (Maybe UTCTime) Source #

The time stamp of the last update to the alarm state.

maTreatMissingData :: Lens' MetricAlarm (Maybe Text) Source #

Sets how this alarm is to handle missing data points. If this parameter is omitted, the default behavior of missing is used.

maPeriod :: Lens' MetricAlarm (Maybe Natural) Source #

The period, in seconds, over which the statistic is applied.

maAlarmDescription :: Lens' MetricAlarm (Maybe Text) Source #

The description of the alarm.

maEvaluationPeriods :: Lens' MetricAlarm (Maybe Natural) Source #

The number of periods over which data is compared to the specified threshold.

maMetricName :: Lens' MetricAlarm (Maybe Text) Source #

The name of the metric associated with the alarm.

maNamespace :: Lens' MetricAlarm (Maybe Text) Source #

The namespace of the metric associated with the alarm.

maComparisonOperator :: Lens' MetricAlarm (Maybe ComparisonOperator) Source #

The arithmetic operation to use when comparing the specified statistic and threshold. The specified statistic value is used as the first operand.

maOKActions :: Lens' MetricAlarm [Text] Source #

The actions to execute when this alarm transitions to the OK state from any other state. Each action is specified as an Amazon Resource Name (ARN).

maEvaluateLowSampleCountPercentile :: Lens' MetricAlarm (Maybe Text) Source #

Used only for alarms based on percentiles. If ignore , the alarm state does not change during periods with too few data points to be statistically significant. If evaluate or this parameter is not used, the alarm is always evaluated and possibly changes state no matter how many data points are available.

maStateValue :: Lens' MetricAlarm (Maybe StateValue) Source #

The state value for the alarm.

maDatapointsToAlarm :: Lens' MetricAlarm (Maybe Natural) Source #

The number of datapoints that must be breaching to trigger the alarm.

maThreshold :: Lens' MetricAlarm (Maybe Double) Source #

The value to compare with the specified statistic.

maAlarmConfigurationUpdatedTimestamp :: Lens' MetricAlarm (Maybe UTCTime) Source #

The time stamp of the last update to the alarm configuration.

maActionsEnabled :: Lens' MetricAlarm (Maybe Bool) Source #

Indicates whether actions should be executed during any changes to the alarm state.

maInsufficientDataActions :: Lens' MetricAlarm [Text] Source #

The actions to execute when this alarm transitions to the INSUFFICIENT_DATA state from any other state. Each action is specified as an Amazon Resource Name (ARN).

maStateReason :: Lens' MetricAlarm (Maybe Text) Source #

An explanation for the alarm state, in text format.

maStateReasonData :: Lens' MetricAlarm (Maybe Text) Source #

An explanation for the alarm state, in JSON format.

maDimensions :: Lens' MetricAlarm [Dimension] Source #

The dimensions for the metric associated with the alarm.

maAlarmARN :: Lens' MetricAlarm (Maybe Text) Source #

The Amazon Resource Name (ARN) of the alarm.

maAlarmActions :: Lens' MetricAlarm [Text] Source #

The actions to execute when this alarm transitions to the ALARM state from any other state. Each action is specified as an Amazon Resource Name (ARN).

maUnit :: Lens' MetricAlarm (Maybe StandardUnit) Source #

The unit of the metric associated with the alarm.

maStatistic :: Lens' MetricAlarm (Maybe Statistic) Source #

The statistic for the metric associated with the alarm, other than percentile. For percentile statistics, use ExtendedStatistic .

maExtendedStatistic :: Lens' MetricAlarm (Maybe Text) Source #

The percentile statistic for the metric associated with the alarm. Specify a value between p0.0 and p100.

MetricDataQuery

data MetricDataQuery Source #

This structure indicates the metric data to return, and whether this call is just retrieving a batch set of data for one metric, or is performing a math expression on metric data. A single GetMetricData call can include up to 100 MetricDataQuery structures.

See: metricDataQuery smart constructor.

Instances
Eq MetricDataQuery Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data MetricDataQuery Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetricDataQuery -> c MetricDataQuery #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetricDataQuery #

toConstr :: MetricDataQuery -> Constr #

dataTypeOf :: MetricDataQuery -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetricDataQuery) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetricDataQuery) #

gmapT :: (forall b. Data b => b -> b) -> MetricDataQuery -> MetricDataQuery #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetricDataQuery -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetricDataQuery -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetricDataQuery -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetricDataQuery -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetricDataQuery -> m MetricDataQuery #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricDataQuery -> m MetricDataQuery #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricDataQuery -> m MetricDataQuery #

Read MetricDataQuery Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show MetricDataQuery Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic MetricDataQuery Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep MetricDataQuery :: Type -> Type #

Hashable MetricDataQuery Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

ToQuery MetricDataQuery Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData MetricDataQuery Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: MetricDataQuery -> () #

type Rep MetricDataQuery Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep MetricDataQuery = D1 (MetaData "MetricDataQuery" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "MetricDataQuery'" PrefixI True) ((S1 (MetaSel (Just "_mdqReturnData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "_mdqExpression") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_mdqLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_mdqMetricStat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MetricStat)) :*: S1 (MetaSel (Just "_mdqId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

metricDataQuery Source #

Arguments

:: Text

mdqId

-> MetricDataQuery 

Creates a value of MetricDataQuery with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • mdqReturnData - Indicates whether to return the time stamps and raw data values of this metric. If you are performing this call just to do math expressions and do not also need the raw data returned, you can specify False . If you omit this, the default of True is used.
  • mdqExpression - The math expression to be performed on the returned data, if this structure is performing a math expression. For more information about metric math expressions, see Metric Math Syntax and Functions in the Amazon CloudWatch User Guide . Within one MetricDataQuery structure, you must specify either Expression or MetricStat but not both.
  • mdqLabel - A human-readable label for this metric or expression. This is especially useful if this is an expression, so that you know what the value represents. If the metric or expression is shown in a CloudWatch dashboard widget, the label is shown. If Label is omitted, CloudWatch generates a default.
  • mdqMetricStat - The metric to be returned, along with statistics, period, and units. Use this parameter only if this structure is performing a data retrieval and not performing a math expression on the returned data. Within one MetricDataQuery structure, you must specify either Expression or MetricStat but not both.
  • mdqId - A short name used to tie this structure to the results in the response. This name must be unique within a single call to GetMetricData . If you are performing math expressions on this set of data, this name represents that data and can serve as a variable in the mathematical expression. The valid characters are letters, numbers, and underscore. The first character must be a lowercase letter.

mdqReturnData :: Lens' MetricDataQuery (Maybe Bool) Source #

Indicates whether to return the time stamps and raw data values of this metric. If you are performing this call just to do math expressions and do not also need the raw data returned, you can specify False . If you omit this, the default of True is used.

mdqExpression :: Lens' MetricDataQuery (Maybe Text) Source #

The math expression to be performed on the returned data, if this structure is performing a math expression. For more information about metric math expressions, see Metric Math Syntax and Functions in the Amazon CloudWatch User Guide . Within one MetricDataQuery structure, you must specify either Expression or MetricStat but not both.

mdqLabel :: Lens' MetricDataQuery (Maybe Text) Source #

A human-readable label for this metric or expression. This is especially useful if this is an expression, so that you know what the value represents. If the metric or expression is shown in a CloudWatch dashboard widget, the label is shown. If Label is omitted, CloudWatch generates a default.

mdqMetricStat :: Lens' MetricDataQuery (Maybe MetricStat) Source #

The metric to be returned, along with statistics, period, and units. Use this parameter only if this structure is performing a data retrieval and not performing a math expression on the returned data. Within one MetricDataQuery structure, you must specify either Expression or MetricStat but not both.

mdqId :: Lens' MetricDataQuery Text Source #

A short name used to tie this structure to the results in the response. This name must be unique within a single call to GetMetricData . If you are performing math expressions on this set of data, this name represents that data and can serve as a variable in the mathematical expression. The valid characters are letters, numbers, and underscore. The first character must be a lowercase letter.

MetricDataResult

data MetricDataResult Source #

A GetMetricData call returns an array of MetricDataResult structures. Each of these structures includes the data points for that metric, along with the time stamps of those data points and other identifying information.

See: metricDataResult smart constructor.

Instances
Eq MetricDataResult Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data MetricDataResult Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetricDataResult -> c MetricDataResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetricDataResult #

toConstr :: MetricDataResult -> Constr #

dataTypeOf :: MetricDataResult -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetricDataResult) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetricDataResult) #

gmapT :: (forall b. Data b => b -> b) -> MetricDataResult -> MetricDataResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetricDataResult -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetricDataResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetricDataResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetricDataResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetricDataResult -> m MetricDataResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricDataResult -> m MetricDataResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricDataResult -> m MetricDataResult #

Read MetricDataResult Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show MetricDataResult Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic MetricDataResult Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep MetricDataResult :: Type -> Type #

Hashable MetricDataResult Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

FromXML MetricDataResult Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData MetricDataResult Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: MetricDataResult -> () #

type Rep MetricDataResult Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep MetricDataResult = D1 (MetaData "MetricDataResult" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "MetricDataResult'" PrefixI True) ((S1 (MetaSel (Just "_mdrValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Double])) :*: (S1 (MetaSel (Just "_mdrId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_mdrTimestamps") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ISO8601])))) :*: (S1 (MetaSel (Just "_mdrMessages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [MessageData])) :*: (S1 (MetaSel (Just "_mdrLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_mdrStatusCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe StatusCode))))))

metricDataResult :: MetricDataResult Source #

Creates a value of MetricDataResult with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • mdrValues - The data points for the metric corresponding to Timestamps . The number of values always matches the number of time stamps and the time stamp for Values[x] is Timestamps[x].
  • mdrId - The short name you specified to represent this metric.
  • mdrTimestamps - The time stamps for the data points, formatted in Unix timestamp format. The number of time stamps always matches the number of values and the value for Timestamps[x] is Values[x].
  • mdrMessages - A list of messages with additional information about the data returned.
  • mdrLabel - The human-readable label associated with the data.
  • mdrStatusCode - The status of the returned data. Complete indicates that all data points in the requested time range were returned. PartialData means that an incomplete set of data points were returned. You can use the NextToken value that was returned and repeat your request to get more data points. NextToken is not returned if you are performing a math expression. InternalError indicates that an error occurred. Retry your request using NextToken , if present.

mdrValues :: Lens' MetricDataResult [Double] Source #

The data points for the metric corresponding to Timestamps . The number of values always matches the number of time stamps and the time stamp for Values[x] is Timestamps[x].

mdrId :: Lens' MetricDataResult (Maybe Text) Source #

The short name you specified to represent this metric.

mdrTimestamps :: Lens' MetricDataResult [UTCTime] Source #

The time stamps for the data points, formatted in Unix timestamp format. The number of time stamps always matches the number of values and the value for Timestamps[x] is Values[x].

mdrMessages :: Lens' MetricDataResult [MessageData] Source #

A list of messages with additional information about the data returned.

mdrLabel :: Lens' MetricDataResult (Maybe Text) Source #

The human-readable label associated with the data.

mdrStatusCode :: Lens' MetricDataResult (Maybe StatusCode) Source #

The status of the returned data. Complete indicates that all data points in the requested time range were returned. PartialData means that an incomplete set of data points were returned. You can use the NextToken value that was returned and repeat your request to get more data points. NextToken is not returned if you are performing a math expression. InternalError indicates that an error occurred. Retry your request using NextToken , if present.

MetricDatum

data MetricDatum Source #

Encapsulates the information sent to either create a metric or add new values to be aggregated into an existing metric.

See: metricDatum smart constructor.

Instances
Eq MetricDatum Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data MetricDatum Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetricDatum -> c MetricDatum #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetricDatum #

toConstr :: MetricDatum -> Constr #

dataTypeOf :: MetricDatum -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetricDatum) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetricDatum) #

gmapT :: (forall b. Data b => b -> b) -> MetricDatum -> MetricDatum #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetricDatum -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetricDatum -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetricDatum -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetricDatum -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetricDatum -> m MetricDatum #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricDatum -> m MetricDatum #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricDatum -> m MetricDatum #

Read MetricDatum Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show MetricDatum Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic MetricDatum Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep MetricDatum :: Type -> Type #

Hashable MetricDatum Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

ToQuery MetricDatum Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData MetricDatum Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: MetricDatum -> () #

type Rep MetricDatum Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

metricDatum Source #

Creates a value of MetricDatum with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • mdValue - The value for the metric. Although the parameter accepts numbers of type Double, CloudWatch rejects values that are either too small or too large. Values must be in the range of 8.515920e-109 to 1.174271e+108 (Base 10) or 2e-360 to 2e360 (Base 2). In addition, special values (for example, NaN, +Infinity, -Infinity) are not supported.
  • mdStorageResolution - Valid values are 1 and 60. Setting this to 1 specifies this metric as a high-resolution metric, so that CloudWatch stores the metric with sub-minute resolution down to one second. Setting this to 60 specifies this metric as a regular-resolution metric, which CloudWatch stores at 1-minute resolution. Currently, high resolution is available only for custom metrics. For more information about high-resolution metrics, see High-Resolution Metrics in the Amazon CloudWatch User Guide . This field is optional, if you do not specify it the default of 60 is used.
  • mdDimensions - The dimensions associated with the metric.
  • mdUnit - The unit of the metric.
  • mdTimestamp - The time the metric data was received, expressed as the number of milliseconds since Jan 1, 1970 00:00:00 UTC.
  • mdStatisticValues - The statistical values for the metric.
  • mdMetricName - The name of the metric.

mdValue :: Lens' MetricDatum (Maybe Double) Source #

The value for the metric. Although the parameter accepts numbers of type Double, CloudWatch rejects values that are either too small or too large. Values must be in the range of 8.515920e-109 to 1.174271e+108 (Base 10) or 2e-360 to 2e360 (Base 2). In addition, special values (for example, NaN, +Infinity, -Infinity) are not supported.

mdStorageResolution :: Lens' MetricDatum (Maybe Natural) Source #

Valid values are 1 and 60. Setting this to 1 specifies this metric as a high-resolution metric, so that CloudWatch stores the metric with sub-minute resolution down to one second. Setting this to 60 specifies this metric as a regular-resolution metric, which CloudWatch stores at 1-minute resolution. Currently, high resolution is available only for custom metrics. For more information about high-resolution metrics, see High-Resolution Metrics in the Amazon CloudWatch User Guide . This field is optional, if you do not specify it the default of 60 is used.

mdDimensions :: Lens' MetricDatum [Dimension] Source #

The dimensions associated with the metric.

mdUnit :: Lens' MetricDatum (Maybe StandardUnit) Source #

The unit of the metric.

mdTimestamp :: Lens' MetricDatum (Maybe UTCTime) Source #

The time the metric data was received, expressed as the number of milliseconds since Jan 1, 1970 00:00:00 UTC.

mdStatisticValues :: Lens' MetricDatum (Maybe StatisticSet) Source #

The statistical values for the metric.

mdMetricName :: Lens' MetricDatum Text Source #

The name of the metric.

MetricStat

data MetricStat Source #

This structure defines the metric to be returned, along with the statistics, period, and units.

See: metricStat smart constructor.

Instances
Eq MetricStat Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data MetricStat Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetricStat -> c MetricStat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetricStat #

toConstr :: MetricStat -> Constr #

dataTypeOf :: MetricStat -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MetricStat) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetricStat) #

gmapT :: (forall b. Data b => b -> b) -> MetricStat -> MetricStat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetricStat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetricStat -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetricStat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetricStat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetricStat -> m MetricStat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricStat -> m MetricStat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetricStat -> m MetricStat #

Read MetricStat Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show MetricStat Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic MetricStat Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep MetricStat :: Type -> Type #

Hashable MetricStat Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

ToQuery MetricStat Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData MetricStat Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: MetricStat -> () #

type Rep MetricStat Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep MetricStat = D1 (MetaData "MetricStat" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "MetricStat'" PrefixI True) ((S1 (MetaSel (Just "_msUnit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe StandardUnit)) :*: S1 (MetaSel (Just "_msMetric") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Metric)) :*: (S1 (MetaSel (Just "_msPeriod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Nat) :*: S1 (MetaSel (Just "_msStat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

metricStat Source #

Creates a value of MetricStat with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • msUnit - The unit to use for the returned data points.
  • msMetric - The metric to return, including the metric name, namespace, and dimensions.
  • msPeriod - The period to use when retrieving the metric.
  • msStat - The statistic to return. It can include any CloudWatch statistic or extended statistic.

msUnit :: Lens' MetricStat (Maybe StandardUnit) Source #

The unit to use for the returned data points.

msMetric :: Lens' MetricStat Metric Source #

The metric to return, including the metric name, namespace, and dimensions.

msPeriod :: Lens' MetricStat Natural Source #

The period to use when retrieving the metric.

msStat :: Lens' MetricStat Text Source #

The statistic to return. It can include any CloudWatch statistic or extended statistic.

StatisticSet

data StatisticSet Source #

Represents a set of statistics that describes a specific metric.

See: statisticSet smart constructor.

Instances
Eq StatisticSet Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Data StatisticSet Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StatisticSet -> c StatisticSet #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StatisticSet #

toConstr :: StatisticSet -> Constr #

dataTypeOf :: StatisticSet -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StatisticSet) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StatisticSet) #

gmapT :: (forall b. Data b => b -> b) -> StatisticSet -> StatisticSet #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StatisticSet -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StatisticSet -> r #

gmapQ :: (forall d. Data d => d -> u) -> StatisticSet -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StatisticSet -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StatisticSet -> m StatisticSet #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StatisticSet -> m StatisticSet #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StatisticSet -> m StatisticSet #

Read StatisticSet Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Show StatisticSet Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Generic StatisticSet Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Associated Types

type Rep StatisticSet :: Type -> Type #

Hashable StatisticSet Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

ToQuery StatisticSet Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

NFData StatisticSet Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

Methods

rnf :: StatisticSet -> () #

type Rep StatisticSet Source # 
Instance details

Defined in Network.AWS.CloudWatch.Types.Product

type Rep StatisticSet = D1 (MetaData "StatisticSet" "Network.AWS.CloudWatch.Types.Product" "amazonka-cloudwatch-1.6.1-7Rnwowqga1k8zXg3cAhS87" False) (C1 (MetaCons "StatisticSet'" PrefixI True) ((S1 (MetaSel (Just "_ssSampleCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "_ssSum") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Just "_ssMinimum") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "_ssMaximum") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))))

statisticSet Source #

Creates a value of StatisticSet with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ssSampleCount - The number of samples used for the statistic set.
  • ssSum - The sum of values for the sample set.
  • ssMinimum - The minimum value of the sample set.
  • ssMaximum - The maximum value of the sample set.

ssSampleCount :: Lens' StatisticSet Double Source #

The number of samples used for the statistic set.

ssSum :: Lens' StatisticSet Double Source #

The sum of values for the sample set.

ssMinimum :: Lens' StatisticSet Double Source #

The minimum value of the sample set.

ssMaximum :: Lens' StatisticSet Double Source #

The maximum value of the sample set.