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

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

-- |
-- Module      : Amazonka.WAF.UpdateRateBasedRule
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This is __AWS WAF Classic__ documentation. For more information, see
-- <https://docs.aws.amazon.com/waf/latest/developerguide/classic-waf-chapter.html AWS WAF Classic>
-- in the developer guide.
--
-- __For the latest version of AWS WAF__, use the AWS WAFV2 API and see the
-- <https://docs.aws.amazon.com/waf/latest/developerguide/waf-chapter.html AWS WAF Developer Guide>.
-- With the latest version, AWS WAF has a single set of endpoints for
-- regional and global use.
--
-- Inserts or deletes Predicate objects in a rule and updates the
-- @RateLimit@ in the rule.
--
-- Each @Predicate@ object identifies a predicate, such as a ByteMatchSet
-- or an IPSet, that specifies the web requests that you want to block or
-- count. The @RateLimit@ specifies the number of requests every five
-- minutes that triggers the rule.
--
-- If you add more than one predicate to a @RateBasedRule@, a request must
-- match all the predicates and exceed the @RateLimit@ to be counted or
-- blocked. For example, suppose you add the following to a
-- @RateBasedRule@:
--
-- -   An @IPSet@ that matches the IP address @192.0.2.44\/32@
--
-- -   A @ByteMatchSet@ that matches @BadBot@ in the @User-Agent@ header
--
-- Further, you specify a @RateLimit@ of 1,000.
--
-- You then add the @RateBasedRule@ to a @WebACL@ and specify that you want
-- to block requests that satisfy the rule. For a request to be blocked, it
-- must come from the IP address 192.0.2.44 /and/ the @User-Agent@ header
-- in the request must contain the value @BadBot@. Further, requests that
-- match these two conditions much be received at a rate of more than 1,000
-- every five minutes. If the rate drops below this limit, AWS WAF no
-- longer blocks the requests.
--
-- As a second example, suppose you want to limit requests to a particular
-- page on your site. To do this, you could add the following to a
-- @RateBasedRule@:
--
-- -   A @ByteMatchSet@ with @FieldToMatch@ of @URI@
--
-- -   A @PositionalConstraint@ of @STARTS_WITH@
--
-- -   A @TargetString@ of @login@
--
-- Further, you specify a @RateLimit@ of 1,000.
--
-- By adding this @RateBasedRule@ to a @WebACL@, you could limit requests
-- to your login page without affecting the rest of your site.
module Amazonka.WAF.UpdateRateBasedRule
  ( -- * Creating a Request
    UpdateRateBasedRule (..),
    newUpdateRateBasedRule,

    -- * Request Lenses
    updateRateBasedRule_ruleId,
    updateRateBasedRule_changeToken,
    updateRateBasedRule_updates,
    updateRateBasedRule_rateLimit,

    -- * Destructuring the Response
    UpdateRateBasedRuleResponse (..),
    newUpdateRateBasedRuleResponse,

    -- * Response Lenses
    updateRateBasedRuleResponse_changeToken,
    updateRateBasedRuleResponse_httpStatus,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.WAF.Types

-- | /See:/ 'newUpdateRateBasedRule' smart constructor.
data UpdateRateBasedRule = UpdateRateBasedRule'
  { -- | The @RuleId@ of the @RateBasedRule@ that you want to update. @RuleId@ is
    -- returned by @CreateRateBasedRule@ and by ListRateBasedRules.
    UpdateRateBasedRule -> Text
ruleId :: Prelude.Text,
    -- | The value returned by the most recent call to GetChangeToken.
    UpdateRateBasedRule -> Text
changeToken :: Prelude.Text,
    -- | An array of @RuleUpdate@ objects that you want to insert into or delete
    -- from a RateBasedRule.
    UpdateRateBasedRule -> [RuleUpdate]
updates :: [RuleUpdate],
    -- | 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.
    UpdateRateBasedRule -> Natural
rateLimit :: Prelude.Natural
  }
  deriving (UpdateRateBasedRule -> UpdateRateBasedRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRateBasedRule -> UpdateRateBasedRule -> Bool
$c/= :: UpdateRateBasedRule -> UpdateRateBasedRule -> Bool
== :: UpdateRateBasedRule -> UpdateRateBasedRule -> Bool
$c== :: UpdateRateBasedRule -> UpdateRateBasedRule -> Bool
Prelude.Eq, ReadPrec [UpdateRateBasedRule]
ReadPrec UpdateRateBasedRule
Int -> ReadS UpdateRateBasedRule
ReadS [UpdateRateBasedRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRateBasedRule]
$creadListPrec :: ReadPrec [UpdateRateBasedRule]
readPrec :: ReadPrec UpdateRateBasedRule
$creadPrec :: ReadPrec UpdateRateBasedRule
readList :: ReadS [UpdateRateBasedRule]
$creadList :: ReadS [UpdateRateBasedRule]
readsPrec :: Int -> ReadS UpdateRateBasedRule
$creadsPrec :: Int -> ReadS UpdateRateBasedRule
Prelude.Read, Int -> UpdateRateBasedRule -> ShowS
[UpdateRateBasedRule] -> ShowS
UpdateRateBasedRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRateBasedRule] -> ShowS
$cshowList :: [UpdateRateBasedRule] -> ShowS
show :: UpdateRateBasedRule -> String
$cshow :: UpdateRateBasedRule -> String
showsPrec :: Int -> UpdateRateBasedRule -> ShowS
$cshowsPrec :: Int -> UpdateRateBasedRule -> ShowS
Prelude.Show, forall x. Rep UpdateRateBasedRule x -> UpdateRateBasedRule
forall x. UpdateRateBasedRule -> Rep UpdateRateBasedRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRateBasedRule x -> UpdateRateBasedRule
$cfrom :: forall x. UpdateRateBasedRule -> Rep UpdateRateBasedRule x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRateBasedRule' 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:
--
-- 'ruleId', 'updateRateBasedRule_ruleId' - The @RuleId@ of the @RateBasedRule@ that you want to update. @RuleId@ is
-- returned by @CreateRateBasedRule@ and by ListRateBasedRules.
--
-- 'changeToken', 'updateRateBasedRule_changeToken' - The value returned by the most recent call to GetChangeToken.
--
-- 'updates', 'updateRateBasedRule_updates' - An array of @RuleUpdate@ objects that you want to insert into or delete
-- from a RateBasedRule.
--
-- 'rateLimit', 'updateRateBasedRule_rateLimit' - 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.
newUpdateRateBasedRule ::
  -- | 'ruleId'
  Prelude.Text ->
  -- | 'changeToken'
  Prelude.Text ->
  -- | 'rateLimit'
  Prelude.Natural ->
  UpdateRateBasedRule
newUpdateRateBasedRule :: Text -> Text -> Natural -> UpdateRateBasedRule
newUpdateRateBasedRule
  Text
pRuleId_
  Text
pChangeToken_
  Natural
pRateLimit_ =
    UpdateRateBasedRule'
      { $sel:ruleId:UpdateRateBasedRule' :: Text
ruleId = Text
pRuleId_,
        $sel:changeToken:UpdateRateBasedRule' :: Text
changeToken = Text
pChangeToken_,
        $sel:updates:UpdateRateBasedRule' :: [RuleUpdate]
updates = forall a. Monoid a => a
Prelude.mempty,
        $sel:rateLimit:UpdateRateBasedRule' :: Natural
rateLimit = Natural
pRateLimit_
      }

-- | The @RuleId@ of the @RateBasedRule@ that you want to update. @RuleId@ is
-- returned by @CreateRateBasedRule@ and by ListRateBasedRules.
updateRateBasedRule_ruleId :: Lens.Lens' UpdateRateBasedRule Prelude.Text
updateRateBasedRule_ruleId :: Lens' UpdateRateBasedRule Text
updateRateBasedRule_ruleId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRateBasedRule' {Text
ruleId :: Text
$sel:ruleId:UpdateRateBasedRule' :: UpdateRateBasedRule -> Text
ruleId} -> Text
ruleId) (\s :: UpdateRateBasedRule
s@UpdateRateBasedRule' {} Text
a -> UpdateRateBasedRule
s {$sel:ruleId:UpdateRateBasedRule' :: Text
ruleId = Text
a} :: UpdateRateBasedRule)

-- | The value returned by the most recent call to GetChangeToken.
updateRateBasedRule_changeToken :: Lens.Lens' UpdateRateBasedRule Prelude.Text
updateRateBasedRule_changeToken :: Lens' UpdateRateBasedRule Text
updateRateBasedRule_changeToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRateBasedRule' {Text
changeToken :: Text
$sel:changeToken:UpdateRateBasedRule' :: UpdateRateBasedRule -> Text
changeToken} -> Text
changeToken) (\s :: UpdateRateBasedRule
s@UpdateRateBasedRule' {} Text
a -> UpdateRateBasedRule
s {$sel:changeToken:UpdateRateBasedRule' :: Text
changeToken = Text
a} :: UpdateRateBasedRule)

-- | An array of @RuleUpdate@ objects that you want to insert into or delete
-- from a RateBasedRule.
updateRateBasedRule_updates :: Lens.Lens' UpdateRateBasedRule [RuleUpdate]
updateRateBasedRule_updates :: Lens' UpdateRateBasedRule [RuleUpdate]
updateRateBasedRule_updates = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRateBasedRule' {[RuleUpdate]
updates :: [RuleUpdate]
$sel:updates:UpdateRateBasedRule' :: UpdateRateBasedRule -> [RuleUpdate]
updates} -> [RuleUpdate]
updates) (\s :: UpdateRateBasedRule
s@UpdateRateBasedRule' {} [RuleUpdate]
a -> UpdateRateBasedRule
s {$sel:updates:UpdateRateBasedRule' :: [RuleUpdate]
updates = [RuleUpdate]
a} :: UpdateRateBasedRule) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | 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.
updateRateBasedRule_rateLimit :: Lens.Lens' UpdateRateBasedRule Prelude.Natural
updateRateBasedRule_rateLimit :: Lens' UpdateRateBasedRule Natural
updateRateBasedRule_rateLimit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRateBasedRule' {Natural
rateLimit :: Natural
$sel:rateLimit:UpdateRateBasedRule' :: UpdateRateBasedRule -> Natural
rateLimit} -> Natural
rateLimit) (\s :: UpdateRateBasedRule
s@UpdateRateBasedRule' {} Natural
a -> UpdateRateBasedRule
s {$sel:rateLimit:UpdateRateBasedRule' :: Natural
rateLimit = Natural
a} :: UpdateRateBasedRule)

instance Core.AWSRequest UpdateRateBasedRule where
  type
    AWSResponse UpdateRateBasedRule =
      UpdateRateBasedRuleResponse
  request :: (Service -> Service)
-> UpdateRateBasedRule -> Request UpdateRateBasedRule
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateRateBasedRule
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateRateBasedRule)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> UpdateRateBasedRuleResponse
UpdateRateBasedRuleResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ChangeToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable UpdateRateBasedRule where
  hashWithSalt :: Int -> UpdateRateBasedRule -> Int
hashWithSalt Int
_salt UpdateRateBasedRule' {Natural
[RuleUpdate]
Text
rateLimit :: Natural
updates :: [RuleUpdate]
changeToken :: Text
ruleId :: Text
$sel:rateLimit:UpdateRateBasedRule' :: UpdateRateBasedRule -> Natural
$sel:updates:UpdateRateBasedRule' :: UpdateRateBasedRule -> [RuleUpdate]
$sel:changeToken:UpdateRateBasedRule' :: UpdateRateBasedRule -> Text
$sel:ruleId:UpdateRateBasedRule' :: UpdateRateBasedRule -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ruleId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
changeToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [RuleUpdate]
updates
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
rateLimit

instance Prelude.NFData UpdateRateBasedRule where
  rnf :: UpdateRateBasedRule -> ()
rnf UpdateRateBasedRule' {Natural
[RuleUpdate]
Text
rateLimit :: Natural
updates :: [RuleUpdate]
changeToken :: Text
ruleId :: Text
$sel:rateLimit:UpdateRateBasedRule' :: UpdateRateBasedRule -> Natural
$sel:updates:UpdateRateBasedRule' :: UpdateRateBasedRule -> [RuleUpdate]
$sel:changeToken:UpdateRateBasedRule' :: UpdateRateBasedRule -> Text
$sel:ruleId:UpdateRateBasedRule' :: UpdateRateBasedRule -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
ruleId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
changeToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [RuleUpdate]
updates
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
rateLimit

instance Data.ToHeaders UpdateRateBasedRule where
  toHeaders :: UpdateRateBasedRule -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSWAF_20150824.UpdateRateBasedRule" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateRateBasedRule where
  toJSON :: UpdateRateBasedRule -> Value
toJSON UpdateRateBasedRule' {Natural
[RuleUpdate]
Text
rateLimit :: Natural
updates :: [RuleUpdate]
changeToken :: Text
ruleId :: Text
$sel:rateLimit:UpdateRateBasedRule' :: UpdateRateBasedRule -> Natural
$sel:updates:UpdateRateBasedRule' :: UpdateRateBasedRule -> [RuleUpdate]
$sel:changeToken:UpdateRateBasedRule' :: UpdateRateBasedRule -> Text
$sel:ruleId:UpdateRateBasedRule' :: UpdateRateBasedRule -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"RuleId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
ruleId),
            forall a. a -> Maybe a
Prelude.Just (Key
"ChangeToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
changeToken),
            forall a. a -> Maybe a
Prelude.Just (Key
"Updates" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [RuleUpdate]
updates),
            forall a. a -> Maybe a
Prelude.Just (Key
"RateLimit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
rateLimit)
          ]
      )

instance Data.ToPath UpdateRateBasedRule where
  toPath :: UpdateRateBasedRule -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery UpdateRateBasedRule where
  toQuery :: UpdateRateBasedRule -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateRateBasedRuleResponse' smart constructor.
data UpdateRateBasedRuleResponse = UpdateRateBasedRuleResponse'
  { -- | The @ChangeToken@ that you used to submit the @UpdateRateBasedRule@
    -- request. You can also use this value to query the status of the request.
    -- For more information, see GetChangeTokenStatus.
    UpdateRateBasedRuleResponse -> Maybe Text
changeToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateRateBasedRuleResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateRateBasedRuleResponse -> UpdateRateBasedRuleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRateBasedRuleResponse -> UpdateRateBasedRuleResponse -> Bool
$c/= :: UpdateRateBasedRuleResponse -> UpdateRateBasedRuleResponse -> Bool
== :: UpdateRateBasedRuleResponse -> UpdateRateBasedRuleResponse -> Bool
$c== :: UpdateRateBasedRuleResponse -> UpdateRateBasedRuleResponse -> Bool
Prelude.Eq, ReadPrec [UpdateRateBasedRuleResponse]
ReadPrec UpdateRateBasedRuleResponse
Int -> ReadS UpdateRateBasedRuleResponse
ReadS [UpdateRateBasedRuleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRateBasedRuleResponse]
$creadListPrec :: ReadPrec [UpdateRateBasedRuleResponse]
readPrec :: ReadPrec UpdateRateBasedRuleResponse
$creadPrec :: ReadPrec UpdateRateBasedRuleResponse
readList :: ReadS [UpdateRateBasedRuleResponse]
$creadList :: ReadS [UpdateRateBasedRuleResponse]
readsPrec :: Int -> ReadS UpdateRateBasedRuleResponse
$creadsPrec :: Int -> ReadS UpdateRateBasedRuleResponse
Prelude.Read, Int -> UpdateRateBasedRuleResponse -> ShowS
[UpdateRateBasedRuleResponse] -> ShowS
UpdateRateBasedRuleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRateBasedRuleResponse] -> ShowS
$cshowList :: [UpdateRateBasedRuleResponse] -> ShowS
show :: UpdateRateBasedRuleResponse -> String
$cshow :: UpdateRateBasedRuleResponse -> String
showsPrec :: Int -> UpdateRateBasedRuleResponse -> ShowS
$cshowsPrec :: Int -> UpdateRateBasedRuleResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateRateBasedRuleResponse x -> UpdateRateBasedRuleResponse
forall x.
UpdateRateBasedRuleResponse -> Rep UpdateRateBasedRuleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateRateBasedRuleResponse x -> UpdateRateBasedRuleResponse
$cfrom :: forall x.
UpdateRateBasedRuleResponse -> Rep UpdateRateBasedRuleResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRateBasedRuleResponse' 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:
--
-- 'changeToken', 'updateRateBasedRuleResponse_changeToken' - The @ChangeToken@ that you used to submit the @UpdateRateBasedRule@
-- request. You can also use this value to query the status of the request.
-- For more information, see GetChangeTokenStatus.
--
-- 'httpStatus', 'updateRateBasedRuleResponse_httpStatus' - The response's http status code.
newUpdateRateBasedRuleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateRateBasedRuleResponse
newUpdateRateBasedRuleResponse :: Int -> UpdateRateBasedRuleResponse
newUpdateRateBasedRuleResponse Int
pHttpStatus_ =
  UpdateRateBasedRuleResponse'
    { $sel:changeToken:UpdateRateBasedRuleResponse' :: Maybe Text
changeToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateRateBasedRuleResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @ChangeToken@ that you used to submit the @UpdateRateBasedRule@
-- request. You can also use this value to query the status of the request.
-- For more information, see GetChangeTokenStatus.
updateRateBasedRuleResponse_changeToken :: Lens.Lens' UpdateRateBasedRuleResponse (Prelude.Maybe Prelude.Text)
updateRateBasedRuleResponse_changeToken :: Lens' UpdateRateBasedRuleResponse (Maybe Text)
updateRateBasedRuleResponse_changeToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRateBasedRuleResponse' {Maybe Text
changeToken :: Maybe Text
$sel:changeToken:UpdateRateBasedRuleResponse' :: UpdateRateBasedRuleResponse -> Maybe Text
changeToken} -> Maybe Text
changeToken) (\s :: UpdateRateBasedRuleResponse
s@UpdateRateBasedRuleResponse' {} Maybe Text
a -> UpdateRateBasedRuleResponse
s {$sel:changeToken:UpdateRateBasedRuleResponse' :: Maybe Text
changeToken = Maybe Text
a} :: UpdateRateBasedRuleResponse)

-- | The response's http status code.
updateRateBasedRuleResponse_httpStatus :: Lens.Lens' UpdateRateBasedRuleResponse Prelude.Int
updateRateBasedRuleResponse_httpStatus :: Lens' UpdateRateBasedRuleResponse Int
updateRateBasedRuleResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRateBasedRuleResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateRateBasedRuleResponse' :: UpdateRateBasedRuleResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateRateBasedRuleResponse
s@UpdateRateBasedRuleResponse' {} Int
a -> UpdateRateBasedRuleResponse
s {$sel:httpStatus:UpdateRateBasedRuleResponse' :: Int
httpStatus = Int
a} :: UpdateRateBasedRuleResponse)

instance Prelude.NFData UpdateRateBasedRuleResponse where
  rnf :: UpdateRateBasedRuleResponse -> ()
rnf UpdateRateBasedRuleResponse' {Int
Maybe Text
httpStatus :: Int
changeToken :: Maybe Text
$sel:httpStatus:UpdateRateBasedRuleResponse' :: UpdateRateBasedRuleResponse -> Int
$sel:changeToken:UpdateRateBasedRuleResponse' :: UpdateRateBasedRuleResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
changeToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus