amazonka-waf-regional-1.5.0: Amazon WAF Regional SDK.

Copyright(c) 2013-2017 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.WAFRegional

Contents

Description

This is the AWS WAF Regional API Reference for using AWS WAF with Elastic Load Balancing (ELB) Application Load Balancers. The AWS WAF actions and data types listed in the reference are available for protecting Application Load Balancers. You can use these actions and data types by means of the endpoints listed in AWS Regions and Endpoints . This guide is for developers who need detailed information about the AWS WAF API actions, data types, and errors. For detailed information about AWS WAF features and an overview of how to use the AWS WAF API, see the AWS WAF Developer Guide .

Synopsis

Service Configuration

wAFRegional :: Service Source #

API version 2016-11-28 of the Amazon WAF Regional 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 WAFRegional.

WAFInvalidAccountException

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

The operation failed because you tried to create, update, or delete an object by using an invalid account identifier.

WAFReferencedItemException

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

The operation failed because you tried to delete an object that is still in use. For example:

  • You tried to delete a ByteMatchSet that is still referenced by a Rule .
  • You tried to delete a Rule that is still referenced by a WebACL .

WAFInvalidRegexPatternException

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

The regular expression (regex) you specified in RegexPatternString is invalid.

WAFInvalidOperationException

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

The operation failed because there was nothing to do. For example:

  • You tried to remove a Rule from a WebACL , but the Rule isn't in the specified WebACL .
  • You tried to remove an IP address from an IPSet , but the IP address isn't in the specified IPSet .
  • You tried to remove a ByteMatchTuple from a ByteMatchSet , but the ByteMatchTuple isn't in the specified WebACL .
  • You tried to add a Rule to a WebACL , but the Rule already exists in the specified WebACL .
  • You tried to add an IP address to an IPSet , but the IP address already exists in the specified IPSet .
  • You tried to add a ByteMatchTuple to a ByteMatchSet , but the ByteMatchTuple already exists in the specified WebACL .

WAFNonexistentItemException

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

The operation failed because the referenced object doesn't exist.

WAFInvalidParameterException

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

The operation failed because AWS WAF didn't recognize a parameter in the request. For example:

  • You specified an invalid parameter name.
  • You specified an invalid value.
  • You tried to update an object (ByteMatchSet , IPSet , Rule , or WebACL ) using an action other than INSERT or DELETE .
  • You tried to create a WebACL with a DefaultAction Type other than ALLOW , BLOCK , or COUNT .
  • You tried to create a RateBasedRule with a RateKey value other than IP .
  • You tried to update a WebACL with a WafAction Type other than ALLOW , BLOCK , or COUNT .
  • You tried to update a ByteMatchSet with a FieldToMatch Type other than HEADER, METHOD, QUERY_STRING, URI, or BODY.
  • You tried to update a ByteMatchSet with a Field of HEADER but no value for Data .
  • Your request references an ARN that is malformed, or corresponds to a resource with which a web ACL cannot be associated.

WAFLimitsExceededException

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

The operation exceeds a resource limit, for example, the maximum number of WebACL objects that you can create for an AWS account. For more information, see Limits in the AWS WAF Developer Guide .

WAFStaleDataException

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

The operation failed because you tried to create, update, or delete an object by using a change token that has already been used.

WAFInternalErrorException

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

The operation failed because of a system problem, even though the request was valid. Retry your request.

WAFNonexistentContainerException

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

The operation failed because you tried to add an object to or delete an object from another object that doesn't exist. For example:

  • You tried to add a Rule to or delete a Rule from a WebACL that doesn't exist.
  • You tried to add a ByteMatchSet to or delete a ByteMatchSet from a Rule that doesn't exist.
  • You tried to add an IP address to or delete an IP address from an IPSet that doesn't exist.
  • You tried to add a ByteMatchTuple to or delete a ByteMatchTuple from a ByteMatchSet that doesn't exist.

WAFUnavailableEntityException

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

The operation failed because the entity referenced is temporarily unavailable. Retry your request.

WAFDisallowedNameException

WAFNonEmptyEntityException

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

The operation failed because you tried to delete an object that isn't empty. For example:

  • You tried to delete a WebACL that still contains one or more Rule objects.
  • You tried to delete a Rule that still contains one or more ByteMatchSet objects or other predicates.
  • You tried to delete a ByteMatchSet that contains one or more ByteMatchTuple objects.
  • You tried to delete an IPSet that references one or more IP addresses.

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.

ListRateBasedRules

GetSizeConstraintSet

DeleteRateBasedRule

UpdateRateBasedRule

UpdateRule

DeleteRule

CreateIPSet

GetChangeTokenStatus

DeleteWebACL

UpdateWebACL

ListWebACLs

ListRules

CreateRule

CreateWebACL

GetGeoMatchSet

ListByteMatchSets

ListGeoMatchSets

DeleteRegexMatchSet

UpdateRegexMatchSet

GetIPSet

GetWebACL

GetRule

DeleteXSSMatchSet

UpdateXSSMatchSet

ListXSSMatchSets

CreateGeoMatchSet

GetChangeToken

ListSizeConstraintSets

ListResourcesForWebACL

GetSampledRequests

GetSqlInjectionMatchSet

GetWebACLForResource

DisassociateWebACL

CreateSqlInjectionMatchSet

GetXSSMatchSet

CreateByteMatchSet

UpdateByteMatchSet

DeleteByteMatchSet

GetRateBasedRuleManagedKeys

AssociateWebACL

GetRegexMatchSet

DeleteIPSet

UpdateIPSet

ListIPSets

ListRegexMatchSets

CreateXSSMatchSet

DeleteGeoMatchSet

UpdateGeoMatchSet

GetByteMatchSet

CreateRegexMatchSet

GetRateBasedRule

CreateRegexPatternSet

DeleteSizeConstraintSet

UpdateSizeConstraintSet

DeleteRegexPatternSet

UpdateRegexPatternSet

CreateSizeConstraintSet

ListRegexPatternSets

ListSqlInjectionMatchSets

GetRegexPatternSet

CreateRateBasedRule

DeleteSqlInjectionMatchSet

UpdateSqlInjectionMatchSet

Types

ChangeAction

data ChangeAction Source #

Constructors

Delete 
Insert 

Instances

Bounded ChangeAction Source # 
Enum ChangeAction Source # 
Eq ChangeAction Source # 
Data ChangeAction Source # 

Methods

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

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

toConstr :: ChangeAction -> Constr #

dataTypeOf :: ChangeAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ChangeAction Source # 
Read ChangeAction Source # 
Show ChangeAction Source # 
Generic ChangeAction Source # 

Associated Types

type Rep ChangeAction :: * -> * #

Hashable ChangeAction Source # 
ToJSON ChangeAction Source # 
NFData ChangeAction Source # 

Methods

rnf :: ChangeAction -> () #

ToQuery ChangeAction Source # 
ToHeader ChangeAction Source # 
ToByteString ChangeAction Source # 
FromText ChangeAction Source # 
ToText ChangeAction Source # 

Methods

toText :: ChangeAction -> Text #

type Rep ChangeAction Source # 
type Rep ChangeAction = D1 (MetaData "ChangeAction" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) ((:+:) (C1 (MetaCons "Delete" PrefixI False) U1) (C1 (MetaCons "Insert" PrefixI False) U1))

ChangeTokenStatus

data ChangeTokenStatus Source #

Constructors

Insync 
Pending 
Provisioned 

Instances

Bounded ChangeTokenStatus Source # 
Enum ChangeTokenStatus Source # 
Eq ChangeTokenStatus Source # 
Data ChangeTokenStatus Source # 

Methods

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

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

toConstr :: ChangeTokenStatus -> Constr #

dataTypeOf :: ChangeTokenStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ChangeTokenStatus -> () #

ToQuery ChangeTokenStatus Source # 
ToHeader ChangeTokenStatus Source # 
ToByteString ChangeTokenStatus Source # 
FromText ChangeTokenStatus Source # 
ToText ChangeTokenStatus Source # 
type Rep ChangeTokenStatus Source # 
type Rep ChangeTokenStatus = D1 (MetaData "ChangeTokenStatus" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) ((:+:) (C1 (MetaCons "Insync" PrefixI False) U1) ((:+:) (C1 (MetaCons "Pending" PrefixI False) U1) (C1 (MetaCons "Provisioned" PrefixI False) U1)))

ComparisonOperator

data ComparisonOperator Source #

Constructors

EQ' 
GE 
GT' 
LE 
LT' 
NE 

Instances

Bounded ComparisonOperator Source # 
Enum ComparisonOperator Source # 
Eq ComparisonOperator Source # 
Data ComparisonOperator Source # 

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 # 
Read ComparisonOperator Source # 
Show ComparisonOperator Source # 
Generic ComparisonOperator Source # 
Hashable ComparisonOperator Source # 
FromJSON ComparisonOperator Source # 
ToJSON ComparisonOperator Source # 
NFData ComparisonOperator Source # 

Methods

rnf :: ComparisonOperator -> () #

ToQuery ComparisonOperator Source # 
ToHeader ComparisonOperator Source # 
ToByteString ComparisonOperator Source # 
FromText ComparisonOperator Source # 
ToText ComparisonOperator Source # 
type Rep ComparisonOperator Source # 
type Rep ComparisonOperator = D1 (MetaData "ComparisonOperator" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) ((:+:) ((:+:) (C1 (MetaCons "EQ'" PrefixI False) U1) ((:+:) (C1 (MetaCons "GE" PrefixI False) U1) (C1 (MetaCons "GT'" PrefixI False) U1))) ((:+:) (C1 (MetaCons "LE" PrefixI False) U1) ((:+:) (C1 (MetaCons "LT'" PrefixI False) U1) (C1 (MetaCons "NE" PrefixI False) U1))))

GeoMatchConstraintType

data GeoMatchConstraintType Source #

Constructors

Country 

Instances

Bounded GeoMatchConstraintType Source # 
Enum GeoMatchConstraintType Source # 
Eq GeoMatchConstraintType Source # 
Data GeoMatchConstraintType Source # 

Methods

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

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

toConstr :: GeoMatchConstraintType -> Constr #

dataTypeOf :: GeoMatchConstraintType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GeoMatchConstraintType Source # 
Read GeoMatchConstraintType Source # 
Show GeoMatchConstraintType Source # 
Generic GeoMatchConstraintType Source # 
Hashable GeoMatchConstraintType Source # 
FromJSON GeoMatchConstraintType Source # 
ToJSON GeoMatchConstraintType Source # 
NFData GeoMatchConstraintType Source # 

Methods

rnf :: GeoMatchConstraintType -> () #

ToQuery GeoMatchConstraintType Source # 
ToHeader GeoMatchConstraintType Source # 
ToByteString GeoMatchConstraintType Source # 
FromText GeoMatchConstraintType Source # 
ToText GeoMatchConstraintType Source # 
type Rep GeoMatchConstraintType Source # 
type Rep GeoMatchConstraintType = D1 (MetaData "GeoMatchConstraintType" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "Country" PrefixI False) U1)

GeoMatchConstraintValue

data GeoMatchConstraintValue Source #

Constructors

GMCVAD 
GMCVAE 
GMCVAF 
GMCVAG 
GMCVAI 
GMCVAL 
GMCVAM 
GMCVAO 
GMCVAQ 
GMCVAR 
GMCVAS 
GMCVAT 
GMCVAU 
GMCVAW 
GMCVAX 
GMCVAZ 
GMCVBA 
GMCVBB 
GMCVBD 
GMCVBE 
GMCVBF 
GMCVBG 
GMCVBH 
GMCVBI 
GMCVBJ 
GMCVBL 
GMCVBM 
GMCVBN 
GMCVBO 
GMCVBQ 
GMCVBR 
GMCVBS 
GMCVBT 
GMCVBV 
GMCVBW 
GMCVBY 
GMCVBZ 
GMCVCA 
GMCVCC 
GMCVCD 
GMCVCF 
GMCVCG 
GMCVCH 
GMCVCI 
GMCVCK 
GMCVCL 
GMCVCM 
GMCVCN 
GMCVCO 
GMCVCR 
GMCVCU 
GMCVCV 
GMCVCW 
GMCVCX 
GMCVCY 
GMCVCZ 
GMCVDE 
GMCVDJ 
GMCVDK 
GMCVDM 
GMCVDO 
GMCVDZ 
GMCVEC 
GMCVEE 
GMCVEG 
GMCVEH 
GMCVER 
GMCVES 
GMCVET 
GMCVFI 
GMCVFJ 
GMCVFK 
GMCVFM 
GMCVFO 
GMCVFR 
GMCVGA 
GMCVGB 
GMCVGD 
GMCVGE 
GMCVGF 
GMCVGG 
GMCVGH 
GMCVGI 
GMCVGL 
GMCVGM 
GMCVGN 
GMCVGP 
GMCVGQ 
GMCVGR 
GMCVGS 
GMCVGT' 
GMCVGU 
GMCVGW 
GMCVGY 
GMCVHK 
GMCVHM 
GMCVHN 
GMCVHR 
GMCVHT 
GMCVHU 
GMCVIE 
GMCVIL 
GMCVIM 
GMCVIN 
GMCVIO 
GMCVIQ 
GMCVIR 
GMCVIS 
GMCVIT 
GMCVId 
GMCVJE 
GMCVJM 
GMCVJO 
GMCVJP 
GMCVKE 
GMCVKG 
GMCVKH 
GMCVKI 
GMCVKM 
GMCVKN 
GMCVKP 
GMCVKR 
GMCVKW 
GMCVKY 
GMCVKZ 
GMCVLA 
GMCVLB 
GMCVLC 
GMCVLI 
GMCVLK 
GMCVLR 
GMCVLS 
GMCVLT' 
GMCVLU 
GMCVLV 
GMCVLY 
GMCVMA 
GMCVMC 
GMCVMD 
GMCVME 
GMCVMF 
GMCVMG 
GMCVMH 
GMCVMK 
GMCVML 
GMCVMM 
GMCVMN 
GMCVMO 
GMCVMP 
GMCVMQ 
GMCVMR 
GMCVMS 
GMCVMT 
GMCVMU 
GMCVMV 
GMCVMW 
GMCVMX 
GMCVMY 
GMCVMZ 
GMCVNA 
GMCVNC 
GMCVNE 
GMCVNF 
GMCVNG 
GMCVNI 
GMCVNL 
GMCVNO 
GMCVNP 
GMCVNR 
GMCVNU 
GMCVNZ 
GMCVOM 
GMCVPA 
GMCVPE 
GMCVPF 
GMCVPG 
GMCVPH 
GMCVPK 
GMCVPL 
GMCVPM 
GMCVPN 
GMCVPR 
GMCVPS 
GMCVPT 
GMCVPW 
GMCVPY 
GMCVQA 
GMCVRE 
GMCVRO 
GMCVRS 
GMCVRU 
GMCVRW 
GMCVSA 
GMCVSB 
GMCVSC 
GMCVSD 
GMCVSE 
GMCVSG 
GMCVSH 
GMCVSI 
GMCVSJ 
GMCVSK 
GMCVSL 
GMCVSM 
GMCVSN 
GMCVSO 
GMCVSR 
GMCVSS 
GMCVST 
GMCVSV 
GMCVSX 
GMCVSY 
GMCVSZ 
GMCVTC 
GMCVTD 
GMCVTF 
GMCVTG 
GMCVTH 
GMCVTJ 
GMCVTK 
GMCVTL 
GMCVTM 
GMCVTN 
GMCVTO 
GMCVTR 
GMCVTT 
GMCVTV 
GMCVTW 
GMCVTZ 
GMCVUA 
GMCVUG 
GMCVUM 
GMCVUS 
GMCVUY 
GMCVUZ 
GMCVVA 
GMCVVC 
GMCVVE 
GMCVVG 
GMCVVI 
GMCVVN 
GMCVVU 
GMCVWF 
GMCVWS 
GMCVYE 
GMCVYT 
GMCVZA 
GMCVZM 
GMCVZW 

Instances

Bounded GeoMatchConstraintValue Source # 
Enum GeoMatchConstraintValue Source # 
Eq GeoMatchConstraintValue Source # 
Data GeoMatchConstraintValue Source # 

Methods

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

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

toConstr :: GeoMatchConstraintValue -> Constr #

dataTypeOf :: GeoMatchConstraintValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GeoMatchConstraintValue Source # 
Read GeoMatchConstraintValue Source # 
Show GeoMatchConstraintValue Source # 
Generic GeoMatchConstraintValue Source # 
Hashable GeoMatchConstraintValue Source # 
FromJSON GeoMatchConstraintValue Source # 
ToJSON GeoMatchConstraintValue Source # 
NFData GeoMatchConstraintValue Source # 

Methods

rnf :: GeoMatchConstraintValue -> () #

ToQuery GeoMatchConstraintValue Source # 
ToHeader GeoMatchConstraintValue Source # 
ToByteString GeoMatchConstraintValue Source # 
FromText GeoMatchConstraintValue Source # 
ToText GeoMatchConstraintValue Source # 
type Rep GeoMatchConstraintValue Source # 
type Rep GeoMatchConstraintValue = D1 (MetaData "GeoMatchConstraintValue" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVAD" PrefixI False) U1) ((:+:) (C1 (MetaCons "GMCVAE" PrefixI False) U1) (C1 (MetaCons "GMCVAF" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVAG" PrefixI False) U1) (C1 (MetaCons "GMCVAI" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVAL" PrefixI False) U1) (C1 (MetaCons "GMCVAM" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVAO" PrefixI False) U1) (C1 (MetaCons "GMCVAQ" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVAR" PrefixI False) U1) (C1 (MetaCons "GMCVAS" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVAT" PrefixI False) U1) (C1 (MetaCons "GMCVAU" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVAW" PrefixI False) U1) (C1 (MetaCons "GMCVAX" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVAZ" PrefixI False) U1) (C1 (MetaCons "GMCVBA" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVBB" PrefixI False) U1) (C1 (MetaCons "GMCVBD" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVBE" PrefixI False) U1) (C1 (MetaCons "GMCVBF" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVBG" PrefixI False) U1) (C1 (MetaCons "GMCVBH" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVBI" PrefixI False) U1) (C1 (MetaCons "GMCVBJ" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVBL" PrefixI False) U1) (C1 (MetaCons "GMCVBM" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVBN" PrefixI False) U1) (C1 (MetaCons "GMCVBO" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVBQ" PrefixI False) U1) (C1 (MetaCons "GMCVBR" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVBS" PrefixI False) U1) ((:+:) (C1 (MetaCons "GMCVBT" PrefixI False) U1) (C1 (MetaCons "GMCVBV" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVBW" PrefixI False) U1) (C1 (MetaCons "GMCVBY" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVBZ" PrefixI False) U1) (C1 (MetaCons "GMCVCA" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVCC" PrefixI False) U1) (C1 (MetaCons "GMCVCD" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVCF" PrefixI False) U1) (C1 (MetaCons "GMCVCG" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVCH" PrefixI False) U1) (C1 (MetaCons "GMCVCI" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVCK" PrefixI False) U1) (C1 (MetaCons "GMCVCL" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVCM" PrefixI False) U1) (C1 (MetaCons "GMCVCN" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVCO" PrefixI False) U1) (C1 (MetaCons "GMCVCR" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVCU" PrefixI False) U1) (C1 (MetaCons "GMCVCV" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVCW" PrefixI False) U1) (C1 (MetaCons "GMCVCX" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVCY" PrefixI False) U1) (C1 (MetaCons "GMCVCZ" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVDE" PrefixI False) U1) (C1 (MetaCons "GMCVDJ" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVDK" PrefixI False) U1) (C1 (MetaCons "GMCVDM" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVDO" PrefixI False) U1) (C1 (MetaCons "GMCVDZ" PrefixI False) U1))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVEC" PrefixI False) U1) ((:+:) (C1 (MetaCons "GMCVEE" PrefixI False) U1) (C1 (MetaCons "GMCVEG" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVEH" PrefixI False) U1) (C1 (MetaCons "GMCVER" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVES" PrefixI False) U1) (C1 (MetaCons "GMCVET" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVFI" PrefixI False) U1) (C1 (MetaCons "GMCVFJ" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVFK" PrefixI False) U1) (C1 (MetaCons "GMCVFM" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVFO" PrefixI False) U1) (C1 (MetaCons "GMCVFR" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVGA" PrefixI False) U1) (C1 (MetaCons "GMCVGB" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVGD" PrefixI False) U1) (C1 (MetaCons "GMCVGE" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVGF" PrefixI False) U1) (C1 (MetaCons "GMCVGG" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVGH" PrefixI False) U1) (C1 (MetaCons "GMCVGI" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVGL" PrefixI False) U1) (C1 (MetaCons "GMCVGM" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVGN" PrefixI False) U1) (C1 (MetaCons "GMCVGP" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVGQ" PrefixI False) U1) (C1 (MetaCons "GMCVGR" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVGS" PrefixI False) U1) (C1 (MetaCons "GMCVGT'" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVGU" PrefixI False) U1) (C1 (MetaCons "GMCVGW" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVGY" PrefixI False) U1) ((:+:) (C1 (MetaCons "GMCVHK" PrefixI False) U1) (C1 (MetaCons "GMCVHM" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVHN" PrefixI False) U1) (C1 (MetaCons "GMCVHR" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVHT" PrefixI False) U1) (C1 (MetaCons "GMCVHU" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVIE" PrefixI False) U1) (C1 (MetaCons "GMCVIL" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVIM" PrefixI False) U1) (C1 (MetaCons "GMCVIN" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVIO" PrefixI False) U1) (C1 (MetaCons "GMCVIQ" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVIR" PrefixI False) U1) (C1 (MetaCons "GMCVIS" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVIT" PrefixI False) U1) (C1 (MetaCons "GMCVId" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVJE" PrefixI False) U1) (C1 (MetaCons "GMCVJM" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVJO" PrefixI False) U1) (C1 (MetaCons "GMCVJP" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVKE" PrefixI False) U1) (C1 (MetaCons "GMCVKG" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVKH" PrefixI False) U1) (C1 (MetaCons "GMCVKI" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVKM" PrefixI False) U1) (C1 (MetaCons "GMCVKN" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVKP" PrefixI False) U1) (C1 (MetaCons "GMCVKR" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVKW" PrefixI False) U1) (C1 (MetaCons "GMCVKY" PrefixI False) U1)))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVKZ" PrefixI False) U1) ((:+:) (C1 (MetaCons "GMCVLA" PrefixI False) U1) (C1 (MetaCons "GMCVLB" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVLC" PrefixI False) U1) (C1 (MetaCons "GMCVLI" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVLK" PrefixI False) U1) (C1 (MetaCons "GMCVLR" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVLS" PrefixI False) U1) (C1 (MetaCons "GMCVLT'" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVLU" PrefixI False) U1) (C1 (MetaCons "GMCVLV" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVLY" PrefixI False) U1) (C1 (MetaCons "GMCVMA" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVMC" PrefixI False) U1) (C1 (MetaCons "GMCVMD" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVME" PrefixI False) U1) (C1 (MetaCons "GMCVMF" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVMG" PrefixI False) U1) (C1 (MetaCons "GMCVMH" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVMK" PrefixI False) U1) (C1 (MetaCons "GMCVML" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVMM" PrefixI False) U1) (C1 (MetaCons "GMCVMN" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVMO" PrefixI False) U1) (C1 (MetaCons "GMCVMP" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVMQ" PrefixI False) U1) (C1 (MetaCons "GMCVMR" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVMS" PrefixI False) U1) (C1 (MetaCons "GMCVMT" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVMU" PrefixI False) U1) (C1 (MetaCons "GMCVMV" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVMW" PrefixI False) U1) ((:+:) (C1 (MetaCons "GMCVMX" PrefixI False) U1) (C1 (MetaCons "GMCVMY" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVMZ" PrefixI False) U1) (C1 (MetaCons "GMCVNA" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVNC" PrefixI False) U1) (C1 (MetaCons "GMCVNE" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVNF" PrefixI False) U1) (C1 (MetaCons "GMCVNG" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVNI" PrefixI False) U1) (C1 (MetaCons "GMCVNL" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVNO" PrefixI False) U1) (C1 (MetaCons "GMCVNP" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVNR" PrefixI False) U1) (C1 (MetaCons "GMCVNU" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVNZ" PrefixI False) U1) (C1 (MetaCons "GMCVOM" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVPA" PrefixI False) U1) (C1 (MetaCons "GMCVPE" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVPF" PrefixI False) U1) (C1 (MetaCons "GMCVPG" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVPH" PrefixI False) U1) (C1 (MetaCons "GMCVPK" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVPL" PrefixI False) U1) (C1 (MetaCons "GMCVPM" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVPN" PrefixI False) U1) (C1 (MetaCons "GMCVPR" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVPS" PrefixI False) U1) (C1 (MetaCons "GMCVPT" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVPW" PrefixI False) U1) (C1 (MetaCons "GMCVPY" PrefixI False) U1))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVQA" PrefixI False) U1) ((:+:) (C1 (MetaCons "GMCVRE" PrefixI False) U1) (C1 (MetaCons "GMCVRO" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVRS" PrefixI False) U1) (C1 (MetaCons "GMCVRU" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVRW" PrefixI False) U1) (C1 (MetaCons "GMCVSA" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVSB" PrefixI False) U1) (C1 (MetaCons "GMCVSC" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVSD" PrefixI False) U1) (C1 (MetaCons "GMCVSE" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVSG" PrefixI False) U1) (C1 (MetaCons "GMCVSH" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVSI" PrefixI False) U1) (C1 (MetaCons "GMCVSJ" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVSK" PrefixI False) U1) (C1 (MetaCons "GMCVSL" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVSM" PrefixI False) U1) (C1 (MetaCons "GMCVSN" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVSO" PrefixI False) U1) (C1 (MetaCons "GMCVSR" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVSS" PrefixI False) U1) (C1 (MetaCons "GMCVST" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVSV" PrefixI False) U1) (C1 (MetaCons "GMCVSX" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVSY" PrefixI False) U1) (C1 (MetaCons "GMCVSZ" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVTC" PrefixI False) U1) (C1 (MetaCons "GMCVTD" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVTF" PrefixI False) U1) (C1 (MetaCons "GMCVTG" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVTH" PrefixI False) U1) (C1 (MetaCons "GMCVTJ" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVTK" PrefixI False) U1) (C1 (MetaCons "GMCVTL" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVTM" PrefixI False) U1) (C1 (MetaCons "GMCVTN" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVTO" PrefixI False) U1) (C1 (MetaCons "GMCVTR" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVTT" PrefixI False) U1) (C1 (MetaCons "GMCVTV" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVTW" PrefixI False) U1) (C1 (MetaCons "GMCVTZ" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVUA" PrefixI False) U1) (C1 (MetaCons "GMCVUG" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVUM" PrefixI False) U1) (C1 (MetaCons "GMCVUS" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVUY" PrefixI False) U1) (C1 (MetaCons "GMCVUZ" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVVA" PrefixI False) U1) (C1 (MetaCons "GMCVVC" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVVE" PrefixI False) U1) (C1 (MetaCons "GMCVVG" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVVI" PrefixI False) U1) (C1 (MetaCons "GMCVVN" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GMCVVU" PrefixI False) U1) (C1 (MetaCons "GMCVWF" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVWS" PrefixI False) U1) (C1 (MetaCons "GMCVYE" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "GMCVYT" PrefixI False) U1) (C1 (MetaCons "GMCVZA" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GMCVZM" PrefixI False) U1) (C1 (MetaCons "GMCVZW" PrefixI False) U1)))))))))

IPSetDescriptorType

data IPSetDescriptorType Source #

Constructors

IPV4 
IPV6 

Instances

Bounded IPSetDescriptorType Source # 
Enum IPSetDescriptorType Source # 
Eq IPSetDescriptorType Source # 
Data IPSetDescriptorType Source # 

Methods

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

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

toConstr :: IPSetDescriptorType -> Constr #

dataTypeOf :: IPSetDescriptorType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IPSetDescriptorType Source # 
Read IPSetDescriptorType Source # 
Show IPSetDescriptorType Source # 
Generic IPSetDescriptorType Source # 
Hashable IPSetDescriptorType Source # 
FromJSON IPSetDescriptorType Source # 
ToJSON IPSetDescriptorType Source # 
NFData IPSetDescriptorType Source # 

Methods

rnf :: IPSetDescriptorType -> () #

ToQuery IPSetDescriptorType Source # 
ToHeader IPSetDescriptorType Source # 
ToByteString IPSetDescriptorType Source # 
FromText IPSetDescriptorType Source # 
ToText IPSetDescriptorType Source # 
type Rep IPSetDescriptorType Source # 
type Rep IPSetDescriptorType = D1 (MetaData "IPSetDescriptorType" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) ((:+:) (C1 (MetaCons "IPV4" PrefixI False) U1) (C1 (MetaCons "IPV6" PrefixI False) U1))

MatchFieldType

data MatchFieldType Source #

Constructors

Body 
Header 
Method 
QueryString 
URI 

Instances

Bounded MatchFieldType Source # 
Enum MatchFieldType Source # 
Eq MatchFieldType Source # 
Data MatchFieldType Source # 

Methods

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

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

toConstr :: MatchFieldType -> Constr #

dataTypeOf :: MatchFieldType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MatchFieldType Source # 
Read MatchFieldType Source # 
Show MatchFieldType Source # 
Generic MatchFieldType Source # 

Associated Types

type Rep MatchFieldType :: * -> * #

Hashable MatchFieldType Source # 
FromJSON MatchFieldType Source # 
ToJSON MatchFieldType Source # 
NFData MatchFieldType Source # 

Methods

rnf :: MatchFieldType -> () #

ToQuery MatchFieldType Source # 
ToHeader MatchFieldType Source # 
ToByteString MatchFieldType Source # 
FromText MatchFieldType Source # 
ToText MatchFieldType Source # 
type Rep MatchFieldType Source # 
type Rep MatchFieldType = D1 (MetaData "MatchFieldType" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) ((:+:) ((:+:) (C1 (MetaCons "Body" PrefixI False) U1) (C1 (MetaCons "Header" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Method" PrefixI False) U1) ((:+:) (C1 (MetaCons "QueryString" PrefixI False) U1) (C1 (MetaCons "URI" PrefixI False) U1))))

PositionalConstraint

data PositionalConstraint Source #

Instances

Bounded PositionalConstraint Source # 
Enum PositionalConstraint Source # 
Eq PositionalConstraint Source # 
Data PositionalConstraint Source # 

Methods

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

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

toConstr :: PositionalConstraint -> Constr #

dataTypeOf :: PositionalConstraint -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PositionalConstraint Source # 
Read PositionalConstraint Source # 
Show PositionalConstraint Source # 
Generic PositionalConstraint Source # 
Hashable PositionalConstraint Source # 
FromJSON PositionalConstraint Source # 
ToJSON PositionalConstraint Source # 
NFData PositionalConstraint Source # 

Methods

rnf :: PositionalConstraint -> () #

ToQuery PositionalConstraint Source # 
ToHeader PositionalConstraint Source # 
ToByteString PositionalConstraint Source # 
FromText PositionalConstraint Source # 
ToText PositionalConstraint Source # 
type Rep PositionalConstraint Source # 
type Rep PositionalConstraint = D1 (MetaData "PositionalConstraint" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) ((:+:) ((:+:) (C1 (MetaCons "Contains" PrefixI False) U1) (C1 (MetaCons "ContainsWord" PrefixI False) U1)) ((:+:) (C1 (MetaCons "EndsWith" PrefixI False) U1) ((:+:) (C1 (MetaCons "Exactly" PrefixI False) U1) (C1 (MetaCons "StartsWith" PrefixI False) U1))))

PredicateType

data PredicateType Source #

Instances

Bounded PredicateType Source # 
Enum PredicateType Source # 
Eq PredicateType Source # 
Data PredicateType Source # 

Methods

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

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

toConstr :: PredicateType -> Constr #

dataTypeOf :: PredicateType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PredicateType Source # 
Read PredicateType Source # 
Show PredicateType Source # 
Generic PredicateType Source # 

Associated Types

type Rep PredicateType :: * -> * #

Hashable PredicateType Source # 
FromJSON PredicateType Source # 
ToJSON PredicateType Source # 
NFData PredicateType Source # 

Methods

rnf :: PredicateType -> () #

ToQuery PredicateType Source # 
ToHeader PredicateType Source # 
ToByteString PredicateType Source # 
FromText PredicateType Source # 
ToText PredicateType Source # 

Methods

toText :: PredicateType -> Text #

type Rep PredicateType Source # 
type Rep PredicateType = D1 (MetaData "PredicateType" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) ((:+:) ((:+:) (C1 (MetaCons "ByteMatch" PrefixI False) U1) ((:+:) (C1 (MetaCons "GeoMatch" PrefixI False) U1) (C1 (MetaCons "IPMatch" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "RegexMatch" PrefixI False) U1) (C1 (MetaCons "SizeConstraint" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SqlInjectionMatch" PrefixI False) U1) (C1 (MetaCons "XSSMatch" PrefixI False) U1))))

RateKey

data RateKey Source #

Constructors

IP 

Instances

Bounded RateKey Source # 
Enum RateKey Source # 
Eq RateKey Source # 

Methods

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

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

Data RateKey Source # 

Methods

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

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

toConstr :: RateKey -> Constr #

dataTypeOf :: RateKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RateKey Source # 
Read RateKey Source # 
Show RateKey Source # 
Generic RateKey Source # 

Associated Types

type Rep RateKey :: * -> * #

Methods

from :: RateKey -> Rep RateKey x #

to :: Rep RateKey x -> RateKey #

Hashable RateKey Source # 

Methods

hashWithSalt :: Int -> RateKey -> Int #

hash :: RateKey -> Int #

FromJSON RateKey Source # 
ToJSON RateKey Source # 
NFData RateKey Source # 

Methods

rnf :: RateKey -> () #

ToQuery RateKey Source # 
ToHeader RateKey Source # 

Methods

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

ToByteString RateKey Source # 

Methods

toBS :: RateKey -> ByteString #

FromText RateKey Source # 
ToText RateKey Source # 

Methods

toText :: RateKey -> Text #

type Rep RateKey Source # 
type Rep RateKey = D1 (MetaData "RateKey" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "IP" PrefixI False) U1)

TextTransformation

data TextTransformation Source #

Instances

Bounded TextTransformation Source # 
Enum TextTransformation Source # 
Eq TextTransformation Source # 
Data TextTransformation Source # 

Methods

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

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

toConstr :: TextTransformation -> Constr #

dataTypeOf :: TextTransformation -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TextTransformation Source # 
Read TextTransformation Source # 
Show TextTransformation Source # 
Generic TextTransformation Source # 
Hashable TextTransformation Source # 
FromJSON TextTransformation Source # 
ToJSON TextTransformation Source # 
NFData TextTransformation Source # 

Methods

rnf :: TextTransformation -> () #

ToQuery TextTransformation Source # 
ToHeader TextTransformation Source # 
ToByteString TextTransformation Source # 
FromText TextTransformation Source # 
ToText TextTransformation Source # 
type Rep TextTransformation Source # 
type Rep TextTransformation = D1 (MetaData "TextTransformation" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) ((:+:) ((:+:) (C1 (MetaCons "CmdLine" PrefixI False) U1) ((:+:) (C1 (MetaCons "CompressWhiteSpace" PrefixI False) U1) (C1 (MetaCons "HTMLEntityDecode" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Lowercase" PrefixI False) U1) ((:+:) (C1 (MetaCons "None" PrefixI False) U1) (C1 (MetaCons "URLDecode" PrefixI False) U1))))

WafActionType

data WafActionType Source #

Constructors

Allow 
Block 
Count 

Instances

Bounded WafActionType Source # 
Enum WafActionType Source # 
Eq WafActionType Source # 
Data WafActionType Source # 

Methods

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

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

toConstr :: WafActionType -> Constr #

dataTypeOf :: WafActionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord WafActionType Source # 
Read WafActionType Source # 
Show WafActionType Source # 
Generic WafActionType Source # 

Associated Types

type Rep WafActionType :: * -> * #

Hashable WafActionType Source # 
FromJSON WafActionType Source # 
ToJSON WafActionType Source # 
NFData WafActionType Source # 

Methods

rnf :: WafActionType -> () #

ToQuery WafActionType Source # 
ToHeader WafActionType Source # 
ToByteString WafActionType Source # 
FromText WafActionType Source # 
ToText WafActionType Source # 

Methods

toText :: WafActionType -> Text #

type Rep WafActionType Source # 
type Rep WafActionType = D1 (MetaData "WafActionType" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) ((:+:) (C1 (MetaCons "Allow" PrefixI False) U1) ((:+:) (C1 (MetaCons "Block" PrefixI False) U1) (C1 (MetaCons "Count" PrefixI False) U1)))

WafRuleType

data WafRuleType Source #

Constructors

RateBased 
Regular 

Instances

Bounded WafRuleType Source # 
Enum WafRuleType Source # 
Eq WafRuleType Source # 
Data WafRuleType Source # 

Methods

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

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

toConstr :: WafRuleType -> Constr #

dataTypeOf :: WafRuleType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord WafRuleType Source # 
Read WafRuleType Source # 
Show WafRuleType Source # 
Generic WafRuleType Source # 

Associated Types

type Rep WafRuleType :: * -> * #

Hashable WafRuleType Source # 
FromJSON WafRuleType Source # 
ToJSON WafRuleType Source # 
NFData WafRuleType Source # 

Methods

rnf :: WafRuleType -> () #

ToQuery WafRuleType Source # 
ToHeader WafRuleType Source # 
ToByteString WafRuleType Source # 
FromText WafRuleType Source # 
ToText WafRuleType Source # 

Methods

toText :: WafRuleType -> Text #

type Rep WafRuleType Source # 
type Rep WafRuleType = D1 (MetaData "WafRuleType" "Network.AWS.WAFRegional.Types.Sum" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) ((:+:) (C1 (MetaCons "RateBased" PrefixI False) U1) (C1 (MetaCons "Regular" PrefixI False) U1))

ActivatedRule

data ActivatedRule Source #

The ActivatedRule object in an UpdateWebACL request specifies a Rule that you want to insert or delete, the priority of the Rule in the WebACL , and the action that you want AWS WAF to take when a web request matches the Rule (ALLOW , BLOCK , or COUNT ).

To specify whether to insert or delete a Rule , use the Action parameter in the WebACLUpdate data type.

See: activatedRule smart constructor.

Instances

Eq ActivatedRule Source # 
Data ActivatedRule Source # 

Methods

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

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

toConstr :: ActivatedRule -> Constr #

dataTypeOf :: ActivatedRule -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ActivatedRule Source # 
Show ActivatedRule Source # 
Generic ActivatedRule Source # 

Associated Types

type Rep ActivatedRule :: * -> * #

Hashable ActivatedRule Source # 
FromJSON ActivatedRule Source # 
ToJSON ActivatedRule Source # 
NFData ActivatedRule Source # 

Methods

rnf :: ActivatedRule -> () #

type Rep ActivatedRule Source # 
type Rep ActivatedRule = D1 (MetaData "ActivatedRule" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "ActivatedRule'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_arType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe WafRuleType))) (S1 (MetaSel (Just Symbol "_arPriority") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "_arRuleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_arAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WafAction)))))

activatedRule Source #

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

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

  • arType - The rule type, either REGULAR , as defined by Rule , or RATE_BASED , as defined by RateBasedRule . The default is REGULAR. Although this field is optional, be aware that if you try to add a RATE_BASED rule to a web ACL without setting the type, the UpdateWebACL request will fail because the request tries to add a REGULAR rule with the specified ID, which does not exist.
  • arPriority - Specifies the order in which the Rules in a WebACL are evaluated. Rules with a lower value for Priority are evaluated before Rules with a higher value. The value must be a unique integer. If you add multiple Rules to a WebACL , the values don't need to be consecutive.
  • arRuleId - The RuleId for a Rule . You use RuleId to get more information about a Rule (see GetRule ), update a Rule (see UpdateRule ), insert a Rule into a WebACL or delete a one from a WebACL (see UpdateWebACL ), or delete a Rule from AWS WAF (see DeleteRule ). RuleId is returned by CreateRule and by ListRules .
  • arAction - Specifies the action that CloudFront or AWS WAF takes when a web request matches the conditions in the Rule . Valid values for Action include the following: * ALLOW : CloudFront responds with the requested object. * BLOCK : CloudFront responds with an HTTP 403 (Forbidden) status code. * COUNT : AWS WAF increments a counter of requests that match the conditions in the rule and then continues to inspect the web request based on the remaining rules in the web ACL.

arType :: Lens' ActivatedRule (Maybe WafRuleType) Source #

The rule type, either REGULAR , as defined by Rule , or RATE_BASED , as defined by RateBasedRule . The default is REGULAR. Although this field is optional, be aware that if you try to add a RATE_BASED rule to a web ACL without setting the type, the UpdateWebACL request will fail because the request tries to add a REGULAR rule with the specified ID, which does not exist.

arPriority :: Lens' ActivatedRule Int Source #

Specifies the order in which the Rules in a WebACL are evaluated. Rules with a lower value for Priority are evaluated before Rules with a higher value. The value must be a unique integer. If you add multiple Rules to a WebACL , the values don't need to be consecutive.

arRuleId :: Lens' ActivatedRule Text Source #

The RuleId for a Rule . You use RuleId to get more information about a Rule (see GetRule ), update a Rule (see UpdateRule ), insert a Rule into a WebACL or delete a one from a WebACL (see UpdateWebACL ), or delete a Rule from AWS WAF (see DeleteRule ). RuleId is returned by CreateRule and by ListRules .

arAction :: Lens' ActivatedRule WafAction Source #

Specifies the action that CloudFront or AWS WAF takes when a web request matches the conditions in the Rule . Valid values for Action include the following: * ALLOW : CloudFront responds with the requested object. * BLOCK : CloudFront responds with an HTTP 403 (Forbidden) status code. * COUNT : AWS WAF increments a counter of requests that match the conditions in the rule and then continues to inspect the web request based on the remaining rules in the web ACL.

ByteMatchSet

data ByteMatchSet Source #

In a GetByteMatchSet request, ByteMatchSet is a complex type that contains the ByteMatchSetId and Name of a ByteMatchSet , and the values that you specified when you updated the ByteMatchSet .

A complex type that contains ByteMatchTuple objects, which specify the parts of web requests that you want AWS WAF to inspect and the values that you want AWS WAF to search for. If a ByteMatchSet contains more than one ByteMatchTuple object, a request needs to match the settings in only one ByteMatchTuple to be considered a match.

See: byteMatchSet smart constructor.

Instances

Eq ByteMatchSet Source # 
Data ByteMatchSet Source # 

Methods

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

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

toConstr :: ByteMatchSet -> Constr #

dataTypeOf :: ByteMatchSet -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ByteMatchSet Source # 
Show ByteMatchSet Source # 
Generic ByteMatchSet Source # 

Associated Types

type Rep ByteMatchSet :: * -> * #

Hashable ByteMatchSet Source # 
FromJSON ByteMatchSet Source # 
NFData ByteMatchSet Source # 

Methods

rnf :: ByteMatchSet -> () #

type Rep ByteMatchSet Source # 
type Rep ByteMatchSet = D1 (MetaData "ByteMatchSet" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "ByteMatchSet'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bmsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_bmsByteMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_bmsByteMatchTuples") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [ByteMatchTuple])))))

byteMatchSet Source #

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

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

  • bmsName - A friendly name or description of the ByteMatchSet . You can't change Name after you create a ByteMatchSet .
  • bmsByteMatchSetId - The ByteMatchSetId for a ByteMatchSet . You use ByteMatchSetId to get information about a ByteMatchSet (see GetByteMatchSet ), update a ByteMatchSet (see UpdateByteMatchSet ), insert a ByteMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a ByteMatchSet from AWS WAF (see DeleteByteMatchSet ). ByteMatchSetId is returned by CreateByteMatchSet and by ListByteMatchSets .
  • bmsByteMatchTuples - Specifies the bytes (typically a string that corresponds with ASCII characters) that you want AWS WAF to search for in web requests, the location in requests that you want AWS WAF to search, and other settings.

bmsName :: Lens' ByteMatchSet (Maybe Text) Source #

A friendly name or description of the ByteMatchSet . You can't change Name after you create a ByteMatchSet .

bmsByteMatchSetId :: Lens' ByteMatchSet Text Source #

The ByteMatchSetId for a ByteMatchSet . You use ByteMatchSetId to get information about a ByteMatchSet (see GetByteMatchSet ), update a ByteMatchSet (see UpdateByteMatchSet ), insert a ByteMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a ByteMatchSet from AWS WAF (see DeleteByteMatchSet ). ByteMatchSetId is returned by CreateByteMatchSet and by ListByteMatchSets .

bmsByteMatchTuples :: Lens' ByteMatchSet [ByteMatchTuple] Source #

Specifies the bytes (typically a string that corresponds with ASCII characters) that you want AWS WAF to search for in web requests, the location in requests that you want AWS WAF to search, and other settings.

ByteMatchSetSummary

data ByteMatchSetSummary Source #

Returned by ListByteMatchSets . Each ByteMatchSetSummary object includes the Name and ByteMatchSetId for one ByteMatchSet .

See: byteMatchSetSummary smart constructor.

Instances

Eq ByteMatchSetSummary Source # 
Data ByteMatchSetSummary Source # 

Methods

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

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

toConstr :: ByteMatchSetSummary -> Constr #

dataTypeOf :: ByteMatchSetSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: ByteMatchSetSummary -> () #

type Rep ByteMatchSetSummary Source # 
type Rep ByteMatchSetSummary = D1 (MetaData "ByteMatchSetSummary" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "ByteMatchSetSummary'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bmssByteMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_bmssName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

byteMatchSetSummary Source #

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

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

  • bmssByteMatchSetId - The ByteMatchSetId for a ByteMatchSet . You use ByteMatchSetId to get information about a ByteMatchSet , update a ByteMatchSet , remove a ByteMatchSet from a Rule , and delete a ByteMatchSet from AWS WAF. ByteMatchSetId is returned by CreateByteMatchSet and by ListByteMatchSets .
  • bmssName - A friendly name or description of the ByteMatchSet . You can't change Name after you create a ByteMatchSet .

bmssByteMatchSetId :: Lens' ByteMatchSetSummary Text Source #

The ByteMatchSetId for a ByteMatchSet . You use ByteMatchSetId to get information about a ByteMatchSet , update a ByteMatchSet , remove a ByteMatchSet from a Rule , and delete a ByteMatchSet from AWS WAF. ByteMatchSetId is returned by CreateByteMatchSet and by ListByteMatchSets .

bmssName :: Lens' ByteMatchSetSummary Text Source #

A friendly name or description of the ByteMatchSet . You can't change Name after you create a ByteMatchSet .

ByteMatchSetUpdate

data ByteMatchSetUpdate Source #

In an UpdateByteMatchSet request, ByteMatchSetUpdate specifies whether to insert or delete a ByteMatchTuple and includes the settings for the ByteMatchTuple .

See: byteMatchSetUpdate smart constructor.

Instances

Eq ByteMatchSetUpdate Source # 
Data ByteMatchSetUpdate Source # 

Methods

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

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

toConstr :: ByteMatchSetUpdate -> Constr #

dataTypeOf :: ByteMatchSetUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ByteMatchSetUpdate Source # 
Show ByteMatchSetUpdate Source # 
Generic ByteMatchSetUpdate Source # 
Hashable ByteMatchSetUpdate Source # 
ToJSON ByteMatchSetUpdate Source # 
NFData ByteMatchSetUpdate Source # 

Methods

rnf :: ByteMatchSetUpdate -> () #

type Rep ByteMatchSetUpdate Source # 
type Rep ByteMatchSetUpdate = D1 (MetaData "ByteMatchSetUpdate" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "ByteMatchSetUpdate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_bmsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction)) (S1 (MetaSel (Just Symbol "_bmsuByteMatchTuple") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteMatchTuple))))

byteMatchSetUpdate Source #

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

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

  • bmsuAction - Specifies whether to insert or delete a ByteMatchTuple .
  • bmsuByteMatchTuple - Information about the part of a web request that you want AWS WAF to inspect and the value that you want AWS WAF to search for. If you specify DELETE for the value of Action , the ByteMatchTuple values must exactly match the values in the ByteMatchTuple that you want to delete from the ByteMatchSet .

bmsuAction :: Lens' ByteMatchSetUpdate ChangeAction Source #

Specifies whether to insert or delete a ByteMatchTuple .

bmsuByteMatchTuple :: Lens' ByteMatchSetUpdate ByteMatchTuple Source #

Information about the part of a web request that you want AWS WAF to inspect and the value that you want AWS WAF to search for. If you specify DELETE for the value of Action , the ByteMatchTuple values must exactly match the values in the ByteMatchTuple that you want to delete from the ByteMatchSet .

ByteMatchTuple

data ByteMatchTuple Source #

The bytes (typically a string that corresponds with ASCII characters) that you want AWS WAF to search for in web requests, the location in requests that you want AWS WAF to search, and other settings.

See: byteMatchTuple smart constructor.

Instances

Eq ByteMatchTuple Source # 
Data ByteMatchTuple Source # 

Methods

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

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

toConstr :: ByteMatchTuple -> Constr #

dataTypeOf :: ByteMatchTuple -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ByteMatchTuple Source # 
Show ByteMatchTuple Source # 
Generic ByteMatchTuple Source # 

Associated Types

type Rep ByteMatchTuple :: * -> * #

Hashable ByteMatchTuple Source # 
FromJSON ByteMatchTuple Source # 
ToJSON ByteMatchTuple Source # 
NFData ByteMatchTuple Source # 

Methods

rnf :: ByteMatchTuple -> () #

type Rep ByteMatchTuple Source # 
type Rep ByteMatchTuple = D1 (MetaData "ByteMatchTuple" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "ByteMatchTuple'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_bmtFieldToMatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FieldToMatch)) (S1 (MetaSel (Just Symbol "_bmtTargetString") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Base64))) ((:*:) (S1 (MetaSel (Just Symbol "_bmtTextTransformation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextTransformation)) (S1 (MetaSel (Just Symbol "_bmtPositionalConstraint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PositionalConstraint)))))

byteMatchTuple Source #

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

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

  • bmtFieldToMatch - The part of a web request that you want AWS WAF to search, such as a specified header or a query string. For more information, see FieldToMatch .
  • bmtTargetString - The value that you want AWS WAF to search for. AWS WAF searches for the specified string in the part of web requests that you specified in FieldToMatch . The maximum length of the value is 50 bytes. Valid values depend on the values that you specified for FieldToMatch : * HEADER : The value that you want AWS WAF to search for in the request header that you specified in FieldToMatch , for example, the value of the User-Agent or Referer header. * METHOD : The HTTP method, which indicates the type of operation specified in the request. CloudFront supports the following methods: DELETE , GET , HEAD , OPTIONS , PATCH , POST , and PUT . * QUERY_STRING : The value that you want AWS WAF to search for in the query string, which is the part of a URL that appears after a ? character. * URI : The value that you want AWS WAF to search for in the part of a URL that identifies a resource, for example, imagesdaily-ad.jpg . * BODY : The part of a request that contains any additional data that you want to send to your web server as the HTTP request body, such as data from a form. The request body immediately follows the request headers. Note that only the first 8192 bytes of the request body are forwarded to AWS WAF for inspection. To allow or block requests based on the length of the body, you can create a size constraint set. For more information, see CreateSizeConstraintSet . If TargetString includes alphabetic characters A-Z and a-z, note that the value is case sensitive. If you're using the AWS WAF API Specify a base64-encoded version of the value. The maximum length of the value before you base64-encode it is 50 bytes. For example, suppose the value of Type is HEADER and the value of Data is User-Agent . If you want to search the User-Agent header for the value BadBot , you base64-encode BadBot using MIME base64 encoding and include the resulting value, QmFkQm90 , in the value of TargetString . If you're using the AWS CLI or one of the AWS SDKs The value that you want AWS WAF to search for. The SDK automatically base64 encodes the value.-- Note: This Lens automatically encodes and decodes Base64 data. The underlying isomorphism will encode to Base64 representation during serialisation, and decode from Base64 representation during deserialisation. This Lens accepts and returns only raw unencoded data.
  • bmtTextTransformation - Text transformations eliminate some of the unusual formatting that attackers use in web requests in an effort to bypass AWS WAF. If you specify a transformation, AWS WAF performs the transformation on TargetString before inspecting a request for a match. CMD_LINE When you're concerned that attackers are injecting an operating system commandline command and using unusual formatting to disguise some or all of the command, use this option to perform the following transformations: * Delete the following characters: " ' ^ * Delete spaces before the following characters: / ( * Replace the following characters with a space: , ; * Replace multiple spaces with one space * Convert uppercase letters (A-Z) to lowercase (a-z) COMPRESS_WHITE_SPACE Use this option to replace the following characters with a space character (decimal 32): * f, formfeed, decimal 12 * t, tab, decimal 9 * n, newline, decimal 10 * r, carriage return, decimal 13 * v, vertical tab, decimal 11 * non-breaking space, decimal 160 COMPRESS_WHITE_SPACE also replaces multiple spaces with one space. HTML_ENTITY_DECODE Use this option to replace HTML-encoded characters with unencoded characters. HTML_ENTITY_DECODE performs the following operations: * Replaces (ampersand)quot; with " * Replaces (ampersand)nbsp; with a non-breaking space, decimal 160 * Replaces (ampersand)lt; with a "less than" symbol * Replaces (ampersand)gt; with > * Replaces characters that are represented in hexadecimal format, (ampersand)#xhhhh; , with the corresponding characters * Replaces characters that are represented in decimal format, (ampersand)#nnnn; , with the corresponding characters LOWERCASE Use this option to convert uppercase letters (A-Z) to lowercase (a-z). URL_DECODE Use this option to decode a URL-encoded value. NONE Specify NONE if you don't want to perform any text transformations.
  • bmtPositionalConstraint - Within the portion of a web request that you want to search (for example, in the query string, if any), specify where you want AWS WAF to search. Valid values include the following: CONTAINS The specified part of the web request must include the value of TargetString , but the location doesn't matter. CONTAINS_WORD The specified part of the web request must include the value of TargetString , and TargetString must contain only alphanumeric characters or underscore (A-Z, a-z, 0-9, or _). In addition, TargetString must be a word, which means one of the following: * TargetString exactly matches the value of the specified part of the web request, such as the value of a header. * TargetString is at the beginning of the specified part of the web request and is followed by a character other than an alphanumeric character or underscore (_), for example, BadBot; . * TargetString is at the end of the specified part of the web request and is preceded by a character other than an alphanumeric character or underscore (_), for example, ;BadBot . * TargetString is in the middle of the specified part of the web request and is preceded and followed by characters other than alphanumeric characters or underscore (_), for example, -BadBot; . EXACTLY The value of the specified part of the web request must exactly match the value of TargetString . STARTS_WITH The value of TargetString must appear at the beginning of the specified part of the web request. ENDS_WITH The value of TargetString must appear at the end of the specified part of the web request.

bmtFieldToMatch :: Lens' ByteMatchTuple FieldToMatch Source #

The part of a web request that you want AWS WAF to search, such as a specified header or a query string. For more information, see FieldToMatch .

bmtTargetString :: Lens' ByteMatchTuple ByteString Source #

The value that you want AWS WAF to search for. AWS WAF searches for the specified string in the part of web requests that you specified in FieldToMatch . The maximum length of the value is 50 bytes. Valid values depend on the values that you specified for FieldToMatch : * HEADER : The value that you want AWS WAF to search for in the request header that you specified in FieldToMatch , for example, the value of the User-Agent or Referer header. * METHOD : The HTTP method, which indicates the type of operation specified in the request. CloudFront supports the following methods: DELETE , GET , HEAD , OPTIONS , PATCH , POST , and PUT . * QUERY_STRING : The value that you want AWS WAF to search for in the query string, which is the part of a URL that appears after a ? character. * URI : The value that you want AWS WAF to search for in the part of a URL that identifies a resource, for example, imagesdaily-ad.jpg . * BODY : The part of a request that contains any additional data that you want to send to your web server as the HTTP request body, such as data from a form. The request body immediately follows the request headers. Note that only the first 8192 bytes of the request body are forwarded to AWS WAF for inspection. To allow or block requests based on the length of the body, you can create a size constraint set. For more information, see CreateSizeConstraintSet . If TargetString includes alphabetic characters A-Z and a-z, note that the value is case sensitive. If you're using the AWS WAF API Specify a base64-encoded version of the value. The maximum length of the value before you base64-encode it is 50 bytes. For example, suppose the value of Type is HEADER and the value of Data is User-Agent . If you want to search the User-Agent header for the value BadBot , you base64-encode BadBot using MIME base64 encoding and include the resulting value, QmFkQm90 , in the value of TargetString . If you're using the AWS CLI or one of the AWS SDKs The value that you want AWS WAF to search for. The SDK automatically base64 encodes the value.-- Note: This Lens automatically encodes and decodes Base64 data. The underlying isomorphism will encode to Base64 representation during serialisation, and decode from Base64 representation during deserialisation. This Lens accepts and returns only raw unencoded data.

bmtTextTransformation :: Lens' ByteMatchTuple TextTransformation Source #

Text transformations eliminate some of the unusual formatting that attackers use in web requests in an effort to bypass AWS WAF. If you specify a transformation, AWS WAF performs the transformation on TargetString before inspecting a request for a match. CMD_LINE When you're concerned that attackers are injecting an operating system commandline command and using unusual formatting to disguise some or all of the command, use this option to perform the following transformations: * Delete the following characters: " ' ^ * Delete spaces before the following characters: / ( * Replace the following characters with a space: , ; * Replace multiple spaces with one space * Convert uppercase letters (A-Z) to lowercase (a-z) COMPRESS_WHITE_SPACE Use this option to replace the following characters with a space character (decimal 32): * f, formfeed, decimal 12 * t, tab, decimal 9 * n, newline, decimal 10 * r, carriage return, decimal 13 * v, vertical tab, decimal 11 * non-breaking space, decimal 160 COMPRESS_WHITE_SPACE also replaces multiple spaces with one space. HTML_ENTITY_DECODE Use this option to replace HTML-encoded characters with unencoded characters. HTML_ENTITY_DECODE performs the following operations: * Replaces (ampersand)quot; with " * Replaces (ampersand)nbsp; with a non-breaking space, decimal 160 * Replaces (ampersand)lt; with a "less than" symbol * Replaces (ampersand)gt; with > * Replaces characters that are represented in hexadecimal format, (ampersand)#xhhhh; , with the corresponding characters * Replaces characters that are represented in decimal format, (ampersand)#nnnn; , with the corresponding characters LOWERCASE Use this option to convert uppercase letters (A-Z) to lowercase (a-z). URL_DECODE Use this option to decode a URL-encoded value. NONE Specify NONE if you don't want to perform any text transformations.

bmtPositionalConstraint :: Lens' ByteMatchTuple PositionalConstraint Source #

Within the portion of a web request that you want to search (for example, in the query string, if any), specify where you want AWS WAF to search. Valid values include the following: CONTAINS The specified part of the web request must include the value of TargetString , but the location doesn't matter. CONTAINS_WORD The specified part of the web request must include the value of TargetString , and TargetString must contain only alphanumeric characters or underscore (A-Z, a-z, 0-9, or _). In addition, TargetString must be a word, which means one of the following: * TargetString exactly matches the value of the specified part of the web request, such as the value of a header. * TargetString is at the beginning of the specified part of the web request and is followed by a character other than an alphanumeric character or underscore (_), for example, BadBot; . * TargetString is at the end of the specified part of the web request and is preceded by a character other than an alphanumeric character or underscore (_), for example, ;BadBot . * TargetString is in the middle of the specified part of the web request and is preceded and followed by characters other than alphanumeric characters or underscore (_), for example, -BadBot; . EXACTLY The value of the specified part of the web request must exactly match the value of TargetString . STARTS_WITH The value of TargetString must appear at the beginning of the specified part of the web request. ENDS_WITH The value of TargetString must appear at the end of the specified part of the web request.

FieldToMatch

data FieldToMatch Source #

Specifies where in a web request to look for TargetString .

See: fieldToMatch smart constructor.

Instances

Eq FieldToMatch Source # 
Data FieldToMatch Source # 

Methods

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

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

toConstr :: FieldToMatch -> Constr #

dataTypeOf :: FieldToMatch -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FieldToMatch Source # 
Show FieldToMatch Source # 
Generic FieldToMatch Source # 

Associated Types

type Rep FieldToMatch :: * -> * #

Hashable FieldToMatch Source # 
FromJSON FieldToMatch Source # 
ToJSON FieldToMatch Source # 
NFData FieldToMatch Source # 

Methods

rnf :: FieldToMatch -> () #

type Rep FieldToMatch Source # 
type Rep FieldToMatch = D1 (MetaData "FieldToMatch" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "FieldToMatch'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ftmData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ftmType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MatchFieldType))))

fieldToMatch Source #

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

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

  • ftmData - When the value of Type is HEADER , enter the name of the header that you want AWS WAF to search, for example, User-Agent or Referer . If the value of Type is any other value, omit Data . The name of the header is not case sensitive.
  • ftmType - The part of the web request that you want AWS WAF to search for a specified string. Parts of a request that you can search include the following: * HEADER : A specified request header, for example, the value of the User-Agent or Referer header. If you choose HEADER for the type, specify the name of the header in Data . * METHOD : The HTTP method, which indicated the type of operation that the request is asking the origin to perform. Amazon CloudFront supports the following methods: DELETE , GET , HEAD , OPTIONS , PATCH , POST , and PUT . * QUERY_STRING : A query string, which is the part of a URL that appears after a ? character, if any. * URI : The part of a web request that identifies a resource, for example, imagesdaily-ad.jpg . * BODY : The part of a request that contains any additional data that you want to send to your web server as the HTTP request body, such as data from a form. The request body immediately follows the request headers. Note that only the first 8192 bytes of the request body are forwarded to AWS WAF for inspection. To allow or block requests based on the length of the body, you can create a size constraint set. For more information, see CreateSizeConstraintSet .

ftmData :: Lens' FieldToMatch (Maybe Text) Source #

When the value of Type is HEADER , enter the name of the header that you want AWS WAF to search, for example, User-Agent or Referer . If the value of Type is any other value, omit Data . The name of the header is not case sensitive.

ftmType :: Lens' FieldToMatch MatchFieldType Source #

The part of the web request that you want AWS WAF to search for a specified string. Parts of a request that you can search include the following: * HEADER : A specified request header, for example, the value of the User-Agent or Referer header. If you choose HEADER for the type, specify the name of the header in Data . * METHOD : The HTTP method, which indicated the type of operation that the request is asking the origin to perform. Amazon CloudFront supports the following methods: DELETE , GET , HEAD , OPTIONS , PATCH , POST , and PUT . * QUERY_STRING : A query string, which is the part of a URL that appears after a ? character, if any. * URI : The part of a web request that identifies a resource, for example, imagesdaily-ad.jpg . * BODY : The part of a request that contains any additional data that you want to send to your web server as the HTTP request body, such as data from a form. The request body immediately follows the request headers. Note that only the first 8192 bytes of the request body are forwarded to AWS WAF for inspection. To allow or block requests based on the length of the body, you can create a size constraint set. For more information, see CreateSizeConstraintSet .

GeoMatchConstraint

data GeoMatchConstraint Source #

The country from which web requests originate that you want AWS WAF to search for.

See: geoMatchConstraint smart constructor.

Instances

Eq GeoMatchConstraint Source # 
Data GeoMatchConstraint Source # 

Methods

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

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

toConstr :: GeoMatchConstraint -> Constr #

dataTypeOf :: GeoMatchConstraint -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GeoMatchConstraint Source # 
Show GeoMatchConstraint Source # 
Generic GeoMatchConstraint Source # 
Hashable GeoMatchConstraint Source # 
FromJSON GeoMatchConstraint Source # 
ToJSON GeoMatchConstraint Source # 
NFData GeoMatchConstraint Source # 

Methods

rnf :: GeoMatchConstraint -> () #

type Rep GeoMatchConstraint Source # 
type Rep GeoMatchConstraint = D1 (MetaData "GeoMatchConstraint" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "GeoMatchConstraint'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gmcType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 GeoMatchConstraintType)) (S1 (MetaSel (Just Symbol "_gmcValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 GeoMatchConstraintValue))))

geoMatchConstraint Source #

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

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

  • gmcType - The type of geographical area you want AWS WAF to search for. Currently Country is the only valid value.
  • gmcValue - The country that you want AWS WAF to search for.

gmcType :: Lens' GeoMatchConstraint GeoMatchConstraintType Source #

The type of geographical area you want AWS WAF to search for. Currently Country is the only valid value.

gmcValue :: Lens' GeoMatchConstraint GeoMatchConstraintValue Source #

The country that you want AWS WAF to search for.

GeoMatchSet

data GeoMatchSet Source #

Contains one or more countries that AWS WAF will search for.

See: geoMatchSet smart constructor.

Instances

Eq GeoMatchSet Source # 
Data GeoMatchSet Source # 

Methods

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

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

toConstr :: GeoMatchSet -> Constr #

dataTypeOf :: GeoMatchSet -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GeoMatchSet Source # 
Show GeoMatchSet Source # 
Generic GeoMatchSet Source # 

Associated Types

type Rep GeoMatchSet :: * -> * #

Hashable GeoMatchSet Source # 
FromJSON GeoMatchSet Source # 
NFData GeoMatchSet Source # 

Methods

rnf :: GeoMatchSet -> () #

type Rep GeoMatchSet Source # 
type Rep GeoMatchSet = D1 (MetaData "GeoMatchSet" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "GeoMatchSet'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gmsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_gmsGeoMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_gmsGeoMatchConstraints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [GeoMatchConstraint])))))

geoMatchSet Source #

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

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

  • gmsName - A friendly name or description of the GeoMatchSet . You can't change the name of an GeoMatchSet after you create it.
  • gmsGeoMatchSetId - The GeoMatchSetId for an GeoMatchSet . You use GeoMatchSetId to get information about a GeoMatchSet (see GeoMatchSet ), update a GeoMatchSet (see UpdateGeoMatchSet ), insert a GeoMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a GeoMatchSet from AWS WAF (see DeleteGeoMatchSet ). GeoMatchSetId is returned by CreateGeoMatchSet and by ListGeoMatchSets .
  • gmsGeoMatchConstraints - An array of GeoMatchConstraint objects, which contain the country that you want AWS WAF to search for.

gmsName :: Lens' GeoMatchSet (Maybe Text) Source #

A friendly name or description of the GeoMatchSet . You can't change the name of an GeoMatchSet after you create it.

gmsGeoMatchSetId :: Lens' GeoMatchSet Text Source #

The GeoMatchSetId for an GeoMatchSet . You use GeoMatchSetId to get information about a GeoMatchSet (see GeoMatchSet ), update a GeoMatchSet (see UpdateGeoMatchSet ), insert a GeoMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a GeoMatchSet from AWS WAF (see DeleteGeoMatchSet ). GeoMatchSetId is returned by CreateGeoMatchSet and by ListGeoMatchSets .

gmsGeoMatchConstraints :: Lens' GeoMatchSet [GeoMatchConstraint] Source #

An array of GeoMatchConstraint objects, which contain the country that you want AWS WAF to search for.

GeoMatchSetSummary

data GeoMatchSetSummary Source #

Contains the identifier and the name of the GeoMatchSet .

See: geoMatchSetSummary smart constructor.

Instances

Eq GeoMatchSetSummary Source # 
Data GeoMatchSetSummary Source # 

Methods

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

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

toConstr :: GeoMatchSetSummary -> Constr #

dataTypeOf :: GeoMatchSetSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: GeoMatchSetSummary -> () #

type Rep GeoMatchSetSummary Source # 
type Rep GeoMatchSetSummary = D1 (MetaData "GeoMatchSetSummary" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "GeoMatchSetSummary'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gmssGeoMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_gmssName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

geoMatchSetSummary Source #

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

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

  • gmssGeoMatchSetId - The GeoMatchSetId for an GeoMatchSet . You can use GeoMatchSetId in a GetGeoMatchSet request to get detailed information about an GeoMatchSet .
  • gmssName - A friendly name or description of the GeoMatchSet . You can't change the name of an GeoMatchSet after you create it.

gmssGeoMatchSetId :: Lens' GeoMatchSetSummary Text Source #

The GeoMatchSetId for an GeoMatchSet . You can use GeoMatchSetId in a GetGeoMatchSet request to get detailed information about an GeoMatchSet .

gmssName :: Lens' GeoMatchSetSummary Text Source #

A friendly name or description of the GeoMatchSet . You can't change the name of an GeoMatchSet after you create it.

GeoMatchSetUpdate

data GeoMatchSetUpdate Source #

Specifies the type of update to perform to an GeoMatchSet with UpdateGeoMatchSet .

See: geoMatchSetUpdate smart constructor.

Instances

Eq GeoMatchSetUpdate Source # 
Data GeoMatchSetUpdate Source # 

Methods

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

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

toConstr :: GeoMatchSetUpdate -> Constr #

dataTypeOf :: GeoMatchSetUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GeoMatchSetUpdate Source # 
Show GeoMatchSetUpdate Source # 
Generic GeoMatchSetUpdate Source # 
Hashable GeoMatchSetUpdate Source # 
ToJSON GeoMatchSetUpdate Source # 
NFData GeoMatchSetUpdate Source # 

Methods

rnf :: GeoMatchSetUpdate -> () #

type Rep GeoMatchSetUpdate Source # 
type Rep GeoMatchSetUpdate = D1 (MetaData "GeoMatchSetUpdate" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "GeoMatchSetUpdate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gmsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction)) (S1 (MetaSel (Just Symbol "_gmsuGeoMatchConstraint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 GeoMatchConstraint))))

geoMatchSetUpdate Source #

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

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

  • gmsuAction - Specifies whether to insert or delete a country with UpdateGeoMatchSet .
  • gmsuGeoMatchConstraint - The country from which web requests originate that you want AWS WAF to search for.

gmsuAction :: Lens' GeoMatchSetUpdate ChangeAction Source #

Specifies whether to insert or delete a country with UpdateGeoMatchSet .

gmsuGeoMatchConstraint :: Lens' GeoMatchSetUpdate GeoMatchConstraint Source #

The country from which web requests originate that you want AWS WAF to search for.

HTTPHeader

data HTTPHeader Source #

The response from a GetSampledRequests request includes an HTTPHeader complex type that appears as Headers in the response syntax. HTTPHeader contains the names and values of all of the headers that appear in one of the web requests that were returned by GetSampledRequests .

See: hTTPHeader smart constructor.

Instances

Eq HTTPHeader Source # 
Data HTTPHeader Source # 

Methods

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

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

toConstr :: HTTPHeader -> Constr #

dataTypeOf :: HTTPHeader -> DataType #

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

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

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

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

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

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

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

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

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

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

Read HTTPHeader Source # 
Show HTTPHeader Source # 
Generic HTTPHeader Source # 

Associated Types

type Rep HTTPHeader :: * -> * #

Hashable HTTPHeader Source # 
FromJSON HTTPHeader Source # 
NFData HTTPHeader Source # 

Methods

rnf :: HTTPHeader -> () #

type Rep HTTPHeader Source # 
type Rep HTTPHeader = D1 (MetaData "HTTPHeader" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "HTTPHeader'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_httphValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_httphName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

hTTPHeader :: HTTPHeader Source #

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

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

  • httphValue - The value of one of the headers in the sampled web request.
  • httphName - The name of one of the headers in the sampled web request.

httphValue :: Lens' HTTPHeader (Maybe Text) Source #

The value of one of the headers in the sampled web request.

httphName :: Lens' HTTPHeader (Maybe Text) Source #

The name of one of the headers in the sampled web request.

HTTPRequest

data HTTPRequest Source #

The response from a GetSampledRequests request includes an HTTPRequest complex type that appears as Request in the response syntax. HTTPRequest contains information about one of the web requests that were returned by GetSampledRequests .

See: hTTPRequest smart constructor.

Instances

Eq HTTPRequest Source # 
Data HTTPRequest Source # 

Methods

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

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

toConstr :: HTTPRequest -> Constr #

dataTypeOf :: HTTPRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Read HTTPRequest Source # 
Show HTTPRequest Source # 
Generic HTTPRequest Source # 

Associated Types

type Rep HTTPRequest :: * -> * #

Hashable HTTPRequest Source # 
FromJSON HTTPRequest Source # 
NFData HTTPRequest Source # 

Methods

rnf :: HTTPRequest -> () #

type Rep HTTPRequest Source # 
type Rep HTTPRequest = D1 (MetaData "HTTPRequest" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "HTTPRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_httprHTTPVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_httprCountry") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_httprURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_httprHeaders") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [HTTPHeader]))) ((:*:) (S1 (MetaSel (Just Symbol "_httprMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_httprClientIP") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

hTTPRequest :: HTTPRequest Source #

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

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

  • httprHTTPVersion - The HTTP version specified in the sampled web request, for example, HTTP/1.1 .
  • httprCountry - The two-letter country code for the country that the request originated from. For a current list of country codes, see the Wikipedia entry ISO 3166-1 alpha-2 .
  • httprURI - The part of a web request that identifies the resource, for example, imagesdaily-ad.jpg .
  • httprHeaders - A complex type that contains two values for each header in the sampled web request: the name of the header and the value of the header.
  • httprMethod - The HTTP method specified in the sampled web request. CloudFront supports the following methods: DELETE , GET , HEAD , OPTIONS , PATCH , POST , and PUT .
  • httprClientIP - The IP address that the request originated from. If the WebACL is associated with a CloudFront distribution, this is the value of one of the following fields in CloudFront access logs: * c-ip , if the viewer did not use an HTTP proxy or a load balancer to send the request * x-forwarded-for , if the viewer did use an HTTP proxy or a load balancer to send the request

httprHTTPVersion :: Lens' HTTPRequest (Maybe Text) Source #

The HTTP version specified in the sampled web request, for example, HTTP/1.1 .

httprCountry :: Lens' HTTPRequest (Maybe Text) Source #

The two-letter country code for the country that the request originated from. For a current list of country codes, see the Wikipedia entry ISO 3166-1 alpha-2 .

httprURI :: Lens' HTTPRequest (Maybe Text) Source #

The part of a web request that identifies the resource, for example, imagesdaily-ad.jpg .

httprHeaders :: Lens' HTTPRequest [HTTPHeader] Source #

A complex type that contains two values for each header in the sampled web request: the name of the header and the value of the header.

httprMethod :: Lens' HTTPRequest (Maybe Text) Source #

The HTTP method specified in the sampled web request. CloudFront supports the following methods: DELETE , GET , HEAD , OPTIONS , PATCH , POST , and PUT .

httprClientIP :: Lens' HTTPRequest (Maybe Text) Source #

The IP address that the request originated from. If the WebACL is associated with a CloudFront distribution, this is the value of one of the following fields in CloudFront access logs: * c-ip , if the viewer did not use an HTTP proxy or a load balancer to send the request * x-forwarded-for , if the viewer did use an HTTP proxy or a load balancer to send the request

IPSet

data IPSet Source #

Contains one or more IP addresses or blocks of IP addresses specified in Classless Inter-Domain Routing (CIDR) notation. AWS WAF supports 8, 16, 24, and 32 IP address ranges for IPv4, and 24, 32, 48, 56, 64 and 128 for IPv6.

To specify an individual IP address, you specify the four-part IP address followed by a /32 , for example, 192.0.2.031. To block a range of IP addresses, you can specify a @128 , 64 , 56 , 48 , 32 , 24 , 16 , or 8@ CIDR. For more information about CIDR notation, see the Wikipedia entry <https:en.wikipedia.orgwiki/Classless_Inter-Domain_Routing Classless Inter-Domain Routing> .

See: ipSet smart constructor.

Instances

Eq IPSet Source # 

Methods

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

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

Data IPSet Source # 

Methods

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

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

toConstr :: IPSet -> Constr #

dataTypeOf :: IPSet -> DataType #

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

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

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

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

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

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

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

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

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

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

Read IPSet Source # 
Show IPSet Source # 

Methods

showsPrec :: Int -> IPSet -> ShowS #

show :: IPSet -> String #

showList :: [IPSet] -> ShowS #

Generic IPSet Source # 

Associated Types

type Rep IPSet :: * -> * #

Methods

from :: IPSet -> Rep IPSet x #

to :: Rep IPSet x -> IPSet #

Hashable IPSet Source # 

Methods

hashWithSalt :: Int -> IPSet -> Int #

hash :: IPSet -> Int #

FromJSON IPSet Source # 
NFData IPSet Source # 

Methods

rnf :: IPSet -> () #

type Rep IPSet Source # 
type Rep IPSet = D1 (MetaData "IPSet" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "IPSet'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_isName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_isIPSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_isIPSetDescriptors") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [IPSetDescriptor])))))

ipSet Source #

Arguments

:: Text

isIPSetId

-> IPSet 

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

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

  • isName - A friendly name or description of the IPSet . You can't change the name of an IPSet after you create it.
  • isIPSetId - The IPSetId for an IPSet . You use IPSetId to get information about an IPSet (see GetIPSet ), update an IPSet (see UpdateIPSet ), insert an IPSet into a Rule or delete one from a Rule (see UpdateRule ), and delete an IPSet from AWS WAF (see DeleteIPSet ). IPSetId is returned by CreateIPSet and by ListIPSets .
  • isIPSetDescriptors - The IP address type (IPV4 or IPV6 ) and the IP address range (in CIDR notation) that web requests originate from. If the WebACL is associated with a CloudFront distribution and the viewer did not use an HTTP proxy or a load balancer to send the request, this is the value of the c-ip field in the CloudFront access logs.

isName :: Lens' IPSet (Maybe Text) Source #

A friendly name or description of the IPSet . You can't change the name of an IPSet after you create it.

isIPSetId :: Lens' IPSet Text Source #

The IPSetId for an IPSet . You use IPSetId to get information about an IPSet (see GetIPSet ), update an IPSet (see UpdateIPSet ), insert an IPSet into a Rule or delete one from a Rule (see UpdateRule ), and delete an IPSet from AWS WAF (see DeleteIPSet ). IPSetId is returned by CreateIPSet and by ListIPSets .

isIPSetDescriptors :: Lens' IPSet [IPSetDescriptor] Source #

The IP address type (IPV4 or IPV6 ) and the IP address range (in CIDR notation) that web requests originate from. If the WebACL is associated with a CloudFront distribution and the viewer did not use an HTTP proxy or a load balancer to send the request, this is the value of the c-ip field in the CloudFront access logs.

IPSetDescriptor

data IPSetDescriptor Source #

Specifies the IP address type (IPV4 or IPV6 ) and the IP address range (in CIDR format) that web requests originate from.

See: ipSetDescriptor smart constructor.

Instances

Eq IPSetDescriptor Source # 
Data IPSetDescriptor Source # 

Methods

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

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

toConstr :: IPSetDescriptor -> Constr #

dataTypeOf :: IPSetDescriptor -> DataType #

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

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

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

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

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

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

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

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

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

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

Read IPSetDescriptor Source # 
Show IPSetDescriptor Source # 
Generic IPSetDescriptor Source # 
Hashable IPSetDescriptor Source # 
FromJSON IPSetDescriptor Source # 
ToJSON IPSetDescriptor Source # 
NFData IPSetDescriptor Source # 

Methods

rnf :: IPSetDescriptor -> () #

type Rep IPSetDescriptor Source # 
type Rep IPSetDescriptor = D1 (MetaData "IPSetDescriptor" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "IPSetDescriptor'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_isdType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 IPSetDescriptorType)) (S1 (MetaSel (Just Symbol "_isdValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

ipSetDescriptor Source #

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

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

  • isdType - Specify IPV4 or IPV6 .
  • isdValue - Specify an IPv4 address by using CIDR notation. For example: * To configure AWS WAF to allow, block, or count requests that originated from the IP address 192.0.2.44, specify 192.0.2.44/32 . * To configure AWS WAF to allow, block, or count requests that originated from IP addresses from 192.0.2.0 to 192.0.2.255, specify 192.0.2.0/24 . For more information about CIDR notation, see the Wikipedia entry Classless Inter-Domain Routing . Specify an IPv6 address by using CIDR notation. For example: * To configure AWS WAF to allow, block, or count requests that originated from the IP address 1111:0000:0000:0000:0000:0000:0000:0111, specify 1111:0000:0000:0000:0000:0000:0000:0111/128 . * To configure AWS WAF to allow, block, or count requests that originated from IP addresses 1111:0000:0000:0000:0000:0000:0000:0000 to 1111:0000:0000:0000:ffff:ffff:ffff:ffff, specify 1111:0000:0000:0000:0000:0000:0000:0000/64 .

isdValue :: Lens' IPSetDescriptor Text Source #

Specify an IPv4 address by using CIDR notation. For example: * To configure AWS WAF to allow, block, or count requests that originated from the IP address 192.0.2.44, specify 192.0.2.44/32 . * To configure AWS WAF to allow, block, or count requests that originated from IP addresses from 192.0.2.0 to 192.0.2.255, specify 192.0.2.0/24 . For more information about CIDR notation, see the Wikipedia entry Classless Inter-Domain Routing . Specify an IPv6 address by using CIDR notation. For example: * To configure AWS WAF to allow, block, or count requests that originated from the IP address 1111:0000:0000:0000:0000:0000:0000:0111, specify 1111:0000:0000:0000:0000:0000:0000:0111/128 . * To configure AWS WAF to allow, block, or count requests that originated from IP addresses 1111:0000:0000:0000:0000:0000:0000:0000 to 1111:0000:0000:0000:ffff:ffff:ffff:ffff, specify 1111:0000:0000:0000:0000:0000:0000:0000/64 .

IPSetSummary

data IPSetSummary Source #

Contains the identifier and the name of the IPSet .

See: ipSetSummary smart constructor.

Instances

Eq IPSetSummary Source # 
Data IPSetSummary Source # 

Methods

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

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

toConstr :: IPSetSummary -> Constr #

dataTypeOf :: IPSetSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read IPSetSummary Source # 
Show IPSetSummary Source # 
Generic IPSetSummary Source # 

Associated Types

type Rep IPSetSummary :: * -> * #

Hashable IPSetSummary Source # 
FromJSON IPSetSummary Source # 
NFData IPSetSummary Source # 

Methods

rnf :: IPSetSummary -> () #

type Rep IPSetSummary Source # 
type Rep IPSetSummary = D1 (MetaData "IPSetSummary" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "IPSetSummary'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_issIPSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_issName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

ipSetSummary Source #

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

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

  • issIPSetId - The IPSetId for an IPSet . You can use IPSetId in a GetIPSet request to get detailed information about an IPSet .
  • issName - A friendly name or description of the IPSet . You can't change the name of an IPSet after you create it.

issIPSetId :: Lens' IPSetSummary Text Source #

The IPSetId for an IPSet . You can use IPSetId in a GetIPSet request to get detailed information about an IPSet .

issName :: Lens' IPSetSummary Text Source #

A friendly name or description of the IPSet . You can't change the name of an IPSet after you create it.

IPSetUpdate

data IPSetUpdate Source #

Specifies the type of update to perform to an IPSet with UpdateIPSet .

See: ipSetUpdate smart constructor.

Instances

Eq IPSetUpdate Source # 
Data IPSetUpdate Source # 

Methods

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

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

toConstr :: IPSetUpdate -> Constr #

dataTypeOf :: IPSetUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read IPSetUpdate Source # 
Show IPSetUpdate Source # 
Generic IPSetUpdate Source # 

Associated Types

type Rep IPSetUpdate :: * -> * #

Hashable IPSetUpdate Source # 
ToJSON IPSetUpdate Source # 
NFData IPSetUpdate Source # 

Methods

rnf :: IPSetUpdate -> () #

type Rep IPSetUpdate Source # 
type Rep IPSetUpdate = D1 (MetaData "IPSetUpdate" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "IPSetUpdate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_isuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction)) (S1 (MetaSel (Just Symbol "_isuIPSetDescriptor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 IPSetDescriptor))))

ipSetUpdate Source #

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

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

  • isuAction - Specifies whether to insert or delete an IP address with UpdateIPSet .
  • isuIPSetDescriptor - The IP address type (IPV4 or IPV6 ) and the IP address range (in CIDR notation) that web requests originate from.

isuAction :: Lens' IPSetUpdate ChangeAction Source #

Specifies whether to insert or delete an IP address with UpdateIPSet .

isuIPSetDescriptor :: Lens' IPSetUpdate IPSetDescriptor Source #

The IP address type (IPV4 or IPV6 ) and the IP address range (in CIDR notation) that web requests originate from.

Predicate

data Predicate Source #

Specifies the ByteMatchSet , IPSet , SqlInjectionMatchSet , XssMatchSet , RegexMatchSet , GeoMatchSet , and SizeConstraintSet objects that you want to add to a Rule and, for each object, indicates whether you want to negate the settings, for example, requests that do NOT originate from the IP address 192.0.2.44.

See: predicate smart constructor.

Instances

Eq Predicate Source # 
Data Predicate Source # 

Methods

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

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

toConstr :: Predicate -> Constr #

dataTypeOf :: Predicate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Predicate Source # 
Show Predicate Source # 
Generic Predicate Source # 

Associated Types

type Rep Predicate :: * -> * #

Hashable Predicate Source # 
FromJSON Predicate Source # 
ToJSON Predicate Source # 
NFData Predicate Source # 

Methods

rnf :: Predicate -> () #

type Rep Predicate Source # 
type Rep Predicate = D1 (MetaData "Predicate" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "Predicate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pNegated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "_pType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PredicateType)) (S1 (MetaSel (Just Symbol "_pDataId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

predicate Source #

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

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

  • pNegated - Set Negated to False if you want AWS WAF to allow, block, or count requests based on the settings in the specified ByteMatchSet , IPSet , SqlInjectionMatchSet , XssMatchSet , RegexMatchSet , GeoMatchSet , or SizeConstraintSet . For example, if an IPSet includes the IP address 192.0.2.44 , AWS WAF will allow or block requests based on that IP address. Set Negated to True if you want AWS WAF to allow or block a request based on the negation of the settings in the ByteMatchSet , IPSet , SqlInjectionMatchSet , XssMatchSet , RegexMatchSet , GeoMatchSet , or SizeConstraintSet . For example, if an IPSet includes the IP address 192.0.2.44 , AWS WAF will allow, block, or count requests based on all IP addresses except 192.0.2.44 .
  • pType - The type of predicate in a Rule , such as ByteMatchSet or IPSet .
  • pDataId - A unique identifier for a predicate in a Rule , such as ByteMatchSetId or IPSetId . The ID is returned by the corresponding Create or List command.

pNegated :: Lens' Predicate Bool Source #

Set Negated to False if you want AWS WAF to allow, block, or count requests based on the settings in the specified ByteMatchSet , IPSet , SqlInjectionMatchSet , XssMatchSet , RegexMatchSet , GeoMatchSet , or SizeConstraintSet . For example, if an IPSet includes the IP address 192.0.2.44 , AWS WAF will allow or block requests based on that IP address. Set Negated to True if you want AWS WAF to allow or block a request based on the negation of the settings in the ByteMatchSet , IPSet , SqlInjectionMatchSet , XssMatchSet , RegexMatchSet , GeoMatchSet , or SizeConstraintSet . For example, if an IPSet includes the IP address 192.0.2.44 , AWS WAF will allow, block, or count requests based on all IP addresses except 192.0.2.44 .

pType :: Lens' Predicate PredicateType Source #

The type of predicate in a Rule , such as ByteMatchSet or IPSet .

pDataId :: Lens' Predicate Text Source #

A unique identifier for a predicate in a Rule , such as ByteMatchSetId or IPSetId . The ID is returned by the corresponding Create or List command.

RateBasedRule

data RateBasedRule Source #

A RateBasedRule is identical to a regular Rule , with one addition: a RateBasedRule counts the number of requests that arrive from a specified IP address every five minutes. For example, based on recent requests that you've seen from an attacker, you might create a RateBasedRule that includes the following conditions:

  • The requests come from 192.0.2.44.
  • They contain the value BadBot in the User-Agent header.

In the rule, you also define the rate limit as 15,000.

Requests that meet both of these conditions and exceed 15,000 requests every five minutes trigger the rule's action (block or count), which is defined in the web ACL.

See: rateBasedRule smart constructor.

Instances

Eq RateBasedRule Source # 
Data RateBasedRule Source # 

Methods

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

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

toConstr :: RateBasedRule -> Constr #

dataTypeOf :: RateBasedRule -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RateBasedRule Source # 
Show RateBasedRule Source # 
Generic RateBasedRule Source # 

Associated Types

type Rep RateBasedRule :: * -> * #

Hashable RateBasedRule Source # 
FromJSON RateBasedRule Source # 
NFData RateBasedRule Source # 

Methods

rnf :: RateBasedRule -> () #

type Rep RateBasedRule Source # 
type Rep RateBasedRule = D1 (MetaData "RateBasedRule" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "RateBasedRule'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rbrMetricName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rbrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rbrRuleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rbrMatchPredicates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Predicate])) ((:*:) (S1 (MetaSel (Just Symbol "_rbrRateKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RateKey)) (S1 (MetaSel (Just Symbol "_rbrRateLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Nat))))))

rateBasedRule Source #

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

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

  • rbrMetricName - A friendly name or description for the metrics for a RateBasedRule . The name can contain only alphanumeric characters (A-Z, a-z, 0-9); the name can't contain whitespace. You can't change the name of the metric after you create the RateBasedRule .
  • rbrName - A friendly name or description for a RateBasedRule . You can't change the name of a RateBasedRule after you create it.
  • rbrRuleId - A unique identifier for a RateBasedRule . You use RuleId to get more information about a RateBasedRule (see GetRateBasedRule ), update a RateBasedRule (see UpdateRateBasedRule ), insert a RateBasedRule into a WebACL or delete one from a WebACL (see UpdateWebACL ), or delete a RateBasedRule from AWS WAF (see DeleteRateBasedRule ).
  • rbrMatchPredicates - The Predicates object contains one Predicate element for each ByteMatchSet , IPSet , or SqlInjectionMatchSet object that you want to include in a RateBasedRule .
  • rbrRateKey - The field that AWS WAF uses to determine if requests are likely arriving from single source and thus subject to rate monitoring. The only valid value for RateKey is IP . IP indicates that requests arriving from the same IP address are subject to the RateLimit that is specified in the RateBasedRule .
  • rbrRateLimit - The maximum number of requests, which have an identical value in the field specified by the RateKey , allowed in a five-minute period. If the number of requests exceeds the RateLimit and the other predicates specified in the rule are also met, AWS WAF triggers the action that is specified for this rule.

rbrMetricName :: Lens' RateBasedRule (Maybe Text) Source #

A friendly name or description for the metrics for a RateBasedRule . The name can contain only alphanumeric characters (A-Z, a-z, 0-9); the name can't contain whitespace. You can't change the name of the metric after you create the RateBasedRule .

rbrName :: Lens' RateBasedRule (Maybe Text) Source #

A friendly name or description for a RateBasedRule . You can't change the name of a RateBasedRule after you create it.

rbrRuleId :: Lens' RateBasedRule Text Source #

A unique identifier for a RateBasedRule . You use RuleId to get more information about a RateBasedRule (see GetRateBasedRule ), update a RateBasedRule (see UpdateRateBasedRule ), insert a RateBasedRule into a WebACL or delete one from a WebACL (see UpdateWebACL ), or delete a RateBasedRule from AWS WAF (see DeleteRateBasedRule ).

rbrMatchPredicates :: Lens' RateBasedRule [Predicate] Source #

The Predicates object contains one Predicate element for each ByteMatchSet , IPSet , or SqlInjectionMatchSet object that you want to include in a RateBasedRule .

rbrRateKey :: Lens' RateBasedRule RateKey Source #

The field that AWS WAF uses to determine if requests are likely arriving from single source and thus subject to rate monitoring. The only valid value for RateKey is IP . IP indicates that requests arriving from the same IP address are subject to the RateLimit that is specified in the RateBasedRule .

rbrRateLimit :: Lens' RateBasedRule Natural Source #

The maximum number of requests, which have an identical value in the field specified by the RateKey , allowed in a five-minute period. If the number of requests exceeds the RateLimit and the other predicates specified in the rule are also met, AWS WAF triggers the action that is specified for this rule.

RegexMatchSet

data RegexMatchSet Source #

In a GetRegexMatchSet request, RegexMatchSet is a complex type that contains the RegexMatchSetId and Name of a RegexMatchSet , and the values that you specified when you updated the RegexMatchSet .

The values are contained in a RegexMatchTuple object, which specify the parts of web requests that you want AWS WAF to inspect and the values that you want AWS WAF to search for. If a RegexMatchSet contains more than one RegexMatchTuple object, a request needs to match the settings in only one ByteMatchTuple to be considered a match.

See: regexMatchSet smart constructor.

Instances

Eq RegexMatchSet Source # 
Data RegexMatchSet Source # 

Methods

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

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

toConstr :: RegexMatchSet -> Constr #

dataTypeOf :: RegexMatchSet -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RegexMatchSet Source # 
Show RegexMatchSet Source # 
Generic RegexMatchSet Source # 

Associated Types

type Rep RegexMatchSet :: * -> * #

Hashable RegexMatchSet Source # 
FromJSON RegexMatchSet Source # 
NFData RegexMatchSet Source # 

Methods

rnf :: RegexMatchSet -> () #

type Rep RegexMatchSet Source # 
type Rep RegexMatchSet = D1 (MetaData "RegexMatchSet" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "RegexMatchSet'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rmsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rmsRegexMatchTuples") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RegexMatchTuple]))) (S1 (MetaSel (Just Symbol "_rmsRegexMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

regexMatchSet :: RegexMatchSet Source #

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

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

  • rmsName - A friendly name or description of the RegexMatchSet . You can't change Name after you create a RegexMatchSet .
  • rmsRegexMatchTuples - Contains an array of RegexMatchTuple objects. Each RegexMatchTuple object contains: * The part of a web request that you want AWS WAF to inspect, such as a query string or the value of the User-Agent header. * The identifier of the pattern (a regular expression) that you want AWS WAF to look for. For more information, see RegexPatternSet . * Whether to perform any conversions on the request, such as converting it to lowercase, before inspecting it for the specified string.
  • rmsRegexMatchSetId - The RegexMatchSetId for a RegexMatchSet . You use RegexMatchSetId to get information about a RegexMatchSet (see GetRegexMatchSet ), update a RegexMatchSet (see UpdateRegexMatchSet ), insert a RegexMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a RegexMatchSet from AWS WAF (see DeleteRegexMatchSet ). RegexMatchSetId is returned by CreateRegexMatchSet and by ListRegexMatchSets .

rmsName :: Lens' RegexMatchSet (Maybe Text) Source #

A friendly name or description of the RegexMatchSet . You can't change Name after you create a RegexMatchSet .

rmsRegexMatchTuples :: Lens' RegexMatchSet [RegexMatchTuple] Source #

Contains an array of RegexMatchTuple objects. Each RegexMatchTuple object contains: * The part of a web request that you want AWS WAF to inspect, such as a query string or the value of the User-Agent header. * The identifier of the pattern (a regular expression) that you want AWS WAF to look for. For more information, see RegexPatternSet . * Whether to perform any conversions on the request, such as converting it to lowercase, before inspecting it for the specified string.

rmsRegexMatchSetId :: Lens' RegexMatchSet (Maybe Text) Source #

The RegexMatchSetId for a RegexMatchSet . You use RegexMatchSetId to get information about a RegexMatchSet (see GetRegexMatchSet ), update a RegexMatchSet (see UpdateRegexMatchSet ), insert a RegexMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a RegexMatchSet from AWS WAF (see DeleteRegexMatchSet ). RegexMatchSetId is returned by CreateRegexMatchSet and by ListRegexMatchSets .

RegexMatchSetSummary

data RegexMatchSetSummary Source #

Returned by ListRegexMatchSets . Each RegexMatchSetSummary object includes the Name and RegexMatchSetId for one RegexMatchSet .

See: regexMatchSetSummary smart constructor.

Instances

Eq RegexMatchSetSummary Source # 
Data RegexMatchSetSummary Source # 

Methods

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

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

toConstr :: RegexMatchSetSummary -> Constr #

dataTypeOf :: RegexMatchSetSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: RegexMatchSetSummary -> () #

type Rep RegexMatchSetSummary Source # 
type Rep RegexMatchSetSummary = D1 (MetaData "RegexMatchSetSummary" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "RegexMatchSetSummary'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rmssRegexMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_rmssName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

regexMatchSetSummary Source #

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

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

  • rmssRegexMatchSetId - The RegexMatchSetId for a RegexMatchSet . You use RegexMatchSetId to get information about a RegexMatchSet , update a RegexMatchSet , remove a RegexMatchSet from a Rule , and delete a RegexMatchSet from AWS WAF. RegexMatchSetId is returned by CreateRegexMatchSet and by ListRegexMatchSets .
  • rmssName - A friendly name or description of the RegexMatchSet . You can't change Name after you create a RegexMatchSet .

rmssRegexMatchSetId :: Lens' RegexMatchSetSummary Text Source #

The RegexMatchSetId for a RegexMatchSet . You use RegexMatchSetId to get information about a RegexMatchSet , update a RegexMatchSet , remove a RegexMatchSet from a Rule , and delete a RegexMatchSet from AWS WAF. RegexMatchSetId is returned by CreateRegexMatchSet and by ListRegexMatchSets .

rmssName :: Lens' RegexMatchSetSummary Text Source #

A friendly name or description of the RegexMatchSet . You can't change Name after you create a RegexMatchSet .

RegexMatchSetUpdate

data RegexMatchSetUpdate Source #

In an UpdateRegexMatchSet request, RegexMatchSetUpdate specifies whether to insert or delete a RegexMatchTuple and includes the settings for the RegexMatchTuple .

See: regexMatchSetUpdate smart constructor.

Instances

Eq RegexMatchSetUpdate Source # 
Data RegexMatchSetUpdate Source # 

Methods

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

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

toConstr :: RegexMatchSetUpdate -> Constr #

dataTypeOf :: RegexMatchSetUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RegexMatchSetUpdate Source # 
Show RegexMatchSetUpdate Source # 
Generic RegexMatchSetUpdate Source # 
Hashable RegexMatchSetUpdate Source # 
ToJSON RegexMatchSetUpdate Source # 
NFData RegexMatchSetUpdate Source # 

Methods

rnf :: RegexMatchSetUpdate -> () #

type Rep RegexMatchSetUpdate Source # 
type Rep RegexMatchSetUpdate = D1 (MetaData "RegexMatchSetUpdate" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "RegexMatchSetUpdate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rmsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction)) (S1 (MetaSel (Just Symbol "_rmsuRegexMatchTuple") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RegexMatchTuple))))

regexMatchSetUpdate Source #

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

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

  • rmsuAction - Specifies whether to insert or delete a RegexMatchTuple .
  • rmsuRegexMatchTuple - Information about the part of a web request that you want AWS WAF to inspect and the identifier of the regular expression (regex) pattern that you want AWS WAF to search for. If you specify DELETE for the value of Action , the RegexMatchTuple values must exactly match the values in the RegexMatchTuple that you want to delete from the RegexMatchSet .

rmsuAction :: Lens' RegexMatchSetUpdate ChangeAction Source #

Specifies whether to insert or delete a RegexMatchTuple .

rmsuRegexMatchTuple :: Lens' RegexMatchSetUpdate RegexMatchTuple Source #

Information about the part of a web request that you want AWS WAF to inspect and the identifier of the regular expression (regex) pattern that you want AWS WAF to search for. If you specify DELETE for the value of Action , the RegexMatchTuple values must exactly match the values in the RegexMatchTuple that you want to delete from the RegexMatchSet .

RegexMatchTuple

data RegexMatchTuple Source #

The regular expression pattern that you want AWS WAF to search for in web requests, the location in requests that you want AWS WAF to search, and other settings. Each RegexMatchTuple object contains:

  • The part of a web request that you want AWS WAF to inspect, such as a query string or the value of the User-Agent header.
  • The identifier of the pattern (a regular expression) that you want AWS WAF to look for. For more information, see RegexPatternSet .
  • Whether to perform any conversions on the request, such as converting it to lowercase, before inspecting it for the specified string.

See: regexMatchTuple smart constructor.

Instances

Eq RegexMatchTuple Source # 
Data RegexMatchTuple Source # 

Methods

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

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

toConstr :: RegexMatchTuple -> Constr #

dataTypeOf :: RegexMatchTuple -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RegexMatchTuple Source # 
Show RegexMatchTuple Source # 
Generic RegexMatchTuple Source # 
Hashable RegexMatchTuple Source # 
FromJSON RegexMatchTuple Source # 
ToJSON RegexMatchTuple Source # 
NFData RegexMatchTuple Source # 

Methods

rnf :: RegexMatchTuple -> () #

type Rep RegexMatchTuple Source # 
type Rep RegexMatchTuple = D1 (MetaData "RegexMatchTuple" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "RegexMatchTuple'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rmtFieldToMatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FieldToMatch)) ((:*:) (S1 (MetaSel (Just Symbol "_rmtTextTransformation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextTransformation)) (S1 (MetaSel (Just Symbol "_rmtRegexPatternSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

regexMatchTuple Source #

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

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

  • rmtFieldToMatch - Specifies where in a web request to look for the RegexPatternSet .
  • rmtTextTransformation - Text transformations eliminate some of the unusual formatting that attackers use in web requests in an effort to bypass AWS WAF. If you specify a transformation, AWS WAF performs the transformation on RegexPatternSet before inspecting a request for a match. CMD_LINE When you're concerned that attackers are injecting an operating system commandline command and using unusual formatting to disguise some or all of the command, use this option to perform the following transformations: * Delete the following characters: " ' ^ * Delete spaces before the following characters: / ( * Replace the following characters with a space: , ; * Replace multiple spaces with one space * Convert uppercase letters (A-Z) to lowercase (a-z) COMPRESS_WHITE_SPACE Use this option to replace the following characters with a space character (decimal 32): * f, formfeed, decimal 12 * t, tab, decimal 9 * n, newline, decimal 10 * r, carriage return, decimal 13 * v, vertical tab, decimal 11 * non-breaking space, decimal 160 COMPRESS_WHITE_SPACE also replaces multiple spaces with one space. HTML_ENTITY_DECODE Use this option to replace HTML-encoded characters with unencoded characters. HTML_ENTITY_DECODE performs the following operations: * Replaces (ampersand)quot; with " * Replaces (ampersand)nbsp; with a non-breaking space, decimal 160 * Replaces (ampersand)lt; with a "less than" symbol * Replaces (ampersand)gt; with > * Replaces characters that are represented in hexadecimal format, (ampersand)#xhhhh; , with the corresponding characters * Replaces characters that are represented in decimal format, (ampersand)#nnnn; , with the corresponding characters LOWERCASE Use this option to convert uppercase letters (A-Z) to lowercase (a-z). URL_DECODE Use this option to decode a URL-encoded value. NONE Specify NONE if you don't want to perform any text transformations.
  • rmtRegexPatternSetId - The RegexPatternSetId for a RegexPatternSet . You use RegexPatternSetId to get information about a RegexPatternSet (see GetRegexPatternSet ), update a RegexPatternSet (see UpdateRegexPatternSet ), insert a RegexPatternSet into a RegexMatchSet or delete one from a RegexMatchSet (see UpdateRegexMatchSet ), and delete an RegexPatternSet from AWS WAF (see DeleteRegexPatternSet ). RegexPatternSetId is returned by CreateRegexPatternSet and by ListRegexPatternSets .

rmtFieldToMatch :: Lens' RegexMatchTuple FieldToMatch Source #

Specifies where in a web request to look for the RegexPatternSet .

rmtTextTransformation :: Lens' RegexMatchTuple TextTransformation Source #

Text transformations eliminate some of the unusual formatting that attackers use in web requests in an effort to bypass AWS WAF. If you specify a transformation, AWS WAF performs the transformation on RegexPatternSet before inspecting a request for a match. CMD_LINE When you're concerned that attackers are injecting an operating system commandline command and using unusual formatting to disguise some or all of the command, use this option to perform the following transformations: * Delete the following characters: " ' ^ * Delete spaces before the following characters: / ( * Replace the following characters with a space: , ; * Replace multiple spaces with one space * Convert uppercase letters (A-Z) to lowercase (a-z) COMPRESS_WHITE_SPACE Use this option to replace the following characters with a space character (decimal 32): * f, formfeed, decimal 12 * t, tab, decimal 9 * n, newline, decimal 10 * r, carriage return, decimal 13 * v, vertical tab, decimal 11 * non-breaking space, decimal 160 COMPRESS_WHITE_SPACE also replaces multiple spaces with one space. HTML_ENTITY_DECODE Use this option to replace HTML-encoded characters with unencoded characters. HTML_ENTITY_DECODE performs the following operations: * Replaces (ampersand)quot; with " * Replaces (ampersand)nbsp; with a non-breaking space, decimal 160 * Replaces (ampersand)lt; with a "less than" symbol * Replaces (ampersand)gt; with > * Replaces characters that are represented in hexadecimal format, (ampersand)#xhhhh; , with the corresponding characters * Replaces characters that are represented in decimal format, (ampersand)#nnnn; , with the corresponding characters LOWERCASE Use this option to convert uppercase letters (A-Z) to lowercase (a-z). URL_DECODE Use this option to decode a URL-encoded value. NONE Specify NONE if you don't want to perform any text transformations.

rmtRegexPatternSetId :: Lens' RegexMatchTuple Text Source #

The RegexPatternSetId for a RegexPatternSet . You use RegexPatternSetId to get information about a RegexPatternSet (see GetRegexPatternSet ), update a RegexPatternSet (see UpdateRegexPatternSet ), insert a RegexPatternSet into a RegexMatchSet or delete one from a RegexMatchSet (see UpdateRegexMatchSet ), and delete an RegexPatternSet from AWS WAF (see DeleteRegexPatternSet ). RegexPatternSetId is returned by CreateRegexPatternSet and by ListRegexPatternSets .

RegexPatternSet

data RegexPatternSet Source #

The RegexPatternSet specifies the regular expression (regex) pattern that you want AWS WAF to search for, such as B[a]dB[o0]t@ . You can then configure AWS WAF to reject those requests.

See: regexPatternSet smart constructor.

Instances

Eq RegexPatternSet Source # 
Data RegexPatternSet Source # 

Methods

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

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

toConstr :: RegexPatternSet -> Constr #

dataTypeOf :: RegexPatternSet -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: RegexPatternSet -> () #

type Rep RegexPatternSet Source # 
type Rep RegexPatternSet = D1 (MetaData "RegexPatternSet" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "RegexPatternSet'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rpsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rpsRegexPatternSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_rpsRegexPatternStrings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text])))))

regexPatternSet Source #

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

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

  • rpsName - A friendly name or description of the RegexPatternSet . You can't change Name after you create a RegexPatternSet .
  • rpsRegexPatternSetId - The identifier for the RegexPatternSet . You use RegexPatternSetId to get information about a RegexPatternSet , update a RegexPatternSet , remove a RegexPatternSet from a RegexMatchSet , and delete a RegexPatternSet from AWS WAF. RegexMatchSetId is returned by CreateRegexPatternSet and by ListRegexPatternSets .
  • rpsRegexPatternStrings - Specifies the regular expression (regex) patterns that you want AWS WAF to search for, such as B[a]dB[o0]t@ .

rpsName :: Lens' RegexPatternSet (Maybe Text) Source #

A friendly name or description of the RegexPatternSet . You can't change Name after you create a RegexPatternSet .

rpsRegexPatternSetId :: Lens' RegexPatternSet Text Source #

The identifier for the RegexPatternSet . You use RegexPatternSetId to get information about a RegexPatternSet , update a RegexPatternSet , remove a RegexPatternSet from a RegexMatchSet , and delete a RegexPatternSet from AWS WAF. RegexMatchSetId is returned by CreateRegexPatternSet and by ListRegexPatternSets .

rpsRegexPatternStrings :: Lens' RegexPatternSet [Text] Source #

Specifies the regular expression (regex) patterns that you want AWS WAF to search for, such as B[a]dB[o0]t@ .

RegexPatternSetSummary

data RegexPatternSetSummary Source #

Returned by ListRegexPatternSets . Each RegexPatternSetSummary object includes the Name and RegexPatternSetId for one RegexPatternSet .

See: regexPatternSetSummary smart constructor.

Instances

Eq RegexPatternSetSummary Source # 
Data RegexPatternSetSummary Source # 

Methods

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

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

toConstr :: RegexPatternSetSummary -> Constr #

dataTypeOf :: RegexPatternSetSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: RegexPatternSetSummary -> () #

type Rep RegexPatternSetSummary Source # 
type Rep RegexPatternSetSummary = D1 (MetaData "RegexPatternSetSummary" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "RegexPatternSetSummary'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rpssRegexPatternSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_rpssName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

regexPatternSetSummary Source #

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

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

  • rpssRegexPatternSetId - The RegexPatternSetId for a RegexPatternSet . You use RegexPatternSetId to get information about a RegexPatternSet , update a RegexPatternSet , remove a RegexPatternSet from a RegexMatchSet , and delete a RegexPatternSet from AWS WAF. RegexPatternSetId is returned by CreateRegexPatternSet and by ListRegexPatternSets .
  • rpssName - A friendly name or description of the RegexPatternSet . You can't change Name after you create a RegexPatternSet .

rpssRegexPatternSetId :: Lens' RegexPatternSetSummary Text Source #

The RegexPatternSetId for a RegexPatternSet . You use RegexPatternSetId to get information about a RegexPatternSet , update a RegexPatternSet , remove a RegexPatternSet from a RegexMatchSet , and delete a RegexPatternSet from AWS WAF. RegexPatternSetId is returned by CreateRegexPatternSet and by ListRegexPatternSets .

rpssName :: Lens' RegexPatternSetSummary Text Source #

A friendly name or description of the RegexPatternSet . You can't change Name after you create a RegexPatternSet .

RegexPatternSetUpdate

data RegexPatternSetUpdate Source #

In an UpdateRegexPatternSet request, RegexPatternSetUpdate specifies whether to insert or delete a RegexPatternString and includes the settings for the RegexPatternString .

See: regexPatternSetUpdate smart constructor.

Instances

Eq RegexPatternSetUpdate Source # 
Data RegexPatternSetUpdate Source # 

Methods

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

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

toConstr :: RegexPatternSetUpdate -> Constr #

dataTypeOf :: RegexPatternSetUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RegexPatternSetUpdate Source # 
Show RegexPatternSetUpdate Source # 
Generic RegexPatternSetUpdate Source # 
Hashable RegexPatternSetUpdate Source # 
ToJSON RegexPatternSetUpdate Source # 
NFData RegexPatternSetUpdate Source # 

Methods

rnf :: RegexPatternSetUpdate -> () #

type Rep RegexPatternSetUpdate Source # 
type Rep RegexPatternSetUpdate = D1 (MetaData "RegexPatternSetUpdate" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "RegexPatternSetUpdate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rpsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction)) (S1 (MetaSel (Just Symbol "_rpsuRegexPatternString") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

regexPatternSetUpdate Source #

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

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

  • rpsuAction - Specifies whether to insert or delete a RegexPatternString .
  • rpsuRegexPatternString - Specifies the regular expression (regex) pattern that you want AWS WAF to search for, such as B[a]dB[o0]t@ .

rpsuAction :: Lens' RegexPatternSetUpdate ChangeAction Source #

Specifies whether to insert or delete a RegexPatternString .

rpsuRegexPatternString :: Lens' RegexPatternSetUpdate Text Source #

Specifies the regular expression (regex) pattern that you want AWS WAF to search for, such as B[a]dB[o0]t@ .

Rule

data Rule Source #

A combination of ByteMatchSet , IPSet , and/or SqlInjectionMatchSet objects that identify the web requests that you want to allow, block, or count. For example, you might create a Rule that includes the following predicates:

  • An IPSet that causes AWS WAF to search for web requests that originate from the IP address 192.0.2.44
  • A ByteMatchSet that causes AWS WAF to search for web requests for which the value of the User-Agent header is BadBot .

To match the settings in this Rule , a request must originate from 192.0.2.44 AND include a User-Agent header for which the value is BadBot .

See: rule smart constructor.

Instances

Eq Rule Source # 

Methods

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

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

Data Rule Source # 

Methods

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

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

toConstr :: Rule -> Constr #

dataTypeOf :: Rule -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Rule Source # 
Show Rule Source # 

Methods

showsPrec :: Int -> Rule -> ShowS #

show :: Rule -> String #

showList :: [Rule] -> ShowS #

Generic Rule Source # 

Associated Types

type Rep Rule :: * -> * #

Methods

from :: Rule -> Rep Rule x #

to :: Rep Rule x -> Rule #

Hashable Rule Source # 

Methods

hashWithSalt :: Int -> Rule -> Int #

hash :: Rule -> Int #

FromJSON Rule Source # 
NFData Rule Source # 

Methods

rnf :: Rule -> () #

type Rep Rule Source # 
type Rep Rule = D1 (MetaData "Rule" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "Rule'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rMetricName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rRuleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_rPredicates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Predicate])))))

rule Source #

Arguments

:: Text

rRuleId

-> Rule 

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

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

  • rMetricName - A friendly name or description for the metrics for this Rule . The name can contain only alphanumeric characters (A-Z, a-z, 0-9); the name can't contain whitespace. You can't change MetricName after you create the Rule .
  • rName - The friendly name or description for the Rule . You can't change the name of a Rule after you create it.
  • rRuleId - A unique identifier for a Rule . You use RuleId to get more information about a Rule (see GetRule ), update a Rule (see UpdateRule ), insert a Rule into a WebACL or delete a one from a WebACL (see UpdateWebACL ), or delete a Rule from AWS WAF (see DeleteRule ). RuleId is returned by CreateRule and by ListRules .
  • rPredicates - The Predicates object contains one Predicate element for each ByteMatchSet , IPSet , or SqlInjectionMatchSet object that you want to include in a Rule .

rMetricName :: Lens' Rule (Maybe Text) Source #

A friendly name or description for the metrics for this Rule . The name can contain only alphanumeric characters (A-Z, a-z, 0-9); the name can't contain whitespace. You can't change MetricName after you create the Rule .

rName :: Lens' Rule (Maybe Text) Source #

The friendly name or description for the Rule . You can't change the name of a Rule after you create it.

rRuleId :: Lens' Rule Text Source #

A unique identifier for a Rule . You use RuleId to get more information about a Rule (see GetRule ), update a Rule (see UpdateRule ), insert a Rule into a WebACL or delete a one from a WebACL (see UpdateWebACL ), or delete a Rule from AWS WAF (see DeleteRule ). RuleId is returned by CreateRule and by ListRules .

rPredicates :: Lens' Rule [Predicate] Source #

The Predicates object contains one Predicate element for each ByteMatchSet , IPSet , or SqlInjectionMatchSet object that you want to include in a Rule .

RuleSummary

data RuleSummary Source #

Contains the identifier and the friendly name or description of the Rule .

See: ruleSummary smart constructor.

Instances

Eq RuleSummary Source # 
Data RuleSummary Source # 

Methods

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

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

toConstr :: RuleSummary -> Constr #

dataTypeOf :: RuleSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RuleSummary Source # 
Show RuleSummary Source # 
Generic RuleSummary Source # 

Associated Types

type Rep RuleSummary :: * -> * #

Hashable RuleSummary Source # 
FromJSON RuleSummary Source # 
NFData RuleSummary Source # 

Methods

rnf :: RuleSummary -> () #

type Rep RuleSummary Source # 
type Rep RuleSummary = D1 (MetaData "RuleSummary" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "RuleSummary'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rsRuleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_rsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

ruleSummary Source #

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

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

  • rsRuleId - A unique identifier for a Rule . You use RuleId to get more information about a Rule (see GetRule ), update a Rule (see UpdateRule ), insert a Rule into a WebACL or delete one from a WebACL (see UpdateWebACL ), or delete a Rule from AWS WAF (see DeleteRule ). RuleId is returned by CreateRule and by ListRules .
  • rsName - A friendly name or description of the Rule . You can't change the name of a Rule after you create it.

rsRuleId :: Lens' RuleSummary Text Source #

A unique identifier for a Rule . You use RuleId to get more information about a Rule (see GetRule ), update a Rule (see UpdateRule ), insert a Rule into a WebACL or delete one from a WebACL (see UpdateWebACL ), or delete a Rule from AWS WAF (see DeleteRule ). RuleId is returned by CreateRule and by ListRules .

rsName :: Lens' RuleSummary Text Source #

A friendly name or description of the Rule . You can't change the name of a Rule after you create it.

RuleUpdate

data RuleUpdate Source #

Specifies a Predicate (such as an IPSet ) and indicates whether you want to add it to a Rule or delete it from a Rule .

See: ruleUpdate smart constructor.

Instances

Eq RuleUpdate Source # 
Data RuleUpdate Source # 

Methods

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

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

toConstr :: RuleUpdate -> Constr #

dataTypeOf :: RuleUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RuleUpdate Source # 
Show RuleUpdate Source # 
Generic RuleUpdate Source # 

Associated Types

type Rep RuleUpdate :: * -> * #

Hashable RuleUpdate Source # 
ToJSON RuleUpdate Source # 
NFData RuleUpdate Source # 

Methods

rnf :: RuleUpdate -> () #

type Rep RuleUpdate Source # 
type Rep RuleUpdate = D1 (MetaData "RuleUpdate" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "RuleUpdate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ruAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction)) (S1 (MetaSel (Just Symbol "_ruPredicate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Predicate))))

ruleUpdate Source #

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

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

  • ruAction - Specify INSERT to add a Predicate to a Rule . Use DELETE to remove a Predicate from a Rule .
  • ruPredicate - The ID of the Predicate (such as an IPSet ) that you want to add to a Rule .

ruAction :: Lens' RuleUpdate ChangeAction Source #

Specify INSERT to add a Predicate to a Rule . Use DELETE to remove a Predicate from a Rule .

ruPredicate :: Lens' RuleUpdate Predicate Source #

The ID of the Predicate (such as an IPSet ) that you want to add to a Rule .

SampledHTTPRequest

data SampledHTTPRequest Source #

The response from a GetSampledRequests request includes a SampledHTTPRequests complex type that appears as SampledRequests in the response syntax. SampledHTTPRequests contains one SampledHTTPRequest object for each web request that is returned by GetSampledRequests .

See: sampledHTTPRequest smart constructor.

Instances

Eq SampledHTTPRequest Source # 
Data SampledHTTPRequest Source # 

Methods

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

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

toConstr :: SampledHTTPRequest -> Constr #

dataTypeOf :: SampledHTTPRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: SampledHTTPRequest -> () #

type Rep SampledHTTPRequest Source # 
type Rep SampledHTTPRequest = D1 (MetaData "SampledHTTPRequest" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "SampledHTTPRequest'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_shttprAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_shttprTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)))) ((:*:) (S1 (MetaSel (Just Symbol "_shttprRequest") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HTTPRequest)) (S1 (MetaSel (Just Symbol "_shttprWeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Nat)))))

sampledHTTPRequest Source #

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

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

  • shttprAction - The action for the Rule that the request matched: ALLOW , BLOCK , or COUNT .
  • shttprTimestamp - The time at which AWS WAF received the request from your AWS resource, in Unix time format (in seconds).
  • shttprRequest - A complex type that contains detailed information about the request.
  • shttprWeight - A value that indicates how one result in the response relates proportionally to other results in the response. A result that has a weight of 2 represents roughly twice as many CloudFront web requests as a result that has a weight of 1 .

shttprAction :: Lens' SampledHTTPRequest (Maybe Text) Source #

The action for the Rule that the request matched: ALLOW , BLOCK , or COUNT .

shttprTimestamp :: Lens' SampledHTTPRequest (Maybe UTCTime) Source #

The time at which AWS WAF received the request from your AWS resource, in Unix time format (in seconds).

shttprRequest :: Lens' SampledHTTPRequest HTTPRequest Source #

A complex type that contains detailed information about the request.

shttprWeight :: Lens' SampledHTTPRequest Natural Source #

A value that indicates how one result in the response relates proportionally to other results in the response. A result that has a weight of 2 represents roughly twice as many CloudFront web requests as a result that has a weight of 1 .

SizeConstraint

data SizeConstraint Source #

Specifies a constraint on the size of a part of the web request. AWS WAF uses the Size , ComparisonOperator , and FieldToMatch to build an expression in the form of "Size ComparisonOperator size in bytes of FieldToMatch ". If that expression is true, the SizeConstraint is considered to match.

See: sizeConstraint smart constructor.

Instances

Eq SizeConstraint Source # 
Data SizeConstraint Source # 

Methods

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

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

toConstr :: SizeConstraint -> Constr #

dataTypeOf :: SizeConstraint -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SizeConstraint Source # 
Show SizeConstraint Source # 
Generic SizeConstraint Source # 

Associated Types

type Rep SizeConstraint :: * -> * #

Hashable SizeConstraint Source # 
FromJSON SizeConstraint Source # 
ToJSON SizeConstraint Source # 
NFData SizeConstraint Source # 

Methods

rnf :: SizeConstraint -> () #

type Rep SizeConstraint Source # 
type Rep SizeConstraint = D1 (MetaData "SizeConstraint" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "SizeConstraint'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_scFieldToMatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FieldToMatch)) (S1 (MetaSel (Just Symbol "_scTextTransformation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextTransformation))) ((:*:) (S1 (MetaSel (Just Symbol "_scComparisonOperator") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ComparisonOperator)) (S1 (MetaSel (Just Symbol "_scSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Nat)))))

sizeConstraint Source #

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

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

  • scFieldToMatch - Specifies where in a web request to look for the size constraint.
  • scTextTransformation - Text transformations eliminate some of the unusual formatting that attackers use in web requests in an effort to bypass AWS WAF. If you specify a transformation, AWS WAF performs the transformation on FieldToMatch before inspecting a request for a match. Note that if you choose BODY for the value of Type , you must choose NONE for TextTransformation because CloudFront forwards only the first 8192 bytes for inspection. NONE Specify NONE if you don't want to perform any text transformations. CMD_LINE When you're concerned that attackers are injecting an operating system command line command and using unusual formatting to disguise some or all of the command, use this option to perform the following transformations: * Delete the following characters: " ' ^ * Delete spaces before the following characters: / ( * Replace the following characters with a space: , ; * Replace multiple spaces with one space * Convert uppercase letters (A-Z) to lowercase (a-z) COMPRESS_WHITE_SPACE Use this option to replace the following characters with a space character (decimal 32): * f, formfeed, decimal 12 * t, tab, decimal 9 * n, newline, decimal 10 * r, carriage return, decimal 13 * v, vertical tab, decimal 11 * non-breaking space, decimal 160 COMPRESS_WHITE_SPACE also replaces multiple spaces with one space. HTML_ENTITY_DECODE Use this option to replace HTML-encoded characters with unencoded characters. HTML_ENTITY_DECODE performs the following operations: * Replaces (ampersand)quot; with " * Replaces (ampersand)nbsp; with a non-breaking space, decimal 160 * Replaces (ampersand)lt; with a "less than" symbol * Replaces (ampersand)gt; with > * Replaces characters that are represented in hexadecimal format, (ampersand)#xhhhh; , with the corresponding characters * Replaces characters that are represented in decimal format, (ampersand)#nnnn; , with the corresponding characters LOWERCASE Use this option to convert uppercase letters (A-Z) to lowercase (a-z). URL_DECODE Use this option to decode a URL-encoded value.
  • scComparisonOperator - The type of comparison you want AWS WAF to perform. AWS WAF uses this in combination with the provided Size and FieldToMatch to build an expression in the form of "Size ComparisonOperator size in bytes of FieldToMatch ". If that expression is true, the SizeConstraint is considered to match. EQ : Used to test if the Size is equal to the size of the FieldToMatch NE : Used to test if the Size is not equal to the size of the FieldToMatch LE : Used to test if the Size is less than or equal to the size of the FieldToMatch LT : Used to test if the Size is strictly less than the size of the FieldToMatch GE : Used to test if the Size is greater than or equal to the size of the FieldToMatch GT : Used to test if the Size is strictly greater than the size of the FieldToMatch
  • scSize - The size in bytes that you want AWS WAF to compare against the size of the specified FieldToMatch . AWS WAF uses this in combination with ComparisonOperator and FieldToMatch to build an expression in the form of "Size ComparisonOperator size in bytes of FieldToMatch ". If that expression is true, the SizeConstraint is considered to match. Valid values for size are 0 - 21474836480 bytes (0 - 20 GB). If you specify URI for the value of Type , the in the URI counts as one character. For example, the URI @logo.jpg@ is nine characters long.

scFieldToMatch :: Lens' SizeConstraint FieldToMatch Source #

Specifies where in a web request to look for the size constraint.

scTextTransformation :: Lens' SizeConstraint TextTransformation Source #

Text transformations eliminate some of the unusual formatting that attackers use in web requests in an effort to bypass AWS WAF. If you specify a transformation, AWS WAF performs the transformation on FieldToMatch before inspecting a request for a match. Note that if you choose BODY for the value of Type , you must choose NONE for TextTransformation because CloudFront forwards only the first 8192 bytes for inspection. NONE Specify NONE if you don't want to perform any text transformations. CMD_LINE When you're concerned that attackers are injecting an operating system command line command and using unusual formatting to disguise some or all of the command, use this option to perform the following transformations: * Delete the following characters: " ' ^ * Delete spaces before the following characters: / ( * Replace the following characters with a space: , ; * Replace multiple spaces with one space * Convert uppercase letters (A-Z) to lowercase (a-z) COMPRESS_WHITE_SPACE Use this option to replace the following characters with a space character (decimal 32): * f, formfeed, decimal 12 * t, tab, decimal 9 * n, newline, decimal 10 * r, carriage return, decimal 13 * v, vertical tab, decimal 11 * non-breaking space, decimal 160 COMPRESS_WHITE_SPACE also replaces multiple spaces with one space. HTML_ENTITY_DECODE Use this option to replace HTML-encoded characters with unencoded characters. HTML_ENTITY_DECODE performs the following operations: * Replaces (ampersand)quot; with " * Replaces (ampersand)nbsp; with a non-breaking space, decimal 160 * Replaces (ampersand)lt; with a "less than" symbol * Replaces (ampersand)gt; with > * Replaces characters that are represented in hexadecimal format, (ampersand)#xhhhh; , with the corresponding characters * Replaces characters that are represented in decimal format, (ampersand)#nnnn; , with the corresponding characters LOWERCASE Use this option to convert uppercase letters (A-Z) to lowercase (a-z). URL_DECODE Use this option to decode a URL-encoded value.

scComparisonOperator :: Lens' SizeConstraint ComparisonOperator Source #

The type of comparison you want AWS WAF to perform. AWS WAF uses this in combination with the provided Size and FieldToMatch to build an expression in the form of "Size ComparisonOperator size in bytes of FieldToMatch ". If that expression is true, the SizeConstraint is considered to match. EQ : Used to test if the Size is equal to the size of the FieldToMatch NE : Used to test if the Size is not equal to the size of the FieldToMatch LE : Used to test if the Size is less than or equal to the size of the FieldToMatch LT : Used to test if the Size is strictly less than the size of the FieldToMatch GE : Used to test if the Size is greater than or equal to the size of the FieldToMatch GT : Used to test if the Size is strictly greater than the size of the FieldToMatch

scSize :: Lens' SizeConstraint Natural Source #

The size in bytes that you want AWS WAF to compare against the size of the specified FieldToMatch . AWS WAF uses this in combination with ComparisonOperator and FieldToMatch to build an expression in the form of "Size ComparisonOperator size in bytes of FieldToMatch ". If that expression is true, the SizeConstraint is considered to match. Valid values for size are 0 - 21474836480 bytes (0 - 20 GB). If you specify URI for the value of Type , the in the URI counts as one character. For example, the URI @logo.jpg@ is nine characters long.

SizeConstraintSet

data SizeConstraintSet Source #

A complex type that contains SizeConstraint objects, which specify the parts of web requests that you want AWS WAF to inspect the size of. If a SizeConstraintSet contains more than one SizeConstraint object, a request only needs to match one constraint to be considered a match.

See: sizeConstraintSet smart constructor.

Instances

Eq SizeConstraintSet Source # 
Data SizeConstraintSet Source # 

Methods

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

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

toConstr :: SizeConstraintSet -> Constr #

dataTypeOf :: SizeConstraintSet -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: SizeConstraintSet -> () #

type Rep SizeConstraintSet Source # 
type Rep SizeConstraintSet = D1 (MetaData "SizeConstraintSet" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "SizeConstraintSet'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_scsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_scsSizeConstraintSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_scsSizeConstraints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [SizeConstraint])))))

sizeConstraintSet Source #

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

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

  • scsName - The name, if any, of the SizeConstraintSet .
  • scsSizeConstraintSetId - A unique identifier for a SizeConstraintSet . You use SizeConstraintSetId to get information about a SizeConstraintSet (see GetSizeConstraintSet ), update a SizeConstraintSet (see UpdateSizeConstraintSet ), insert a SizeConstraintSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a SizeConstraintSet from AWS WAF (see DeleteSizeConstraintSet ). SizeConstraintSetId is returned by CreateSizeConstraintSet and by ListSizeConstraintSets .
  • scsSizeConstraints - Specifies the parts of web requests that you want to inspect the size of.

scsName :: Lens' SizeConstraintSet (Maybe Text) Source #

The name, if any, of the SizeConstraintSet .

scsSizeConstraintSetId :: Lens' SizeConstraintSet Text Source #

A unique identifier for a SizeConstraintSet . You use SizeConstraintSetId to get information about a SizeConstraintSet (see GetSizeConstraintSet ), update a SizeConstraintSet (see UpdateSizeConstraintSet ), insert a SizeConstraintSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a SizeConstraintSet from AWS WAF (see DeleteSizeConstraintSet ). SizeConstraintSetId is returned by CreateSizeConstraintSet and by ListSizeConstraintSets .

scsSizeConstraints :: Lens' SizeConstraintSet [SizeConstraint] Source #

Specifies the parts of web requests that you want to inspect the size of.

SizeConstraintSetSummary

data SizeConstraintSetSummary Source #

The Id and Name of a SizeConstraintSet .

See: sizeConstraintSetSummary smart constructor.

Instances

Eq SizeConstraintSetSummary Source # 
Data SizeConstraintSetSummary Source # 

Methods

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

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

toConstr :: SizeConstraintSetSummary -> Constr #

dataTypeOf :: SizeConstraintSetSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SizeConstraintSetSummary Source # 
Show SizeConstraintSetSummary Source # 
Generic SizeConstraintSetSummary Source # 
Hashable SizeConstraintSetSummary Source # 
FromJSON SizeConstraintSetSummary Source # 
NFData SizeConstraintSetSummary Source # 
type Rep SizeConstraintSetSummary Source # 
type Rep SizeConstraintSetSummary = D1 (MetaData "SizeConstraintSetSummary" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "SizeConstraintSetSummary'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_scssSizeConstraintSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_scssName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

sizeConstraintSetSummary Source #

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

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

  • scssSizeConstraintSetId - A unique identifier for a SizeConstraintSet . You use SizeConstraintSetId to get information about a SizeConstraintSet (see GetSizeConstraintSet ), update a SizeConstraintSet (see UpdateSizeConstraintSet ), insert a SizeConstraintSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a SizeConstraintSet from AWS WAF (see DeleteSizeConstraintSet ). SizeConstraintSetId is returned by CreateSizeConstraintSet and by ListSizeConstraintSets .
  • scssName - The name of the SizeConstraintSet , if any.

scssSizeConstraintSetId :: Lens' SizeConstraintSetSummary Text Source #

A unique identifier for a SizeConstraintSet . You use SizeConstraintSetId to get information about a SizeConstraintSet (see GetSizeConstraintSet ), update a SizeConstraintSet (see UpdateSizeConstraintSet ), insert a SizeConstraintSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a SizeConstraintSet from AWS WAF (see DeleteSizeConstraintSet ). SizeConstraintSetId is returned by CreateSizeConstraintSet and by ListSizeConstraintSets .

scssName :: Lens' SizeConstraintSetSummary Text Source #

The name of the SizeConstraintSet , if any.

SizeConstraintSetUpdate

data SizeConstraintSetUpdate Source #

Specifies the part of a web request that you want to inspect the size of and indicates whether you want to add the specification to a SizeConstraintSet or delete it from a SizeConstraintSet .

See: sizeConstraintSetUpdate smart constructor.

Instances

Eq SizeConstraintSetUpdate Source # 
Data SizeConstraintSetUpdate Source # 

Methods

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

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

toConstr :: SizeConstraintSetUpdate -> Constr #

dataTypeOf :: SizeConstraintSetUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SizeConstraintSetUpdate Source # 
Show SizeConstraintSetUpdate Source # 
Generic SizeConstraintSetUpdate Source # 
Hashable SizeConstraintSetUpdate Source # 
ToJSON SizeConstraintSetUpdate Source # 
NFData SizeConstraintSetUpdate Source # 

Methods

rnf :: SizeConstraintSetUpdate -> () #

type Rep SizeConstraintSetUpdate Source # 
type Rep SizeConstraintSetUpdate = D1 (MetaData "SizeConstraintSetUpdate" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "SizeConstraintSetUpdate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_scsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction)) (S1 (MetaSel (Just Symbol "_scsuSizeConstraint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SizeConstraint))))

sizeConstraintSetUpdate Source #

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

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

  • scsuAction - Specify INSERT to add a SizeConstraintSetUpdate to a SizeConstraintSet . Use DELETE to remove a SizeConstraintSetUpdate from a SizeConstraintSet .
  • scsuSizeConstraint - Specifies a constraint on the size of a part of the web request. AWS WAF uses the Size , ComparisonOperator , and FieldToMatch to build an expression in the form of "Size ComparisonOperator size in bytes of FieldToMatch ". If that expression is true, the SizeConstraint is considered to match.

scsuAction :: Lens' SizeConstraintSetUpdate ChangeAction Source #

Specify INSERT to add a SizeConstraintSetUpdate to a SizeConstraintSet . Use DELETE to remove a SizeConstraintSetUpdate from a SizeConstraintSet .

scsuSizeConstraint :: Lens' SizeConstraintSetUpdate SizeConstraint Source #

Specifies a constraint on the size of a part of the web request. AWS WAF uses the Size , ComparisonOperator , and FieldToMatch to build an expression in the form of "Size ComparisonOperator size in bytes of FieldToMatch ". If that expression is true, the SizeConstraint is considered to match.

SqlInjectionMatchSet

data SqlInjectionMatchSet Source #

A complex type that contains SqlInjectionMatchTuple objects, which specify the parts of web requests that you want AWS WAF to inspect for snippets of malicious SQL code and, if you want AWS WAF to inspect a header, the name of the header. If a SqlInjectionMatchSet contains more than one SqlInjectionMatchTuple object, a request needs to include snippets of SQL code in only one of the specified parts of the request to be considered a match.

See: sqlInjectionMatchSet smart constructor.

Instances

Eq SqlInjectionMatchSet Source # 
Data SqlInjectionMatchSet Source # 

Methods

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

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

toConstr :: SqlInjectionMatchSet -> Constr #

dataTypeOf :: SqlInjectionMatchSet -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: SqlInjectionMatchSet -> () #

type Rep SqlInjectionMatchSet Source # 
type Rep SqlInjectionMatchSet = D1 (MetaData "SqlInjectionMatchSet" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "SqlInjectionMatchSet'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_simsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_simsSqlInjectionMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_simsSqlInjectionMatchTuples") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [SqlInjectionMatchTuple])))))

sqlInjectionMatchSet Source #

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

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

  • simsName - The name, if any, of the SqlInjectionMatchSet .
  • simsSqlInjectionMatchSetId - A unique identifier for a SqlInjectionMatchSet . You use SqlInjectionMatchSetId to get information about a SqlInjectionMatchSet (see GetSqlInjectionMatchSet ), update a SqlInjectionMatchSet (see UpdateSqlInjectionMatchSet ), insert a SqlInjectionMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a SqlInjectionMatchSet from AWS WAF (see DeleteSqlInjectionMatchSet ). SqlInjectionMatchSetId is returned by CreateSqlInjectionMatchSet and by ListSqlInjectionMatchSets .
  • simsSqlInjectionMatchTuples - Specifies the parts of web requests that you want to inspect for snippets of malicious SQL code.

simsName :: Lens' SqlInjectionMatchSet (Maybe Text) Source #

The name, if any, of the SqlInjectionMatchSet .

simsSqlInjectionMatchSetId :: Lens' SqlInjectionMatchSet Text Source #

A unique identifier for a SqlInjectionMatchSet . You use SqlInjectionMatchSetId to get information about a SqlInjectionMatchSet (see GetSqlInjectionMatchSet ), update a SqlInjectionMatchSet (see UpdateSqlInjectionMatchSet ), insert a SqlInjectionMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a SqlInjectionMatchSet from AWS WAF (see DeleteSqlInjectionMatchSet ). SqlInjectionMatchSetId is returned by CreateSqlInjectionMatchSet and by ListSqlInjectionMatchSets .

simsSqlInjectionMatchTuples :: Lens' SqlInjectionMatchSet [SqlInjectionMatchTuple] Source #

Specifies the parts of web requests that you want to inspect for snippets of malicious SQL code.

SqlInjectionMatchSetSummary

data SqlInjectionMatchSetSummary Source #

The Id and Name of a SqlInjectionMatchSet .

See: sqlInjectionMatchSetSummary smart constructor.

Instances

Eq SqlInjectionMatchSetSummary Source # 
Data SqlInjectionMatchSetSummary Source # 

Methods

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

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

toConstr :: SqlInjectionMatchSetSummary -> Constr #

dataTypeOf :: SqlInjectionMatchSetSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SqlInjectionMatchSetSummary Source # 
Show SqlInjectionMatchSetSummary Source # 
Generic SqlInjectionMatchSetSummary Source # 
Hashable SqlInjectionMatchSetSummary Source # 
FromJSON SqlInjectionMatchSetSummary Source # 
NFData SqlInjectionMatchSetSummary Source # 
type Rep SqlInjectionMatchSetSummary Source # 
type Rep SqlInjectionMatchSetSummary = D1 (MetaData "SqlInjectionMatchSetSummary" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "SqlInjectionMatchSetSummary'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_simssSqlInjectionMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_simssName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

sqlInjectionMatchSetSummary Source #

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

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

  • simssSqlInjectionMatchSetId - A unique identifier for a SqlInjectionMatchSet . You use SqlInjectionMatchSetId to get information about a SqlInjectionMatchSet (see GetSqlInjectionMatchSet ), update a SqlInjectionMatchSet (see UpdateSqlInjectionMatchSet ), insert a SqlInjectionMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a SqlInjectionMatchSet from AWS WAF (see DeleteSqlInjectionMatchSet ). SqlInjectionMatchSetId is returned by CreateSqlInjectionMatchSet and by ListSqlInjectionMatchSets .
  • simssName - The name of the SqlInjectionMatchSet , if any, specified by Id .

simssSqlInjectionMatchSetId :: Lens' SqlInjectionMatchSetSummary Text Source #

A unique identifier for a SqlInjectionMatchSet . You use SqlInjectionMatchSetId to get information about a SqlInjectionMatchSet (see GetSqlInjectionMatchSet ), update a SqlInjectionMatchSet (see UpdateSqlInjectionMatchSet ), insert a SqlInjectionMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete a SqlInjectionMatchSet from AWS WAF (see DeleteSqlInjectionMatchSet ). SqlInjectionMatchSetId is returned by CreateSqlInjectionMatchSet and by ListSqlInjectionMatchSets .

simssName :: Lens' SqlInjectionMatchSetSummary Text Source #

The name of the SqlInjectionMatchSet , if any, specified by Id .

SqlInjectionMatchSetUpdate

data SqlInjectionMatchSetUpdate Source #

Specifies the part of a web request that you want to inspect for snippets of malicious SQL code and indicates whether you want to add the specification to a SqlInjectionMatchSet or delete it from a SqlInjectionMatchSet .

See: sqlInjectionMatchSetUpdate smart constructor.

Instances

Eq SqlInjectionMatchSetUpdate Source # 
Data SqlInjectionMatchSetUpdate Source # 

Methods

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

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

toConstr :: SqlInjectionMatchSetUpdate -> Constr #

dataTypeOf :: SqlInjectionMatchSetUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SqlInjectionMatchSetUpdate Source # 
Show SqlInjectionMatchSetUpdate Source # 
Generic SqlInjectionMatchSetUpdate Source # 
Hashable SqlInjectionMatchSetUpdate Source # 
ToJSON SqlInjectionMatchSetUpdate Source # 
NFData SqlInjectionMatchSetUpdate Source # 
type Rep SqlInjectionMatchSetUpdate Source # 
type Rep SqlInjectionMatchSetUpdate = D1 (MetaData "SqlInjectionMatchSetUpdate" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "SqlInjectionMatchSetUpdate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_simsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction)) (S1 (MetaSel (Just Symbol "_simsuSqlInjectionMatchTuple") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SqlInjectionMatchTuple))))

sqlInjectionMatchSetUpdate Source #

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

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

simsuAction :: Lens' SqlInjectionMatchSetUpdate ChangeAction Source #

Specify INSERT to add a SqlInjectionMatchSetUpdate to a SqlInjectionMatchSet . Use DELETE to remove a SqlInjectionMatchSetUpdate from a SqlInjectionMatchSet .

simsuSqlInjectionMatchTuple :: Lens' SqlInjectionMatchSetUpdate SqlInjectionMatchTuple Source #

Specifies the part of a web request that you want AWS WAF to inspect for snippets of malicious SQL code and, if you want AWS WAF to inspect a header, the name of the header.

SqlInjectionMatchTuple

data SqlInjectionMatchTuple Source #

Specifies the part of a web request that you want AWS WAF to inspect for snippets of malicious SQL code and, if you want AWS WAF to inspect a header, the name of the header.

See: sqlInjectionMatchTuple smart constructor.

Instances

Eq SqlInjectionMatchTuple Source # 
Data SqlInjectionMatchTuple Source # 

Methods

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

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

toConstr :: SqlInjectionMatchTuple -> Constr #

dataTypeOf :: SqlInjectionMatchTuple -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SqlInjectionMatchTuple Source # 
Show SqlInjectionMatchTuple Source # 
Generic SqlInjectionMatchTuple Source # 
Hashable SqlInjectionMatchTuple Source # 
FromJSON SqlInjectionMatchTuple Source # 
ToJSON SqlInjectionMatchTuple Source # 
NFData SqlInjectionMatchTuple Source # 

Methods

rnf :: SqlInjectionMatchTuple -> () #

type Rep SqlInjectionMatchTuple Source # 
type Rep SqlInjectionMatchTuple = D1 (MetaData "SqlInjectionMatchTuple" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "SqlInjectionMatchTuple'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_simtFieldToMatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FieldToMatch)) (S1 (MetaSel (Just Symbol "_simtTextTransformation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextTransformation))))

sqlInjectionMatchTuple Source #

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

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

  • simtFieldToMatch - Specifies where in a web request to look for snippets of malicious SQL code.
  • simtTextTransformation - Text transformations eliminate some of the unusual formatting that attackers use in web requests in an effort to bypass AWS WAF. If you specify a transformation, AWS WAF performs the transformation on FieldToMatch before inspecting a request for a match. CMD_LINE When you're concerned that attackers are injecting an operating system commandline command and using unusual formatting to disguise some or all of the command, use this option to perform the following transformations: * Delete the following characters: " ' ^ * Delete spaces before the following characters: / ( * Replace the following characters with a space: , ; * Replace multiple spaces with one space * Convert uppercase letters (A-Z) to lowercase (a-z) COMPRESS_WHITE_SPACE Use this option to replace the following characters with a space character (decimal 32): * f, formfeed, decimal 12 * t, tab, decimal 9 * n, newline, decimal 10 * r, carriage return, decimal 13 * v, vertical tab, decimal 11 * non-breaking space, decimal 160 COMPRESS_WHITE_SPACE also replaces multiple spaces with one space. HTML_ENTITY_DECODE Use this option to replace HTML-encoded characters with unencoded characters. HTML_ENTITY_DECODE performs the following operations: * Replaces (ampersand)quot; with " * Replaces (ampersand)nbsp; with a non-breaking space, decimal 160 * Replaces (ampersand)lt; with a "less than" symbol * Replaces (ampersand)gt; with > * Replaces characters that are represented in hexadecimal format, (ampersand)#xhhhh; , with the corresponding characters * Replaces characters that are represented in decimal format, (ampersand)#nnnn; , with the corresponding characters LOWERCASE Use this option to convert uppercase letters (A-Z) to lowercase (a-z). URL_DECODE Use this option to decode a URL-encoded value. NONE Specify NONE if you don't want to perform any text transformations.

simtFieldToMatch :: Lens' SqlInjectionMatchTuple FieldToMatch Source #

Specifies where in a web request to look for snippets of malicious SQL code.

simtTextTransformation :: Lens' SqlInjectionMatchTuple TextTransformation Source #

Text transformations eliminate some of the unusual formatting that attackers use in web requests in an effort to bypass AWS WAF. If you specify a transformation, AWS WAF performs the transformation on FieldToMatch before inspecting a request for a match. CMD_LINE When you're concerned that attackers are injecting an operating system commandline command and using unusual formatting to disguise some or all of the command, use this option to perform the following transformations: * Delete the following characters: " ' ^ * Delete spaces before the following characters: / ( * Replace the following characters with a space: , ; * Replace multiple spaces with one space * Convert uppercase letters (A-Z) to lowercase (a-z) COMPRESS_WHITE_SPACE Use this option to replace the following characters with a space character (decimal 32): * f, formfeed, decimal 12 * t, tab, decimal 9 * n, newline, decimal 10 * r, carriage return, decimal 13 * v, vertical tab, decimal 11 * non-breaking space, decimal 160 COMPRESS_WHITE_SPACE also replaces multiple spaces with one space. HTML_ENTITY_DECODE Use this option to replace HTML-encoded characters with unencoded characters. HTML_ENTITY_DECODE performs the following operations: * Replaces (ampersand)quot; with " * Replaces (ampersand)nbsp; with a non-breaking space, decimal 160 * Replaces (ampersand)lt; with a "less than" symbol * Replaces (ampersand)gt; with > * Replaces characters that are represented in hexadecimal format, (ampersand)#xhhhh; , with the corresponding characters * Replaces characters that are represented in decimal format, (ampersand)#nnnn; , with the corresponding characters LOWERCASE Use this option to convert uppercase letters (A-Z) to lowercase (a-z). URL_DECODE Use this option to decode a URL-encoded value. NONE Specify NONE if you don't want to perform any text transformations.

TimeWindow

data TimeWindow Source #

In a GetSampledRequests request, the StartTime and EndTime objects specify the time range for which you want AWS WAF to return a sample of web requests.

In a GetSampledRequests response, the StartTime and EndTime objects specify the time range for which AWS WAF actually returned a sample of web requests. AWS WAF gets the specified number of requests from among the first 5,000 requests that your AWS resource receives during the specified time period. If your resource receives more than 5,000 requests during that period, AWS WAF stops sampling after the 5,000th request. In that case, EndTime is the time that AWS WAF received the 5,000th request.

See: timeWindow smart constructor.

Instances

Eq TimeWindow Source # 
Data TimeWindow Source # 

Methods

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

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

toConstr :: TimeWindow -> Constr #

dataTypeOf :: TimeWindow -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TimeWindow Source # 
Show TimeWindow Source # 
Generic TimeWindow Source # 

Associated Types

type Rep TimeWindow :: * -> * #

Hashable TimeWindow Source # 
FromJSON TimeWindow Source # 
ToJSON TimeWindow Source # 
NFData TimeWindow Source # 

Methods

rnf :: TimeWindow -> () #

type Rep TimeWindow Source # 
type Rep TimeWindow = D1 (MetaData "TimeWindow" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "TimeWindow'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_twStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 POSIX)) (S1 (MetaSel (Just Symbol "_twEndTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 POSIX))))

timeWindow Source #

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

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

  • twStartTime - The beginning of the time range from which you want GetSampledRequests to return a sample of the requests that your AWS resource received. Specify the date and time in the following format: "2016-09-27T14:50Z" . You can specify any time range in the previous three hours.
  • twEndTime - The end of the time range from which you want GetSampledRequests to return a sample of the requests that your AWS resource received. Specify the date and time in the following format: "2016-09-27T14:50Z" . You can specify any time range in the previous three hours.

twStartTime :: Lens' TimeWindow UTCTime Source #

The beginning of the time range from which you want GetSampledRequests to return a sample of the requests that your AWS resource received. Specify the date and time in the following format: "2016-09-27T14:50Z" . You can specify any time range in the previous three hours.

twEndTime :: Lens' TimeWindow UTCTime Source #

The end of the time range from which you want GetSampledRequests to return a sample of the requests that your AWS resource received. Specify the date and time in the following format: "2016-09-27T14:50Z" . You can specify any time range in the previous three hours.

WafAction

data WafAction Source #

For the action that is associated with a rule in a WebACL , specifies the action that you want AWS WAF to perform when a web request matches all of the conditions in a rule. For the default action in a WebACL , specifies the action that you want AWS WAF to take when a web request doesn't match all of the conditions in any of the rules in a WebACL .

See: wafAction smart constructor.

Instances

Eq WafAction Source # 
Data WafAction Source # 

Methods

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

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

toConstr :: WafAction -> Constr #

dataTypeOf :: WafAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Read WafAction Source # 
Show WafAction Source # 
Generic WafAction Source # 

Associated Types

type Rep WafAction :: * -> * #

Hashable WafAction Source # 
FromJSON WafAction Source # 
ToJSON WafAction Source # 
NFData WafAction Source # 

Methods

rnf :: WafAction -> () #

type Rep WafAction Source # 
type Rep WafAction = D1 (MetaData "WafAction" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" True) (C1 (MetaCons "WafAction'" PrefixI True) (S1 (MetaSel (Just Symbol "_waType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 WafActionType)))

wafAction Source #

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

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

  • waType - Specifies how you want AWS WAF to respond to requests that match the settings in a Rule . Valid settings include the following: * ALLOW : AWS WAF allows requests * BLOCK : AWS WAF blocks requests * COUNT : AWS WAF increments a counter of the requests that match all of the conditions in the rule. AWS WAF then continues to inspect the web request based on the remaining rules in the web ACL. You can't specify COUNT for the default action for a WebACL .

waType :: Lens' WafAction WafActionType Source #

Specifies how you want AWS WAF to respond to requests that match the settings in a Rule . Valid settings include the following: * ALLOW : AWS WAF allows requests * BLOCK : AWS WAF blocks requests * COUNT : AWS WAF increments a counter of the requests that match all of the conditions in the rule. AWS WAF then continues to inspect the web request based on the remaining rules in the web ACL. You can't specify COUNT for the default action for a WebACL .

WebACL

data WebACL Source #

Contains the Rules that identify the requests that you want to allow, block, or count. In a WebACL , you also specify a default action (ALLOW or BLOCK ), and the action for each Rule that you add to a WebACL , for example, block requests from specified IP addresses or block requests from specified referrers. You also associate the WebACL with a CloudFront distribution to identify the requests that you want AWS WAF to filter. If you add more than one Rule to a WebACL , a request needs to match only one of the specifications to be allowed, blocked, or counted. For more information, see UpdateWebACL .

See: webACL smart constructor.

Instances

Eq WebACL Source # 

Methods

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

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

Data WebACL Source # 

Methods

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

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

toConstr :: WebACL -> Constr #

dataTypeOf :: WebACL -> DataType #

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

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

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

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

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

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

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

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

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

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

Read WebACL Source # 
Show WebACL Source # 
Generic WebACL Source # 

Associated Types

type Rep WebACL :: * -> * #

Methods

from :: WebACL -> Rep WebACL x #

to :: Rep WebACL x -> WebACL #

Hashable WebACL Source # 

Methods

hashWithSalt :: Int -> WebACL -> Int #

hash :: WebACL -> Int #

FromJSON WebACL Source # 
NFData WebACL Source # 

Methods

rnf :: WebACL -> () #

type Rep WebACL Source # 
type Rep WebACL = D1 (MetaData "WebACL" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "WebACL'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_waMetricName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_waName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_waWebACLId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_waDefaultAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WafAction)) (S1 (MetaSel (Just Symbol "_waRules") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [ActivatedRule]))))))

webACL Source #

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

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

  • waMetricName - A friendly name or description for the metrics for this WebACL . The name can contain only alphanumeric characters (A-Z, a-z, 0-9); the name can't contain whitespace. You can't change MetricName after you create the WebACL .
  • waName - A friendly name or description of the WebACL . You can't change the name of a WebACL after you create it.
  • waWebACLId - A unique identifier for a WebACL . You use WebACLId to get information about a WebACL (see GetWebACL ), update a WebACL (see UpdateWebACL ), and delete a WebACL from AWS WAF (see DeleteWebACL ). WebACLId is returned by CreateWebACL and by ListWebACLs .
  • waDefaultAction - The action to perform if none of the Rules contained in the WebACL match. The action is specified by the WafAction object.
  • waRules - An array that contains the action for each Rule in a WebACL , the priority of the Rule , and the ID of the Rule .

waMetricName :: Lens' WebACL (Maybe Text) Source #

A friendly name or description for the metrics for this WebACL . The name can contain only alphanumeric characters (A-Z, a-z, 0-9); the name can't contain whitespace. You can't change MetricName after you create the WebACL .

waName :: Lens' WebACL (Maybe Text) Source #

A friendly name or description of the WebACL . You can't change the name of a WebACL after you create it.

waWebACLId :: Lens' WebACL Text Source #

A unique identifier for a WebACL . You use WebACLId to get information about a WebACL (see GetWebACL ), update a WebACL (see UpdateWebACL ), and delete a WebACL from AWS WAF (see DeleteWebACL ). WebACLId is returned by CreateWebACL and by ListWebACLs .

waDefaultAction :: Lens' WebACL WafAction Source #

The action to perform if none of the Rules contained in the WebACL match. The action is specified by the WafAction object.

waRules :: Lens' WebACL [ActivatedRule] Source #

An array that contains the action for each Rule in a WebACL , the priority of the Rule , and the ID of the Rule .

WebACLSummary

data WebACLSummary Source #

Contains the identifier and the name or description of the WebACL .

See: webACLSummary smart constructor.

Instances

Eq WebACLSummary Source # 
Data WebACLSummary Source # 

Methods

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

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

toConstr :: WebACLSummary -> Constr #

dataTypeOf :: WebACLSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read WebACLSummary Source # 
Show WebACLSummary Source # 
Generic WebACLSummary Source # 

Associated Types

type Rep WebACLSummary :: * -> * #

Hashable WebACLSummary Source # 
FromJSON WebACLSummary Source # 
NFData WebACLSummary Source # 

Methods

rnf :: WebACLSummary -> () #

type Rep WebACLSummary Source # 
type Rep WebACLSummary = D1 (MetaData "WebACLSummary" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "WebACLSummary'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_wasWebACLId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_wasName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

webACLSummary Source #

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

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

  • wasWebACLId - A unique identifier for a WebACL . You use WebACLId to get information about a WebACL (see GetWebACL ), update a WebACL (see UpdateWebACL ), and delete a WebACL from AWS WAF (see DeleteWebACL ). WebACLId is returned by CreateWebACL and by ListWebACLs .
  • wasName - A friendly name or description of the WebACL . You can't change the name of a WebACL after you create it.

wasWebACLId :: Lens' WebACLSummary Text Source #

A unique identifier for a WebACL . You use WebACLId to get information about a WebACL (see GetWebACL ), update a WebACL (see UpdateWebACL ), and delete a WebACL from AWS WAF (see DeleteWebACL ). WebACLId is returned by CreateWebACL and by ListWebACLs .

wasName :: Lens' WebACLSummary Text Source #

A friendly name or description of the WebACL . You can't change the name of a WebACL after you create it.

WebACLUpdate

data WebACLUpdate Source #

Specifies whether to insert a Rule into or delete a Rule from a WebACL .

See: webACLUpdate smart constructor.

Instances

Eq WebACLUpdate Source # 
Data WebACLUpdate Source # 

Methods

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

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

toConstr :: WebACLUpdate -> Constr #

dataTypeOf :: WebACLUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read WebACLUpdate Source # 
Show WebACLUpdate Source # 
Generic WebACLUpdate Source # 

Associated Types

type Rep WebACLUpdate :: * -> * #

Hashable WebACLUpdate Source # 
ToJSON WebACLUpdate Source # 
NFData WebACLUpdate Source # 

Methods

rnf :: WebACLUpdate -> () #

type Rep WebACLUpdate Source # 
type Rep WebACLUpdate = D1 (MetaData "WebACLUpdate" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "WebACLUpdate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_wauAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction)) (S1 (MetaSel (Just Symbol "_wauActivatedRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ActivatedRule))))

webACLUpdate Source #

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

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

  • wauAction - Specifies whether to insert a Rule into or delete a Rule from a WebACL .
  • wauActivatedRule - The ActivatedRule object in an UpdateWebACL request specifies a Rule that you want to insert or delete, the priority of the Rule in the WebACL , and the action that you want AWS WAF to take when a web request matches the Rule (ALLOW , BLOCK , or COUNT ).

wauAction :: Lens' WebACLUpdate ChangeAction Source #

Specifies whether to insert a Rule into or delete a Rule from a WebACL .

wauActivatedRule :: Lens' WebACLUpdate ActivatedRule Source #

The ActivatedRule object in an UpdateWebACL request specifies a Rule that you want to insert or delete, the priority of the Rule in the WebACL , and the action that you want AWS WAF to take when a web request matches the Rule (ALLOW , BLOCK , or COUNT ).

XSSMatchSet

data XSSMatchSet Source #

A complex type that contains XssMatchTuple objects, which specify the parts of web requests that you want AWS WAF to inspect for cross-site scripting attacks and, if you want AWS WAF to inspect a header, the name of the header. If a XssMatchSet contains more than one XssMatchTuple object, a request needs to include cross-site scripting attacks in only one of the specified parts of the request to be considered a match.

See: xssMatchSet smart constructor.

Instances

Eq XSSMatchSet Source # 
Data XSSMatchSet Source # 

Methods

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

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

toConstr :: XSSMatchSet -> Constr #

dataTypeOf :: XSSMatchSet -> DataType #

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

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

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

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

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

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

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

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

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

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

Read XSSMatchSet Source # 
Show XSSMatchSet Source # 
Generic XSSMatchSet Source # 

Associated Types

type Rep XSSMatchSet :: * -> * #

Hashable XSSMatchSet Source # 
FromJSON XSSMatchSet Source # 
NFData XSSMatchSet Source # 

Methods

rnf :: XSSMatchSet -> () #

type Rep XSSMatchSet Source # 
type Rep XSSMatchSet = D1 (MetaData "XSSMatchSet" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "XSSMatchSet'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_xmsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_xmsXSSMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_xmsXSSMatchTuples") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [XSSMatchTuple])))))

xssMatchSet Source #

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

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

  • xmsName - The name, if any, of the XssMatchSet .
  • xmsXSSMatchSetId - A unique identifier for an XssMatchSet . You use XssMatchSetId to get information about an XssMatchSet (see GetXssMatchSet ), update an XssMatchSet (see UpdateXssMatchSet ), insert an XssMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete an XssMatchSet from AWS WAF (see DeleteXssMatchSet ). XssMatchSetId is returned by CreateXssMatchSet and by ListXssMatchSets .
  • xmsXSSMatchTuples - Specifies the parts of web requests that you want to inspect for cross-site scripting attacks.

xmsName :: Lens' XSSMatchSet (Maybe Text) Source #

The name, if any, of the XssMatchSet .

xmsXSSMatchSetId :: Lens' XSSMatchSet Text Source #

A unique identifier for an XssMatchSet . You use XssMatchSetId to get information about an XssMatchSet (see GetXssMatchSet ), update an XssMatchSet (see UpdateXssMatchSet ), insert an XssMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete an XssMatchSet from AWS WAF (see DeleteXssMatchSet ). XssMatchSetId is returned by CreateXssMatchSet and by ListXssMatchSets .

xmsXSSMatchTuples :: Lens' XSSMatchSet [XSSMatchTuple] Source #

Specifies the parts of web requests that you want to inspect for cross-site scripting attacks.

XSSMatchSetSummary

data XSSMatchSetSummary Source #

The Id and Name of an XssMatchSet .

See: xssMatchSetSummary smart constructor.

Instances

Eq XSSMatchSetSummary Source # 
Data XSSMatchSetSummary Source # 

Methods

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

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

toConstr :: XSSMatchSetSummary -> Constr #

dataTypeOf :: XSSMatchSetSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Methods

rnf :: XSSMatchSetSummary -> () #

type Rep XSSMatchSetSummary Source # 
type Rep XSSMatchSetSummary = D1 (MetaData "XSSMatchSetSummary" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "XSSMatchSetSummary'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_xmssXSSMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_xmssName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

xssMatchSetSummary Source #

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

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

  • xmssXSSMatchSetId - A unique identifier for an XssMatchSet . You use XssMatchSetId to get information about a XssMatchSet (see GetXssMatchSet ), update an XssMatchSet (see UpdateXssMatchSet ), insert an XssMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete an XssMatchSet from AWS WAF (see DeleteXssMatchSet ). XssMatchSetId is returned by CreateXssMatchSet and by ListXssMatchSets .
  • xmssName - The name of the XssMatchSet , if any, specified by Id .

xmssXSSMatchSetId :: Lens' XSSMatchSetSummary Text Source #

A unique identifier for an XssMatchSet . You use XssMatchSetId to get information about a XssMatchSet (see GetXssMatchSet ), update an XssMatchSet (see UpdateXssMatchSet ), insert an XssMatchSet into a Rule or delete one from a Rule (see UpdateRule ), and delete an XssMatchSet from AWS WAF (see DeleteXssMatchSet ). XssMatchSetId is returned by CreateXssMatchSet and by ListXssMatchSets .

xmssName :: Lens' XSSMatchSetSummary Text Source #

The name of the XssMatchSet , if any, specified by Id .

XSSMatchSetUpdate

data XSSMatchSetUpdate Source #

Specifies the part of a web request that you want to inspect for cross-site scripting attacks and indicates whether you want to add the specification to an XssMatchSet or delete it from an XssMatchSet .

See: xssMatchSetUpdate smart constructor.

Instances

Eq XSSMatchSetUpdate Source # 
Data XSSMatchSetUpdate Source # 

Methods

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

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

toConstr :: XSSMatchSetUpdate -> Constr #

dataTypeOf :: XSSMatchSetUpdate -> DataType #

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

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

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

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

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

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

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

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XSSMatchSetUpdate -> m XSSMatchSetUpdate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XSSMatchSetUpdate -> m XSSMatchSetUpdate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XSSMatchSetUpdate -> m XSSMatchSetUpdate #

Read XSSMatchSetUpdate Source # 
Show XSSMatchSetUpdate Source # 
Generic XSSMatchSetUpdate Source # 
Hashable XSSMatchSetUpdate Source # 
ToJSON XSSMatchSetUpdate Source # 
NFData XSSMatchSetUpdate Source # 

Methods

rnf :: XSSMatchSetUpdate -> () #

type Rep XSSMatchSetUpdate Source # 
type Rep XSSMatchSetUpdate = D1 (MetaData "XSSMatchSetUpdate" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "XSSMatchSetUpdate'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_xmsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction)) (S1 (MetaSel (Just Symbol "_xmsuXSSMatchTuple") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 XSSMatchTuple))))

xssMatchSetUpdate Source #

Creates a value of XSSMatchSetUpdate with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • xmsuAction - Specify INSERT to add a XssMatchSetUpdate to an XssMatchSet . Use DELETE to remove a XssMatchSetUpdate from an XssMatchSet .
  • xmsuXSSMatchTuple - Specifies the part of a web request that you want AWS WAF to inspect for cross-site scripting attacks and, if you want AWS WAF to inspect a header, the name of the header.

xmsuAction :: Lens' XSSMatchSetUpdate ChangeAction Source #

Specify INSERT to add a XssMatchSetUpdate to an XssMatchSet . Use DELETE to remove a XssMatchSetUpdate from an XssMatchSet .

xmsuXSSMatchTuple :: Lens' XSSMatchSetUpdate XSSMatchTuple Source #

Specifies the part of a web request that you want AWS WAF to inspect for cross-site scripting attacks and, if you want AWS WAF to inspect a header, the name of the header.

XSSMatchTuple

data XSSMatchTuple Source #

Specifies the part of a web request that you want AWS WAF to inspect for cross-site scripting attacks and, if you want AWS WAF to inspect a header, the name of the header.

See: xssMatchTuple smart constructor.

Instances

Eq XSSMatchTuple Source # 
Data XSSMatchTuple Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XSSMatchTuple -> c XSSMatchTuple #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XSSMatchTuple #

toConstr :: XSSMatchTuple -> Constr #

dataTypeOf :: XSSMatchTuple -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c XSSMatchTuple) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XSSMatchTuple) #

gmapT :: (forall b. Data b => b -> b) -> XSSMatchTuple -> XSSMatchTuple #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XSSMatchTuple -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XSSMatchTuple -> r #

gmapQ :: (forall d. Data d => d -> u) -> XSSMatchTuple -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> XSSMatchTuple -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XSSMatchTuple -> m XSSMatchTuple #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XSSMatchTuple -> m XSSMatchTuple #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XSSMatchTuple -> m XSSMatchTuple #

Read XSSMatchTuple Source # 
Show XSSMatchTuple Source # 
Generic XSSMatchTuple Source # 

Associated Types

type Rep XSSMatchTuple :: * -> * #

Hashable XSSMatchTuple Source # 
FromJSON XSSMatchTuple Source # 
ToJSON XSSMatchTuple Source # 
NFData XSSMatchTuple Source # 

Methods

rnf :: XSSMatchTuple -> () #

type Rep XSSMatchTuple Source # 
type Rep XSSMatchTuple = D1 (MetaData "XSSMatchTuple" "Network.AWS.WAFRegional.Types.Product" "amazonka-waf-regional-1.5.0-Kn8HIfa7qWEERHHaTClrk5" False) (C1 (MetaCons "XSSMatchTuple'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_xmtFieldToMatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FieldToMatch)) (S1 (MetaSel (Just Symbol "_xmtTextTransformation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextTransformation))))

xssMatchTuple Source #

Creates a value of XSSMatchTuple with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • xmtFieldToMatch - Specifies where in a web request to look for cross-site scripting attacks.
  • xmtTextTransformation - Text transformations eliminate some of the unusual formatting that attackers use in web requests in an effort to bypass AWS WAF. If you specify a transformation, AWS WAF performs the transformation on FieldToMatch before inspecting a request for a match. CMD_LINE When you're concerned that attackers are injecting an operating system commandline command and using unusual formatting to disguise some or all of the command, use this option to perform the following transformations: * Delete the following characters: " ' ^ * Delete spaces before the following characters: / ( * Replace the following characters with a space: , ; * Replace multiple spaces with one space * Convert uppercase letters (A-Z) to lowercase (a-z) COMPRESS_WHITE_SPACE Use this option to replace the following characters with a space character (decimal 32): * f, formfeed, decimal 12 * t, tab, decimal 9 * n, newline, decimal 10 * r, carriage return, decimal 13 * v, vertical tab, decimal 11 * non-breaking space, decimal 160 COMPRESS_WHITE_SPACE also replaces multiple spaces with one space. HTML_ENTITY_DECODE Use this option to replace HTML-encoded characters with unencoded characters. HTML_ENTITY_DECODE performs the following operations: * Replaces (ampersand)quot; with " * Replaces (ampersand)nbsp; with a non-breaking space, decimal 160 * Replaces (ampersand)lt; with a "less than" symbol * Replaces (ampersand)gt; with > * Replaces characters that are represented in hexadecimal format, (ampersand)#xhhhh; , with the corresponding characters * Replaces characters that are represented in decimal format, (ampersand)#nnnn; , with the corresponding characters LOWERCASE Use this option to convert uppercase letters (A-Z) to lowercase (a-z). URL_DECODE Use this option to decode a URL-encoded value. NONE Specify NONE if you don't want to perform any text transformations.

xmtFieldToMatch :: Lens' XSSMatchTuple FieldToMatch Source #

Specifies where in a web request to look for cross-site scripting attacks.

xmtTextTransformation :: Lens' XSSMatchTuple TextTransformation Source #

Text transformations eliminate some of the unusual formatting that attackers use in web requests in an effort to bypass AWS WAF. If you specify a transformation, AWS WAF performs the transformation on FieldToMatch before inspecting a request for a match. CMD_LINE When you're concerned that attackers are injecting an operating system commandline command and using unusual formatting to disguise some or all of the command, use this option to perform the following transformations: * Delete the following characters: " ' ^ * Delete spaces before the following characters: / ( * Replace the following characters with a space: , ; * Replace multiple spaces with one space * Convert uppercase letters (A-Z) to lowercase (a-z) COMPRESS_WHITE_SPACE Use this option to replace the following characters with a space character (decimal 32): * f, formfeed, decimal 12 * t, tab, decimal 9 * n, newline, decimal 10 * r, carriage return, decimal 13 * v, vertical tab, decimal 11 * non-breaking space, decimal 160 COMPRESS_WHITE_SPACE also replaces multiple spaces with one space. HTML_ENTITY_DECODE Use this option to replace HTML-encoded characters with unencoded characters. HTML_ENTITY_DECODE performs the following operations: * Replaces (ampersand)quot; with " * Replaces (ampersand)nbsp; with a non-breaking space, decimal 160 * Replaces (ampersand)lt; with a "less than" symbol * Replaces (ampersand)gt; with > * Replaces characters that are represented in hexadecimal format, (ampersand)#xhhhh; , with the corresponding characters * Replaces characters that are represented in decimal format, (ampersand)#nnnn; , with the corresponding characters LOWERCASE Use this option to convert uppercase letters (A-Z) to lowercase (a-z). URL_DECODE Use this option to decode a URL-encoded value. NONE Specify NONE if you don't want to perform any text transformations.