{-# 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.BouncedRecipientInfo
-- 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.BouncedRecipientInfo 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.BounceType
import Amazonka.SES.Types.RecipientDsnFields

-- | Recipient-related information to include in the Delivery Status
-- Notification (DSN) when an email that Amazon SES receives on your behalf
-- bounces.
--
-- For information about receiving email through Amazon SES, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/receiving-email.html Amazon SES Developer Guide>.
--
-- /See:/ 'newBouncedRecipientInfo' smart constructor.
data BouncedRecipientInfo = BouncedRecipientInfo'
  { -- | The reason for the bounce. You must provide either this parameter or
    -- @RecipientDsnFields@.
    BouncedRecipientInfo -> Maybe BounceType
bounceType :: Prelude.Maybe BounceType,
    -- | This parameter is used only for sending authorization. It is the ARN of
    -- the identity that is associated with the sending authorization policy
    -- that permits you to receive email for the recipient of the bounced
    -- email. For more information about sending authorization, see the
    -- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/sending-authorization.html Amazon SES Developer Guide>.
    BouncedRecipientInfo -> Maybe Text
recipientArn :: Prelude.Maybe Prelude.Text,
    -- | Recipient-related DSN fields, most of which would normally be filled in
    -- automatically when provided with a @BounceType@. You must provide either
    -- this parameter or @BounceType@.
    BouncedRecipientInfo -> Maybe RecipientDsnFields
recipientDsnFields :: Prelude.Maybe RecipientDsnFields,
    -- | The email address of the recipient of the bounced email.
    BouncedRecipientInfo -> Text
recipient :: Prelude.Text
  }
  deriving (BouncedRecipientInfo -> BouncedRecipientInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BouncedRecipientInfo -> BouncedRecipientInfo -> Bool
$c/= :: BouncedRecipientInfo -> BouncedRecipientInfo -> Bool
== :: BouncedRecipientInfo -> BouncedRecipientInfo -> Bool
$c== :: BouncedRecipientInfo -> BouncedRecipientInfo -> Bool
Prelude.Eq, ReadPrec [BouncedRecipientInfo]
ReadPrec BouncedRecipientInfo
Int -> ReadS BouncedRecipientInfo
ReadS [BouncedRecipientInfo]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BouncedRecipientInfo]
$creadListPrec :: ReadPrec [BouncedRecipientInfo]
readPrec :: ReadPrec BouncedRecipientInfo
$creadPrec :: ReadPrec BouncedRecipientInfo
readList :: ReadS [BouncedRecipientInfo]
$creadList :: ReadS [BouncedRecipientInfo]
readsPrec :: Int -> ReadS BouncedRecipientInfo
$creadsPrec :: Int -> ReadS BouncedRecipientInfo
Prelude.Read, Int -> BouncedRecipientInfo -> ShowS
[BouncedRecipientInfo] -> ShowS
BouncedRecipientInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BouncedRecipientInfo] -> ShowS
$cshowList :: [BouncedRecipientInfo] -> ShowS
show :: BouncedRecipientInfo -> String
$cshow :: BouncedRecipientInfo -> String
showsPrec :: Int -> BouncedRecipientInfo -> ShowS
$cshowsPrec :: Int -> BouncedRecipientInfo -> ShowS
Prelude.Show, forall x. Rep BouncedRecipientInfo x -> BouncedRecipientInfo
forall x. BouncedRecipientInfo -> Rep BouncedRecipientInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BouncedRecipientInfo x -> BouncedRecipientInfo
$cfrom :: forall x. BouncedRecipientInfo -> Rep BouncedRecipientInfo x
Prelude.Generic)

-- |
-- Create a value of 'BouncedRecipientInfo' 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:
--
-- 'bounceType', 'bouncedRecipientInfo_bounceType' - The reason for the bounce. You must provide either this parameter or
-- @RecipientDsnFields@.
--
-- 'recipientArn', 'bouncedRecipientInfo_recipientArn' - This parameter is used only for sending authorization. It is the ARN of
-- the identity that is associated with the sending authorization policy
-- that permits you to receive email for the recipient of the bounced
-- email. For more information about sending authorization, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/sending-authorization.html Amazon SES Developer Guide>.
--
-- 'recipientDsnFields', 'bouncedRecipientInfo_recipientDsnFields' - Recipient-related DSN fields, most of which would normally be filled in
-- automatically when provided with a @BounceType@. You must provide either
-- this parameter or @BounceType@.
--
-- 'recipient', 'bouncedRecipientInfo_recipient' - The email address of the recipient of the bounced email.
newBouncedRecipientInfo ::
  -- | 'recipient'
  Prelude.Text ->
  BouncedRecipientInfo
newBouncedRecipientInfo :: Text -> BouncedRecipientInfo
newBouncedRecipientInfo Text
pRecipient_ =
  BouncedRecipientInfo'
    { $sel:bounceType:BouncedRecipientInfo' :: Maybe BounceType
bounceType = forall a. Maybe a
Prelude.Nothing,
      $sel:recipientArn:BouncedRecipientInfo' :: Maybe Text
recipientArn = forall a. Maybe a
Prelude.Nothing,
      $sel:recipientDsnFields:BouncedRecipientInfo' :: Maybe RecipientDsnFields
recipientDsnFields = forall a. Maybe a
Prelude.Nothing,
      $sel:recipient:BouncedRecipientInfo' :: Text
recipient = Text
pRecipient_
    }

-- | The reason for the bounce. You must provide either this parameter or
-- @RecipientDsnFields@.
bouncedRecipientInfo_bounceType :: Lens.Lens' BouncedRecipientInfo (Prelude.Maybe BounceType)
bouncedRecipientInfo_bounceType :: Lens' BouncedRecipientInfo (Maybe BounceType)
bouncedRecipientInfo_bounceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BouncedRecipientInfo' {Maybe BounceType
bounceType :: Maybe BounceType
$sel:bounceType:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe BounceType
bounceType} -> Maybe BounceType
bounceType) (\s :: BouncedRecipientInfo
s@BouncedRecipientInfo' {} Maybe BounceType
a -> BouncedRecipientInfo
s {$sel:bounceType:BouncedRecipientInfo' :: Maybe BounceType
bounceType = Maybe BounceType
a} :: BouncedRecipientInfo)

-- | This parameter is used only for sending authorization. It is the ARN of
-- the identity that is associated with the sending authorization policy
-- that permits you to receive email for the recipient of the bounced
-- email. For more information about sending authorization, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/sending-authorization.html Amazon SES Developer Guide>.
bouncedRecipientInfo_recipientArn :: Lens.Lens' BouncedRecipientInfo (Prelude.Maybe Prelude.Text)
bouncedRecipientInfo_recipientArn :: Lens' BouncedRecipientInfo (Maybe Text)
bouncedRecipientInfo_recipientArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BouncedRecipientInfo' {Maybe Text
recipientArn :: Maybe Text
$sel:recipientArn:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe Text
recipientArn} -> Maybe Text
recipientArn) (\s :: BouncedRecipientInfo
s@BouncedRecipientInfo' {} Maybe Text
a -> BouncedRecipientInfo
s {$sel:recipientArn:BouncedRecipientInfo' :: Maybe Text
recipientArn = Maybe Text
a} :: BouncedRecipientInfo)

-- | Recipient-related DSN fields, most of which would normally be filled in
-- automatically when provided with a @BounceType@. You must provide either
-- this parameter or @BounceType@.
bouncedRecipientInfo_recipientDsnFields :: Lens.Lens' BouncedRecipientInfo (Prelude.Maybe RecipientDsnFields)
bouncedRecipientInfo_recipientDsnFields :: Lens' BouncedRecipientInfo (Maybe RecipientDsnFields)
bouncedRecipientInfo_recipientDsnFields = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BouncedRecipientInfo' {Maybe RecipientDsnFields
recipientDsnFields :: Maybe RecipientDsnFields
$sel:recipientDsnFields:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe RecipientDsnFields
recipientDsnFields} -> Maybe RecipientDsnFields
recipientDsnFields) (\s :: BouncedRecipientInfo
s@BouncedRecipientInfo' {} Maybe RecipientDsnFields
a -> BouncedRecipientInfo
s {$sel:recipientDsnFields:BouncedRecipientInfo' :: Maybe RecipientDsnFields
recipientDsnFields = Maybe RecipientDsnFields
a} :: BouncedRecipientInfo)

-- | The email address of the recipient of the bounced email.
bouncedRecipientInfo_recipient :: Lens.Lens' BouncedRecipientInfo Prelude.Text
bouncedRecipientInfo_recipient :: Lens' BouncedRecipientInfo Text
bouncedRecipientInfo_recipient = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BouncedRecipientInfo' {Text
recipient :: Text
$sel:recipient:BouncedRecipientInfo' :: BouncedRecipientInfo -> Text
recipient} -> Text
recipient) (\s :: BouncedRecipientInfo
s@BouncedRecipientInfo' {} Text
a -> BouncedRecipientInfo
s {$sel:recipient:BouncedRecipientInfo' :: Text
recipient = Text
a} :: BouncedRecipientInfo)

instance Prelude.Hashable BouncedRecipientInfo where
  hashWithSalt :: Int -> BouncedRecipientInfo -> Int
hashWithSalt Int
_salt BouncedRecipientInfo' {Maybe Text
Maybe BounceType
Maybe RecipientDsnFields
Text
recipient :: Text
recipientDsnFields :: Maybe RecipientDsnFields
recipientArn :: Maybe Text
bounceType :: Maybe BounceType
$sel:recipient:BouncedRecipientInfo' :: BouncedRecipientInfo -> Text
$sel:recipientDsnFields:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe RecipientDsnFields
$sel:recipientArn:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe Text
$sel:bounceType:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe BounceType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BounceType
bounceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
recipientArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RecipientDsnFields
recipientDsnFields
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
recipient

instance Prelude.NFData BouncedRecipientInfo where
  rnf :: BouncedRecipientInfo -> ()
rnf BouncedRecipientInfo' {Maybe Text
Maybe BounceType
Maybe RecipientDsnFields
Text
recipient :: Text
recipientDsnFields :: Maybe RecipientDsnFields
recipientArn :: Maybe Text
bounceType :: Maybe BounceType
$sel:recipient:BouncedRecipientInfo' :: BouncedRecipientInfo -> Text
$sel:recipientDsnFields:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe RecipientDsnFields
$sel:recipientArn:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe Text
$sel:bounceType:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe BounceType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe BounceType
bounceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
recipientArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RecipientDsnFields
recipientDsnFields
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
recipient

instance Data.ToQuery BouncedRecipientInfo where
  toQuery :: BouncedRecipientInfo -> QueryString
toQuery BouncedRecipientInfo' {Maybe Text
Maybe BounceType
Maybe RecipientDsnFields
Text
recipient :: Text
recipientDsnFields :: Maybe RecipientDsnFields
recipientArn :: Maybe Text
bounceType :: Maybe BounceType
$sel:recipient:BouncedRecipientInfo' :: BouncedRecipientInfo -> Text
$sel:recipientDsnFields:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe RecipientDsnFields
$sel:recipientArn:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe Text
$sel:bounceType:BouncedRecipientInfo' :: BouncedRecipientInfo -> Maybe BounceType
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"BounceType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe BounceType
bounceType,
        ByteString
"RecipientArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
recipientArn,
        ByteString
"RecipientDsnFields" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe RecipientDsnFields
recipientDsnFields,
        ByteString
"Recipient" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
recipient
      ]