hsemail-1.0: Internet Message ParsersContentsIndex
Text.ParserCombinators.Parsec.Rfc2821
Portabilityportable
Stabilityprovisional
Maintainersimons@cryp.to
Contents
ESMTP State Machine
Data Types for SMTP Commands
Data Types for SMTP Replies
Command Parsers
Argument Parsers
Helper Functions
Description
This module exports parser combinators for the grammar described in RFC2821, "Simple Mail Transfer Protocol", http://www.faqs.org/rfcs/rfc2821.html.
Synopsis
data SessionState
= Unknown
| HaveHelo
| HaveMailFrom
| HaveRcptTo
| HaveData
| HaveQuit
data Event
= Greeting
| SayHelo String
| SayHeloAgain String
| SayEhlo String
| SayEhloAgain String
| SetMailFrom Mailbox
| AddRcptTo Mailbox
| StartData
| Deliver
| NeedHeloFirst
| NeedMailFromFirst
| NeedRcptToFirst
| NotImplemened
| ResetState
| SayOK
| SeeksHelp String
| Shutdown
| SyntaxErrorIn String
| Unrecognized String
type SmtpdFSM = State SessionState Event
smtpdFSM :: String -> SmtpdFSM
handleSmtpCmd :: SmtpCmd -> SmtpdFSM
data SmtpCmd
= Helo String
| Ehlo String
| MailFrom Mailbox
| RcptTo Mailbox
| Data
| Rset
| Send Mailbox
| Soml Mailbox
| Saml Mailbox
| Vrfy String
| Expn String
| Help String
| Noop
| Quit
| Turn
| WrongArg String ParseError
data Mailbox = Mailbox [String] String String
nullPath :: Mailbox
postmaster :: Mailbox
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
reply :: Int -> Int -> Int -> [String] -> SmtpReply
isSuccess :: SmtpReply -> Bool
isFailure :: SmtpReply -> Bool
isShutdown :: SmtpReply -> Bool
type SmtpParser st = CharParser st SmtpCmd
smtpCmd :: SmtpParser st
smtpData :: SmtpParser st
rset :: SmtpParser st
quit :: SmtpParser st
turn :: SmtpParser st
helo :: SmtpParser st
ehlo :: SmtpParser st
mail :: SmtpParser st
rcpt :: SmtpParser st
send :: SmtpParser st
soml :: SmtpParser st
saml :: SmtpParser st
vrfy :: SmtpParser st
expn :: SmtpParser st
help :: SmtpParser st
noop :: SmtpParser st
from_path :: CharParser st Mailbox
to_path :: CharParser st Mailbox
path :: CharParser st Mailbox
mailbox :: CharParser st Mailbox
local_part :: CharParser st String
domain :: CharParser st String
a_d_l :: CharParser st [String]
at_domain :: CharParser st String
address_literal :: CharParser st String
ipv4_literal :: CharParser st String
ipv4addr :: CharParser st String
subdomain :: CharParser st String
dot_string :: CharParser st String
atom :: CharParser a String
snum :: CharParser st String
number :: CharParser st String
word :: CharParser st String
fixCRLF :: String -> String
mkCmd0 :: String -> a -> CharParser st a
mkCmd1 :: String -> (a -> SmtpCmd) -> CharParser st a -> CharParser st SmtpCmd
tokenList :: CharParser st String -> Char -> CharParser st String
ESMTP State Machine
data SessionState
Constructors
Unknown
HaveHelo
HaveMailFrom
HaveRcptTo
HaveData
HaveQuit
show/hide Instances
data Event
Constructors
Greetingreserved for the user
SayHelo String
SayHeloAgain String
SayEhlo String
SayEhloAgain String
SetMailFrom Mailbox
AddRcptTo Mailbox
StartData
Deliverreserved for the user
NeedHeloFirst
NeedMailFromFirst
NeedRcptToFirst
NotImplemenedTurn, Send, Soml, Saml, Vrfy, and Expn.
ResetState
SayOKTriggered in case of Noop or when Rset is used before we even have a state.
SeeksHelp StringThe parameter may be [].
Shutdown
SyntaxErrorIn String
Unrecognized String
show/hide Instances
type SmtpdFSM = State SessionState Event
smtpdFSM :: String -> SmtpdFSM
Parse a line of SMTP dialogue and run handleSmtpCmd to determine the Event. In case of syntax errors, SyntaxErrorIn or Unrecognized will be returned. Inputs must be terminated with crlf. See fixCRLF.
handleSmtpCmd :: SmtpCmd -> SmtpdFSM
For those who want to parse the SmtpCmd themselves. Calling this function in HaveQuit or HaveData will fail an assertion. If assert is disabled, it will return respectively Shutdown and StartData again.
Data Types for SMTP Commands
data SmtpCmd
The smtpCmd parser will create this data type from a string. Note that all command parsers expect their input to be terminated with crlf.
Constructors
Helo String
Ehlo String
MailFrom MailboxMight be nullPath.
RcptTo MailboxMight be postmaster.
Data
Rset
Send Mailbox
Soml Mailbox
Saml Mailbox
Vrfy String
Expn String
Help StringMight be [].
NoopOptional argument ignored.
Quit
Turn
WrongArg String ParseErrorWhen a valid command has been recognized, but the argument parser fails, then this type will be returned. The String contains the name of the command (in all upper-case) and the ParseError is, obviously, the error description.
show/hide Instances
data Mailbox
The most general e-mail address has the form: <[@route,...:]user@domain>. This type, too, supports show and read. Note that a "shown" address is always enclosed in angular brackets. When comparing two mailboxes for equality, the hostname is case-insensitive.
Constructors
Mailbox [String] String String
show/hide Instances
nullPath :: Mailbox
nullPath = Mailbox [] "" "" = "<>"
postmaster :: Mailbox
postmaster = Mailbox [] "postmaster" "" = "<postmaster>"
Data Types for SMTP Replies
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.

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
Constructors
Code SuccessCode Category Int
show/hide Instances
data SuccessCode
Constructors
Unused0
PreliminarySuccess
Success
IntermediateSuccess
TransientFailure
PermanentFailure
show/hide Instances
data Category
Constructors
Syntax
Information
Connection
Unspecified3
Unspecified4
MailSystem
show/hide Instances
reply :: Int -> Int -> Int -> [String] -> SmtpReply
Construct a Reply. Fails assert if invalid numbers are given.
isSuccess :: SmtpReply -> Bool
A reply constitutes "success" if the status code is any of PreliminarySuccess, Success, or IntermediateSuccess.
isFailure :: SmtpReply -> Bool
A reply constitutes "failure" if the status code is either PermanentFailure or TransientFailure.
isShutdown :: SmtpReply -> Bool
The replies 221 and 421 signify Shutdown.
Command Parsers
type SmtpParser st = CharParser st SmtpCmd
The SMTP parsers defined here correspond to the commands specified in RFC2821, so I won't document them individually.
smtpCmd :: SmtpParser st
This parser recognizes any of the SMTP commands defined below. Note that all command parsers expect their input to be terminated with crlf.
smtpData :: SmtpParser st
The parser name "data" was taken.
rset :: SmtpParser st
quit :: SmtpParser st
turn :: SmtpParser st
helo :: SmtpParser st
ehlo :: SmtpParser st
mail :: SmtpParser st
rcpt :: SmtpParser st
send :: SmtpParser st
soml :: SmtpParser st
saml :: SmtpParser st
vrfy :: SmtpParser st
expn :: SmtpParser st
help :: SmtpParser st
noop :: SmtpParser st
May have an optional word argument, but it is ignored.
Argument Parsers
from_path :: CharParser st Mailbox
to_path :: CharParser st Mailbox
path :: CharParser st Mailbox
mailbox :: CharParser st Mailbox
local_part :: CharParser st String
domain :: CharParser st String
a_d_l :: CharParser st [String]
at_domain :: CharParser st String
address_literal :: CharParser st String
TODO: Add IPv6 address and general literals
ipv4_literal :: CharParser st String
ipv4addr :: CharParser st String
subdomain :: CharParser st String
dot_string :: CharParser st String
atom :: CharParser a String
snum :: CharParser st String
number :: CharParser st String
word :: CharParser st String
This is a useful addition: The parser accepts an atom or a quoted_string.
Helper Functions
fixCRLF :: String -> String
Make the string crlf terminated no matter what. '\n' is expanded, otherwise crlf is appended. Note that if the string was terminated incorrectly before, it still is. This function is useful when reading input with hGetLine which removes the end-of-line delimiter.
mkCmd0 :: String -> a -> CharParser st a
Construct a parser for a command without arguments. Expects crlf!
mkCmd1 :: String -> (a -> SmtpCmd) -> CharParser st a -> CharParser st SmtpCmd
Construct a parser for a command with an argument, which the given parser will handle. The result of the argument parser will be applied to the type constructor before it is returned. Expects crlf!
tokenList :: CharParser st String -> Char -> CharParser st String
Produced by Haddock version 0.8