module Aws.Ses.Commands.SendRawEmail
( SendRawEmail(..)
, SendRawEmailResponse(..)
) where
import Data.Text (Text)
import Data.Typeable
import Control.Applicative
import qualified Data.ByteString.Char8 as BS
import Text.XML.Cursor (($//))
import qualified Data.Text.Encoding as T
import Prelude
import Aws.Core
import Aws.Ses.Core
data SendRawEmail =
SendRawEmail
{ SendRawEmail -> [EmailAddress]
srmDestinations :: [EmailAddress]
, SendRawEmail -> RawMessage
srmRawMessage :: RawMessage
, SendRawEmail -> Maybe Sender
srmSource :: Maybe Sender
}
deriving (SendRawEmail -> SendRawEmail -> Bool
(SendRawEmail -> SendRawEmail -> Bool)
-> (SendRawEmail -> SendRawEmail -> Bool) -> Eq SendRawEmail
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SendRawEmail -> SendRawEmail -> Bool
== :: SendRawEmail -> SendRawEmail -> Bool
$c/= :: SendRawEmail -> SendRawEmail -> Bool
/= :: SendRawEmail -> SendRawEmail -> Bool
Eq, Eq SendRawEmail
Eq SendRawEmail =>
(SendRawEmail -> SendRawEmail -> Ordering)
-> (SendRawEmail -> SendRawEmail -> Bool)
-> (SendRawEmail -> SendRawEmail -> Bool)
-> (SendRawEmail -> SendRawEmail -> Bool)
-> (SendRawEmail -> SendRawEmail -> Bool)
-> (SendRawEmail -> SendRawEmail -> SendRawEmail)
-> (SendRawEmail -> SendRawEmail -> SendRawEmail)
-> Ord SendRawEmail
SendRawEmail -> SendRawEmail -> Bool
SendRawEmail -> SendRawEmail -> Ordering
SendRawEmail -> SendRawEmail -> SendRawEmail
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SendRawEmail -> SendRawEmail -> Ordering
compare :: SendRawEmail -> SendRawEmail -> Ordering
$c< :: SendRawEmail -> SendRawEmail -> Bool
< :: SendRawEmail -> SendRawEmail -> Bool
$c<= :: SendRawEmail -> SendRawEmail -> Bool
<= :: SendRawEmail -> SendRawEmail -> Bool
$c> :: SendRawEmail -> SendRawEmail -> Bool
> :: SendRawEmail -> SendRawEmail -> Bool
$c>= :: SendRawEmail -> SendRawEmail -> Bool
>= :: SendRawEmail -> SendRawEmail -> Bool
$cmax :: SendRawEmail -> SendRawEmail -> SendRawEmail
max :: SendRawEmail -> SendRawEmail -> SendRawEmail
$cmin :: SendRawEmail -> SendRawEmail -> SendRawEmail
min :: SendRawEmail -> SendRawEmail -> SendRawEmail
Ord, Int -> SendRawEmail -> ShowS
[SendRawEmail] -> ShowS
SendRawEmail -> String
(Int -> SendRawEmail -> ShowS)
-> (SendRawEmail -> String)
-> ([SendRawEmail] -> ShowS)
-> Show SendRawEmail
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SendRawEmail -> ShowS
showsPrec :: Int -> SendRawEmail -> ShowS
$cshow :: SendRawEmail -> String
show :: SendRawEmail -> String
$cshowList :: [SendRawEmail] -> ShowS
showList :: [SendRawEmail] -> ShowS
Show, Typeable)
instance SignQuery SendRawEmail where
type ServiceConfiguration SendRawEmail = SesConfiguration
signQuery :: forall queryType.
SendRawEmail
-> ServiceConfiguration SendRawEmail queryType
-> SignatureData
-> SignedQuery
signQuery SendRawEmail {[EmailAddress]
Maybe Sender
RawMessage
srmDestinations :: SendRawEmail -> [EmailAddress]
srmRawMessage :: SendRawEmail -> RawMessage
srmSource :: SendRawEmail -> Maybe Sender
srmDestinations :: [EmailAddress]
srmRawMessage :: RawMessage
srmSource :: Maybe Sender
..} =
[(ByteString, ByteString)]
-> SesConfiguration queryType -> SignatureData -> SignedQuery
forall qt.
[(ByteString, ByteString)]
-> SesConfiguration qt -> SignatureData -> SignedQuery
sesSignQuery ([(ByteString, ByteString)]
-> SesConfiguration queryType -> SignatureData -> SignedQuery)
-> [(ByteString, ByteString)]
-> SesConfiguration queryType
-> SignatureData
-> SignedQuery
forall a b. (a -> b) -> a -> b
$ (ByteString
"Action", ByteString
"SendRawEmail") (ByteString, ByteString)
-> [(ByteString, ByteString)] -> [(ByteString, ByteString)]
forall a. a -> [a] -> [a]
:
[[(ByteString, ByteString)]] -> [(ByteString, ByteString)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [(ByteString, ByteString)]
destinations
, RawMessage -> [(ByteString, ByteString)]
forall a. SesAsQuery a => a -> [(ByteString, ByteString)]
sesAsQuery RawMessage
srmRawMessage
, Maybe Sender -> [(ByteString, ByteString)]
forall a. SesAsQuery a => a -> [(ByteString, ByteString)]
sesAsQuery Maybe Sender
srmSource
]
where
destinations :: [(ByteString, ByteString)]
destinations = [ByteString] -> [ByteString] -> [(ByteString, ByteString)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Int -> ByteString
enumMember (Int -> ByteString) -> [Int] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Int
1..] :: [Int]))
(EmailAddress -> ByteString
T.encodeUtf8 (EmailAddress -> ByteString) -> [EmailAddress] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [EmailAddress]
srmDestinations)
enumMember :: Int -> ByteString
enumMember = ByteString -> ByteString -> ByteString
BS.append ByteString
"Destinations.member." (ByteString -> ByteString)
-> (Int -> ByteString) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
BS.pack (String -> ByteString) -> (Int -> String) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show
data SendRawEmailResponse =
SendRawEmailResponse { SendRawEmailResponse -> EmailAddress
srmrMessageId :: Text }
deriving (SendRawEmailResponse -> SendRawEmailResponse -> Bool
(SendRawEmailResponse -> SendRawEmailResponse -> Bool)
-> (SendRawEmailResponse -> SendRawEmailResponse -> Bool)
-> Eq SendRawEmailResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
== :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
$c/= :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
/= :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
Eq, Eq SendRawEmailResponse
Eq SendRawEmailResponse =>
(SendRawEmailResponse -> SendRawEmailResponse -> Ordering)
-> (SendRawEmailResponse -> SendRawEmailResponse -> Bool)
-> (SendRawEmailResponse -> SendRawEmailResponse -> Bool)
-> (SendRawEmailResponse -> SendRawEmailResponse -> Bool)
-> (SendRawEmailResponse -> SendRawEmailResponse -> Bool)
-> (SendRawEmailResponse
-> SendRawEmailResponse -> SendRawEmailResponse)
-> (SendRawEmailResponse
-> SendRawEmailResponse -> SendRawEmailResponse)
-> Ord SendRawEmailResponse
SendRawEmailResponse -> SendRawEmailResponse -> Bool
SendRawEmailResponse -> SendRawEmailResponse -> Ordering
SendRawEmailResponse
-> SendRawEmailResponse -> SendRawEmailResponse
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SendRawEmailResponse -> SendRawEmailResponse -> Ordering
compare :: SendRawEmailResponse -> SendRawEmailResponse -> Ordering
$c< :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
< :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
$c<= :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
<= :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
$c> :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
> :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
$c>= :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
>= :: SendRawEmailResponse -> SendRawEmailResponse -> Bool
$cmax :: SendRawEmailResponse
-> SendRawEmailResponse -> SendRawEmailResponse
max :: SendRawEmailResponse
-> SendRawEmailResponse -> SendRawEmailResponse
$cmin :: SendRawEmailResponse
-> SendRawEmailResponse -> SendRawEmailResponse
min :: SendRawEmailResponse
-> SendRawEmailResponse -> SendRawEmailResponse
Ord, Int -> SendRawEmailResponse -> ShowS
[SendRawEmailResponse] -> ShowS
SendRawEmailResponse -> String
(Int -> SendRawEmailResponse -> ShowS)
-> (SendRawEmailResponse -> String)
-> ([SendRawEmailResponse] -> ShowS)
-> Show SendRawEmailResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SendRawEmailResponse -> ShowS
showsPrec :: Int -> SendRawEmailResponse -> ShowS
$cshow :: SendRawEmailResponse -> String
show :: SendRawEmailResponse -> String
$cshowList :: [SendRawEmailResponse] -> ShowS
showList :: [SendRawEmailResponse] -> ShowS
Show, Typeable)
instance ResponseConsumer SendRawEmail SendRawEmailResponse where
type ResponseMetadata SendRawEmailResponse = SesMetadata
responseConsumer :: Request
-> SendRawEmail
-> IORef (ResponseMetadata SendRawEmailResponse)
-> HTTPResponseConsumer SendRawEmailResponse
responseConsumer Request
_ SendRawEmail
_ =
(Cursor -> Response SesMetadata SendRawEmailResponse)
-> IORef SesMetadata -> HTTPResponseConsumer SendRawEmailResponse
forall a.
(Cursor -> Response SesMetadata a)
-> IORef SesMetadata -> HTTPResponseConsumer a
sesResponseConsumer ((Cursor -> Response SesMetadata SendRawEmailResponse)
-> IORef SesMetadata -> HTTPResponseConsumer SendRawEmailResponse)
-> (Cursor -> Response SesMetadata SendRawEmailResponse)
-> IORef SesMetadata
-> HTTPResponseConsumer SendRawEmailResponse
forall a b. (a -> b) -> a -> b
$ \Cursor
cursor -> do
EmailAddress
messageId <- String -> [EmailAddress] -> Response SesMetadata EmailAddress
forall (m :: * -> *) a. MonadThrow m => String -> [a] -> m a
force String
"MessageId not found" ([EmailAddress] -> Response SesMetadata EmailAddress)
-> [EmailAddress] -> Response SesMetadata EmailAddress
forall a b. (a -> b) -> a -> b
$ Cursor
cursor Cursor -> (Cursor -> [EmailAddress]) -> [EmailAddress]
forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$// EmailAddress -> Cursor -> [EmailAddress]
elContent EmailAddress
"MessageId"
SendRawEmailResponse -> Response SesMetadata SendRawEmailResponse
forall a. a -> Response SesMetadata a
forall (m :: * -> *) a. Monad m => a -> m a
return (EmailAddress -> SendRawEmailResponse
SendRawEmailResponse EmailAddress
messageId)
instance Transaction SendRawEmail SendRawEmailResponse where
instance AsMemoryResponse SendRawEmailResponse where
type MemoryResponse SendRawEmailResponse = SendRawEmailResponse
loadToMemory :: SendRawEmailResponse
-> ResourceT IO (MemoryResponse SendRawEmailResponse)
loadToMemory = SendRawEmailResponse
-> ResourceT IO (MemoryResponse SendRawEmailResponse)
SendRawEmailResponse -> ResourceT IO SendRawEmailResponse
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return