mime-mail-0.5.1: Compose MIME email messages.
Safe HaskellNone
LanguageHaskell2010

Network.Mail.Mime

Synopsis

Datatypes

newtype Boundary Source #

MIME boundary between parts of a message.

Constructors

Boundary 

Fields

Instances

Instances details
Eq Boundary Source # 
Instance details

Defined in Network.Mail.Mime

Show Boundary Source # 
Instance details

Defined in Network.Mail.Mime

Random Boundary Source # 
Instance details

Defined in Network.Mail.Mime

Methods

randomR :: RandomGen g => (Boundary, Boundary) -> g -> (Boundary, g) #

random :: RandomGen g => g -> (Boundary, g) #

randomRs :: RandomGen g => (Boundary, Boundary) -> g -> [Boundary] #

randoms :: RandomGen g => g -> [Boundary] #

data Mail Source #

An entire mail message.

Constructors

Mail 

Fields

Instances

Instances details
Show Mail Source # 
Instance details

Defined in Network.Mail.Mime

Methods

showsPrec :: Int -> Mail -> ShowS #

show :: Mail -> String #

showList :: [Mail] -> ShowS #

Generic Mail Source # 
Instance details

Defined in Network.Mail.Mime

Associated Types

type Rep Mail :: Type -> Type #

Methods

from :: Mail -> Rep Mail x #

to :: Rep Mail x -> Mail #

type Rep Mail Source # 
Instance details

Defined in Network.Mail.Mime

emptyMail :: Address -> Mail Source #

A mail message with the provided from address and no other fields filled in.

data Address Source #

Constructors

Address 

Instances

Instances details
Eq Address Source # 
Instance details

Defined in Network.Mail.Mime

Methods

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

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

Show Address Source # 
Instance details

Defined in Network.Mail.Mime

IsString Address Source # 
Instance details

Defined in Network.Mail.Mime

Methods

fromString :: String -> Address #

Generic Address Source # 
Instance details

Defined in Network.Mail.Mime

Associated Types

type Rep Address :: Type -> Type #

Methods

from :: Address -> Rep Address x #

to :: Rep Address x -> Address #

type Rep Address Source # 
Instance details

Defined in Network.Mail.Mime

type Rep Address = D1 ('MetaData "Address" "Network.Mail.Mime" "mime-mail-0.5.1-66CNjK9GzUy1UxWBoGDjk9" 'False) (C1 ('MetaCons "Address" 'PrefixI 'True) (S1 ('MetaSel ('Just "addressName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "addressEmail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

type Alternatives = [Part] Source #

Multiple alternative representations of the same data. For example, you could provide a plain-text and HTML version of a message.

data Part Source #

A single part of a multipart message.

Constructors

Part 

Fields

Instances

Instances details
Eq Part Source # 
Instance details

Defined in Network.Mail.Mime

Methods

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

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

Show Part Source # 
Instance details

Defined in Network.Mail.Mime

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

Generic Part Source # 
Instance details

Defined in Network.Mail.Mime

Associated Types

type Rep Part :: Type -> Type #

Methods

from :: Part -> Rep Part x #

to :: Rep Part x -> Part #

type Rep Part Source # 
Instance details

Defined in Network.Mail.Mime

data PartContent Source #

NestedParts are for multipart-related: One HTML part and some inline images

Instances

Instances details
Eq PartContent Source # 
Instance details

Defined in Network.Mail.Mime

Show PartContent Source # 
Instance details

Defined in Network.Mail.Mime

Generic PartContent Source # 
Instance details

Defined in Network.Mail.Mime

Associated Types

type Rep PartContent :: Type -> Type #

type Rep PartContent Source # 
Instance details

Defined in Network.Mail.Mime

type Rep PartContent = D1 ('MetaData "PartContent" "Network.Mail.Mime" "mime-mail-0.5.1-66CNjK9GzUy1UxWBoGDjk9" 'False) (C1 ('MetaCons "PartContent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: C1 ('MetaCons "NestedParts" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Part])))

data Disposition Source #

Instances

Instances details
Eq Disposition Source # 
Instance details

Defined in Network.Mail.Mime

Show Disposition Source # 
Instance details

Defined in Network.Mail.Mime

Generic Disposition Source # 
Instance details

Defined in Network.Mail.Mime

Associated Types

type Rep Disposition :: Type -> Type #

type Rep Disposition Source # 
Instance details

Defined in Network.Mail.Mime

type Rep Disposition = D1 ('MetaData "Disposition" "Network.Mail.Mime" "mime-mail-0.5.1-66CNjK9GzUy1UxWBoGDjk9" 'False) (C1 ('MetaCons "AttachmentDisposition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "InlineDisposition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "DefaultDisposition" 'PrefixI 'False) (U1 :: Type -> Type)))

data Encoding Source #

How to encode a single part. You should use Base64 for binary data.

Instances

Instances details
Eq Encoding Source # 
Instance details

Defined in Network.Mail.Mime

Show Encoding Source # 
Instance details

Defined in Network.Mail.Mime

Generic Encoding Source # 
Instance details

Defined in Network.Mail.Mime

Associated Types

type Rep Encoding :: Type -> Type #

Methods

from :: Encoding -> Rep Encoding x #

to :: Rep Encoding x -> Encoding #

type Rep Encoding Source # 
Instance details

Defined in Network.Mail.Mime

type Rep Encoding = D1 ('MetaData "Encoding" "Network.Mail.Mime" "mime-mail-0.5.1-66CNjK9GzUy1UxWBoGDjk9" 'False) ((C1 ('MetaCons "None" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Base64" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "QuotedPrintableText" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuotedPrintableBinary" 'PrefixI 'False) (U1 :: Type -> Type)))

data InlineImage Source #

Instances

Instances details
Show InlineImage Source # 
Instance details

Defined in Network.Mail.Mime

data ImageContent Source #

Instances

Instances details
Show ImageContent Source # 
Instance details

Defined in Network.Mail.Mime

Render a message

renderMail :: RandomGen g => g -> Mail -> (ByteString, g) Source #

Render a Mail with a given RandomGen for producing boundaries.

renderMail' :: Mail -> IO ByteString Source #

Like renderMail, but generates a random boundary.

Sending messages

sendmail :: ByteString -> IO () Source #

Send a fully-formed email message via the default sendmail executable with default options.

sendmailCustom Source #

Arguments

:: FilePath

sendmail executable path

-> [String]

sendmail command-line options

-> ByteString

mail message as lazy bytestring

-> IO () 

Send a fully-formed email message via the specified sendmail executable with specified options.

sendmailCustomCaptureOutput :: FilePath -> [String] -> ByteString -> IO (ByteString, ByteString) Source #

Like sendmailCustom, but also returns sendmail's output to stderr and stdout as strict ByteStrings.

Since 0.4.9

renderSendMail :: Mail -> IO () Source #

Render an email message and send via the default sendmail executable with default options.

renderSendMailCustom Source #

Arguments

:: FilePath

sendmail executable path

-> [String]

sendmail command-line options

-> Mail

mail to render and send

-> IO () 

Render an email message and send via the specified sendmail executable with specified options.

High-level Mail creation

simpleMail Source #

Arguments

:: Address

to

-> Address

from

-> Text

subject

-> Text

plain body

-> Text

HTML body

-> [(Text, FilePath)]

content type and path of attachments

-> IO Mail 

A simple interface for generating an email with HTML and plain-text alternatives and some file attachments.

Note that we use lazy IO for reading in the attachment contents.

simpleMail' Source #

Arguments

:: Address

to

-> Address

from

-> Text

subject

-> Text

body

-> Mail 

A simple interface for generating an email with only plain-text body.

simpleMailInMemory Source #

Arguments

:: Address

to

-> Address

from

-> Text

subject

-> Text

plain body

-> Text

HTML body

-> [(Text, Text, ByteString)]

content type, file name and contents of attachments

-> Mail 

A simple interface for generating an email with HTML and plain-text alternatives and some ByteString attachments.

Since 0.4.7

simpleMailWithImages Source #

Arguments

:: [Address]

to (multiple)

-> Address

from

-> Text

subject

-> Text

plain body

-> Text

HTML body

-> [InlineImage] 
-> [(Text, FilePath)]

content type and path of attachments

-> IO Mail 

An interface for generating an email with HTML and plain-text alternatives, some file attachments, and inline images. Note that we use lazy IO for reading in the attachment and inlined images. Inline images can be referred to from the HTML content using the src="cid:{{CONTENT-ID}}" syntax, where CONTENT-ID is the filename of the image.

Since 0.5.0

Utilities

addPart :: Alternatives -> Mail -> Mail Source #

Add an Alternative to the Mails parts.

To e.g. add a plain text body use > addPart [plainPart body] (emptyMail from)

addAttachment :: Text -> FilePath -> Mail -> IO Mail Source #

Add an attachment from a file and construct a Part.

addAttachmentBS Source #

Arguments

:: Text

content type

-> Text

file name

-> ByteString

content

-> Mail 
-> Mail 

Add an attachment from a ByteString and construct a Part.

Since 0.4.7

addAttachmentsBS :: [(Text, Text, ByteString)] -> Mail -> Mail Source #

Since 0.4.7

renderAddress :: Address -> Text Source #

Format an E-Mail address according to the name-addr form (see: RFC5322 § 3.4 "Address specification", i.e: [display-name] <addr-spec>) This can be handy for adding custom headers that require such format.

Since: 0.4.11

htmlPart :: Text -> Part Source #

Construct a UTF-8-encoded html Part.

plainPart :: Text -> Part Source #

Construct a UTF-8-encoded plain-text Part.

filePart :: Text -> FilePath -> IO Part Source #

Construct a BASE64-encoded file attachment Part

Since 0.5.0

filePartBS :: Text -> Text -> ByteString -> Part Source #

Construct a BASE64-encoded file attachment Part

Since 0.5.0

randomString :: RandomGen d => Int -> d -> (String, d) Source #

Generates a random sequence of alphanumerics of the given length.

quotedPrintable :: Bool -> ByteString -> Builder Source #

The first parameter denotes whether the input should be treated as text. If treated as text, then CRs will be stripped and LFs output as CRLFs. If binary, then CRs and LFs will be escaped.

relatedPart :: [Part] -> Part Source #

Add a Related Part

addImage :: InlineImage -> IO Part Source #

Add an inline image from a file and construct a Part.

Since 0.5.0