hailgun-simple-0.1.0.0: Easy-to-use wrapper for the hailgun package

CopyrightDennis Gosnell 2016
LicenseBSD3
MaintainerDennis Gosnell (cdep.illabout@gmail.com)
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Mail.Hailgun.Simple

Contents

Description

This module provides a simple, easy-to-use wrapper around the hailgun package. hailgun is a package providing a way to send email using Mailgun.

Here is a short example of how to use this package:

  {-# LANGUAGE OverloadedStrings #-}
  {-# LANGUAGE QuasiQuotes #-}

  module FooBar where

  import Control.Monad.Reader (ReaderT)
  import Data.Text (Text)
  import Data.Text.Encoding (encodeUtf8)
  import Text.Email.Validate (EmailAddress)
  import Text.Shakespeare.Text (sbt)
  import Mail.Hailgun.Simple
         (MessageContent(TextOnly), Email(..), EmailError,
          HailgunContext, ResponseFromMailgun, sendEmail)

  -- This function will send a new user an email.
  sendEmailToNewUser
    :: Text -- ^ user's name
    -> EmailAddress -- ^ user's email address
    -> ReaderT HailgunContext IO (Either EmailError ResponseFromMailgun)
  sendEmailToNewUser name emailaddress = do
    let email = Email
          { emailSubject = "Thanks for signing up!"
          , emailBody = TextOnly $ encodeUtf8 body
          , emailReplyTo = myEmailAddress
          , emailRecipientsTo = [emailaddress]
          , emailRecipientsCC = []
          , emailRecipientsBCC = []
          , emailAttachments = []
          }
    sendEmail email
    where
      body :: Text
      body = [sbt|Hi #{name}!
                 |
                 |Thanks for signing up to our service!
                 |
                 |From your friends at foobar.com :-)|]

  myEmailAddress :: EmailAddress
  myEmailAddress = undefined

Synopsis

Sending an Email

sendEmail :: forall r m. (HasHailgunContext r, MonadIO m, MonadReader r m) => Email -> m (Either EmailError ResponseFromMailgun) Source #

Send an Email.

Returns an EmailErrorIncorrectEmailFormat error if the format of the email was not correct (for instance, if the email senders or receivers were incorrect, or the attachments are specified incorrectly). If you are constructing an Email by hand (and not programatically), this error will indicate a programmer error.

Returns an EmailErrorSendError if there was a problem with actually sending the Email. This will usually be an error from the Mailgun servers.

Email

data MessageContent :: * #

Any email content that you wish to send should be encoded into these types before it is sent. Currently, according to the API, you should always send a Text Only part in the email and you can optionally add a nicely formatted HTML version of that email to the sent message.

It is best to send multi-part emails using both text and HTML or text only. Sending HTML only
email is not well received by ESPs.

(Source)

This API mirrors that advice so that you can always get it right.

Constructors

TextOnly

The Text only version of the message content.

Fields

  • textContent :: ByteString

    The text content that you wish to send (please note that many clients will take the HTML version first if it is present but that the text version is a great fallback).

TextAndHTML

A message that contains both a Text version of the email content and a HTML version of the email content.

Fields

  • textContent :: ByteString

    The text content that you wish to send (please note that many clients will take the HTML version first if it is present but that the text version is a great fallback).

  • htmlContent :: ByteString

    The HTML content that you wish to send.

Response

data ResponseFromMailgun Source #

Response returned from Mailgun's servers.

Constructors

ResponseFromMailgun 

Fields

Instances

Data ResponseFromMailgun Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResponseFromMailgun -> c ResponseFromMailgun #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResponseFromMailgun #

toConstr :: ResponseFromMailgun -> Constr #

dataTypeOf :: ResponseFromMailgun -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ResponseFromMailgun) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResponseFromMailgun) #

gmapT :: (forall b. Data b => b -> b) -> ResponseFromMailgun -> ResponseFromMailgun #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResponseFromMailgun -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResponseFromMailgun -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResponseFromMailgun -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResponseFromMailgun -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResponseFromMailgun -> m ResponseFromMailgun #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResponseFromMailgun -> m ResponseFromMailgun #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResponseFromMailgun -> m ResponseFromMailgun #

Show ResponseFromMailgun Source # 
Generic ResponseFromMailgun Source # 
type Rep ResponseFromMailgun Source # 
type Rep ResponseFromMailgun = D1 (MetaData "ResponseFromMailgun" "Mail.Hailgun.Simple" "hailgun-simple-0.1.0.0-jSC07BJfx51PHMb4uiE19" False) (C1 (MetaCons "ResponseFromMailgun" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "mailgunMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "mailgunId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

HailgunContext

data HailgunContext :: * #

When comunnicating to the Mailgun service you need to have some common pieces of information to authenticate successfully. This context encapsulates that required information.

Constructors

HailgunContext 

Fields

class HasHailgunContext r where Source #

This class provides one layer (or multiple layers) of indirection. It makes it possible to pass sendEmail a generic configuration datatype that contains a HailgunContext instead of a HailgunContext directly.

For instance, imagine you had a configuration datatype like this:

  data Config = Config
    { configDatabasePool :: Pool
    , configHailgunContext :: HailgunContext
    }

You could create an instance of HasHailgunContext for Config like this:

  instance HasHailgunContext Config where
    getHailgunContext :: Config -> HailgunContext
    getHailgunContext = configHailgunContext

Now, you can pass Config to sendEmail instead of a HailgunContext directly.

Minimal complete definition

getHailgunContext

Errors

data EmailError Source #

Datatype to represent possible errors with sending an email.

Constructors

EmailErrorIncorrectEmailFormat Text

Email was in incorrect format. Since we are creating emails by hand, this error should never occur.

EmailErrorSendError Text

Error from Mailgun when trying to send an email.

Instances

Show EmailError Source # 
Generic EmailError Source # 

Associated Types

type Rep EmailError :: * -> * #

type Rep EmailError Source # 
type Rep EmailError = D1 (MetaData "EmailError" "Mail.Hailgun.Simple" "hailgun-simple-0.1.0.0-jSC07BJfx51PHMb4uiE19" False) ((:+:) (C1 (MetaCons "EmailErrorIncorrectEmailFormat" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) (C1 (MetaCons "EmailErrorSendError" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

Lower-level calls