| Copyright | (c) 2007-2019 Peter Simons |
|---|---|
| License | BSD3 |
| Maintainer | simons@cryp.to |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Text.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
- data EsmtpCmd
- data Mailbox = Mailbox [String] String String
- nullPath :: Mailbox
- postmaster :: Mailbox
- data EsmtpReply = Reply EsmtpCode [String]
- data EsmtpCode = Code SuccessCode Category Int
- data SuccessCode
- data Category
- reply :: Int -> Int -> Int -> [String] -> EsmtpReply
- isSuccess :: EsmtpReply -> Bool
- isFailure :: EsmtpReply -> Bool
- isShutdown :: EsmtpReply -> Bool
- smtpCmd :: Stream s m Char => ParsecT s u m EsmtpCmd
- smtpData :: Stream s m Char => ParsecT s u m EsmtpCmd
- rset :: Stream s m Char => ParsecT s u m EsmtpCmd
- quit :: Stream s m Char => ParsecT s u m EsmtpCmd
- turn :: Stream s m Char => ParsecT s u m EsmtpCmd
- helo :: Stream s m Char => ParsecT s u m EsmtpCmd
- ehlo :: Stream s m Char => ParsecT s u m EsmtpCmd
- mail :: Stream s m Char => ParsecT s u m EsmtpCmd
- rcpt :: Stream s m Char => ParsecT s u m EsmtpCmd
- send :: Stream s m Char => ParsecT s u m EsmtpCmd
- soml :: Stream s m Char => ParsecT s u m EsmtpCmd
- saml :: Stream s m Char => ParsecT s u m EsmtpCmd
- vrfy :: Stream s m Char => ParsecT s u m EsmtpCmd
- expn :: Stream s m Char => ParsecT s u m EsmtpCmd
- help :: Stream s m Char => ParsecT s u m EsmtpCmd
- noop :: Stream s m Char => ParsecT s u m EsmtpCmd
- 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 -> EsmtpCmd) -> ParsecT s u m a -> ParsecT s u m EsmtpCmd
- tokenList :: Stream s m Char => ParsecT s u m String -> Char -> ParsecT s u m String
Data Types for ESMTP 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 |
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.
postmaster :: Mailbox Source #
postmaster = Mailbox [] "postmaster" "" = "<postmaster>"
Data Types for ESMTP Replies
data EsmtpReply Source #
An ESMTP 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"
Instances
| Show EsmtpReply Source # | |
Defined in Text.Parsec.Rfc2821 Methods showsPrec :: Int -> EsmtpReply -> ShowS # show :: EsmtpReply -> String # showList :: [EsmtpReply] -> ShowS # | |
Constructors
| Code SuccessCode Category Int |
data SuccessCode Source #
Constructors
| Unused0 | |
| PreliminarySuccess | |
| Success | |
| IntermediateSuccess | |
| TransientFailure | |
| PermanentFailure |
Instances
Constructors
| Syntax | |
| Information | |
| Connection | |
| Unspecified3 | |
| Unspecified4 | |
| MailSystem |
Instances
| Bounded Category Source # | |
| Enum Category Source # | |
Defined in Text.Parsec.Rfc2821 | |
| Eq Category Source # | |
| Ord Category Source # | |
Defined in Text.Parsec.Rfc2821 | |
| Show Category Source # | |
reply :: Int -> Int -> Int -> [String] -> EsmtpReply Source #
Construct a EsmtpReply. Fails assert if invalid numbers are given.
isSuccess :: EsmtpReply -> Bool Source #
A reply constitutes "success" if the status code is any of
PreliminarySuccess, Success, or IntermediateSuccess.
isFailure :: EsmtpReply -> Bool Source #
A reply constitutes "failure" if the status code is either
PermanentFailure or TransientFailure.
isShutdown :: EsmtpReply -> Bool Source #
The replies 221 and 421 signify Shutdown.
Command Parsers
smtpCmd :: Stream s m Char => ParsecT s u m EsmtpCmd Source #
This parser recognizes any of the ESMTP 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 EsmtpCmd 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 -> EsmtpCmd) -> ParsecT s u m a -> ParsecT s u m EsmtpCmd 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!