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

Data.MIME

Description

This module extends Data.IMF with types for handling MIME messages (RFC 2045, 2046, 2183 and others).

Synopsis

Overview / HOWTO

Creating and serialising mail

Create an inline, plain text message and render it:

λ> :set -XOverloadedStrings
λ> import Data.MIME
λ> msg = createTextPlainMessage "Hello, world!"
λ> s = renderMessage msg
λ> Data.ByteString.Lazy.Char8.putStrLn s
MIME-Version: 1.0
Content-Transfer-Encoding: 7bit
Content-Disposition: inline
Content-Type: text/plain; charset=us-ascii

Hello, world!

Optics are provided for getting and setting the sender and recipient fields:

headerFrom, headerReplyTo, headerTo, headerCC, headerBCC
  :: (HasHeaders a)
  => CharsetLookup -> Lens' a [Address]

Example:

λ> alice = Single "alice@example.com"
λ> :t alice
alice :: Address
λ> bob = Single "bob@example.net"
λ> msgFromAliceToBob = set (headerFrom defaultCharsets) [alice] . set (headerTo defaultCharsets) [bob] $ msg
λ> Data.ByteString.Lazy.Char8.putStrLn (renderMessage msgFromAliceToBob)
MIME-Version: 1.0
From: alice@example.com
To: bob@example.net
Content-Transfer-Encoding: 7bit
Content-Disposition: inline
Content-Type: text/plain; charset=us-ascii

Hello, world!

NOTE: the values alice and bob in the above example make use of the non-total instance IsString Mailbox. This instance is provided as convenience for static values. For parsing mailboxes, use one of:

Data.IMF.mailbox      :: CharsetLookup -> Parser ByteString Mailbox
Data.IMF.Text.mailbox ::                  Parser       Text Mailbox

The Subject header is set via headerSubject. Other single-valued headers can be set via headerText.

λ> :{
| Data.ByteString.Lazy.Char8.putStrLn . renderMessage $
|   set (headerText defaultCharsets "Comments") (Just "와")
|   . set (headerSubject defaultCharsets) (Just "Hi from Alice")
|   $ msgFromAliceToBob
| :}

MIME-Version: 1.0
Comments: =?utf-8?B?7JmA?=
Subject: Hi from Alice
From: alice@example.com
To: bob@example.net
Content-Transfer-Encoding: 7bit
Content-Disposition: inline
Content-Type: text/plain; charset=us-ascii

Hello, world!

To create multipart messages you need to construct a Boundary value. Boundary values should be unique (not appearing elsewhere in a message). High-entropy random values are good. You can use mkBoundary to construct a value (checking that the input is a legal value). Or you can ask purebred-email to generate a conformant value, as below.

λ> import System.Random
λ> boundary <- getStdRandom uniform :: IO Boundary
λ> boundary
Boundary "MEgno8wUdTT/g8vB,vj.3K8sjU6i_r=CFf1jqrAmnxrv0a/9PA'G4hQ8oE,u016w"

Create a multipart message with attachment:

λ> attachment = createAttachment "application/json" (Just "data.json") "{\"foo\":42}"
λ> msg2 = createMultipartMixedMessage boundary (msg :| [attachment])
λ> s2 = renderMessage msg2
λ> Data.ByteString.Lazy.Char8.putStrLn s2
MIME-Version: 1.0
Content-Type: multipart/mixed;
 boundary="MEgno8wUdTT/g8vB,vj.3K8sjU6i_r=CFf1jqrAmnxrv0a/9PA'G4hQ8oE,u016w"

--MEgno8wUdTT/g8vB,vj.3K8sjU6i_r=CFf1jqrAmnxrv0a/9PA'G4hQ8oE,u016w
MIME-Version: 1.0
Content-Transfer-Encoding: 7bit
Content-Disposition: inline
Content-Type: text/plain; charset=us-ascii

Hello, world!
--MEgno8wUdTT/g8vB,vj.3K8sjU6i_r=CFf1jqrAmnxrv0a/9PA'G4hQ8oE,u016w
MIME-Version: 1.0
Content-Transfer-Encoding: 7bit
Content-Disposition: attachment; filename=data.json
Content-Type: application/json

{"foo":42}
--MEgno8wUdTT/g8vB,vj.3K8sjU6i_r=CFf1jqrAmnxrv0a/9PA'G4hQ8oE,u016w--

NOTE: for writing a Message to an IO handle, buildMessage is more efficient than renderMessage.

Parsing mail

Most often you will parse a message like this:

λ> parsedMessage = parse (message mime) s2
λ> :t parsedMessage
parsedMessage :: Either String MIMEMessage
λ> parsedMessage == Right msg2
True

The message function builds a parser for a message. It is abstracted over the body type; the argument is a function that can inspect headers and return a parser for the body. If you are parsing MIME messages (or plain RFC 5322 messages), the mime function is the right one to use.

Inspecting messages

Parsing an email is nice, but your normally want to get at the content inside. One of the most important tasks is __finding entities__ of interest, e.g. attachments, plain text or HTML bodies. The entities optic is a fold over all leaf entities in the message. That is, the leaves of (possibly nested) multipart messages and "message/rfc822" encapsulations. You can use filtered to refine the query.

For example, let's say you want to find the first text/plain entity in a message. Define a predicate with the help of the matchContentType function:

λ> isTextPlain = matchContentType "text" (Just "plain") . view contentType
λ> :t isTextPlain
isTextPlain :: HasHeaders s => s -> Bool
λ> (isTextPlain msg, isTextPlain msg2)
(True,False)

Now we can use the predicate to construct a fold and retrieve the body. If there is no matching entity the result would be Nothing.

λ> firstOf (entities . filtered isTextPlain . body) msg2
Just "Hello, world!"

For attachments, you may be interested in the binary data and the filename (if specified). In the following example we get the (optional) filenames and (decoded) body of all attachments, as a list of tuples. The attachments traversal targets non-multipart entities with Content-Disposition: attachment. The transferDecoded' optic undoes the Content-Transfer-Encoding of the entity.

λ> :set -XTypeFamilies
λ> getFilename = preview (contentDisposition . _Just . filename defaultCharsets)
λ> getBody = preview (transferDecoded' . _Right . body)
λ> getAttachment = liftA2 (,) getFilename getBody
λ> toListOf (attachments . to getAttachment) msg2
[(Just "data.json",Just "{\"foo\":42}")]

Finally, note that the filename optic takes an argument: it is a function for looking up a character set. Supporting every possible character encoding is a bit tricky so we let the user supply a map of supported charsets, and provide defaultCharsets which supports ASCII, UTF-8 and ISO-8859-1.

λ> :t filename
filename
  :: (HasParameters a, Applicative f) =>
     CharsetLookup -> (T.Text -> f T.Text) -> a -> f a
λ> :t defaultCharsets
defaultCharsets :: CharsetLookup
λ> :i CharsetLookup
type CharsetLookup = CI Char8.ByteString -> Maybe Data.MIME.Charset.Charset

Unicode support

In Australia we say "Hello world" upside down:

λ> msg3 = createTextPlainMessage "ɥǝןןo ʍoɹןp"
λ> Data.ByteString.Lazy.Char8.putStrLn $ renderMessage msg3
MIME-Version: 1.0
Content-Transfer-Encoding: base64
Content-Disposition: inline
Content-Type: text/plain; charset=utf-8

yaXHndef159vIMqNb8m5159w

Charset set and transfer encoding are handled automatically. If the message only includes characters representable in ASCII, the charset will be us-ascii, otherwise utf-8.

To read the message as Text you must perform transfer decoding and charset decoding. The transferDecoded optic performs transfer decoding, as does its sibling transferDecoded' which is monomorphic in the error type. Similarly, charsetText and charsetText' perform text decoding according to the character set.

If you don't mind throwing away decoding errors, the simplest way to get the text of a message is:

λ> Just ent = firstOf (entities . filtered isTextPlain) msg3
λ> :t ent
ent :: WireEntity
λ> text = preview (transferDecoded' . _Right . charsetText' defaultCharsets . _Right) ent
λ> :t text
text :: Maybe T.Text
λ> traverse_ Data.Text.IO.putStrLn text
ɥǝןןo ʍoɹןp

As mentioned earlier, functions that perform text decoding take a CharsetLookup parameter, and we provide defaultCharsets for convenience.

API

MIME data type

data MIME Source #

MIME message body. Either a single Part, or Multipart. Only the body is represented; preamble and epilogue are not.

Instances

Instances details
Show MIME Source # 
Instance details

Defined in Data.MIME

Methods

showsPrec :: Int -> MIME -> ShowS #

show :: MIME -> String #

showList :: [MIME] -> ShowS #

Eq MIME Source # 
Instance details

Defined in Data.MIME

Methods

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

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

EqMessage MIME Source #

Ignores the presence/absense of MIME-Version header

Instance details

Defined in Data.MIME

RenderMessage MIME Source #

Sets the MIME-Version: 1.0 header.

Instance details

Defined in Data.MIME

type MessageContext MIME Source # 
Instance details

Defined in Data.MIME

mime :: Headers -> BodyHandler MIME Source #

Top-level MIME body parser that uses headers to decide how to parse the body.

Do not use this parser for parsing a nested message. This parser should only be used when the message you want to parse is the whole input. If you use it to parse a nested message it will treat the remainder of the outer message(s) as part of the epilogue.

Preambles and epilogues are discarded.

This parser accepts non-MIME messages, and treats them as a single part.

data EncStateByte Source #

Entity requires content-transfer-encoding to send, and may require charset decoding to read.

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 #

type Decoded ByteEntity Source # 
Instance details

Defined in Data.MIME

Accessing and processing entities

entities :: Traversal' MIMEMessage WireEntity Source #

Get all leaf entities from the MIME message. Entities that failed to parse are skipped.

attachments :: Traversal' MIMEMessage WireEntity Source #

Leaf entities with Content-Disposition: attachment

isAttachment :: HasHeaders a => a -> Bool Source #

MIMEMessage content disposition is an Attachment

transferDecoded :: (HasTransferEncoding a, AsTransferEncodingError e, Profunctor p, Contravariant f) => Optic' p f a (Either e (TransferDecoded a)) Source #

Perform content transfer decoding.

transferDecoded' :: (HasTransferEncoding a, Profunctor p, Contravariant f) => Optic' p f a (Either TransferEncodingError (TransferDecoded a)) Source #

Perform content transfer decoding (monomorphic error type).

charsetDecoded :: (HasCharset a, AsCharsetError e) => CharsetLookup -> forall p f. (Profunctor p, Contravariant f) => Optic' p f a (Either e (Decoded a)) Source #

Structure with the encoded data replaced with Text

charsetDecoded' :: HasCharset a => CharsetLookup -> forall p f. (Profunctor p, Contravariant f) => Optic' p f a (Either CharsetError (Decoded a)) Source #

Structure with the encoded data replaced with Text (monomorphic error type)

Header processing

decodeEncodedWords :: CharsetLookup -> ByteString -> Text Source #

RFC 2047 and RFC 2231 define the encoded-words mechanism for embedding non-ASCII data in headers. This function locates encoded-words and decodes them.

λ> T.putStrLn $ decodeEncodedWords defaultCharsets "hello =?utf-8?B?5LiW55WM?=!"
hello 世界!

If parsing fails or the encoding is unrecognised the encoded-word is left unchanged in the result.

λ> T.putStrLn $ decodeEncodedWords defaultCharsets "=?utf-8?B?bogus?="
=?utf-8?B?bogus?=

λ> T.putStrLn $ decodeEncodedWords defaultCharsets "=?utf-8?X?unrecognised_encoding?="
=?utf-8?X?unrecognised_encoding?=

Language specification is supported (the datum is discarded).

λ> T.putStrLn $ decodeEncodedWords defaultCharsets "=?utf-8*es?Q?hola_mundo!?="
hola mundo!

Content-Type header

contentType :: HasHeaders a => Lens' a ContentType Source #

Lens to the content-type header. Probably not a lawful lens.

If the header is not specified or is syntactically invalid, defaultContentType is used. For more info see https://tools.ietf.org/html/rfc2045#section-5.2.

If the Content-Transfer-Encoding is unrecognised, the actual Content-Type value is ignored and application/octet-stream is returned, as required by https://tools.ietf.org/html/rfc2049#section-2.

When setting, if the header already exists it is replaced, otherwise it is added. Unrecognised Content-Transfer-Encoding is ignored when setting.

Note: when dealing with Multipart or Encapsulated messages, the Content-Type header will be overridden when serialising the message. This avoids scenarios where the Content-Type does not match the structure of the message. In general, the Content-Type header should be treated as "read only" for multipart or encapsulated message.

data ContentTypeWith a Source #

Content-Type (type and subtype) with explicit parameters type. Use parameters to access the parameters field. Example:

ContentType "text" "plain" (Parameters [("charset", "utf-8")])

You can also use -XOverloadedStrings but be aware the conversion is non-total (throws an error if it cannot parse the string).

Constructors

ContentType (CI ByteString) (CI ByteString) a 

Instances

Instances details
IsString ContentType Source #

NON-TOTAL parses the Content-Type (including parameters) and throws an error if the parse fails

Instance details

Defined in Data.MIME

HasParameters ContentType Source # 
Instance details

Defined in Data.MIME

Generic (ContentTypeWith a) Source # 
Instance details

Defined in Data.MIME

Associated Types

type Rep (ContentTypeWith a) :: Type -> Type #

Show a => Show (ContentTypeWith a) Source # 
Instance details

Defined in Data.MIME

NFData a => NFData (ContentTypeWith a) Source # 
Instance details

Defined in Data.MIME

Methods

rnf :: ContentTypeWith a -> () #

Eq a => Eq (ContentTypeWith a) Source #

Compares type and subtype case-insensitively; parameters are also compared. Use matchContentType if you just want to match on the media type while ignoring parameters.

Instance details

Defined in Data.MIME

type Rep (ContentTypeWith a) Source # 
Instance details

Defined in Data.MIME

matchContentType Source #

Arguments

:: CI ByteString

type

-> Maybe (CI ByteString)

optional subtype

-> ContentTypeWith a 
-> Bool 

Match content type. If Nothing is given for subtype, any subtype is accepted.

parseContentType :: Parser ContentType Source #

Parser for Content-Type header

showContentType :: ContentType -> Text Source #

Rendered content type field value for displaying

multipart media type

data MultipartSubtype Source #

Constructors

Mixed

RFC 2046 §5.1.3. Independent body parts, bundled in a particular order.

Alternative

RFC 2046 §5.1.4. Each part is an alternative version of the same content (e.g. plain text and HTML), in order of increasing faithfulness to the original content.

Digest

RFC 2046 §5.1.5. Collection of messages. Parts should have Content-Type: message/rfc822.

Parallel

RFC 2046 §5.1.6. Independent body parts, order not significants. Parts may be displayed in parallel if the system supports it.

Related

Aggregate or compound objects. Per RFC 2387 the type parameter is required. Sadly some major producers omit it, so this constructor must admit that case. See https://github.com/purebred-mua/purebred-email/issues/68.

Fields

  • (Maybe (ContentTypeWith ()))

    The type parameter must be specified and its value is the MIME media type of the "root" body part. It permits a MIME user agent to determine the Content-Type without reference to the enclosed body part. If the value of the type parameter and the root body part's Content-Type differ then the User Agent's behavior is undefined.

  • (Maybe ContentID)

    The start parameter, if given, points, via a Content-ID, to the body part that contains the object root. The default root is the first body part within the multipart/related body.

  • (Maybe ByteString)

    start-info parameter. Applications that use multipart/related must specify the interpretation of start-info. User Agents shall provide the parameter's value to the processing application.

Signed

RFC 1847 §2.1. Signed messages.

Fields

Encrypted

RFC 1847 §2.2.

Fields

Report

RFC 6522. Electronic mail reports.

Fields

Multilingual

RFC 8255. Multilingual messages. The first part should be a multilingual explanatory preface. Subsequent parts MUST have a Content-Language and a Content-Type field, and MAY have a Content-Translation-Type field.

Unrecognised (CI ByteString) 

Instances

Instances details
Show MultipartSubtype Source # 
Instance details

Defined in Data.MIME

Eq MultipartSubtype Source # 
Instance details

Defined in Data.MIME

boundary parameter

data Boundary Source #

MIME boundary. Use makeBoundary to construct, and unBoundary to unwrap.

Use the Uniform instance to generate a random Boundary to use when constructing messages. For example:

getStdRandom uniform :: MonadIO m =>  m Boundary
getStdRandom uniform ::              IO Boundary

Instances

Instances details
Show Boundary Source # 
Instance details

Defined in Data.MIME.Boundary

Eq Boundary Source # 
Instance details

Defined in Data.MIME.Boundary

Uniform Boundary Source # 
Instance details

Defined in Data.MIME.Boundary

Methods

uniformM :: StatefulGen g m => g -> m Boundary #

mimeBoundary :: Traversal' ContentType ByteString Source #

Traversal of boundary parameter (which may be unspecified)

Content-Type values

contentTypeMultipartMixed :: Boundary -> ContentType Source #

multipart/mixed; boundary=asdf

defaultContentType :: ContentType Source #

text/plain; charset=us-ascii

Content-Disposition header

contentDisposition :: HasHeaders a => Lens' a (Maybe ContentDisposition) Source #

Access Content-Disposition header.

Unrecognised disposition types are coerced to Attachment in accordance with RFC 2183 §2.8 which states: Unrecognized disposition types should be treated as attachment.

This optic does not distinguish between missing header or malformed value.

data ContentDisposition Source #

Content-Disposition header (RFC 2183).

Use parameters to access the parameters.

Instances

Instances details
Generic ContentDisposition Source # 
Instance details

Defined in Data.MIME

Associated Types

type Rep ContentDisposition :: Type -> Type #

Show ContentDisposition Source # 
Instance details

Defined in Data.MIME

NFData ContentDisposition Source # 
Instance details

Defined in Data.MIME

Methods

rnf :: ContentDisposition -> () #

HasParameters ContentDisposition Source # 
Instance details

Defined in Data.MIME

type Rep ContentDisposition Source # 
Instance details

Defined in Data.MIME

type Rep ContentDisposition = D1 ('MetaData "ContentDisposition" "Data.MIME" "purebred-email-0.6-O0tXp2Beg5GhPyBH3nCml" 'False) (C1 ('MetaCons "ContentDisposition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DispositionType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Parameters)))

data DispositionType Source #

Constructors

Inline 
Attachment 

Instances

Instances details
Generic DispositionType Source # 
Instance details

Defined in Data.MIME

Associated Types

type Rep DispositionType :: Type -> Type #

Show DispositionType Source # 
Instance details

Defined in Data.MIME

NFData DispositionType Source # 
Instance details

Defined in Data.MIME

Methods

rnf :: DispositionType -> () #

Eq DispositionType Source # 
Instance details

Defined in Data.MIME

type Rep DispositionType Source # 
Instance details

Defined in Data.MIME

type Rep DispositionType = D1 ('MetaData "DispositionType" "Data.MIME" "purebred-email-0.6-O0tXp2Beg5GhPyBH3nCml" 'False) (C1 ('MetaCons "Inline" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Attachment" 'PrefixI 'False) (U1 :: Type -> Type))

filename :: HasParameters a => CharsetLookup -> Traversal' a Text Source #

Traverse the value of the filename parameter (if present).

filenameParameter :: HasParameters a => Lens' a (Maybe EncodedParameterValue) Source #

Access the filename parameter as a Maybe (ParameterValue B.ByteString).

This can be used to read or set the filename parameter (see also the newParameter convenience function):

λ> let hdrs = Headers [("Content-Disposition", "attachment")]
λ> set (contentDisposition . filenameParameter) (Just (newParameter "foo.txt")) hdrs
Headers [("Content-Disposition","attachment; filename=foo.txt")]

renderContentDisposition :: ContentDisposition -> ByteString Source #

Render the Content-Disposition value, including parameters.

Content-ID header

data ContentID Source #

The Content-ID value may be used for uniquely identifying MIME entities in several contexts, particularly for caching data referenced by the message/external-body mechanism. Although the Content-ID header is generally optional, its use is MANDATORY in implementations which generate data of the optional MIME media type message/external-body. That is, each message/external-body entity must have a Content-ID field to permit caching of such data.

Instances

Instances details
Show ContentID Source # 
Instance details

Defined in Data.MIME

Eq ContentID Source # 
Instance details

Defined in Data.MIME

Mail creation

Common use cases

createTextPlainMessage :: Text -> MIMEMessage Source #

Create an inline, text/plain, utf-8 encoded message

createAttachment :: ContentType -> Maybe FilePath -> ByteString -> MIMEMessage Source #

Create an attachment from the given file contents. Optionally set the filename parameter to the given file path.

createAttachmentFromFile :: ContentType -> FilePath -> IO MIMEMessage Source #

Create an attachment from a given file path. Note: The filename content disposition is set to the given FilePath. For privacy reasons, you can unset/change it. See filename for examples.

createMultipartMixedMessage Source #

Arguments

:: Boundary 
-> NonEmpty MIMEMessage

parts

-> MIMEMessage 

Create a mixed MIMEMessage with an inline text/plain part and multiple attachments

setTextPlainBody :: Text -> Message ctx a -> MIMEMessage Source #

Set an inline, text/plain, utf-8 encoded message body

Forward

encapsulate :: MIMEMessage -> MIMEMessage Source #

Encapsulate a message as a message/rfc822 message. You can use this in creating forwarded or bounce messages.

Re-exports

defaultCharsets :: CharsetLookup Source #

Supports US-ASCII, UTF-8 and ISO-8859-1, UTF-16[BE|LE] and UTF-32[BE|LE]. The purebred-icu package provides support for more charsets.

module Data.IMF