module Stratosphere.SES.EmailIdentity (
module Exports, EmailIdentity(..), mkEmailIdentity
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.SES.EmailIdentity.ConfigurationSetAttributesProperty as Exports
import {-# SOURCE #-} Stratosphere.SES.EmailIdentity.DkimAttributesProperty as Exports
import {-# SOURCE #-} Stratosphere.SES.EmailIdentity.DkimSigningAttributesProperty as Exports
import {-# SOURCE #-} Stratosphere.SES.EmailIdentity.FeedbackAttributesProperty as Exports
import {-# SOURCE #-} Stratosphere.SES.EmailIdentity.MailFromAttributesProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data EmailIdentity
=
EmailIdentity {EmailIdentity -> ()
haddock_workaround_ :: (),
EmailIdentity -> Maybe ConfigurationSetAttributesProperty
configurationSetAttributes :: (Prelude.Maybe ConfigurationSetAttributesProperty),
EmailIdentity -> Maybe DkimAttributesProperty
dkimAttributes :: (Prelude.Maybe DkimAttributesProperty),
EmailIdentity -> Maybe DkimSigningAttributesProperty
dkimSigningAttributes :: (Prelude.Maybe DkimSigningAttributesProperty),
EmailIdentity -> Value Text
emailIdentity :: (Value Prelude.Text),
EmailIdentity -> Maybe FeedbackAttributesProperty
feedbackAttributes :: (Prelude.Maybe FeedbackAttributesProperty),
EmailIdentity -> Maybe MailFromAttributesProperty
mailFromAttributes :: (Prelude.Maybe MailFromAttributesProperty),
EmailIdentity -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag])}
deriving stock (EmailIdentity -> EmailIdentity -> Bool
(EmailIdentity -> EmailIdentity -> Bool)
-> (EmailIdentity -> EmailIdentity -> Bool) -> Eq EmailIdentity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EmailIdentity -> EmailIdentity -> Bool
== :: EmailIdentity -> EmailIdentity -> Bool
$c/= :: EmailIdentity -> EmailIdentity -> Bool
/= :: EmailIdentity -> EmailIdentity -> Bool
Prelude.Eq, Int -> EmailIdentity -> ShowS
[EmailIdentity] -> ShowS
EmailIdentity -> String
(Int -> EmailIdentity -> ShowS)
-> (EmailIdentity -> String)
-> ([EmailIdentity] -> ShowS)
-> Show EmailIdentity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EmailIdentity -> ShowS
showsPrec :: Int -> EmailIdentity -> ShowS
$cshow :: EmailIdentity -> String
show :: EmailIdentity -> String
$cshowList :: [EmailIdentity] -> ShowS
showList :: [EmailIdentity] -> ShowS
Prelude.Show)
mkEmailIdentity :: Value Prelude.Text -> EmailIdentity
mkEmailIdentity :: Value Text -> EmailIdentity
mkEmailIdentity Value Text
emailIdentity
= EmailIdentity
{haddock_workaround_ :: ()
haddock_workaround_ = (), emailIdentity :: Value Text
emailIdentity = Value Text
emailIdentity,
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
configurationSetAttributes = Maybe ConfigurationSetAttributesProperty
forall a. Maybe a
Prelude.Nothing,
dkimAttributes :: Maybe DkimAttributesProperty
dkimAttributes = Maybe DkimAttributesProperty
forall a. Maybe a
Prelude.Nothing,
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
dkimSigningAttributes = Maybe DkimSigningAttributesProperty
forall a. Maybe a
Prelude.Nothing,
feedbackAttributes :: Maybe FeedbackAttributesProperty
feedbackAttributes = Maybe FeedbackAttributesProperty
forall a. Maybe a
Prelude.Nothing,
mailFromAttributes :: Maybe MailFromAttributesProperty
mailFromAttributes = Maybe MailFromAttributesProperty
forall a. Maybe a
Prelude.Nothing, tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties EmailIdentity where
toResourceProperties :: EmailIdentity -> ResourceProperties
toResourceProperties EmailIdentity {Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: EmailIdentity -> ()
configurationSetAttributes :: EmailIdentity -> Maybe ConfigurationSetAttributesProperty
dkimAttributes :: EmailIdentity -> Maybe DkimAttributesProperty
dkimSigningAttributes :: EmailIdentity -> Maybe DkimSigningAttributesProperty
emailIdentity :: EmailIdentity -> Value Text
feedbackAttributes :: EmailIdentity -> Maybe FeedbackAttributesProperty
mailFromAttributes :: EmailIdentity -> Maybe MailFromAttributesProperty
tags :: EmailIdentity -> Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::SES::EmailIdentity", supportsTags :: Bool
supportsTags = Bool
Prelude.True,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"EmailIdentity" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
emailIdentity]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> ConfigurationSetAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConfigurationSetAttributes"
(ConfigurationSetAttributesProperty -> (Key, Value))
-> Maybe ConfigurationSetAttributesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConfigurationSetAttributesProperty
configurationSetAttributes,
Key -> DkimAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DkimAttributes" (DkimAttributesProperty -> (Key, Value))
-> Maybe DkimAttributesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DkimAttributesProperty
dkimAttributes,
Key -> DkimSigningAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DkimSigningAttributes"
(DkimSigningAttributesProperty -> (Key, Value))
-> Maybe DkimSigningAttributesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DkimSigningAttributesProperty
dkimSigningAttributes,
Key -> FeedbackAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FeedbackAttributes" (FeedbackAttributesProperty -> (Key, Value))
-> Maybe FeedbackAttributesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FeedbackAttributesProperty
feedbackAttributes,
Key -> MailFromAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MailFromAttributes" (MailFromAttributesProperty -> (Key, Value))
-> Maybe MailFromAttributesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe MailFromAttributesProperty
mailFromAttributes,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags]))}
instance JSON.ToJSON EmailIdentity where
toJSON :: EmailIdentity -> Value
toJSON EmailIdentity {Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: EmailIdentity -> ()
configurationSetAttributes :: EmailIdentity -> Maybe ConfigurationSetAttributesProperty
dkimAttributes :: EmailIdentity -> Maybe DkimAttributesProperty
dkimSigningAttributes :: EmailIdentity -> Maybe DkimSigningAttributesProperty
emailIdentity :: EmailIdentity -> Value Text
feedbackAttributes :: EmailIdentity -> Maybe FeedbackAttributesProperty
mailFromAttributes :: EmailIdentity -> Maybe MailFromAttributesProperty
tags :: EmailIdentity -> Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"EmailIdentity" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
emailIdentity]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> ConfigurationSetAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConfigurationSetAttributes"
(ConfigurationSetAttributesProperty -> (Key, Value))
-> Maybe ConfigurationSetAttributesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConfigurationSetAttributesProperty
configurationSetAttributes,
Key -> DkimAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DkimAttributes" (DkimAttributesProperty -> (Key, Value))
-> Maybe DkimAttributesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DkimAttributesProperty
dkimAttributes,
Key -> DkimSigningAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DkimSigningAttributes"
(DkimSigningAttributesProperty -> (Key, Value))
-> Maybe DkimSigningAttributesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DkimSigningAttributesProperty
dkimSigningAttributes,
Key -> FeedbackAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FeedbackAttributes" (FeedbackAttributesProperty -> (Key, Value))
-> Maybe FeedbackAttributesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FeedbackAttributesProperty
feedbackAttributes,
Key -> MailFromAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MailFromAttributes" (MailFromAttributesProperty -> (Key, Value))
-> Maybe MailFromAttributesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe MailFromAttributesProperty
mailFromAttributes,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags])))
instance Property "ConfigurationSetAttributes" EmailIdentity where
type PropertyType "ConfigurationSetAttributes" EmailIdentity = ConfigurationSetAttributesProperty
set :: PropertyType "ConfigurationSetAttributes" EmailIdentity
-> EmailIdentity -> EmailIdentity
set PropertyType "ConfigurationSetAttributes" EmailIdentity
newValue EmailIdentity {Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: EmailIdentity -> ()
configurationSetAttributes :: EmailIdentity -> Maybe ConfigurationSetAttributesProperty
dkimAttributes :: EmailIdentity -> Maybe DkimAttributesProperty
dkimSigningAttributes :: EmailIdentity -> Maybe DkimSigningAttributesProperty
emailIdentity :: EmailIdentity -> Value Text
feedbackAttributes :: EmailIdentity -> Maybe FeedbackAttributesProperty
mailFromAttributes :: EmailIdentity -> Maybe MailFromAttributesProperty
tags :: EmailIdentity -> Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
= EmailIdentity
{configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
configurationSetAttributes = ConfigurationSetAttributesProperty
-> Maybe ConfigurationSetAttributesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ConfigurationSetAttributes" EmailIdentity
ConfigurationSetAttributesProperty
newValue, Maybe [Tag]
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: ()
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
instance Property "DkimAttributes" EmailIdentity where
type PropertyType "DkimAttributes" EmailIdentity = DkimAttributesProperty
set :: PropertyType "DkimAttributes" EmailIdentity
-> EmailIdentity -> EmailIdentity
set PropertyType "DkimAttributes" EmailIdentity
newValue EmailIdentity {Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: EmailIdentity -> ()
configurationSetAttributes :: EmailIdentity -> Maybe ConfigurationSetAttributesProperty
dkimAttributes :: EmailIdentity -> Maybe DkimAttributesProperty
dkimSigningAttributes :: EmailIdentity -> Maybe DkimSigningAttributesProperty
emailIdentity :: EmailIdentity -> Value Text
feedbackAttributes :: EmailIdentity -> Maybe FeedbackAttributesProperty
mailFromAttributes :: EmailIdentity -> Maybe MailFromAttributesProperty
tags :: EmailIdentity -> Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
= EmailIdentity {dkimAttributes :: Maybe DkimAttributesProperty
dkimAttributes = DkimAttributesProperty -> Maybe DkimAttributesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DkimAttributes" EmailIdentity
DkimAttributesProperty
newValue, Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
instance Property "DkimSigningAttributes" EmailIdentity where
type PropertyType "DkimSigningAttributes" EmailIdentity = DkimSigningAttributesProperty
set :: PropertyType "DkimSigningAttributes" EmailIdentity
-> EmailIdentity -> EmailIdentity
set PropertyType "DkimSigningAttributes" EmailIdentity
newValue EmailIdentity {Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: EmailIdentity -> ()
configurationSetAttributes :: EmailIdentity -> Maybe ConfigurationSetAttributesProperty
dkimAttributes :: EmailIdentity -> Maybe DkimAttributesProperty
dkimSigningAttributes :: EmailIdentity -> Maybe DkimSigningAttributesProperty
emailIdentity :: EmailIdentity -> Value Text
feedbackAttributes :: EmailIdentity -> Maybe FeedbackAttributesProperty
mailFromAttributes :: EmailIdentity -> Maybe MailFromAttributesProperty
tags :: EmailIdentity -> Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
= EmailIdentity {dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
dkimSigningAttributes = DkimSigningAttributesProperty
-> Maybe DkimSigningAttributesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DkimSigningAttributes" EmailIdentity
DkimSigningAttributesProperty
newValue, Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
instance Property "EmailIdentity" EmailIdentity where
type PropertyType "EmailIdentity" EmailIdentity = Value Prelude.Text
set :: PropertyType "EmailIdentity" EmailIdentity
-> EmailIdentity -> EmailIdentity
set PropertyType "EmailIdentity" EmailIdentity
newValue EmailIdentity {Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: EmailIdentity -> ()
configurationSetAttributes :: EmailIdentity -> Maybe ConfigurationSetAttributesProperty
dkimAttributes :: EmailIdentity -> Maybe DkimAttributesProperty
dkimSigningAttributes :: EmailIdentity -> Maybe DkimSigningAttributesProperty
emailIdentity :: EmailIdentity -> Value Text
feedbackAttributes :: EmailIdentity -> Maybe FeedbackAttributesProperty
mailFromAttributes :: EmailIdentity -> Maybe MailFromAttributesProperty
tags :: EmailIdentity -> Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
= EmailIdentity {emailIdentity :: Value Text
emailIdentity = PropertyType "EmailIdentity" EmailIdentity
Value Text
newValue, Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
instance Property "FeedbackAttributes" EmailIdentity where
type PropertyType "FeedbackAttributes" EmailIdentity = FeedbackAttributesProperty
set :: PropertyType "FeedbackAttributes" EmailIdentity
-> EmailIdentity -> EmailIdentity
set PropertyType "FeedbackAttributes" EmailIdentity
newValue EmailIdentity {Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: EmailIdentity -> ()
configurationSetAttributes :: EmailIdentity -> Maybe ConfigurationSetAttributesProperty
dkimAttributes :: EmailIdentity -> Maybe DkimAttributesProperty
dkimSigningAttributes :: EmailIdentity -> Maybe DkimSigningAttributesProperty
emailIdentity :: EmailIdentity -> Value Text
feedbackAttributes :: EmailIdentity -> Maybe FeedbackAttributesProperty
mailFromAttributes :: EmailIdentity -> Maybe MailFromAttributesProperty
tags :: EmailIdentity -> Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
= EmailIdentity {feedbackAttributes :: Maybe FeedbackAttributesProperty
feedbackAttributes = FeedbackAttributesProperty -> Maybe FeedbackAttributesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "FeedbackAttributes" EmailIdentity
FeedbackAttributesProperty
newValue, Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
instance Property "MailFromAttributes" EmailIdentity where
type PropertyType "MailFromAttributes" EmailIdentity = MailFromAttributesProperty
set :: PropertyType "MailFromAttributes" EmailIdentity
-> EmailIdentity -> EmailIdentity
set PropertyType "MailFromAttributes" EmailIdentity
newValue EmailIdentity {Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: EmailIdentity -> ()
configurationSetAttributes :: EmailIdentity -> Maybe ConfigurationSetAttributesProperty
dkimAttributes :: EmailIdentity -> Maybe DkimAttributesProperty
dkimSigningAttributes :: EmailIdentity -> Maybe DkimSigningAttributesProperty
emailIdentity :: EmailIdentity -> Value Text
feedbackAttributes :: EmailIdentity -> Maybe FeedbackAttributesProperty
mailFromAttributes :: EmailIdentity -> Maybe MailFromAttributesProperty
tags :: EmailIdentity -> Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
= EmailIdentity {mailFromAttributes :: Maybe MailFromAttributesProperty
mailFromAttributes = MailFromAttributesProperty -> Maybe MailFromAttributesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MailFromAttributes" EmailIdentity
MailFromAttributesProperty
newValue, Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
()
Value Text
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
tags :: Maybe [Tag]
..}
instance Property "Tags" EmailIdentity where
type PropertyType "Tags" EmailIdentity = [Tag]
set :: PropertyType "Tags" EmailIdentity -> EmailIdentity -> EmailIdentity
set PropertyType "Tags" EmailIdentity
newValue EmailIdentity {Maybe [Tag]
Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: EmailIdentity -> ()
configurationSetAttributes :: EmailIdentity -> Maybe ConfigurationSetAttributesProperty
dkimAttributes :: EmailIdentity -> Maybe DkimAttributesProperty
dkimSigningAttributes :: EmailIdentity -> Maybe DkimSigningAttributesProperty
emailIdentity :: EmailIdentity -> Value Text
feedbackAttributes :: EmailIdentity -> Maybe FeedbackAttributesProperty
mailFromAttributes :: EmailIdentity -> Maybe MailFromAttributesProperty
tags :: EmailIdentity -> Maybe [Tag]
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
tags :: Maybe [Tag]
..}
= EmailIdentity {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" EmailIdentity
newValue, Maybe ConfigurationSetAttributesProperty
Maybe DkimAttributesProperty
Maybe DkimSigningAttributesProperty
Maybe FeedbackAttributesProperty
Maybe MailFromAttributesProperty
()
Value Text
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
haddock_workaround_ :: ()
configurationSetAttributes :: Maybe ConfigurationSetAttributesProperty
dkimAttributes :: Maybe DkimAttributesProperty
dkimSigningAttributes :: Maybe DkimSigningAttributesProperty
emailIdentity :: Value Text
feedbackAttributes :: Maybe FeedbackAttributesProperty
mailFromAttributes :: Maybe MailFromAttributesProperty
..}