| Portability | portable |
|---|---|
| Stability | provisional |
| Maintainer | simons@cryp.to |
| Safe Haskell | Safe-Inferred |
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.
- 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
- data Mailbox = Mailbox [String] String String
- nullPath :: Mailbox
- postmaster :: Mailbox
- data SmtpReply = Reply SmtpCode [String]
- data SmtpCode = Code SuccessCode Category Int
- data SuccessCode
- 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
- mail :: SmtpParser st
- ehlo :: SmtpParser st
- helo :: SmtpParser st
- turn :: SmtpParser st
- quit :: SmtpParser st
- rcpt :: SmtpParser st
- expn :: SmtpParser st
- vrfy :: SmtpParser st
- saml :: SmtpParser st
- soml :: SmtpParser st
- send :: 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 Source
Constructors
| Unknown | |
| HaveHelo | |
| HaveMailFrom | |
| HaveRcptTo | |
| HaveData | |
| HaveQuit |
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 | |
| ResetState | |
| SayOK | Triggered in case of |
| SeeksHelp String | The parameter may be |
| Shutdown | |
| SyntaxErrorIn String | |
| Unrecognized String |
type SmtpdFSM = State SessionState EventSource
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.
Data Types for SMTP Commands
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 |
| RcptTo Mailbox | Might be |
| 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 |
postmaster = Mailbox [] "postmaster" "" = "<postmaster>"
Data Types for SMTP Replies
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"
data SuccessCode Source
Constructors
| Syntax | |
| Information | |
| Connection | |
| Unspecified3 | |
| Unspecified4 | |
| MailSystem |
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.
rset :: SmtpParser stSource
mail :: SmtpParser stSource
ehlo :: SmtpParser stSource
helo :: SmtpParser stSource
turn :: SmtpParser stSource
quit :: SmtpParser stSource
rcpt :: SmtpParser stSource
expn :: SmtpParser stSource
vrfy :: SmtpParser stSource
saml :: SmtpParser stSource
soml :: SmtpParser stSource
send :: SmtpParser stSource
help :: SmtpParser stSource
noop :: SmtpParser stSource
May have an optional word argument, but it is ignored.
Argument Parsers
from_path :: CharParser st MailboxSource
to_path :: CharParser st MailboxSource
path :: CharParser st MailboxSource
mailbox :: CharParser st MailboxSource
local_part :: CharParser st StringSource
domain :: CharParser st StringSource
a_d_l :: CharParser st [String]Source
at_domain :: CharParser st StringSource
address_literal :: CharParser st StringSource
TODO: Add IPv6 address and general literals
ipv4addr :: CharParser st StringSource
subdomain :: CharParser st StringSource
dot_string :: CharParser st StringSource
atom :: CharParser a StringSource
snum :: CharParser st StringSource
number :: CharParser st StringSource
word :: CharParser st StringSource
This is a useful addition: The parser accepts an atom
or a quoted_string.
Helper Functions
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!
tokenList :: CharParser st String -> Char -> CharParser st StringSource