| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
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->BodyHandlera) -> Parser (Messagectx a)
The Message type is parameterised over the body type, and a
phantom type that can be used for context.
dataMessagectx a =MessageHeadersa
Headers and body can be accessed via the headers, header and
body optics.
headers::HasHeadersa => Lens' a Headers headers :: Lens' (Messagectx b) Headersheader::HasHeadersa => CI B.ByteString -> Traversal' a B.ByteString header :: CI B.ByteString -> Traversal' (Messagectx b) B.ByteString header :: CI B.ByteString -> Traversal'HeadersB.ByteStringbody:: Lens (Messagectx 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 = caseparse(message(const takeByteString)) input of Left errMsg -> hPutStrLn stderr errMsg *> exitFailure Right (msg :: Message () B.ByteString) -> do T.putStrLn $ "subject: " <> foldOf (headerSubjectdefaultCharsets) msg putStrLn $ "num headers: " <> show (length (viewheadersmsg)) putStrLn $ "body length: " <> show (B.length (viewbodymsg))
Synopsis
- data Message s a = Message Headers a
- message :: (Headers -> BodyHandler a) -> Parser (Message (MessageContext a) a)
- type family MessageContext a
- data BodyHandler a
- = RequiredBody (Parser a)
- | OptionalBody (Parser a, a)
- | NoBody a
- body :: Lens (Message ctx a) (Message ctx' b) a b
- class EqMessage a where
- reply :: CharsetLookup -> ReplySettings -> Message ctx a -> Message ctx ()
- data ReplySettings = ReplySettings ReplyMode ReplyFromMode ReplyFromRewriteMode SelfInRecipientsMode AuthorMailboxes
- defaultReplySettings :: AuthorMailboxes -> ReplySettings
- data ReplyMode
- data ReplyFromMode
- data ReplyFromRewriteMode
- data SelfInRecipientsMode
- type AuthorMailboxes = NonEmpty Mailbox
- replyMode :: Lens' ReplySettings ReplyMode
- replyFromMode :: Lens' ReplySettings ReplyFromMode
- replyFromRewriteMode :: Lens' ReplySettings ReplyFromRewriteMode
- selfInRecipientsMode :: Lens' ReplySettings SelfInRecipientsMode
- authorMailboxes :: Lens' ReplySettings AuthorMailboxes
- type Header = (CI ByteString, ByteString)
- class HasHeaders a where
- headerList :: HasHeaders a => Lens' a [(CI ByteString, ByteString)]
- newtype Headers = Headers [Header]
- headerDate :: HasHeaders a => Lens' a (Maybe ZonedTime)
- dateTime :: Parser ZonedTime
- headerFrom :: HasHeaders a => CharsetLookup -> Lens' a [Address]
- headerReplyTo :: HasHeaders a => CharsetLookup -> Lens' a [Address]
- headerTo :: HasHeaders a => CharsetLookup -> Lens' a [Address]
- headerCC :: HasHeaders a => CharsetLookup -> Lens' a [Address]
- headerBCC :: HasHeaders a => CharsetLookup -> Lens' a [Address]
- headerMessageID :: HasHeaders a => Lens' a (Maybe MessageID)
- headerInReplyTo :: HasHeaders a => Lens' a [MessageID]
- headerReferences :: HasHeaders a => Lens' a [MessageID]
- headerSubject :: HasHeaders a => CharsetLookup -> Lens' a (Maybe Text)
- header :: HasHeaders a => CI ByteString -> Traversal' a ByteString
- headerText :: HasHeaders a => CharsetLookup -> CI ByteString -> Lens' a (Maybe Text)
- data MessageID
- parseMessageID :: Parser MessageID
- buildMessageID :: MessageID -> Builder
- renderMessageID :: MessageID -> ByteString
- data Address
- address :: CharsetLookup -> Parser Address
- addressList :: CharsetLookup -> Parser [Address]
- data AddrSpec = AddrSpec ByteString Domain
- data Domain
- data Mailbox = Mailbox (Maybe Text) AddrSpec
- mailbox :: CharsetLookup -> Parser Mailbox
- mailboxList :: CharsetLookup -> Parser [Mailbox]
- parse :: Cons s s Word8 Word8 => Parser a -> s -> Either String a
- parsed :: Cons s s Word8 Word8 => Parser a -> Fold s a
- parsePrint :: Parser a -> (a -> ByteString) -> Prism' ByteString a
- crlf :: Alternative (f s) => CharParsing f s a => f s ()
- quotedString :: (Alternative (f s), CharParsing f s a, SM s) => f s s
- field :: Parser (CI ByteString, ByteString)
- buildMessage :: forall ctx a. RenderMessage a => Message ctx a -> Builder
- renderMessage :: RenderMessage a => Message ctx a -> ByteString
- class RenderMessage a where
- renderRFC5322Date :: ZonedTime -> ByteString
- buildFields :: Headers -> Builder
- buildField :: (CI ByteString, ByteString) -> Builder
- renderAddressSpec :: AddrSpec -> ByteString
- renderMailbox :: Mailbox -> ByteString
- renderMailboxes :: [Mailbox] -> ByteString
- renderAddress :: Address -> ByteString
- renderAddresses :: [Address] -> ByteString
Message types
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.
Instances
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
| type MessageContext MIME Source # | |
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 |
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
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-Toto theMessage-IDof the parent message. - Sets the
Referencesheader, following the requirements in RFC 5322 §3.6.4. - Sets the
Subjectby 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
Fromheader. If theReplyFromModeisReplyFromMatchingMailboxand one of theauthorMailboxesis a recipient of the parent message, that address will be used as theFromaddress. Also, ifReplyFromRewriteModeisReplyFromRewriteOn, the matching value inauthorMailboxesreplaces 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 theFromaddress will be the preferred (first) author mailbox. Sets
ToandCcaccording toReplyModeandSelfInRecipientsMode. These headers are described in RFC 5322 §3.6.3.- In
ReplyToSendermode, theToheader of the reply will contain the addresses from theReply-Toheader if it is present, otherwise it will contain the addresses from theFromheader. - In
ReplyToGroupmode, if the parent message has only one recipient (across theToandCcheaders), the behaviour is the same asReplyToSendermode (Reply-Tois respected). If the parent message has multiple recipients, theReply-Toheader is ignored, theToheader of the reply will contain the addresses from theFromheader, and theCcheader of the reply will contain the addresses from theToandCcheaders. - If the
SelfInRecipientsModeisSelfInRecipientsRemove, any of theauthorMailboxeswill be removed from theToandCcheaders.
- In
data ReplySettings Source #
All the settings to control how to construct a reply to a message.
defaultReplySettings :: AuthorMailboxes -> ReplySettings Source #
Given author mailboxes, get a default ReplySettings. The default
settings are: ReplyToSender, ReplyFromMatchingMailbox,
ReplyFromRewriteOn, and SelfInRecipientsRemove.
Specify how to choose recipients when replying.
TODO: "list reply" mode
Constructors
| ReplyToSender | Reply to the sender of the email only, or |
| ReplyToGroup | Reply to sender and |
data ReplyFromMode Source #
How to choose the From address.
Constructors
| ReplyFromPreferredMailbox | Always reply |
| 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 |
| ReplyFromRewriteOn | Use the |
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
type Header = (CI ByteString, ByteString) Source #
class HasHeaders a where Source #
headerList :: HasHeaders a => Lens' a [(CI ByteString, ByteString)] Source #
Access headers as a list of key/value pairs.
Instances
| Generic Headers Source # | |
| Show Headers Source # | |
| NFData Headers Source # | |
| Eq Headers Source # | |
| At Headers Source # | Acts upon the first occurrence of the header only. |
| Ixed Headers Source # | |
| HasHeaders Headers Source # | |
| type Rep Headers Source # | |
| type Index Headers Source # | |
Defined in Data.IMF | |
| type IxValue Headers Source # | |
Defined in Data.IMF | |
Date and Time
headerDate :: HasHeaders a => Lens' a (Maybe ZonedTime) Source #
Originator
headerFrom :: HasHeaders a => CharsetLookup -> Lens' a [Address] Source #
headerReplyTo :: HasHeaders a => CharsetLookup -> Lens' a [Address] Source #
Destination Address
headerTo :: HasHeaders a => CharsetLookup -> Lens' a [Address] Source #
headerCC :: HasHeaders a => CharsetLookup -> Lens' a [Address] Source #
headerBCC :: HasHeaders a => CharsetLookup -> Lens' a [Address] Source #
Identification
headerMessageID :: HasHeaders a => Lens' a (Maybe MessageID) Source #
headerInReplyTo :: HasHeaders a => Lens' a [MessageID] Source #
headerReferences :: HasHeaders a => Lens' a [MessageID] Source #
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
Instances
| Show MessageID Source # | |
| Eq MessageID Source # | |
| Ord MessageID Source # | |
buildMessageID :: MessageID -> Builder Source #
Address types
Instances
| Generic Address Source # | |
| Show Address Source # | |
| NFData Address Source # | |
| Eq Address Source # | |
| type Rep Address Source # | |
Defined in Data.IMF type Rep Address = D1 ('MetaData "Address" "Data.IMF" "purebred-email-0.6.0.2-KNqpzoszl1mJkrfXLq3jbo" 'False) (C1 ('MetaCons "Single" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mailbox)) :+: C1 ('MetaCons "Group" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Mailbox]))) | |
addressList :: CharsetLookup -> Parser [Address] 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
| Generic AddrSpec Source # | |
| Show AddrSpec Source # | |
| NFData AddrSpec Source # | |
| Eq AddrSpec Source # | |
| type Rep AddrSpec Source # | |
Defined in Data.IMF type Rep AddrSpec = D1 ('MetaData "AddrSpec" "Data.IMF" "purebred-email-0.6.0.2-KNqpzoszl1mJkrfXLq3jbo" '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))) | |
A DNS name or "domain literal" (address literal). DNS names are compared case-insensitively.
Constructors
| DomainDotAtom (NonEmpty (CI ByteString)) | |
| DomainLiteral ByteString |
Instances
| Generic Domain Source # | |
| Show Domain Source # | |
| NFData Domain Source # | |
| Eq Domain Source # | |
| type Rep Domain Source # | |
Defined in Data.IMF type Rep Domain = D1 ('MetaData "Domain" "Data.IMF" "purebred-email-0.6.0.2-KNqpzoszl1mJkrfXLq3jbo" '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))) | |
Email address with optional display name.
The Eq instance compares the display name case
sensitively and the address as described at AddrSpec.
Instances
| IsString Mailbox Source # | |
Defined in Data.IMF Methods fromString :: String -> Mailbox # | |
| Generic Mailbox Source # | |
| Show Mailbox Source # | |
| NFData Mailbox Source # | |
| Eq Mailbox Source # | |
| type Rep Mailbox Source # | |
Defined in Data.IMF type Rep Mailbox = D1 ('MetaData "Mailbox" "Data.IMF" "purebred-email-0.6.0.2-KNqpzoszl1mJkrfXLq3jbo" '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))) | |
mailboxList :: CharsetLookup -> Parser [Mailbox] Source #
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.
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
field :: Parser (CI ByteString, ByteString) Source #
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
buildFields :: Headers -> Builder Source #
buildField :: (CI ByteString, ByteString) -> Builder Source #
renderMailbox :: Mailbox -> ByteString Source #
renderMailboxes :: [Mailbox] -> ByteString Source #
renderAddress :: Address -> ByteString Source #
renderAddresses :: [Address] -> ByteString Source #