{-# 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.SES.CreateReceiptRule
-- 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 a receipt rule.
--
-- For information about setting up receipt rules, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/receiving-email-receipt-rules.html Amazon SES Developer Guide>.
--
-- You can execute this operation no more than once per second.
module Amazonka.SES.CreateReceiptRule
  ( -- * Creating a Request
    CreateReceiptRule (..),
    newCreateReceiptRule,

    -- * Request Lenses
    createReceiptRule_after,
    createReceiptRule_ruleSetName,
    createReceiptRule_rule,

    -- * Destructuring the Response
    CreateReceiptRuleResponse (..),
    newCreateReceiptRuleResponse,

    -- * Response Lenses
    createReceiptRuleResponse_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.SES.Types

-- | Represents a request to create a receipt rule. You use receipt rules to
-- receive email with Amazon SES. For more information, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/receiving-email-concepts.html Amazon SES Developer Guide>.
--
-- /See:/ 'newCreateReceiptRule' smart constructor.
data CreateReceiptRule = CreateReceiptRule'
  { -- | The name of an existing rule after which the new rule will be placed. If
    -- this parameter is null, the new rule will be inserted at the beginning
    -- of the rule list.
    CreateReceiptRule -> Maybe Text
after :: Prelude.Maybe Prelude.Text,
    -- | The name of the rule set that the receipt rule will be added to.
    CreateReceiptRule -> Text
ruleSetName :: Prelude.Text,
    -- | A data structure that contains the specified rule\'s name, actions,
    -- recipients, domains, enabled status, scan status, and TLS policy.
    CreateReceiptRule -> ReceiptRule
rule :: ReceiptRule
  }
  deriving (CreateReceiptRule -> CreateReceiptRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateReceiptRule -> CreateReceiptRule -> Bool
$c/= :: CreateReceiptRule -> CreateReceiptRule -> Bool
== :: CreateReceiptRule -> CreateReceiptRule -> Bool
$c== :: CreateReceiptRule -> CreateReceiptRule -> Bool
Prelude.Eq, ReadPrec [CreateReceiptRule]
ReadPrec CreateReceiptRule
Int -> ReadS CreateReceiptRule
ReadS [CreateReceiptRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateReceiptRule]
$creadListPrec :: ReadPrec [CreateReceiptRule]
readPrec :: ReadPrec CreateReceiptRule
$creadPrec :: ReadPrec CreateReceiptRule
readList :: ReadS [CreateReceiptRule]
$creadList :: ReadS [CreateReceiptRule]
readsPrec :: Int -> ReadS CreateReceiptRule
$creadsPrec :: Int -> ReadS CreateReceiptRule
Prelude.Read, Int -> CreateReceiptRule -> ShowS
[CreateReceiptRule] -> ShowS
CreateReceiptRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateReceiptRule] -> ShowS
$cshowList :: [CreateReceiptRule] -> ShowS
show :: CreateReceiptRule -> String
$cshow :: CreateReceiptRule -> String
showsPrec :: Int -> CreateReceiptRule -> ShowS
$cshowsPrec :: Int -> CreateReceiptRule -> ShowS
Prelude.Show, forall x. Rep CreateReceiptRule x -> CreateReceiptRule
forall x. CreateReceiptRule -> Rep CreateReceiptRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateReceiptRule x -> CreateReceiptRule
$cfrom :: forall x. CreateReceiptRule -> Rep CreateReceiptRule x
Prelude.Generic)

-- |
-- Create a value of 'CreateReceiptRule' 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:
--
-- 'after', 'createReceiptRule_after' - The name of an existing rule after which the new rule will be placed. If
-- this parameter is null, the new rule will be inserted at the beginning
-- of the rule list.
--
-- 'ruleSetName', 'createReceiptRule_ruleSetName' - The name of the rule set that the receipt rule will be added to.
--
-- 'rule', 'createReceiptRule_rule' - A data structure that contains the specified rule\'s name, actions,
-- recipients, domains, enabled status, scan status, and TLS policy.
newCreateReceiptRule ::
  -- | 'ruleSetName'
  Prelude.Text ->
  -- | 'rule'
  ReceiptRule ->
  CreateReceiptRule
newCreateReceiptRule :: Text -> ReceiptRule -> CreateReceiptRule
newCreateReceiptRule Text
pRuleSetName_ ReceiptRule
pRule_ =
  CreateReceiptRule'
    { $sel:after:CreateReceiptRule' :: Maybe Text
after = forall a. Maybe a
Prelude.Nothing,
      $sel:ruleSetName:CreateReceiptRule' :: Text
ruleSetName = Text
pRuleSetName_,
      $sel:rule:CreateReceiptRule' :: ReceiptRule
rule = ReceiptRule
pRule_
    }

-- | The name of an existing rule after which the new rule will be placed. If
-- this parameter is null, the new rule will be inserted at the beginning
-- of the rule list.
createReceiptRule_after :: Lens.Lens' CreateReceiptRule (Prelude.Maybe Prelude.Text)
createReceiptRule_after :: Lens' CreateReceiptRule (Maybe Text)
createReceiptRule_after = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateReceiptRule' {Maybe Text
after :: Maybe Text
$sel:after:CreateReceiptRule' :: CreateReceiptRule -> Maybe Text
after} -> Maybe Text
after) (\s :: CreateReceiptRule
s@CreateReceiptRule' {} Maybe Text
a -> CreateReceiptRule
s {$sel:after:CreateReceiptRule' :: Maybe Text
after = Maybe Text
a} :: CreateReceiptRule)

-- | The name of the rule set that the receipt rule will be added to.
createReceiptRule_ruleSetName :: Lens.Lens' CreateReceiptRule Prelude.Text
createReceiptRule_ruleSetName :: Lens' CreateReceiptRule Text
createReceiptRule_ruleSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateReceiptRule' {Text
ruleSetName :: Text
$sel:ruleSetName:CreateReceiptRule' :: CreateReceiptRule -> Text
ruleSetName} -> Text
ruleSetName) (\s :: CreateReceiptRule
s@CreateReceiptRule' {} Text
a -> CreateReceiptRule
s {$sel:ruleSetName:CreateReceiptRule' :: Text
ruleSetName = Text
a} :: CreateReceiptRule)

-- | A data structure that contains the specified rule\'s name, actions,
-- recipients, domains, enabled status, scan status, and TLS policy.
createReceiptRule_rule :: Lens.Lens' CreateReceiptRule ReceiptRule
createReceiptRule_rule :: Lens' CreateReceiptRule ReceiptRule
createReceiptRule_rule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateReceiptRule' {ReceiptRule
rule :: ReceiptRule
$sel:rule:CreateReceiptRule' :: CreateReceiptRule -> ReceiptRule
rule} -> ReceiptRule
rule) (\s :: CreateReceiptRule
s@CreateReceiptRule' {} ReceiptRule
a -> CreateReceiptRule
s {$sel:rule:CreateReceiptRule' :: ReceiptRule
rule = ReceiptRule
a} :: CreateReceiptRule)

instance Core.AWSRequest CreateReceiptRule where
  type
    AWSResponse CreateReceiptRule =
      CreateReceiptRuleResponse
  request :: (Service -> Service)
-> CreateReceiptRule -> Request CreateReceiptRule
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateReceiptRule
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateReceiptRule)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"CreateReceiptRuleResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> CreateReceiptRuleResponse
CreateReceiptRuleResponse'
            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))
      )

instance Prelude.Hashable CreateReceiptRule where
  hashWithSalt :: Int -> CreateReceiptRule -> Int
hashWithSalt Int
_salt CreateReceiptRule' {Maybe Text
Text
ReceiptRule
rule :: ReceiptRule
ruleSetName :: Text
after :: Maybe Text
$sel:rule:CreateReceiptRule' :: CreateReceiptRule -> ReceiptRule
$sel:ruleSetName:CreateReceiptRule' :: CreateReceiptRule -> Text
$sel:after:CreateReceiptRule' :: CreateReceiptRule -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
after
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ruleSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ReceiptRule
rule

instance Prelude.NFData CreateReceiptRule where
  rnf :: CreateReceiptRule -> ()
rnf CreateReceiptRule' {Maybe Text
Text
ReceiptRule
rule :: ReceiptRule
ruleSetName :: Text
after :: Maybe Text
$sel:rule:CreateReceiptRule' :: CreateReceiptRule -> ReceiptRule
$sel:ruleSetName:CreateReceiptRule' :: CreateReceiptRule -> Text
$sel:after:CreateReceiptRule' :: CreateReceiptRule -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
after
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ruleSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ReceiptRule
rule

instance Data.ToHeaders CreateReceiptRule where
  toHeaders :: CreateReceiptRule -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery CreateReceiptRule where
  toQuery :: CreateReceiptRule -> QueryString
toQuery CreateReceiptRule' {Maybe Text
Text
ReceiptRule
rule :: ReceiptRule
ruleSetName :: Text
after :: Maybe Text
$sel:rule:CreateReceiptRule' :: CreateReceiptRule -> ReceiptRule
$sel:ruleSetName:CreateReceiptRule' :: CreateReceiptRule -> Text
$sel:after:CreateReceiptRule' :: CreateReceiptRule -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateReceiptRule" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"After" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
after,
        ByteString
"RuleSetName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
ruleSetName,
        ByteString
"Rule" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ReceiptRule
rule
      ]

-- | An empty element returned on a successful request.
--
-- /See:/ 'newCreateReceiptRuleResponse' smart constructor.
data CreateReceiptRuleResponse = CreateReceiptRuleResponse'
  { -- | The response's http status code.
    CreateReceiptRuleResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateReceiptRuleResponse -> CreateReceiptRuleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateReceiptRuleResponse -> CreateReceiptRuleResponse -> Bool
$c/= :: CreateReceiptRuleResponse -> CreateReceiptRuleResponse -> Bool
== :: CreateReceiptRuleResponse -> CreateReceiptRuleResponse -> Bool
$c== :: CreateReceiptRuleResponse -> CreateReceiptRuleResponse -> Bool
Prelude.Eq, ReadPrec [CreateReceiptRuleResponse]
ReadPrec CreateReceiptRuleResponse
Int -> ReadS CreateReceiptRuleResponse
ReadS [CreateReceiptRuleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateReceiptRuleResponse]
$creadListPrec :: ReadPrec [CreateReceiptRuleResponse]
readPrec :: ReadPrec CreateReceiptRuleResponse
$creadPrec :: ReadPrec CreateReceiptRuleResponse
readList :: ReadS [CreateReceiptRuleResponse]
$creadList :: ReadS [CreateReceiptRuleResponse]
readsPrec :: Int -> ReadS CreateReceiptRuleResponse
$creadsPrec :: Int -> ReadS CreateReceiptRuleResponse
Prelude.Read, Int -> CreateReceiptRuleResponse -> ShowS
[CreateReceiptRuleResponse] -> ShowS
CreateReceiptRuleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateReceiptRuleResponse] -> ShowS
$cshowList :: [CreateReceiptRuleResponse] -> ShowS
show :: CreateReceiptRuleResponse -> String
$cshow :: CreateReceiptRuleResponse -> String
showsPrec :: Int -> CreateReceiptRuleResponse -> ShowS
$cshowsPrec :: Int -> CreateReceiptRuleResponse -> ShowS
Prelude.Show, forall x.
Rep CreateReceiptRuleResponse x -> CreateReceiptRuleResponse
forall x.
CreateReceiptRuleResponse -> Rep CreateReceiptRuleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateReceiptRuleResponse x -> CreateReceiptRuleResponse
$cfrom :: forall x.
CreateReceiptRuleResponse -> Rep CreateReceiptRuleResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateReceiptRuleResponse' 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', 'createReceiptRuleResponse_httpStatus' - The response's http status code.
newCreateReceiptRuleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateReceiptRuleResponse
newCreateReceiptRuleResponse :: Int -> CreateReceiptRuleResponse
newCreateReceiptRuleResponse Int
pHttpStatus_ =
  CreateReceiptRuleResponse'
    { $sel:httpStatus:CreateReceiptRuleResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData CreateReceiptRuleResponse where
  rnf :: CreateReceiptRuleResponse -> ()
rnf CreateReceiptRuleResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateReceiptRuleResponse' :: CreateReceiptRuleResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus