SMTPClient-1.1.0: A simple SMTP client library

Safe HaskellNone

Network.SMTP.Client

Description

An SMTP client in the IO Monad.

Data structures for representing SMTP status codes and email messages are re-exported here from Text.ParserCombinators.Parsec.Rfc2821 and Text.ParserCombinators.Parsec.Rfc2822 in the hsemail package.

Here's a working example:

 import Network.SMTP.ClientSession
 import Network.SMTP.Client
 import Network.Socket
 import System.Time
 import System.IO
 import Data.IORef
 
 myDomain = "example.com"
 smtpHost = "mail.example.com"    -- <-- Your SMTP server here
 
 main = do
     now <- getClockTime
     nowCT <- toCalendarTime now
     let message = Message [
                 From [NameAddr (Just "Mr. Nobody") "nobody@example.com"],
                 To   [NameAddr (Just "Mr. Somebody") "somebody@example.com"],
                 Subject "I'm using SMTPClient!",
                 Date nowCT
             ]
             ("Dear Sir,\n"++
              "It has come to my attention that this is an email.\n"++
              "Yours sincerely,\n"++
              "Mr. Nobody\n")
     addrs <- getAddrInfo Nothing (Just smtpHost) (Just "25")
     putStrLn $ "connecting to "++show (map addrAddress addrs)
     sentRef <- newIORef []
     sendSMTP' (hPutStrLn stderr) (Just sentRef) myDomain addrs [message]
     statuses <- readIORef sentRef
     -- If no exception was caught, statuses is guaranteed to be
     -- the same length as the list of input messages, therefore head won't fail here.
     case head statuses of
         Nothing     -> putStrLn "Message successfully sent"
         Just status -> putStrLn $ "Message send failed with status "++show status

Synopsis

Documentation

sendSMTPSource

Arguments

:: Maybe (IORef [Maybe SmtpReply])

For storing failure statuses of messages sent so far

-> String

Domain name for EHLO command

-> [AddrInfo]

Network addresses of SMTP server (will try each in turn)

-> [Message]

List of messages to send

-> IO () 

Send a list of email messages to an SMTP server. Throws SMTPException on failure at the communication protocol level, and it can also throw socket-level exceptions.

The optional IORef is used to store a list of statuses for messages sent so far, where Nothing means success. The list elements correspond to the elements of the input message list. If the caller catches an exception, this list is likely to be shorter than the input message list: The length of the list indicates how many messages were dispatched. If no exception is caught, the length of the statuses will equal the length of the input messages list.

The message body may use either "\n" or "\r\n" as an end-of-line marker and in either case it will be sent correctly to the server.

sendSMTP'Source

Arguments

:: (String -> IO ())

Diagnostic log function

-> Maybe (IORef [Maybe SmtpReply])

For storing failure statuses of messages sent so far

-> String

Domain name for EHLO command

-> [AddrInfo]

Network addresses of SMTP server (will try each in turn)

-> [Message]

List of messages to send

-> IO () 

Like sendSMTP but takes an additional function for logging all input and output for diagnostic purposes.

processSMTPSource

Arguments

:: (String -> IO ())

Diagnostic log function

-> Maybe (IORef [Maybe SmtpReply])

For storing failure statuses of messages sent so far

-> Handle 
-> SMTPState 
-> IO () 

A lower level function that does the I/O processing for an SMTP client session on a handle. Returns when the session has completed, with the handle still open.

data SMTPException Source

An exception indicating a communications failure at the level of the SMTP protocol.

Constructors

SMTPException String 

data SmtpReply

An SMTP reply is a three-digit return code plus some waste of bandwidth called "comments". This is what the list of strings is for; one string per line in the reply. show will append an "\r\n" end-of-line marker to each entry in that list, so that the resulting string is ready to be sent back to the peer. For example:

>>> show $ Reply (Code Success MailSystem 0) ["worked", "like", "a charm" ]
"250-worked\r\n250-like\r\n250 a charm\r\n"

If the message is an empty list [], a default text will be constructed:

>>> show $ Reply (Code Success MailSystem 0) []
"250 Success in category MailSystem\r\n"

Constructors

Reply SmtpCode [String] 

Instances

data SmtpCode

Instances

data GenericMessage a

This data type repesents a parsed Internet Message as defined in this RFC. It consists of an arbitrary number of header lines, represented in the Field data type, and a message body, which may be empty.

Constructors

Message [Field] a 

Instances

data Field

This data type represents any of the header fields defined in this RFC. Each of the various instances contains with the return value of the corresponding parser.

Instances

data NameAddr

A NameAddr is composed of an optional realname a mandatory e-mail address.

Instances