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@somewhere.com
”)*
* [(“Person recipient“, “recipient@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: : 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.