Safe Haskell | None |
---|---|
Language | Haskell98 |
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
- data SendMailSettings = SendMailSettings (Feed -> FeedElement -> SMTPServer) FormatMail
- data FormatMail = FormatMail {
- formatFrom :: Feed -> FeedElement -> Address
- formatSubject :: Feed -> FeedElement -> Text
- formatBody :: Feed -> FeedElement -> Text
- formatTo :: Feed -> FeedElement -> [Address]
- data SMTPServer = SMTPServer (Maybe Authentication) ConnectionSettings
- data Authentication = Authentication AuthType Username Password
- data ConnectionSettings
- type ServerName = String
- type Password = String
- type Username = String
- mkHandle :: MonadBase IO m => SendMailSettings -> Handle m
- defaultFormatFrom :: Feed -> FeedElement -> Address
- defaultFormatSubject :: Feed -> FeedElement -> Text
- defaultFormatBody :: Feed -> FeedElement -> Text
- authenticate_ :: SMTPConnection -> Authentication -> IO Bool
- withSMTPConnection :: SMTPServer -> (SMTPConnection -> IO a) -> IO a
- buildMail :: FormatMail -> UTCTime -> TimeZone -> Feed -> FeedElement -> Mail
- module Imm.Hooks
- sendMimeMail2 :: Mail -> SMTPConnection -> IO ()
- sendMimeMail' :: String -> String -> String -> Text -> Text -> [(Text, Text, ByteString)] -> SMTPConnection -> IO ()
- sendMimeMail :: String -> String -> String -> Text -> Text -> [(Text, FilePath)] -> SMTPConnection -> IO ()
- sendPlainTextMail :: String -> String -> String -> Text -> SMTPConnection -> IO ()
- doSMTPStream :: BSStream -> (SMTPConnection -> IO a) -> IO a
- doSMTP :: String -> (SMTPConnection -> IO a) -> IO a
- doSMTPPort :: String -> PortNumber -> (SMTPConnection -> IO a) -> IO a
- sendMail :: String -> [String] -> ByteString -> SMTPConnection -> IO ()
- authenticate :: AuthType -> UserName -> Password -> SMTPConnection -> IO Bool
- closeSMTP :: SMTPConnection -> IO ()
- sendCommand :: SMTPConnection -> Command -> IO (ReplyCode, ByteString)
- connectStream :: BSStream -> IO SMTPConnection
- connectSMTP :: String -> IO SMTPConnection
- connectSMTPPort :: String -> PortNumber -> IO SMTPConnection
- data SMTPConnection
- data Command
- data Response
- = Ok
- | SystemStatus
- | HelpMessage
- | ServiceReady
- | ServiceClosing
- | UserNotLocal
- | CannotVerify
- | StartMailInput
- | ServiceNotAvailable
- | MailboxUnavailable
- | ErrorInProcessing
- | InsufficientSystemStorage
- | SyntaxError
- | ParameterError
- | CommandNotImplemented
- | BadSequence
- | ParameterNotImplemented
- | MailboxUnavailableError
- | UserNotLocalError
- | ExceededStorage
- | MailboxNotAllowed
- | TransactionFailed
- data AuthType
- defaultSettingsSMTPSTARTTLS :: Settings
- defaultSettingsSMTPSSL :: Settings
- doSMTPSTARTTLSWithSettings :: String -> Settings -> (SMTPConnection -> IO a) -> IO a
- doSMTPSTARTTLS :: String -> (SMTPConnection -> IO a) -> IO a
- doSMTPSSLWithSettings :: String -> Settings -> (SMTPConnection -> IO a) -> IO a
- doSMTPSSL :: String -> (SMTPConnection -> IO a) -> IO a
- connectSMTPSTARTTLSWithSettings :: String -> Settings -> IO SMTPConnection
- connectSMTPSTARTTLS :: String -> IO SMTPConnection
- connectSMTPSSLWithSettings :: String -> Settings -> IO SMTPConnection
- connectSMTPSSL :: String -> IO SMTPConnection
- data Settings = Settings {}
- quotedPrintable :: Bool -> ByteString -> Builder
- addAttachmentsBS :: [(Text, Text, ByteString)] -> Mail -> Mail
- addAttachmentBSCid :: Text -> Text -> ByteString -> Text -> Mail -> Mail
- addAttachmentBS :: Text -> Text -> ByteString -> Mail -> Mail
- addAttachments :: [(Text, FilePath)] -> Mail -> IO Mail
- addAttachmentCid :: Text -> FilePath -> Text -> Mail -> IO Mail
- addAttachment :: Text -> FilePath -> Mail -> IO Mail
- htmlPart :: Text -> Part
- plainPart :: Text -> Part
- addPart :: Alternatives -> Mail -> Mail
- simpleMailInMemory :: Address -> Address -> Text -> Text -> Text -> [(Text, Text, ByteString)] -> Mail
- simpleMail' :: Address -> Address -> Text -> Text -> Mail
- simpleMail :: Address -> Address -> Text -> Text -> Text -> [(Text, FilePath)] -> IO Mail
- renderSendMailCustom :: FilePath -> [String] -> Mail -> IO ()
- sendmailCustomCaptureOutput :: FilePath -> [String] -> ByteString -> IO (ByteString, ByteString)
- sendmailCustom :: FilePath -> [String] -> ByteString -> IO ()
- renderSendMail :: Mail -> IO ()
- renderMail' :: Mail -> IO ByteString
- renderAddress :: Address -> Text
- renderMail :: RandomGen g => g -> Mail -> (ByteString, g)
- emptyMail :: Address -> Mail
- randomString :: RandomGen d => Int -> d -> (String, d)
- newtype Boundary = Boundary {
- unBoundary :: Text
- data Mail = Mail {}
- data Address = Address {
- addressName :: Maybe Text
- addressEmail :: Text
- data Encoding
- type Alternatives = [Part]
- data Part = Part {}
- type Headers = [(ByteString, Text)]
Documentation
data SendMailSettings Source #
data FormatMail Source #
How to format outgoing mails from feed elements
FormatMail | |
|
data SMTPServer Source #
Instances
Eq SMTPServer Source # | |
Defined in Imm.Hooks.SendMail (==) :: SMTPServer -> SMTPServer -> Bool # (/=) :: SMTPServer -> SMTPServer -> Bool # | |
Show SMTPServer Source # | |
Defined in Imm.Hooks.SendMail showsPrec :: Int -> SMTPServer -> ShowS # show :: SMTPServer -> String # showList :: [SMTPServer] -> ShowS # |
data Authentication Source #
How to authenticate to the SMTP server
Instances
Eq Authentication Source # | |
Defined in Imm.Hooks.SendMail (==) :: Authentication -> Authentication -> Bool # (/=) :: Authentication -> Authentication -> Bool # | |
Show Authentication Source # | |
Defined in Imm.Hooks.SendMail showsPrec :: Int -> Authentication -> ShowS # show :: Authentication -> String # showList :: [Authentication] -> ShowS # |
data ConnectionSettings Source #
How to connect to the SMTP server
Instances
Eq ConnectionSettings Source # | |
Defined in Imm.Hooks.SendMail (==) :: ConnectionSettings -> ConnectionSettings -> Bool # (/=) :: ConnectionSettings -> ConnectionSettings -> Bool # | |
Show ConnectionSettings Source # | |
Defined in Imm.Hooks.SendMail showsPrec :: Int -> ConnectionSettings -> ShowS # show :: ConnectionSettings -> String # showList :: [ConnectionSettings] -> ShowS # |
type ServerName = String Source #
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
authenticate_ :: SMTPConnection -> Authentication -> IO Bool Source #
withSMTPConnection :: SMTPServer -> (SMTPConnection -> IO a) -> IO a Source #
buildMail :: FormatMail -> UTCTime -> TimeZone -> Feed -> FeedElement -> Mail Source #
Build mail from a given feed
module Imm.Hooks
sendMimeMail2 :: Mail -> SMTPConnection -> IO () #
:: 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
.
:: 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.
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.
:: 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
:: String | name of the server |
-> IO SMTPConnection |
connecting SMTP server with the specified name and port 25.
:: String | name of the server |
-> PortNumber | port number |
-> IO SMTPConnection |
connecting SMTP server with the specified name and port number.
data SMTPConnection #
doSMTPSTARTTLSWithSettings :: String -> Settings -> (SMTPConnection -> IO a) -> IO a #
doSMTPSTARTTLS :: String -> (SMTPConnection -> IO a) -> IO a #
doSMTPSSLWithSettings :: String -> Settings -> (SMTPConnection -> IO a) -> IO a #
connectSMTPSSL :: String -> IO SMTPConnection #
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
Since: mime-mail-0.4.12
:: Text | content type |
-> Text | file name |
-> ByteString | content |
Add an attachment from a ByteString
and construct a Part
.
Since 0.4.7
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
.
addPart :: Alternatives -> Mail -> Mail #
Add an Alternative
to the Mail
s parts.
To e.g. add a plain text body use > addPart [plainPart body] (emptyMail from)
:: Address | to |
-> Address | from |
-> Text | subject |
-> Text | plain body |
-> Text | HTML body |
-> [(Text, Text, ByteString)] | content type, file name and contents of attachments |
A simple interface for generating an email with HTML and plain-text
alternatives and some ByteString
attachments.
Since 0.4.7
A simple interface for generating an email with only plain-text body.
:: 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.
:: FilePath | sendmail executable path |
-> [String] | sendmail command-line options |
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
:: 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) #
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.
MIME boundary between parts of a message.
Instances
Eq Boundary | |
Show Boundary | |
Random Boundary | |
Defined in Network.Mail.Mime |
An entire mail message.
|
Address | |
|
How to encode a single part. You should use Base64
for binary data.
type Alternatives = [Part] #
Multiple alternative representations of the same data. For example, you could provide a plain-text and HTML version of a message.
A single part of a multipart message.
Part | |
|
type Headers = [(ByteString, Text)] #