hsemail-1.1

PortabilityHaskell 2-pre
Stabilityprovisional
Maintainersimons@cryp.to

Text.ParserCombinators.Parsec.Rfc2821

Contents

Description

This module exports parser combinators for the grammar described in RFC2821, "Simple Mail Transfer Protocol", http://www.faqs.org/rfcs/rfc2821.html.

Synopsis

ESMTP State Machine

data Event Source

Constructors

Greeting

reserved for the user

SayHelo String 
SayHeloAgain String 
SayEhlo String 
SayEhloAgain String 
SetMailFrom Mailbox 
AddRcptTo Mailbox 
StartData 
Deliver

reserved for the user

NeedHeloFirst 
NeedMailFromFirst 
NeedRcptToFirst 
NotImplemened

Turn, Send, Soml, Saml, Vrfy, and Expn.

ResetState 
SayOK

Triggered in case of Noop or when Rset is used before we even have a state.

SeeksHelp String

The parameter may be [].

Shutdown 
SyntaxErrorIn String 
Unrecognized String 

Instances

smtpdFSM :: String -> SmtpdFSMSource

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 -> SmtpdFSMSource

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 Source

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 Mailbox

Might be nullPath.

RcptTo Mailbox

Might be postmaster.

Data 
Rset 
Send Mailbox 
Soml Mailbox 
Saml Mailbox 
Vrfy String 
Expn String 
Help String

Might be [].

Noop

Optional argument ignored.

Quit 
Turn 
WrongArg String ParseError

When 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.

Instances

data Mailbox Source

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 

nullPath :: MailboxSource

nullPath = Mailbox [] "" "" = "<>"

postmaster :: MailboxSource

postmaster = Mailbox [] "postmaster" "" = "<postmaster>"

Data Types for SMTP Replies

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] 

Instances

data SmtpCode Source

Instances

reply :: Int -> Int -> Int -> [String] -> SmtpReplySource

Construct a Reply. Fails assert if invalid numbers are given.

isSuccess :: SmtpReply -> BoolSource

A reply constitutes "success" if the status code is any of PreliminarySuccess, Success, or IntermediateSuccess.

isFailure :: SmtpReply -> BoolSource

A reply constitutes "failure" if the status code is either PermanentFailure or TransientFailure.

isShutdown :: SmtpReply -> BoolSource

The replies 221 and 421 signify Shutdown.

Command Parsers

type SmtpParser st = CharParser st SmtpCmdSource

The SMTP parsers defined here correspond to the commands specified in RFC2821, so I won't document them individually.

smtpCmd :: SmtpParser stSource

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 stSource

The parser name "data" was taken.

noop :: SmtpParser stSource

May have an optional word argument, but it is ignored.

Argument Parsers

address_literal :: CharParser st StringSource

TODO: Add IPv6 address and general literals

word :: CharParser st StringSource

This is a useful addition: The parser accepts an atom or a quoted_string.

Helper Functions

fixCRLF :: String -> StringSource

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 System.IO.hGetLine which removes the end-of-line delimiter.

mkCmd0 :: String -> a -> CharParser st aSource

Construct a parser for a command without arguments. Expects crlf!

mkCmd1 :: String -> (a -> SmtpCmd) -> CharParser st a -> CharParser st SmtpCmdSource

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!