SMTPClient-1.0: A simple SMTP clientSource codeContentsIndex
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.

Synopsis
sendSMTP :: Maybe (IORef [Maybe SmtpReply]) -> String -> SockAddr -> [Message] -> IO ()
sendSMTP' :: (String -> IO ()) -> Maybe (IORef [Maybe SmtpReply]) -> String -> SockAddr -> [Message] -> IO ()
processSMTP :: (String -> IO ()) -> Maybe (IORef [Maybe SmtpReply]) -> Handle -> SMTPState -> IO ()
data SMTPException = SMTPException String
data SmtpReply = Reply SmtpCode [String]
data SmtpCode = Code SuccessCode Category Int
data SuccessCode
= Unused0
| PreliminarySuccess
| Success
| IntermediateSuccess
| TransientFailure
| PermanentFailure
data Category
= Syntax
| Information
| Connection
| Unspecified3
| Unspecified4
| MailSystem
data Message = Message [Field] String
data Field
= OptionalField String String
| From [NameAddr]
| Sender NameAddr
| ReturnPath String
| ReplyTo [NameAddr]
| To [NameAddr]
| Cc [NameAddr]
| Bcc [NameAddr]
| MessageID String
| InReplyTo [String]
| References [String]
| Subject String
| Comments String
| Keywords [[String]]
| Date CalendarTime
| ResentDate CalendarTime
| ResentFrom [NameAddr]
| ResentSender NameAddr
| ResentTo [NameAddr]
| ResentCc [NameAddr]
| ResentBcc [NameAddr]
| ResentMessageID String
| ResentReplyTo [NameAddr]
| Received ([(String, String)], CalendarTime)
| ObsReceived [(String, String)]
data NameAddr = NameAddr {
nameAddr_name :: Maybe String
nameAddr_addr :: String
}
Documentation
sendSMTPSource
:: Maybe (IORef [Maybe SmtpReply])For storing failure statuses of messages sent so far
-> StringDomain name for EHLO command
-> SockAddrNetwork address of SMTP server
-> [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
:: String -> IO ()Diagnostic log function
-> Maybe (IORef [Maybe SmtpReply])For storing failure statuses of messages sent so far
-> StringDomain name for EHLO command
-> SockAddrNetwork address of SMTP server
-> [Message]List of messages to send
-> IO ()
Like sendSMTP but takes an additional function for logging all input and output for diagnostic purposes.
processSMTPSource
:: 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
show/hide Instances
data SmtpReply Source

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.

Here is an example:

*Rfc2821> print $ Reply (Code Success MailSystem 0) ["worked", "like", "a charm" ] 250-worked 250-like 250 a charm

If the message is [], you'll get a really helpful default text.

Constructors
Reply SmtpCode [String]
show/hide Instances
data SmtpCode Source
Constructors
Code SuccessCode Category Int
show/hide Instances
data SuccessCode Source
Constructors
Unused0
PreliminarySuccess
Success
IntermediateSuccess
TransientFailure
PermanentFailure
show/hide Instances
data Category Source
Constructors
Syntax
Information
Connection
Unspecified3
Unspecified4
MailSystem
show/hide Instances
data Message Source
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] String
show/hide Instances
data Field Source
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.
Constructors
OptionalField String String
From [NameAddr]
Sender NameAddr
ReturnPath String
ReplyTo [NameAddr]
To [NameAddr]
Cc [NameAddr]
Bcc [NameAddr]
MessageID String
InReplyTo [String]
References [String]
Subject String
Comments String
Keywords [[String]]
Date CalendarTime
ResentDate CalendarTime
ResentFrom [NameAddr]
ResentSender NameAddr
ResentTo [NameAddr]
ResentCc [NameAddr]
ResentBcc [NameAddr]
ResentMessageID String
ResentReplyTo [NameAddr]
Received ([(String, String)], CalendarTime)
ObsReceived [(String, String)]
show/hide Instances
data NameAddr Source
A NameAddr is composed of an optional realname a mandatory e-mail address.
Constructors
NameAddr
nameAddr_name :: Maybe String
nameAddr_addr :: String
show/hide Instances
Produced by Haddock version 2.6.0