Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module extends Data.IMF with types for handling MIME messages (RFC 2045, 2046, 2183 and others).
Synopsis
- data MIME
- = Part ByteString
- | Encapsulated MIMEMessage
- | Multipart MultipartSubtype Boundary (NonEmpty MIMEMessage)
- | FailedParse MIMEParseError ByteString
- mime :: Headers -> BodyHandler MIME
- type MIMEMessage = Message EncStateWire MIME
- type WireEntity = Message EncStateWire ByteString
- type ByteEntity = Message EncStateByte ByteString
- type TextEntity = Message () Text
- data EncStateWire
- data EncStateByte
- entities :: Traversal' MIMEMessage WireEntity
- attachments :: Traversal' MIMEMessage WireEntity
- isAttachment :: HasHeaders a => a -> Bool
- transferDecoded :: (HasTransferEncoding a, AsTransferEncodingError e, Profunctor p, Contravariant f) => Optic' p f a (Either e (TransferDecoded a))
- transferDecoded' :: (HasTransferEncoding a, Profunctor p, Contravariant f) => Optic' p f a (Either TransferEncodingError (TransferDecoded a))
- charsetDecoded :: (HasCharset a, AsCharsetError e) => CharsetLookup -> forall p f. (Profunctor p, Contravariant f) => Optic' p f a (Either e (Decoded a))
- charsetDecoded' :: HasCharset a => CharsetLookup -> forall p f. (Profunctor p, Contravariant f) => Optic' p f a (Either CharsetError (Decoded a))
- decodeEncodedWords :: CharsetLookup -> ByteString -> Text
- contentType :: HasHeaders a => Lens' a ContentType
- data ContentTypeWith a = ContentType (CI ByteString) (CI ByteString) a
- type ContentType = ContentTypeWith Parameters
- ctType :: Lens' (ContentTypeWith a) (CI ByteString)
- ctSubtype :: Lens' (ContentTypeWith a) (CI ByteString)
- matchContentType :: CI ByteString -> Maybe (CI ByteString) -> ContentTypeWith a -> Bool
- parseContentType :: Parser ContentType
- renderContentType :: ContentType -> ByteString
- showContentType :: ContentType -> Text
- data MultipartSubtype
- data Boundary
- makeBoundary :: ByteString -> Either ByteString Boundary
- unBoundary :: Boundary -> ByteString
- mimeBoundary :: Traversal' ContentType ByteString
- contentTypeTextPlain :: ContentType
- contentTypeApplicationOctetStream :: ContentType
- contentTypeMultipartMixed :: Boundary -> ContentType
- defaultContentType :: ContentType
- contentDisposition :: HasHeaders a => Lens' a (Maybe ContentDisposition)
- data ContentDisposition = ContentDisposition DispositionType Parameters
- data DispositionType
- = Inline
- | Attachment
- dispositionType :: Lens' ContentDisposition DispositionType
- filename :: HasParameters a => CharsetLookup -> Traversal' a Text
- filenameParameter :: HasParameters a => Lens' a (Maybe EncodedParameterValue)
- renderContentDisposition :: ContentDisposition -> ByteString
- data ContentID
- makeContentID :: ByteString -> Either ByteString ContentID
- parseContentID :: Parser ContentID
- buildContentID :: ContentID -> Builder
- renderContentID :: ContentID -> ByteString
- headerContentID :: HasHeaders a => Lens' a (Maybe ContentID)
- createTextPlainMessage :: Text -> MIMEMessage
- createAttachment :: ContentType -> Maybe FilePath -> ByteString -> MIMEMessage
- createAttachmentFromFile :: ContentType -> FilePath -> IO MIMEMessage
- createMultipartMixedMessage :: Boundary -> NonEmpty MIMEMessage -> MIMEMessage
- setTextPlainBody :: Text -> Message ctx a -> MIMEMessage
- encapsulate :: MIMEMessage -> MIMEMessage
- type CharsetLookup = CI ByteString -> Maybe Charset
- defaultCharsets :: CharsetLookup
- module Data.IMF
- module Data.MIME.Parameter
- module Data.MIME.Error
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
. This instance
is provided as convenience for static values. For parsing mailboxes,
use one of:IsString
Mailbox
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 StringMIMEMessage
λ> 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") . viewcontentType
λ> :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.
λ> :tfilename
filename :: (HasParameters
a, Applicative f) =>CharsetLookup
-> (T.Text -> f T.Text) -> a -> f a λ> :tdefaultCharsets
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
MIME message body. Either a single Part
, or Multipart
.
Only the body is represented; preamble and epilogue are not.
Part ByteString | |
Encapsulated MIMEMessage | |
Multipart MultipartSubtype Boundary (NonEmpty MIMEMessage) | |
FailedParse MIMEParseError ByteString |
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.
type MIMEMessage = Message EncStateWire MIME Source #
type WireEntity = Message EncStateWire ByteString Source #
type ByteEntity = Message EncStateByte ByteString Source #
type TextEntity = Message () Text Source #
data EncStateWire Source #
Entity is formatted for transfer. Processing requires transfer decoding.
Instances
HasTransferEncoding WireEntity Source # | |
Defined in Data.MIME type TransferDecoded WireEntity Source # transferEncodingName :: Getter WireEntity TransferEncodingName Source # transferEncodedData :: Getter WireEntity ByteString Source # transferDecoded :: (AsTransferEncodingError e, Profunctor p, Contravariant f) => Optic' p f WireEntity (Either e (TransferDecoded WireEntity)) Source # transferDecoded' :: (Profunctor p, Contravariant f) => Optic' p f WireEntity (Either TransferEncodingError (TransferDecoded WireEntity)) Source # transferEncode :: TransferDecoded WireEntity -> WireEntity Source # | |
type TransferDecoded WireEntity Source # | |
Defined in Data.MIME |
data EncStateByte Source #
Entity requires content-transfer-encoding to send, and may require charset decoding to read.
Instances
HasCharset ByteEntity Source # | RFC 6657
specifies that each subtype of the
|
Defined in Data.MIME type Decoded ByteEntity Source # charsetName :: Getter ByteEntity (Maybe CharsetName) Source # charsetData :: Getter ByteEntity ByteString Source # charsetDecoded :: AsCharsetError e => CharsetLookup -> forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Profunctor p, Contravariant f) => Optic' p f ByteEntity (Either e (Decoded ByteEntity)) Source # charsetDecoded' :: CharsetLookup -> forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Profunctor p, Contravariant f) => Optic' p f ByteEntity (Either CharsetError (Decoded ByteEntity)) Source # | |
type Decoded ByteEntity Source # | |
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).
ContentType (CI ByteString) (CI ByteString) a |
Instances
type ContentType = ContentTypeWith Parameters Source #
ctType :: Lens' (ContentTypeWith a) (CI ByteString) Source #
ctSubtype :: Lens' (ContentTypeWith a) (CI ByteString) Source #
:: 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 #
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 |
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
|
| |
Signed | RFC 1847 §2.1. Signed messages. |
| |
Encrypted | |
| |
Report | RFC 6522. Electronic mail reports. |
| |
Multilingual | RFC 8255.
Multilingual messages. The first part should be a multilingual
explanatory preface. Subsequent parts MUST have a
|
Unrecognised (CI ByteString) |
Instances
Show MultipartSubtype Source # | |
Defined in Data.MIME showsPrec :: Int -> MultipartSubtype -> ShowS # show :: MultipartSubtype -> String # showList :: [MultipartSubtype] -> ShowS # | |
Eq MultipartSubtype Source # | |
Defined in Data.MIME (==) :: MultipartSubtype -> MultipartSubtype -> Bool # (/=) :: MultipartSubtype -> MultipartSubtype -> Bool # |
boundary
parameter
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 BoundarygetStdRandom
uniform
:: IO Boundary
unBoundary :: Boundary -> ByteString Source #
mimeBoundary :: Traversal' ContentType ByteString Source #
Traversal of boundary
parameter (which may be unspecified)
Content-Type values
contentTypeTextPlain :: ContentType Source #
text/plain
contentTypeApplicationOctetStream :: ContentType Source #
application/octet-stream
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
data DispositionType Source #
Instances
Generic DispositionType Source # | |
Defined in Data.MIME type Rep DispositionType :: Type -> Type # from :: DispositionType -> Rep DispositionType x # to :: Rep DispositionType x -> DispositionType # | |
Show DispositionType Source # | |
Defined in Data.MIME showsPrec :: Int -> DispositionType -> ShowS # show :: DispositionType -> String # showList :: [DispositionType] -> ShowS # | |
NFData DispositionType Source # | |
Defined in Data.MIME rnf :: DispositionType -> () # | |
Eq DispositionType Source # | |
Defined in Data.MIME (==) :: DispositionType -> DispositionType -> Bool # (/=) :: DispositionType -> DispositionType -> Bool # | |
type Rep DispositionType Source # | |
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
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.
buildContentID :: ContentID -> Builder Source #
headerContentID :: HasHeaders a => Lens' a (Maybe ContentID) Source #
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.
createMultipartMixedMessage Source #
:: 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
type CharsetLookup = CI ByteString -> Maybe Charset Source #
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
module Data.MIME.Parameter
module Data.MIME.Error