Copyright | (c) 2013 Peter Simons |
---|---|
License | BSD3 |
Maintainer | simons@cryp.to |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This module exports parser combinators for the grammar described in RFC2821, "Simple Mail Transfer Protocol", http://www.faqs.org/rfcs/rfc2821.html.
- data SessionState
- 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
- reply :: Int -> Int -> Int -> [String] -> SmtpReply
- isSuccess :: SmtpReply -> Bool
- isFailure :: SmtpReply -> Bool
- isShutdown :: SmtpReply -> Bool
- smtpCmd :: Stream s m Char => ParsecT s u m SmtpCmd
- smtpData :: Stream s m Char => ParsecT s u m SmtpCmd
- rset :: Stream s m Char => ParsecT s u m SmtpCmd
- quit :: Stream s m Char => ParsecT s u m SmtpCmd
- turn :: Stream s m Char => ParsecT s u m SmtpCmd
- helo :: Stream s m Char => ParsecT s u m SmtpCmd
- ehlo :: Stream s m Char => ParsecT s u m SmtpCmd
- mail :: Stream s m Char => ParsecT s u m SmtpCmd
- rcpt :: Stream s m Char => ParsecT s u m SmtpCmd
- send :: Stream s m Char => ParsecT s u m SmtpCmd
- soml :: Stream s m Char => ParsecT s u m SmtpCmd
- saml :: Stream s m Char => ParsecT s u m SmtpCmd
- vrfy :: Stream s m Char => ParsecT s u m SmtpCmd
- expn :: Stream s m Char => ParsecT s u m SmtpCmd
- help :: Stream s m Char => ParsecT s u m SmtpCmd
- noop :: Stream s m Char => ParsecT s u m SmtpCmd
- from_path :: Stream s m Char => ParsecT s u m Mailbox
- to_path :: Stream s m Char => ParsecT s u m Mailbox
- path :: Stream s m Char => ParsecT s u m Mailbox
- mailbox :: Stream s m Char => ParsecT s u m Mailbox
- local_part :: Stream s m Char => ParsecT s u m String
- domain :: Stream s m Char => ParsecT s u m String
- a_d_l :: Stream s m Char => ParsecT s u m [String]
- at_domain :: Stream s m Char => ParsecT s u m String
- address_literal :: Stream s m Char => ParsecT s u m String
- ipv4_literal :: Stream s m Char => ParsecT s u m String
- ipv4addr :: Stream s m Char => ParsecT s u m String
- subdomain :: Stream s m Char => ParsecT s u m String
- dot_string :: Stream s m Char => ParsecT s u m String
- atom :: Stream s m Char => ParsecT s u m String
- snum :: Stream s m Char => ParsecT s u m String
- number :: Stream s m Char => ParsecT s u m String
- word :: Stream s m Char => ParsecT s u m String
- fixCRLF :: String -> String
- mkCmd0 :: Stream s m Char => String -> a -> ParsecT s u m a
- mkCmd1 :: Stream s m Char => String -> (a -> SmtpCmd) -> ParsecT s u m a -> ParsecT s u m SmtpCmd
- tokenList :: Stream s m Char => ParsecT s u m String -> Char -> ParsecT s u m String
ESMTP State Machine
data SessionState Source #
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 |
smtpdFSM :: String -> SmtpdFSM Source #
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 Source #
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
.
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 Source #
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 #
isSuccess :: SmtpReply -> Bool Source #
A reply constitutes "success" if the status code is
any of PreliminarySuccess
, Success
, or
IntermediateSuccess
.
isFailure :: SmtpReply -> Bool Source #
A reply constitutes "failure" if the status code is
either PermanentFailure
or TransientFailure
.
Command Parsers
smtpCmd :: Stream s m Char => ParsecT s u m SmtpCmd Source #
The SMTP parsers defined here correspond to the commands specified in RFC2821, so I won't document them individually.
This parser recognizes any of the SMTP commands defined
below. Note that all command parsers expect their input
to be terminated with crlf
.
noop :: Stream s m Char => ParsecT s u m SmtpCmd Source #
May have an optional word
argument, but it is ignored.
Argument Parsers
address_literal :: Stream s m Char => ParsecT s u m String Source #
TODO: Add IPv6 address and general literals
word :: Stream s m Char => ParsecT s u m String Source #
This is a useful addition: The parser accepts an atom
or a quoted_string
.
Helper Functions
mkCmd0 :: Stream s m Char => String -> a -> ParsecT s u m a Source #
Construct a parser for a command without arguments.
Expects crlf
!
mkCmd1 :: Stream s m Char => String -> (a -> SmtpCmd) -> ParsecT s u m a -> ParsecT s u m SmtpCmd Source #
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
!