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

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

-- |
-- Module      : Amazonka.WAFRegional.CreateSqlInjectionMatchSet
-- 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 SqlInjectionMatchSet, which you use to allow, block, or count
-- requests that contain snippets of SQL code in a specified part of web
-- requests. AWS WAF searches for character sequences that are likely to be
-- malicious strings.
--
-- To create and configure a @SqlInjectionMatchSet@, perform the following
-- steps:
--
-- 1.  Use GetChangeToken to get the change token that you provide in the
--     @ChangeToken@ parameter of a @CreateSqlInjectionMatchSet@ request.
--
-- 2.  Submit a @CreateSqlInjectionMatchSet@ request.
--
-- 3.  Use @GetChangeToken@ to get the change token that you provide in the
--     @ChangeToken@ parameter of an UpdateSqlInjectionMatchSet request.
--
-- 4.  Submit an UpdateSqlInjectionMatchSet request to specify the parts of
--     web requests in which you want to allow, block, or count malicious
--     SQL code.
--
-- For more information about how to use the AWS WAF API to allow or block
-- HTTP requests, see the
-- <https://docs.aws.amazon.com/waf/latest/developerguide/ AWS WAF Developer Guide>.
module Amazonka.WAFRegional.CreateSqlInjectionMatchSet
  ( -- * Creating a Request
    CreateSqlInjectionMatchSet (..),
    newCreateSqlInjectionMatchSet,

    -- * Request Lenses
    createSqlInjectionMatchSet_name,
    createSqlInjectionMatchSet_changeToken,

    -- * Destructuring the Response
    CreateSqlInjectionMatchSetResponse (..),
    newCreateSqlInjectionMatchSetResponse,

    -- * Response Lenses
    createSqlInjectionMatchSetResponse_changeToken,
    createSqlInjectionMatchSetResponse_sqlInjectionMatchSet,
    createSqlInjectionMatchSetResponse_httpStatus,
  )
where

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

-- | A request to create a SqlInjectionMatchSet.
--
-- /See:/ 'newCreateSqlInjectionMatchSet' smart constructor.
data CreateSqlInjectionMatchSet = CreateSqlInjectionMatchSet'
  { -- | A friendly name or description for the SqlInjectionMatchSet that you\'re
    -- creating. You can\'t change @Name@ after you create the
    -- @SqlInjectionMatchSet@.
    CreateSqlInjectionMatchSet -> Text
name :: Prelude.Text,
    -- | The value returned by the most recent call to GetChangeToken.
    CreateSqlInjectionMatchSet -> Text
changeToken :: Prelude.Text
  }
  deriving (CreateSqlInjectionMatchSet -> CreateSqlInjectionMatchSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSqlInjectionMatchSet -> CreateSqlInjectionMatchSet -> Bool
$c/= :: CreateSqlInjectionMatchSet -> CreateSqlInjectionMatchSet -> Bool
== :: CreateSqlInjectionMatchSet -> CreateSqlInjectionMatchSet -> Bool
$c== :: CreateSqlInjectionMatchSet -> CreateSqlInjectionMatchSet -> Bool
Prelude.Eq, ReadPrec [CreateSqlInjectionMatchSet]
ReadPrec CreateSqlInjectionMatchSet
Int -> ReadS CreateSqlInjectionMatchSet
ReadS [CreateSqlInjectionMatchSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSqlInjectionMatchSet]
$creadListPrec :: ReadPrec [CreateSqlInjectionMatchSet]
readPrec :: ReadPrec CreateSqlInjectionMatchSet
$creadPrec :: ReadPrec CreateSqlInjectionMatchSet
readList :: ReadS [CreateSqlInjectionMatchSet]
$creadList :: ReadS [CreateSqlInjectionMatchSet]
readsPrec :: Int -> ReadS CreateSqlInjectionMatchSet
$creadsPrec :: Int -> ReadS CreateSqlInjectionMatchSet
Prelude.Read, Int -> CreateSqlInjectionMatchSet -> ShowS
[CreateSqlInjectionMatchSet] -> ShowS
CreateSqlInjectionMatchSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSqlInjectionMatchSet] -> ShowS
$cshowList :: [CreateSqlInjectionMatchSet] -> ShowS
show :: CreateSqlInjectionMatchSet -> String
$cshow :: CreateSqlInjectionMatchSet -> String
showsPrec :: Int -> CreateSqlInjectionMatchSet -> ShowS
$cshowsPrec :: Int -> CreateSqlInjectionMatchSet -> ShowS
Prelude.Show, forall x.
Rep CreateSqlInjectionMatchSet x -> CreateSqlInjectionMatchSet
forall x.
CreateSqlInjectionMatchSet -> Rep CreateSqlInjectionMatchSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateSqlInjectionMatchSet x -> CreateSqlInjectionMatchSet
$cfrom :: forall x.
CreateSqlInjectionMatchSet -> Rep CreateSqlInjectionMatchSet x
Prelude.Generic)

-- |
-- Create a value of 'CreateSqlInjectionMatchSet' 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:
--
-- 'name', 'createSqlInjectionMatchSet_name' - A friendly name or description for the SqlInjectionMatchSet that you\'re
-- creating. You can\'t change @Name@ after you create the
-- @SqlInjectionMatchSet@.
--
-- 'changeToken', 'createSqlInjectionMatchSet_changeToken' - The value returned by the most recent call to GetChangeToken.
newCreateSqlInjectionMatchSet ::
  -- | 'name'
  Prelude.Text ->
  -- | 'changeToken'
  Prelude.Text ->
  CreateSqlInjectionMatchSet
newCreateSqlInjectionMatchSet :: Text -> Text -> CreateSqlInjectionMatchSet
newCreateSqlInjectionMatchSet Text
pName_ Text
pChangeToken_ =
  CreateSqlInjectionMatchSet'
    { $sel:name:CreateSqlInjectionMatchSet' :: Text
name = Text
pName_,
      $sel:changeToken:CreateSqlInjectionMatchSet' :: Text
changeToken = Text
pChangeToken_
    }

-- | A friendly name or description for the SqlInjectionMatchSet that you\'re
-- creating. You can\'t change @Name@ after you create the
-- @SqlInjectionMatchSet@.
createSqlInjectionMatchSet_name :: Lens.Lens' CreateSqlInjectionMatchSet Prelude.Text
createSqlInjectionMatchSet_name :: Lens' CreateSqlInjectionMatchSet Text
createSqlInjectionMatchSet_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSqlInjectionMatchSet' {Text
name :: Text
$sel:name:CreateSqlInjectionMatchSet' :: CreateSqlInjectionMatchSet -> Text
name} -> Text
name) (\s :: CreateSqlInjectionMatchSet
s@CreateSqlInjectionMatchSet' {} Text
a -> CreateSqlInjectionMatchSet
s {$sel:name:CreateSqlInjectionMatchSet' :: Text
name = Text
a} :: CreateSqlInjectionMatchSet)

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

instance Core.AWSRequest CreateSqlInjectionMatchSet where
  type
    AWSResponse CreateSqlInjectionMatchSet =
      CreateSqlInjectionMatchSetResponse
  request :: (Service -> Service)
-> CreateSqlInjectionMatchSet -> Request CreateSqlInjectionMatchSet
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 CreateSqlInjectionMatchSet
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateSqlInjectionMatchSet)))
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 SqlInjectionMatchSet
-> Int
-> CreateSqlInjectionMatchSetResponse
CreateSqlInjectionMatchSetResponse'
            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
"SqlInjectionMatchSet")
            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 CreateSqlInjectionMatchSet where
  hashWithSalt :: Int -> CreateSqlInjectionMatchSet -> Int
hashWithSalt Int
_salt CreateSqlInjectionMatchSet' {Text
changeToken :: Text
name :: Text
$sel:changeToken:CreateSqlInjectionMatchSet' :: CreateSqlInjectionMatchSet -> Text
$sel:name:CreateSqlInjectionMatchSet' :: CreateSqlInjectionMatchSet -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
changeToken

instance Prelude.NFData CreateSqlInjectionMatchSet where
  rnf :: CreateSqlInjectionMatchSet -> ()
rnf CreateSqlInjectionMatchSet' {Text
changeToken :: Text
name :: Text
$sel:changeToken:CreateSqlInjectionMatchSet' :: CreateSqlInjectionMatchSet -> Text
$sel:name:CreateSqlInjectionMatchSet' :: CreateSqlInjectionMatchSet -> Text
..} =
    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
changeToken

instance Data.ToHeaders CreateSqlInjectionMatchSet where
  toHeaders :: CreateSqlInjectionMatchSet -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSWAF_Regional_20161128.CreateSqlInjectionMatchSet" ::
                          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 CreateSqlInjectionMatchSet where
  toJSON :: CreateSqlInjectionMatchSet -> Value
toJSON CreateSqlInjectionMatchSet' {Text
changeToken :: Text
name :: Text
$sel:changeToken:CreateSqlInjectionMatchSet' :: CreateSqlInjectionMatchSet -> Text
$sel:name:CreateSqlInjectionMatchSet' :: CreateSqlInjectionMatchSet -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ 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
"ChangeToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
changeToken)
          ]
      )

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

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

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

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

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

-- | A SqlInjectionMatchSet.
createSqlInjectionMatchSetResponse_sqlInjectionMatchSet :: Lens.Lens' CreateSqlInjectionMatchSetResponse (Prelude.Maybe SqlInjectionMatchSet)
createSqlInjectionMatchSetResponse_sqlInjectionMatchSet :: Lens'
  CreateSqlInjectionMatchSetResponse (Maybe SqlInjectionMatchSet)
createSqlInjectionMatchSetResponse_sqlInjectionMatchSet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSqlInjectionMatchSetResponse' {Maybe SqlInjectionMatchSet
sqlInjectionMatchSet :: Maybe SqlInjectionMatchSet
$sel:sqlInjectionMatchSet:CreateSqlInjectionMatchSetResponse' :: CreateSqlInjectionMatchSetResponse -> Maybe SqlInjectionMatchSet
sqlInjectionMatchSet} -> Maybe SqlInjectionMatchSet
sqlInjectionMatchSet) (\s :: CreateSqlInjectionMatchSetResponse
s@CreateSqlInjectionMatchSetResponse' {} Maybe SqlInjectionMatchSet
a -> CreateSqlInjectionMatchSetResponse
s {$sel:sqlInjectionMatchSet:CreateSqlInjectionMatchSetResponse' :: Maybe SqlInjectionMatchSet
sqlInjectionMatchSet = Maybe SqlInjectionMatchSet
a} :: CreateSqlInjectionMatchSetResponse)

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

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