Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.SendGridV3.Api
Description
Module that implements the Mail API of SendGrid v3. https://sendgrid.com/docs/API_Reference/api_v3.html
{-# LANGUAGE OverloadedStrings #-} import Data.List.NonEmpty (fromList) import Network.SendGridV3.Api import Control.Lens ((^.)) import Network.Wreq (responseStatus, statusCode) sendGridApiKey :: ApiKey sendGridApiKey = ApiKey "SG..." testMail :: Mail () () testMail = let to = personalization $ fromList [MailAddress "john@example.com" "John Doe"] from = MailAddress "jane@example.com" "Jane Smith" subject = "Email Subject" content = fromList [mailContentText "Example Content"] in mail [to] from subject content main :: IO () main = do -- Send an email, overriding options as needed eResponse <- sendMail sendGridApiKey (testMail { _mailSendAt = Just 1516468000 }) case eResponse of Left httpException -> error $ show httpException Right response -> print (response ^. responseStatus . statusCode)
Synopsis
- sendGridAPI :: Text
- data ApiKey = ApiKey {}
- data MailAddress = MailAddress {}
- data MailContent = MailContent {}
- mailContentText :: Text -> MailContent
- mailContentHtml :: Text -> MailContent
- data Personalization = Personalization {
- _personalizationTo :: NonEmpty MailAddress
- _personalizationCc :: Maybe [MailAddress]
- _personalizationBcc :: Maybe [MailAddress]
- _personalizationSubject :: Maybe Text
- _personalizationHeaders :: Maybe [(Text, Text)]
- _personalizationSubstitutions :: Maybe Object
- _personalizationSendAt :: Maybe Int
- _personalizationDynamicTemplateData :: Maybe Value
- personalization :: NonEmpty MailAddress -> Personalization
- data Disposition
- = Inline
- | Attachment
- data MailAttachment = MailAttachment {}
- data Asm = Asm {
- _asmGroupId :: Int
- _asmGroupsToDisplay :: Maybe [Int]
- data Bcc = Bcc {}
- data BypassListManagement = BypassListManagement {}
- data Footer = Footer {}
- data SandboxMode = SandboxMode {}
- data SpamCheck = SpamCheck {}
- data ClickTracking = ClickTracking {}
- data OpenTracking = OpenTracking {}
- data SubscriptionTracking = SubscriptionTracking {}
- data Ganalytics = Ganalytics {}
- data TrackingSettings = TrackingSettings {}
- data MailSettings = MailSettings {}
- data Mail a b = Mail {
- _mailPersonalizations :: [Personalization]
- _mailFrom :: MailAddress
- _mailReplyTo :: Maybe MailAddress
- _mailSubject :: Text
- _mailContent :: Maybe (NonEmpty MailContent)
- _mailAttachments :: Maybe [MailAttachment]
- _mailTemplateId :: Maybe Text
- _mailSections :: Maybe a
- _mailHeaders :: Maybe [(Text, Text)]
- _mailCategories :: Maybe [Text]
- _mailCustomArgs :: Maybe b
- _mailSendAt :: Maybe Int
- _mailBatchId :: Maybe Text
- _mailAsm :: Maybe Asm
- _mailIpPoolName :: Maybe Text
- _mailMailSettings :: Maybe MailSettings
- _mailTrackingSettings :: Maybe TrackingSettings
- mail :: (ToJSON a, ToJSON b) => [Personalization] -> MailAddress -> Text -> Maybe (NonEmpty MailContent) -> Mail a b
- sendMail :: (ToJSON a, ToJSON b) => ApiKey -> Mail a b -> IO (Either HttpException (Response ByteString))
Documentation
sendGridAPI :: Text Source #
URL to SendGrid Mail API
Bearer Token for the API
data MailAddress Source #
Constructors
MailAddress | |
Fields
|
Instances
Eq MailAddress Source # | |
Defined in Network.SendGridV3.Api | |
Show MailAddress Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> MailAddress -> ShowS # show :: MailAddress -> String # showList :: [MailAddress] -> ShowS # | |
ToJSON MailAddress Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: MailAddress -> Value # toEncoding :: MailAddress -> Encoding # toJSONList :: [MailAddress] -> Value # toEncodingList :: [MailAddress] -> Encoding # |
data MailContent Source #
Constructors
MailContent | |
Fields
|
Instances
Eq MailContent Source # | |
Defined in Network.SendGridV3.Api | |
Show MailContent Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> MailContent -> ShowS # show :: MailContent -> String # showList :: [MailContent] -> ShowS # | |
ToJSON MailContent Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: MailContent -> Value # toEncoding :: MailContent -> Encoding # toJSONList :: [MailContent] -> Value # toEncodingList :: [MailContent] -> Encoding # |
mailContentText :: Text -> MailContent Source #
M̀ailContent constructor for text/plain
mailContentHtml :: Text -> MailContent Source #
M̀ailContent constructor for text/html
data Personalization Source #
An array of messages and their metadata. Each object within personalizations can be thought of as an envelope - it defines who should receive an individual message and how that message should be handled.
Constructors
Personalization | |
Fields
|
Instances
Eq Personalization Source # | |
Defined in Network.SendGridV3.Api Methods (==) :: Personalization -> Personalization -> Bool # (/=) :: Personalization -> Personalization -> Bool # | |
Show Personalization Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> Personalization -> ShowS # show :: Personalization -> String # showList :: [Personalization] -> ShowS # | |
ToJSON Personalization Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: Personalization -> Value # toEncoding :: Personalization -> Encoding # toJSONList :: [Personalization] -> Value # toEncodingList :: [Personalization] -> Encoding # |
personalization :: NonEmpty MailAddress -> Personalization Source #
Personalization smart constructor only asking for the mandatory fields
data Disposition Source #
The content-disposition of the attachment specifying how you would like the attachment to be displayed.
Constructors
Inline | Results in the attached file being displayed automatically within the message. |
Attachment | Results in the attached file requiring some action to be taken before it is displayed (e.g. opening or downloading the file). |
Instances
Eq Disposition Source # | |
Defined in Network.SendGridV3.Api | |
Show Disposition Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> Disposition -> ShowS # show :: Disposition -> String # showList :: [Disposition] -> ShowS # | |
ToJSON Disposition Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: Disposition -> Value # toEncoding :: Disposition -> Encoding # toJSONList :: [Disposition] -> Value # toEncodingList :: [Disposition] -> Encoding # |
data MailAttachment Source #
Constructors
MailAttachment | |
Fields
|
Instances
Eq MailAttachment Source # | |
Defined in Network.SendGridV3.Api Methods (==) :: MailAttachment -> MailAttachment -> Bool # (/=) :: MailAttachment -> MailAttachment -> Bool # | |
Show MailAttachment Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> MailAttachment -> ShowS # show :: MailAttachment -> String # showList :: [MailAttachment] -> ShowS # | |
ToJSON MailAttachment Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: MailAttachment -> Value # toEncoding :: MailAttachment -> Encoding # toJSONList :: [MailAttachment] -> Value # toEncodingList :: [MailAttachment] -> Encoding # |
An object allowing you to specify how to handle unsubscribes.
Constructors
Asm | |
Fields
|
This allows you to have a blind carbon copy automatically sent to the specified email address for every email that is sent.
Constructors
Bcc | |
data BypassListManagement Source #
Allows you to bypass all unsubscribe groups and suppressions to ensure that the email is delivered to every single recipient. This should only be used in emergencies when it is absolutely necessary that every recipient receives your email.
Constructors
BypassListManagement | |
Fields
|
Instances
Eq BypassListManagement Source # | |
Defined in Network.SendGridV3.Api Methods (==) :: BypassListManagement -> BypassListManagement -> Bool # (/=) :: BypassListManagement -> BypassListManagement -> Bool # | |
Show BypassListManagement Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> BypassListManagement -> ShowS # show :: BypassListManagement -> String # showList :: [BypassListManagement] -> ShowS # | |
ToJSON BypassListManagement Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: BypassListManagement -> Value # toEncoding :: BypassListManagement -> Encoding # toJSONList :: [BypassListManagement] -> Value # toEncodingList :: [BypassListManagement] -> Encoding # |
The default footer that you would like included on every email.
Constructors
Footer | |
Fields
|
Instances
data SandboxMode Source #
This allows you to send a test email to ensure that your request body is valid and formatted correctly.
Constructors
SandboxMode | |
Fields
|
Instances
Eq SandboxMode Source # | |
Defined in Network.SendGridV3.Api | |
Show SandboxMode Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> SandboxMode -> ShowS # show :: SandboxMode -> String # showList :: [SandboxMode] -> ShowS # | |
ToJSON SandboxMode Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: SandboxMode -> Value # toEncoding :: SandboxMode -> Encoding # toJSONList :: [SandboxMode] -> Value # toEncodingList :: [SandboxMode] -> Encoding # |
This allows you to test the content of your email for spam.
Constructors
SpamCheck | |
Fields
|
data ClickTracking Source #
Allows you to track whether a recipient clicked a link in your email.
Constructors
ClickTracking | |
Fields
|
Instances
Eq ClickTracking Source # | |
Defined in Network.SendGridV3.Api Methods (==) :: ClickTracking -> ClickTracking -> Bool # (/=) :: ClickTracking -> ClickTracking -> Bool # | |
Show ClickTracking Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> ClickTracking -> ShowS # show :: ClickTracking -> String # showList :: [ClickTracking] -> ShowS # | |
ToJSON ClickTracking Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: ClickTracking -> Value # toEncoding :: ClickTracking -> Encoding # toJSONList :: [ClickTracking] -> Value # toEncodingList :: [ClickTracking] -> Encoding # |
data OpenTracking Source #
Allows you to track whether the email was opened or not.
Constructors
OpenTracking | |
Fields
|
Instances
Eq OpenTracking Source # | |
Defined in Network.SendGridV3.Api | |
Show OpenTracking Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> OpenTracking -> ShowS # show :: OpenTracking -> String # showList :: [OpenTracking] -> ShowS # | |
ToJSON OpenTracking Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: OpenTracking -> Value # toEncoding :: OpenTracking -> Encoding # toJSONList :: [OpenTracking] -> Value # toEncodingList :: [OpenTracking] -> Encoding # |
data SubscriptionTracking Source #
Allows you to insert a subscription management link.
Constructors
SubscriptionTracking | |
Fields
|
Instances
Eq SubscriptionTracking Source # | |
Defined in Network.SendGridV3.Api Methods (==) :: SubscriptionTracking -> SubscriptionTracking -> Bool # (/=) :: SubscriptionTracking -> SubscriptionTracking -> Bool # | |
Show SubscriptionTracking Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> SubscriptionTracking -> ShowS # show :: SubscriptionTracking -> String # showList :: [SubscriptionTracking] -> ShowS # | |
ToJSON SubscriptionTracking Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: SubscriptionTracking -> Value # toEncoding :: SubscriptionTracking -> Encoding # toJSONList :: [SubscriptionTracking] -> Value # toEncodingList :: [SubscriptionTracking] -> Encoding # |
data Ganalytics Source #
Allows you to enable tracking provided by Google Analytics
Constructors
Ganalytics | |
Fields
|
Instances
Eq Ganalytics Source # | |
Defined in Network.SendGridV3.Api | |
Show Ganalytics Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> Ganalytics -> ShowS # show :: Ganalytics -> String # showList :: [Ganalytics] -> ShowS # | |
ToJSON Ganalytics Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: Ganalytics -> Value # toEncoding :: Ganalytics -> Encoding # toJSONList :: [Ganalytics] -> Value # toEncodingList :: [Ganalytics] -> Encoding # |
data TrackingSettings Source #
Constructors
TrackingSettings | |
Fields
|
Instances
Eq TrackingSettings Source # | |
Defined in Network.SendGridV3.Api Methods (==) :: TrackingSettings -> TrackingSettings -> Bool # (/=) :: TrackingSettings -> TrackingSettings -> Bool # | |
Show TrackingSettings Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> TrackingSettings -> ShowS # show :: TrackingSettings -> String # showList :: [TrackingSettings] -> ShowS # | |
ToJSON TrackingSettings Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: TrackingSettings -> Value # toEncoding :: TrackingSettings -> Encoding # toJSONList :: [TrackingSettings] -> Value # toEncodingList :: [TrackingSettings] -> Encoding # |
data MailSettings Source #
A collection of different mail settings that you can use to specify how you would like this email to be handled.
Constructors
MailSettings | |
Fields
|
Instances
Eq MailSettings Source # | |
Defined in Network.SendGridV3.Api | |
Show MailSettings Source # | |
Defined in Network.SendGridV3.Api Methods showsPrec :: Int -> MailSettings -> ShowS # show :: MailSettings -> String # showList :: [MailSettings] -> ShowS # | |
ToJSON MailSettings Source # | |
Defined in Network.SendGridV3.Api Methods toJSON :: MailSettings -> Value # toEncoding :: MailSettings -> Encoding # toJSONList :: [MailSettings] -> Value # toEncodingList :: [MailSettings] -> Encoding # |
Constructors
Fields
|
mail :: (ToJSON a, ToJSON b) => [Personalization] -> MailAddress -> Text -> Maybe (NonEmpty MailContent) -> Mail a b Source #
sendMail :: (ToJSON a, ToJSON b) => ApiKey -> Mail a b -> IO (Either HttpException (Response ByteString)) Source #
Send an email via the SendGrid
API.
a
- Type of Mail Section, see
_mailSections
for details. b
- Type of Custom Arg, see
_mailCustomArgs
for details.
Returns either:
- A successful
from the SendGrid API
- An Response
, thrown from HttpException
postWith