{-# 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.ReorderReceiptRuleSet
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Reorders the receipt rules within a receipt rule set.
--
-- All of the rules in the rule set must be represented in this request.
-- That is, this API will return an error if the reorder request doesn\'t
-- explicitly position all of the rules.
--
-- For information about managing receipt rule sets, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/receiving-email-managing-receipt-rule-sets.html Amazon SES Developer Guide>.
--
-- You can execute this operation no more than once per second.
module Amazonka.SES.ReorderReceiptRuleSet
  ( -- * Creating a Request
    ReorderReceiptRuleSet (..),
    newReorderReceiptRuleSet,

    -- * Request Lenses
    reorderReceiptRuleSet_ruleSetName,
    reorderReceiptRuleSet_ruleNames,

    -- * Destructuring the Response
    ReorderReceiptRuleSetResponse (..),
    newReorderReceiptRuleSetResponse,

    -- * Response Lenses
    reorderReceiptRuleSetResponse_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 reorder the receipt rules within a receipt rule
-- set. You use receipt rule sets 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:/ 'newReorderReceiptRuleSet' smart constructor.
data ReorderReceiptRuleSet = ReorderReceiptRuleSet'
  { -- | The name of the receipt rule set to reorder.
    ReorderReceiptRuleSet -> Text
ruleSetName :: Prelude.Text,
    -- | A list of the specified receipt rule set\'s receipt rules in the order
    -- that you want to put them.
    ReorderReceiptRuleSet -> [Text]
ruleNames :: [Prelude.Text]
  }
  deriving (ReorderReceiptRuleSet -> ReorderReceiptRuleSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReorderReceiptRuleSet -> ReorderReceiptRuleSet -> Bool
$c/= :: ReorderReceiptRuleSet -> ReorderReceiptRuleSet -> Bool
== :: ReorderReceiptRuleSet -> ReorderReceiptRuleSet -> Bool
$c== :: ReorderReceiptRuleSet -> ReorderReceiptRuleSet -> Bool
Prelude.Eq, ReadPrec [ReorderReceiptRuleSet]
ReadPrec ReorderReceiptRuleSet
Int -> ReadS ReorderReceiptRuleSet
ReadS [ReorderReceiptRuleSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReorderReceiptRuleSet]
$creadListPrec :: ReadPrec [ReorderReceiptRuleSet]
readPrec :: ReadPrec ReorderReceiptRuleSet
$creadPrec :: ReadPrec ReorderReceiptRuleSet
readList :: ReadS [ReorderReceiptRuleSet]
$creadList :: ReadS [ReorderReceiptRuleSet]
readsPrec :: Int -> ReadS ReorderReceiptRuleSet
$creadsPrec :: Int -> ReadS ReorderReceiptRuleSet
Prelude.Read, Int -> ReorderReceiptRuleSet -> ShowS
[ReorderReceiptRuleSet] -> ShowS
ReorderReceiptRuleSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReorderReceiptRuleSet] -> ShowS
$cshowList :: [ReorderReceiptRuleSet] -> ShowS
show :: ReorderReceiptRuleSet -> String
$cshow :: ReorderReceiptRuleSet -> String
showsPrec :: Int -> ReorderReceiptRuleSet -> ShowS
$cshowsPrec :: Int -> ReorderReceiptRuleSet -> ShowS
Prelude.Show, forall x. Rep ReorderReceiptRuleSet x -> ReorderReceiptRuleSet
forall x. ReorderReceiptRuleSet -> Rep ReorderReceiptRuleSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReorderReceiptRuleSet x -> ReorderReceiptRuleSet
$cfrom :: forall x. ReorderReceiptRuleSet -> Rep ReorderReceiptRuleSet x
Prelude.Generic)

-- |
-- Create a value of 'ReorderReceiptRuleSet' 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:
--
-- 'ruleSetName', 'reorderReceiptRuleSet_ruleSetName' - The name of the receipt rule set to reorder.
--
-- 'ruleNames', 'reorderReceiptRuleSet_ruleNames' - A list of the specified receipt rule set\'s receipt rules in the order
-- that you want to put them.
newReorderReceiptRuleSet ::
  -- | 'ruleSetName'
  Prelude.Text ->
  ReorderReceiptRuleSet
newReorderReceiptRuleSet :: Text -> ReorderReceiptRuleSet
newReorderReceiptRuleSet Text
pRuleSetName_ =
  ReorderReceiptRuleSet'
    { $sel:ruleSetName:ReorderReceiptRuleSet' :: Text
ruleSetName = Text
pRuleSetName_,
      $sel:ruleNames:ReorderReceiptRuleSet' :: [Text]
ruleNames = forall a. Monoid a => a
Prelude.mempty
    }

-- | The name of the receipt rule set to reorder.
reorderReceiptRuleSet_ruleSetName :: Lens.Lens' ReorderReceiptRuleSet Prelude.Text
reorderReceiptRuleSet_ruleSetName :: Lens' ReorderReceiptRuleSet Text
reorderReceiptRuleSet_ruleSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReorderReceiptRuleSet' {Text
ruleSetName :: Text
$sel:ruleSetName:ReorderReceiptRuleSet' :: ReorderReceiptRuleSet -> Text
ruleSetName} -> Text
ruleSetName) (\s :: ReorderReceiptRuleSet
s@ReorderReceiptRuleSet' {} Text
a -> ReorderReceiptRuleSet
s {$sel:ruleSetName:ReorderReceiptRuleSet' :: Text
ruleSetName = Text
a} :: ReorderReceiptRuleSet)

-- | A list of the specified receipt rule set\'s receipt rules in the order
-- that you want to put them.
reorderReceiptRuleSet_ruleNames :: Lens.Lens' ReorderReceiptRuleSet [Prelude.Text]
reorderReceiptRuleSet_ruleNames :: Lens' ReorderReceiptRuleSet [Text]
reorderReceiptRuleSet_ruleNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReorderReceiptRuleSet' {[Text]
ruleNames :: [Text]
$sel:ruleNames:ReorderReceiptRuleSet' :: ReorderReceiptRuleSet -> [Text]
ruleNames} -> [Text]
ruleNames) (\s :: ReorderReceiptRuleSet
s@ReorderReceiptRuleSet' {} [Text]
a -> ReorderReceiptRuleSet
s {$sel:ruleNames:ReorderReceiptRuleSet' :: [Text]
ruleNames = [Text]
a} :: ReorderReceiptRuleSet) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest ReorderReceiptRuleSet where
  type
    AWSResponse ReorderReceiptRuleSet =
      ReorderReceiptRuleSetResponse
  request :: (Service -> Service)
-> ReorderReceiptRuleSet -> Request ReorderReceiptRuleSet
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 ReorderReceiptRuleSet
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ReorderReceiptRuleSet)))
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
"ReorderReceiptRuleSetResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> ReorderReceiptRuleSetResponse
ReorderReceiptRuleSetResponse'
            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 ReorderReceiptRuleSet where
  hashWithSalt :: Int -> ReorderReceiptRuleSet -> Int
hashWithSalt Int
_salt ReorderReceiptRuleSet' {[Text]
Text
ruleNames :: [Text]
ruleSetName :: Text
$sel:ruleNames:ReorderReceiptRuleSet' :: ReorderReceiptRuleSet -> [Text]
$sel:ruleSetName:ReorderReceiptRuleSet' :: ReorderReceiptRuleSet -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ruleSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
ruleNames

instance Prelude.NFData ReorderReceiptRuleSet where
  rnf :: ReorderReceiptRuleSet -> ()
rnf ReorderReceiptRuleSet' {[Text]
Text
ruleNames :: [Text]
ruleSetName :: Text
$sel:ruleNames:ReorderReceiptRuleSet' :: ReorderReceiptRuleSet -> [Text]
$sel:ruleSetName:ReorderReceiptRuleSet' :: ReorderReceiptRuleSet -> Text
..} =
    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 [Text]
ruleNames

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

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

instance Data.ToQuery ReorderReceiptRuleSet where
  toQuery :: ReorderReceiptRuleSet -> QueryString
toQuery ReorderReceiptRuleSet' {[Text]
Text
ruleNames :: [Text]
ruleSetName :: Text
$sel:ruleNames:ReorderReceiptRuleSet' :: ReorderReceiptRuleSet -> [Text]
$sel:ruleSetName:ReorderReceiptRuleSet' :: ReorderReceiptRuleSet -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ReorderReceiptRuleSet" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"RuleSetName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
ruleSetName,
        ByteString
"RuleNames"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Text]
ruleNames
      ]

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

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

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

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