{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.WAFV2.Types.RateBasedStatement
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.WAFV2.Types.RateBasedStatement where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.WAFV2.Types.ForwardedIPConfig
import Amazonka.WAFV2.Types.RateBasedStatementAggregateKeyType
import {-# SOURCE #-} Amazonka.WAFV2.Types.Statement

-- | A rate-based rule tracks the rate of requests for each originating IP
-- address, and triggers the rule action when the rate exceeds a limit that
-- you specify on the number of requests in any 5-minute time span. You can
-- use this to put a temporary block on requests from an IP address that is
-- sending excessive requests.
--
-- WAF tracks and manages web requests separately for each instance of a
-- rate-based rule that you use. For example, if you provide the same
-- rate-based rule settings in two web ACLs, each of the two rule
-- statements represents a separate instance of the rate-based rule and
-- gets its own tracking and management by WAF. If you define a rate-based
-- rule inside a rule group, and then use that rule group in multiple
-- places, each use creates a separate instance of the rate-based rule that
-- gets its own tracking and management by WAF.
--
-- When the rule action triggers, WAF blocks additional requests from the
-- IP address until the request rate falls below the limit.
--
-- You can optionally nest another statement inside the rate-based
-- statement, to narrow the scope of the rule so that it only counts
-- requests that match the nested statement. For example, based on recent
-- requests that you have seen from an attacker, you might create a
-- rate-based rule with a nested AND rule statement that contains the
-- following nested statements:
--
-- -   An IP match statement with an IP set that specified the address
--     192.0.2.44.
--
-- -   A string match statement that searches in the User-Agent header for
--     the string BadBot.
--
-- In this rate-based rule, you also define a rate limit. For this example,
-- the rate limit is 1,000. Requests that meet the criteria of both of the
-- nested statements are counted. If the count exceeds 1,000 requests per
-- five minutes, the rule action triggers. Requests that do not meet the
-- criteria of both of the nested statements are not counted towards the
-- rate limit and are not affected by this rule.
--
-- You cannot nest a @RateBasedStatement@ inside another statement, for
-- example inside a @NotStatement@ or @OrStatement@. You can define a
-- @RateBasedStatement@ inside a web ACL and inside a rule group.
--
-- /See:/ 'newRateBasedStatement' smart constructor.
data RateBasedStatement = RateBasedStatement'
  { -- | The configuration for inspecting IP addresses in an HTTP header that you
    -- specify, instead of using the IP address that\'s reported by the web
    -- request origin. Commonly, this is the X-Forwarded-For (XFF) header, but
    -- you can specify any header name.
    --
    -- If the specified header isn\'t present in the request, WAF doesn\'t
    -- apply the rule to the web request at all.
    --
    -- This is required if @AggregateKeyType@ is set to @FORWARDED_IP@.
    RateBasedStatement -> Maybe ForwardedIPConfig
forwardedIPConfig :: Prelude.Maybe ForwardedIPConfig,
    -- | An optional nested statement that narrows the scope of the web requests
    -- that are evaluated by the rate-based statement. Requests are only
    -- tracked by the rate-based statement if they match the scope-down
    -- statement. You can use any nestable Statement in the scope-down
    -- statement, and you can nest statements at any level, the same as you can
    -- for a rule statement.
    RateBasedStatement -> Maybe Statement
scopeDownStatement :: Prelude.Maybe Statement,
    -- | The limit on requests per 5-minute period for a single originating IP
    -- address. If the statement includes a @ScopeDownStatement@, this limit is
    -- applied only to the requests that match the statement.
    RateBasedStatement -> Natural
limit :: Prelude.Natural,
    -- | Setting that indicates how to aggregate the request counts. The options
    -- are the following:
    --
    -- -   IP - Aggregate the request counts on the IP address from the web
    --     request origin.
    --
    -- -   FORWARDED_IP - Aggregate the request counts on the first IP address
    --     in an HTTP header. If you use this, configure the
    --     @ForwardedIPConfig@, to specify the header to use.
    RateBasedStatement -> RateBasedStatementAggregateKeyType
aggregateKeyType :: RateBasedStatementAggregateKeyType
  }
  deriving (RateBasedStatement -> RateBasedStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RateBasedStatement -> RateBasedStatement -> Bool
$c/= :: RateBasedStatement -> RateBasedStatement -> Bool
== :: RateBasedStatement -> RateBasedStatement -> Bool
$c== :: RateBasedStatement -> RateBasedStatement -> Bool
Prelude.Eq, ReadPrec [RateBasedStatement]
ReadPrec RateBasedStatement
Int -> ReadS RateBasedStatement
ReadS [RateBasedStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RateBasedStatement]
$creadListPrec :: ReadPrec [RateBasedStatement]
readPrec :: ReadPrec RateBasedStatement
$creadPrec :: ReadPrec RateBasedStatement
readList :: ReadS [RateBasedStatement]
$creadList :: ReadS [RateBasedStatement]
readsPrec :: Int -> ReadS RateBasedStatement
$creadsPrec :: Int -> ReadS RateBasedStatement
Prelude.Read, Int -> RateBasedStatement -> ShowS
[RateBasedStatement] -> ShowS
RateBasedStatement -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RateBasedStatement] -> ShowS
$cshowList :: [RateBasedStatement] -> ShowS
show :: RateBasedStatement -> String
$cshow :: RateBasedStatement -> String
showsPrec :: Int -> RateBasedStatement -> ShowS
$cshowsPrec :: Int -> RateBasedStatement -> ShowS
Prelude.Show, forall x. Rep RateBasedStatement x -> RateBasedStatement
forall x. RateBasedStatement -> Rep RateBasedStatement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RateBasedStatement x -> RateBasedStatement
$cfrom :: forall x. RateBasedStatement -> Rep RateBasedStatement x
Prelude.Generic)

-- |
-- Create a value of 'RateBasedStatement' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'forwardedIPConfig', 'rateBasedStatement_forwardedIPConfig' - The configuration for inspecting IP addresses in an HTTP header that you
-- specify, instead of using the IP address that\'s reported by the web
-- request origin. Commonly, this is the X-Forwarded-For (XFF) header, but
-- you can specify any header name.
--
-- If the specified header isn\'t present in the request, WAF doesn\'t
-- apply the rule to the web request at all.
--
-- This is required if @AggregateKeyType@ is set to @FORWARDED_IP@.
--
-- 'scopeDownStatement', 'rateBasedStatement_scopeDownStatement' - An optional nested statement that narrows the scope of the web requests
-- that are evaluated by the rate-based statement. Requests are only
-- tracked by the rate-based statement if they match the scope-down
-- statement. You can use any nestable Statement in the scope-down
-- statement, and you can nest statements at any level, the same as you can
-- for a rule statement.
--
-- 'limit', 'rateBasedStatement_limit' - The limit on requests per 5-minute period for a single originating IP
-- address. If the statement includes a @ScopeDownStatement@, this limit is
-- applied only to the requests that match the statement.
--
-- 'aggregateKeyType', 'rateBasedStatement_aggregateKeyType' - Setting that indicates how to aggregate the request counts. The options
-- are the following:
--
-- -   IP - Aggregate the request counts on the IP address from the web
--     request origin.
--
-- -   FORWARDED_IP - Aggregate the request counts on the first IP address
--     in an HTTP header. If you use this, configure the
--     @ForwardedIPConfig@, to specify the header to use.
newRateBasedStatement ::
  -- | 'limit'
  Prelude.Natural ->
  -- | 'aggregateKeyType'
  RateBasedStatementAggregateKeyType ->
  RateBasedStatement
newRateBasedStatement :: Natural -> RateBasedStatementAggregateKeyType -> RateBasedStatement
newRateBasedStatement Natural
pLimit_ RateBasedStatementAggregateKeyType
pAggregateKeyType_ =
  RateBasedStatement'
    { $sel:forwardedIPConfig:RateBasedStatement' :: Maybe ForwardedIPConfig
forwardedIPConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:scopeDownStatement:RateBasedStatement' :: Maybe Statement
scopeDownStatement = forall a. Maybe a
Prelude.Nothing,
      $sel:limit:RateBasedStatement' :: Natural
limit = Natural
pLimit_,
      $sel:aggregateKeyType:RateBasedStatement' :: RateBasedStatementAggregateKeyType
aggregateKeyType = RateBasedStatementAggregateKeyType
pAggregateKeyType_
    }

-- | The configuration for inspecting IP addresses in an HTTP header that you
-- specify, instead of using the IP address that\'s reported by the web
-- request origin. Commonly, this is the X-Forwarded-For (XFF) header, but
-- you can specify any header name.
--
-- If the specified header isn\'t present in the request, WAF doesn\'t
-- apply the rule to the web request at all.
--
-- This is required if @AggregateKeyType@ is set to @FORWARDED_IP@.
rateBasedStatement_forwardedIPConfig :: Lens.Lens' RateBasedStatement (Prelude.Maybe ForwardedIPConfig)
rateBasedStatement_forwardedIPConfig :: Lens' RateBasedStatement (Maybe ForwardedIPConfig)
rateBasedStatement_forwardedIPConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RateBasedStatement' {Maybe ForwardedIPConfig
forwardedIPConfig :: Maybe ForwardedIPConfig
$sel:forwardedIPConfig:RateBasedStatement' :: RateBasedStatement -> Maybe ForwardedIPConfig
forwardedIPConfig} -> Maybe ForwardedIPConfig
forwardedIPConfig) (\s :: RateBasedStatement
s@RateBasedStatement' {} Maybe ForwardedIPConfig
a -> RateBasedStatement
s {$sel:forwardedIPConfig:RateBasedStatement' :: Maybe ForwardedIPConfig
forwardedIPConfig = Maybe ForwardedIPConfig
a} :: RateBasedStatement)

-- | An optional nested statement that narrows the scope of the web requests
-- that are evaluated by the rate-based statement. Requests are only
-- tracked by the rate-based statement if they match the scope-down
-- statement. You can use any nestable Statement in the scope-down
-- statement, and you can nest statements at any level, the same as you can
-- for a rule statement.
rateBasedStatement_scopeDownStatement :: Lens.Lens' RateBasedStatement (Prelude.Maybe Statement)
rateBasedStatement_scopeDownStatement :: Lens' RateBasedStatement (Maybe Statement)
rateBasedStatement_scopeDownStatement = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RateBasedStatement' {Maybe Statement
scopeDownStatement :: Maybe Statement
$sel:scopeDownStatement:RateBasedStatement' :: RateBasedStatement -> Maybe Statement
scopeDownStatement} -> Maybe Statement
scopeDownStatement) (\s :: RateBasedStatement
s@RateBasedStatement' {} Maybe Statement
a -> RateBasedStatement
s {$sel:scopeDownStatement:RateBasedStatement' :: Maybe Statement
scopeDownStatement = Maybe Statement
a} :: RateBasedStatement)

-- | The limit on requests per 5-minute period for a single originating IP
-- address. If the statement includes a @ScopeDownStatement@, this limit is
-- applied only to the requests that match the statement.
rateBasedStatement_limit :: Lens.Lens' RateBasedStatement Prelude.Natural
rateBasedStatement_limit :: Lens' RateBasedStatement Natural
rateBasedStatement_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RateBasedStatement' {Natural
limit :: Natural
$sel:limit:RateBasedStatement' :: RateBasedStatement -> Natural
limit} -> Natural
limit) (\s :: RateBasedStatement
s@RateBasedStatement' {} Natural
a -> RateBasedStatement
s {$sel:limit:RateBasedStatement' :: Natural
limit = Natural
a} :: RateBasedStatement)

-- | Setting that indicates how to aggregate the request counts. The options
-- are the following:
--
-- -   IP - Aggregate the request counts on the IP address from the web
--     request origin.
--
-- -   FORWARDED_IP - Aggregate the request counts on the first IP address
--     in an HTTP header. If you use this, configure the
--     @ForwardedIPConfig@, to specify the header to use.
rateBasedStatement_aggregateKeyType :: Lens.Lens' RateBasedStatement RateBasedStatementAggregateKeyType
rateBasedStatement_aggregateKeyType :: Lens' RateBasedStatement RateBasedStatementAggregateKeyType
rateBasedStatement_aggregateKeyType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RateBasedStatement' {RateBasedStatementAggregateKeyType
aggregateKeyType :: RateBasedStatementAggregateKeyType
$sel:aggregateKeyType:RateBasedStatement' :: RateBasedStatement -> RateBasedStatementAggregateKeyType
aggregateKeyType} -> RateBasedStatementAggregateKeyType
aggregateKeyType) (\s :: RateBasedStatement
s@RateBasedStatement' {} RateBasedStatementAggregateKeyType
a -> RateBasedStatement
s {$sel:aggregateKeyType:RateBasedStatement' :: RateBasedStatementAggregateKeyType
aggregateKeyType = RateBasedStatementAggregateKeyType
a} :: RateBasedStatement)

instance Data.FromJSON RateBasedStatement where
  parseJSON :: Value -> Parser RateBasedStatement
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"RateBasedStatement"
      ( \Object
x ->
          Maybe ForwardedIPConfig
-> Maybe Statement
-> Natural
-> RateBasedStatementAggregateKeyType
-> RateBasedStatement
RateBasedStatement'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ForwardedIPConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ScopeDownStatement")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Limit")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"AggregateKeyType")
      )

instance Prelude.Hashable RateBasedStatement where
  hashWithSalt :: Int -> RateBasedStatement -> Int
hashWithSalt Int
_salt RateBasedStatement' {Natural
Maybe ForwardedIPConfig
Maybe Statement
RateBasedStatementAggregateKeyType
aggregateKeyType :: RateBasedStatementAggregateKeyType
limit :: Natural
scopeDownStatement :: Maybe Statement
forwardedIPConfig :: Maybe ForwardedIPConfig
$sel:aggregateKeyType:RateBasedStatement' :: RateBasedStatement -> RateBasedStatementAggregateKeyType
$sel:limit:RateBasedStatement' :: RateBasedStatement -> Natural
$sel:scopeDownStatement:RateBasedStatement' :: RateBasedStatement -> Maybe Statement
$sel:forwardedIPConfig:RateBasedStatement' :: RateBasedStatement -> Maybe ForwardedIPConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ForwardedIPConfig
forwardedIPConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Statement
scopeDownStatement
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` RateBasedStatementAggregateKeyType
aggregateKeyType

instance Prelude.NFData RateBasedStatement where
  rnf :: RateBasedStatement -> ()
rnf RateBasedStatement' {Natural
Maybe ForwardedIPConfig
Maybe Statement
RateBasedStatementAggregateKeyType
aggregateKeyType :: RateBasedStatementAggregateKeyType
limit :: Natural
scopeDownStatement :: Maybe Statement
forwardedIPConfig :: Maybe ForwardedIPConfig
$sel:aggregateKeyType:RateBasedStatement' :: RateBasedStatement -> RateBasedStatementAggregateKeyType
$sel:limit:RateBasedStatement' :: RateBasedStatement -> Natural
$sel:scopeDownStatement:RateBasedStatement' :: RateBasedStatement -> Maybe Statement
$sel:forwardedIPConfig:RateBasedStatement' :: RateBasedStatement -> Maybe ForwardedIPConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ForwardedIPConfig
forwardedIPConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Statement
scopeDownStatement
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RateBasedStatementAggregateKeyType
aggregateKeyType

instance Data.ToJSON RateBasedStatement where
  toJSON :: RateBasedStatement -> Value
toJSON RateBasedStatement' {Natural
Maybe ForwardedIPConfig
Maybe Statement
RateBasedStatementAggregateKeyType
aggregateKeyType :: RateBasedStatementAggregateKeyType
limit :: Natural
scopeDownStatement :: Maybe Statement
forwardedIPConfig :: Maybe ForwardedIPConfig
$sel:aggregateKeyType:RateBasedStatement' :: RateBasedStatement -> RateBasedStatementAggregateKeyType
$sel:limit:RateBasedStatement' :: RateBasedStatement -> Natural
$sel:scopeDownStatement:RateBasedStatement' :: RateBasedStatement -> Maybe Statement
$sel:forwardedIPConfig:RateBasedStatement' :: RateBasedStatement -> Maybe ForwardedIPConfig
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ForwardedIPConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ForwardedIPConfig
forwardedIPConfig,
            (Key
"ScopeDownStatement" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Statement
scopeDownStatement,
            forall a. a -> Maybe a
Prelude.Just (Key
"Limit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
limit),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"AggregateKeyType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= RateBasedStatementAggregateKeyType
aggregateKeyType)
          ]
      )