Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
An entire mail message.
|
Instances
Show Mail Source # | |
Generic Mail Source # | |
type Rep Mail Source # | |
Defined in Network.Mail.Mime type Rep Mail = D1 ('MetaData "Mail" "Network.Mail.Mime" "mime-mail-0.5.1-66CNjK9GzUy1UxWBoGDjk9" 'False) (C1 ('MetaCons "Mail" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mailFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Address) :*: (S1 ('MetaSel ('Just "mailTo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Address]) :*: S1 ('MetaSel ('Just "mailCc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Address]))) :*: (S1 ('MetaSel ('Just "mailBcc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Address]) :*: (S1 ('MetaSel ('Just "mailHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Headers) :*: S1 ('MetaSel ('Just "mailParts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Alternatives]))))) |
emptyMail :: Address -> Mail Source #
A mail message with the provided from
address and no other
fields filled in.
Address | |
|
Instances
Eq Address Source # | |
Show Address Source # | |
IsString Address Source # | |
Defined in Network.Mail.Mime fromString :: String -> Address # | |
Generic Address Source # | |
type Rep Address Source # | |
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.
A single part of a multipart message.
Part | |
|
Instances
Eq Part Source # | |
Show Part Source # | |
Generic Part Source # | |
type Rep Part Source # | |
Defined in Network.Mail.Mime type Rep Part = D1 ('MetaData "Part" "Network.Mail.Mime" "mime-mail-0.5.1-66CNjK9GzUy1UxWBoGDjk9" 'False) (C1 ('MetaCons "Part" 'PrefixI 'True) ((S1 ('MetaSel ('Just "partType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "partEncoding") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Encoding)) :*: (S1 ('MetaSel ('Just "partDisposition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Disposition) :*: (S1 ('MetaSel ('Just "partHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Headers) :*: S1 ('MetaSel ('Just "partContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PartContent))))) |
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 # | |
Generic PartContent Source # | |
Defined in Network.Mail.Mime type Rep PartContent :: Type -> Type # from :: PartContent -> Rep PartContent x # to :: Rep PartContent x -> PartContent # | |
type Rep PartContent Source # | |
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
How to encode a single part. You should use Base64
for binary data.
Instances
Eq Encoding Source # | |
Show Encoding Source # | |
Generic Encoding Source # | |
type Rep Encoding Source # | |
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
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 #
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 #