sendgrid-v3-0.1.1.0: Sendgrid v3 API library

Safe HaskellNone
LanguageHaskell2010

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

sendGridApiKey :: ApiKey
sendGridApiKey = "SG..."

testMail :: Mail () ()
testMail addr =
  let from'    = "john.doe+from@doe.com"
      subject' = "Email Subject"
      content' = fromList [mailContentText "Example Content"]
  in mail [] from' subject' content'

main :: IO ()
main = do
  -- Simple Send
  statusCode <- sendMail sendGridApiKey testMail
  -- Send with further options
  statusCode <- sendMail sendGridApiKey (testMail { _mailSendAt = Just 1516468000 })
  return ()
Synopsis

Documentation

sendGridAPI :: Text Source #

URL to SendGrid Mail API

data ApiKey Source #

Bearer Token for the API

Constructors

ApiKey 

Fields

Instances
Eq ApiKey Source # 
Instance details

Defined in Network.SendGridV3.Api

Methods

(==) :: ApiKey -> ApiKey -> Bool #

(/=) :: ApiKey -> ApiKey -> Bool #

Show ApiKey Source # 
Instance details

Defined in Network.SendGridV3.Api

data MailAddress Source #

Constructors

MailAddress 

Fields

data MailContent Source #

Constructors

MailContent 

Fields

  • _mailContentType :: Text

    The mime type of the content you are including in your email. For example, “textplain” or “texthtml”.

  • _mailContentValue :: Text

    The actual content of the specified mime type that you are including in your email.

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

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).

data MailAttachment Source #

Constructors

MailAttachment 

Fields

data Asm Source #

An object allowing you to specify how to handle unsubscribes.

Constructors

Asm 

Fields

  • _asmGroupId :: Int

    The unsubscribe group to associate with this email.

  • _asmGroupsToDisplay :: Maybe [Int]

    An array containing the unsubscribe groups that you would like to be displayed on the unsubscribe preferences page.

Instances
Eq Asm Source # 
Instance details

Defined in Network.SendGridV3.Api

Methods

(==) :: Asm -> Asm -> Bool #

(/=) :: Asm -> Asm -> Bool #

Show Asm Source # 
Instance details

Defined in Network.SendGridV3.Api

Methods

showsPrec :: Int -> Asm -> ShowS #

show :: Asm -> String #

showList :: [Asm] -> ShowS #

ToJSON Asm Source # 
Instance details

Defined in Network.SendGridV3.Api

data Bcc Source #

This allows you to have a blind carbon copy automatically sent to the specified email address for every email that is sent.

Constructors

Bcc 

Fields

Instances
Eq Bcc Source # 
Instance details

Defined in Network.SendGridV3.Api

Methods

(==) :: Bcc -> Bcc -> Bool #

(/=) :: Bcc -> Bcc -> Bool #

Show Bcc Source # 
Instance details

Defined in Network.SendGridV3.Api

Methods

showsPrec :: Int -> Bcc -> ShowS #

show :: Bcc -> String #

showList :: [Bcc] -> ShowS #

ToJSON Bcc Source # 
Instance details

Defined in Network.SendGridV3.Api

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

data Footer Source #

The default footer that you would like included on every email.

Constructors

Footer 

Fields

Instances
Eq Footer Source # 
Instance details

Defined in Network.SendGridV3.Api

Methods

(==) :: Footer -> Footer -> Bool #

(/=) :: Footer -> Footer -> Bool #

Show Footer Source # 
Instance details

Defined in Network.SendGridV3.Api

ToJSON Footer Source # 
Instance details

Defined in Network.SendGridV3.Api

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

data SpamCheck Source #

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

data OpenTracking Source #

Allows you to track whether the email was opened or not.

Constructors

OpenTracking 

Fields

data SubscriptionTracking Source #

Allows you to insert a subscription management link.

Constructors

SubscriptionTracking 

Fields

data Ganalytics Source #

Allows you to enable tracking provided by Google Analytics

Constructors

Ganalytics 

Fields

data TrackingSettings Source #

Constructors

TrackingSettings 

Fields

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

data Mail a b Source #

Constructors

Mail 

Fields

  • _mailPersonalizations :: [Personalization]

    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.

  • _mailFrom :: MailAddress

    Address details of the person to whom you are sending an email.

  • _mailReplyTo :: Maybe MailAddress

    Address details of the person to whom you are sending an email.

  • _mailSubject :: Text

    The subject of your email.

  • _mailContent :: NonEmpty MailContent

    An array in which you may specify the content of your email. You can include multiple mime types of content, but you must specify at least one mime type.

  • _mailAttachments :: Maybe [MailAttachment]

    An array of objects in which you can specify any attachments you want to include.

  • _mailTemplateId :: Maybe Text

    The id of a template that you would like to use. If you use a template that contains a subject and content (either text or html), you do not need to specify those at the personalizations nor message level.

  • _mailSections :: Maybe a

    An object of key/value pairs that define block sections of code to be used as substitutions.

  • _mailHeaders :: Maybe [(Text, Text)]

    An object containing key/value pairs of header names and the value to substitute for them. You must ensure these are properly encoded if they contain unicode characters. Must not be one of the reserved headers.

  • _mailCategories :: Maybe [Text]

    An array of category names for this message. Each category name may not exceed 255 characters.

  • _mailCustomArgs :: Maybe b

    Values that are specific to the entire send that will be carried along with | the email and its activity data.

  • _mailSendAt :: Maybe Int

    A unix timestamp allowing you to specify when you want your email to be delivered.

  • _mailBatchId :: Maybe Text

    This ID represents a batch of emails to be sent at the same time. Including a batch_id in your request allows you include this email in that batch, and also enables you to cancel or pause the delivery of that batch. For more information, see https://sendgrid.com/docs/API_Reference/Web_API_v3/cancel_schedule_send.html

  • _mailAsm :: Maybe Asm

    An object allowing you to specify how to handle unsubscribes.

  • _mailIpPoolName :: Maybe Text

    The IP Pool that you would like to send this email from.

  • _mailMailSettings :: Maybe MailSettings

    A collection of different mail settings that you can use to specify how you would like this email to be handled.

  • _mailTrackingSettings :: Maybe TrackingSettings

    Settings to determine how you would like to track the metrics of how your recipients interact with your email.

Instances
(Eq a, Eq b) => Eq (Mail a b) Source # 
Instance details

Defined in Network.SendGridV3.Api

Methods

(==) :: Mail a b -> Mail a b -> Bool #

(/=) :: Mail a b -> Mail a b -> Bool #

(Show a, Show b) => Show (Mail a b) Source # 
Instance details

Defined in Network.SendGridV3.Api

Methods

showsPrec :: Int -> Mail a b -> ShowS #

show :: Mail a b -> String #

showList :: [Mail a b] -> ShowS #

(ToJSON a, ToJSON b) => ToJSON (Mail a b) Source # 
Instance details

Defined in Network.SendGridV3.Api

Methods

toJSON :: Mail a b -> Value #

toEncoding :: Mail a b -> Encoding #

toJSONList :: [Mail a b] -> Value #

toEncodingList :: [Mail a b] -> Encoding #

mail :: (ToJSON a, ToJSON b) => [Personalization] -> MailAddress -> Text -> NonEmpty MailContent -> Mail a b Source #

Smart constructor for Mail, asking only for the mandatory Mail parameters.

sendMail :: (ToJSON a, ToJSON b) => ApiKey -> Mail a b -> IO Int 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.