{-# 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.BulkEmailDestination
-- 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.BulkEmailDestination 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.Destination
import Amazonka.SES.Types.MessageTag

-- | An array that contains one or more Destinations, as well as the tags and
-- replacement data associated with each of those Destinations.
--
-- /See:/ 'newBulkEmailDestination' smart constructor.
data BulkEmailDestination = BulkEmailDestination'
  { -- | A list of tags, in the form of name\/value pairs, to apply to an email
    -- that you send using @SendBulkTemplatedEmail@. Tags correspond to
    -- characteristics of the email that you define, so that you can publish
    -- email sending events.
    BulkEmailDestination -> Maybe [MessageTag]
replacementTags :: Prelude.Maybe [MessageTag],
    -- | A list of replacement values to apply to the template. This parameter is
    -- a JSON object, typically consisting of key-value pairs in which the keys
    -- correspond to replacement tags in the email template.
    BulkEmailDestination -> Maybe Text
replacementTemplateData :: Prelude.Maybe Prelude.Text,
    BulkEmailDestination -> Destination
destination :: Destination
  }
  deriving (BulkEmailDestination -> BulkEmailDestination -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BulkEmailDestination -> BulkEmailDestination -> Bool
$c/= :: BulkEmailDestination -> BulkEmailDestination -> Bool
== :: BulkEmailDestination -> BulkEmailDestination -> Bool
$c== :: BulkEmailDestination -> BulkEmailDestination -> Bool
Prelude.Eq, ReadPrec [BulkEmailDestination]
ReadPrec BulkEmailDestination
Int -> ReadS BulkEmailDestination
ReadS [BulkEmailDestination]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BulkEmailDestination]
$creadListPrec :: ReadPrec [BulkEmailDestination]
readPrec :: ReadPrec BulkEmailDestination
$creadPrec :: ReadPrec BulkEmailDestination
readList :: ReadS [BulkEmailDestination]
$creadList :: ReadS [BulkEmailDestination]
readsPrec :: Int -> ReadS BulkEmailDestination
$creadsPrec :: Int -> ReadS BulkEmailDestination
Prelude.Read, Int -> BulkEmailDestination -> ShowS
[BulkEmailDestination] -> ShowS
BulkEmailDestination -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BulkEmailDestination] -> ShowS
$cshowList :: [BulkEmailDestination] -> ShowS
show :: BulkEmailDestination -> String
$cshow :: BulkEmailDestination -> String
showsPrec :: Int -> BulkEmailDestination -> ShowS
$cshowsPrec :: Int -> BulkEmailDestination -> ShowS
Prelude.Show, forall x. Rep BulkEmailDestination x -> BulkEmailDestination
forall x. BulkEmailDestination -> Rep BulkEmailDestination x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BulkEmailDestination x -> BulkEmailDestination
$cfrom :: forall x. BulkEmailDestination -> Rep BulkEmailDestination x
Prelude.Generic)

-- |
-- Create a value of 'BulkEmailDestination' 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:
--
-- 'replacementTags', 'bulkEmailDestination_replacementTags' - A list of tags, in the form of name\/value pairs, to apply to an email
-- that you send using @SendBulkTemplatedEmail@. Tags correspond to
-- characteristics of the email that you define, so that you can publish
-- email sending events.
--
-- 'replacementTemplateData', 'bulkEmailDestination_replacementTemplateData' - A list of replacement values to apply to the template. This parameter is
-- a JSON object, typically consisting of key-value pairs in which the keys
-- correspond to replacement tags in the email template.
--
-- 'destination', 'bulkEmailDestination_destination' - Undocumented member.
newBulkEmailDestination ::
  -- | 'destination'
  Destination ->
  BulkEmailDestination
newBulkEmailDestination :: Destination -> BulkEmailDestination
newBulkEmailDestination Destination
pDestination_ =
  BulkEmailDestination'
    { $sel:replacementTags:BulkEmailDestination' :: Maybe [MessageTag]
replacementTags =
        forall a. Maybe a
Prelude.Nothing,
      $sel:replacementTemplateData:BulkEmailDestination' :: Maybe Text
replacementTemplateData = forall a. Maybe a
Prelude.Nothing,
      $sel:destination:BulkEmailDestination' :: Destination
destination = Destination
pDestination_
    }

-- | A list of tags, in the form of name\/value pairs, to apply to an email
-- that you send using @SendBulkTemplatedEmail@. Tags correspond to
-- characteristics of the email that you define, so that you can publish
-- email sending events.
bulkEmailDestination_replacementTags :: Lens.Lens' BulkEmailDestination (Prelude.Maybe [MessageTag])
bulkEmailDestination_replacementTags :: Lens' BulkEmailDestination (Maybe [MessageTag])
bulkEmailDestination_replacementTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BulkEmailDestination' {Maybe [MessageTag]
replacementTags :: Maybe [MessageTag]
$sel:replacementTags:BulkEmailDestination' :: BulkEmailDestination -> Maybe [MessageTag]
replacementTags} -> Maybe [MessageTag]
replacementTags) (\s :: BulkEmailDestination
s@BulkEmailDestination' {} Maybe [MessageTag]
a -> BulkEmailDestination
s {$sel:replacementTags:BulkEmailDestination' :: Maybe [MessageTag]
replacementTags = Maybe [MessageTag]
a} :: BulkEmailDestination) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A list of replacement values to apply to the template. This parameter is
-- a JSON object, typically consisting of key-value pairs in which the keys
-- correspond to replacement tags in the email template.
bulkEmailDestination_replacementTemplateData :: Lens.Lens' BulkEmailDestination (Prelude.Maybe Prelude.Text)
bulkEmailDestination_replacementTemplateData :: Lens' BulkEmailDestination (Maybe Text)
bulkEmailDestination_replacementTemplateData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BulkEmailDestination' {Maybe Text
replacementTemplateData :: Maybe Text
$sel:replacementTemplateData:BulkEmailDestination' :: BulkEmailDestination -> Maybe Text
replacementTemplateData} -> Maybe Text
replacementTemplateData) (\s :: BulkEmailDestination
s@BulkEmailDestination' {} Maybe Text
a -> BulkEmailDestination
s {$sel:replacementTemplateData:BulkEmailDestination' :: Maybe Text
replacementTemplateData = Maybe Text
a} :: BulkEmailDestination)

-- | Undocumented member.
bulkEmailDestination_destination :: Lens.Lens' BulkEmailDestination Destination
bulkEmailDestination_destination :: Lens' BulkEmailDestination Destination
bulkEmailDestination_destination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BulkEmailDestination' {Destination
destination :: Destination
$sel:destination:BulkEmailDestination' :: BulkEmailDestination -> Destination
destination} -> Destination
destination) (\s :: BulkEmailDestination
s@BulkEmailDestination' {} Destination
a -> BulkEmailDestination
s {$sel:destination:BulkEmailDestination' :: Destination
destination = Destination
a} :: BulkEmailDestination)

instance Prelude.Hashable BulkEmailDestination where
  hashWithSalt :: Int -> BulkEmailDestination -> Int
hashWithSalt Int
_salt BulkEmailDestination' {Maybe [MessageTag]
Maybe Text
Destination
destination :: Destination
replacementTemplateData :: Maybe Text
replacementTags :: Maybe [MessageTag]
$sel:destination:BulkEmailDestination' :: BulkEmailDestination -> Destination
$sel:replacementTemplateData:BulkEmailDestination' :: BulkEmailDestination -> Maybe Text
$sel:replacementTags:BulkEmailDestination' :: BulkEmailDestination -> Maybe [MessageTag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [MessageTag]
replacementTags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
replacementTemplateData
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Destination
destination

instance Prelude.NFData BulkEmailDestination where
  rnf :: BulkEmailDestination -> ()
rnf BulkEmailDestination' {Maybe [MessageTag]
Maybe Text
Destination
destination :: Destination
replacementTemplateData :: Maybe Text
replacementTags :: Maybe [MessageTag]
$sel:destination:BulkEmailDestination' :: BulkEmailDestination -> Destination
$sel:replacementTemplateData:BulkEmailDestination' :: BulkEmailDestination -> Maybe Text
$sel:replacementTags:BulkEmailDestination' :: BulkEmailDestination -> Maybe [MessageTag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [MessageTag]
replacementTags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
replacementTemplateData
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Destination
destination

instance Data.ToQuery BulkEmailDestination where
  toQuery :: BulkEmailDestination -> QueryString
toQuery BulkEmailDestination' {Maybe [MessageTag]
Maybe Text
Destination
destination :: Destination
replacementTemplateData :: Maybe Text
replacementTags :: Maybe [MessageTag]
$sel:destination:BulkEmailDestination' :: BulkEmailDestination -> Destination
$sel:replacementTemplateData:BulkEmailDestination' :: BulkEmailDestination -> Maybe Text
$sel:replacementTags:BulkEmailDestination' :: BulkEmailDestination -> Maybe [MessageTag]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"ReplacementTags"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [MessageTag]
replacementTags
            ),
        ByteString
"ReplacementTemplateData"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
replacementTemplateData,
        ByteString
"Destination" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Destination
destination
      ]