{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Network.SendGridV3.Api where
import Control.Exception ( try )
import Control.Lens hiding ( from
, to
, (.=)
)
import Data.Aeson
import Data.Aeson.TH
import Data.ByteString.Lazy ( ByteString )
import Data.Char ( toLower )
import Data.List.NonEmpty ( NonEmpty )
import Data.Semigroup ( (<>) )
import qualified Data.Text as T
import Data.Text.Encoding
import Network.HTTP.Client ( HttpException )
import Network.SendGridV3.JSON ( unPrefix )
import Network.Wreq hiding ( Options )
sendGridAPI :: T.Text
sendGridAPI :: Text
sendGridAPI = Text
"https://api.sendgrid.com/v3/mail/send"
data ApiKey = ApiKey { ApiKey -> Text
_apiKey :: T.Text } deriving (Int -> ApiKey -> ShowS
[ApiKey] -> ShowS
ApiKey -> String
(Int -> ApiKey -> ShowS)
-> (ApiKey -> String) -> ([ApiKey] -> ShowS) -> Show ApiKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApiKey] -> ShowS
$cshowList :: [ApiKey] -> ShowS
show :: ApiKey -> String
$cshow :: ApiKey -> String
showsPrec :: Int -> ApiKey -> ShowS
$cshowsPrec :: Int -> ApiKey -> ShowS
Show, ApiKey -> ApiKey -> Bool
(ApiKey -> ApiKey -> Bool)
-> (ApiKey -> ApiKey -> Bool) -> Eq ApiKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApiKey -> ApiKey -> Bool
$c/= :: ApiKey -> ApiKey -> Bool
== :: ApiKey -> ApiKey -> Bool
$c== :: ApiKey -> ApiKey -> Bool
Eq)
data MailAddress = MailAddress
{
MailAddress -> Text
_mailAddressEmail :: T.Text
, MailAddress -> Text
_mailAddressName :: T.Text
} deriving (Int -> MailAddress -> ShowS
[MailAddress] -> ShowS
MailAddress -> String
(Int -> MailAddress -> ShowS)
-> (MailAddress -> String)
-> ([MailAddress] -> ShowS)
-> Show MailAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MailAddress] -> ShowS
$cshowList :: [MailAddress] -> ShowS
show :: MailAddress -> String
$cshow :: MailAddress -> String
showsPrec :: Int -> MailAddress -> ShowS
$cshowsPrec :: Int -> MailAddress -> ShowS
Show, MailAddress -> MailAddress -> Bool
(MailAddress -> MailAddress -> Bool)
-> (MailAddress -> MailAddress -> Bool) -> Eq MailAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MailAddress -> MailAddress -> Bool
$c/= :: MailAddress -> MailAddress -> Bool
== :: MailAddress -> MailAddress -> Bool
$c== :: MailAddress -> MailAddress -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_mailAddress"
, constructorTagModifier = map toLower }) ''MailAddress)
data MailContent = MailContent
{
MailContent -> Text
_mailContentType :: T.Text
, MailContent -> Text
_mailContentValue :: T.Text
} deriving (Int -> MailContent -> ShowS
[MailContent] -> ShowS
MailContent -> String
(Int -> MailContent -> ShowS)
-> (MailContent -> String)
-> ([MailContent] -> ShowS)
-> Show MailContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MailContent] -> ShowS
$cshowList :: [MailContent] -> ShowS
show :: MailContent -> String
$cshow :: MailContent -> String
showsPrec :: Int -> MailContent -> ShowS
$cshowsPrec :: Int -> MailContent -> ShowS
Show, MailContent -> MailContent -> Bool
(MailContent -> MailContent -> Bool)
-> (MailContent -> MailContent -> Bool) -> Eq MailContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MailContent -> MailContent -> Bool
$c/= :: MailContent -> MailContent -> Bool
== :: MailContent -> MailContent -> Bool
$c== :: MailContent -> MailContent -> Bool
Eq)
mailContentText :: T.Text -> MailContent
mailContentText :: Text -> MailContent
mailContentText Text
txt = Text -> Text -> MailContent
MailContent Text
"text/plain" Text
txt
mailContentHtml :: T.Text -> MailContent
mailContentHtml :: Text -> MailContent
mailContentHtml Text
html = Text -> Text -> MailContent
MailContent Text
"text/html" Text
html
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_mailContent"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''MailContent)
data Personalization = Personalization
{
Personalization -> NonEmpty MailAddress
_personalizationTo :: NonEmpty MailAddress
, Personalization -> Maybe [MailAddress]
_personalizationCc :: Maybe [MailAddress]
, Personalization -> Maybe [MailAddress]
_personalizationBcc :: Maybe [MailAddress]
, Personalization -> Maybe Text
_personalizationSubject :: Maybe T.Text
, :: Maybe [(T.Text, T.Text)]
, Personalization -> Maybe Object
_personalizationSubstitutions :: Maybe Object
, Personalization -> Maybe Int
_personalizationSendAt :: Maybe Int
, Personalization -> Maybe Value
_personalizationDynamicTemplateData :: Maybe Value
} deriving (Int -> Personalization -> ShowS
[Personalization] -> ShowS
Personalization -> String
(Int -> Personalization -> ShowS)
-> (Personalization -> String)
-> ([Personalization] -> ShowS)
-> Show Personalization
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Personalization] -> ShowS
$cshowList :: [Personalization] -> ShowS
show :: Personalization -> String
$cshow :: Personalization -> String
showsPrec :: Int -> Personalization -> ShowS
$cshowsPrec :: Int -> Personalization -> ShowS
Show, Personalization -> Personalization -> Bool
(Personalization -> Personalization -> Bool)
-> (Personalization -> Personalization -> Bool)
-> Eq Personalization
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Personalization -> Personalization -> Bool
$c/= :: Personalization -> Personalization -> Bool
== :: Personalization -> Personalization -> Bool
$c== :: Personalization -> Personalization -> Bool
Eq)
personalization :: NonEmpty MailAddress -> Personalization
personalization :: NonEmpty MailAddress -> Personalization
personalization NonEmpty MailAddress
to = Personalization :: NonEmpty MailAddress
-> Maybe [MailAddress]
-> Maybe [MailAddress]
-> Maybe Text
-> Maybe [(Text, Text)]
-> Maybe Object
-> Maybe Int
-> Maybe Value
-> Personalization
Personalization
{ _personalizationTo :: NonEmpty MailAddress
_personalizationTo = NonEmpty MailAddress
to
, _personalizationCc :: Maybe [MailAddress]
_personalizationCc = Maybe [MailAddress]
forall a. Maybe a
Nothing
, _personalizationBcc :: Maybe [MailAddress]
_personalizationBcc = Maybe [MailAddress]
forall a. Maybe a
Nothing
, _personalizationSubject :: Maybe Text
_personalizationSubject = Maybe Text
forall a. Maybe a
Nothing
, _personalizationHeaders :: Maybe [(Text, Text)]
_personalizationHeaders = Maybe [(Text, Text)]
forall a. Maybe a
Nothing
, _personalizationSubstitutions :: Maybe Object
_personalizationSubstitutions = Maybe Object
forall a. Maybe a
Nothing
, _personalizationSendAt :: Maybe Int
_personalizationSendAt = Maybe Int
forall a. Maybe a
Nothing
, _personalizationDynamicTemplateData :: Maybe Value
_personalizationDynamicTemplateData = Maybe Value
forall a. Maybe a
Nothing
}
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_personalization"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''Personalization)
data Disposition =
Inline
| Attachment
deriving (Int -> Disposition -> ShowS
[Disposition] -> ShowS
Disposition -> String
(Int -> Disposition -> ShowS)
-> (Disposition -> String)
-> ([Disposition] -> ShowS)
-> Show Disposition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Disposition] -> ShowS
$cshowList :: [Disposition] -> ShowS
show :: Disposition -> String
$cshow :: Disposition -> String
showsPrec :: Int -> Disposition -> ShowS
$cshowsPrec :: Int -> Disposition -> ShowS
Show, Disposition -> Disposition -> Bool
(Disposition -> Disposition -> Bool)
-> (Disposition -> Disposition -> Bool) -> Eq Disposition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Disposition -> Disposition -> Bool
$c/= :: Disposition -> Disposition -> Bool
== :: Disposition -> Disposition -> Bool
$c== :: Disposition -> Disposition -> Bool
Eq)
instance ToJSON Disposition where
toJSON :: Disposition -> Value
toJSON Disposition
Inline = Value
"inline"
toJSON Disposition
Attachment = Value
"attachment"
data MailAttachment = MailAttachment
{
MailAttachment -> Text
_mailAttachmentContent :: T.Text
, MailAttachment -> Maybe Text
_mailAttachmentType :: Maybe T.Text
, MailAttachment -> Text
_mailAttachmentFilename :: T.Text
, MailAttachment -> Maybe Disposition
_mailAttachmentDisposition :: Maybe Disposition
, MailAttachment -> Text
_mailAttachmentContentId :: T.Text
} deriving (Int -> MailAttachment -> ShowS
[MailAttachment] -> ShowS
MailAttachment -> String
(Int -> MailAttachment -> ShowS)
-> (MailAttachment -> String)
-> ([MailAttachment] -> ShowS)
-> Show MailAttachment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MailAttachment] -> ShowS
$cshowList :: [MailAttachment] -> ShowS
show :: MailAttachment -> String
$cshow :: MailAttachment -> String
showsPrec :: Int -> MailAttachment -> ShowS
$cshowsPrec :: Int -> MailAttachment -> ShowS
Show, MailAttachment -> MailAttachment -> Bool
(MailAttachment -> MailAttachment -> Bool)
-> (MailAttachment -> MailAttachment -> Bool) -> Eq MailAttachment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MailAttachment -> MailAttachment -> Bool
$c/= :: MailAttachment -> MailAttachment -> Bool
== :: MailAttachment -> MailAttachment -> Bool
$c== :: MailAttachment -> MailAttachment -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_mailAttachment"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''MailAttachment)
data Asm = Asm
{
Asm -> Int
_asmGroupId :: Int
, Asm -> Maybe [Int]
_asmGroupsToDisplay :: Maybe [Int]
} deriving (Int -> Asm -> ShowS
[Asm] -> ShowS
Asm -> String
(Int -> Asm -> ShowS)
-> (Asm -> String) -> ([Asm] -> ShowS) -> Show Asm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Asm] -> ShowS
$cshowList :: [Asm] -> ShowS
show :: Asm -> String
$cshow :: Asm -> String
showsPrec :: Int -> Asm -> ShowS
$cshowsPrec :: Int -> Asm -> ShowS
Show, Asm -> Asm -> Bool
(Asm -> Asm -> Bool) -> (Asm -> Asm -> Bool) -> Eq Asm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Asm -> Asm -> Bool
$c/= :: Asm -> Asm -> Bool
== :: Asm -> Asm -> Bool
$c== :: Asm -> Asm -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_asm"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''Asm)
data Bcc = Bcc
{
Bcc -> Maybe Bool
_bccEnable :: Maybe Bool
, Bcc -> Maybe Text
_bccEmail :: Maybe T.Text
} deriving (Int -> Bcc -> ShowS
[Bcc] -> ShowS
Bcc -> String
(Int -> Bcc -> ShowS)
-> (Bcc -> String) -> ([Bcc] -> ShowS) -> Show Bcc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bcc] -> ShowS
$cshowList :: [Bcc] -> ShowS
show :: Bcc -> String
$cshow :: Bcc -> String
showsPrec :: Int -> Bcc -> ShowS
$cshowsPrec :: Int -> Bcc -> ShowS
Show, Bcc -> Bcc -> Bool
(Bcc -> Bcc -> Bool) -> (Bcc -> Bcc -> Bool) -> Eq Bcc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bcc -> Bcc -> Bool
$c/= :: Bcc -> Bcc -> Bool
== :: Bcc -> Bcc -> Bool
$c== :: Bcc -> Bcc -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_bcc"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''Bcc)
data BypassListManagement = BypassListManagement
{
BypassListManagement -> Bool
_bypassListManagementEnable :: Bool
} deriving (Int -> BypassListManagement -> ShowS
[BypassListManagement] -> ShowS
BypassListManagement -> String
(Int -> BypassListManagement -> ShowS)
-> (BypassListManagement -> String)
-> ([BypassListManagement] -> ShowS)
-> Show BypassListManagement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BypassListManagement] -> ShowS
$cshowList :: [BypassListManagement] -> ShowS
show :: BypassListManagement -> String
$cshow :: BypassListManagement -> String
showsPrec :: Int -> BypassListManagement -> ShowS
$cshowsPrec :: Int -> BypassListManagement -> ShowS
Show, BypassListManagement -> BypassListManagement -> Bool
(BypassListManagement -> BypassListManagement -> Bool)
-> (BypassListManagement -> BypassListManagement -> Bool)
-> Eq BypassListManagement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BypassListManagement -> BypassListManagement -> Bool
$c/= :: BypassListManagement -> BypassListManagement -> Bool
== :: BypassListManagement -> BypassListManagement -> Bool
$c== :: BypassListManagement -> BypassListManagement -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_bypassListManagement"
, constructorTagModifier = map toLower }) ''BypassListManagement)
data =
{
:: Maybe Bool
, :: Maybe T.Text
, :: Maybe T.Text
} deriving (Int -> Footer -> ShowS
[Footer] -> ShowS
Footer -> String
(Int -> Footer -> ShowS)
-> (Footer -> String) -> ([Footer] -> ShowS) -> Show Footer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Footer] -> ShowS
$cshowList :: [Footer] -> ShowS
show :: Footer -> String
$cshow :: Footer -> String
showsPrec :: Int -> Footer -> ShowS
$cshowsPrec :: Int -> Footer -> ShowS
Show, Footer -> Footer -> Bool
(Footer -> Footer -> Bool)
-> (Footer -> Footer -> Bool) -> Eq Footer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Footer -> Footer -> Bool
$c/= :: Footer -> Footer -> Bool
== :: Footer -> Footer -> Bool
$c== :: Footer -> Footer -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_footer"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''Footer)
data SandboxMode = SandboxMode
{
SandboxMode -> Bool
_sandboxModeEnable :: Bool
} deriving (Int -> SandboxMode -> ShowS
[SandboxMode] -> ShowS
SandboxMode -> String
(Int -> SandboxMode -> ShowS)
-> (SandboxMode -> String)
-> ([SandboxMode] -> ShowS)
-> Show SandboxMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SandboxMode] -> ShowS
$cshowList :: [SandboxMode] -> ShowS
show :: SandboxMode -> String
$cshow :: SandboxMode -> String
showsPrec :: Int -> SandboxMode -> ShowS
$cshowsPrec :: Int -> SandboxMode -> ShowS
Show, SandboxMode -> SandboxMode -> Bool
(SandboxMode -> SandboxMode -> Bool)
-> (SandboxMode -> SandboxMode -> Bool) -> Eq SandboxMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SandboxMode -> SandboxMode -> Bool
$c/= :: SandboxMode -> SandboxMode -> Bool
== :: SandboxMode -> SandboxMode -> Bool
$c== :: SandboxMode -> SandboxMode -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_sandboxMode"
, constructorTagModifier = map toLower }) ''SandboxMode)
data SpamCheck = SpamCheck
{
SpamCheck -> Maybe Bool
_spamCheckEnable :: Maybe Bool
, SpamCheck -> Maybe Int
_spamCheckThreshold :: Maybe Int
, SpamCheck -> Maybe Text
_spamCheckPostToUrl :: Maybe T.Text
} deriving (Int -> SpamCheck -> ShowS
[SpamCheck] -> ShowS
SpamCheck -> String
(Int -> SpamCheck -> ShowS)
-> (SpamCheck -> String)
-> ([SpamCheck] -> ShowS)
-> Show SpamCheck
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpamCheck] -> ShowS
$cshowList :: [SpamCheck] -> ShowS
show :: SpamCheck -> String
$cshow :: SpamCheck -> String
showsPrec :: Int -> SpamCheck -> ShowS
$cshowsPrec :: Int -> SpamCheck -> ShowS
Show, SpamCheck -> SpamCheck -> Bool
(SpamCheck -> SpamCheck -> Bool)
-> (SpamCheck -> SpamCheck -> Bool) -> Eq SpamCheck
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpamCheck -> SpamCheck -> Bool
$c/= :: SpamCheck -> SpamCheck -> Bool
== :: SpamCheck -> SpamCheck -> Bool
$c== :: SpamCheck -> SpamCheck -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_spamCheck"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''SpamCheck)
data ClickTracking = ClickTracking
{
ClickTracking -> Maybe Bool
_clickTrackingEnable :: Maybe Bool
, ClickTracking -> Maybe Bool
_clickTrackingEnableText :: Maybe Bool
} deriving (Int -> ClickTracking -> ShowS
[ClickTracking] -> ShowS
ClickTracking -> String
(Int -> ClickTracking -> ShowS)
-> (ClickTracking -> String)
-> ([ClickTracking] -> ShowS)
-> Show ClickTracking
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClickTracking] -> ShowS
$cshowList :: [ClickTracking] -> ShowS
show :: ClickTracking -> String
$cshow :: ClickTracking -> String
showsPrec :: Int -> ClickTracking -> ShowS
$cshowsPrec :: Int -> ClickTracking -> ShowS
Show, ClickTracking -> ClickTracking -> Bool
(ClickTracking -> ClickTracking -> Bool)
-> (ClickTracking -> ClickTracking -> Bool) -> Eq ClickTracking
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClickTracking -> ClickTracking -> Bool
$c/= :: ClickTracking -> ClickTracking -> Bool
== :: ClickTracking -> ClickTracking -> Bool
$c== :: ClickTracking -> ClickTracking -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_clickTracking"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''ClickTracking)
data OpenTracking = OpenTracking
{
OpenTracking -> Maybe Bool
_openTrackingEnable :: Maybe Bool
, OpenTracking -> Maybe Text
_openTrackingSubstitutionTag :: Maybe T.Text
} deriving (Int -> OpenTracking -> ShowS
[OpenTracking] -> ShowS
OpenTracking -> String
(Int -> OpenTracking -> ShowS)
-> (OpenTracking -> String)
-> ([OpenTracking] -> ShowS)
-> Show OpenTracking
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OpenTracking] -> ShowS
$cshowList :: [OpenTracking] -> ShowS
show :: OpenTracking -> String
$cshow :: OpenTracking -> String
showsPrec :: Int -> OpenTracking -> ShowS
$cshowsPrec :: Int -> OpenTracking -> ShowS
Show, OpenTracking -> OpenTracking -> Bool
(OpenTracking -> OpenTracking -> Bool)
-> (OpenTracking -> OpenTracking -> Bool) -> Eq OpenTracking
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpenTracking -> OpenTracking -> Bool
$c/= :: OpenTracking -> OpenTracking -> Bool
== :: OpenTracking -> OpenTracking -> Bool
$c== :: OpenTracking -> OpenTracking -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_openTracking"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''OpenTracking)
data SubscriptionTracking = SubscriptionTracking
{
SubscriptionTracking -> Maybe Bool
_subscriptionTrackingEnable :: Maybe Bool
, SubscriptionTracking -> Maybe Text
_subscriptionTrackingText :: Maybe T.Text
, SubscriptionTracking -> Maybe Text
_subscriptionTrackingHTML :: Maybe T.Text
, SubscriptionTracking -> Maybe Text
_subscriptionTrackingSubstitutionTag :: Maybe T.Text
} deriving (Int -> SubscriptionTracking -> ShowS
[SubscriptionTracking] -> ShowS
SubscriptionTracking -> String
(Int -> SubscriptionTracking -> ShowS)
-> (SubscriptionTracking -> String)
-> ([SubscriptionTracking] -> ShowS)
-> Show SubscriptionTracking
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionTracking] -> ShowS
$cshowList :: [SubscriptionTracking] -> ShowS
show :: SubscriptionTracking -> String
$cshow :: SubscriptionTracking -> String
showsPrec :: Int -> SubscriptionTracking -> ShowS
$cshowsPrec :: Int -> SubscriptionTracking -> ShowS
Show, SubscriptionTracking -> SubscriptionTracking -> Bool
(SubscriptionTracking -> SubscriptionTracking -> Bool)
-> (SubscriptionTracking -> SubscriptionTracking -> Bool)
-> Eq SubscriptionTracking
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionTracking -> SubscriptionTracking -> Bool
$c/= :: SubscriptionTracking -> SubscriptionTracking -> Bool
== :: SubscriptionTracking -> SubscriptionTracking -> Bool
$c== :: SubscriptionTracking -> SubscriptionTracking -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_subscriptionTracking"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''SubscriptionTracking)
data Ganalytics = Ganalytics
{
Ganalytics -> Maybe Bool
_ganalyticsEnable :: Maybe Bool
, Ganalytics -> Maybe Text
_ganalyticsUTMSource :: Maybe T.Text
, Ganalytics -> Maybe Text
_ganalyticsUTMMedium :: Maybe T.Text
, Ganalytics -> Maybe Text
_ganalyticsUTMTerm :: Maybe T.Text
, Ganalytics -> Maybe Text
_ganalyticsUTMContent :: Maybe T.Text
, Ganalytics -> Maybe Text
_ganalyticsUTMCampaign :: Maybe T.Text
} deriving (Int -> Ganalytics -> ShowS
[Ganalytics] -> ShowS
Ganalytics -> String
(Int -> Ganalytics -> ShowS)
-> (Ganalytics -> String)
-> ([Ganalytics] -> ShowS)
-> Show Ganalytics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ganalytics] -> ShowS
$cshowList :: [Ganalytics] -> ShowS
show :: Ganalytics -> String
$cshow :: Ganalytics -> String
showsPrec :: Int -> Ganalytics -> ShowS
$cshowsPrec :: Int -> Ganalytics -> ShowS
Show, Ganalytics -> Ganalytics -> Bool
(Ganalytics -> Ganalytics -> Bool)
-> (Ganalytics -> Ganalytics -> Bool) -> Eq Ganalytics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ganalytics -> Ganalytics -> Bool
$c/= :: Ganalytics -> Ganalytics -> Bool
== :: Ganalytics -> Ganalytics -> Bool
$c== :: Ganalytics -> Ganalytics -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_ganalytics"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''Ganalytics)
data TrackingSettings = TrackingSettings
{
TrackingSettings -> ClickTracking
_trackingSettingsClickTracking :: ClickTracking
, TrackingSettings -> OpenTracking
_trackingSettingsOpenTracking :: OpenTracking
, TrackingSettings -> SubscriptionTracking
_trackingSettingsSubscriptionTracking :: SubscriptionTracking
, TrackingSettings -> Ganalytics
_trackingSettingsGanalytics :: Ganalytics
} deriving (Int -> TrackingSettings -> ShowS
[TrackingSettings] -> ShowS
TrackingSettings -> String
(Int -> TrackingSettings -> ShowS)
-> (TrackingSettings -> String)
-> ([TrackingSettings] -> ShowS)
-> Show TrackingSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TrackingSettings] -> ShowS
$cshowList :: [TrackingSettings] -> ShowS
show :: TrackingSettings -> String
$cshow :: TrackingSettings -> String
showsPrec :: Int -> TrackingSettings -> ShowS
$cshowsPrec :: Int -> TrackingSettings -> ShowS
Show, TrackingSettings -> TrackingSettings -> Bool
(TrackingSettings -> TrackingSettings -> Bool)
-> (TrackingSettings -> TrackingSettings -> Bool)
-> Eq TrackingSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TrackingSettings -> TrackingSettings -> Bool
$c/= :: TrackingSettings -> TrackingSettings -> Bool
== :: TrackingSettings -> TrackingSettings -> Bool
$c== :: TrackingSettings -> TrackingSettings -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_trackingSettings"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''TrackingSettings)
data MailSettings = MailSettings
{
MailSettings -> Maybe Bcc
_mailSettingsBcc :: Maybe Bcc
, MailSettings -> Maybe BypassListManagement
_mailSettingsBypassListManagement :: Maybe BypassListManagement
, :: Maybe Footer
, MailSettings -> Maybe SandboxMode
_mailSettingsSandboxMode :: Maybe SandboxMode
, MailSettings -> Maybe SpamCheck
_mailSettingsSpamCheck :: Maybe SpamCheck
} deriving (Int -> MailSettings -> ShowS
[MailSettings] -> ShowS
MailSettings -> String
(Int -> MailSettings -> ShowS)
-> (MailSettings -> String)
-> ([MailSettings] -> ShowS)
-> Show MailSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MailSettings] -> ShowS
$cshowList :: [MailSettings] -> ShowS
show :: MailSettings -> String
$cshow :: MailSettings -> String
showsPrec :: Int -> MailSettings -> ShowS
$cshowsPrec :: Int -> MailSettings -> ShowS
Show, MailSettings -> MailSettings -> Bool
(MailSettings -> MailSettings -> Bool)
-> (MailSettings -> MailSettings -> Bool) -> Eq MailSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MailSettings -> MailSettings -> Bool
$c/= :: MailSettings -> MailSettings -> Bool
== :: MailSettings -> MailSettings -> Bool
$c== :: MailSettings -> MailSettings -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_mailSettings"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''MailSettings)
data Mail a b = Mail
{
Mail a b -> [Personalization]
_mailPersonalizations :: [Personalization]
, Mail a b -> MailAddress
_mailFrom :: MailAddress
, Mail a b -> Maybe MailAddress
_mailReplyTo :: Maybe MailAddress
, Mail a b -> Text
_mailSubject :: T.Text
, Mail a b -> Maybe (NonEmpty MailContent)
_mailContent :: Maybe (NonEmpty MailContent)
, Mail a b -> Maybe [MailAttachment]
_mailAttachments :: Maybe [MailAttachment]
, Mail a b -> Maybe Text
_mailTemplateId :: Maybe T.Text
, Mail a b -> Maybe a
_mailSections :: Maybe a
, :: Maybe [(T.Text, T.Text)]
, Mail a b -> Maybe [Text]
_mailCategories :: Maybe [T.Text]
, Mail a b -> Maybe b
_mailCustomArgs :: Maybe b
, Mail a b -> Maybe Int
_mailSendAt :: Maybe Int
, Mail a b -> Maybe Text
_mailBatchId :: Maybe T.Text
, Mail a b -> Maybe Asm
_mailAsm :: Maybe Asm
, Mail a b -> Maybe Text
_mailIpPoolName :: Maybe T.Text
, Mail a b -> Maybe MailSettings
_mailMailSettings :: Maybe MailSettings
, Mail a b -> Maybe TrackingSettings
_mailTrackingSettings :: Maybe TrackingSettings
} deriving (Int -> Mail a b -> ShowS
[Mail a b] -> ShowS
Mail a b -> String
(Int -> Mail a b -> ShowS)
-> (Mail a b -> String) -> ([Mail a b] -> ShowS) -> Show (Mail a b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b. (Show a, Show b) => Int -> Mail a b -> ShowS
forall a b. (Show a, Show b) => [Mail a b] -> ShowS
forall a b. (Show a, Show b) => Mail a b -> String
showList :: [Mail a b] -> ShowS
$cshowList :: forall a b. (Show a, Show b) => [Mail a b] -> ShowS
show :: Mail a b -> String
$cshow :: forall a b. (Show a, Show b) => Mail a b -> String
showsPrec :: Int -> Mail a b -> ShowS
$cshowsPrec :: forall a b. (Show a, Show b) => Int -> Mail a b -> ShowS
Show, Mail a b -> Mail a b -> Bool
(Mail a b -> Mail a b -> Bool)
-> (Mail a b -> Mail a b -> Bool) -> Eq (Mail a b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall a b. (Eq a, Eq b) => Mail a b -> Mail a b -> Bool
/= :: Mail a b -> Mail a b -> Bool
$c/= :: forall a b. (Eq a, Eq b) => Mail a b -> Mail a b -> Bool
== :: Mail a b -> Mail a b -> Bool
$c== :: forall a b. (Eq a, Eq b) => Mail a b -> Mail a b -> Bool
Eq)
$(deriveToJSON (defaultOptions
{ fieldLabelModifier = unPrefix "_mail"
, omitNothingFields = True
, constructorTagModifier = map toLower }) ''Mail)
mail
:: (ToJSON a, ToJSON b)
=> [Personalization]
-> MailAddress
-> T.Text
-> Maybe (NonEmpty MailContent)
-> Mail a b
mail :: [Personalization]
-> MailAddress -> Text -> Maybe (NonEmpty MailContent) -> Mail a b
mail [Personalization]
personalizations MailAddress
from Text
subject Maybe (NonEmpty MailContent)
mContent = Mail :: forall a b.
[Personalization]
-> MailAddress
-> Maybe MailAddress
-> Text
-> Maybe (NonEmpty MailContent)
-> Maybe [MailAttachment]
-> Maybe Text
-> Maybe a
-> Maybe [(Text, Text)]
-> Maybe [Text]
-> Maybe b
-> Maybe Int
-> Maybe Text
-> Maybe Asm
-> Maybe Text
-> Maybe MailSettings
-> Maybe TrackingSettings
-> Mail a b
Mail
{ _mailPersonalizations :: [Personalization]
_mailPersonalizations = [Personalization]
personalizations
, _mailFrom :: MailAddress
_mailFrom = MailAddress
from
, _mailReplyTo :: Maybe MailAddress
_mailReplyTo = Maybe MailAddress
forall a. Maybe a
Nothing
, _mailSubject :: Text
_mailSubject = Text
subject
, _mailContent :: Maybe (NonEmpty MailContent)
_mailContent = Maybe (NonEmpty MailContent)
mContent
, _mailAttachments :: Maybe [MailAttachment]
_mailAttachments = Maybe [MailAttachment]
forall a. Maybe a
Nothing
, _mailTemplateId :: Maybe Text
_mailTemplateId = Maybe Text
forall a. Maybe a
Nothing
, _mailSections :: Maybe a
_mailSections = forall a. Maybe a
Nothing :: Maybe a
, _mailHeaders :: Maybe [(Text, Text)]
_mailHeaders = Maybe [(Text, Text)]
forall a. Maybe a
Nothing
, _mailCategories :: Maybe [Text]
_mailCategories = Maybe [Text]
forall a. Maybe a
Nothing
, _mailCustomArgs :: Maybe b
_mailCustomArgs = forall a. Maybe a
Nothing :: Maybe b
, _mailSendAt :: Maybe Int
_mailSendAt = Maybe Int
forall a. Maybe a
Nothing
, _mailBatchId :: Maybe Text
_mailBatchId = Maybe Text
forall a. Maybe a
Nothing
, _mailAsm :: Maybe Asm
_mailAsm = Maybe Asm
forall a. Maybe a
Nothing
, _mailIpPoolName :: Maybe Text
_mailIpPoolName = Maybe Text
forall a. Maybe a
Nothing
, _mailMailSettings :: Maybe MailSettings
_mailMailSettings = Maybe MailSettings
forall a. Maybe a
Nothing
, _mailTrackingSettings :: Maybe TrackingSettings
_mailTrackingSettings = Maybe TrackingSettings
forall a. Maybe a
Nothing
}
sendMail
:: (ToJSON a, ToJSON b)
=> ApiKey
-> Mail a b
-> IO (Either HttpException (Response ByteString))
sendMail :: ApiKey
-> Mail a b -> IO (Either HttpException (Response ByteString))
sendMail (ApiKey Text
key) Mail a b
mail' = do
let tkn :: ByteString
tkn = Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Text
"Bearer " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
key
opts :: Options
opts =
Options
defaults
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& (HeaderName -> Lens' Options [ByteString]
header HeaderName
"Authorization" (([ByteString] -> Identity [ByteString])
-> Options -> Identity Options)
-> [ByteString] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [ByteString
tkn])
(Options -> Options) -> (Options -> Options) -> Options -> Options
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HeaderName -> Lens' Options [ByteString]
header HeaderName
"Content-Type" (([ByteString] -> Identity [ByteString])
-> Options -> Identity Options)
-> [ByteString] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [ByteString
"application/json"])
IO (Response ByteString)
-> IO (Either HttpException (Response ByteString))
forall e a. Exception e => IO a -> IO (Either e a)
try (IO (Response ByteString)
-> IO (Either HttpException (Response ByteString)))
-> (ByteString -> IO (Response ByteString))
-> ByteString
-> IO (Either HttpException (Response ByteString))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> String -> ByteString -> IO (Response ByteString)
forall a.
Postable a =>
Options -> String -> a -> IO (Response ByteString)
postWith Options
opts (Text -> String
T.unpack Text
sendGridAPI) (ByteString -> IO (Either HttpException (Response ByteString)))
-> ByteString -> IO (Either HttpException (Response ByteString))
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode (Mail a b -> Value
forall a. ToJSON a => a -> Value
toJSON Mail a b
mail')