[Haskell-cafe] Re: Should Yesod.Mail be a separate package?

Michael Snoyman michael at snoyman.com
Mon Oct 18 08:57:41 EDT 2010


On Mon, Oct 18, 2010 at 2:37 PM, Robert Wills <wrwills at gmail.com> wrote:
> I've had a look at mime-mail and think it provides a nice interface
> for sending emails.
>
> I started trying to write up a simple default interface to it for
> easily adding attachments (I was going to look at adding a
> pandoc-based automatic markdown to html later today).
>
> getMimeType ('g':'p':'j':'.':_) =  "image/jpeg"
> getMimeType ('g':'e':'p':'j':'.':_) =  "image/jpeg"
> getMimeType ('f':'d':'p':'.':_) =  "application/pdf"
>
> simpleMail to from subject body attachments =
>    do
>      readAttachments <- mapM (\x -> B.readFile x) attachments
>      return Mail {
>                   mailHeaders =
>                       [ ("To", to)
>                       ,("From", from)
>                       ,("Subject", subject)
>                       ]
>                 , mailParts =
>                     [
>                      [ Part "text/plain" None Nothing $ LU.fromString
> $ unlines body
>                      , Part "text/html" None Nothing $ LU.fromString
> $ unlines body
>                      ]]
>                     ++
>                     (map (\x -> [Part (getMimeType $ reverse $ fst x)
> Base64 (Just $ fst x) $ snd x])
>                              $ zip attachments readAttachments)
>                 }
>
>
> main = do
>  myMail <-  simpleMail
>             "wrwills at gmail.com"
>             "mimemail at test.com"
>             "a test message"
>             [ "so much depends"
>             , "upon"
>             , "a red wheel"
>             , "barrow 你好"
>             ]
>             ["/tmp/cv.pdf", "/tmp/img.jpg"]
>  renderSendMail myMail

This is *exactly* the kind of high-level interface I was hoping
someone would provide ;). Anyone have any objections to this being the
de-facto "simple" interface for mime-mail?

> HaskellNet uses Bytestrings for sending mail so it might be easier to
> use it for basic smarthost
> sending with mime-mail than with SMTPClient -- but then again
> SMTPClient looks at first blush
> to be more adaptable.
>
> I tried to use put the result of renderMail' into HaskellNet's sendMail
>
>  renderedMail <- renderMail' myMail
>  HN.sendMail from [to] renderedMail con
>  HN.closeSMTP con
>
> but the typechecker didn't like it:
>    Couldn't match expected type `Data.ByteString.Internal.ByteString'
>           against inferred type `B.ByteString'
>    In the third argument of `HN.sendMail', namely `renderedMail'
>
> because B.ByteString is Data.ByteString.Lazy.
>
> Not sure how easy that would be to fix.  I'm a little confused by all
> the different
> types of ByteStrings.

I can help out there. A lazy ByteString is nothing more than a lazy
list of strict ByteStrings. This can be more efficient since we don't
need a gigantic single block of memory, and can also allow us to
generate data lazily, one chunk at a time. Converting a lazy
ByteString to a strict one can be done with:

import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L

lazyToStrict = S.concat . L.toChunks

And as a bonus:

strictToLazy = L.fromChunks . return

There's performance issues to take into account when converting a lazy
bytestring into a strict one, *especially* when dealing with possibly
large attachments. If HaskellNet accepted a lazy bytestring, for
example, you would be able to send very large attachments with your
code above without using up much memory, due to the lazy IO performed
by readFile. However, calling lazyToStrict above will force the entire
email body, and thus the entirety of all attachments, into memory.

I haven't looked at HaskellNet yet, but my initial recommendation
would be to add support for a lazy interface as well.

Michael


More information about the Haskell-Cafe mailing list