{-# LANGUAGE ScopedTypeVariables #-}
module Network.HaskellNet.SMTP
(
SMTPConnection
, doSMTPPort
, doSMTP
, doSMTPStream
, authenticate
, AuthType(..)
, sendMail
, sendPlainTextMail
, sendMimeMail
, sendMimeMail'
, sendMimeMail2
, connectSMTPPort
, connectSMTP
, connectStream
, closeSMTP
, gracefullyCloseSMTP
, SMTPException(..)
) where
import Network.HaskellNet.BSStream
import qualified Data.ByteString.Char8 as BS
import Network.BSD (getHostName)
import Network.Socket
import Network.Compat
import Control.Applicative
import Control.Exception
import Control.Monad (unless, when)
import Network.HaskellNet.Auth
import Network.Mail.Mime
import qualified Data.ByteString.Lazy as B
import qualified Data.Text.Lazy as LT
import qualified Data.Text as T
import GHC.Stack
import Prelude
import Network.HaskellNet.SMTP.Internal
connectSMTPPort :: String
-> PortNumber
-> IO SMTPConnection
connectSMTPPort :: String -> PortNumber -> IO SMTPConnection
connectSMTPPort String
hostname PortNumber
port =
(Handle -> BSStream
handleToStream (Handle -> BSStream) -> IO Handle -> IO BSStream
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> PortNumber -> IO Handle
connectTo String
hostname PortNumber
port)
IO BSStream -> (BSStream -> IO SMTPConnection) -> IO SMTPConnection
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HasCallStack => BSStream -> IO SMTPConnection
BSStream -> IO SMTPConnection
connectStream
connectSMTP :: String
-> IO SMTPConnection
connectSMTP :: String -> IO SMTPConnection
connectSMTP = (String -> PortNumber -> IO SMTPConnection)
-> PortNumber -> String -> IO SMTPConnection
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> PortNumber -> IO SMTPConnection
connectSMTPPort PortNumber
25
connectStream :: HasCallStack => BSStream -> IO SMTPConnection
connectStream :: BSStream -> IO SMTPConnection
connectStream BSStream
st =
do (ReplyCode
code1, ByteString
_) <- BSStream -> IO (ReplyCode, ByteString)
parseResponse BSStream
st
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ReplyCode
code1 ReplyCode -> ReplyCode -> Bool
forall a. Eq a => a -> a -> Bool
== ReplyCode
220) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
BSStream -> IO ()
bsClose BSStream
st
SMTPException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (SMTPException -> IO ()) -> SMTPException -> IO ()
forall a b. (a -> b) -> a -> b
$ ReplyCode -> SMTPException
UnexpectedGreeting ReplyCode
code1
Text
senderHost <- String -> Text
T.pack (String -> Text) -> IO String -> IO Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO String
getHostName
ByteString
msg <- SMTPConnection
-> Command -> ReplyCode -> [ReplyCode] -> IO ByteString
tryCommand (BSStream -> [ByteString] -> SMTPConnection
SMTPC BSStream
st []) (Text -> Command
EHLO Text
senderHost) ReplyCode
3 [ReplyCode
250]
SMTPConnection -> IO SMTPConnection
forall (m :: * -> *) a. Monad m => a -> m a
return (BSStream -> [ByteString] -> SMTPConnection
SMTPC BSStream
st ([ByteString] -> [ByteString]
forall a. [a] -> [a]
tail ([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
BS.lines ByteString
msg))
authenticate :: AuthType -> UserName -> Password -> SMTPConnection -> IO Bool
authenticate :: AuthType -> String -> String -> SMTPConnection -> IO Bool
authenticate AuthType
at String
username String
password SMTPConnection
conn = do
(ReplyCode
code, ByteString
_) <- SMTPConnection -> Command -> IO (ReplyCode, ByteString)
sendCommand SMTPConnection
conn (Command -> IO (ReplyCode, ByteString))
-> Command -> IO (ReplyCode, ByteString)
forall a b. (a -> b) -> a -> b
$ AuthType -> String -> String -> Command
AUTH AuthType
at String
username String
password
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (ReplyCode
code ReplyCode -> ReplyCode -> Bool
forall a. Eq a => a -> a -> Bool
== ReplyCode
235)
doSMTPPort :: String -> PortNumber -> (SMTPConnection -> IO a) -> IO a
doSMTPPort :: String -> PortNumber -> (SMTPConnection -> IO a) -> IO a
doSMTPPort String
host PortNumber
port SMTPConnection -> IO a
f =
IO SMTPConnection
-> (SMTPConnection -> IO ()) -> (SMTPConnection -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (String -> PortNumber -> IO SMTPConnection
connectSMTPPort String
host PortNumber
port)
(\(SMTPC BSStream
conn [ByteString]
_) -> BSStream -> IO ()
bsClose BSStream
conn)
(\SMTPConnection
c -> SMTPConnection -> IO a
f SMTPConnection
c IO a -> (a -> IO a) -> IO a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
x -> SMTPConnection -> IO ()
quitSMTP SMTPConnection
c IO () -> IO a -> IO a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x)
doSMTP :: String -> (SMTPConnection -> IO a) -> IO a
doSMTP :: String -> (SMTPConnection -> IO a) -> IO a
doSMTP String
host = String -> PortNumber -> (SMTPConnection -> IO a) -> IO a
forall a. String -> PortNumber -> (SMTPConnection -> IO a) -> IO a
doSMTPPort String
host PortNumber
25
doSMTPStream :: BSStream -> (SMTPConnection -> IO a) -> IO a
doSMTPStream :: BSStream -> (SMTPConnection -> IO a) -> IO a
doSMTPStream BSStream
s SMTPConnection -> IO a
f =
IO SMTPConnection
-> (SMTPConnection -> IO ()) -> (SMTPConnection -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (HasCallStack => BSStream -> IO SMTPConnection
BSStream -> IO SMTPConnection
connectStream BSStream
s)
(\(SMTPC BSStream
conn [ByteString]
_) -> BSStream -> IO ()
bsClose BSStream
conn)
(\SMTPConnection
c -> SMTPConnection -> IO a
f SMTPConnection
c IO a -> (a -> IO a) -> IO a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
x -> SMTPConnection -> IO ()
quitSMTP SMTPConnection
c IO () -> IO a -> IO a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x)
{-# DEPRECATED sendPlainTextMail "Use 'sendMail (Network.Mail.Mime.simpleMail' to from subject plainBody)' instead" #-}
sendPlainTextMail :: Address
-> Address
-> T.Text
-> LT.Text
-> SMTPConnection
-> IO ()
sendPlainTextMail :: Address -> Address -> Text -> Text -> SMTPConnection -> IO ()
sendPlainTextMail Address
to Address
from Text
subject Text
body SMTPConnection
con =
let mail :: Mail
mail = Address -> Address -> Text -> Text -> Mail
simpleMail' Address
to Address
from Text
subject Text
body
in HasCallStack => Mail -> SMTPConnection -> IO ()
Mail -> SMTPConnection -> IO ()
sendMail Mail
mail SMTPConnection
con
{-# DEPRECATED sendMimeMail "Use 'Network.Mail.Mime.simpleMail to from subject plainBody htmlBody attachments >>= \\mail -> sendMail mail conn' instead" #-}
sendMimeMail :: Address
-> Address
-> T.Text
-> LT.Text
-> LT.Text
-> [(T.Text, FilePath)]
-> SMTPConnection
-> IO ()
sendMimeMail :: Address
-> Address
-> Text
-> Text
-> Text
-> [(Text, String)]
-> SMTPConnection
-> IO ()
sendMimeMail Address
to Address
from Text
subject Text
plainBody Text
htmlBody [(Text, String)]
attachments SMTPConnection
con = do
Mail
myMail <- Address
-> Address -> Text -> Text -> Text -> [(Text, String)] -> IO Mail
simpleMail Address
to Address
from Text
subject Text
plainBody Text
htmlBody [(Text, String)]
attachments
HasCallStack => Mail -> SMTPConnection -> IO ()
Mail -> SMTPConnection -> IO ()
sendMail Mail
myMail SMTPConnection
con
{-# DEPRECATED sendMimeMail' "Use 'sendMail (Network.Mail.Mime.simpleMailInMemory to from subject plainBody htmlBody attachments) conn'" #-}
sendMimeMail' :: Address
-> Address
-> T.Text
-> LT.Text
-> LT.Text
-> [(T.Text, T.Text, B.ByteString)]
-> SMTPConnection
-> IO ()
sendMimeMail' :: Address
-> Address
-> Text
-> Text
-> Text
-> [(Text, Text, ByteString)]
-> SMTPConnection
-> IO ()
sendMimeMail' Address
to Address
from Text
subject Text
plainBody Text
htmlBody [(Text, Text, ByteString)]
attachments SMTPConnection
con = do
let myMail :: Mail
myMail = Address
-> Address
-> Text
-> Text
-> Text
-> [(Text, Text, ByteString)]
-> Mail
simpleMailInMemory Address
to Address
from Text
subject Text
plainBody Text
htmlBody [(Text, Text, ByteString)]
attachments
HasCallStack => Mail -> SMTPConnection -> IO ()
Mail -> SMTPConnection -> IO ()
sendMail Mail
myMail SMTPConnection
con
{-# DEPRECATED sendMimeMail2 "Use sendMail instead" #-}
sendMimeMail2 :: HasCallStack => Mail -> SMTPConnection -> IO ()
sendMimeMail2 :: Mail -> SMTPConnection -> IO ()
sendMimeMail2 = HasCallStack => Mail -> SMTPConnection -> IO ()
Mail -> SMTPConnection -> IO ()
sendMail
sendMail :: HasCallStack => Mail -> SMTPConnection -> IO ()
sendMail :: Mail -> SMTPConnection -> IO ()
sendMail Mail
mail SMTPConnection
conn = do
let recps :: [Address]
recps = Mail -> [Address]
mailTo Mail
mail [Address] -> [Address] -> [Address]
forall a. [a] -> [a] -> [a]
++ Mail -> [Address]
mailCc Mail
mail [Address] -> [Address] -> [Address]
forall a. [a] -> [a] -> [a]
++ Mail -> [Address]
mailBcc Mail
mail
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([Address] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Address]
recps) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ SMTPException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (SMTPException -> IO ()) -> SMTPException -> IO ()
forall a b. (a -> b) -> a -> b
$ Mail -> SMTPException
NoRecipients Mail
mail
ByteString
renderedMail <- Mail -> IO ByteString
renderMail' (Mail -> IO ByteString) -> Mail -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Mail
mail { mailBcc :: [Address]
mailBcc = [] }
Address -> [Address] -> ByteString -> SMTPConnection -> IO ()
sendMailData (Mail -> Address
mailFrom Mail
mail) [Address]
recps (ByteString -> ByteString
B.toStrict ByteString
renderedMail) SMTPConnection
conn