[Haskell-cafe] Sending email

David Escobar davidescobar1976 at gmail.com
Mon Apr 18 21:42:51 UTC 2016


Hi everyone,
I'm trying to use the *Network.Mail.SMTP* library to send email:

*{-# LANGUAGE OverloadedStrings #-}*

*module Main where*

*import Control.Exception*

*import qualified Data.Text as T*
*import qualified Data.Text.Lazy as LT*
*import Network.Mail.SMTP*

*main :: IO ()*
*main = do*
*  sendEmail (“Person sender”, “sender at somewhere.com
<sender at somewhere.com>”)*
*            [(“Person recipient“, “recipient at somewhere.com
<recipient at somewhere.com>”)]*
*            "Test email"*
*            "Some message goes here."*


*sendEmail :: (T.Text, T.Text) -> [(T.Text, T.Text)] -> T.Text -> T.Text ->
IO ()*
*sendEmail (fromName, fromEmail) toAddresses subject' body' = do*
*  let toNameAddrs = map (\(toName, toEmail) -> Address (Just toName)
toEmail) toAddresses*
*      msg = simpleMail (Address (Just fromName) fromEmail)*
*                       toNameAddrs*
*                       []*
*                       []*
*                       subject'*
*                       [ plainTextPart $ LT.fromStrict body' ]*
*  result <- try $ sendMailWithLogin' "smtp.gmail.com
<http://smtp.gmail.com>"*
*                                     465 -- SSL port*
*                                     “sender_login”*
*                                     “sender_password”*
*                                     msg :: IO (Either SomeException ())*
*  case result of*
*    Left e -> putStrLn $ "Exception caught: " ++ (displayException e)*
*    Right _ -> putStrLn "Sent email successfully."*


The program compiles, but when I run it, I get:

*Exception caught: <socket: 49>: Data.ByteString.hGetLine: end of file*

I tried using the TLS port of 587, but then I just get an authentication
failure. Am I using the wrong library or is it just the wrong
configuration. Thanks.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160418/e5c5ee9d/attachment.html>


More information about the Haskell-Cafe mailing list