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

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

-- |
-- Module      : Amazonka.WAF.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)
--
-- 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.
--
-- Creates a @RuleGroup@. A rule group is a collection of predefined rules
-- that you add to a web ACL. You use UpdateRuleGroup to add rules to the
-- rule group.
--
-- Rule groups are subject to the following limits:
--
-- -   Three rule groups per account. You can request an increase to this
--     limit by contacting customer support.
--
-- -   One rule group per web ACL.
--
-- -   Ten rules per rule group.
--
-- 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.WAF.CreateRuleGroup
  ( -- * Creating a Request
    CreateRuleGroup (..),
    newCreateRuleGroup,

    -- * Request Lenses
    createRuleGroup_tags,
    createRuleGroup_name,
    createRuleGroup_metricName,
    createRuleGroup_changeToken,

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

    -- * Response Lenses
    createRuleGroupResponse_changeToken,
    createRuleGroupResponse_ruleGroup,
    createRuleGroupResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateRuleGroup' smart constructor.
data CreateRuleGroup = CreateRuleGroup'
  { CreateRuleGroup -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | A friendly name or description of the RuleGroup. You can\'t change
    -- @Name@ after you create a @RuleGroup@.
    CreateRuleGroup -> Text
name :: Prelude.Text,
    -- | A friendly name or description for the metrics for this @RuleGroup@. The
    -- name can contain only alphanumeric characters (A-Z, a-z, 0-9), with
    -- maximum length 128 and minimum length one. It can\'t contain whitespace
    -- or metric names reserved for AWS WAF, including \"All\" and
    -- \"Default_Action.\" You can\'t change the name of the metric after you
    -- create the @RuleGroup@.
    CreateRuleGroup -> Text
metricName :: Prelude.Text,
    -- | The value returned by the most recent call to GetChangeToken.
    CreateRuleGroup -> Text
changeToken :: Prelude.Text
  }
  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:
--
-- 'tags', 'createRuleGroup_tags' -
--
-- 'name', 'createRuleGroup_name' - A friendly name or description of the RuleGroup. You can\'t change
-- @Name@ after you create a @RuleGroup@.
--
-- 'metricName', 'createRuleGroup_metricName' - A friendly name or description for the metrics for this @RuleGroup@. The
-- name can contain only alphanumeric characters (A-Z, a-z, 0-9), with
-- maximum length 128 and minimum length one. It can\'t contain whitespace
-- or metric names reserved for AWS WAF, including \"All\" and
-- \"Default_Action.\" You can\'t change the name of the metric after you
-- create the @RuleGroup@.
--
-- 'changeToken', 'createRuleGroup_changeToken' - The value returned by the most recent call to GetChangeToken.
newCreateRuleGroup ::
  -- | 'name'
  Prelude.Text ->
  -- | 'metricName'
  Prelude.Text ->
  -- | 'changeToken'
  Prelude.Text ->
  CreateRuleGroup
newCreateRuleGroup :: Text -> Text -> Text -> CreateRuleGroup
newCreateRuleGroup Text
pName_ Text
pMetricName_ Text
pChangeToken_ =
  CreateRuleGroup'
    { $sel:tags:CreateRuleGroup' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateRuleGroup' :: Text
name = Text
pName_,
      $sel:metricName:CreateRuleGroup' :: Text
metricName = Text
pMetricName_,
      $sel:changeToken:CreateRuleGroup' :: Text
changeToken = Text
pChangeToken_
    }

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

-- | A friendly name or description of the RuleGroup. You can\'t change
-- @Name@ after you create a @RuleGroup@.
createRuleGroup_name :: Lens.Lens' CreateRuleGroup Prelude.Text
createRuleGroup_name :: Lens' CreateRuleGroup Text
createRuleGroup_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroup' {Text
name :: Text
$sel:name:CreateRuleGroup' :: CreateRuleGroup -> Text
name} -> Text
name) (\s :: CreateRuleGroup
s@CreateRuleGroup' {} Text
a -> CreateRuleGroup
s {$sel:name:CreateRuleGroup' :: Text
name = Text
a} :: CreateRuleGroup)

-- | A friendly name or description for the metrics for this @RuleGroup@. The
-- name can contain only alphanumeric characters (A-Z, a-z, 0-9), with
-- maximum length 128 and minimum length one. It can\'t contain whitespace
-- or metric names reserved for AWS WAF, including \"All\" and
-- \"Default_Action.\" You can\'t change the name of the metric after you
-- create the @RuleGroup@.
createRuleGroup_metricName :: Lens.Lens' CreateRuleGroup Prelude.Text
createRuleGroup_metricName :: Lens' CreateRuleGroup Text
createRuleGroup_metricName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroup' {Text
metricName :: Text
$sel:metricName:CreateRuleGroup' :: CreateRuleGroup -> Text
metricName} -> Text
metricName) (\s :: CreateRuleGroup
s@CreateRuleGroup' {} Text
a -> CreateRuleGroup
s {$sel:metricName:CreateRuleGroup' :: Text
metricName = Text
a} :: CreateRuleGroup)

-- | The value returned by the most recent call to GetChangeToken.
createRuleGroup_changeToken :: Lens.Lens' CreateRuleGroup Prelude.Text
createRuleGroup_changeToken :: Lens' CreateRuleGroup Text
createRuleGroup_changeToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroup' {Text
changeToken :: Text
$sel:changeToken:CreateRuleGroup' :: CreateRuleGroup -> Text
changeToken} -> Text
changeToken) (\s :: CreateRuleGroup
s@CreateRuleGroup' {} Text
a -> CreateRuleGroup
s {$sel:changeToken:CreateRuleGroup' :: Text
changeToken = Text
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 ->
          Maybe Text -> Maybe RuleGroup -> Int -> CreateRuleGroupResponse
CreateRuleGroupResponse'
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RuleGroup")
            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 CreateRuleGroup where
  hashWithSalt :: Int -> CreateRuleGroup -> Int
hashWithSalt Int
_salt CreateRuleGroup' {Maybe (NonEmpty Tag)
Text
changeToken :: Text
metricName :: Text
name :: Text
tags :: Maybe (NonEmpty Tag)
$sel:changeToken:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:metricName:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:name:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:tags:CreateRuleGroup' :: CreateRuleGroup -> Maybe (NonEmpty Tag)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
metricName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
changeToken

instance Prelude.NFData CreateRuleGroup where
  rnf :: CreateRuleGroup -> ()
rnf CreateRuleGroup' {Maybe (NonEmpty Tag)
Text
changeToken :: Text
metricName :: Text
name :: Text
tags :: Maybe (NonEmpty Tag)
$sel:changeToken:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:metricName:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:name:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:tags:CreateRuleGroup' :: CreateRuleGroup -> Maybe (NonEmpty Tag)
..} =
    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
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
metricName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
changeToken

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
"AWSWAF_20150824.CreateRuleGroup" ::
                          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 CreateRuleGroup where
  toJSON :: CreateRuleGroup -> Value
toJSON CreateRuleGroup' {Maybe (NonEmpty Tag)
Text
changeToken :: Text
metricName :: Text
name :: Text
tags :: Maybe (NonEmpty Tag)
$sel:changeToken:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:metricName:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:name:CreateRuleGroup' :: CreateRuleGroup -> Text
$sel:tags:CreateRuleGroup' :: CreateRuleGroup -> Maybe (NonEmpty Tag)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"MetricName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
metricName),
            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 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 @ChangeToken@ that you used to submit the @CreateRuleGroup@ request.
    -- You can also use this value to query the status of the request. For more
    -- information, see GetChangeTokenStatus.
    CreateRuleGroupResponse -> Maybe Text
changeToken :: Prelude.Maybe Prelude.Text,
    -- | An empty RuleGroup.
    CreateRuleGroupResponse -> Maybe RuleGroup
ruleGroup :: Prelude.Maybe RuleGroup,
    -- | The response's http status code.
    CreateRuleGroupResponse -> Int
httpStatus :: Prelude.Int
  }
  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:
--
-- 'changeToken', 'createRuleGroupResponse_changeToken' - The @ChangeToken@ that you used to submit the @CreateRuleGroup@ request.
-- You can also use this value to query the status of the request. For more
-- information, see GetChangeTokenStatus.
--
-- 'ruleGroup', 'createRuleGroupResponse_ruleGroup' - An empty RuleGroup.
--
-- 'httpStatus', 'createRuleGroupResponse_httpStatus' - The response's http status code.
newCreateRuleGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateRuleGroupResponse
newCreateRuleGroupResponse :: Int -> CreateRuleGroupResponse
newCreateRuleGroupResponse Int
pHttpStatus_ =
  CreateRuleGroupResponse'
    { $sel:changeToken:CreateRuleGroupResponse' :: Maybe Text
changeToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ruleGroup:CreateRuleGroupResponse' :: Maybe RuleGroup
ruleGroup = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateRuleGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | An empty RuleGroup.
createRuleGroupResponse_ruleGroup :: Lens.Lens' CreateRuleGroupResponse (Prelude.Maybe RuleGroup)
createRuleGroupResponse_ruleGroup :: Lens' CreateRuleGroupResponse (Maybe RuleGroup)
createRuleGroupResponse_ruleGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleGroupResponse' {Maybe RuleGroup
ruleGroup :: Maybe RuleGroup
$sel:ruleGroup:CreateRuleGroupResponse' :: CreateRuleGroupResponse -> Maybe RuleGroup
ruleGroup} -> Maybe RuleGroup
ruleGroup) (\s :: CreateRuleGroupResponse
s@CreateRuleGroupResponse' {} Maybe RuleGroup
a -> CreateRuleGroupResponse
s {$sel:ruleGroup:CreateRuleGroupResponse' :: Maybe RuleGroup
ruleGroup = Maybe RuleGroup
a} :: CreateRuleGroupResponse)

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

instance Prelude.NFData CreateRuleGroupResponse where
  rnf :: CreateRuleGroupResponse -> ()
rnf CreateRuleGroupResponse' {Int
Maybe Text
Maybe RuleGroup
httpStatus :: Int
ruleGroup :: Maybe RuleGroup
changeToken :: Maybe Text
$sel:httpStatus:CreateRuleGroupResponse' :: CreateRuleGroupResponse -> Int
$sel:ruleGroup:CreateRuleGroupResponse' :: CreateRuleGroupResponse -> Maybe RuleGroup
$sel:changeToken:CreateRuleGroupResponse' :: CreateRuleGroupResponse -> 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 Maybe RuleGroup
ruleGroup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus