{-# 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.CreateRuleGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates the specified stateless or stateful rule group, which includes
-- the rules for network traffic inspection, a capacity setting, and tags.
--
-- You provide your rule group specification in your request using either
-- @RuleGroup@ or @Rules@.
module Amazonka.NetworkFirewall.CreateRuleGroup
  ( -- * Creating a Request
    CreateRuleGroup (..),
    newCreateRuleGroup,

    -- * Request Lenses
    createRuleGroup_description,
    createRuleGroup_dryRun,
    createRuleGroup_encryptionConfiguration,
    createRuleGroup_ruleGroup,
    createRuleGroup_rules,
    createRuleGroup_sourceMetadata,
    createRuleGroup_tags,
    createRuleGroup_ruleGroupName,
    createRuleGroup_type,
    createRuleGroup_capacity,

    -- * Destructuring the Response
    CreateRuleGroupResponse (..),
    newCreateRuleGroupResponse,

    -- * Response Lenses
    createRuleGroupResponse_httpStatus,
    createRuleGroupResponse_updateToken,
    createRuleGroupResponse_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:/ 'newCreateRuleGroup' smart constructor.
data CreateRuleGroup = CreateRuleGroup'
  { -- | A description of the rule group.
    CreateRuleGroup -> 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.
    CreateRuleGroup -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | A complex type that contains settings for encryption of your rule group
    -- resources.
    CreateRuleGroup -> 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.
    CreateRuleGroup -> Maybe RuleGroup
ruleGroup :: Prelude.Maybe RuleGroup,
    -- | 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.
    CreateRuleGroup -> 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.
    CreateRuleGroup -> Maybe SourceMetadata
sourceMetadata :: Prelude.Maybe SourceMetadata,
    -- | The key:value pairs to associate with the resource.
    CreateRuleGroup -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | The descriptive name of the rule group. You can\'t change the name of a
    -- rule group after you create it.
    CreateRuleGroup -> Text
ruleGroupName :: Prelude.Text,
    -- | 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.
    CreateRuleGroup -> RuleGroupType
type' :: RuleGroupType,
    -- | The maximum operating resources that this rule group can use. Rule group
    -- capacity is fixed at creation. When you update a rule group, you are
    -- limited to this capacity. When you reference a rule group from a
    -- firewall policy, Network Firewall reserves this capacity for the rule
    -- group.
    --
    -- You can retrieve the capacity that would be required for a rule group
    -- before you create the rule group by calling CreateRuleGroup with
    -- @DryRun@ set to @TRUE@.
    --
    -- You can\'t change or exceed this capacity when you update the rule
    -- group, so leave room for your rule group to grow.
    --
    -- __Capacity for a stateless rule group__
    --
    -- For a stateless rule group, the capacity required is the sum of the
    -- capacity requirements of the individual rules that you expect to have in
    -- the rule group.
    --
    -- To calculate the capacity requirement of a single rule, multiply the
    -- capacity requirement values of each of the rule\'s match settings:
    --
    -- -   A match setting with no criteria specified has a value of 1.
    --
    -- -   A match setting with @Any@ specified has a value of 1.
    --
    -- -   All other match settings have a value equal to the number of
    --     elements provided in the setting. For example, a protocol setting
    --     [\"UDP\"] and a source setting [\"10.0.0.0\/24\"] each have a value
    --     of 1. A protocol setting [\"UDP\",\"TCP\"] has a value of 2. A
    --     source setting [\"10.0.0.0\/24\",\"10.0.0.1\/24\",\"10.0.0.2\/24\"]
    --     has a value of 3.
    --
    -- A rule with no criteria specified in any of its match settings has a
    -- capacity requirement of 1. A rule with protocol setting
    -- [\"UDP\",\"TCP\"], source setting
    -- [\"10.0.0.0\/24\",\"10.0.0.1\/24\",\"10.0.0.2\/24\"], and a single
    -- specification or no specification for each of the other match settings
    -- has a capacity requirement of 6.
    --
    -- __Capacity for a stateful rule group__
    --
    -- For a stateful rule group, the minimum capacity required is the number
    -- of individual rules that you expect to have in the rule group.
    CreateRuleGroup -> Int
capacity :: Prelude.Int
  }
  deriving (CreateRuleGroup -> CreateRuleGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRuleGroup -> CreateRuleGroup -> Bool
$c/= :: CreateRuleGroup -> CreateRuleGroup -> Bool
== :: CreateRuleGroup -> CreateRuleGroup -> Bool
$c== :: CreateRuleGroup -> CreateRuleGroup -> Bool
Prelude.Eq, ReadPrec [CreateRuleGroup]
ReadPrec CreateRuleGroup
Int -> ReadS CreateRuleGroup
ReadS [CreateRuleGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRuleGroup]
$creadListPrec :: ReadPrec [CreateRuleGroup]
readPrec :: ReadPrec CreateRuleGroup
$creadPrec :: ReadPrec CreateRuleGroup
readList :: ReadS [CreateRuleGroup]
$creadList :: ReadS [CreateRuleGroup]
readsPrec :: Int -> ReadS CreateRuleGroup
$creadsPrec :: Int -> ReadS CreateRuleGroup
Prelude.Read, Int -> CreateRuleGroup -> ShowS
[CreateRuleGroup] -> ShowS
CreateRuleGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRuleGroup] -> ShowS
$cshowList :: [CreateRuleGroup] -> ShowS
show :: CreateRuleGroup -> String
$cshow :: CreateRuleGroup -> String
showsPrec :: Int -> CreateRuleGroup -> ShowS
$cshowsPrec :: Int -> CreateRuleGroup -> ShowS
Prelude.Show, forall x. Rep CreateRuleGroup x -> CreateRuleGroup
forall x. CreateRuleGroup -> Rep CreateRuleGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateRuleGroup x -> CreateRuleGroup
$cfrom :: forall x. CreateRuleGroup -> Rep CreateRuleGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateRuleGroup' 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', 'createRuleGroup_description' - A description of the rule group.
--
-- 'dryRun', 'createRuleGroup_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', 'createRuleGroup_encryptionConfiguration' - A complex type that contains settings for encryption of your rule group
-- resources.
--
-- 'ruleGroup', 'createRuleGroup_ruleGroup' - An object that defines the rule group rules.
--
-- You must provide either this rule group setting or a @Rules@ setting,
-- but not both.
--
-- 'rules', 'createRuleGroup_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', 'createRuleGroup_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.
--
-- 'tags', 'createRuleGroup_tags' - The key:value pairs to associate with the resource.
--
-- 'ruleGroupName', 'createRuleGroup_ruleGroupName' - The descriptive name of the rule group. You can\'t change the name of a
-- rule group after you create it.
--
-- 'type'', 'createRuleGroup_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.
--
-- 'capacity', 'createRuleGroup_capacity' - The maximum operating resources that this rule group can use. Rule group
-- capacity is fixed at creation. When you update a rule group, you are
-- limited to this capacity. When you reference a rule group from a
-- firewall policy, Network Firewall reserves this capacity for the rule
-- group.
--
-- You can retrieve the capacity that would be required for a rule group
-- before you create the rule group by calling CreateRuleGroup with
-- @DryRun@ set to @TRUE@.
--
-- You can\'t change or exceed this capacity when you update the rule
-- group, so leave room for your rule group to grow.
--
-- __Capacity for a stateless rule group__
--
-- For a stateless rule group, the capacity required is the sum of the
-- capacity requirements of the individual rules that you expect to have in
-- the rule group.
--
-- To calculate the capacity requirement of a single rule, multiply the
-- capacity requirement values of each of the rule\'s match settings:
--
-- -   A match setting with no criteria specified has a value of 1.
--
-- -   A match setting with @Any@ specified has a value of 1.
--
-- -   All other match settings have a value equal to the number of
--     elements provided in the setting. For example, a protocol setting
--     [\"UDP\"] and a source setting [\"10.0.0.0\/24\"] each have a value
--     of 1. A protocol setting [\"UDP\",\"TCP\"] has a value of 2. A
--     source setting [\"10.0.0.0\/24\",\"10.0.0.1\/24\",\"10.0.0.2\/24\"]
--     has a value of 3.
--
-- A rule with no criteria specified in any of its match settings has a
-- capacity requirement of 1. A rule with protocol setting
-- [\"UDP\",\"TCP\"], source setting
-- [\"10.0.0.0\/24\",\"10.0.0.1\/24\",\"10.0.0.2\/24\"], and a single
-- specification or no specification for each of the other match settings
-- has a capacity requirement of 6.
--
-- __Capacity for a stateful rule group__
--
-- For a stateful rule group, the minimum capacity required is the number
-- of individual rules that you expect to have in the rule group.
newCreateRuleGroup ::
  -- | 'ruleGroupName'
  Prelude.Text ->
  -- | 'type''
  RuleGroupType ->
  -- | 'capacity'
  Prelude.Int ->
  CreateRuleGroup
newCreateRuleGroup :: Text -> RuleGroupType -> Int -> CreateRuleGroup
newCreateRuleGroup Text
pRuleGroupName_ RuleGroupType
pType_ Int
pCapacity_ =
  CreateRuleGroup'
    { $sel:description:CreateRuleGroup' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:dryRun:CreateRuleGroup' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionConfiguration:CreateRuleGroup' :: Maybe EncryptionConfiguration
encryptionConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:ruleGroup:CreateRuleGroup' :: Maybe RuleGroup
ruleGroup = forall a. Maybe a
Prelude.Nothing,
      $sel:rules:CreateRuleGroup' :: Maybe Text
rules = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceMetadata:CreateRuleGroup' :: Maybe SourceMetadata
sourceMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateRuleGroup' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:ruleGroupName:CreateRuleGroup' :: Text
ruleGroupName = Text
pRuleGroupName_,
      $sel:type':CreateRuleGroup' :: RuleGroupType
type' = RuleGroupType
pType_,
      $sel:capacity:CreateRuleGroup' :: Int
capacity = Int
pCapacity_
    }

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

-- | 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.
createRuleGroup_dryRun :: Lens.Lens' CreateRuleGroup (Prelude.Maybe Prelude.Bool)
createRuleGroup_dryRun :: Lens' CreateRuleGroup (Maybe Bool)
createRuleGroup_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroup' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:CreateRuleGroup' :: CreateRuleGroup -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: CreateRuleGroup
s@CreateRuleGroup' {} Maybe Bool
a -> CreateRuleGroup
s {$sel:dryRun:CreateRuleGroup' :: Maybe Bool
dryRun = Maybe Bool
a} :: CreateRuleGroup)

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

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

-- | 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.
createRuleGroup_rules :: Lens.Lens' CreateRuleGroup (Prelude.Maybe Prelude.Text)
createRuleGroup_rules :: Lens' CreateRuleGroup (Maybe Text)
createRuleGroup_rules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroup' {Maybe Text
rules :: Maybe Text
$sel:rules:CreateRuleGroup' :: CreateRuleGroup -> Maybe Text
rules} -> Maybe Text
rules) (\s :: CreateRuleGroup
s@CreateRuleGroup' {} Maybe Text
a -> CreateRuleGroup
s {$sel:rules:CreateRuleGroup' :: Maybe Text
rules = Maybe Text
a} :: CreateRuleGroup)

-- | 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.
createRuleGroup_sourceMetadata :: Lens.Lens' CreateRuleGroup (Prelude.Maybe SourceMetadata)
createRuleGroup_sourceMetadata :: Lens' CreateRuleGroup (Maybe SourceMetadata)
createRuleGroup_sourceMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroup' {Maybe SourceMetadata
sourceMetadata :: Maybe SourceMetadata
$sel:sourceMetadata:CreateRuleGroup' :: CreateRuleGroup -> Maybe SourceMetadata
sourceMetadata} -> Maybe SourceMetadata
sourceMetadata) (\s :: CreateRuleGroup
s@CreateRuleGroup' {} Maybe SourceMetadata
a -> CreateRuleGroup
s {$sel:sourceMetadata:CreateRuleGroup' :: Maybe SourceMetadata
sourceMetadata = Maybe SourceMetadata
a} :: CreateRuleGroup)

-- | The key:value pairs to associate with the resource.
createRuleGroup_tags :: Lens.Lens' CreateRuleGroup (Prelude.Maybe (Prelude.NonEmpty Tag))
createRuleGroup_tags :: Lens' CreateRuleGroup (Maybe (NonEmpty Tag))
createRuleGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroup' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:CreateRuleGroup' :: CreateRuleGroup -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: CreateRuleGroup
s@CreateRuleGroup' {} Maybe (NonEmpty Tag)
a -> CreateRuleGroup
s {$sel:tags:CreateRuleGroup' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
a} :: CreateRuleGroup) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The descriptive name of the rule group. You can\'t change the name of a
-- rule group after you create it.
createRuleGroup_ruleGroupName :: Lens.Lens' CreateRuleGroup Prelude.Text
createRuleGroup_ruleGroupName :: Lens' CreateRuleGroup Text
createRuleGroup_ruleGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroup' {Text
ruleGroupName :: Text
$sel:ruleGroupName:CreateRuleGroup' :: CreateRuleGroup -> Text
ruleGroupName} -> Text
ruleGroupName) (\s :: CreateRuleGroup
s@CreateRuleGroup' {} Text
a -> CreateRuleGroup
s {$sel:ruleGroupName:CreateRuleGroup' :: Text
ruleGroupName = Text
a} :: CreateRuleGroup)

-- | 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.
createRuleGroup_type :: Lens.Lens' CreateRuleGroup RuleGroupType
createRuleGroup_type :: Lens' CreateRuleGroup RuleGroupType
createRuleGroup_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroup' {RuleGroupType
type' :: RuleGroupType
$sel:type':CreateRuleGroup' :: CreateRuleGroup -> RuleGroupType
type'} -> RuleGroupType
type') (\s :: CreateRuleGroup
s@CreateRuleGroup' {} RuleGroupType
a -> CreateRuleGroup
s {$sel:type':CreateRuleGroup' :: RuleGroupType
type' = RuleGroupType
a} :: CreateRuleGroup)

-- | The maximum operating resources that this rule group can use. Rule group
-- capacity is fixed at creation. When you update a rule group, you are
-- limited to this capacity. When you reference a rule group from a
-- firewall policy, Network Firewall reserves this capacity for the rule
-- group.
--
-- You can retrieve the capacity that would be required for a rule group
-- before you create the rule group by calling CreateRuleGroup with
-- @DryRun@ set to @TRUE@.
--
-- You can\'t change or exceed this capacity when you update the rule
-- group, so leave room for your rule group to grow.
--
-- __Capacity for a stateless rule group__
--
-- For a stateless rule group, the capacity required is the sum of the
-- capacity requirements of the individual rules that you expect to have in
-- the rule group.
--
-- To calculate the capacity requirement of a single rule, multiply the
-- capacity requirement values of each of the rule\'s match settings:
--
-- -   A match setting with no criteria specified has a value of 1.
--
-- -   A match setting with @Any@ specified has a value of 1.
--
-- -   All other match settings have a value equal to the number of
--     elements provided in the setting. For example, a protocol setting
--     [\"UDP\"] and a source setting [\"10.0.0.0\/24\"] each have a value
--     of 1. A protocol setting [\"UDP\",\"TCP\"] has a value of 2. A
--     source setting [\"10.0.0.0\/24\",\"10.0.0.1\/24\",\"10.0.0.2\/24\"]
--     has a value of 3.
--
-- A rule with no criteria specified in any of its match settings has a
-- capacity requirement of 1. A rule with protocol setting
-- [\"UDP\",\"TCP\"], source setting
-- [\"10.0.0.0\/24\",\"10.0.0.1\/24\",\"10.0.0.2\/24\"], and a single
-- specification or no specification for each of the other match settings
-- has a capacity requirement of 6.
--
-- __Capacity for a stateful rule group__
--
-- For a stateful rule group, the minimum capacity required is the number
-- of individual rules that you expect to have in the rule group.
createRuleGroup_capacity :: Lens.Lens' CreateRuleGroup Prelude.Int
createRuleGroup_capacity :: Lens' CreateRuleGroup Int
createRuleGroup_capacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroup' {Int
capacity :: Int
$sel:capacity:CreateRuleGroup' :: CreateRuleGroup -> Int
capacity} -> Int
capacity) (\s :: CreateRuleGroup
s@CreateRuleGroup' {} Int
a -> CreateRuleGroup
s {$sel:capacity:CreateRuleGroup' :: Int
capacity = Int
a} :: CreateRuleGroup)

instance Core.AWSRequest CreateRuleGroup where
  type
    AWSResponse CreateRuleGroup =
      CreateRuleGroupResponse
  request :: (Service -> Service) -> CreateRuleGroup -> Request CreateRuleGroup
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 CreateRuleGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateRuleGroup)))
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 -> CreateRuleGroupResponse
CreateRuleGroupResponse'
            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 CreateRuleGroup where
  hashWithSalt :: Int -> CreateRuleGroup -> Int
hashWithSalt Int
_salt CreateRuleGroup' {Int
Maybe Bool
Maybe (NonEmpty Tag)
Maybe Text
Maybe EncryptionConfiguration
Maybe SourceMetadata
Maybe RuleGroup
Text
RuleGroupType
capacity :: Int
type' :: RuleGroupType
ruleGroupName :: Text
tags :: Maybe (NonEmpty Tag)
sourceMetadata :: Maybe SourceMetadata
rules :: Maybe Text
ruleGroup :: Maybe RuleGroup
encryptionConfiguration :: Maybe EncryptionConfiguration
dryRun :: Maybe Bool
description :: Maybe Text
$sel:capacity:CreateRuleGroup' :: CreateRuleGroup -> Int
$sel:type':CreateRuleGroup' :: CreateRuleGroup -> RuleGroupType
$sel:ruleGroupName:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:tags:CreateRuleGroup' :: CreateRuleGroup -> Maybe (NonEmpty Tag)
$sel:sourceMetadata:CreateRuleGroup' :: CreateRuleGroup -> Maybe SourceMetadata
$sel:rules:CreateRuleGroup' :: CreateRuleGroup -> Maybe Text
$sel:ruleGroup:CreateRuleGroup' :: CreateRuleGroup -> Maybe RuleGroup
$sel:encryptionConfiguration:CreateRuleGroup' :: CreateRuleGroup -> Maybe EncryptionConfiguration
$sel:dryRun:CreateRuleGroup' :: CreateRuleGroup -> Maybe Bool
$sel:description:CreateRuleGroup' :: CreateRuleGroup -> 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
rules
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SourceMetadata
sourceMetadata
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ruleGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` RuleGroupType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
capacity

instance Prelude.NFData CreateRuleGroup where
  rnf :: CreateRuleGroup -> ()
rnf CreateRuleGroup' {Int
Maybe Bool
Maybe (NonEmpty Tag)
Maybe Text
Maybe EncryptionConfiguration
Maybe SourceMetadata
Maybe RuleGroup
Text
RuleGroupType
capacity :: Int
type' :: RuleGroupType
ruleGroupName :: Text
tags :: Maybe (NonEmpty Tag)
sourceMetadata :: Maybe SourceMetadata
rules :: Maybe Text
ruleGroup :: Maybe RuleGroup
encryptionConfiguration :: Maybe EncryptionConfiguration
dryRun :: Maybe Bool
description :: Maybe Text
$sel:capacity:CreateRuleGroup' :: CreateRuleGroup -> Int
$sel:type':CreateRuleGroup' :: CreateRuleGroup -> RuleGroupType
$sel:ruleGroupName:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:tags:CreateRuleGroup' :: CreateRuleGroup -> Maybe (NonEmpty Tag)
$sel:sourceMetadata:CreateRuleGroup' :: CreateRuleGroup -> Maybe SourceMetadata
$sel:rules:CreateRuleGroup' :: CreateRuleGroup -> Maybe Text
$sel:ruleGroup:CreateRuleGroup' :: CreateRuleGroup -> Maybe RuleGroup
$sel:encryptionConfiguration:CreateRuleGroup' :: CreateRuleGroup -> Maybe EncryptionConfiguration
$sel:dryRun:CreateRuleGroup' :: CreateRuleGroup -> Maybe Bool
$sel:description:CreateRuleGroup' :: CreateRuleGroup -> 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
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 (NonEmpty Tag)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ruleGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RuleGroupType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
capacity

instance Data.ToHeaders CreateRuleGroup where
  toHeaders :: CreateRuleGroup -> 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.CreateRuleGroup" ::
                          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 CreateRuleGroup where
  toJSON :: CreateRuleGroup -> Value
toJSON CreateRuleGroup' {Int
Maybe Bool
Maybe (NonEmpty Tag)
Maybe Text
Maybe EncryptionConfiguration
Maybe SourceMetadata
Maybe RuleGroup
Text
RuleGroupType
capacity :: Int
type' :: RuleGroupType
ruleGroupName :: Text
tags :: Maybe (NonEmpty Tag)
sourceMetadata :: Maybe SourceMetadata
rules :: Maybe Text
ruleGroup :: Maybe RuleGroup
encryptionConfiguration :: Maybe EncryptionConfiguration
dryRun :: Maybe Bool
description :: Maybe Text
$sel:capacity:CreateRuleGroup' :: CreateRuleGroup -> Int
$sel:type':CreateRuleGroup' :: CreateRuleGroup -> RuleGroupType
$sel:ruleGroupName:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:tags:CreateRuleGroup' :: CreateRuleGroup -> Maybe (NonEmpty Tag)
$sel:sourceMetadata:CreateRuleGroup' :: CreateRuleGroup -> Maybe SourceMetadata
$sel:rules:CreateRuleGroup' :: CreateRuleGroup -> Maybe Text
$sel:ruleGroup:CreateRuleGroup' :: CreateRuleGroup -> Maybe RuleGroup
$sel:encryptionConfiguration:CreateRuleGroup' :: CreateRuleGroup -> Maybe EncryptionConfiguration
$sel:dryRun:CreateRuleGroup' :: CreateRuleGroup -> Maybe Bool
$sel:description:CreateRuleGroup' :: CreateRuleGroup -> 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
"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
"Tags" 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 (NonEmpty Tag)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"RuleGroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
ruleGroupName),
            forall a. a -> Maybe a
Prelude.Just (Key
"Type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= RuleGroupType
type'),
            forall a. a -> Maybe a
Prelude.Just (Key
"Capacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Int
capacity)
          ]
      )

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

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

-- | /See:/ 'newCreateRuleGroupResponse' smart constructor.
data CreateRuleGroupResponse = CreateRuleGroupResponse'
  { -- | The response's http status code.
    CreateRuleGroupResponse -> 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.
    CreateRuleGroupResponse -> 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.
    CreateRuleGroupResponse -> RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
  }
  deriving (CreateRuleGroupResponse -> CreateRuleGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRuleGroupResponse -> CreateRuleGroupResponse -> Bool
$c/= :: CreateRuleGroupResponse -> CreateRuleGroupResponse -> Bool
== :: CreateRuleGroupResponse -> CreateRuleGroupResponse -> Bool
$c== :: CreateRuleGroupResponse -> CreateRuleGroupResponse -> Bool
Prelude.Eq, ReadPrec [CreateRuleGroupResponse]
ReadPrec CreateRuleGroupResponse
Int -> ReadS CreateRuleGroupResponse
ReadS [CreateRuleGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRuleGroupResponse]
$creadListPrec :: ReadPrec [CreateRuleGroupResponse]
readPrec :: ReadPrec CreateRuleGroupResponse
$creadPrec :: ReadPrec CreateRuleGroupResponse
readList :: ReadS [CreateRuleGroupResponse]
$creadList :: ReadS [CreateRuleGroupResponse]
readsPrec :: Int -> ReadS CreateRuleGroupResponse
$creadsPrec :: Int -> ReadS CreateRuleGroupResponse
Prelude.Read, Int -> CreateRuleGroupResponse -> ShowS
[CreateRuleGroupResponse] -> ShowS
CreateRuleGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRuleGroupResponse] -> ShowS
$cshowList :: [CreateRuleGroupResponse] -> ShowS
show :: CreateRuleGroupResponse -> String
$cshow :: CreateRuleGroupResponse -> String
showsPrec :: Int -> CreateRuleGroupResponse -> ShowS
$cshowsPrec :: Int -> CreateRuleGroupResponse -> ShowS
Prelude.Show, forall x. Rep CreateRuleGroupResponse x -> CreateRuleGroupResponse
forall x. CreateRuleGroupResponse -> Rep CreateRuleGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateRuleGroupResponse x -> CreateRuleGroupResponse
$cfrom :: forall x. CreateRuleGroupResponse -> Rep CreateRuleGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateRuleGroupResponse' 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', 'createRuleGroupResponse_httpStatus' - The response's http status code.
--
-- 'updateToken', 'createRuleGroupResponse_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', 'createRuleGroupResponse_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.
newCreateRuleGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'updateToken'
  Prelude.Text ->
  -- | 'ruleGroupResponse'
  RuleGroupResponse ->
  CreateRuleGroupResponse
newCreateRuleGroupResponse :: Int -> Text -> RuleGroupResponse -> CreateRuleGroupResponse
newCreateRuleGroupResponse
  Int
pHttpStatus_
  Text
pUpdateToken_
  RuleGroupResponse
pRuleGroupResponse_ =
    CreateRuleGroupResponse'
      { $sel:httpStatus:CreateRuleGroupResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:updateToken:CreateRuleGroupResponse' :: Text
updateToken = Text
pUpdateToken_,
        $sel:ruleGroupResponse:CreateRuleGroupResponse' :: RuleGroupResponse
ruleGroupResponse = RuleGroupResponse
pRuleGroupResponse_
      }

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

-- | 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.
createRuleGroupResponse_updateToken :: Lens.Lens' CreateRuleGroupResponse Prelude.Text
createRuleGroupResponse_updateToken :: Lens' CreateRuleGroupResponse Text
createRuleGroupResponse_updateToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroupResponse' {Text
updateToken :: Text
$sel:updateToken:CreateRuleGroupResponse' :: CreateRuleGroupResponse -> Text
updateToken} -> Text
updateToken) (\s :: CreateRuleGroupResponse
s@CreateRuleGroupResponse' {} Text
a -> CreateRuleGroupResponse
s {$sel:updateToken:CreateRuleGroupResponse' :: Text
updateToken = Text
a} :: CreateRuleGroupResponse)

-- | 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.
createRuleGroupResponse_ruleGroupResponse :: Lens.Lens' CreateRuleGroupResponse RuleGroupResponse
createRuleGroupResponse_ruleGroupResponse :: Lens' CreateRuleGroupResponse RuleGroupResponse
createRuleGroupResponse_ruleGroupResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroupResponse' {RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
$sel:ruleGroupResponse:CreateRuleGroupResponse' :: CreateRuleGroupResponse -> RuleGroupResponse
ruleGroupResponse} -> RuleGroupResponse
ruleGroupResponse) (\s :: CreateRuleGroupResponse
s@CreateRuleGroupResponse' {} RuleGroupResponse
a -> CreateRuleGroupResponse
s {$sel:ruleGroupResponse:CreateRuleGroupResponse' :: RuleGroupResponse
ruleGroupResponse = RuleGroupResponse
a} :: CreateRuleGroupResponse)

instance Prelude.NFData CreateRuleGroupResponse where
  rnf :: CreateRuleGroupResponse -> ()
rnf CreateRuleGroupResponse' {Int
Text
RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
updateToken :: Text
httpStatus :: Int
$sel:ruleGroupResponse:CreateRuleGroupResponse' :: CreateRuleGroupResponse -> RuleGroupResponse
$sel:updateToken:CreateRuleGroupResponse' :: CreateRuleGroupResponse -> Text
$sel:httpStatus:CreateRuleGroupResponse' :: CreateRuleGroupResponse -> 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