{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.BulkEmailDestinationStatus
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.SES.Types.BulkEmailDestinationStatus 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 Amazonka.SES.Types.BulkEmailStatus

-- | An object that contains the response from the @SendBulkTemplatedEmail@
-- operation.
--
-- /See:/ 'newBulkEmailDestinationStatus' smart constructor.
data BulkEmailDestinationStatus = BulkEmailDestinationStatus'
  { -- | A description of an error that prevented a message being sent using the
    -- @SendBulkTemplatedEmail@ operation.
    BulkEmailDestinationStatus -> Maybe Text
error :: Prelude.Maybe Prelude.Text,
    -- | The unique message identifier returned from the @SendBulkTemplatedEmail@
    -- operation.
    BulkEmailDestinationStatus -> Maybe Text
messageId :: Prelude.Maybe Prelude.Text,
    -- | The status of a message sent using the @SendBulkTemplatedEmail@
    -- operation.
    --
    -- Possible values for this parameter include:
    --
    -- -   @Success@: Amazon SES accepted the message, and will attempt to
    --     deliver it to the recipients.
    --
    -- -   @MessageRejected@: The message was rejected because it contained a
    --     virus.
    --
    -- -   @MailFromDomainNotVerified@: The sender\'s email address or domain
    --     was not verified.
    --
    -- -   @ConfigurationSetDoesNotExist@: The configuration set you specified
    --     does not exist.
    --
    -- -   @TemplateDoesNotExist@: The template you specified does not exist.
    --
    -- -   @AccountSuspended@: Your account has been shut down because of
    --     issues related to your email sending practices.
    --
    -- -   @AccountThrottled@: The number of emails you can send has been
    --     reduced because your account has exceeded its allocated sending
    --     limit.
    --
    -- -   @AccountDailyQuotaExceeded@: You have reached or exceeded the
    --     maximum number of emails you can send from your account in a 24-hour
    --     period.
    --
    -- -   @InvalidSendingPoolName@: The configuration set you specified refers
    --     to an IP pool that does not exist.
    --
    -- -   @AccountSendingPaused@: Email sending for the Amazon SES account was
    --     disabled using the UpdateAccountSendingEnabled operation.
    --
    -- -   @ConfigurationSetSendingPaused@: Email sending for this
    --     configuration set was disabled using the
    --     UpdateConfigurationSetSendingEnabled operation.
    --
    -- -   @InvalidParameterValue@: One or more of the parameters you specified
    --     when calling this operation was invalid. See the error message for
    --     additional information.
    --
    -- -   @TransientFailure@: Amazon SES was unable to process your request
    --     because of a temporary issue.
    --
    -- -   @Failed@: Amazon SES was unable to process your request. See the
    --     error message for additional information.
    BulkEmailDestinationStatus -> Maybe BulkEmailStatus
status :: Prelude.Maybe BulkEmailStatus
  }
  deriving (BulkEmailDestinationStatus -> BulkEmailDestinationStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BulkEmailDestinationStatus -> BulkEmailDestinationStatus -> Bool
$c/= :: BulkEmailDestinationStatus -> BulkEmailDestinationStatus -> Bool
== :: BulkEmailDestinationStatus -> BulkEmailDestinationStatus -> Bool
$c== :: BulkEmailDestinationStatus -> BulkEmailDestinationStatus -> Bool
Prelude.Eq, ReadPrec [BulkEmailDestinationStatus]
ReadPrec BulkEmailDestinationStatus
Int -> ReadS BulkEmailDestinationStatus
ReadS [BulkEmailDestinationStatus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BulkEmailDestinationStatus]
$creadListPrec :: ReadPrec [BulkEmailDestinationStatus]
readPrec :: ReadPrec BulkEmailDestinationStatus
$creadPrec :: ReadPrec BulkEmailDestinationStatus
readList :: ReadS [BulkEmailDestinationStatus]
$creadList :: ReadS [BulkEmailDestinationStatus]
readsPrec :: Int -> ReadS BulkEmailDestinationStatus
$creadsPrec :: Int -> ReadS BulkEmailDestinationStatus
Prelude.Read, Int -> BulkEmailDestinationStatus -> ShowS
[BulkEmailDestinationStatus] -> ShowS
BulkEmailDestinationStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BulkEmailDestinationStatus] -> ShowS
$cshowList :: [BulkEmailDestinationStatus] -> ShowS
show :: BulkEmailDestinationStatus -> String
$cshow :: BulkEmailDestinationStatus -> String
showsPrec :: Int -> BulkEmailDestinationStatus -> ShowS
$cshowsPrec :: Int -> BulkEmailDestinationStatus -> ShowS
Prelude.Show, forall x.
Rep BulkEmailDestinationStatus x -> BulkEmailDestinationStatus
forall x.
BulkEmailDestinationStatus -> Rep BulkEmailDestinationStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BulkEmailDestinationStatus x -> BulkEmailDestinationStatus
$cfrom :: forall x.
BulkEmailDestinationStatus -> Rep BulkEmailDestinationStatus x
Prelude.Generic)

-- |
-- Create a value of 'BulkEmailDestinationStatus' 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:
--
-- 'error', 'bulkEmailDestinationStatus_error' - A description of an error that prevented a message being sent using the
-- @SendBulkTemplatedEmail@ operation.
--
-- 'messageId', 'bulkEmailDestinationStatus_messageId' - The unique message identifier returned from the @SendBulkTemplatedEmail@
-- operation.
--
-- 'status', 'bulkEmailDestinationStatus_status' - The status of a message sent using the @SendBulkTemplatedEmail@
-- operation.
--
-- Possible values for this parameter include:
--
-- -   @Success@: Amazon SES accepted the message, and will attempt to
--     deliver it to the recipients.
--
-- -   @MessageRejected@: The message was rejected because it contained a
--     virus.
--
-- -   @MailFromDomainNotVerified@: The sender\'s email address or domain
--     was not verified.
--
-- -   @ConfigurationSetDoesNotExist@: The configuration set you specified
--     does not exist.
--
-- -   @TemplateDoesNotExist@: The template you specified does not exist.
--
-- -   @AccountSuspended@: Your account has been shut down because of
--     issues related to your email sending practices.
--
-- -   @AccountThrottled@: The number of emails you can send has been
--     reduced because your account has exceeded its allocated sending
--     limit.
--
-- -   @AccountDailyQuotaExceeded@: You have reached or exceeded the
--     maximum number of emails you can send from your account in a 24-hour
--     period.
--
-- -   @InvalidSendingPoolName@: The configuration set you specified refers
--     to an IP pool that does not exist.
--
-- -   @AccountSendingPaused@: Email sending for the Amazon SES account was
--     disabled using the UpdateAccountSendingEnabled operation.
--
-- -   @ConfigurationSetSendingPaused@: Email sending for this
--     configuration set was disabled using the
--     UpdateConfigurationSetSendingEnabled operation.
--
-- -   @InvalidParameterValue@: One or more of the parameters you specified
--     when calling this operation was invalid. See the error message for
--     additional information.
--
-- -   @TransientFailure@: Amazon SES was unable to process your request
--     because of a temporary issue.
--
-- -   @Failed@: Amazon SES was unable to process your request. See the
--     error message for additional information.
newBulkEmailDestinationStatus ::
  BulkEmailDestinationStatus
newBulkEmailDestinationStatus :: BulkEmailDestinationStatus
newBulkEmailDestinationStatus =
  BulkEmailDestinationStatus'
    { $sel:error:BulkEmailDestinationStatus' :: Maybe Text
error =
        forall a. Maybe a
Prelude.Nothing,
      $sel:messageId:BulkEmailDestinationStatus' :: Maybe Text
messageId = forall a. Maybe a
Prelude.Nothing,
      $sel:status:BulkEmailDestinationStatus' :: Maybe BulkEmailStatus
status = forall a. Maybe a
Prelude.Nothing
    }

-- | A description of an error that prevented a message being sent using the
-- @SendBulkTemplatedEmail@ operation.
bulkEmailDestinationStatus_error :: Lens.Lens' BulkEmailDestinationStatus (Prelude.Maybe Prelude.Text)
bulkEmailDestinationStatus_error :: Lens' BulkEmailDestinationStatus (Maybe Text)
bulkEmailDestinationStatus_error = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BulkEmailDestinationStatus' {Maybe Text
error :: Maybe Text
$sel:error:BulkEmailDestinationStatus' :: BulkEmailDestinationStatus -> Maybe Text
error} -> Maybe Text
error) (\s :: BulkEmailDestinationStatus
s@BulkEmailDestinationStatus' {} Maybe Text
a -> BulkEmailDestinationStatus
s {$sel:error:BulkEmailDestinationStatus' :: Maybe Text
error = Maybe Text
a} :: BulkEmailDestinationStatus)

-- | The unique message identifier returned from the @SendBulkTemplatedEmail@
-- operation.
bulkEmailDestinationStatus_messageId :: Lens.Lens' BulkEmailDestinationStatus (Prelude.Maybe Prelude.Text)
bulkEmailDestinationStatus_messageId :: Lens' BulkEmailDestinationStatus (Maybe Text)
bulkEmailDestinationStatus_messageId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BulkEmailDestinationStatus' {Maybe Text
messageId :: Maybe Text
$sel:messageId:BulkEmailDestinationStatus' :: BulkEmailDestinationStatus -> Maybe Text
messageId} -> Maybe Text
messageId) (\s :: BulkEmailDestinationStatus
s@BulkEmailDestinationStatus' {} Maybe Text
a -> BulkEmailDestinationStatus
s {$sel:messageId:BulkEmailDestinationStatus' :: Maybe Text
messageId = Maybe Text
a} :: BulkEmailDestinationStatus)

-- | The status of a message sent using the @SendBulkTemplatedEmail@
-- operation.
--
-- Possible values for this parameter include:
--
-- -   @Success@: Amazon SES accepted the message, and will attempt to
--     deliver it to the recipients.
--
-- -   @MessageRejected@: The message was rejected because it contained a
--     virus.
--
-- -   @MailFromDomainNotVerified@: The sender\'s email address or domain
--     was not verified.
--
-- -   @ConfigurationSetDoesNotExist@: The configuration set you specified
--     does not exist.
--
-- -   @TemplateDoesNotExist@: The template you specified does not exist.
--
-- -   @AccountSuspended@: Your account has been shut down because of
--     issues related to your email sending practices.
--
-- -   @AccountThrottled@: The number of emails you can send has been
--     reduced because your account has exceeded its allocated sending
--     limit.
--
-- -   @AccountDailyQuotaExceeded@: You have reached or exceeded the
--     maximum number of emails you can send from your account in a 24-hour
--     period.
--
-- -   @InvalidSendingPoolName@: The configuration set you specified refers
--     to an IP pool that does not exist.
--
-- -   @AccountSendingPaused@: Email sending for the Amazon SES account was
--     disabled using the UpdateAccountSendingEnabled operation.
--
-- -   @ConfigurationSetSendingPaused@: Email sending for this
--     configuration set was disabled using the
--     UpdateConfigurationSetSendingEnabled operation.
--
-- -   @InvalidParameterValue@: One or more of the parameters you specified
--     when calling this operation was invalid. See the error message for
--     additional information.
--
-- -   @TransientFailure@: Amazon SES was unable to process your request
--     because of a temporary issue.
--
-- -   @Failed@: Amazon SES was unable to process your request. See the
--     error message for additional information.
bulkEmailDestinationStatus_status :: Lens.Lens' BulkEmailDestinationStatus (Prelude.Maybe BulkEmailStatus)
bulkEmailDestinationStatus_status :: Lens' BulkEmailDestinationStatus (Maybe BulkEmailStatus)
bulkEmailDestinationStatus_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BulkEmailDestinationStatus' {Maybe BulkEmailStatus
status :: Maybe BulkEmailStatus
$sel:status:BulkEmailDestinationStatus' :: BulkEmailDestinationStatus -> Maybe BulkEmailStatus
status} -> Maybe BulkEmailStatus
status) (\s :: BulkEmailDestinationStatus
s@BulkEmailDestinationStatus' {} Maybe BulkEmailStatus
a -> BulkEmailDestinationStatus
s {$sel:status:BulkEmailDestinationStatus' :: Maybe BulkEmailStatus
status = Maybe BulkEmailStatus
a} :: BulkEmailDestinationStatus)

instance Data.FromXML BulkEmailDestinationStatus where
  parseXML :: [Node] -> Either String BulkEmailDestinationStatus
parseXML [Node]
x =
    Maybe Text
-> Maybe Text
-> Maybe BulkEmailStatus
-> BulkEmailDestinationStatus
BulkEmailDestinationStatus'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Error")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MessageId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Status")

instance Prelude.Hashable BulkEmailDestinationStatus where
  hashWithSalt :: Int -> BulkEmailDestinationStatus -> Int
hashWithSalt Int
_salt BulkEmailDestinationStatus' {Maybe Text
Maybe BulkEmailStatus
status :: Maybe BulkEmailStatus
messageId :: Maybe Text
error :: Maybe Text
$sel:status:BulkEmailDestinationStatus' :: BulkEmailDestinationStatus -> Maybe BulkEmailStatus
$sel:messageId:BulkEmailDestinationStatus' :: BulkEmailDestinationStatus -> Maybe Text
$sel:error:BulkEmailDestinationStatus' :: BulkEmailDestinationStatus -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
error
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
messageId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BulkEmailStatus
status

instance Prelude.NFData BulkEmailDestinationStatus where
  rnf :: BulkEmailDestinationStatus -> ()
rnf BulkEmailDestinationStatus' {Maybe Text
Maybe BulkEmailStatus
status :: Maybe BulkEmailStatus
messageId :: Maybe Text
error :: Maybe Text
$sel:status:BulkEmailDestinationStatus' :: BulkEmailDestinationStatus -> Maybe BulkEmailStatus
$sel:messageId:BulkEmailDestinationStatus' :: BulkEmailDestinationStatus -> Maybe Text
$sel:error:BulkEmailDestinationStatus' :: BulkEmailDestinationStatus -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
error
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
messageId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BulkEmailStatus
status