amazonka-shield-1.6.0: Amazon Shield 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.Shield

Contents

Description

AWS Shield Advanced

This is the AWS Shield Advanced API Reference . This guide is for developers who need detailed information about the AWS Shield Advanced API actions, data types, and errors. For detailed information about AWS WAF and AWS Shield Advanced features and an overview of how to use the AWS WAF and AWS Shield Advanced APIs, see the AWS WAF and AWS Shield Developer Guide .

Synopsis

Service Configuration

shield :: Service Source #

API version 2016-06-02 of the Amazon Shield 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 Shield.

InvalidResourceException

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

Exception that indicates that the resource is invalid. You might not have access to the resource, or the resource might not exist.

InvalidParameterException

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

Exception that indicates that the parameters passed to the API are invalid.

LimitsExceededException

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

Exception that indicates that the operation would exceed a limit.

Type is the type of limit that would be exceeded.

Limit is the threshold that would be exceeded.

InternalErrorException

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

Exception that indicates that a problem occurred with the service infrastructure. You can retry the request.

ResourceAlreadyExistsException

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

Exception indicating the specified resource already exists.

OptimisticLockException

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

Exception that indicates that the protection state has been modified by another client. You can retry the request.

InvalidOperationException

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

Exception that indicates that the operation would not cause any change to occur.

LockedSubscriptionException

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

Exception that indicates that the subscription you are trying to delete has not yet completed the 1-year commitment. You cannot delete this subscription.

ResourceNotFoundException

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

Exception indicating the specified 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.

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.

CreateSubscription

ListProtections (Paginated)

DeleteSubscription

DescribeAttack

DescribeProtection

ListAttacks

CreateProtection

DeleteProtection

GetSubscriptionState

DescribeSubscription

Types

AttackLayer

data AttackLayer Source #

Constructors

Application 
Network 

Instances

Bounded AttackLayer Source # 
Enum AttackLayer Source # 
Eq AttackLayer Source # 
Data AttackLayer Source # 

Methods

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

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

toConstr :: AttackLayer -> Constr #

dataTypeOf :: AttackLayer -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AttackLayer Source # 
Read AttackLayer Source # 
Show AttackLayer Source # 
Generic AttackLayer Source # 

Associated Types

type Rep AttackLayer :: * -> * #

Hashable AttackLayer Source # 
FromJSON AttackLayer Source # 
NFData AttackLayer Source # 

Methods

rnf :: AttackLayer -> () #

ToHeader AttackLayer Source # 
ToQuery AttackLayer Source # 
ToByteString AttackLayer Source # 
FromText AttackLayer Source # 
ToText AttackLayer Source # 

Methods

toText :: AttackLayer -> Text #

type Rep AttackLayer Source # 
type Rep AttackLayer = D1 * (MetaData "AttackLayer" "Network.AWS.Shield.Types.Sum" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) ((:+:) * (C1 * (MetaCons "Application" PrefixI False) (U1 *)) (C1 * (MetaCons "Network" PrefixI False) (U1 *)))

AttackPropertyIdentifier

data AttackPropertyIdentifier Source #

Instances

Bounded AttackPropertyIdentifier Source # 
Enum AttackPropertyIdentifier Source # 
Eq AttackPropertyIdentifier Source # 
Data AttackPropertyIdentifier Source # 

Methods

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

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

toConstr :: AttackPropertyIdentifier -> Constr #

dataTypeOf :: AttackPropertyIdentifier -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AttackPropertyIdentifier Source # 
Read AttackPropertyIdentifier Source # 
Show AttackPropertyIdentifier Source # 
Generic AttackPropertyIdentifier Source # 
Hashable AttackPropertyIdentifier Source # 
FromJSON AttackPropertyIdentifier Source # 
NFData AttackPropertyIdentifier Source # 
ToHeader AttackPropertyIdentifier Source # 
ToQuery AttackPropertyIdentifier Source # 
ToByteString AttackPropertyIdentifier Source # 
FromText AttackPropertyIdentifier Source # 
ToText AttackPropertyIdentifier Source # 
type Rep AttackPropertyIdentifier Source # 
type Rep AttackPropertyIdentifier = D1 * (MetaData "AttackPropertyIdentifier" "Network.AWS.Shield.Types.Sum" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) ((:+:) * ((:+:) * (C1 * (MetaCons "DestinationURL" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Referrer" PrefixI False) (U1 *)) (C1 * (MetaCons "SourceASN" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "SourceCountry" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SourceIPAddress" PrefixI False) (U1 *)) (C1 * (MetaCons "SourceUserAgent" PrefixI False) (U1 *)))))

SubResourceType

data SubResourceType Source #

Constructors

IP 
URL 

Instances

Bounded SubResourceType Source # 
Enum SubResourceType Source # 
Eq SubResourceType Source # 
Data SubResourceType Source # 

Methods

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

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

toConstr :: SubResourceType -> Constr #

dataTypeOf :: SubResourceType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SubResourceType Source # 
Read SubResourceType Source # 
Show SubResourceType Source # 
Generic SubResourceType Source # 
Hashable SubResourceType Source # 
FromJSON SubResourceType Source # 
NFData SubResourceType Source # 

Methods

rnf :: SubResourceType -> () #

ToHeader SubResourceType Source # 
ToQuery SubResourceType Source # 
ToByteString SubResourceType Source # 
FromText SubResourceType Source # 
ToText SubResourceType Source # 
type Rep SubResourceType Source # 
type Rep SubResourceType = D1 * (MetaData "SubResourceType" "Network.AWS.Shield.Types.Sum" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) ((:+:) * (C1 * (MetaCons "IP" PrefixI False) (U1 *)) (C1 * (MetaCons "URL" PrefixI False) (U1 *)))

SubscriptionState

data SubscriptionState Source #

Constructors

Active 
Inactive 

Instances

Bounded SubscriptionState Source # 
Enum SubscriptionState Source # 
Eq SubscriptionState Source # 
Data SubscriptionState Source # 

Methods

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

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

toConstr :: SubscriptionState -> Constr #

dataTypeOf :: SubscriptionState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SubscriptionState Source # 
Read SubscriptionState Source # 
Show SubscriptionState Source # 
Generic SubscriptionState Source # 
Hashable SubscriptionState Source # 
FromJSON SubscriptionState Source # 
NFData SubscriptionState Source # 

Methods

rnf :: SubscriptionState -> () #

ToHeader SubscriptionState Source # 
ToQuery SubscriptionState Source # 
ToByteString SubscriptionState Source # 
FromText SubscriptionState Source # 
ToText SubscriptionState Source # 
type Rep SubscriptionState Source # 
type Rep SubscriptionState = D1 * (MetaData "SubscriptionState" "Network.AWS.Shield.Types.Sum" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) ((:+:) * (C1 * (MetaCons "Active" PrefixI False) (U1 *)) (C1 * (MetaCons "Inactive" PrefixI False) (U1 *)))

Unit

data Unit Source #

Constructors

Bits 
Bytes 
Packets 
Requests 

Instances

Bounded Unit Source # 
Enum Unit Source # 

Methods

succ :: Unit -> Unit #

pred :: Unit -> Unit #

toEnum :: Int -> Unit #

fromEnum :: Unit -> Int #

enumFrom :: Unit -> [Unit] #

enumFromThen :: Unit -> Unit -> [Unit] #

enumFromTo :: Unit -> Unit -> [Unit] #

enumFromThenTo :: Unit -> Unit -> Unit -> [Unit] #

Eq Unit Source # 

Methods

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

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

Data Unit Source # 

Methods

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

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

toConstr :: Unit -> Constr #

dataTypeOf :: Unit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Unit Source # 

Methods

compare :: Unit -> Unit -> Ordering #

(<) :: Unit -> Unit -> Bool #

(<=) :: Unit -> Unit -> Bool #

(>) :: Unit -> Unit -> Bool #

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

max :: Unit -> Unit -> Unit #

min :: Unit -> Unit -> Unit #

Read Unit Source # 
Show Unit Source # 

Methods

showsPrec :: Int -> Unit -> ShowS #

show :: Unit -> String #

showList :: [Unit] -> ShowS #

Generic Unit Source # 

Associated Types

type Rep Unit :: * -> * #

Methods

from :: Unit -> Rep Unit x #

to :: Rep Unit x -> Unit #

Hashable Unit Source # 

Methods

hashWithSalt :: Int -> Unit -> Int #

hash :: Unit -> Int #

FromJSON Unit Source # 
NFData Unit Source # 

Methods

rnf :: Unit -> () #

ToHeader Unit Source # 

Methods

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

ToQuery Unit Source # 

Methods

toQuery :: Unit -> QueryString #

ToByteString Unit Source # 

Methods

toBS :: Unit -> ByteString #

FromText Unit Source # 

Methods

parser :: Parser Unit #

ToText Unit Source # 

Methods

toText :: Unit -> Text #

type Rep Unit Source # 
type Rep Unit = D1 * (MetaData "Unit" "Network.AWS.Shield.Types.Sum" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Bits" PrefixI False) (U1 *)) (C1 * (MetaCons "Bytes" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Packets" PrefixI False) (U1 *)) (C1 * (MetaCons "Requests" PrefixI False) (U1 *))))

AttackDetail

data AttackDetail Source #

The details of a DDoS attack.

See: attackDetail smart constructor.

Instances

Eq AttackDetail Source # 
Data AttackDetail Source # 

Methods

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

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

toConstr :: AttackDetail -> Constr #

dataTypeOf :: AttackDetail -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AttackDetail Source # 
Show AttackDetail Source # 
Generic AttackDetail Source # 

Associated Types

type Rep AttackDetail :: * -> * #

Hashable AttackDetail Source # 
FromJSON AttackDetail Source # 
NFData AttackDetail Source # 

Methods

rnf :: AttackDetail -> () #

type Rep AttackDetail Source # 

attackDetail :: AttackDetail Source #

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

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

adAttackId :: Lens' AttackDetail (Maybe Text) Source #

The unique identifier (ID) of the attack.

adStartTime :: Lens' AttackDetail (Maybe UTCTime) Source #

The time the attack started, in Unix time in seconds. For more information see timestamp .

adSubResources :: Lens' AttackDetail [SubResourceSummary] Source #

If applicable, additional detail about the resource being attacked, for example, IP address or URL.

adMitigations :: Lens' AttackDetail [Mitigation] Source #

List of mitigation actions taken for the attack.

adAttackCounters :: Lens' AttackDetail [SummarizedCounter] Source #

List of counters that describe the attack for the specified time period.

adResourceARN :: Lens' AttackDetail (Maybe Text) Source #

The ARN (Amazon Resource Name) of the resource that was attacked.

adEndTime :: Lens' AttackDetail (Maybe UTCTime) Source #

The time the attack ended, in Unix time in seconds. For more information see timestamp .

AttackProperty

data AttackProperty Source #

Details of the described attack.

See: attackProperty smart constructor.

Instances

Eq AttackProperty Source # 
Data AttackProperty Source # 

Methods

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

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

toConstr :: AttackProperty -> Constr #

dataTypeOf :: AttackProperty -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AttackProperty Source # 
Show AttackProperty Source # 
Generic AttackProperty Source # 

Associated Types

type Rep AttackProperty :: * -> * #

Hashable AttackProperty Source # 
FromJSON AttackProperty Source # 
NFData AttackProperty Source # 

Methods

rnf :: AttackProperty -> () #

type Rep AttackProperty Source # 
type Rep AttackProperty = D1 * (MetaData "AttackProperty" "Network.AWS.Shield.Types.Product" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) (C1 * (MetaCons "AttackProperty'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_apAttackLayer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AttackLayer))) (S1 * (MetaSel (Just Symbol "_apTopContributors") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Contributor])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_apAttackPropertyIdentifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AttackPropertyIdentifier))) ((:*:) * (S1 * (MetaSel (Just Symbol "_apTotal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) (S1 * (MetaSel (Just Symbol "_apUnit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Unit)))))))

attackProperty :: AttackProperty Source #

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

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

  • apAttackLayer - The type of DDoS event that was observed. NETWORK indicates layer 3 and layer 4 events and APPLICATION indicates layer 7 events.
  • apTopContributors - The array of Contributor objects that includes the top five contributors to an attack.
  • apAttackPropertyIdentifier - Defines the DDoS attack property information that is provided.
  • apTotal - The total contributions made to this attack by all contributors, not just the five listed in the TopContributors list.
  • apUnit - The unit of the Value of the contributions.

apAttackLayer :: Lens' AttackProperty (Maybe AttackLayer) Source #

The type of DDoS event that was observed. NETWORK indicates layer 3 and layer 4 events and APPLICATION indicates layer 7 events.

apTopContributors :: Lens' AttackProperty [Contributor] Source #

The array of Contributor objects that includes the top five contributors to an attack.

apAttackPropertyIdentifier :: Lens' AttackProperty (Maybe AttackPropertyIdentifier) Source #

Defines the DDoS attack property information that is provided.

apTotal :: Lens' AttackProperty (Maybe Integer) Source #

The total contributions made to this attack by all contributors, not just the five listed in the TopContributors list.

apUnit :: Lens' AttackProperty (Maybe Unit) Source #

The unit of the Value of the contributions.

AttackSummary

data AttackSummary Source #

Summarizes all DDoS attacks for a specified time period.

See: attackSummary smart constructor.

Instances

Eq AttackSummary Source # 
Data AttackSummary Source # 

Methods

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

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

toConstr :: AttackSummary -> Constr #

dataTypeOf :: AttackSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AttackSummary Source # 
Show AttackSummary Source # 
Generic AttackSummary Source # 

Associated Types

type Rep AttackSummary :: * -> * #

Hashable AttackSummary Source # 
FromJSON AttackSummary Source # 
NFData AttackSummary Source # 

Methods

rnf :: AttackSummary -> () #

type Rep AttackSummary Source # 
type Rep AttackSummary = D1 * (MetaData "AttackSummary" "Network.AWS.Shield.Types.Product" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) (C1 * (MetaCons "AttackSummary'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_asAttackVectors") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [AttackVectorDescription]))) (S1 * (MetaSel (Just Symbol "_asAttackId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_asStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) ((:*:) * (S1 * (MetaSel (Just Symbol "_asResourceARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_asEndTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))))))

attackSummary :: AttackSummary Source #

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

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

  • asAttackVectors - The list of attacks for a specified time period.
  • asAttackId - The unique identifier (ID) of the attack.
  • asStartTime - The start time of the attack, in Unix time in seconds. For more information see timestamp .
  • asResourceARN - The ARN (Amazon Resource Name) of the resource that was attacked.
  • asEndTime - The end time of the attack, in Unix time in seconds. For more information see timestamp .

asAttackVectors :: Lens' AttackSummary [AttackVectorDescription] Source #

The list of attacks for a specified time period.

asAttackId :: Lens' AttackSummary (Maybe Text) Source #

The unique identifier (ID) of the attack.

asStartTime :: Lens' AttackSummary (Maybe UTCTime) Source #

The start time of the attack, in Unix time in seconds. For more information see timestamp .

asResourceARN :: Lens' AttackSummary (Maybe Text) Source #

The ARN (Amazon Resource Name) of the resource that was attacked.

asEndTime :: Lens' AttackSummary (Maybe UTCTime) Source #

The end time of the attack, in Unix time in seconds. For more information see timestamp .

AttackVectorDescription

data AttackVectorDescription Source #

Describes the attack.

See: attackVectorDescription smart constructor.

Instances

Eq AttackVectorDescription Source # 
Data AttackVectorDescription Source # 

Methods

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

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

toConstr :: AttackVectorDescription -> Constr #

dataTypeOf :: AttackVectorDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AttackVectorDescription Source # 
Show AttackVectorDescription Source # 
Generic AttackVectorDescription Source # 
Hashable AttackVectorDescription Source # 
FromJSON AttackVectorDescription Source # 
NFData AttackVectorDescription Source # 

Methods

rnf :: AttackVectorDescription -> () #

type Rep AttackVectorDescription Source # 
type Rep AttackVectorDescription = D1 * (MetaData "AttackVectorDescription" "Network.AWS.Shield.Types.Product" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" True) (C1 * (MetaCons "AttackVectorDescription'" PrefixI True) (S1 * (MetaSel (Just Symbol "_avdVectorType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

attackVectorDescription Source #

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

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

  • avdVectorType - The attack type. Valid values: * UDP_TRAFFIC * UDP_FRAGMENT * GENERIC_UDP_REFLECTION * DNS_REFLECTION * NTP_REFLECTION * CHARGEN_REFLECTION * SSDP_REFLECTION * PORT_MAPPER * RIP_REFLECTION * SNMP_REFLECTION * MSSQL_REFLECTION * NET_BIOS_REFLECTION * SYN_FLOOD * ACK_FLOOD * REQUEST_FLOOD

avdVectorType :: Lens' AttackVectorDescription Text Source #

The attack type. Valid values: * UDP_TRAFFIC * UDP_FRAGMENT * GENERIC_UDP_REFLECTION * DNS_REFLECTION * NTP_REFLECTION * CHARGEN_REFLECTION * SSDP_REFLECTION * PORT_MAPPER * RIP_REFLECTION * SNMP_REFLECTION * MSSQL_REFLECTION * NET_BIOS_REFLECTION * SYN_FLOOD * ACK_FLOOD * REQUEST_FLOOD

Contributor

data Contributor Source #

A contributor to the attack and their contribution.

See: contributor smart constructor.

Instances

Eq Contributor Source # 
Data Contributor Source # 

Methods

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

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

toConstr :: Contributor -> Constr #

dataTypeOf :: Contributor -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Contributor Source # 
Show Contributor Source # 
Generic Contributor Source # 

Associated Types

type Rep Contributor :: * -> * #

Hashable Contributor Source # 
FromJSON Contributor Source # 
NFData Contributor Source # 

Methods

rnf :: Contributor -> () #

type Rep Contributor Source # 
type Rep Contributor = D1 * (MetaData "Contributor" "Network.AWS.Shield.Types.Product" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) (C1 * (MetaCons "Contributor'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) (S1 * (MetaSel (Just Symbol "_cName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

contributor :: Contributor Source #

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

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

  • cValue - The contribution of this contributor expressed in Protection units. For example 10,000 .
  • cName - The name of the contributor. This is dependent on the AttackPropertyIdentifier . For example, if the AttackPropertyIdentifier is SOURCE_COUNTRY , the Name could be United States .

cValue :: Lens' Contributor (Maybe Integer) Source #

The contribution of this contributor expressed in Protection units. For example 10,000 .

cName :: Lens' Contributor (Maybe Text) Source #

The name of the contributor. This is dependent on the AttackPropertyIdentifier . For example, if the AttackPropertyIdentifier is SOURCE_COUNTRY , the Name could be United States .

Mitigation

data Mitigation Source #

The mitigation applied to a DDoS attack.

See: mitigation smart constructor.

Instances

Eq Mitigation Source # 
Data Mitigation Source # 

Methods

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

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

toConstr :: Mitigation -> Constr #

dataTypeOf :: Mitigation -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Mitigation Source # 
Show Mitigation Source # 
Generic Mitigation Source # 

Associated Types

type Rep Mitigation :: * -> * #

Hashable Mitigation Source # 
FromJSON Mitigation Source # 
NFData Mitigation Source # 

Methods

rnf :: Mitigation -> () #

type Rep Mitigation Source # 
type Rep Mitigation = D1 * (MetaData "Mitigation" "Network.AWS.Shield.Types.Product" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" True) (C1 * (MetaCons "Mitigation'" PrefixI True) (S1 * (MetaSel (Just Symbol "_mMitigationName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))))

mitigation :: Mitigation Source #

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

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

mMitigationName :: Lens' Mitigation (Maybe Text) Source #

The name of the mitigation taken for this attack.

Protection

data Protection Source #

An object that represents a resource that is under DDoS protection.

See: protection smart constructor.

Instances

Eq Protection Source # 
Data Protection Source # 

Methods

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

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

toConstr :: Protection -> Constr #

dataTypeOf :: Protection -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Protection Source # 
Show Protection Source # 
Generic Protection Source # 

Associated Types

type Rep Protection :: * -> * #

Hashable Protection Source # 
FromJSON Protection Source # 
NFData Protection Source # 

Methods

rnf :: Protection -> () #

type Rep Protection Source # 
type Rep Protection = D1 * (MetaData "Protection" "Network.AWS.Shield.Types.Product" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) (C1 * (MetaCons "Protection'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pResourceARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_pName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_pId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

protection :: Protection Source #

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

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

  • pResourceARN - The ARN (Amazon Resource Name) of the AWS resource that is protected.
  • pName - The friendly name of the protection. For example, My CloudFront distributions .
  • pId - The unique identifier (ID) of the protection.

pResourceARN :: Lens' Protection (Maybe Text) Source #

The ARN (Amazon Resource Name) of the AWS resource that is protected.

pName :: Lens' Protection (Maybe Text) Source #

The friendly name of the protection. For example, My CloudFront distributions .

pId :: Lens' Protection (Maybe Text) Source #

The unique identifier (ID) of the protection.

SubResourceSummary

data SubResourceSummary Source #

The attack information for the specified SubResource.

See: subResourceSummary smart constructor.

Instances

Eq SubResourceSummary Source # 
Data SubResourceSummary Source # 

Methods

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

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

toConstr :: SubResourceSummary -> Constr #

dataTypeOf :: SubResourceSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SubResourceSummary Source # 
Show SubResourceSummary Source # 
Generic SubResourceSummary Source # 
Hashable SubResourceSummary Source # 
FromJSON SubResourceSummary Source # 
NFData SubResourceSummary Source # 

Methods

rnf :: SubResourceSummary -> () #

type Rep SubResourceSummary Source # 
type Rep SubResourceSummary = D1 * (MetaData "SubResourceSummary" "Network.AWS.Shield.Types.Product" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) (C1 * (MetaCons "SubResourceSummary'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_srsCounters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [SummarizedCounter]))) (S1 * (MetaSel (Just Symbol "_srsAttackVectors") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [SummarizedAttackVector])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_srsId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_srsType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SubResourceType))))))

subResourceSummary :: SubResourceSummary Source #

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

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

  • srsCounters - The counters that describe the details of the attack.
  • srsAttackVectors - The list of attack types and associated counters.
  • srsId - The unique identifier (ID) of the SubResource .
  • srsType - The SubResource type.

srsCounters :: Lens' SubResourceSummary [SummarizedCounter] Source #

The counters that describe the details of the attack.

srsAttackVectors :: Lens' SubResourceSummary [SummarizedAttackVector] Source #

The list of attack types and associated counters.

srsId :: Lens' SubResourceSummary (Maybe Text) Source #

The unique identifier (ID) of the SubResource .

Subscription

data Subscription Source #

Information about the AWS Shield Advanced subscription for an account.

See: subscription smart constructor.

Instances

Eq Subscription Source # 
Data Subscription Source # 

Methods

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

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

toConstr :: Subscription -> Constr #

dataTypeOf :: Subscription -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Subscription Source # 
Show Subscription Source # 
Generic Subscription Source # 

Associated Types

type Rep Subscription :: * -> * #

Hashable Subscription Source # 
FromJSON Subscription Source # 
NFData Subscription Source # 

Methods

rnf :: Subscription -> () #

type Rep Subscription Source # 
type Rep Subscription = D1 * (MetaData "Subscription" "Network.AWS.Shield.Types.Product" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) (C1 * (MetaCons "Subscription'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_sTimeCommitmentInSeconds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_sStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))))

subscription :: Subscription Source #

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

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

  • sTimeCommitmentInSeconds - The length, in seconds, of the AWS Shield Advanced subscription for the account.
  • sStartTime - The start time of the subscription, in Unix time in seconds. For more information see timestamp .

sTimeCommitmentInSeconds :: Lens' Subscription (Maybe Natural) Source #

The length, in seconds, of the AWS Shield Advanced subscription for the account.

sStartTime :: Lens' Subscription (Maybe UTCTime) Source #

The start time of the subscription, in Unix time in seconds. For more information see timestamp .

SummarizedAttackVector

data SummarizedAttackVector Source #

A summary of information about the attack.

See: summarizedAttackVector smart constructor.

Instances

Eq SummarizedAttackVector Source # 
Data SummarizedAttackVector Source # 

Methods

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

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

toConstr :: SummarizedAttackVector -> Constr #

dataTypeOf :: SummarizedAttackVector -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SummarizedAttackVector Source # 
Show SummarizedAttackVector Source # 
Generic SummarizedAttackVector Source # 
Hashable SummarizedAttackVector Source # 
FromJSON SummarizedAttackVector Source # 
NFData SummarizedAttackVector Source # 

Methods

rnf :: SummarizedAttackVector -> () #

type Rep SummarizedAttackVector Source # 
type Rep SummarizedAttackVector = D1 * (MetaData "SummarizedAttackVector" "Network.AWS.Shield.Types.Product" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) (C1 * (MetaCons "SummarizedAttackVector'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_savVectorCounters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [SummarizedCounter]))) (S1 * (MetaSel (Just Symbol "_savVectorType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

summarizedAttackVector Source #

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

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

  • savVectorCounters - The list of counters that describe the details of the attack.
  • savVectorType - The attack type, for example, SNMP reflection or SYN flood.

savVectorCounters :: Lens' SummarizedAttackVector [SummarizedCounter] Source #

The list of counters that describe the details of the attack.

savVectorType :: Lens' SummarizedAttackVector Text Source #

The attack type, for example, SNMP reflection or SYN flood.

SummarizedCounter

data SummarizedCounter Source #

The counter that describes a DDoS attack.

See: summarizedCounter smart constructor.

Instances

Eq SummarizedCounter Source # 
Data SummarizedCounter Source # 

Methods

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

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

toConstr :: SummarizedCounter -> Constr #

dataTypeOf :: SummarizedCounter -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SummarizedCounter Source # 
Show SummarizedCounter Source # 
Generic SummarizedCounter Source # 
Hashable SummarizedCounter Source # 
FromJSON SummarizedCounter Source # 
NFData SummarizedCounter Source # 

Methods

rnf :: SummarizedCounter -> () #

type Rep SummarizedCounter Source # 

summarizedCounter :: SummarizedCounter Source #

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

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

  • scMax - The maximum value of the counter for a specified time period.
  • scAverage - The average value of the counter for a specified time period.
  • scN - The number of counters for a specified time period.
  • scName - The counter name.
  • scSum - The total of counter values for a specified time period.
  • scUnit - The unit of the counters.

scMax :: Lens' SummarizedCounter (Maybe Double) Source #

The maximum value of the counter for a specified time period.

scAverage :: Lens' SummarizedCounter (Maybe Double) Source #

The average value of the counter for a specified time period.

scN :: Lens' SummarizedCounter (Maybe Int) Source #

The number of counters for a specified time period.

scSum :: Lens' SummarizedCounter (Maybe Double) Source #

The total of counter values for a specified time period.

scUnit :: Lens' SummarizedCounter (Maybe Text) Source #

The unit of the counters.

TimeRange

data TimeRange Source #

The time range.

See: timeRange smart constructor.

Instances

Eq TimeRange Source # 
Data TimeRange Source # 

Methods

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

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

toConstr :: TimeRange -> Constr #

dataTypeOf :: TimeRange -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TimeRange Source # 
Show TimeRange Source # 
Generic TimeRange Source # 

Associated Types

type Rep TimeRange :: * -> * #

Hashable TimeRange Source # 
ToJSON TimeRange Source # 
NFData TimeRange Source # 

Methods

rnf :: TimeRange -> () #

type Rep TimeRange Source # 
type Rep TimeRange = D1 * (MetaData "TimeRange" "Network.AWS.Shield.Types.Product" "amazonka-shield-1.6.0-2xi7D1IHnHkEfNzXOp5G0j" False) (C1 * (MetaCons "TimeRange'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_trFromInclusive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_trToExclusive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))))

timeRange :: TimeRange Source #

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

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

trFromInclusive :: Lens' TimeRange (Maybe UTCTime) Source #

The start time, in Unix time in seconds. For more information see timestamp .

trToExclusive :: Lens' TimeRange (Maybe UTCTime) Source #

The end time, in Unix time in seconds. For more information see timestamp .