{-# 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.CreateRule
-- 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 @Rule@, which contains the @IPSet@ objects, @ByteMatchSet@
-- objects, and other predicates that identify the requests that you want
-- to block. If you add more than one predicate to a @Rule@, a request must
-- match all of the specifications to be allowed or blocked. For example,
-- suppose that you add the following to a @Rule@:
--
-- -   An @IPSet@ that matches the IP address @192.0.2.44\/32@
--
-- -   A @ByteMatchSet@ that matches @BadBot@ in the @User-Agent@ header
--
-- You then add the @Rule@ to a @WebACL@ and specify that you want to
-- blocks requests that satisfy the @Rule@. For a request to be blocked, it
-- must come from the IP address 192.0.2.44 /and/ the @User-Agent@ header
-- in the request must contain the value @BadBot@.
--
-- To create and configure a @Rule@, perform the following steps:
--
-- 1.  Create and update the predicates that you want to include in the
--     @Rule@. For more information, see CreateByteMatchSet, CreateIPSet,
--     and CreateSqlInjectionMatchSet.
--
-- 2.  Use GetChangeToken to get the change token that you provide in the
--     @ChangeToken@ parameter of a @CreateRule@ request.
--
-- 3.  Submit a @CreateRule@ request.
--
-- 4.  Use @GetChangeToken@ to get the change token that you provide in the
--     @ChangeToken@ parameter of an UpdateRule request.
--
-- 5.  Submit an @UpdateRule@ request to specify the predicates that you
--     want to include in the @Rule@.
--
-- 6.  Create and update a @WebACL@ that contains the @Rule@. For more
--     information, see CreateWebACL.
--
-- 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.CreateRule
  ( -- * Creating a Request
    CreateRule (..),
    newCreateRule,

    -- * Request Lenses
    createRule_tags,
    createRule_name,
    createRule_metricName,
    createRule_changeToken,

    -- * Destructuring the Response
    CreateRuleResponse (..),
    newCreateRuleResponse,

    -- * Response Lenses
    createRuleResponse_changeToken,
    createRuleResponse_rule,
    createRuleResponse_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:/ 'newCreateRule' smart constructor.
data CreateRule = CreateRule'
  { CreateRule -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | A friendly name or description of the Rule. You can\'t change the name
    -- of a @Rule@ after you create it.
    CreateRule -> Text
name :: Prelude.Text,
    -- | A friendly name or description for the metrics for this @Rule@. 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 @Rule@.
    CreateRule -> Text
metricName :: Prelude.Text,
    -- | The value returned by the most recent call to GetChangeToken.
    CreateRule -> Text
changeToken :: Prelude.Text
  }
  deriving (CreateRule -> CreateRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRule -> CreateRule -> Bool
$c/= :: CreateRule -> CreateRule -> Bool
== :: CreateRule -> CreateRule -> Bool
$c== :: CreateRule -> CreateRule -> Bool
Prelude.Eq, ReadPrec [CreateRule]
ReadPrec CreateRule
Int -> ReadS CreateRule
ReadS [CreateRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRule]
$creadListPrec :: ReadPrec [CreateRule]
readPrec :: ReadPrec CreateRule
$creadPrec :: ReadPrec CreateRule
readList :: ReadS [CreateRule]
$creadList :: ReadS [CreateRule]
readsPrec :: Int -> ReadS CreateRule
$creadsPrec :: Int -> ReadS CreateRule
Prelude.Read, Int -> CreateRule -> ShowS
[CreateRule] -> ShowS
CreateRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRule] -> ShowS
$cshowList :: [CreateRule] -> ShowS
show :: CreateRule -> String
$cshow :: CreateRule -> String
showsPrec :: Int -> CreateRule -> ShowS
$cshowsPrec :: Int -> CreateRule -> ShowS
Prelude.Show, forall x. Rep CreateRule x -> CreateRule
forall x. CreateRule -> Rep CreateRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateRule x -> CreateRule
$cfrom :: forall x. CreateRule -> Rep CreateRule x
Prelude.Generic)

-- |
-- Create a value of 'CreateRule' 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', 'createRule_tags' -
--
-- 'name', 'createRule_name' - A friendly name or description of the Rule. You can\'t change the name
-- of a @Rule@ after you create it.
--
-- 'metricName', 'createRule_metricName' - A friendly name or description for the metrics for this @Rule@. 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 @Rule@.
--
-- 'changeToken', 'createRule_changeToken' - The value returned by the most recent call to GetChangeToken.
newCreateRule ::
  -- | 'name'
  Prelude.Text ->
  -- | 'metricName'
  Prelude.Text ->
  -- | 'changeToken'
  Prelude.Text ->
  CreateRule
newCreateRule :: Text -> Text -> Text -> CreateRule
newCreateRule Text
pName_ Text
pMetricName_ Text
pChangeToken_ =
  CreateRule'
    { $sel:tags:CreateRule' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateRule' :: Text
name = Text
pName_,
      $sel:metricName:CreateRule' :: Text
metricName = Text
pMetricName_,
      $sel:changeToken:CreateRule' :: Text
changeToken = Text
pChangeToken_
    }

createRule_tags :: Lens.Lens' CreateRule (Prelude.Maybe (Prelude.NonEmpty Tag))
createRule_tags :: Lens' CreateRule (Maybe (NonEmpty Tag))
createRule_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRule' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:CreateRule' :: CreateRule -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: CreateRule
s@CreateRule' {} Maybe (NonEmpty Tag)
a -> CreateRule
s {$sel:tags:CreateRule' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
a} :: CreateRule) 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 Rule. You can\'t change the name
-- of a @Rule@ after you create it.
createRule_name :: Lens.Lens' CreateRule Prelude.Text
createRule_name :: Lens' CreateRule Text
createRule_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRule' {Text
name :: Text
$sel:name:CreateRule' :: CreateRule -> Text
name} -> Text
name) (\s :: CreateRule
s@CreateRule' {} Text
a -> CreateRule
s {$sel:name:CreateRule' :: Text
name = Text
a} :: CreateRule)

-- | A friendly name or description for the metrics for this @Rule@. 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 @Rule@.
createRule_metricName :: Lens.Lens' CreateRule Prelude.Text
createRule_metricName :: Lens' CreateRule Text
createRule_metricName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRule' {Text
metricName :: Text
$sel:metricName:CreateRule' :: CreateRule -> Text
metricName} -> Text
metricName) (\s :: CreateRule
s@CreateRule' {} Text
a -> CreateRule
s {$sel:metricName:CreateRule' :: Text
metricName = Text
a} :: CreateRule)

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

instance Core.AWSRequest CreateRule where
  type AWSResponse CreateRule = CreateRuleResponse
  request :: (Service -> Service) -> CreateRule -> Request CreateRule
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 CreateRule
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateRule)))
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 Rule -> Int -> CreateRuleResponse
CreateRuleResponse'
            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
"Rule")
            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 CreateRule where
  hashWithSalt :: Int -> CreateRule -> Int
hashWithSalt Int
_salt CreateRule' {Maybe (NonEmpty Tag)
Text
changeToken :: Text
metricName :: Text
name :: Text
tags :: Maybe (NonEmpty Tag)
$sel:changeToken:CreateRule' :: CreateRule -> Text
$sel:metricName:CreateRule' :: CreateRule -> Text
$sel:name:CreateRule' :: CreateRule -> Text
$sel:tags:CreateRule' :: CreateRule -> 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 CreateRule where
  rnf :: CreateRule -> ()
rnf CreateRule' {Maybe (NonEmpty Tag)
Text
changeToken :: Text
metricName :: Text
name :: Text
tags :: Maybe (NonEmpty Tag)
$sel:changeToken:CreateRule' :: CreateRule -> Text
$sel:metricName:CreateRule' :: CreateRule -> Text
$sel:name:CreateRule' :: CreateRule -> Text
$sel:tags:CreateRule' :: CreateRule -> 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 CreateRule where
  toHeaders :: CreateRule -> 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.CreateRule" :: 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 CreateRule where
  toJSON :: CreateRule -> Value
toJSON CreateRule' {Maybe (NonEmpty Tag)
Text
changeToken :: Text
metricName :: Text
name :: Text
tags :: Maybe (NonEmpty Tag)
$sel:changeToken:CreateRule' :: CreateRule -> Text
$sel:metricName:CreateRule' :: CreateRule -> Text
$sel:name:CreateRule' :: CreateRule -> Text
$sel:tags:CreateRule' :: CreateRule -> 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 CreateRule where
  toPath :: CreateRule -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'CreateRuleResponse' 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', 'createRuleResponse_changeToken' - The @ChangeToken@ that you used to submit the @CreateRule@ request. You
-- can also use this value to query the status of the request. For more
-- information, see GetChangeTokenStatus.
--
-- 'rule', 'createRuleResponse_rule' - The Rule returned in the @CreateRule@ response.
--
-- 'httpStatus', 'createRuleResponse_httpStatus' - The response's http status code.
newCreateRuleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateRuleResponse
newCreateRuleResponse :: Int -> CreateRuleResponse
newCreateRuleResponse Int
pHttpStatus_ =
  CreateRuleResponse'
    { $sel:changeToken:CreateRuleResponse' :: Maybe Text
changeToken = forall a. Maybe a
Prelude.Nothing,
      $sel:rule:CreateRuleResponse' :: Maybe Rule
rule = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateRuleResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | The Rule returned in the @CreateRule@ response.
createRuleResponse_rule :: Lens.Lens' CreateRuleResponse (Prelude.Maybe Rule)
createRuleResponse_rule :: Lens' CreateRuleResponse (Maybe Rule)
createRuleResponse_rule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRuleResponse' {Maybe Rule
rule :: Maybe Rule
$sel:rule:CreateRuleResponse' :: CreateRuleResponse -> Maybe Rule
rule} -> Maybe Rule
rule) (\s :: CreateRuleResponse
s@CreateRuleResponse' {} Maybe Rule
a -> CreateRuleResponse
s {$sel:rule:CreateRuleResponse' :: Maybe Rule
rule = Maybe Rule
a} :: CreateRuleResponse)

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

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