purebred-email-0.1.0.0: types and parser for email messages (including MIME)

Safe HaskellNone
LanguageHaskell2010

Data.MIME

Contents

Description

MIME messages (RFC 2045, RFC 2046 and friends).

Synopsis

Overview

This module extends RFC5322 with types for handling MIME messages. It provides the mime parsing helper function for use with message.

mime :: Headers -> Parser MIME
message mime :: Parser (Message ctx MIME)

The Message data type has a phantom type parameter for context. In this module we use it to track whether the body has content transfer encoding or charset encoding applied. Type aliases are provided for convenince.

data Message ctx a = Message Headers a
data EncStateWire
data EncStateByte

type MIMEMessage = Message EncStateWire MIME
type WireEntity = Message EncStateWire B.ByteString
type ByteEntity = Message EncStateByte B.ByteString
type TextEntity = Message () T.Text

Folds are provided over all leaf entities, and entities that are identified as attachments:

entities :: Fold MIMEMessage WireEntity
attachments :: Fold MIMEMessage WireEntity

Content transfer decoding is performed using the transferDecoded optic. This will convert Quoted-Printable or Base64 encoded entities into their decoded form.

transferDecoded :: Getter WireEntity (Either EncodingError ByteEntity)
transferDecoded :: Getter WireEntity (Either EncodingError ByteEntity)
transferDecoded :: (HasTransferEncoding a, AsTransferEncodingError e) => Getter a (Either e (TransferDecoded a))

Charset decoding is performed using the charsetDecoded optic:

charsetDecoded :: Getter ByteEntity (Either EncodingError TextEntity)
charsetDecoded :: Getter ByteEntity (Either EncodingError TextEntity)
charsetDecoded :: (HasCharset a, AsCharsetError e) => Getter a (Either e (Decoded a))

Examples / HOWTO

Parse a MIME message:

parse (message mime) :: ByteString -> Either String MIMEMessage

Find the first entity with the text/plain content type:

getTextPlain :: MIMEMessage -> Maybe WireEntity
getTextPlain = firstOf (entities . filtered f)
  where
  f = matchContentType "text" (Just "plain") . view (headers . contentType)

Perform content transfer decoding and charset decoding while preserving decode errors:

view transferDecoded >=> view charsetDecoded :: WireEntity -> Either EncodingError TextEntity

Get all attachments (transfer decoded) and their filenames (if specified):

getAttachments :: MIMEMessage -> [(Either EncodingError B.ByteString, Maybe T.Text)]
getAttachments = toListOf (attachments . to (liftA2 (,) content name)
  where
  content = view transferDecodedBytes
  name = preview (headers . contentDisposition . filename)

Create an inline, plain text message and render it:

renderMessage $ createTextPlainMessage "This is a test body"

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

Defined in Data.MIME

Methods

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

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

Show MIME Source # 
Instance details

Defined in Data.MIME

Methods

showsPrec :: Int -> MIME -> ShowS #

show :: MIME -> String #

showList :: [MIME] -> ShowS #

mime :: Headers -> Parser 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 unconditionally treats them as a single part.

data EncStateByte Source #

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

Instances
HasCharset ByteEntity Source #

RFC 2046 §4.1.2. defines the default character set to be US-ASCII.

Instance details

Defined in Data.MIME

Associated Types

type Decoded ByteEntity :: Type 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

attachments :: Traversal' MIMEMessage WireEntity Source #

Leaf entities with Content-Disposition: attachment

isAttachment :: MIMEMessage -> Bool Source #

MIMEMessage content disposition is an Attachment

transferDecoded :: (HasTransferEncoding a, AsTransferEncodingError e) => Getter a (Either e (TransferDecoded a)) Source #

Perform content transfer decoding.

charsetDecoded :: (HasCharset a, AsCharsetError e) => Getter a (Either e (Decoded a)) Source #

Structure with the encoded data replaced with Text

Header processing

decodeEncodedWords :: 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 "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 "=?utf-8?B?bogus?="
=?utf-8?B?bogus?=

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

Language specification is supported (the datum is discarded).

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

Content-Type header

contentType :: Lens' Headers 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.

data ContentType Source #

Content-Type header (RFC 2183). Use parameters to access the parameters. Example:

ContentType "text" "plain" [("charset", "utf-8")]
Instances
Eq ContentType Source #

Equality of Content-Type. Type and subtype are compared case-insensitively and 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

Show ContentType Source # 
Instance details

Defined in Data.MIME

Generic ContentType Source # 
Instance details

Defined in Data.MIME

Associated Types

type Rep ContentType :: Type -> Type #

NFData ContentType Source # 
Instance details

Defined in Data.MIME

Methods

rnf :: ContentType -> () #

HasParameters ContentType Source # 
Instance details

Defined in Data.MIME

type Rep ContentType Source # 
Instance details

Defined in Data.MIME

matchContentType Source #

Arguments

:: CI ByteString

type

-> Maybe (CI ByteString)

optional subtype

-> ContentType 
-> Bool 

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

ctEq :: ContentType -> ContentType -> Bool Source #

Deprecated: Use matchContentType instead

Are the type and subtype the same? (parameters are ignored)

parseContentType :: Parser ContentType Source #

Parser for Content-Type header

showContentType :: ContentType -> Text Source #

Rendered content type field value for displaying

mimeBoundary :: Traversal' ContentType ByteString Source #

Get the boundary, if specified

Content-Type values

contentTypeMultipartMixed :: ByteString -> ContentType Source #

multipart/mixed; boundary=asdf

defaultContentType :: ContentType Source #

text/plain; charset=us-ascii

Content-Disposition header

contentDisposition :: Traversal' Headers ContentDisposition Source #

Get 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.

The fold may be empty, e.g. if the header is absent or unparseable.

data ContentDisposition Source #

Content-Disposition header (RFC 2183).

Use parameters to access the parameters.

data DispositionType Source #

Constructors

Inline 
Attachment 
Instances
Eq DispositionType Source # 
Instance details

Defined in Data.MIME

Show DispositionType Source # 
Instance details

Defined in Data.MIME

Generic DispositionType Source # 
Instance details

Defined in Data.MIME

Associated Types

type Rep DispositionType :: Type -> Type #

NFData DispositionType Source # 
Instance details

Defined in Data.MIME

Methods

rnf :: DispositionType -> () #

type Rep DispositionType Source # 
Instance details

Defined in Data.MIME

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

filename :: HasParameters a => 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")]

Serialisation

renderMessage :: MIMEMessage -> ByteString Source #

Serialise a given MIMEMessage into a ByteString. The message is serialised as is. No additional headers are set.

buildMessage :: MIMEMessage -> Builder Source #

Serialise a given MIMEMessage using a Builder

Mail creation

replyHeaderReferences :: Getter Headers (Maybe ByteString) Source #

Returns a space delimited ByteString with values from identification fields from the parents message Headers. Rules to gather the values are in accordance to RFC5322 - 3.6.4 as follows sorted by priority (first has precedence): * Values from References and `Message-ID` (if any) * Values from 'In-Reply-To' and 'Message-ID' (if any) * Value from 'Message-ID' (in case it's the first reply to a parent mail) * otherwise Nothing is returned indicating that the replying mail should not have a References field.

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.

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

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

createTextPlainMessage Source #

Arguments

:: Text

message body

-> MIMEMessage 

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

createMultipartMixedMessage Source #

Arguments

:: ByteString

Boundary

-> [MIMEMessage]

attachments

-> MIMEMessage 

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

Additional headers can be set (e.g. cc) by using At and Ixed, for example:

λ> set (at "subject") (Just "Hey there") $ Headers []
Headers [("subject", "Hey there")]

You can also use the Mailbox instances:

λ> let address = Mailbox (Just "roman") (AddrSpec "roman" (DomainLiteral "192.168.1.1"))
λ> set (at "cc") (Just $ renderMailbox address) $ Headers []
Headers [("cc", "\"roman\" roman@192.168.1.1")]

Re-exports