{-# 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.CreateRegexPatternSet
-- 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 @RegexPatternSet@. You then use UpdateRegexPatternSet to
-- specify the regular expression (regex) pattern that you want AWS WAF to
-- search for, such as @B[a\@]dB[o0]t@. You can then configure AWS WAF to
-- reject those requests.
--
-- To create and configure a @RegexPatternSet@, perform the following
-- steps:
--
-- 1.  Use GetChangeToken to get the change token that you provide in the
--     @ChangeToken@ parameter of a @CreateRegexPatternSet@ request.
--
-- 2.  Submit a @CreateRegexPatternSet@ request.
--
-- 3.  Use @GetChangeToken@ to get the change token that you provide in the
--     @ChangeToken@ parameter of an @UpdateRegexPatternSet@ request.
--
-- 4.  Submit an UpdateRegexPatternSet request to specify the string that
--     you want AWS WAF to watch for.
--
-- 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.CreateRegexPatternSet
  ( -- * Creating a Request
    CreateRegexPatternSet (..),
    newCreateRegexPatternSet,

    -- * Request Lenses
    createRegexPatternSet_name,
    createRegexPatternSet_changeToken,

    -- * Destructuring the Response
    CreateRegexPatternSetResponse (..),
    newCreateRegexPatternSetResponse,

    -- * Response Lenses
    createRegexPatternSetResponse_changeToken,
    createRegexPatternSetResponse_regexPatternSet,
    createRegexPatternSetResponse_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

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

-- |
-- Create a value of 'CreateRegexPatternSet' 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', 'createRegexPatternSet_name' - A friendly name or description of the RegexPatternSet. You can\'t change
-- @Name@ after you create a @RegexPatternSet@.
--
-- 'changeToken', 'createRegexPatternSet_changeToken' - The value returned by the most recent call to GetChangeToken.
newCreateRegexPatternSet ::
  -- | 'name'
  Prelude.Text ->
  -- | 'changeToken'
  Prelude.Text ->
  CreateRegexPatternSet
newCreateRegexPatternSet :: Text -> Text -> CreateRegexPatternSet
newCreateRegexPatternSet Text
pName_ Text
pChangeToken_ =
  CreateRegexPatternSet'
    { $sel:name:CreateRegexPatternSet' :: Text
name = Text
pName_,
      $sel:changeToken:CreateRegexPatternSet' :: Text
changeToken = Text
pChangeToken_
    }

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

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

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

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

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

-- |
-- Create a value of 'CreateRegexPatternSetResponse' 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', 'createRegexPatternSetResponse_changeToken' - The @ChangeToken@ that you used to submit the @CreateRegexPatternSet@
-- request. You can also use this value to query the status of the request.
-- For more information, see GetChangeTokenStatus.
--
-- 'regexPatternSet', 'createRegexPatternSetResponse_regexPatternSet' - A RegexPatternSet that contains no objects.
--
-- 'httpStatus', 'createRegexPatternSetResponse_httpStatus' - The response's http status code.
newCreateRegexPatternSetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateRegexPatternSetResponse
newCreateRegexPatternSetResponse :: Int -> CreateRegexPatternSetResponse
newCreateRegexPatternSetResponse Int
pHttpStatus_ =
  CreateRegexPatternSetResponse'
    { $sel:changeToken:CreateRegexPatternSetResponse' :: Maybe Text
changeToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:regexPatternSet:CreateRegexPatternSetResponse' :: Maybe RegexPatternSet
regexPatternSet = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateRegexPatternSetResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | A RegexPatternSet that contains no objects.
createRegexPatternSetResponse_regexPatternSet :: Lens.Lens' CreateRegexPatternSetResponse (Prelude.Maybe RegexPatternSet)
createRegexPatternSetResponse_regexPatternSet :: Lens' CreateRegexPatternSetResponse (Maybe RegexPatternSet)
createRegexPatternSetResponse_regexPatternSet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRegexPatternSetResponse' {Maybe RegexPatternSet
regexPatternSet :: Maybe RegexPatternSet
$sel:regexPatternSet:CreateRegexPatternSetResponse' :: CreateRegexPatternSetResponse -> Maybe RegexPatternSet
regexPatternSet} -> Maybe RegexPatternSet
regexPatternSet) (\s :: CreateRegexPatternSetResponse
s@CreateRegexPatternSetResponse' {} Maybe RegexPatternSet
a -> CreateRegexPatternSetResponse
s {$sel:regexPatternSet:CreateRegexPatternSetResponse' :: Maybe RegexPatternSet
regexPatternSet = Maybe RegexPatternSet
a} :: CreateRegexPatternSetResponse)

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

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