hsemail-2.1.0: Parsec parsers for the RFC2822 Internet Message format

Copyright(c) 2007-2019 Peter Simons
LicenseBSD3
Maintainersimons@cryp.to
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

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 Types for ESMTP Commands

data EsmtpCmd 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
Show EsmtpCmd Source # 
Instance details

Defined in Text.Parsec.Rfc2821

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 
Instances
Eq Mailbox Source # 
Instance details

Defined in Text.Parsec.Rfc2821

Methods

(==) :: Mailbox -> Mailbox -> Bool #

(/=) :: Mailbox -> Mailbox -> Bool #

Read Mailbox Source # 
Instance details

Defined in Text.Parsec.Rfc2821

Show Mailbox Source # 
Instance details

Defined in Text.Parsec.Rfc2821

nullPath :: Mailbox Source #

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

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"

Constructors

Reply EsmtpCode [String] 
Instances
Show EsmtpReply Source # 
Instance details

Defined in Text.Parsec.Rfc2821

data EsmtpCode Source #

Instances
Show EsmtpCode Source # 
Instance details

Defined in Text.Parsec.Rfc2821

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.

smtpData :: Stream s m Char => ParsecT s u m EsmtpCmd Source #

The parser name "data" was taken.

noop :: Stream s m Char => ParsecT s u m EsmtpCmd Source #

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

Argument Parsers

a_d_l :: Stream s m Char => ParsecT s u m [String] Source #

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

fixCRLF :: String -> String Source #

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 :: 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!

tokenList :: Stream s m Char => ParsecT s u m String -> Char -> ParsecT s u m String Source #

tokenList p . will parse a token of the form "p.p", or "p.p.p", and so on. Used in domain and dot_string, for example.