{-# 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.WAFRegional.UpdateRuleGroup
-- 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 ActivatedRule objects in a @RuleGroup@.
--
-- You can only insert @REGULAR@ rules into a rule group.
--
-- You can have a maximum of ten rules per rule group.
--
-- To create and configure a @RuleGroup@, perform the following steps:
--
-- 1.  Create and update the @Rules@ that you want to include in the
--     @RuleGroup@. See CreateRule.
--
-- 2.  Use @GetChangeToken@ to get the change token that you provide in the
--     @ChangeToken@ parameter of an UpdateRuleGroup request.
--
-- 3.  Submit an @UpdateRuleGroup@ request to add @Rules@ to the
--     @RuleGroup@.
--
-- 4.  Create and update a @WebACL@ that contains the @RuleGroup@. See
--     CreateWebACL.
--
-- If you want to replace one @Rule@ with another, you delete the existing
-- one and add the new one.
--
-- For more information about how to use the AWS WAF API to allow or block
-- HTTP requests, see the
-- <https://docs.aws.amazon.com/waf/latest/developerguide/ AWS WAF Developer Guide>.
module Amazonka.WAFRegional.UpdateRuleGroup
  ( -- * Creating a Request
    UpdateRuleGroup (..),
    newUpdateRuleGroup,

    -- * Request Lenses
    updateRuleGroup_ruleGroupId,
    updateRuleGroup_updates,
    updateRuleGroup_changeToken,

    -- * Destructuring the Response
    UpdateRuleGroupResponse (..),
    newUpdateRuleGroupResponse,

    -- * Response Lenses
    updateRuleGroupResponse_changeToken,
    updateRuleGroupResponse_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.WAFRegional.Types

-- | /See:/ 'newUpdateRuleGroup' smart constructor.
data UpdateRuleGroup = UpdateRuleGroup'
  { -- | The @RuleGroupId@ of the RuleGroup that you want to update.
    -- @RuleGroupId@ is returned by CreateRuleGroup and by ListRuleGroups.
    UpdateRuleGroup -> Text
ruleGroupId :: Prelude.Text,
    -- | An array of @RuleGroupUpdate@ objects that you want to insert into or
    -- delete from a RuleGroup.
    --
    -- You can only insert @REGULAR@ rules into a rule group.
    --
    -- @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@.
    UpdateRuleGroup -> NonEmpty RuleGroupUpdate
updates :: Prelude.NonEmpty RuleGroupUpdate,
    -- | The value returned by the most recent call to GetChangeToken.
    UpdateRuleGroup -> Text
changeToken :: Prelude.Text
  }
  deriving (UpdateRuleGroup -> UpdateRuleGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRuleGroup -> UpdateRuleGroup -> Bool
$c/= :: UpdateRuleGroup -> UpdateRuleGroup -> Bool
== :: UpdateRuleGroup -> UpdateRuleGroup -> Bool
$c== :: UpdateRuleGroup -> UpdateRuleGroup -> Bool
Prelude.Eq, ReadPrec [UpdateRuleGroup]
ReadPrec UpdateRuleGroup
Int -> ReadS UpdateRuleGroup
ReadS [UpdateRuleGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRuleGroup]
$creadListPrec :: ReadPrec [UpdateRuleGroup]
readPrec :: ReadPrec UpdateRuleGroup
$creadPrec :: ReadPrec UpdateRuleGroup
readList :: ReadS [UpdateRuleGroup]
$creadList :: ReadS [UpdateRuleGroup]
readsPrec :: Int -> ReadS UpdateRuleGroup
$creadsPrec :: Int -> ReadS UpdateRuleGroup
Prelude.Read, Int -> UpdateRuleGroup -> ShowS
[UpdateRuleGroup] -> ShowS
UpdateRuleGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRuleGroup] -> ShowS
$cshowList :: [UpdateRuleGroup] -> ShowS
show :: UpdateRuleGroup -> String
$cshow :: UpdateRuleGroup -> String
showsPrec :: Int -> UpdateRuleGroup -> ShowS
$cshowsPrec :: Int -> UpdateRuleGroup -> ShowS
Prelude.Show, forall x. Rep UpdateRuleGroup x -> UpdateRuleGroup
forall x. UpdateRuleGroup -> Rep UpdateRuleGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRuleGroup x -> UpdateRuleGroup
$cfrom :: forall x. UpdateRuleGroup -> Rep UpdateRuleGroup x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRuleGroup' 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:
--
-- 'ruleGroupId', 'updateRuleGroup_ruleGroupId' - The @RuleGroupId@ of the RuleGroup that you want to update.
-- @RuleGroupId@ is returned by CreateRuleGroup and by ListRuleGroups.
--
-- 'updates', 'updateRuleGroup_updates' - An array of @RuleGroupUpdate@ objects that you want to insert into or
-- delete from a RuleGroup.
--
-- You can only insert @REGULAR@ rules into a rule group.
--
-- @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@.
--
-- 'changeToken', 'updateRuleGroup_changeToken' - The value returned by the most recent call to GetChangeToken.
newUpdateRuleGroup ::
  -- | 'ruleGroupId'
  Prelude.Text ->
  -- | 'updates'
  Prelude.NonEmpty RuleGroupUpdate ->
  -- | 'changeToken'
  Prelude.Text ->
  UpdateRuleGroup
newUpdateRuleGroup :: Text -> NonEmpty RuleGroupUpdate -> Text -> UpdateRuleGroup
newUpdateRuleGroup
  Text
pRuleGroupId_
  NonEmpty RuleGroupUpdate
pUpdates_
  Text
pChangeToken_ =
    UpdateRuleGroup'
      { $sel:ruleGroupId:UpdateRuleGroup' :: Text
ruleGroupId = Text
pRuleGroupId_,
        $sel:updates:UpdateRuleGroup' :: NonEmpty RuleGroupUpdate
updates = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty RuleGroupUpdate
pUpdates_,
        $sel:changeToken:UpdateRuleGroup' :: Text
changeToken = Text
pChangeToken_
      }

-- | The @RuleGroupId@ of the RuleGroup that you want to update.
-- @RuleGroupId@ is returned by CreateRuleGroup and by ListRuleGroups.
updateRuleGroup_ruleGroupId :: Lens.Lens' UpdateRuleGroup Prelude.Text
updateRuleGroup_ruleGroupId :: Lens' UpdateRuleGroup Text
updateRuleGroup_ruleGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Text
ruleGroupId :: Text
$sel:ruleGroupId:UpdateRuleGroup' :: UpdateRuleGroup -> Text
ruleGroupId} -> Text
ruleGroupId) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Text
a -> UpdateRuleGroup
s {$sel:ruleGroupId:UpdateRuleGroup' :: Text
ruleGroupId = Text
a} :: UpdateRuleGroup)

-- | An array of @RuleGroupUpdate@ objects that you want to insert into or
-- delete from a RuleGroup.
--
-- You can only insert @REGULAR@ rules into a rule group.
--
-- @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@.
updateRuleGroup_updates :: Lens.Lens' UpdateRuleGroup (Prelude.NonEmpty RuleGroupUpdate)
updateRuleGroup_updates :: Lens' UpdateRuleGroup (NonEmpty RuleGroupUpdate)
updateRuleGroup_updates = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {NonEmpty RuleGroupUpdate
updates :: NonEmpty RuleGroupUpdate
$sel:updates:UpdateRuleGroup' :: UpdateRuleGroup -> NonEmpty RuleGroupUpdate
updates} -> NonEmpty RuleGroupUpdate
updates) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} NonEmpty RuleGroupUpdate
a -> UpdateRuleGroup
s {$sel:updates:UpdateRuleGroup' :: NonEmpty RuleGroupUpdate
updates = NonEmpty RuleGroupUpdate
a} :: UpdateRuleGroup) 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 value returned by the most recent call to GetChangeToken.
updateRuleGroup_changeToken :: Lens.Lens' UpdateRuleGroup Prelude.Text
updateRuleGroup_changeToken :: Lens' UpdateRuleGroup Text
updateRuleGroup_changeToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Text
changeToken :: Text
$sel:changeToken:UpdateRuleGroup' :: UpdateRuleGroup -> Text
changeToken} -> Text
changeToken) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Text
a -> UpdateRuleGroup
s {$sel:changeToken:UpdateRuleGroup' :: Text
changeToken = Text
a} :: UpdateRuleGroup)

instance Core.AWSRequest UpdateRuleGroup where
  type
    AWSResponse UpdateRuleGroup =
      UpdateRuleGroupResponse
  request :: (Service -> Service) -> UpdateRuleGroup -> Request UpdateRuleGroup
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 UpdateRuleGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateRuleGroup)))
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 -> UpdateRuleGroupResponse
UpdateRuleGroupResponse'
            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 UpdateRuleGroup where
  hashWithSalt :: Int -> UpdateRuleGroup -> Int
hashWithSalt Int
_salt UpdateRuleGroup' {NonEmpty RuleGroupUpdate
Text
changeToken :: Text
updates :: NonEmpty RuleGroupUpdate
ruleGroupId :: Text
$sel:changeToken:UpdateRuleGroup' :: UpdateRuleGroup -> Text
$sel:updates:UpdateRuleGroup' :: UpdateRuleGroup -> NonEmpty RuleGroupUpdate
$sel:ruleGroupId:UpdateRuleGroup' :: UpdateRuleGroup -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ruleGroupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty RuleGroupUpdate
updates
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
changeToken

instance Prelude.NFData UpdateRuleGroup where
  rnf :: UpdateRuleGroup -> ()
rnf UpdateRuleGroup' {NonEmpty RuleGroupUpdate
Text
changeToken :: Text
updates :: NonEmpty RuleGroupUpdate
ruleGroupId :: Text
$sel:changeToken:UpdateRuleGroup' :: UpdateRuleGroup -> Text
$sel:updates:UpdateRuleGroup' :: UpdateRuleGroup -> NonEmpty RuleGroupUpdate
$sel:ruleGroupId:UpdateRuleGroup' :: UpdateRuleGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
ruleGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty RuleGroupUpdate
updates
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
changeToken

instance Data.ToHeaders UpdateRuleGroup where
  toHeaders :: UpdateRuleGroup -> 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_Regional_20161128.UpdateRuleGroup" ::
                          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 UpdateRuleGroup where
  toJSON :: UpdateRuleGroup -> Value
toJSON UpdateRuleGroup' {NonEmpty RuleGroupUpdate
Text
changeToken :: Text
updates :: NonEmpty RuleGroupUpdate
ruleGroupId :: Text
$sel:changeToken:UpdateRuleGroup' :: UpdateRuleGroup -> Text
$sel:updates:UpdateRuleGroup' :: UpdateRuleGroup -> NonEmpty RuleGroupUpdate
$sel:ruleGroupId:UpdateRuleGroup' :: UpdateRuleGroup -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"RuleGroupId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
ruleGroupId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Updates" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty RuleGroupUpdate
updates),
            forall a. a -> Maybe a
Prelude.Just (Key
"ChangeToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
changeToken)
          ]
      )

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

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

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

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

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

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

instance Prelude.NFData UpdateRuleGroupResponse where
  rnf :: UpdateRuleGroupResponse -> ()
rnf UpdateRuleGroupResponse' {Int
Maybe Text
httpStatus :: Int
changeToken :: Maybe Text
$sel:httpStatus:UpdateRuleGroupResponse' :: UpdateRuleGroupResponse -> Int
$sel:changeToken:UpdateRuleGroupResponse' :: UpdateRuleGroupResponse -> 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