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

Robert Wills wrwills at gmail.com
Mon Oct 18 08:37:05 EDT 2010


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


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.

-Rob

On Mon, Oct 18, 2010 at 12:29 PM, Michael Snoyman <michael at snoyman.com> wrote:
> On Sun, Oct 17, 2010 at 7:07 PM, Jeremy Shaw <jeremy at n-heptane.com> wrote:
>> On Sun, Oct 17, 2010 at 10:14 AM, Michael Snoyman <michael at snoyman.com> wrote:
>>
>>> I'm sure people would love to see built-in support for serving over
>>> SMTP, but I think that's more appropriate for a different package.
>>> Proper SMTP support will also include SSL/TLS support, which will
>>> require even more dependencies.
>>
>> SMTPClient,
>>
>> http://hackage.haskell.org/package/SMTPClient-1.0.3
>>
>> can be used to send mail via SMTP to a smart host. It is still based
>> on 'String', but it is a start. To send a simple message you can do:
>>
>>  import Network.SMTP.Simple
>>  import System.IO
>>
>>  main :: IO ()
>>  main = do
>>     sendSimpleMessages (hPutStrLn stderr) "10.2.23.11" "example.com" [message]
>>     where message = SimpleMessage
>>                         [NameAddr (Just "John Doe") "johnd at example.com"]
>>                         [NameAddr (Just "Team") "team at exmaple.com"]
>>                         "My test email using Network.SMTP.Simple"
>>                         "Hi, this is a test email which uses SMTPClient."
>>
>> I wonder what it would take to make it so that the message body could
>> be multipart mime...
>
> Currently, the idea in mime-mail is to produce fully-formed messages,
> complete with headers, encoded as UTF-8 lazy bytestrings. To address
> the headers issue, we would need to do one of:
>
> * Allow SMTPClient to accept messages with the headers already attached.
> * Modify mime-mail to produce a list of headers separate from the
> message content. I'm not opposed to this.
>
> Regarding the String/ByteString issue, there are three choices I believe:
>
> * Switch mime-mail to use Strings. I *am* opposed to this ;).
> * Switch SMTPClient to use ByteStrings. I think this is the right answer.
> * Leave the libraries as-is, and just use a Lazy.Char8.unpack to bridge the two.
>
> Am I leaving anything out? I'd be happy to try and get mime-mail to
> work with SMTPClient.
>
> Michael
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list