amazonka-waf-1.6.1: Amazon WAF SDK.

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

Network.AWS.WAF.Types

Contents

Description

 
Synopsis

Service Configuration

waf :: Service Source #

API version 2015-08-24 of the Amazon WAF SDK configuration.

Errors

_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.

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

The specified subscription does not exist.

_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 :: AsError a => Getting (First ServiceError) a ServiceError Source #

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

_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 :: AsError a => Getting (First ServiceError) a ServiceError Source #

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

_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 :: 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 .

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

The operation failed because the specified policy is not in the proper format.

The policy is subject to the following restrictions:

  • You can attach only one policy with each PutPermissionPolicy request.
  • The policy must include an Effect , Action and Principal .
  • Effect must specify Allow .
  • The Action in the policy must be waf:UpdateWebACL or waf-regional:UpdateWebACL . Any extra or wildcard actions in the policy will be rejected.
  • The policy cannot include a Resource parameter.
  • The ARN in the request must be a valid WAF RuleGroup ARN and the RuleGroup must exist in the same region.
  • The user making the request must be the owner of the RuleGroup.
  • Your policy must be composed using IAM Policy version 2012-10-17.

_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 :: 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 :: 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.

_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.

ChangeAction

data ChangeAction Source #

Constructors

Delete 
Insert 
Instances
Bounded ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep ChangeAction :: Type -> Type #

Hashable ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

toText :: ChangeAction -> Text #

NFData ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: ChangeAction -> () #

type Rep ChangeAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep ChangeAction = D1 (MetaData "ChangeAction" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "Delete" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Insert" PrefixI False) (U1 :: Type -> Type))

ChangeTokenStatus

data ChangeTokenStatus Source #

Constructors

Insync 
Pending 
Provisioned 
Instances
Bounded ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep ChangeTokenStatus :: Type -> Type #

Hashable ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

NFData ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: ChangeTokenStatus -> () #

type Rep ChangeTokenStatus Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep ChangeTokenStatus = D1 (MetaData "ChangeTokenStatus" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "Insync" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Pending" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Provisioned" PrefixI False) (U1 :: Type -> Type)))

ComparisonOperator

data ComparisonOperator Source #

Constructors

EQ' 
GE 
GT' 
LE 
LT' 
NE 
Instances
Bounded ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

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

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

toConstr :: ComparisonOperator -> Constr #

dataTypeOf :: ComparisonOperator -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep ComparisonOperator :: Type -> Type #

Hashable ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

NFData ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: ComparisonOperator -> () #

type Rep ComparisonOperator Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep ComparisonOperator = D1 (MetaData "ComparisonOperator" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) ((C1 (MetaCons "EQ'" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GE" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GT'" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "LE" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "LT'" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NE" PrefixI False) (U1 :: Type -> Type))))

GeoMatchConstraintType

data GeoMatchConstraintType Source #

Constructors

Country 
Instances
Bounded GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep GeoMatchConstraintType :: Type -> Type #

Hashable GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

NFData GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: GeoMatchConstraintType -> () #

type Rep GeoMatchConstraintType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep GeoMatchConstraintType = D1 (MetaData "GeoMatchConstraintType" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "Country" PrefixI False) (U1 :: Type -> Type))

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep GeoMatchConstraintValue :: Type -> Type #

Hashable GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

NFData GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: GeoMatchConstraintValue -> () #

type Rep GeoMatchConstraintValue Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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

IPSetDescriptorType

data IPSetDescriptorType Source #

Constructors

IPV4 
IPV6 
Instances
Bounded IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep IPSetDescriptorType :: Type -> Type #

Hashable IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

NFData IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: IPSetDescriptorType -> () #

type Rep IPSetDescriptorType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep IPSetDescriptorType = D1 (MetaData "IPSetDescriptorType" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "IPV4" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IPV6" PrefixI False) (U1 :: Type -> Type))

MatchFieldType

data MatchFieldType Source #

Constructors

Body 
Header 
Method 
QueryString 
URI 
Instances
Bounded MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep MatchFieldType :: Type -> Type #

Hashable MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

NFData MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: MatchFieldType -> () #

type Rep MatchFieldType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep MatchFieldType = D1 (MetaData "MatchFieldType" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) ((C1 (MetaCons "Body" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Header" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Method" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "QueryString" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "URI" PrefixI False) (U1 :: Type -> Type))))

PositionalConstraint

data PositionalConstraint Source #

Instances
Bounded PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep PositionalConstraint :: Type -> Type #

Hashable PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

NFData PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: PositionalConstraint -> () #

type Rep PositionalConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep PositionalConstraint = D1 (MetaData "PositionalConstraint" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) ((C1 (MetaCons "Contains" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ContainsWord" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "EndsWith" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Exactly" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StartsWith" PrefixI False) (U1 :: Type -> Type))))

PredicateType

data PredicateType Source #

Instances
Bounded PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep PredicateType :: Type -> Type #

Hashable PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

toText :: PredicateType -> Text #

NFData PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: PredicateType -> () #

type Rep PredicateType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep PredicateType = D1 (MetaData "PredicateType" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) ((C1 (MetaCons "ByteMatch" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GeoMatch" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IPMatch" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "RegexMatch" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SizeConstraint" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SqlInjectionMatch" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "XSSMatch" PrefixI False) (U1 :: Type -> Type))))

RateKey

data RateKey Source #

Constructors

IP 
Instances
Bounded RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

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

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

Data RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep RateKey :: Type -> Type #

Methods

from :: RateKey -> Rep RateKey x #

to :: Rep RateKey x -> RateKey #

Hashable RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

hashWithSalt :: Int -> RateKey -> Int #

hash :: RateKey -> Int #

ToJSON RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

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

ToQuery RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

toBS :: RateKey -> ByteString #

FromText RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

toText :: RateKey -> Text #

NFData RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: RateKey -> () #

type Rep RateKey Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep RateKey = D1 (MetaData "RateKey" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "IP" PrefixI False) (U1 :: Type -> Type))

TextTransformation

data TextTransformation Source #

Instances
Bounded TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep TextTransformation :: Type -> Type #

Hashable TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

NFData TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: TextTransformation -> () #

type Rep TextTransformation Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep TextTransformation = D1 (MetaData "TextTransformation" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) ((C1 (MetaCons "CmdLine" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CompressWhiteSpace" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HTMLEntityDecode" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Lowercase" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "None" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "URLDecode" PrefixI False) (U1 :: Type -> Type))))

WafActionType

data WafActionType Source #

Constructors

Allow 
Block 
Count 
Instances
Bounded WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep WafActionType :: Type -> Type #

Hashable WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

toText :: WafActionType -> Text #

NFData WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: WafActionType -> () #

type Rep WafActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep WafActionType = D1 (MetaData "WafActionType" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "Allow" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Block" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Count" PrefixI False) (U1 :: Type -> Type)))

WafOverrideActionType

data WafOverrideActionType Source #

Constructors

WOATCount 
WOATNone 
Instances
Bounded WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

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

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

toConstr :: WafOverrideActionType -> Constr #

dataTypeOf :: WafOverrideActionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep WafOverrideActionType :: Type -> Type #

Hashable WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

NFData WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: WafOverrideActionType -> () #

type Rep WafOverrideActionType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep WafOverrideActionType = D1 (MetaData "WafOverrideActionType" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "WOATCount" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WOATNone" PrefixI False) (U1 :: Type -> Type))

WafRuleType

data WafRuleType Source #

Constructors

Group 
RateBased 
Regular 
Instances
Bounded WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Enum WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Eq WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Data WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Read WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Show WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Generic WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Associated Types

type Rep WafRuleType :: Type -> Type #

Hashable WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToJSON WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromJSON WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToHeader WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToQuery WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToByteString WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

FromText WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

ToText WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

toText :: WafRuleType -> Text #

NFData WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

Methods

rnf :: WafRuleType -> () #

type Rep WafRuleType Source # 
Instance details

Defined in Network.AWS.WAF.Types.Sum

type Rep WafRuleType = D1 (MetaData "WafRuleType" "Network.AWS.WAF.Types.Sum" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "Group" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RateBased" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Regular" PrefixI False) (U1 :: Type -> Type)))

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data ActivatedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show ActivatedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic ActivatedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep ActivatedRule :: Type -> Type #

Hashable ActivatedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON ActivatedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON ActivatedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData ActivatedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: ActivatedRule -> () #

type Rep ActivatedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep ActivatedRule = D1 (MetaData "ActivatedRule" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "ActivatedRule'" PrefixI True) ((S1 (MetaSel (Just "_arOverrideAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe WafOverrideAction)) :*: S1 (MetaSel (Just "_arAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe WafAction))) :*: (S1 (MetaSel (Just "_arType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe WafRuleType)) :*: (S1 (MetaSel (Just "_arPriority") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_arRuleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

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:

  • arOverrideAction - Use the OverrideAction to test your RuleGroup . Any rule in a RuleGroup can potentially block a request. If you set the OverrideAction to None , the RuleGroup will block a request if any individual rule in the RuleGroup matches the request and is configured to block that request. However if you first want to test the RuleGroup , set the OverrideAction to Count . The RuleGroup will then override any block action specified by individual rules contained within the group. Instead of blocking matching requests, those requests will be counted. You can view a record of counted requests using GetSampledRequests . ActivatedRule|OverrideAction applies only when updating or adding a RuleGroup to a WebACL . In this case you do not use ActivatedRule|Action . For all other update requests, ActivatedRule|Action is used instead of ActivatedRule|OverrideAction .
  • 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. ActivatedRule|OverrideAction applies only when updating or adding a RuleGroup to a WebACL . In this case you do not use ActivatedRule|Action . For all other update requests, ActivatedRule|Action is used instead of ActivatedRule|OverrideAction .
  • arType - The rule type, either REGULAR , as defined by Rule , RATE_BASED , as defined by RateBasedRule , or GROUP , as defined by RuleGroup . 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 .

arOverrideAction :: Lens' ActivatedRule (Maybe WafOverrideAction) Source #

Use the OverrideAction to test your RuleGroup . Any rule in a RuleGroup can potentially block a request. If you set the OverrideAction to None , the RuleGroup will block a request if any individual rule in the RuleGroup matches the request and is configured to block that request. However if you first want to test the RuleGroup , set the OverrideAction to Count . The RuleGroup will then override any block action specified by individual rules contained within the group. Instead of blocking matching requests, those requests will be counted. You can view a record of counted requests using GetSampledRequests . ActivatedRule|OverrideAction applies only when updating or adding a RuleGroup to a WebACL . In this case you do not use ActivatedRule|Action . For all other update requests, ActivatedRule|Action is used instead of ActivatedRule|OverrideAction .

arAction :: Lens' ActivatedRule (Maybe 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. ActivatedRule|OverrideAction applies only when updating or adding a RuleGroup to a WebACL . In this case you do not use ActivatedRule|Action . For all other update requests, ActivatedRule|Action is used instead of ActivatedRule|OverrideAction .

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

The rule type, either REGULAR , as defined by Rule , RATE_BASED , as defined by RateBasedRule , or GROUP , as defined by RuleGroup . 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 .

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data ByteMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show ByteMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic ByteMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep ByteMatchSet :: Type -> Type #

Hashable ByteMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON ByteMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData ByteMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: ByteMatchSet -> () #

type Rep ByteMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep ByteMatchSet = D1 (MetaData "ByteMatchSet" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "ByteMatchSet'" PrefixI True) (S1 (MetaSel (Just "_bmsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_bmsByteMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data ByteMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show ByteMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic ByteMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep ByteMatchSetSummary :: Type -> Type #

Hashable ByteMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON ByteMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData ByteMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: ByteMatchSetSummary -> () #

type Rep ByteMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep ByteMatchSetSummary = D1 (MetaData "ByteMatchSetSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "ByteMatchSetSummary'" PrefixI True) (S1 (MetaSel (Just "_bmssByteMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data ByteMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show ByteMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic ByteMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep ByteMatchSetUpdate :: Type -> Type #

Hashable ByteMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON ByteMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData ByteMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: ByteMatchSetUpdate -> () #

type Rep ByteMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep ByteMatchSetUpdate = D1 (MetaData "ByteMatchSetUpdate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "ByteMatchSetUpdate'" PrefixI True) (S1 (MetaSel (Just "_bmsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data ByteMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show ByteMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic ByteMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep ByteMatchTuple :: Type -> Type #

Hashable ByteMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON ByteMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON ByteMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData ByteMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: ByteMatchTuple -> () #

type Rep ByteMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep ByteMatchTuple = D1 (MetaData "ByteMatchTuple" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "ByteMatchTuple'" PrefixI True) ((S1 (MetaSel (Just "_bmtFieldToMatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FieldToMatch) :*: S1 (MetaSel (Just "_bmtTargetString") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Base64)) :*: (S1 (MetaSel (Just "_bmtTextTransformation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextTransformation) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data FieldToMatch Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show FieldToMatch Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic FieldToMatch Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep FieldToMatch :: Type -> Type #

Hashable FieldToMatch Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON FieldToMatch Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON FieldToMatch Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData FieldToMatch Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: FieldToMatch -> () #

type Rep FieldToMatch Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep FieldToMatch = D1 (MetaData "FieldToMatch" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "FieldToMatch'" PrefixI True) (S1 (MetaSel (Just "_ftmData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data GeoMatchConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show GeoMatchConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic GeoMatchConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep GeoMatchConstraint :: Type -> Type #

Hashable GeoMatchConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON GeoMatchConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON GeoMatchConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData GeoMatchConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: GeoMatchConstraint -> () #

type Rep GeoMatchConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep GeoMatchConstraint = D1 (MetaData "GeoMatchConstraint" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "GeoMatchConstraint'" PrefixI True) (S1 (MetaSel (Just "_gmcType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 GeoMatchConstraintType) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data GeoMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show GeoMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic GeoMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep GeoMatchSet :: Type -> Type #

Hashable GeoMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON GeoMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData GeoMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: GeoMatchSet -> () #

type Rep GeoMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep GeoMatchSet = D1 (MetaData "GeoMatchSet" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "GeoMatchSet'" PrefixI True) (S1 (MetaSel (Just "_gmsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_gmsGeoMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data GeoMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show GeoMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic GeoMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep GeoMatchSetSummary :: Type -> Type #

Hashable GeoMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON GeoMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData GeoMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: GeoMatchSetSummary -> () #

type Rep GeoMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep GeoMatchSetSummary = D1 (MetaData "GeoMatchSetSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "GeoMatchSetSummary'" PrefixI True) (S1 (MetaSel (Just "_gmssGeoMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data GeoMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show GeoMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic GeoMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep GeoMatchSetUpdate :: Type -> Type #

Hashable GeoMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON GeoMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData GeoMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: GeoMatchSetUpdate -> () #

type Rep GeoMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep GeoMatchSetUpdate = D1 (MetaData "GeoMatchSetUpdate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "GeoMatchSetUpdate'" PrefixI True) (S1 (MetaSel (Just "_gmsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data HTTPHeader Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show HTTPHeader Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic HTTPHeader Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep HTTPHeader :: Type -> Type #

Hashable HTTPHeader Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON HTTPHeader Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData HTTPHeader Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: HTTPHeader -> () #

type Rep HTTPHeader Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep HTTPHeader = D1 (MetaData "HTTPHeader" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "HTTPHeader'" PrefixI True) (S1 (MetaSel (Just "_httphValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data HTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show HTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic HTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep HTTPRequest :: Type -> Type #

Hashable HTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON HTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData HTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: HTTPRequest -> () #

type Rep HTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep HTTPRequest = D1 (MetaData "HTTPRequest" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "HTTPRequest'" PrefixI True) ((S1 (MetaSel (Just "_httprHTTPVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_httprCountry") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_httprURI") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "_httprHeaders") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [HTTPHeader])) :*: (S1 (MetaSel (Just "_httprMethod") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

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

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

Data IPSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show IPSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

showsPrec :: Int -> IPSet -> ShowS #

show :: IPSet -> String #

showList :: [IPSet] -> ShowS #

Generic IPSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep IPSet :: Type -> Type #

Methods

from :: IPSet -> Rep IPSet x #

to :: Rep IPSet x -> IPSet #

Hashable IPSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

hashWithSalt :: Int -> IPSet -> Int #

hash :: IPSet -> Int #

FromJSON IPSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData IPSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: IPSet -> () #

type Rep IPSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep IPSet = D1 (MetaData "IPSet" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "IPSet'" PrefixI True) (S1 (MetaSel (Just "_isName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_isIPSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data IPSetDescriptor Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show IPSetDescriptor Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic IPSetDescriptor Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep IPSetDescriptor :: Type -> Type #

Hashable IPSetDescriptor Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON IPSetDescriptor Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON IPSetDescriptor Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData IPSetDescriptor Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: IPSetDescriptor -> () #

type Rep IPSetDescriptor Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep IPSetDescriptor = D1 (MetaData "IPSetDescriptor" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "IPSetDescriptor'" PrefixI True) (S1 (MetaSel (Just "_isdType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 IPSetDescriptorType) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data IPSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show IPSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic IPSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep IPSetSummary :: Type -> Type #

Hashable IPSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON IPSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData IPSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: IPSetSummary -> () #

type Rep IPSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep IPSetSummary = D1 (MetaData "IPSetSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "IPSetSummary'" PrefixI True) (S1 (MetaSel (Just "_issIPSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data IPSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show IPSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic IPSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep IPSetUpdate :: Type -> Type #

Hashable IPSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON IPSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData IPSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: IPSetUpdate -> () #

type Rep IPSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep IPSetUpdate = D1 (MetaData "IPSetUpdate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "IPSetUpdate'" PrefixI True) (S1 (MetaSel (Just "_isuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data Predicate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show Predicate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic Predicate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep Predicate :: Type -> Type #

Hashable Predicate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON Predicate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON Predicate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData Predicate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: Predicate -> () #

type Rep Predicate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep Predicate = D1 (MetaData "Predicate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "Predicate'" PrefixI True) (S1 (MetaSel (Just "_pNegated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: (S1 (MetaSel (Just "_pType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PredicateType) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RateBasedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RateBasedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RateBasedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RateBasedRule :: Type -> Type #

Hashable RateBasedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON RateBasedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RateBasedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RateBasedRule -> () #

type Rep RateBasedRule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RateBasedRule = D1 (MetaData "RateBasedRule" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RateBasedRule'" PrefixI True) ((S1 (MetaSel (Just "_rbrMetricName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rbrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rbrRuleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) :*: (S1 (MetaSel (Just "_rbrMatchPredicates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Predicate]) :*: (S1 (MetaSel (Just "_rbrRateKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RateKey) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RegexMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RegexMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RegexMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RegexMatchSet :: Type -> Type #

Hashable RegexMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON RegexMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RegexMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RegexMatchSet -> () #

type Rep RegexMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RegexMatchSet = D1 (MetaData "RegexMatchSet" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RegexMatchSet'" PrefixI True) (S1 (MetaSel (Just "_rmsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rmsRegexMatchTuples") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RegexMatchTuple])) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RegexMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RegexMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RegexMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RegexMatchSetSummary :: Type -> Type #

Hashable RegexMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON RegexMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RegexMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RegexMatchSetSummary -> () #

type Rep RegexMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RegexMatchSetSummary = D1 (MetaData "RegexMatchSetSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RegexMatchSetSummary'" PrefixI True) (S1 (MetaSel (Just "_rmssRegexMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RegexMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RegexMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RegexMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RegexMatchSetUpdate :: Type -> Type #

Hashable RegexMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON RegexMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RegexMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RegexMatchSetUpdate -> () #

type Rep RegexMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RegexMatchSetUpdate = D1 (MetaData "RegexMatchSetUpdate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RegexMatchSetUpdate'" PrefixI True) (S1 (MetaSel (Just "_rmsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RegexMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RegexMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RegexMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RegexMatchTuple :: Type -> Type #

Hashable RegexMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON RegexMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON RegexMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RegexMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RegexMatchTuple -> () #

type Rep RegexMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RegexMatchTuple = D1 (MetaData "RegexMatchTuple" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RegexMatchTuple'" PrefixI True) (S1 (MetaSel (Just "_rmtFieldToMatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FieldToMatch) :*: (S1 (MetaSel (Just "_rmtTextTransformation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextTransformation) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RegexPatternSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RegexPatternSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RegexPatternSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RegexPatternSet :: Type -> Type #

Hashable RegexPatternSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON RegexPatternSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RegexPatternSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RegexPatternSet -> () #

type Rep RegexPatternSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RegexPatternSet = D1 (MetaData "RegexPatternSet" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RegexPatternSet'" PrefixI True) (S1 (MetaSel (Just "_rpsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rpsRegexPatternSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RegexPatternSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RegexPatternSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RegexPatternSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RegexPatternSetSummary :: Type -> Type #

Hashable RegexPatternSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON RegexPatternSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RegexPatternSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RegexPatternSetSummary -> () #

type Rep RegexPatternSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RegexPatternSetSummary = D1 (MetaData "RegexPatternSetSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RegexPatternSetSummary'" PrefixI True) (S1 (MetaSel (Just "_rpssRegexPatternSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RegexPatternSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RegexPatternSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RegexPatternSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RegexPatternSetUpdate :: Type -> Type #

Hashable RegexPatternSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON RegexPatternSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RegexPatternSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RegexPatternSetUpdate -> () #

type Rep RegexPatternSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RegexPatternSetUpdate = D1 (MetaData "RegexPatternSetUpdate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RegexPatternSetUpdate'" PrefixI True) (S1 (MetaSel (Just "_rpsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

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

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

Data Rule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show Rule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

showsPrec :: Int -> Rule -> ShowS #

show :: Rule -> String #

showList :: [Rule] -> ShowS #

Generic Rule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep Rule :: Type -> Type #

Methods

from :: Rule -> Rep Rule x #

to :: Rep Rule x -> Rule #

Hashable Rule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

hashWithSalt :: Int -> Rule -> Int #

hash :: Rule -> Int #

FromJSON Rule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData Rule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: Rule -> () #

type Rep Rule Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep Rule = D1 (MetaData "Rule" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "Rule'" PrefixI True) ((S1 (MetaSel (Just "_rMetricName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_rRuleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 .

RuleGroup

data RuleGroup Source #

A collection of predefined rules that you can add to a web ACL.

Rule groups are subject to the following limits:

  • Three rule groups per account. You can request an increase to this limit by contacting customer support.
  • One rule group per web ACL.
  • Ten rules per rule group.

See: ruleGroup smart constructor.

Instances
Eq RuleGroup Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RuleGroup Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

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

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

toConstr :: RuleGroup -> Constr #

dataTypeOf :: RuleGroup -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RuleGroup Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RuleGroup Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RuleGroup Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RuleGroup :: Type -> Type #

Hashable RuleGroup Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON RuleGroup Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RuleGroup Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RuleGroup -> () #

type Rep RuleGroup Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RuleGroup = D1 (MetaData "RuleGroup" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RuleGroup'" PrefixI True) (S1 (MetaSel (Just "_rgMetricName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rgName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rgRuleGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

ruleGroup Source #

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

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

  • rgMetricName - A friendly name or description for the metrics for this RuleGroup . 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 RuleGroup .
  • rgName - The friendly name or description for the RuleGroup . You can't change the name of a RuleGroup after you create it.
  • rgRuleGroupId - A unique identifier for a RuleGroup . You use RuleGroupId to get more information about a RuleGroup (see GetRuleGroup ), update a RuleGroup (see UpdateRuleGroup ), insert a RuleGroup into a WebACL or delete a one from a WebACL (see UpdateWebACL ), or delete a RuleGroup from AWS WAF (see DeleteRuleGroup ). RuleGroupId is returned by CreateRuleGroup and by ListRuleGroups .

rgMetricName :: Lens' RuleGroup (Maybe Text) Source #

A friendly name or description for the metrics for this RuleGroup . 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 RuleGroup .

rgName :: Lens' RuleGroup (Maybe Text) Source #

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

rgRuleGroupId :: Lens' RuleGroup Text Source #

A unique identifier for a RuleGroup . You use RuleGroupId to get more information about a RuleGroup (see GetRuleGroup ), update a RuleGroup (see UpdateRuleGroup ), insert a RuleGroup into a WebACL or delete a one from a WebACL (see UpdateWebACL ), or delete a RuleGroup from AWS WAF (see DeleteRuleGroup ). RuleGroupId is returned by CreateRuleGroup and by ListRuleGroups .

RuleGroupSummary

data RuleGroupSummary Source #

Contains the identifier and the friendly name or description of the RuleGroup .

See: ruleGroupSummary smart constructor.

Instances
Eq RuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

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

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

toConstr :: RuleGroupSummary -> Constr #

dataTypeOf :: RuleGroupSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RuleGroupSummary :: Type -> Type #

Hashable RuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON RuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RuleGroupSummary -> () #

type Rep RuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RuleGroupSummary = D1 (MetaData "RuleGroupSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RuleGroupSummary'" PrefixI True) (S1 (MetaSel (Just "_rgsRuleGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_rgsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

ruleGroupSummary Source #

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

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

  • rgsRuleGroupId - A unique identifier for a RuleGroup . You use RuleGroupId to get more information about a RuleGroup (see GetRuleGroup ), update a RuleGroup (see UpdateRuleGroup ), insert a RuleGroup into a WebACL or delete one from a WebACL (see UpdateWebACL ), or delete a RuleGroup from AWS WAF (see DeleteRuleGroup ). RuleGroupId is returned by CreateRuleGroup and by ListRuleGroups .
  • rgsName - A friendly name or description of the RuleGroup . You can't change the name of a RuleGroup after you create it.

rgsRuleGroupId :: Lens' RuleGroupSummary Text Source #

A unique identifier for a RuleGroup . You use RuleGroupId to get more information about a RuleGroup (see GetRuleGroup ), update a RuleGroup (see UpdateRuleGroup ), insert a RuleGroup into a WebACL or delete one from a WebACL (see UpdateWebACL ), or delete a RuleGroup from AWS WAF (see DeleteRuleGroup ). RuleGroupId is returned by CreateRuleGroup and by ListRuleGroups .

rgsName :: Lens' RuleGroupSummary Text Source #

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

RuleGroupUpdate

data RuleGroupUpdate Source #

Specifies an ActivatedRule and indicates whether you want to add it to a RuleGroup or delete it from a RuleGroup .

See: ruleGroupUpdate smart constructor.

Instances
Eq RuleGroupUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RuleGroupUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

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

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

toConstr :: RuleGroupUpdate -> Constr #

dataTypeOf :: RuleGroupUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RuleGroupUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RuleGroupUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RuleGroupUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RuleGroupUpdate :: Type -> Type #

Hashable RuleGroupUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON RuleGroupUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RuleGroupUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RuleGroupUpdate -> () #

type Rep RuleGroupUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RuleGroupUpdate = D1 (MetaData "RuleGroupUpdate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RuleGroupUpdate'" PrefixI True) (S1 (MetaSel (Just "_rguAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction) :*: S1 (MetaSel (Just "_rguActivatedRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ActivatedRule)))

ruleGroupUpdate Source #

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

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

  • rguAction - Specify INSERT to add an ActivatedRule to a RuleGroup . Use DELETE to remove an ActivatedRule from a RuleGroup .
  • rguActivatedRule - The ActivatedRule object 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 ).

rguAction :: Lens' RuleGroupUpdate ChangeAction Source #

Specify INSERT to add an ActivatedRule to a RuleGroup . Use DELETE to remove an ActivatedRule from a RuleGroup .

rguActivatedRule :: Lens' RuleGroupUpdate ActivatedRule Source #

The ActivatedRule object 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 ).

RuleSummary

data RuleSummary Source #

Contains the identifier and the friendly name or description of the Rule .

See: ruleSummary smart constructor.

Instances
Eq RuleSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RuleSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RuleSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RuleSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RuleSummary :: Type -> Type #

Hashable RuleSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON RuleSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RuleSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RuleSummary -> () #

type Rep RuleSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RuleSummary = D1 (MetaData "RuleSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RuleSummary'" PrefixI True) (S1 (MetaSel (Just "_rsRuleId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data RuleUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show RuleUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic RuleUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep RuleUpdate :: Type -> Type #

Hashable RuleUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON RuleUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData RuleUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: RuleUpdate -> () #

type Rep RuleUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep RuleUpdate = D1 (MetaData "RuleUpdate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "RuleUpdate'" PrefixI True) (S1 (MetaSel (Just "_ruAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data SampledHTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show SampledHTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic SampledHTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep SampledHTTPRequest :: Type -> Type #

Hashable SampledHTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON SampledHTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData SampledHTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: SampledHTTPRequest -> () #

type Rep SampledHTTPRequest Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SampledHTTPRequest = D1 (MetaData "SampledHTTPRequest" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "SampledHTTPRequest'" PrefixI True) ((S1 (MetaSel (Just "_shttprRuleWithinRuleGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_shttprAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_shttprTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe POSIX)) :*: (S1 (MetaSel (Just "_shttprRequest") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HTTPRequest) :*: S1 (MetaSel (Just "_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:

  • shttprRuleWithinRuleGroup - This value is returned if the GetSampledRequests request specifies the ID of a RuleGroup rather than the ID of an individual rule. RuleWithinRuleGroup is the rule within the specified RuleGroup that matched the request listed in the response.
  • 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 .

shttprRuleWithinRuleGroup :: Lens' SampledHTTPRequest (Maybe Text) Source #

This value is returned if the GetSampledRequests request specifies the ID of a RuleGroup rather than the ID of an individual rule. RuleWithinRuleGroup is the rule within the specified RuleGroup that matched the request listed in the response.

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data SizeConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show SizeConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic SizeConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep SizeConstraint :: Type -> Type #

Hashable SizeConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON SizeConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON SizeConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData SizeConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: SizeConstraint -> () #

type Rep SizeConstraint Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SizeConstraint = D1 (MetaData "SizeConstraint" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "SizeConstraint'" PrefixI True) ((S1 (MetaSel (Just "_scFieldToMatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FieldToMatch) :*: S1 (MetaSel (Just "_scTextTransformation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextTransformation)) :*: (S1 (MetaSel (Just "_scComparisonOperator") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ComparisonOperator) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data SizeConstraintSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show SizeConstraintSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic SizeConstraintSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep SizeConstraintSet :: Type -> Type #

Hashable SizeConstraintSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON SizeConstraintSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData SizeConstraintSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: SizeConstraintSet -> () #

type Rep SizeConstraintSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SizeConstraintSet = D1 (MetaData "SizeConstraintSet" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "SizeConstraintSet'" PrefixI True) (S1 (MetaSel (Just "_scsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_scsSizeConstraintSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data SizeConstraintSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show SizeConstraintSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic SizeConstraintSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep SizeConstraintSetSummary :: Type -> Type #

Hashable SizeConstraintSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON SizeConstraintSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData SizeConstraintSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SizeConstraintSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SizeConstraintSetSummary = D1 (MetaData "SizeConstraintSetSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "SizeConstraintSetSummary'" PrefixI True) (S1 (MetaSel (Just "_scssSizeConstraintSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data SizeConstraintSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show SizeConstraintSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic SizeConstraintSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep SizeConstraintSetUpdate :: Type -> Type #

Hashable SizeConstraintSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON SizeConstraintSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData SizeConstraintSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: SizeConstraintSetUpdate -> () #

type Rep SizeConstraintSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SizeConstraintSetUpdate = D1 (MetaData "SizeConstraintSetUpdate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "SizeConstraintSetUpdate'" PrefixI True) (S1 (MetaSel (Just "_scsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data SqlInjectionMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show SqlInjectionMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic SqlInjectionMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep SqlInjectionMatchSet :: Type -> Type #

Hashable SqlInjectionMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON SqlInjectionMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData SqlInjectionMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: SqlInjectionMatchSet -> () #

type Rep SqlInjectionMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SqlInjectionMatchSet = D1 (MetaData "SqlInjectionMatchSet" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "SqlInjectionMatchSet'" PrefixI True) (S1 (MetaSel (Just "_simsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_simsSqlInjectionMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data SqlInjectionMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show SqlInjectionMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic SqlInjectionMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep SqlInjectionMatchSetSummary :: Type -> Type #

Hashable SqlInjectionMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON SqlInjectionMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData SqlInjectionMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SqlInjectionMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SqlInjectionMatchSetSummary = D1 (MetaData "SqlInjectionMatchSetSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "SqlInjectionMatchSetSummary'" PrefixI True) (S1 (MetaSel (Just "_simssSqlInjectionMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data SqlInjectionMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show SqlInjectionMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic SqlInjectionMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep SqlInjectionMatchSetUpdate :: Type -> Type #

Hashable SqlInjectionMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON SqlInjectionMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData SqlInjectionMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SqlInjectionMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SqlInjectionMatchSetUpdate = D1 (MetaData "SqlInjectionMatchSetUpdate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "SqlInjectionMatchSetUpdate'" PrefixI True) (S1 (MetaSel (Just "_simsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data SqlInjectionMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show SqlInjectionMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic SqlInjectionMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep SqlInjectionMatchTuple :: Type -> Type #

Hashable SqlInjectionMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON SqlInjectionMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON SqlInjectionMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData SqlInjectionMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: SqlInjectionMatchTuple -> () #

type Rep SqlInjectionMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SqlInjectionMatchTuple = D1 (MetaData "SqlInjectionMatchTuple" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "SqlInjectionMatchTuple'" PrefixI True) (S1 (MetaSel (Just "_simtFieldToMatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FieldToMatch) :*: S1 (MetaSel (Just "_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.

SubscribedRuleGroupSummary

data SubscribedRuleGroupSummary Source #

A summary of the rule groups you are subscribed to.

See: subscribedRuleGroupSummary smart constructor.

Instances
Eq SubscribedRuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data SubscribedRuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

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

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

toConstr :: SubscribedRuleGroupSummary -> Constr #

dataTypeOf :: SubscribedRuleGroupSummary -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SubscribedRuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show SubscribedRuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic SubscribedRuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep SubscribedRuleGroupSummary :: Type -> Type #

Hashable SubscribedRuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON SubscribedRuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData SubscribedRuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SubscribedRuleGroupSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep SubscribedRuleGroupSummary = D1 (MetaData "SubscribedRuleGroupSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "SubscribedRuleGroupSummary'" PrefixI True) (S1 (MetaSel (Just "_srgsRuleGroupId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "_srgsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_srgsMetricName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

subscribedRuleGroupSummary Source #

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

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

  • srgsRuleGroupId - A unique identifier for a RuleGroup .
  • srgsName - A friendly name or description of the RuleGroup . You can't change the name of a RuleGroup after you create it.
  • srgsMetricName - A friendly name or description for the metrics for this RuleGroup . 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 RuleGroup .

srgsRuleGroupId :: Lens' SubscribedRuleGroupSummary Text Source #

A unique identifier for a RuleGroup .

srgsName :: Lens' SubscribedRuleGroupSummary Text Source #

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

srgsMetricName :: Lens' SubscribedRuleGroupSummary Text Source #

A friendly name or description for the metrics for this RuleGroup . 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 RuleGroup .

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data TimeWindow Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show TimeWindow Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic TimeWindow Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep TimeWindow :: Type -> Type #

Hashable TimeWindow Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON TimeWindow Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON TimeWindow Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData TimeWindow Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: TimeWindow -> () #

type Rep TimeWindow Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep TimeWindow = D1 (MetaData "TimeWindow" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "TimeWindow'" PrefixI True) (S1 (MetaSel (Just "_twStartTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 POSIX) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data WafAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show WafAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic WafAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep WafAction :: Type -> Type #

Hashable WafAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON WafAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON WafAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData WafAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: WafAction -> () #

type Rep WafAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep WafAction = D1 (MetaData "WafAction" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" True) (C1 (MetaCons "WafAction'" PrefixI True) (S1 (MetaSel (Just "_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 .

WafOverrideAction

data WafOverrideAction Source #

The action to take if any rule within the RuleGroup matches a request.

See: wafOverrideAction smart constructor.

Instances
Eq WafOverrideAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data WafOverrideAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

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

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

toConstr :: WafOverrideAction -> Constr #

dataTypeOf :: WafOverrideAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Read WafOverrideAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show WafOverrideAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic WafOverrideAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep WafOverrideAction :: Type -> Type #

Hashable WafOverrideAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON WafOverrideAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON WafOverrideAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData WafOverrideAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: WafOverrideAction -> () #

type Rep WafOverrideAction Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep WafOverrideAction = D1 (MetaData "WafOverrideAction" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" True) (C1 (MetaCons "WafOverrideAction'" PrefixI True) (S1 (MetaSel (Just "_woaType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 WafOverrideActionType)))

wafOverrideAction Source #

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

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

  • woaType - COUNT overrides the action specified by the individual rule within a RuleGroup . If set to NONE , the rule's action will take place.

woaType :: Lens' WafOverrideAction WafOverrideActionType Source #

COUNT overrides the action specified by the individual rule within a RuleGroup . If set to NONE , the rule's action will take place.

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

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

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

Data WebACL Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show WebACL Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic WebACL Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep WebACL :: Type -> Type #

Methods

from :: WebACL -> Rep WebACL x #

to :: Rep WebACL x -> WebACL #

Hashable WebACL Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

hashWithSalt :: Int -> WebACL -> Int #

hash :: WebACL -> Int #

FromJSON WebACL Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData WebACL Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: WebACL -> () #

type Rep WebACL Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep WebACL = D1 (MetaData "WebACL" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "WebACL'" PrefixI True) ((S1 (MetaSel (Just "_waMetricName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_waName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_waWebACLId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "_waDefaultAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WafAction) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data WebACLSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show WebACLSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic WebACLSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep WebACLSummary :: Type -> Type #

Hashable WebACLSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON WebACLSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData WebACLSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: WebACLSummary -> () #

type Rep WebACLSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep WebACLSummary = D1 (MetaData "WebACLSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "WebACLSummary'" PrefixI True) (S1 (MetaSel (Just "_wasWebACLId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data WebACLUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show WebACLUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic WebACLUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep WebACLUpdate :: Type -> Type #

Hashable WebACLUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON WebACLUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData WebACLUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: WebACLUpdate -> () #

type Rep WebACLUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep WebACLUpdate = D1 (MetaData "WebACLUpdate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "WebACLUpdate'" PrefixI True) (S1 (MetaSel (Just "_wauAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data XSSMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show XSSMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic XSSMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep XSSMatchSet :: Type -> Type #

Hashable XSSMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON XSSMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData XSSMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: XSSMatchSet -> () #

type Rep XSSMatchSet Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep XSSMatchSet = D1 (MetaData "XSSMatchSet" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "XSSMatchSet'" PrefixI True) (S1 (MetaSel (Just "_xmsName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_xmsXSSMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data XSSMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show XSSMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic XSSMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep XSSMatchSetSummary :: Type -> Type #

Hashable XSSMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON XSSMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData XSSMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: XSSMatchSetSummary -> () #

type Rep XSSMatchSetSummary Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep XSSMatchSetSummary = D1 (MetaData "XSSMatchSetSummary" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "XSSMatchSetSummary'" PrefixI True) (S1 (MetaSel (Just "_xmssXSSMatchSetId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data XSSMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show XSSMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic XSSMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep XSSMatchSetUpdate :: Type -> Type #

Hashable XSSMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON XSSMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData XSSMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: XSSMatchSetUpdate -> () #

type Rep XSSMatchSetUpdate Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep XSSMatchSetUpdate = D1 (MetaData "XSSMatchSetUpdate" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "XSSMatchSetUpdate'" PrefixI True) (S1 (MetaSel (Just "_xmsuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ChangeAction) :*: S1 (MetaSel (Just "_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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Data XSSMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

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 # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Show XSSMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Generic XSSMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Associated Types

type Rep XSSMatchTuple :: Type -> Type #

Hashable XSSMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

ToJSON XSSMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

FromJSON XSSMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

NFData XSSMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

Methods

rnf :: XSSMatchTuple -> () #

type Rep XSSMatchTuple Source # 
Instance details

Defined in Network.AWS.WAF.Types.Product

type Rep XSSMatchTuple = D1 (MetaData "XSSMatchTuple" "Network.AWS.WAF.Types.Product" "amazonka-waf-1.6.1-AAUMqlxoZ2N3dlHnZE2nzz" False) (C1 (MetaCons "XSSMatchTuple'" PrefixI True) (S1 (MetaSel (Just "_xmtFieldToMatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FieldToMatch) :*: S1 (MetaSel (Just "_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.