{-# 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.NetworkFirewall.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)
--
-- Updates the rule settings for the specified rule group. You use a rule
-- group by reference in one or more firewall policies. When you modify a
-- rule group, you modify all firewall policies that use the rule group.
--
-- To update a rule group, first call DescribeRuleGroup to retrieve the
-- current RuleGroup object, update the object as needed, and then provide
-- the updated object to this call.
module Amazonka.NetworkFirewall.UpdateRuleGroup
  ( -- * Creating a Request
    UpdateRuleGroup (..),
    newUpdateRuleGroup,

    -- * Request Lenses
    updateRuleGroup_description,
    updateRuleGroup_dryRun,
    updateRuleGroup_encryptionConfiguration,
    updateRuleGroup_ruleGroup,
    updateRuleGroup_ruleGroupArn,
    updateRuleGroup_ruleGroupName,
    updateRuleGroup_rules,
    updateRuleGroup_sourceMetadata,
    updateRuleGroup_type,
    updateRuleGroup_updateToken,

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

    -- * Response Lenses
    updateRuleGroupResponse_httpStatus,
    updateRuleGroupResponse_updateToken,
    updateRuleGroupResponse_ruleGroupResponse,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.NetworkFirewall.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateRuleGroup' smart constructor.
data UpdateRuleGroup = UpdateRuleGroup'
  { -- | A description of the rule group.
    UpdateRuleGroup -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether you want Network Firewall to just check the validity
    -- of the request, rather than run the request.
    --
    -- If set to @TRUE@, Network Firewall checks whether the request can run
    -- successfully, but doesn\'t actually make the requested changes. The call
    -- returns the value that the request would return if you ran it with dry
    -- run set to @FALSE@, but doesn\'t make additions or changes to your
    -- resources. This option allows you to make sure that you have the
    -- required permissions to run the request and that your request parameters
    -- are valid.
    --
    -- If set to @FALSE@, Network Firewall makes the requested changes to your
    -- resources.
    UpdateRuleGroup -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | A complex type that contains settings for encryption of your rule group
    -- resources.
    UpdateRuleGroup -> Maybe EncryptionConfiguration
encryptionConfiguration :: Prelude.Maybe EncryptionConfiguration,
    -- | An object that defines the rule group rules.
    --
    -- You must provide either this rule group setting or a @Rules@ setting,
    -- but not both.
    UpdateRuleGroup -> Maybe RuleGroup
ruleGroup :: Prelude.Maybe RuleGroup,
    -- | The Amazon Resource Name (ARN) of the rule group.
    --
    -- You must specify the ARN or the name, and you can specify both.
    UpdateRuleGroup -> Maybe Text
ruleGroupArn :: Prelude.Maybe Prelude.Text,
    -- | The descriptive name of the rule group. You can\'t change the name of a
    -- rule group after you create it.
    --
    -- You must specify the ARN or the name, and you can specify both.
    UpdateRuleGroup -> Maybe Text
ruleGroupName :: Prelude.Maybe Prelude.Text,
    -- | A string containing stateful rule group rules specifications in Suricata
    -- flat format, with one rule per line. Use this to import your existing
    -- Suricata compatible rule groups.
    --
    -- You must provide either this rules setting or a populated @RuleGroup@
    -- setting, but not both.
    --
    -- You can provide your rule group specification in Suricata flat format
    -- through this setting when you create or update your rule group. The call
    -- response returns a RuleGroup object that Network Firewall has populated
    -- from your string.
    UpdateRuleGroup -> Maybe Text
rules :: Prelude.Maybe Prelude.Text,
    -- | A complex type that contains metadata about the rule group that your own
    -- rule group is copied from. You can use the metadata to keep track of
    -- updates made to the originating rule group.
    UpdateRuleGroup -> Maybe SourceMetadata
sourceMetadata :: Prelude.Maybe SourceMetadata,
    -- | Indicates whether the rule group is stateless or stateful. If the rule
    -- group is stateless, it contains stateless rules. If it is stateful, it
    -- contains stateful rules.
    --
    -- This setting is required for requests that do not include the
    -- @RuleGroupARN@.
    UpdateRuleGroup -> Maybe RuleGroupType
type' :: Prelude.Maybe RuleGroupType,
    -- | A token used for optimistic locking. Network Firewall returns a token to
    -- your requests that access the rule group. The token marks the state of
    -- the rule group resource at the time of the request.
    --
    -- To make changes to the rule group, you provide the token in your
    -- request. Network Firewall uses the token to ensure that the rule group
    -- hasn\'t changed since you last retrieved it. If it has changed, the
    -- operation fails with an @InvalidTokenException@. If this happens,
    -- retrieve the rule group again to get a current copy of it with a current
    -- token. Reapply your changes as needed, then try the operation again
    -- using the new token.
    UpdateRuleGroup -> Text
updateToken :: 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:
--
-- 'description', 'updateRuleGroup_description' - A description of the rule group.
--
-- 'dryRun', 'updateRuleGroup_dryRun' - Indicates whether you want Network Firewall to just check the validity
-- of the request, rather than run the request.
--
-- If set to @TRUE@, Network Firewall checks whether the request can run
-- successfully, but doesn\'t actually make the requested changes. The call
-- returns the value that the request would return if you ran it with dry
-- run set to @FALSE@, but doesn\'t make additions or changes to your
-- resources. This option allows you to make sure that you have the
-- required permissions to run the request and that your request parameters
-- are valid.
--
-- If set to @FALSE@, Network Firewall makes the requested changes to your
-- resources.
--
-- 'encryptionConfiguration', 'updateRuleGroup_encryptionConfiguration' - A complex type that contains settings for encryption of your rule group
-- resources.
--
-- 'ruleGroup', 'updateRuleGroup_ruleGroup' - An object that defines the rule group rules.
--
-- You must provide either this rule group setting or a @Rules@ setting,
-- but not both.
--
-- 'ruleGroupArn', 'updateRuleGroup_ruleGroupArn' - The Amazon Resource Name (ARN) of the rule group.
--
-- You must specify the ARN or the name, and you can specify both.
--
-- 'ruleGroupName', 'updateRuleGroup_ruleGroupName' - The descriptive name of the rule group. You can\'t change the name of a
-- rule group after you create it.
--
-- You must specify the ARN or the name, and you can specify both.
--
-- 'rules', 'updateRuleGroup_rules' - A string containing stateful rule group rules specifications in Suricata
-- flat format, with one rule per line. Use this to import your existing
-- Suricata compatible rule groups.
--
-- You must provide either this rules setting or a populated @RuleGroup@
-- setting, but not both.
--
-- You can provide your rule group specification in Suricata flat format
-- through this setting when you create or update your rule group. The call
-- response returns a RuleGroup object that Network Firewall has populated
-- from your string.
--
-- 'sourceMetadata', 'updateRuleGroup_sourceMetadata' - A complex type that contains metadata about the rule group that your own
-- rule group is copied from. You can use the metadata to keep track of
-- updates made to the originating rule group.
--
-- 'type'', 'updateRuleGroup_type' - Indicates whether the rule group is stateless or stateful. If the rule
-- group is stateless, it contains stateless rules. If it is stateful, it
-- contains stateful rules.
--
-- This setting is required for requests that do not include the
-- @RuleGroupARN@.
--
-- 'updateToken', 'updateRuleGroup_updateToken' - A token used for optimistic locking. Network Firewall returns a token to
-- your requests that access the rule group. The token marks the state of
-- the rule group resource at the time of the request.
--
-- To make changes to the rule group, you provide the token in your
-- request. Network Firewall uses the token to ensure that the rule group
-- hasn\'t changed since you last retrieved it. If it has changed, the
-- operation fails with an @InvalidTokenException@. If this happens,
-- retrieve the rule group again to get a current copy of it with a current
-- token. Reapply your changes as needed, then try the operation again
-- using the new token.
newUpdateRuleGroup ::
  -- | 'updateToken'
  Prelude.Text ->
  UpdateRuleGroup
newUpdateRuleGroup :: Text -> UpdateRuleGroup
newUpdateRuleGroup Text
pUpdateToken_ =
  UpdateRuleGroup'
    { $sel:description:UpdateRuleGroup' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:dryRun:UpdateRuleGroup' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionConfiguration:UpdateRuleGroup' :: Maybe EncryptionConfiguration
encryptionConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:ruleGroup:UpdateRuleGroup' :: Maybe RuleGroup
ruleGroup = forall a. Maybe a
Prelude.Nothing,
      $sel:ruleGroupArn:UpdateRuleGroup' :: Maybe Text
ruleGroupArn = forall a. Maybe a
Prelude.Nothing,
      $sel:ruleGroupName:UpdateRuleGroup' :: Maybe Text
ruleGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:rules:UpdateRuleGroup' :: Maybe Text
rules = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceMetadata:UpdateRuleGroup' :: Maybe SourceMetadata
sourceMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:type':UpdateRuleGroup' :: Maybe RuleGroupType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:updateToken:UpdateRuleGroup' :: Text
updateToken = Text
pUpdateToken_
    }

-- | A description of the rule group.
updateRuleGroup_description :: Lens.Lens' UpdateRuleGroup (Prelude.Maybe Prelude.Text)
updateRuleGroup_description :: Lens' UpdateRuleGroup (Maybe Text)
updateRuleGroup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Maybe Text
description :: Maybe Text
$sel:description:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Maybe Text
a -> UpdateRuleGroup
s {$sel:description:UpdateRuleGroup' :: Maybe Text
description = Maybe Text
a} :: UpdateRuleGroup)

-- | Indicates whether you want Network Firewall to just check the validity
-- of the request, rather than run the request.
--
-- If set to @TRUE@, Network Firewall checks whether the request can run
-- successfully, but doesn\'t actually make the requested changes. The call
-- returns the value that the request would return if you ran it with dry
-- run set to @FALSE@, but doesn\'t make additions or changes to your
-- resources. This option allows you to make sure that you have the
-- required permissions to run the request and that your request parameters
-- are valid.
--
-- If set to @FALSE@, Network Firewall makes the requested changes to your
-- resources.
updateRuleGroup_dryRun :: Lens.Lens' UpdateRuleGroup (Prelude.Maybe Prelude.Bool)
updateRuleGroup_dryRun :: Lens' UpdateRuleGroup (Maybe Bool)
updateRuleGroup_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Maybe Bool
a -> UpdateRuleGroup
s {$sel:dryRun:UpdateRuleGroup' :: Maybe Bool
dryRun = Maybe Bool
a} :: UpdateRuleGroup)

-- | A complex type that contains settings for encryption of your rule group
-- resources.
updateRuleGroup_encryptionConfiguration :: Lens.Lens' UpdateRuleGroup (Prelude.Maybe EncryptionConfiguration)
updateRuleGroup_encryptionConfiguration :: Lens' UpdateRuleGroup (Maybe EncryptionConfiguration)
updateRuleGroup_encryptionConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Maybe EncryptionConfiguration
encryptionConfiguration :: Maybe EncryptionConfiguration
$sel:encryptionConfiguration:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe EncryptionConfiguration
encryptionConfiguration} -> Maybe EncryptionConfiguration
encryptionConfiguration) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Maybe EncryptionConfiguration
a -> UpdateRuleGroup
s {$sel:encryptionConfiguration:UpdateRuleGroup' :: Maybe EncryptionConfiguration
encryptionConfiguration = Maybe EncryptionConfiguration
a} :: UpdateRuleGroup)

-- | An object that defines the rule group rules.
--
-- You must provide either this rule group setting or a @Rules@ setting,
-- but not both.
updateRuleGroup_ruleGroup :: Lens.Lens' UpdateRuleGroup (Prelude.Maybe RuleGroup)
updateRuleGroup_ruleGroup :: Lens' UpdateRuleGroup (Maybe RuleGroup)
updateRuleGroup_ruleGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Maybe RuleGroup
ruleGroup :: Maybe RuleGroup
$sel:ruleGroup:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe RuleGroup
ruleGroup} -> Maybe RuleGroup
ruleGroup) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Maybe RuleGroup
a -> UpdateRuleGroup
s {$sel:ruleGroup:UpdateRuleGroup' :: Maybe RuleGroup
ruleGroup = Maybe RuleGroup
a} :: UpdateRuleGroup)

-- | The Amazon Resource Name (ARN) of the rule group.
--
-- You must specify the ARN or the name, and you can specify both.
updateRuleGroup_ruleGroupArn :: Lens.Lens' UpdateRuleGroup (Prelude.Maybe Prelude.Text)
updateRuleGroup_ruleGroupArn :: Lens' UpdateRuleGroup (Maybe Text)
updateRuleGroup_ruleGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Maybe Text
ruleGroupArn :: Maybe Text
$sel:ruleGroupArn:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
ruleGroupArn} -> Maybe Text
ruleGroupArn) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Maybe Text
a -> UpdateRuleGroup
s {$sel:ruleGroupArn:UpdateRuleGroup' :: Maybe Text
ruleGroupArn = Maybe Text
a} :: UpdateRuleGroup)

-- | The descriptive name of the rule group. You can\'t change the name of a
-- rule group after you create it.
--
-- You must specify the ARN or the name, and you can specify both.
updateRuleGroup_ruleGroupName :: Lens.Lens' UpdateRuleGroup (Prelude.Maybe Prelude.Text)
updateRuleGroup_ruleGroupName :: Lens' UpdateRuleGroup (Maybe Text)
updateRuleGroup_ruleGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Maybe Text
ruleGroupName :: Maybe Text
$sel:ruleGroupName:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
ruleGroupName} -> Maybe Text
ruleGroupName) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Maybe Text
a -> UpdateRuleGroup
s {$sel:ruleGroupName:UpdateRuleGroup' :: Maybe Text
ruleGroupName = Maybe Text
a} :: UpdateRuleGroup)

-- | A string containing stateful rule group rules specifications in Suricata
-- flat format, with one rule per line. Use this to import your existing
-- Suricata compatible rule groups.
--
-- You must provide either this rules setting or a populated @RuleGroup@
-- setting, but not both.
--
-- You can provide your rule group specification in Suricata flat format
-- through this setting when you create or update your rule group. The call
-- response returns a RuleGroup object that Network Firewall has populated
-- from your string.
updateRuleGroup_rules :: Lens.Lens' UpdateRuleGroup (Prelude.Maybe Prelude.Text)
updateRuleGroup_rules :: Lens' UpdateRuleGroup (Maybe Text)
updateRuleGroup_rules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Maybe Text
rules :: Maybe Text
$sel:rules:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
rules} -> Maybe Text
rules) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Maybe Text
a -> UpdateRuleGroup
s {$sel:rules:UpdateRuleGroup' :: Maybe Text
rules = Maybe Text
a} :: UpdateRuleGroup)

-- | A complex type that contains metadata about the rule group that your own
-- rule group is copied from. You can use the metadata to keep track of
-- updates made to the originating rule group.
updateRuleGroup_sourceMetadata :: Lens.Lens' UpdateRuleGroup (Prelude.Maybe SourceMetadata)
updateRuleGroup_sourceMetadata :: Lens' UpdateRuleGroup (Maybe SourceMetadata)
updateRuleGroup_sourceMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Maybe SourceMetadata
sourceMetadata :: Maybe SourceMetadata
$sel:sourceMetadata:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe SourceMetadata
sourceMetadata} -> Maybe SourceMetadata
sourceMetadata) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Maybe SourceMetadata
a -> UpdateRuleGroup
s {$sel:sourceMetadata:UpdateRuleGroup' :: Maybe SourceMetadata
sourceMetadata = Maybe SourceMetadata
a} :: UpdateRuleGroup)

-- | Indicates whether the rule group is stateless or stateful. If the rule
-- group is stateless, it contains stateless rules. If it is stateful, it
-- contains stateful rules.
--
-- This setting is required for requests that do not include the
-- @RuleGroupARN@.
updateRuleGroup_type :: Lens.Lens' UpdateRuleGroup (Prelude.Maybe RuleGroupType)
updateRuleGroup_type :: Lens' UpdateRuleGroup (Maybe RuleGroupType)
updateRuleGroup_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Maybe RuleGroupType
type' :: Maybe RuleGroupType
$sel:type':UpdateRuleGroup' :: UpdateRuleGroup -> Maybe RuleGroupType
type'} -> Maybe RuleGroupType
type') (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Maybe RuleGroupType
a -> UpdateRuleGroup
s {$sel:type':UpdateRuleGroup' :: Maybe RuleGroupType
type' = Maybe RuleGroupType
a} :: UpdateRuleGroup)

-- | A token used for optimistic locking. Network Firewall returns a token to
-- your requests that access the rule group. The token marks the state of
-- the rule group resource at the time of the request.
--
-- To make changes to the rule group, you provide the token in your
-- request. Network Firewall uses the token to ensure that the rule group
-- hasn\'t changed since you last retrieved it. If it has changed, the
-- operation fails with an @InvalidTokenException@. If this happens,
-- retrieve the rule group again to get a current copy of it with a current
-- token. Reapply your changes as needed, then try the operation again
-- using the new token.
updateRuleGroup_updateToken :: Lens.Lens' UpdateRuleGroup Prelude.Text
updateRuleGroup_updateToken :: Lens' UpdateRuleGroup Text
updateRuleGroup_updateToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroup' {Text
updateToken :: Text
$sel:updateToken:UpdateRuleGroup' :: UpdateRuleGroup -> Text
updateToken} -> Text
updateToken) (\s :: UpdateRuleGroup
s@UpdateRuleGroup' {} Text
a -> UpdateRuleGroup
s {$sel:updateToken:UpdateRuleGroup' :: Text
updateToken = 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 ->
          Int -> Text -> RuleGroupResponse -> UpdateRuleGroupResponse
UpdateRuleGroupResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"UpdateToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"RuleGroupResponse")
      )

instance Prelude.Hashable UpdateRuleGroup where
  hashWithSalt :: Int -> UpdateRuleGroup -> Int
hashWithSalt Int
_salt UpdateRuleGroup' {Maybe Bool
Maybe Text
Maybe EncryptionConfiguration
Maybe RuleGroupType
Maybe SourceMetadata
Maybe RuleGroup
Text
updateToken :: Text
type' :: Maybe RuleGroupType
sourceMetadata :: Maybe SourceMetadata
rules :: Maybe Text
ruleGroupName :: Maybe Text
ruleGroupArn :: Maybe Text
ruleGroup :: Maybe RuleGroup
encryptionConfiguration :: Maybe EncryptionConfiguration
dryRun :: Maybe Bool
description :: Maybe Text
$sel:updateToken:UpdateRuleGroup' :: UpdateRuleGroup -> Text
$sel:type':UpdateRuleGroup' :: UpdateRuleGroup -> Maybe RuleGroupType
$sel:sourceMetadata:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe SourceMetadata
$sel:rules:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
$sel:ruleGroupName:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
$sel:ruleGroupArn:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
$sel:ruleGroup:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe RuleGroup
$sel:encryptionConfiguration:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe EncryptionConfiguration
$sel:dryRun:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Bool
$sel:description:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EncryptionConfiguration
encryptionConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RuleGroup
ruleGroup
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ruleGroupArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ruleGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
rules
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SourceMetadata
sourceMetadata
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RuleGroupType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
updateToken

instance Prelude.NFData UpdateRuleGroup where
  rnf :: UpdateRuleGroup -> ()
rnf UpdateRuleGroup' {Maybe Bool
Maybe Text
Maybe EncryptionConfiguration
Maybe RuleGroupType
Maybe SourceMetadata
Maybe RuleGroup
Text
updateToken :: Text
type' :: Maybe RuleGroupType
sourceMetadata :: Maybe SourceMetadata
rules :: Maybe Text
ruleGroupName :: Maybe Text
ruleGroupArn :: Maybe Text
ruleGroup :: Maybe RuleGroup
encryptionConfiguration :: Maybe EncryptionConfiguration
dryRun :: Maybe Bool
description :: Maybe Text
$sel:updateToken:UpdateRuleGroup' :: UpdateRuleGroup -> Text
$sel:type':UpdateRuleGroup' :: UpdateRuleGroup -> Maybe RuleGroupType
$sel:sourceMetadata:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe SourceMetadata
$sel:rules:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
$sel:ruleGroupName:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
$sel:ruleGroupArn:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
$sel:ruleGroup:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe RuleGroup
$sel:encryptionConfiguration:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe EncryptionConfiguration
$sel:dryRun:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Bool
$sel:description:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionConfiguration
encryptionConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RuleGroup
ruleGroup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ruleGroupArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ruleGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
rules
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SourceMetadata
sourceMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RuleGroupType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
updateToken

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
"NetworkFirewall_20201112.UpdateRuleGroup" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateRuleGroup where
  toJSON :: UpdateRuleGroup -> Value
toJSON UpdateRuleGroup' {Maybe Bool
Maybe Text
Maybe EncryptionConfiguration
Maybe RuleGroupType
Maybe SourceMetadata
Maybe RuleGroup
Text
updateToken :: Text
type' :: Maybe RuleGroupType
sourceMetadata :: Maybe SourceMetadata
rules :: Maybe Text
ruleGroupName :: Maybe Text
ruleGroupArn :: Maybe Text
ruleGroup :: Maybe RuleGroup
encryptionConfiguration :: Maybe EncryptionConfiguration
dryRun :: Maybe Bool
description :: Maybe Text
$sel:updateToken:UpdateRuleGroup' :: UpdateRuleGroup -> Text
$sel:type':UpdateRuleGroup' :: UpdateRuleGroup -> Maybe RuleGroupType
$sel:sourceMetadata:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe SourceMetadata
$sel:rules:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
$sel:ruleGroupName:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
$sel:ruleGroupArn:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
$sel:ruleGroup:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe RuleGroup
$sel:encryptionConfiguration:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe EncryptionConfiguration
$sel:dryRun:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Bool
$sel:description:UpdateRuleGroup' :: UpdateRuleGroup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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 Text
description,
            (Key
"DryRun" 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 Bool
dryRun,
            (Key
"EncryptionConfiguration" 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 EncryptionConfiguration
encryptionConfiguration,
            (Key
"RuleGroup" 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 RuleGroup
ruleGroup,
            (Key
"RuleGroupArn" 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 Text
ruleGroupArn,
            (Key
"RuleGroupName" 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 Text
ruleGroupName,
            (Key
"Rules" 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 Text
rules,
            (Key
"SourceMetadata" 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 SourceMetadata
sourceMetadata,
            (Key
"Type" 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 RuleGroupType
type',
            forall a. a -> Maybe a
Prelude.Just (Key
"UpdateToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
updateToken)
          ]
      )

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 response's http status code.
    UpdateRuleGroupResponse -> Int
httpStatus :: Prelude.Int,
    -- | A token used for optimistic locking. Network Firewall returns a token to
    -- your requests that access the rule group. The token marks the state of
    -- the rule group resource at the time of the request.
    --
    -- To make changes to the rule group, you provide the token in your
    -- request. Network Firewall uses the token to ensure that the rule group
    -- hasn\'t changed since you last retrieved it. If it has changed, the
    -- operation fails with an @InvalidTokenException@. If this happens,
    -- retrieve the rule group again to get a current copy of it with a current
    -- token. Reapply your changes as needed, then try the operation again
    -- using the new token.
    UpdateRuleGroupResponse -> Text
updateToken :: Prelude.Text,
    -- | The high-level properties of a rule group. This, along with the
    -- RuleGroup, define the rule group. You can retrieve all objects for a
    -- rule group by calling DescribeRuleGroup.
    UpdateRuleGroupResponse -> RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
  }
  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:
--
-- 'httpStatus', 'updateRuleGroupResponse_httpStatus' - The response's http status code.
--
-- 'updateToken', 'updateRuleGroupResponse_updateToken' - A token used for optimistic locking. Network Firewall returns a token to
-- your requests that access the rule group. The token marks the state of
-- the rule group resource at the time of the request.
--
-- To make changes to the rule group, you provide the token in your
-- request. Network Firewall uses the token to ensure that the rule group
-- hasn\'t changed since you last retrieved it. If it has changed, the
-- operation fails with an @InvalidTokenException@. If this happens,
-- retrieve the rule group again to get a current copy of it with a current
-- token. Reapply your changes as needed, then try the operation again
-- using the new token.
--
-- 'ruleGroupResponse', 'updateRuleGroupResponse_ruleGroupResponse' - The high-level properties of a rule group. This, along with the
-- RuleGroup, define the rule group. You can retrieve all objects for a
-- rule group by calling DescribeRuleGroup.
newUpdateRuleGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'updateToken'
  Prelude.Text ->
  -- | 'ruleGroupResponse'
  RuleGroupResponse ->
  UpdateRuleGroupResponse
newUpdateRuleGroupResponse :: Int -> Text -> RuleGroupResponse -> UpdateRuleGroupResponse
newUpdateRuleGroupResponse
  Int
pHttpStatus_
  Text
pUpdateToken_
  RuleGroupResponse
pRuleGroupResponse_ =
    UpdateRuleGroupResponse'
      { $sel:httpStatus:UpdateRuleGroupResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:updateToken:UpdateRuleGroupResponse' :: Text
updateToken = Text
pUpdateToken_,
        $sel:ruleGroupResponse:UpdateRuleGroupResponse' :: RuleGroupResponse
ruleGroupResponse = RuleGroupResponse
pRuleGroupResponse_
      }

-- | 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)

-- | A token used for optimistic locking. Network Firewall returns a token to
-- your requests that access the rule group. The token marks the state of
-- the rule group resource at the time of the request.
--
-- To make changes to the rule group, you provide the token in your
-- request. Network Firewall uses the token to ensure that the rule group
-- hasn\'t changed since you last retrieved it. If it has changed, the
-- operation fails with an @InvalidTokenException@. If this happens,
-- retrieve the rule group again to get a current copy of it with a current
-- token. Reapply your changes as needed, then try the operation again
-- using the new token.
updateRuleGroupResponse_updateToken :: Lens.Lens' UpdateRuleGroupResponse Prelude.Text
updateRuleGroupResponse_updateToken :: Lens' UpdateRuleGroupResponse Text
updateRuleGroupResponse_updateToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroupResponse' {Text
updateToken :: Text
$sel:updateToken:UpdateRuleGroupResponse' :: UpdateRuleGroupResponse -> Text
updateToken} -> Text
updateToken) (\s :: UpdateRuleGroupResponse
s@UpdateRuleGroupResponse' {} Text
a -> UpdateRuleGroupResponse
s {$sel:updateToken:UpdateRuleGroupResponse' :: Text
updateToken = Text
a} :: UpdateRuleGroupResponse)

-- | The high-level properties of a rule group. This, along with the
-- RuleGroup, define the rule group. You can retrieve all objects for a
-- rule group by calling DescribeRuleGroup.
updateRuleGroupResponse_ruleGroupResponse :: Lens.Lens' UpdateRuleGroupResponse RuleGroupResponse
updateRuleGroupResponse_ruleGroupResponse :: Lens' UpdateRuleGroupResponse RuleGroupResponse
updateRuleGroupResponse_ruleGroupResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRuleGroupResponse' {RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
$sel:ruleGroupResponse:UpdateRuleGroupResponse' :: UpdateRuleGroupResponse -> RuleGroupResponse
ruleGroupResponse} -> RuleGroupResponse
ruleGroupResponse) (\s :: UpdateRuleGroupResponse
s@UpdateRuleGroupResponse' {} RuleGroupResponse
a -> UpdateRuleGroupResponse
s {$sel:ruleGroupResponse:UpdateRuleGroupResponse' :: RuleGroupResponse
ruleGroupResponse = RuleGroupResponse
a} :: UpdateRuleGroupResponse)

instance Prelude.NFData UpdateRuleGroupResponse where
  rnf :: UpdateRuleGroupResponse -> ()
rnf UpdateRuleGroupResponse' {Int
Text
RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
updateToken :: Text
httpStatus :: Int
$sel:ruleGroupResponse:UpdateRuleGroupResponse' :: UpdateRuleGroupResponse -> RuleGroupResponse
$sel:updateToken:UpdateRuleGroupResponse' :: UpdateRuleGroupResponse -> Text
$sel:httpStatus:UpdateRuleGroupResponse' :: UpdateRuleGroupResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
updateToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RuleGroupResponse
ruleGroupResponse