purebred-email-0.6: types and parser for email messages (including MIME)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.IMF

Description

Internet Message Format (IMF), which is used for electronic mail (email), as specified by RFC 5322 and updated by RFC 6854.

The parser allows LF line endings in addition to CRLF. RFC 5322 specifies CRLF line endings but LF-only is common in on-disk formats. Serialisation functions produces CRLF line endings.

The main parsing function is message. It takes a second function that can inspect the headers to determine how to parse the body.

message :: (Headers -> BodyHandler a) -> Parser (Message ctx a)

The Message type is parameterised over the body type, and a phantom type that can be used for context.

data Message ctx a = Message Headers a

Headers and body can be accessed via the headers, header and body optics.

headers :: HasHeaders a => Lens'       a         Headers
headers ::                 Lens' (Message ctx b) Headers

header :: HasHeaders a => CI B.ByteString -> Traversal'        a        B.ByteString
header ::                 CI B.ByteString -> Traversal' (Message ctx b) B.ByteString
header ::                 CI B.ByteString -> Traversal'     Headers     B.ByteString

body :: Lens (Message ctx a) (Message ctx' b) a b

The following example program parses an input, interpreting the body as a raw ByteString, and prints the subject (if present), the number of headers and the body length. The message context type is ().

analyse :: B.ByteString -> IO ()
analyse input =
  case parse (message (const takeByteString)) of
    Left errMsg -> hPutStrLn stderr errMsg *> exitFailure
    Right (msg :: Message () B.ByteString) -> do
      T.putStrLn $ "subject: " <> foldOf (headerSubject defaultCharsets) msg
      putStrLn $ "num headers: " <> show (length (view headers msg))
      putStrLn $ "body length: " <> show (B.length (view body msg))
Synopsis

Message types

data Message s a Source #

Message type, parameterised over context and body type. The context type is not used in this module but is provided for uses such as tracking the transfer/charset encoding state in MIME messages.

Constructors

Message Headers a 

Instances

Instances details
HasCharset ByteEntity Source #

RFC 6657 specifies that each subtype of the text media type can define its own default value for the charset parameter, including the absense of any default. It can also specify that the charset information is transported inside the payload (such as in text/xml. Behaviour for common media types includes:

text/plain
Default: us-ascii (RFC 6657)
text/csv
Default: utf-8 (RFC 7111)
text/markdown
No default; charset parameter is REQUIRED (RFC 7763)
text/enriched
Default: us-ascii (RFC 1896)
text/rtf
Decoded as us-ascii. Serialised RTF must be 7-bit ASCII, with the character set declared in the payload. Decoding RTF is outside the scope of this library. See https://www.iana.org/assignments/media-types/text/rtf.
Instance details

Defined in Data.MIME

Associated Types

type Decoded ByteEntity Source #

HasTransferEncoding WireEntity Source # 
Instance details

Defined in Data.MIME

Associated Types

type TransferDecoded WireEntity Source #

Functor (Message s) Source # 
Instance details

Defined in Data.IMF

Methods

fmap :: (a -> b) -> Message s a -> Message s b #

(<$) :: a -> Message s b -> Message s a #

Generic (Message s a) Source # 
Instance details

Defined in Data.IMF

Associated Types

type Rep (Message s a) :: Type -> Type #

Methods

from :: Message s a -> Rep (Message s a) x #

to :: Rep (Message s a) x -> Message s a #

Show a => Show (Message s a) Source # 
Instance details

Defined in Data.IMF

Methods

showsPrec :: Int -> Message s a -> ShowS #

show :: Message s a -> String #

showList :: [Message s a] -> ShowS #

NFData a => NFData (Message s a) Source # 
Instance details

Defined in Data.IMF

Methods

rnf :: Message s a -> () #

EqMessage a => Eq (Message s a) Source # 
Instance details

Defined in Data.IMF

Methods

(==) :: Message s a -> Message s a -> Bool #

(/=) :: Message s a -> Message s a -> Bool #

HasHeaders (Message s a) Source # 
Instance details

Defined in Data.IMF

type Decoded ByteEntity Source # 
Instance details

Defined in Data.MIME

type TransferDecoded WireEntity Source # 
Instance details

Defined in Data.MIME

type Rep (Message s a) Source # 
Instance details

Defined in Data.IMF

type Rep (Message s a) = D1 ('MetaData "Message" "Data.IMF" "purebred-email-0.6-O0tXp2Beg5GhPyBH3nCml" 'False) (C1 ('MetaCons "Message" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Headers) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

message :: (Headers -> BodyHandler a) -> Parser (Message (MessageContext a) a) Source #

Parse a message. The function argument receives the headers and yields a handler for the message body.

type family MessageContext a Source #

Instances

Instances details
type MessageContext MIME Source # 
Instance details

Defined in Data.MIME

data BodyHandler a Source #

Specify how to handle a message body, including the possibility of optional bodies and no body (which is distinct from empty body).

Constructors

RequiredBody (Parser a) 
OptionalBody (Parser a, a)

If body is present run parser, otherwise use constant value

NoBody a 

body :: Lens (Message ctx a) (Message ctx' b) a b Source #

class EqMessage a where Source #

How to compare messages with this body type.

This class arises because we may want to tweak the headers, possibly in response to body data, or vice-versa, when comparing messages.

The default implementation compares headers and body using (==).

Minimal complete definition

Nothing

Methods

eqMessage :: Message s a -> Message s a -> Bool Source #

default eqMessage :: Eq a => Message s a -> Message s a -> Bool Source #

Instances

Instances details
EqMessage MIME Source #

Ignores the presence/absense of MIME-Version header

Instance details

Defined in Data.MIME

Replying

reply :: CharsetLookup -> ReplySettings -> Message ctx a -> Message ctx () Source #

Construct a reply to a Message, according to the specified ReplySettings and following the requirements and suggestions of RFC 5322. In particular:

  • Sets In-Reply-To to the Message-ID of the parent message.
  • Sets the References header, following the requirements in RFC 5322 §3.6.4.
  • Sets the Subject by prepending "Re: " to the parent subject, unless it already has such a prefix (case-insensitive match). This is the scheme suggested in RFC 5322 §3.6.5.
  • Sets the From header. If the ReplyFromMode is ReplyFromMatchingMailbox and one of the authorMailboxes is a recipient of the parent message, that address will be used as the From address. Also, if ReplyFromRewriteMode is ReplyFromRewriteOn, the matching value in authorMailboxes replaces the value from the parent message. This can be used to rewrite a bare address to one with a display name (or vice-versa). In all other cases the From address will be the preferred (first) author mailbox.
  • Sets To and Cc according to ReplyMode and SelfInRecipientsMode. These headers are described in RFC 5322 §3.6.3.

    • In ReplyToSender mode, the To header of the reply will contain the addresses from the Reply-To header if it is present, otherwise it will contain the addresses from the From header.
    • In ReplyToGroup mode, if the parent message has only one recipient (across the To and Cc headers), the behaviour is the same as ReplyToSender mode (Reply-To is respected). If the parent message has multiple recipients, the Reply-To header is ignored, the To header of the reply will contain the addresses from the From header, and the Cc header of the reply will contain the addresses from the To and Cc headers.
    • If the SelfInRecipientsMode is SelfInRecipientsRemove, any of the authorMailboxes will be removed from the To and Cc headers.

data ReplySettings Source #

All the settings to control how to construct a reply to a message.

data ReplyMode Source #

Specify how to choose recipients when replying.

TODO: "list reply" mode

Constructors

ReplyToSender

Reply to the sender of the email only, or Reply-To header if set.

ReplyToGroup

Reply to sender and Cc all other recipients of the original message.

data ReplyFromMode Source #

How to choose the From address.

Constructors

ReplyFromPreferredMailbox

Always reply From the preferred mailbox

ReplyFromMatchingMailbox

Reply from whichever author mailbox is a recipient of the parent message, or the preferred mailbox if none of the author mailboxes is a visible recipient of the parent message.

data ReplyFromRewriteMode Source #

Whether to use the From address as it appears in the parent message, or as it appears in the AuthorMailboxes.

Constructors

ReplyFromRewriteOff

Use the From mailbox as it appears in the original message.

ReplyFromRewriteOn

Use the From mailbox as it appears in the author mailboxes.

data SelfInRecipientsMode Source #

Constructors

SelfInRecipientsRemove

Remove author mailbox from list of recipients when replying.

SelfInRecipientsIgnore

If author mailbox appears in list of recipients, leave it there.

type AuthorMailboxes = NonEmpty Mailbox Source #

The mailboxes of the entity authoring the reply. The first mailbox is the "preferred" mailbox.

Headers

class HasHeaders a where Source #

Instances

Instances details
HasHeaders Headers Source # 
Instance details

Defined in Data.IMF

HasHeaders (Message s a) Source # 
Instance details

Defined in Data.IMF

headerList :: HasHeaders a => Lens' a [(CI ByteString, ByteString)] Source #

Access headers as a list of key/value pairs.

newtype Headers Source #

Constructors

Headers [Header] 

Instances

Instances details
Generic Headers Source # 
Instance details

Defined in Data.IMF

Associated Types

type Rep Headers :: Type -> Type #

Methods

from :: Headers -> Rep Headers x #

to :: Rep Headers x -> Headers #

Show Headers Source # 
Instance details

Defined in Data.IMF

NFData Headers Source # 
Instance details

Defined in Data.IMF

Methods

rnf :: Headers -> () #

Eq Headers Source # 
Instance details

Defined in Data.IMF

Methods

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

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

At Headers Source #

Acts upon the first occurrence of the header only.

Instance details

Defined in Data.IMF

Ixed Headers Source # 
Instance details

Defined in Data.IMF

HasHeaders Headers Source # 
Instance details

Defined in Data.IMF

type Rep Headers Source # 
Instance details

Defined in Data.IMF

type Rep Headers = D1 ('MetaData "Headers" "Data.IMF" "purebred-email-0.6-O0tXp2Beg5GhPyBH3nCml" 'True) (C1 ('MetaCons "Headers" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Header])))
type Index Headers Source # 
Instance details

Defined in Data.IMF

type IxValue Headers Source # 
Instance details

Defined in Data.IMF

Date and Time

Originator

Destination Address

Identification

Informational

headerSubject :: HasHeaders a => CharsetLookup -> Lens' a (Maybe Text) Source #

Subject header. See headerText for details of conversion to Text.

Arbitrary headers

header :: HasHeaders a => CI ByteString -> Traversal' a ByteString Source #

Target all values of the given header

headerText :: HasHeaders a => CharsetLookup -> CI ByteString -> Lens' a (Maybe Text) Source #

Single-valued header with Text value via encoded-words. The conversion to/from Text is total (encoded-words that failed to be decoded are passed through unchanged). Therefore Nothing means that the header was not present.

Types

Message ID

data MessageID Source #

Instances

Instances details
Show MessageID Source # 
Instance details

Defined in Data.IMF

Eq MessageID Source # 
Instance details

Defined in Data.IMF

Ord MessageID Source # 
Instance details

Defined in Data.IMF

Address types

data Address Source #

Constructors

Single Mailbox 
Group Text [Mailbox] 

Instances

Instances details
Generic Address Source # 
Instance details

Defined in Data.IMF

Associated Types

type Rep Address :: Type -> Type #

Methods

from :: Address -> Rep Address x #

to :: Rep Address x -> Address #

Show Address Source # 
Instance details

Defined in Data.IMF

NFData Address Source # 
Instance details

Defined in Data.IMF

Methods

rnf :: Address -> () #

Eq Address Source # 
Instance details

Defined in Data.IMF

Methods

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

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

type Rep Address Source # 
Instance details

Defined in Data.IMF

data AddrSpec Source #

Email address. The Eq instances compares the local part case sensitively, and the domain part as described at Domain.

Address "detail" (section of local part after a + character; also called "extension" or "subaddress") is part of the local part. Therefore addresses that differ in this aspect, for example alice+bank@example.com and alice+spam@example.com, are unequal.

Constructors

AddrSpec ByteString Domain 

Instances

Instances details
Generic AddrSpec Source # 
Instance details

Defined in Data.IMF

Associated Types

type Rep AddrSpec :: Type -> Type #

Methods

from :: AddrSpec -> Rep AddrSpec x #

to :: Rep AddrSpec x -> AddrSpec #

Show AddrSpec Source # 
Instance details

Defined in Data.IMF

NFData AddrSpec Source # 
Instance details

Defined in Data.IMF

Methods

rnf :: AddrSpec -> () #

Eq AddrSpec Source # 
Instance details

Defined in Data.IMF

type Rep AddrSpec Source # 
Instance details

Defined in Data.IMF

type Rep AddrSpec = D1 ('MetaData "AddrSpec" "Data.IMF" "purebred-email-0.6-O0tXp2Beg5GhPyBH3nCml" 'False) (C1 ('MetaCons "AddrSpec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Domain)))

data Domain Source #

A DNS name or "domain literal" (address literal). DNS names are compared case-insensitively.

Instances

Instances details
Generic Domain Source # 
Instance details

Defined in Data.IMF

Associated Types

type Rep Domain :: Type -> Type #

Methods

from :: Domain -> Rep Domain x #

to :: Rep Domain x -> Domain #

Show Domain Source # 
Instance details

Defined in Data.IMF

NFData Domain Source # 
Instance details

Defined in Data.IMF

Methods

rnf :: Domain -> () #

Eq Domain Source # 
Instance details

Defined in Data.IMF

Methods

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

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

type Rep Domain Source # 
Instance details

Defined in Data.IMF

type Rep Domain = D1 ('MetaData "Domain" "Data.IMF" "purebred-email-0.6-O0tXp2Beg5GhPyBH3nCml" 'False) (C1 ('MetaCons "DomainDotAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (CI ByteString)))) :+: C1 ('MetaCons "DomainLiteral" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data Mailbox Source #

Email address with optional display name. The Eq instance compares the display name case sensitively and the address as described at AddrSpec.

Constructors

Mailbox (Maybe Text) AddrSpec 

Instances

Instances details
IsString Mailbox Source # 
Instance details

Defined in Data.IMF

Methods

fromString :: String -> Mailbox #

Generic Mailbox Source # 
Instance details

Defined in Data.IMF

Associated Types

type Rep Mailbox :: Type -> Type #

Methods

from :: Mailbox -> Rep Mailbox x #

to :: Rep Mailbox x -> Mailbox #

Show Mailbox Source # 
Instance details

Defined in Data.IMF

NFData Mailbox Source # 
Instance details

Defined in Data.IMF

Methods

rnf :: Mailbox -> () #

Eq Mailbox Source # 
Instance details

Defined in Data.IMF

Methods

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

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

type Rep Mailbox Source # 
Instance details

Defined in Data.IMF

type Rep Mailbox = D1 ('MetaData "Mailbox" "Data.IMF" "purebred-email-0.6-O0tXp2Beg5GhPyBH3nCml" 'False) (C1 ('MetaCons "Mailbox" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AddrSpec)))

Parsers

parse :: Cons s s Word8 Word8 => Parser a -> s -> Either String a Source #

Parse an a.

Converts the input to a lazy ByteString. Build with rewrite rules enabled (-O, cabal's default) to achieve the following conversion overheads:

  • Lazy ByteString: no conversion
  • Strict ByteString: O(1) conversion
  • [Word8]: O(n) conversion

It is recommended to use strict bytestring input. Parsing a lazy bytestring will cause numerous parser buffer resizes. The lazy chunks in the input can be GC'd but the buffer keeps growing so you don't actually keep the memory usage low by using a lazy bytestring.

parsed :: Cons s s Word8 Word8 => Parser a -> Fold s a Source #

Given a parser, construct a Fold

See parse for discussion of performance.

parsePrint :: Parser a -> (a -> ByteString) -> Prism' ByteString a Source #

Construct a prism from a parser and a printer

crlf :: Alternative (f s) => CharParsing f s a => f s () Source #

Either CRLF or LF (lots of mail programs transform CRLF to LF)

quotedString :: (Alternative (f s), CharParsing f s a, SM s) => f s s Source #

Helpers

Serialisation

buildMessage :: forall ctx a. RenderMessage a => Message ctx a -> Builder Source #

Construct a Builder for the message. This allows efficient streaming to IO handles.

renderMessage :: RenderMessage a => Message ctx a -> ByteString Source #

Render a message to a lazy ByteString. (You will probably not need a strict ByteString and it is inefficient for most use cases.)

class RenderMessage a where Source #

Define how to render an RFC 5322 message with given payload type.

Minimal complete definition

buildBody

Methods

buildBody :: Headers -> a -> Maybe Builder Source #

Build the body. If there should be no body (as distinct from empty body) return Nothing

tweakHeaders :: a -> Headers -> Headers Source #

Allows tweaking the headers before rendering. Default implementation is a no-op.

Instances

Instances details
RenderMessage MIME Source #

Sets the MIME-Version: 1.0 header.

Instance details

Defined in Data.MIME