{-# LANGUAGE OverloadedStrings, RecordWildCards, ScopedTypeVariables #-}
module Network.Mail.SMTP
(
sendMail
, sendMail'
, sendMailWithLogin
, sendMailWithLogin'
, sendMailWithSender
, sendMailWithSender'
, sendMailTLS
, sendMailTLS'
, sendMailWithLoginTLS
, sendMailWithLoginTLS'
, sendMailWithSenderTLS
, sendMailWithSenderTLS'
, sendMailSTARTTLS
, sendMailSTARTTLS'
, sendMailWithLoginSTARTTLS
, sendMailWithLoginSTARTTLS'
, sendMailWithSenderSTARTTLS
, sendMailWithSenderSTARTTLS'
, simpleMail
, plainTextPart
, htmlPart
, filePart
, module Network.Mail.SMTP.Types
, SMTPConnection
, sendmail
, sendmailCustom
, renderSendMail
, renderSendMailCustom
, connectSMTP
, connectSMTPS
, connectSMTPSTARTTLS
, connectSMTP'
, connectSMTPS'
, connectSMTPSTARTTLS'
, connectSMTPWithHostName
, connectSMTPWithHostNameAndTlsSettings
, connectSMTPWithHostNameAndTlsSettingsSTARTTLS
, sendCommand
, login
, closeSMTP
, renderAndSend
, renderAndSendFrom
)
where
import Network.Mail.SMTP.Auth
import Network.Mail.SMTP.Types
import System.FilePath (takeFileName)
import Control.Monad (unless)
import Data.Char (isDigit)
import Network.Socket
import Network.BSD (getHostName)
import Network.Mail.Mime hiding (filePart, htmlPart, simpleMail)
import qualified Network.Connection as Conn
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import Data.Text.Encoding
data SMTPConnection = SMTPC !Conn.Connection ![ByteString]
instance Eq SMTPConnection where
(==) (SMTPC a _) (SMTPC b _) = Conn.connectionID a == Conn.connectionID b
connectSMTP :: HostName
-> IO SMTPConnection
connectSMTP hostname = connectSMTP' hostname 25
connectSMTPSTARTTLS :: HostName
-> IO SMTPConnection
connectSMTPSTARTTLS hostname = connectSMTPSTARTTLS' hostname 587
defaultTlsSettings :: Conn.TLSSettings
defaultTlsSettings = Conn.TLSSettingsSimple False False False
connectSMTPS :: HostName
-> IO SMTPConnection
connectSMTPS hostname =
connectSMTPS' hostname 465
connectSMTP' :: HostName
-> PortNumber
-> IO SMTPConnection
connectSMTP' hostname port = connectSMTPWithHostName hostname port getHostName
connectSMTPS' :: HostName
-> PortNumber
-> IO SMTPConnection
connectSMTPS' hostname port = connectSMTPWithHostNameAndTlsSettings hostname port getHostName (Just defaultTlsSettings)
connectSMTPSTARTTLS' :: HostName
-> PortNumber
-> IO SMTPConnection
connectSMTPSTARTTLS' hostname port = connectSMTPWithHostNameAndTlsSettingsSTARTTLS hostname port getHostName defaultTlsSettings
connectSMTPWithHostName :: HostName
-> PortNumber
-> IO String
-> IO SMTPConnection
connectSMTPWithHostName hostname port getMailHostName =
connectSMTPWithHostNameAndTlsSettings hostname port getMailHostName Nothing
connectSMTPWithHostNameAndTlsSettings :: HostName
-> PortNumber
-> IO String
-> Maybe Conn.TLSSettings
-> IO SMTPConnection
connectSMTPWithHostNameAndTlsSettings hostname port getMailHostName tlsSettings = do
context <- Conn.initConnectionContext
Conn.connectTo context connParams >>= connectStream getMailHostName
where
connParams = Conn.ConnectionParams hostname port tlsSettings Nothing
connectSMTPWithHostNameAndTlsSettingsSTARTTLS :: HostName
-> PortNumber
-> IO String
-> Conn.TLSSettings
-> IO SMTPConnection
connectSMTPWithHostNameAndTlsSettingsSTARTTLS hostname port getMailHostName tlsSettings = do
context <- Conn.initConnectionContext
Conn.connectTo context connParams >>= connectStreamSTARTTLS getMailHostName context tlsSettings
where
connParams = Conn.ConnectionParams hostname port Nothing Nothing
tryOnce :: SMTPConnection -> Command -> ReplyCode -> IO ByteString
tryOnce = tryCommand 1
tryCommand :: Int -> SMTPConnection -> Command -> ReplyCode
-> IO ByteString
tryCommand tries st cmd expectedReply = do
(code, msg) <- tryCommandNoFail tries st cmd expectedReply
if code == expectedReply
then return msg
else do
closeSMTP st
fail $ "Unexpected reply to: " ++ show cmd ++
", Expected reply code: " ++ show expectedReply ++
", Got this instead: " ++ show code ++ " " ++ show msg
tryCommandNoFail :: Int -> SMTPConnection -> Command -> ReplyCode
-> IO (ReplyCode, ByteString)
tryCommandNoFail tries st cmd expectedReply = do
(code, msg) <- sendCommand st cmd
if code == expectedReply
then return (code, msg)
else if tries > 1
then tryCommandNoFail (tries - 1) st cmd expectedReply
else return (code, msg)
connectStream :: IO String -> Conn.Connection -> IO SMTPConnection
connectStream getMailHostName st = do
(code1, _) <- parseResponse st
unless (code1 == 220) $ do
Conn.connectionClose st
fail "cannot connect to the server"
senderHost <- getMailHostName
(code, initialMsg) <- tryCommandNoFail 3 (SMTPC st []) (EHLO $ B8.pack senderHost) 250
if code == 250
then return (SMTPC st (tail $ B8.lines initialMsg))
else do
msg <- tryCommand 3 (SMTPC st []) (HELO $ B8.pack senderHost) 250
return (SMTPC st (tail $ B8.lines msg))
connectStreamSTARTTLS :: IO String -> Conn.ConnectionContext -> Conn.TLSSettings -> Conn.Connection -> IO SMTPConnection
connectStreamSTARTTLS getMailHostName context tlsSettings st = do
(code1, _) <- parseResponse st
unless (code1 == 220) $ do
Conn.connectionClose st
fail "cannot connect to the server"
senderHost <- getMailHostName
_ <- tryCommand 3 (SMTPC st []) (EHLO $ B8.pack senderHost) 250
_ <- tryCommand 1 (SMTPC st []) STARTTLS 220
_ <- Conn.connectionSetSecure context st tlsSettings
msg <- tryCommand 1 (SMTPC st []) (EHLO $ B8.pack senderHost) 250
return (SMTPC st (tail $ B8.lines msg))
parseResponse :: Conn.Connection -> IO (ReplyCode, ByteString)
parseResponse conn = do
(code, bdy) <- readLines
return (read $ B8.unpack code, B8.unlines bdy)
where
readLines = do
l <- Conn.connectionGetLine 1000 conn
let (c, bdy) = B8.span isDigit l
if not (B8.null bdy) && B8.head bdy == '-'
then do (c2, ls) <- readLines
return (c2, B8.tail bdy:ls)
else return (c, [B8.tail bdy])
sendCommand :: SMTPConnection -> Command -> IO (ReplyCode, ByteString)
sendCommand (SMTPC conn _) (DATA dat) = do
bsPutCrLf conn "DATA"
(code, _) <- parseResponse conn
unless (code == 354) $ fail "this server cannot accept any data."
mapM_ sendLine $ split dat
sendLine dot
parseResponse conn
where
sendLine = bsPutCrLf conn
split = map (padDot . stripCR) . B8.lines
stripCR s = if cr `B8.isSuffixOf` s then B8.init s else s
padDot s = if dot `B8.isPrefixOf` s then dot <> s else s
cr = B8.pack "\r"
dot = B8.pack "."
sendCommand (SMTPC conn _) (AUTH LOGIN username password) = do
bsPutCrLf conn command
_ <- parseResponse conn
bsPutCrLf conn userB64
_ <- parseResponse conn
bsPutCrLf conn passB64
(code, msg) <- parseResponse conn
unless (code == 235) $ fail "authentication failed."
return (code, msg)
where
command = "AUTH LOGIN"
(userB64, passB64) = encodeLogin username password
sendCommand (SMTPC conn _) (AUTH at username password) = do
bsPutCrLf conn command
(code, msg) <- parseResponse conn
unless (code == 334) $ fail "authentication failed."
bsPutCrLf conn $ auth at (B8.unpack msg) username password
parseResponse conn
where
command = B8.pack $ unwords ["AUTH", show at]
sendCommand (SMTPC conn _) meth = do
bsPutCrLf conn command
parseResponse conn
where
command = case meth of
(HELO param) -> "HELO " <> param
(EHLO param) -> "EHLO " <> param
(MAIL param) -> "MAIL FROM:<" <> param <> ">"
(RCPT param) -> "RCPT TO:<" <> param <> ">"
(EXPN param) -> "EXPN " <> param
(VRFY param) -> "VRFY " <> param
(HELP msg) -> if B8.null msg
then "HELP\r\n"
else "HELP " <> msg
NOOP -> "NOOP"
RSET -> "RSET"
QUIT -> "QUIT"
STARTTLS -> "STARTTLS"
DATA{} ->
error "BUG: DATA pattern should be matched by sendCommand patterns"
AUTH{} ->
error "BUG: AUTH pattern should be matched by sendCommand patterns"
closeSMTP :: SMTPConnection -> IO ()
closeSMTP c@(SMTPC conn _) = sendCommand c QUIT >> Conn.connectionClose conn
sendRenderedMail :: ByteString
-> [ByteString]
-> ByteString
-> SMTPConnection
-> IO ()
sendRenderedMail sender receivers dat conn = do
_ <- tryOnce conn (MAIL sender) 250
mapM_ (\r -> tryOnce conn (RCPT r) 250) receivers
_ <- tryOnce conn (DATA dat) 250
return ()
renderAndSend ::SMTPConnection -> Mail -> IO ()
renderAndSend conn mail@Mail{..} = do
rendered <- lazyToStrict `fmap` renderMail' mail
sendRenderedMail from to rendered conn
where enc = encodeUtf8 . addressEmail
from = enc mailFrom
to = map enc $ mailTo ++ mailCc ++ mailBcc
sendMailOnConnection :: Mail -> SMTPConnection -> IO ()
sendMailOnConnection mail con = do
renderAndSend con mail
closeSMTP con
sendMail :: HostName -> Mail -> IO ()
sendMail host mail = connectSMTP host >>= sendMailOnConnection mail
sendMail' :: HostName -> PortNumber -> Mail -> IO ()
sendMail' host port mail = connectSMTP' host port >>= sendMailOnConnection mail
sendMailWithLogin :: HostName -> UserName -> Password -> Mail -> IO ()
sendMailWithLogin host user pass mail = connectSMTP host >>= sendMailWithLoginIntern user pass mail
sendMailWithLogin' :: HostName -> PortNumber -> UserName -> Password -> Mail -> IO ()
sendMailWithLogin' host port user pass mail = connectSMTP' host port >>= sendMailWithLoginIntern user pass mail
sendMailWithSender :: ByteString -> HostName -> Mail -> IO ()
sendMailWithSender sender host mail = connectSMTP host >>= sendMailWithSenderIntern sender mail
sendMailWithSender' :: ByteString -> HostName -> PortNumber -> Mail -> IO ()
sendMailWithSender' sender host port mail = connectSMTP' host port >>= sendMailWithSenderIntern sender mail
sendMailTLS :: HostName -> Mail -> IO ()
sendMailTLS host mail = connectSMTPS host >>= sendMailOnConnection mail
sendMailTLS' :: HostName -> PortNumber -> Mail -> IO ()
sendMailTLS' host port mail = connectSMTPS' host port >>= sendMailOnConnection mail
sendMailWithLoginTLS :: HostName -> UserName -> Password -> Mail -> IO ()
sendMailWithLoginTLS host user pass mail = connectSMTPS host >>= sendMailWithLoginIntern user pass mail
sendMailWithLoginTLS' :: HostName -> PortNumber -> UserName -> Password -> Mail -> IO ()
sendMailWithLoginTLS' host port user pass mail = connectSMTPS' host port >>= sendMailWithLoginIntern user pass mail
sendMailWithSenderTLS :: ByteString -> HostName -> Mail -> IO ()
sendMailWithSenderTLS sender host mail = connectSMTPS host >>= sendMailWithSenderIntern sender mail
sendMailWithSenderTLS' :: ByteString -> HostName -> PortNumber -> Mail -> IO ()
sendMailWithSenderTLS' sender host port mail = connectSMTPS' host port >>= sendMailWithSenderIntern sender mail
sendMailSTARTTLS :: HostName -> Mail -> IO ()
sendMailSTARTTLS host mail = connectSMTPSTARTTLS host >>= sendMailOnConnection mail
sendMailSTARTTLS' :: HostName -> PortNumber -> Mail -> IO ()
sendMailSTARTTLS' host port mail = connectSMTPSTARTTLS' host port >>= sendMailOnConnection mail
sendMailWithLoginSTARTTLS :: HostName -> UserName -> Password -> Mail -> IO ()
sendMailWithLoginSTARTTLS host user pass mail = connectSMTPSTARTTLS host >>= sendMailWithLoginIntern user pass mail
sendMailWithLoginSTARTTLS' :: HostName -> PortNumber -> UserName -> Password -> Mail -> IO ()
sendMailWithLoginSTARTTLS' host port user pass mail = connectSMTPSTARTTLS' host port >>= sendMailWithLoginIntern user pass mail
sendMailWithSenderSTARTTLS :: ByteString -> HostName -> Mail -> IO ()
sendMailWithSenderSTARTTLS sender host mail = connectSMTPSTARTTLS host >>= sendMailWithSenderIntern sender mail
sendMailWithSenderSTARTTLS' :: ByteString -> HostName -> PortNumber -> Mail -> IO ()
sendMailWithSenderSTARTTLS' sender host port mail = connectSMTPSTARTTLS' host port >>= sendMailWithSenderIntern sender mail
sendMailWithLoginIntern :: UserName -> Password -> Mail -> SMTPConnection -> IO ()
sendMailWithLoginIntern user pass mail con = do
_ <- sendCommand con (AUTH LOGIN user pass)
renderAndSend con mail
closeSMTP con
sendMailWithSenderIntern :: ByteString -> Mail -> SMTPConnection -> IO ()
sendMailWithSenderIntern sender mail con = do
renderAndSendFrom sender con mail
closeSMTP con
renderAndSendFrom :: ByteString -> SMTPConnection -> Mail -> IO ()
renderAndSendFrom sender conn mail@Mail{..} = do
rendered <- BL.toStrict `fmap` renderMail' mail
sendRenderedMail sender to rendered conn
where enc = encodeUtf8 . addressEmail
to = map enc $ mailTo ++ mailCc ++ mailBcc
login :: SMTPConnection -> UserName -> Password -> IO (ReplyCode, ByteString)
login con user pass = sendCommand con (AUTH LOGIN user pass)
simpleMail :: Address
-> [Address]
-> [Address]
-> [Address]
-> T.Text
-> [Part]
-> Mail
simpleMail from to cc bcc subject parts =
Mail { mailFrom = from
, mailTo = to
, mailCc = cc
, mailBcc = bcc
, mailHeaders = [ ("Subject", subject) ]
, mailParts = [parts]
}
plainTextPart :: TL.Text -> Part
plainTextPart body = Part "text/plain; charset=utf-8"
QuotedPrintableText DefaultDisposition [] (PartContent $ TL.encodeUtf8 body)
{-# DEPRECATED plainTextPart "Use plainPart from mime-mail package" #-}
htmlPart :: TL.Text -> Part
htmlPart body = Part "text/html; charset=utf-8"
QuotedPrintableText DefaultDisposition [] (PartContent $ TL.encodeUtf8 body)
{-# DEPRECATED htmlPart "Use htmlPart from mime-mail package" #-}
filePart :: T.Text
-> FilePath
-> IO Part
filePart ct fp = do
content <- BL.readFile fp
return $ Part ct Base64 (AttachmentDisposition $ T.pack (takeFileName fp)) [] (PartContent content)
{-# DEPRECATED filePart "Use filePart from mime-mail package" #-}
lazyToStrict :: BL.ByteString -> B.ByteString
lazyToStrict = B.concat . BL.toChunks
crlf :: B8.ByteString
crlf = B8.pack "\r\n"
bsPutCrLf :: Conn.Connection -> ByteString -> IO ()
bsPutCrLf conn = Conn.connectionPut conn . flip B.append crlf