Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- newtype Boundary = Boundary {
- unBoundary :: Text
- data Mail = Mail {}
- emptyMail :: Address -> Mail
- data Address = Address {
- addressName :: Maybe Text
- addressEmail :: Text
- type Alternatives = [Part]
- data Part = Part {}
- data PartContent
- data Disposition
- data Encoding
- data InlineImage = InlineImage {}
- data ImageContent
- type Headers = [(ByteString, Text)]
- renderMail :: RandomGen g => g -> Mail -> (ByteString, g)
- renderMail' :: Mail -> IO ByteString
- sendmail :: ByteString -> IO ()
- sendmailCustom :: FilePath -> [String] -> ByteString -> IO ()
- sendmailCustomCaptureOutput :: FilePath -> [String] -> ByteString -> IO (ByteString, ByteString)
- renderSendMail :: Mail -> IO ()
- renderSendMailCustom :: FilePath -> [String] -> Mail -> IO ()
- simpleMail :: Address -> Address -> Text -> Text -> Text -> [(Text, FilePath)] -> IO Mail
- simpleMail' :: Address -> Address -> Text -> Text -> Mail
- simpleMailInMemory :: Address -> Address -> Text -> Text -> Text -> [(Text, Text, ByteString)] -> Mail
- simpleMailWithImages :: [Address] -> Address -> Text -> Text -> Text -> [InlineImage] -> [(Text, FilePath)] -> IO Mail
- addPart :: Alternatives -> Mail -> Mail
- addAttachment :: Text -> FilePath -> Mail -> IO Mail
- addAttachments :: [(Text, FilePath)] -> Mail -> IO Mail
- addAttachmentBS :: Text -> Text -> ByteString -> Mail -> Mail
- addAttachmentsBS :: [(Text, Text, ByteString)] -> Mail -> Mail
- renderAddress :: Address -> Text
- htmlPart :: Text -> Part
- plainPart :: Text -> Part
- filePart :: Text -> FilePath -> IO Part
- filePartBS :: Text -> Text -> ByteString -> Part
- randomString :: RandomGen d => Int -> d -> (String, d)
- quotedPrintable :: Bool -> ByteString -> Builder
- relatedPart :: [Part] -> Part
- addImage :: InlineImage -> IO Part
- mkImageParts :: [InlineImage] -> IO [Part]
Datatypes
MIME boundary between parts of a message.
Instances
Eq Boundary Source # | |
Show Boundary Source # | |
Random Boundary Source # | |
Defined in Network.Mail.Mime |
An entire mail message.
|
emptyMail :: Address -> Mail Source #
A mail message with the provided from
address and no other
fields filled in.
Address | |
|
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.
A single part of a multipart message.
Part | |
|
data PartContent Source #
NestedParts are for multipart-related: One HTML part and some inline images
Instances
Eq PartContent Source # | |
Defined in Network.Mail.Mime (==) :: PartContent -> PartContent -> Bool # (/=) :: PartContent -> PartContent -> Bool # | |
Show PartContent Source # | |
Defined in Network.Mail.Mime showsPrec :: Int -> PartContent -> ShowS # show :: PartContent -> String # showList :: [PartContent] -> ShowS # |
data Disposition Source #
Instances
Eq Disposition Source # | |
Defined in Network.Mail.Mime (==) :: Disposition -> Disposition -> Bool # (/=) :: Disposition -> Disposition -> Bool # | |
Show Disposition Source # | |
Defined in Network.Mail.Mime showsPrec :: Int -> Disposition -> ShowS # show :: Disposition -> String # showList :: [Disposition] -> ShowS # |
How to encode a single part. You should use Base64
for binary data.
data InlineImage Source #
Instances
Show InlineImage Source # | |
Defined in Network.Mail.Mime showsPrec :: Int -> InlineImage -> ShowS # show :: InlineImage -> String # showList :: [InlineImage] -> ShowS # |
data ImageContent Source #
Instances
Show ImageContent Source # | |
Defined in Network.Mail.Mime showsPrec :: Int -> ImageContent -> ShowS # show :: ImageContent -> String # showList :: [ImageContent] -> ShowS # |
type Headers = [(ByteString, Text)] Source #
Render a message
renderMail :: RandomGen g => g -> Mail -> (ByteString, g) Source #
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.
:: 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.
:: FilePath | sendmail executable path |
-> [String] | sendmail command-line options |
mail to render and send | |
-> IO () |
Render an email message and send via the specified sendmail executable with specified options.
High-level Mail
creation
:: 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.
A simple interface for generating an email with only plain-text body.
:: Address | to |
-> Address | from |
-> Text | subject |
-> Text | plain body |
-> Text | HTML body |
-> [(Text, Text, ByteString)] | content type, file name and contents of attachments |
A simple interface for generating an email with HTML and plain-text
alternatives and some ByteString
attachments.
Since 0.4.7
:: [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 Mail
s 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
.
:: Text | content type |
-> Text | file name |
-> ByteString | content |
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
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
mkImageParts :: [InlineImage] -> IO [Part] Source #