Should Yesod.Mail be a separate package?

Hey all, I wrote a simple email module in Yesod[1] that handles such things as multipart messages and Base64 encoding. It's still missing some features (multipart/alternative, for instance), but it can be useful for throwing together emails. It's currently part of the yesod package, but I'm going to be moving it to a separate package to free me up to make breaking API changes more frequently. As of right now, I'm just going to move it into the yesod-auth package (also being split off from the main yesod package), and therefore it will still have all the dependencies on Yesod. My question is whether people would find this package useful outside the scope of Yesod. There are no dependencies from this module onto any Yesod-specific stuff, so this separation could easily be done. I just don't feel like adding another package to maintain if no one is interested. So if anyone wants this offered up as a separate package, and/or has any API suggestions, please let me know. Michael [1] http://hackage.haskell.org/packages/archive/yesod/0.5.4/doc/html/Yesod-Mail....

Hi Michael,
Last time I checked Hackage for email libraries I could find some
basic SMTP systems but nothing very recent or robust.
Practically every web app needs to send email, so I think that a
robust and well maintained email package would be very useful.
I know you have many other projects going at the minute, but if you
had a chance to create a stand alone email package, I'd be interested
in trying it out.
I've been working on a web app engine that combines Heist from Snap
and several of the WAI packages with an object store system I've
developed myself (and will release on Hackage at some point). Email
was a missing piece and it sounds like your package could fill the gap
nicely.
Kevin
On Oct 17, 8:11 am, Michael Snoyman
Hey all,
I wrote a simple email module in Yesod[1] that handles such things as multipart messages and Base64 encoding. It's still missing some features (multipart/alternative, for instance), but it can be useful for throwing together emails. It's currently part of the yesod package, but I'm going to be moving it to a separate package to free me up to make breaking API changes more frequently.
As of right now, I'm just going to move it into the yesod-auth package (also being split off from the main yesod package), and therefore it will still have all the dependencies on Yesod. My question is whether people would find this package useful outside the scope of Yesod. There are no dependencies from this module onto any Yesod-specific stuff, so this separation could easily be done. I just don't feel like adding another package to maintain if no one is interested.
So if anyone wants this offered up as a separate package, and/or has any API suggestions, please let me know.
Michael
[1]http://hackage.haskell.org/packages/archive/yesod/0.5.4/doc/html/Yeso... _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Last summer I put cabalized HaskellNet (written by Jun Mukai for a
GSOC) (http://hackage.haskell.org/package/HaskellNet)
and uploaded it to hackage. I put myself down as a maintainer but I
haven't done much maintaining.
HaskellNet also does multipart mime and base64 stuff as well as imap
and pop access. I haven't looked at Michael's package yet -- I'll
have a look this morning
to compare.
I've been meaning to add try to tls support to HaskellNet.
I don't have any huge attachment to HaskellNet so I'd be happy to just
help to migrate the useful bits of it to some larger official email
package.
-Rob
On Sun, Oct 17, 2010 at 8:32 AM, Kevin Jardine
Hi Michael,
Last time I checked Hackage for email libraries I could find some basic SMTP systems but nothing very recent or robust.
Practically every web app needs to send email, so I think that a robust and well maintained email package would be very useful.
I know you have many other projects going at the minute, but if you had a chance to create a stand alone email package, I'd be interested in trying it out.
I've been working on a web app engine that combines Heist from Snap and several of the WAI packages with an object store system I've developed myself (and will release on Hackage at some point). Email was a missing piece and it sounds like your package could fill the gap nicely.
Kevin
On Oct 17, 8:11 am, Michael Snoyman
wrote: Hey all,
I wrote a simple email module in Yesod[1] that handles such things as multipart messages and Base64 encoding. It's still missing some features (multipart/alternative, for instance), but it can be useful for throwing together emails. It's currently part of the yesod package, but I'm going to be moving it to a separate package to free me up to make breaking API changes more frequently.
As of right now, I'm just going to move it into the yesod-auth package (also being split off from the main yesod package), and therefore it will still have all the dependencies on Yesod. My question is whether people would find this package useful outside the scope of Yesod. There are no dependencies from this module onto any Yesod-specific stuff, so this separation could easily be done. I just don't feel like adding another package to maintain if no one is interested.
So if anyone wants this offered up as a separate package, and/or has any API suggestions, please let me know.
Michael
[1]http://hackage.haskell.org/packages/archive/yesod/0.5.4/doc/html/Yeso... _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Robert,
I did look at HaskellNet a few months ago.
It looked big and undocumented so I guess I got scared away.
What I'd be interested in is something with the simplicity of the PHP
mail command (or perhaps the phpmailer package).
I dislike PHP as a programming language but it does basic web
functions like outgoing email fairly well.
Perhaps HaskellNet just needs more documentation and examples?
Kevin
On Oct 17, 10:05 am, Robert Wills
Last summer I put cabalized HaskellNet (written by Jun Mukai for a GSOC) (http://hackage.haskell.org/package/HaskellNet) and uploaded it to hackage. I put myself down as a maintainer but I haven't done much maintaining.
HaskellNet also does multipart mime and base64 stuff as well as imap and pop access. I haven't looked at Michael's package yet -- I'll have a look this morning to compare.
I've been meaning to add try to tls support to HaskellNet.
I don't have any huge attachment to HaskellNet so I'd be happy to just help to migrate the useful bits of it to some larger official email package.
-Rob
On Sun, Oct 17, 2010 at 8:32 AM, Kevin Jardine
wrote: Hi Michael,
Last time I checked Hackage for email libraries I could find some basic SMTP systems but nothing very recent or robust.
Practically every web app needs to send email, so I think that a robust and well maintained email package would be very useful.
I know you have many other projects going at the minute, but if you had a chance to create a stand alone email package, I'd be interested in trying it out.
I've been working on a web app engine that combines Heist from Snap and several of the WAI packages with an object store system I've developed myself (and will release on Hackage at some point). Email was a missing piece and it sounds like your package could fill the gap nicely.
Kevin
On Oct 17, 8:11 am, Michael Snoyman
wrote: Hey all,
I wrote a simple email module in Yesod[1] that handles such things as multipart messages and Base64 encoding. It's still missing some features (multipart/alternative, for instance), but it can be useful for throwing together emails. It's currently part of the yesod package, but I'm going to be moving it to a separate package to free me up to make breaking API changes more frequently.
As of right now, I'm just going to move it into the yesod-auth package (also being split off from the main yesod package), and therefore it will still have all the dependencies on Yesod. My question is whether people would find this package useful outside the scope of Yesod. There are no dependencies from this module onto any Yesod-specific stuff, so this separation could easily be done. I just don't feel like adding another package to maintain if no one is interested.
So if anyone wants this offered up as a separate package, and/or has any API suggestions, please let me know.
Michael
[1]http://hackage.haskell.org/packages/archive/yesod/0.5.4/doc/html/Yeso... _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-C...@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Yes you're right Kevin. I'll put up a new release sometime in the
next week with some more examples
and possible some simpler methods if only so HaskellNet can be more
easily evaluated.
As I recall Happstack also uses an smtp library. I forget which one.
-Rob
On Sun, Oct 17, 2010 at 9:29 AM, Kevin Jardine
Hi Robert,
I did look at HaskellNet a few months ago.
It looked big and undocumented so I guess I got scared away.
What I'd be interested in is something with the simplicity of the PHP mail command (or perhaps the phpmailer package).
I dislike PHP as a programming language but it does basic web functions like outgoing email fairly well.
Perhaps HaskellNet just needs more documentation and examples?
Kevin
On Oct 17, 10:05 am, Robert Wills
wrote: Last summer I put cabalized HaskellNet (written by Jun Mukai for a GSOC) (http://hackage.haskell.org/package/HaskellNet) and uploaded it to hackage. I put myself down as a maintainer but I haven't done much maintaining.
HaskellNet also does multipart mime and base64 stuff as well as imap and pop access. I haven't looked at Michael's package yet -- I'll have a look this morning to compare.
I've been meaning to add try to tls support to HaskellNet.
I don't have any huge attachment to HaskellNet so I'd be happy to just help to migrate the useful bits of it to some larger official email package.
-Rob
On Sun, Oct 17, 2010 at 8:32 AM, Kevin Jardine
wrote: Hi Michael,
Last time I checked Hackage for email libraries I could find some basic SMTP systems but nothing very recent or robust.
Practically every web app needs to send email, so I think that a robust and well maintained email package would be very useful.
I know you have many other projects going at the minute, but if you had a chance to create a stand alone email package, I'd be interested in trying it out.
I've been working on a web app engine that combines Heist from Snap and several of the WAI packages with an object store system I've developed myself (and will release on Hackage at some point). Email was a missing piece and it sounds like your package could fill the gap nicely.
Kevin
On Oct 17, 8:11 am, Michael Snoyman
wrote: Hey all,
I wrote a simple email module in Yesod[1] that handles such things as multipart messages and Base64 encoding. It's still missing some features (multipart/alternative, for instance), but it can be useful for throwing together emails. It's currently part of the yesod package, but I'm going to be moving it to a separate package to free me up to make breaking API changes more frequently.
As of right now, I'm just going to move it into the yesod-auth package (also being split off from the main yesod package), and therefore it will still have all the dependencies on Yesod. My question is whether people would find this package useful outside the scope of Yesod. There are no dependencies from this module onto any Yesod-specific stuff, so this separation could easily be done. I just don't feel like adding another package to maintain if no one is interested.
So if anyone wants this offered up as a separate package, and/or has any API suggestions, please let me know.
Michael
[1]http://hackage.haskell.org/packages/archive/yesod/0.5.4/doc/html/Yeso... _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-C...@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Something along the lines of these examples would be helpful I think:
http://phpmailer.worxware.com/index.php?pg=examples
Phpmailer is probably the most widely used email library, so if it
could be shown that there was a Haskell equivalent (or better), I
think that might start attracting the attention of web developers.
Kevin
On Oct 17, 11:13 am, Robert Wills
Yes you're right Kevin. I'll put up a new release sometime in the next week with some more examples and possible some simpler methods if only so HaskellNet can be more easily evaluated.
As I recall Happstack also uses an smtp library. I forget which one.
-Rob
On Sun, Oct 17, 2010 at 9:29 AM, Kevin Jardine
wrote: Hi Robert,
I did look at HaskellNet a few months ago.
It looked big and undocumented so I guess I got scared away.
What I'd be interested in is something with the simplicity of the PHP mail command (or perhaps the phpmailer package).
I dislike PHP as a programming language but it does basic web functions like outgoing email fairly well.
Perhaps HaskellNet just needs more documentation and examples?
Kevin
On Oct 17, 10:05 am, Robert Wills
wrote: Last summer I put cabalized HaskellNet (written by Jun Mukai for a GSOC) (http://hackage.haskell.org/package/HaskellNet) and uploaded it to hackage. I put myself down as a maintainer but I haven't done much maintaining.
HaskellNet also does multipart mime and base64 stuff as well as imap and pop access. I haven't looked at Michael's package yet -- I'll have a look this morning to compare.
I've been meaning to add try to tls support to HaskellNet.
I don't have any huge attachment to HaskellNet so I'd be happy to just help to migrate the useful bits of it to some larger official email package.
-Rob
On Sun, Oct 17, 2010 at 8:32 AM, Kevin Jardine
wrote: Hi Michael,
Last time I checked Hackage for email libraries I could find some basic SMTP systems but nothing very recent or robust.
Practically every web app needs to send email, so I think that a robust and well maintained email package would be very useful.
I know you have many other projects going at the minute, but if you had a chance to create a stand alone email package, I'd be interested in trying it out.
I've been working on a web app engine that combines Heist from Snap and several of the WAI packages with an object store system I've developed myself (and will release on Hackage at some point). Email was a missing piece and it sounds like your package could fill the gap nicely.
Kevin
On Oct 17, 8:11 am, Michael Snoyman
wrote: Hey all,
I wrote a simple email module in Yesod[1] that handles such things as multipart messages and Base64 encoding. It's still missing some features (multipart/alternative, for instance), but it can be useful for throwing together emails. It's currently part of the yesod package, but I'm going to be moving it to a separate package to free me up to make breaking API changes more frequently.
As of right now, I'm just going to move it into the yesod-auth package (also being split off from the main yesod package), and therefore it will still have all the dependencies on Yesod. My question is whether people would find this package useful outside the scope of Yesod. There are no dependencies from this module onto any Yesod-specific stuff, so this separation could easily be done. I just don't feel like adding another package to maintain if no one is interested.
So if anyone wants this offered up as a separate package, and/or has any API suggestions, please let me know.
Michael
[1]http://hackage.haskell.org/packages/archive/yesod/0.5.4/doc/html/Yeso... _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-C...@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-C...@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

I'm a bit partial to Swift Mailer [1]. It's useful to support multiple transport backends, especially in situations where sendmail is not portable. Cheers, Edward [1] http://swiftmailer.org/

OK, I've put together a new repository on github[1]. I've modified the original code from Yesod to now include support for multipart/alternative, and to only create a multipart when there really are multiple parts. I've done some simple tests, and it seems to work just fine. Now a question for everyone interested in this library is: the API is currently very low-level. Should this package include higher-level wrappers? 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. Another possible helper package (an idea from Jeremy Shaw) would be using Pandoc to automatically create multipart messages from markdown. Once again, I won't include support in the main package because it will increase dependencies. Anyway, I'd like to get a first version released within the week so it doesn't hold up Yesod 0.6, but the beauty of having it as a separate package is we can always make changes later. Michael [1] http://github.com/snoyberg/mime-mail

On Sun, Oct 17, 2010 at 10:14 AM, Michael Snoyman
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@example.com"] [NameAddr (Just "Team") "team@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... - jeremy

Quoth Jeremy Shaw
I wonder what it would take to make it so that the message body could be multipart mime...
Well, here's what it takes for me - - function to determine file type of attachment (e.g., image/jpeg) - data encoding (base64, maybe quoted-printable, others) - randomly generated separator string - a few standard header lines like "MIME-Version: 1.0" Not that I actually randomize the separator string, but I should, and I base64 encode everthing. My obscure platform provides the function to determine file type. Donn ------------
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@example.com"] [NameAddr (Just "Team") "team@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...

On Sun, Oct 17, 2010 at 7:07 PM, Jeremy Shaw
On Sun, Oct 17, 2010 at 10:14 AM, Michael Snoyman
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@example.com"] [NameAddr (Just "Team") "team@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

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@gmail.com"
"mimemail@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
On Sun, Oct 17, 2010 at 7:07 PM, Jeremy Shaw
wrote: On Sun, Oct 17, 2010 at 10:14 AM, Michael Snoyman
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@example.com"] [NameAddr (Just "Team") "team@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Oct 18, 2010 at 2:37 PM, Robert Wills
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@gmail.com" "mimemail@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

On Mon, Oct 18, 2010 at 1:57 PM, Michael Snoyman
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?
Cool. It might be good to have something a little more composable so eg you could add ccs without having to drop down to the lower-level.
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:
Great that worked. I'll have a look at HaskellNet and see how easy it'll be to change. I've put the file I was playing with up here: http://gist.github.com/632222 -Rob

I've updated the gist to now include automatic conversion through
pandoc of markdown to html.
On Mon, Oct 18, 2010 at 2:32 PM, Robert Wills
On Mon, Oct 18, 2010 at 1:57 PM, Michael Snoyman
wrote: 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?
Cool. It might be good to have something a little more composable so eg you could add ccs without having to drop down to the lower-level.
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:
Great that worked. I'll have a look at HaskellNet and see how easy it'll be to change.
I've put the file I was playing with up here: http://gist.github.com/632222
-Rob

Just for the record, while I like the markdown-based interface, I
can't include it in the mime-mail package: I'm not going to make
Pandoc a dependency of mime-mail, both for weight and license reasons.
It would be awesome to see a markdown-mail or similar package,
however.
Michael
On Mon, Oct 18, 2010 at 4:33 PM, Robert Wills
I've updated the gist to now include automatic conversion through pandoc of markdown to html.
On Mon, Oct 18, 2010 at 2:32 PM, Robert Wills
wrote: On Mon, Oct 18, 2010 at 1:57 PM, Michael Snoyman
wrote: 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?
Cool. It might be good to have something a little more composable so eg you could add ccs without having to drop down to the lower-level.
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:
Great that worked. I'll have a look at HaskellNet and see how easy it'll be to change.
I've put the file I was playing with up here: http://gist.github.com/632222
-Rob

Yes I was thinking that too. Bringing in Pandoc brings in too many
other dependencies.
Perhaps it could be left in an uncompiled example or readme?
On Mon, Oct 18, 2010 at 6:20 PM, Michael Snoyman
Just for the record, while I like the markdown-based interface, I can't include it in the mime-mail package: I'm not going to make Pandoc a dependency of mime-mail, both for weight and license reasons. It would be awesome to see a markdown-mail or similar package, however.
Michael
On Mon, Oct 18, 2010 at 4:33 PM, Robert Wills
wrote: I've updated the gist to now include automatic conversion through pandoc of markdown to html.
On Mon, Oct 18, 2010 at 2:32 PM, Robert Wills
wrote: On Mon, Oct 18, 2010 at 1:57 PM, Michael Snoyman
wrote: 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?
Cool. It might be good to have something a little more composable so eg you could add ccs without having to drop down to the lower-level.
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:
Great that worked. I'll have a look at HaskellNet and see how easy it'll be to change.
I've put the file I was playing with up here: http://gist.github.com/632222
-Rob

OK everybody, mime-mail is on Hackage[1].
Michael
[1] http://hackage.haskell.org/package/mime-mail
On Mon, Oct 18, 2010 at 3:32 PM, Robert Wills
On Mon, Oct 18, 2010 at 1:57 PM, Michael Snoyman
wrote: 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?
Cool. It might be good to have something a little more composable so eg you could add ccs without having to drop down to the lower-level.
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:
Great that worked. I'll have a look at HaskellNet and see how easy it'll be to change.
I've put the file I was playing with up here: http://gist.github.com/632222
-Rob

Michael Snoyman wrote:
Great news! This is an important package. It's obviously very preliminary, though. This is not trivial to get right - look at the long and colorful history of the Python email library, detailed on the first page of the library documentation. Here are some initial suggestions for improvement: 1. The module name Network.Mail.Mime is too generic. There will also be a parser someday. We should have Types, Parse, and Render in separate modules. I expect each of those to grow gradually as more features are added. On the other hand, I think I like the decision to re-implement just the features of RFC 2822 message format needed for everyday MIME use rather than building this on top of a more generic message type, as is done in Python. It simplifies things. But are multi-line headers supported properly? That's trickier than it looks, there have historically been many wrong implementations out there. That itself could be a reason to build this on top of a proper RFC 2822 implementation. 2. mailHeaders should have an Ord instance that compares case-insensitively, though the underlying Strings should remain Strings. 3. It should be possible to control whether text parts get quoted-printable encoded. Perhaps add QuotedPrintable to Encoding? 4. I don't like having those sendmail things here in the same module and package. It's convenient, but messy in several ways - creates a spurious dependency on process, only works on certain platforms and even then with possible weird platform dependencies, etc. I think this should be in a separate package. Once there is a nice easy-to-use SMTP companion package, I don't think the sendmail things will be used that much anyway. Put them in a separate package, but mention it in prominent places so people will find it. 5. Is the blaze-builder dependency necessary now that Bryan has built those techniques into Data.Text? 6. Are I18N text-encoded headers supported? That's very important, even for simple everyday usage. It's a bit complicated, though. That might be another reason to build on top of a full RFC 2822 implementation. 7. This very simple interface is great for everyday use. Think about how to add the less common options for more general use, without cluttering up the everyday interface - custom parameters for Content-Type and Content-Disposition, specifying the boundary rather than allowing it to be generated automatically, etc. It's important to think about those kinds of things now, before the interface gets set in cement. Thanks, Yitz

On 10/20/10 10:51 AM, Yitzchak Gale wrote:
2. mailHeaders should have an Ord instance that compares case-insensitively, though the underlying Strings should remain Strings.
What is the intended use case? Since many uses of Ord imply filtering out duplicates, this seems like it could result in getting inconsistent capitalization. Granted, the RFC says it's case-insensitive, but some folks like their aesthetics... (then again, those folks should probably use case-normalizers. I'm mostly just curious if the Ord is intended for Data.Map or what.) -- Live well, ~wren

I wrote:
2. mailHeaders should have an Ord instance that compares case-insensitively, though the underlying Strings should remain Strings.
I really meant Eq instance - which then affects the Ord instance, too. Sorry. wren ng thornton wrote:
What is the intended use case? Since many uses of Ord imply filtering out duplicates, this seems like it could result in getting inconsistent capitalization. Granted, the RFC says it's case-insensitive, but some folks like their aesthetics... (then again, those folks should probably use case-normalizers. I'm mostly just curious if the Ord is intended for Data.Map or what.)
Of course the type will preserve case internally. I envision something like a HeaderName type which is a newtype wrapper for String. If you really want to see the details of case when you are doing something other than rendering, you can always extract the String out of the newtype. But semantically, header names are case insensitive. Here is a use case - I want to search for the "From" field in an email. (Or all of the "From" fields, sometimes there is more than one.) Well, someone may have used non-standard case, but it should still match. Regards, Yitz

On Wed, Oct 20, 2010 at 4:51 PM, Yitzchak Gale
Michael Snoyman wrote:
Great news! This is an important package.
It's obviously very preliminary, though. This is not trivial to get right - look at the long and colorful history of the Python email library, detailed on the first page of the library documentation.
Here are some initial suggestions for improvement:
Thanks for all of these comments, you're bringing up a lot of good points. I'll go point-by-point below.
1. The module name Network.Mail.Mime is too generic. There will also be a parser someday. We should have Types, Parse, and Render in separate modules. I expect each of those to grow gradually as more features are added.
If it's all going to live in the same package, I would imagine we'd still want a single module that exports everything anyway. We can worry more about this when we actually have the extra code, but for now I think it would just add another module to maintain, plus an extra few characters people type.
On the other hand, I think I like the decision to re-implement just the features of RFC 2822 message format needed for everyday MIME use rather than building this on top of a more generic message type, as is done in Python. It simplifies things.
But are multi-line headers supported properly? That's trickier than it looks, there have historically been many wrong implementations out there. That itself could be a reason to build this on top of a proper RFC 2822 implementation.
No, multi-line headers are *not* supported. For that matter, I don't believe non-ASCII characters in headers are handled properly either. These would all be welcome patches ;).
2. mailHeaders should have an Ord instance that compares case-insensitively, though the underlying Strings should remain Strings.
The main purpose of this package is simply rendering the messages, not inspecting messages about to be rendered. As such, I'd like to optimize for that case: adding a newtype wrapper here will simply require more typing for users. Someone who wants to do a lookup can always apply a newtype wrapper themselves. By the way, this is the opposite answer I gave regarding the WAI, where inspecting headers is very important. If this is something to be reopened in the future, we should consider the solution used over there (suggested by Gregory Collins), which stores both a regular and lower-cased version of the header.
3. It should be possible to control whether text parts get quoted-printable encoded. Perhaps add QuotedPrintable to Encoding?
Agree, I just didn't have time or need to implement it.
4. I don't like having those sendmail things here in the same module and package. It's convenient, but messy in several ways - creates a spurious dependency on process, only works on certain platforms and even then with possible weird platform dependencies, etc. I think this should be in a separate package. Once there is a nice easy-to-use SMTP companion package, I don't think the sendmail things will be used that much anyway. Put them in a separate package, but mention it in prominent places so people will find it.
I'm not sure that having a process dependency is a problem for anyone. Isn't it included with GHC? Having it there can be *incredibly* useful for development systems, where you may not have a full SMTP server but want to use something like ssmtp, or even a simple shell script that spits the data into a text file (which is what I do). Actually, on this topic, it may be convenient to provide such a "sendmailDebug" function...
5. Is the blaze-builder dependency necessary now that Bryan has built those techniques into Data.Text?
Yes. The rendered mail body isn't text, it's binary. While it's true that actual binary data (like image attachments) should be base64 encoded, there's still the case of the message, which could be encoded any way the user wishes.
6. Are I18N text-encoded headers supported? That's very important, even for simple everyday usage. It's a bit complicated, though. That might be another reason to build on top of a full RFC 2822 implementation.
Agree, just like multi-line headers. But I'm not sure quite how complicated it really is; shouldn't it be a single function that checks for special characters (eg, non-ASCII, newlines) and then escapes them?
7. This very simple interface is great for everyday use. Think about how to add the less common options for more general use, without cluttering up the everyday interface - custom parameters for Content-Type and Content-Disposition, specifying the boundary rather than allowing it to be generated automatically, etc. It's important to think about those kinds of things now, before the interface gets set in cement.
I'm ambivalent about specifying the boundary manually; I can't really think of a use case outside of testing where it's useful. Keep in mind that there could possibly be many boundaries needed for a message. One possibility may be to provide two parameters to the render function, along the lines of "seed" and "seed -> (Boundary, seed)". Michael
participants (8)
-
Donn Cave
-
Edward Z. Yang
-
Jeremy Shaw
-
Kevin Jardine
-
Michael Snoyman
-
Robert Wills
-
wren ng thornton
-
Yitzchak Gale