imm-1.5.0.0: Execute arbitrary actions for each unread element of RSS/Atom feeds

Safe HaskellNone
LanguageHaskell98

Imm.Hooks.SendMail

Description

Implementation of Imm.Hooks that sends a mail via a SMTP server for each new RSS/Atom element. You may want to check out Network.HaskellNet.SMTP, Network.HaskellNet.SMTP.SSL and Network.Mail.Mime modules for additional information.

Here is an example configuration:

sendmail :: SendMailSettings
sendmail = SendMailSettings smtpServer formatMail

formatMail :: FormatMail
formatMail = FormatMail
  (\a b -> (defaultFormatFrom a b) { addressEmail = "user@host" } )
  defaultFormatSubject
  defaultFormatBody
  (\_ _ -> [Address Nothing "user@host"])

smtpServer :: Feed -> FeedElement -> SMTPServer
smtpServer _ _ = SMTPServer
  (Just $ Authentication PLAIN "user" "password")
  (StartTls "smtp.server" defaultSettingsSMTPSTARTTLS)
Synopsis

Documentation

data FormatMail Source #

How to format outgoing mails from feed elements

Constructors

FormatMail 

Fields

data Authentication Source #

How to authenticate to the SMTP server

defaultFormatFrom :: Feed -> FeedElement -> Address Source #

Fill addressName with the feed title and, if available, the authors' names.

This function leaves addressEmail empty. You are expected to fill it adequately, because many SMTP servers enforce constraints on the From: email.

defaultFormatSubject :: Feed -> FeedElement -> Text Source #

Fill mail subject with the element title

defaultFormatBody :: Feed -> FeedElement -> Text Source #

Fill mail body with:

  • a list of links associated to the element
  • the element's content or description/summary

buildMail :: FormatMail -> UTCTime -> TimeZone -> Feed -> FeedElement -> Mail Source #

Build mail from a given feed

module Imm.Hooks

sendMimeMail' #

Arguments

:: String

receiver

-> String

sender

-> String

subject

-> Text

plain text body

-> Text

html body

-> [(Text, Text, ByteString)]

attachments: [(content_type, file_name, content)]

-> SMTPConnection 
-> IO () 

Send a mime mail. The attachments are included with in-memory ByteString.

sendMimeMail #

Arguments

:: String

receiver

-> String

sender

-> String

subject

-> Text

plain text body

-> Text

html body

-> [(Text, FilePath)]

attachments: [(content_type, path)]

-> SMTPConnection 
-> IO () 

Send a mime mail. The attachments are included with the file path.

sendPlainTextMail #

Arguments

:: String

receiver

-> String

sender

-> String

subject

-> Text

body

-> SMTPConnection

the connection

-> IO () 

Send a plain text mail.

doSMTPStream :: BSStream -> (SMTPConnection -> IO a) -> IO a #

doSMTPStream is similar to doSMTPPort, except that its argument is a Stream data instead of hostname and port number.

doSMTP :: String -> (SMTPConnection -> IO a) -> IO a #

doSMTP is similar to doSMTPPort, except that it does not require port number but connects to the server with port 25.

doSMTPPort :: String -> PortNumber -> (SMTPConnection -> IO a) -> IO a #

doSMTPPort open a connection, and do an IO action with the connection, and then close it.

sendMail #

Arguments

:: String

sender mail

-> [String]

receivers

-> ByteString

data

-> SMTPConnection 
-> IO () 

sending a mail to a server. This is achieved by sendMessage. If something is wrong, it raises an IOexception.

authenticate :: AuthType -> UserName -> Password -> SMTPConnection -> IO Bool #

This function will return True if the authentication succeeds. Here's an example of sending a mail with a server that requires authentication:

   authSucceed <- authenticate PLAIN "username" "password" conn
   if authSucceed
       then sendPlainTextMail "receiver@server.com" "sender@server.com" "subject" (T.pack "Hello!") conn
       else print "Authentication failed."

closeSMTP :: SMTPConnection -> IO () #

close the connection. This function send the QUIT method, so you do not have to QUIT method explicitly.

sendCommand :: SMTPConnection -> Command -> IO (ReplyCode, ByteString) #

send a method to a server

connectStream :: BSStream -> IO SMTPConnection #

create SMTPConnection from already connected Stream

connectSMTP #

Arguments

:: String

name of the server

-> IO SMTPConnection 

connecting SMTP server with the specified name and port 25.

connectSMTPPort #

Arguments

:: String

name of the server

-> PortNumber

port number

-> IO SMTPConnection 

connecting SMTP server with the specified name and port number.

data AuthType #

Constructors

PLAIN 
LOGIN 
CRAM_MD5 
Instances
Eq AuthType 
Instance details

Defined in Network.HaskellNet.Auth

Show AuthType 
Instance details

Defined in Network.HaskellNet.Auth

doSMTPSSL :: String -> (SMTPConnection -> IO a) -> IO a #

quotedPrintable :: Bool -> ByteString -> Builder #

The first parameter denotes whether the input should be treated as text. If treated as text, then CRs will be stripped and LFs output as CRLFs. If binary, then CRs and LFs will be escaped.

addAttachmentsBS :: [(Text, Text, ByteString)] -> Mail -> Mail #

Since 0.4.7

addAttachmentBSCid #

Arguments

:: Text

content type

-> Text

file name

-> ByteString

content

-> Text

content ID

-> Mail 
-> Mail 

Since: mime-mail-0.4.12

addAttachmentBS #

Arguments

:: Text

content type

-> Text

file name

-> ByteString

content

-> Mail 
-> Mail 

Add an attachment from a ByteString and construct a Part.

Since 0.4.7

addAttachmentCid #

Arguments

:: Text

content type

-> FilePath

file name

-> Text

content ID

-> Mail 
-> IO Mail 

Add an attachment from a file and construct a Part with the specified content id in the Content-ID header.

Since: mime-mail-0.4.12

addAttachment :: Text -> FilePath -> Mail -> IO Mail #

Add an attachment from a file and construct a Part.

htmlPart :: Text -> Part #

Construct a UTF-8-encoded html Part.

plainPart :: Text -> Part #

Construct a UTF-8-encoded plain-text Part.

addPart :: Alternatives -> Mail -> Mail #

Add an Alternative to the Mails parts.

To e.g. add a plain text body use > addPart [plainPart body] (emptyMail from)

simpleMailInMemory #

Arguments

:: Address

to

-> Address

from

-> Text

subject

-> Text

plain body

-> Text

HTML body

-> [(Text, Text, ByteString)]

content type, file name and contents of attachments

-> Mail 

A simple interface for generating an email with HTML and plain-text alternatives and some ByteString attachments.

Since 0.4.7

simpleMail' #

Arguments

:: Address

to

-> Address

from

-> Text

subject

-> Text

body

-> Mail 

A simple interface for generating an email with only plain-text body.

simpleMail #

Arguments

:: Address

to

-> Address

from

-> Text

subject

-> Text

plain body

-> Text

HTML body

-> [(Text, FilePath)]

content type and path of attachments

-> IO Mail 

A simple interface for generating an email with HTML and plain-text alternatives and some file attachments.

Note that we use lazy IO for reading in the attachment contents.

renderSendMailCustom #

Arguments

:: FilePath

sendmail executable path

-> [String]

sendmail command-line options

-> Mail

mail to render and send

-> IO () 

Render an email message and send via the specified sendmail executable with specified options.

sendmailCustomCaptureOutput :: FilePath -> [String] -> ByteString -> IO (ByteString, ByteString) #

Like sendmailCustom, but also returns sendmail's output to stderr and stdout as strict ByteStrings.

Since 0.4.9

sendmailCustom #

Arguments

:: FilePath

sendmail executable path

-> [String]

sendmail command-line options

-> ByteString

mail message as lazy bytestring

-> IO () 

Send a fully-formed email message via the specified sendmail executable with specified options.

renderSendMail :: Mail -> IO () #

Render an email message and send via the default sendmail executable with default options.

renderMail' :: Mail -> IO ByteString #

Like renderMail, but generates a random boundary.

renderAddress :: Address -> Text #

Format an E-Mail address according to the name-addr form (see: RFC5322 § 3.4 "Address specification", i.e: [display-name] '<'addr-spec'>') This can be handy for adding custom headers that require such format.

Since: mime-mail-0.4.11

renderMail :: RandomGen g => g -> Mail -> (ByteString, g) #

Render a Mail with a given RandomGen for producing boundaries.

emptyMail :: Address -> Mail #

A mail message with the provided from address and no other fields filled in.

randomString :: RandomGen d => Int -> d -> (String, d) #

Generates a random sequence of alphanumerics of the given length.

newtype Boundary #

MIME boundary between parts of a message.

Constructors

Boundary 

Fields

Instances
Eq Boundary 
Instance details

Defined in Network.Mail.Mime

Show Boundary 
Instance details

Defined in Network.Mail.Mime

Random Boundary 
Instance details

Defined in Network.Mail.Mime

data Mail #

An entire mail message.

Constructors

Mail 

Fields

Instances
Show Mail 
Instance details

Defined in Network.Mail.Mime

Methods

showsPrec :: Int -> Mail -> ShowS #

show :: Mail -> String #

showList :: [Mail] -> ShowS #

data Address #

Constructors

Address 
Instances
Eq Address 
Instance details

Defined in Network.Mail.Mime

Methods

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

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

Show Address 
Instance details

Defined in Network.Mail.Mime

IsString Address 
Instance details

Defined in Network.Mail.Mime

Methods

fromString :: String -> Address #

data Encoding #

How to encode a single part. You should use Base64 for binary data.

Instances
Eq Encoding 
Instance details

Defined in Network.Mail.Mime

Show Encoding 
Instance details

Defined in Network.Mail.Mime

type Alternatives = [Part] #

Multiple alternative representations of the same data. For example, you could provide a plain-text and HTML version of a message.

data Part #

A single part of a multipart message.

Constructors

Part 

Fields

Instances
Eq Part 
Instance details

Defined in Network.Mail.Mime

Methods

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

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

Show Part 
Instance details

Defined in Network.Mail.Mime

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

type Headers = [(ByteString, Text)] #