{-# 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.UpdateConfigurationSetSendingEnabled
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enables or disables email sending for messages sent using a specific
-- configuration set in a given AWS Region. You can use this operation in
-- conjunction with Amazon CloudWatch alarms to temporarily pause email
-- sending for a configuration set when the reputation metrics for that
-- configuration set (such as your bounce on complaint rate) exceed certain
-- thresholds.
--
-- You can execute this operation no more than once per second.
module Amazonka.SES.UpdateConfigurationSetSendingEnabled
  ( -- * Creating a Request
    UpdateConfigurationSetSendingEnabled (..),
    newUpdateConfigurationSetSendingEnabled,

    -- * Request Lenses
    updateConfigurationSetSendingEnabled_configurationSetName,
    updateConfigurationSetSendingEnabled_enabled,

    -- * Destructuring the Response
    UpdateConfigurationSetSendingEnabledResponse (..),
    newUpdateConfigurationSetSendingEnabledResponse,
  )
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 enable or disable the email sending capabilities
-- for a specific configuration set.
--
-- /See:/ 'newUpdateConfigurationSetSendingEnabled' smart constructor.
data UpdateConfigurationSetSendingEnabled = UpdateConfigurationSetSendingEnabled'
  { -- | The name of the configuration set that you want to update.
    UpdateConfigurationSetSendingEnabled -> Text
configurationSetName :: Prelude.Text,
    -- | Describes whether email sending is enabled or disabled for the
    -- configuration set.
    UpdateConfigurationSetSendingEnabled -> Bool
enabled :: Prelude.Bool
  }
  deriving (UpdateConfigurationSetSendingEnabled
-> UpdateConfigurationSetSendingEnabled -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConfigurationSetSendingEnabled
-> UpdateConfigurationSetSendingEnabled -> Bool
$c/= :: UpdateConfigurationSetSendingEnabled
-> UpdateConfigurationSetSendingEnabled -> Bool
== :: UpdateConfigurationSetSendingEnabled
-> UpdateConfigurationSetSendingEnabled -> Bool
$c== :: UpdateConfigurationSetSendingEnabled
-> UpdateConfigurationSetSendingEnabled -> Bool
Prelude.Eq, ReadPrec [UpdateConfigurationSetSendingEnabled]
ReadPrec UpdateConfigurationSetSendingEnabled
Int -> ReadS UpdateConfigurationSetSendingEnabled
ReadS [UpdateConfigurationSetSendingEnabled]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConfigurationSetSendingEnabled]
$creadListPrec :: ReadPrec [UpdateConfigurationSetSendingEnabled]
readPrec :: ReadPrec UpdateConfigurationSetSendingEnabled
$creadPrec :: ReadPrec UpdateConfigurationSetSendingEnabled
readList :: ReadS [UpdateConfigurationSetSendingEnabled]
$creadList :: ReadS [UpdateConfigurationSetSendingEnabled]
readsPrec :: Int -> ReadS UpdateConfigurationSetSendingEnabled
$creadsPrec :: Int -> ReadS UpdateConfigurationSetSendingEnabled
Prelude.Read, Int -> UpdateConfigurationSetSendingEnabled -> ShowS
[UpdateConfigurationSetSendingEnabled] -> ShowS
UpdateConfigurationSetSendingEnabled -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConfigurationSetSendingEnabled] -> ShowS
$cshowList :: [UpdateConfigurationSetSendingEnabled] -> ShowS
show :: UpdateConfigurationSetSendingEnabled -> String
$cshow :: UpdateConfigurationSetSendingEnabled -> String
showsPrec :: Int -> UpdateConfigurationSetSendingEnabled -> ShowS
$cshowsPrec :: Int -> UpdateConfigurationSetSendingEnabled -> ShowS
Prelude.Show, forall x.
Rep UpdateConfigurationSetSendingEnabled x
-> UpdateConfigurationSetSendingEnabled
forall x.
UpdateConfigurationSetSendingEnabled
-> Rep UpdateConfigurationSetSendingEnabled x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateConfigurationSetSendingEnabled x
-> UpdateConfigurationSetSendingEnabled
$cfrom :: forall x.
UpdateConfigurationSetSendingEnabled
-> Rep UpdateConfigurationSetSendingEnabled x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConfigurationSetSendingEnabled' 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:
--
-- 'configurationSetName', 'updateConfigurationSetSendingEnabled_configurationSetName' - The name of the configuration set that you want to update.
--
-- 'enabled', 'updateConfigurationSetSendingEnabled_enabled' - Describes whether email sending is enabled or disabled for the
-- configuration set.
newUpdateConfigurationSetSendingEnabled ::
  -- | 'configurationSetName'
  Prelude.Text ->
  -- | 'enabled'
  Prelude.Bool ->
  UpdateConfigurationSetSendingEnabled
newUpdateConfigurationSetSendingEnabled :: Text -> Bool -> UpdateConfigurationSetSendingEnabled
newUpdateConfigurationSetSendingEnabled
  Text
pConfigurationSetName_
  Bool
pEnabled_ =
    UpdateConfigurationSetSendingEnabled'
      { $sel:configurationSetName:UpdateConfigurationSetSendingEnabled' :: Text
configurationSetName =
          Text
pConfigurationSetName_,
        $sel:enabled:UpdateConfigurationSetSendingEnabled' :: Bool
enabled = Bool
pEnabled_
      }

-- | The name of the configuration set that you want to update.
updateConfigurationSetSendingEnabled_configurationSetName :: Lens.Lens' UpdateConfigurationSetSendingEnabled Prelude.Text
updateConfigurationSetSendingEnabled_configurationSetName :: Lens' UpdateConfigurationSetSendingEnabled Text
updateConfigurationSetSendingEnabled_configurationSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfigurationSetSendingEnabled' {Text
configurationSetName :: Text
$sel:configurationSetName:UpdateConfigurationSetSendingEnabled' :: UpdateConfigurationSetSendingEnabled -> Text
configurationSetName} -> Text
configurationSetName) (\s :: UpdateConfigurationSetSendingEnabled
s@UpdateConfigurationSetSendingEnabled' {} Text
a -> UpdateConfigurationSetSendingEnabled
s {$sel:configurationSetName:UpdateConfigurationSetSendingEnabled' :: Text
configurationSetName = Text
a} :: UpdateConfigurationSetSendingEnabled)

-- | Describes whether email sending is enabled or disabled for the
-- configuration set.
updateConfigurationSetSendingEnabled_enabled :: Lens.Lens' UpdateConfigurationSetSendingEnabled Prelude.Bool
updateConfigurationSetSendingEnabled_enabled :: Lens' UpdateConfigurationSetSendingEnabled Bool
updateConfigurationSetSendingEnabled_enabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfigurationSetSendingEnabled' {Bool
enabled :: Bool
$sel:enabled:UpdateConfigurationSetSendingEnabled' :: UpdateConfigurationSetSendingEnabled -> Bool
enabled} -> Bool
enabled) (\s :: UpdateConfigurationSetSendingEnabled
s@UpdateConfigurationSetSendingEnabled' {} Bool
a -> UpdateConfigurationSetSendingEnabled
s {$sel:enabled:UpdateConfigurationSetSendingEnabled' :: Bool
enabled = Bool
a} :: UpdateConfigurationSetSendingEnabled)

instance
  Core.AWSRequest
    UpdateConfigurationSetSendingEnabled
  where
  type
    AWSResponse UpdateConfigurationSetSendingEnabled =
      UpdateConfigurationSetSendingEnabledResponse
  request :: (Service -> Service)
-> UpdateConfigurationSetSendingEnabled
-> Request UpdateConfigurationSetSendingEnabled
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 UpdateConfigurationSetSendingEnabled
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse UpdateConfigurationSetSendingEnabled)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      UpdateConfigurationSetSendingEnabledResponse
UpdateConfigurationSetSendingEnabledResponse'

instance
  Prelude.Hashable
    UpdateConfigurationSetSendingEnabled
  where
  hashWithSalt :: Int -> UpdateConfigurationSetSendingEnabled -> Int
hashWithSalt
    Int
_salt
    UpdateConfigurationSetSendingEnabled' {Bool
Text
enabled :: Bool
configurationSetName :: Text
$sel:enabled:UpdateConfigurationSetSendingEnabled' :: UpdateConfigurationSetSendingEnabled -> Bool
$sel:configurationSetName:UpdateConfigurationSetSendingEnabled' :: UpdateConfigurationSetSendingEnabled -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationSetName
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Bool
enabled

instance
  Prelude.NFData
    UpdateConfigurationSetSendingEnabled
  where
  rnf :: UpdateConfigurationSetSendingEnabled -> ()
rnf UpdateConfigurationSetSendingEnabled' {Bool
Text
enabled :: Bool
configurationSetName :: Text
$sel:enabled:UpdateConfigurationSetSendingEnabled' :: UpdateConfigurationSetSendingEnabled -> Bool
$sel:configurationSetName:UpdateConfigurationSetSendingEnabled' :: UpdateConfigurationSetSendingEnabled -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
configurationSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
enabled

instance
  Data.ToHeaders
    UpdateConfigurationSetSendingEnabled
  where
  toHeaders :: UpdateConfigurationSetSendingEnabled -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance
  Data.ToQuery
    UpdateConfigurationSetSendingEnabled
  where
  toQuery :: UpdateConfigurationSetSendingEnabled -> QueryString
toQuery UpdateConfigurationSetSendingEnabled' {Bool
Text
enabled :: Bool
configurationSetName :: Text
$sel:enabled:UpdateConfigurationSetSendingEnabled' :: UpdateConfigurationSetSendingEnabled -> Bool
$sel:configurationSetName:UpdateConfigurationSetSendingEnabled' :: UpdateConfigurationSetSendingEnabled -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"UpdateConfigurationSetSendingEnabled" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"ConfigurationSetName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
configurationSetName,
        ByteString
"Enabled" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Bool
enabled
      ]

-- | /See:/ 'newUpdateConfigurationSetSendingEnabledResponse' smart constructor.
data UpdateConfigurationSetSendingEnabledResponse = UpdateConfigurationSetSendingEnabledResponse'
  {
  }
  deriving (UpdateConfigurationSetSendingEnabledResponse
-> UpdateConfigurationSetSendingEnabledResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConfigurationSetSendingEnabledResponse
-> UpdateConfigurationSetSendingEnabledResponse -> Bool
$c/= :: UpdateConfigurationSetSendingEnabledResponse
-> UpdateConfigurationSetSendingEnabledResponse -> Bool
== :: UpdateConfigurationSetSendingEnabledResponse
-> UpdateConfigurationSetSendingEnabledResponse -> Bool
$c== :: UpdateConfigurationSetSendingEnabledResponse
-> UpdateConfigurationSetSendingEnabledResponse -> Bool
Prelude.Eq, ReadPrec [UpdateConfigurationSetSendingEnabledResponse]
ReadPrec UpdateConfigurationSetSendingEnabledResponse
Int -> ReadS UpdateConfigurationSetSendingEnabledResponse
ReadS [UpdateConfigurationSetSendingEnabledResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConfigurationSetSendingEnabledResponse]
$creadListPrec :: ReadPrec [UpdateConfigurationSetSendingEnabledResponse]
readPrec :: ReadPrec UpdateConfigurationSetSendingEnabledResponse
$creadPrec :: ReadPrec UpdateConfigurationSetSendingEnabledResponse
readList :: ReadS [UpdateConfigurationSetSendingEnabledResponse]
$creadList :: ReadS [UpdateConfigurationSetSendingEnabledResponse]
readsPrec :: Int -> ReadS UpdateConfigurationSetSendingEnabledResponse
$creadsPrec :: Int -> ReadS UpdateConfigurationSetSendingEnabledResponse
Prelude.Read, Int -> UpdateConfigurationSetSendingEnabledResponse -> ShowS
[UpdateConfigurationSetSendingEnabledResponse] -> ShowS
UpdateConfigurationSetSendingEnabledResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConfigurationSetSendingEnabledResponse] -> ShowS
$cshowList :: [UpdateConfigurationSetSendingEnabledResponse] -> ShowS
show :: UpdateConfigurationSetSendingEnabledResponse -> String
$cshow :: UpdateConfigurationSetSendingEnabledResponse -> String
showsPrec :: Int -> UpdateConfigurationSetSendingEnabledResponse -> ShowS
$cshowsPrec :: Int -> UpdateConfigurationSetSendingEnabledResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateConfigurationSetSendingEnabledResponse x
-> UpdateConfigurationSetSendingEnabledResponse
forall x.
UpdateConfigurationSetSendingEnabledResponse
-> Rep UpdateConfigurationSetSendingEnabledResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateConfigurationSetSendingEnabledResponse x
-> UpdateConfigurationSetSendingEnabledResponse
$cfrom :: forall x.
UpdateConfigurationSetSendingEnabledResponse
-> Rep UpdateConfigurationSetSendingEnabledResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConfigurationSetSendingEnabledResponse' 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.
newUpdateConfigurationSetSendingEnabledResponse ::
  UpdateConfigurationSetSendingEnabledResponse
newUpdateConfigurationSetSendingEnabledResponse :: UpdateConfigurationSetSendingEnabledResponse
newUpdateConfigurationSetSendingEnabledResponse =
  UpdateConfigurationSetSendingEnabledResponse
UpdateConfigurationSetSendingEnabledResponse'

instance
  Prelude.NFData
    UpdateConfigurationSetSendingEnabledResponse
  where
  rnf :: UpdateConfigurationSetSendingEnabledResponse -> ()
rnf UpdateConfigurationSetSendingEnabledResponse
_ = ()