{-# LANGUAGE ScopedTypeVariables #-}
module Network.HaskellNet.SMTP
(
Command(..)
, Response(..)
, AuthType(..)
, SMTPConnection
, connectSMTPPort
, connectSMTP
, connectStream
, sendCommand
, closeSMTP
, authenticate
, sendMail
, doSMTPPort
, doSMTP
, doSMTPStream
, sendPlainTextMail
, sendMimeMail
, sendMimeMail'
, sendMimeMail2
)
where
import Network.HaskellNet.BSStream
import Data.ByteString (ByteString)
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 Data.Char (isDigit)
import Network.HaskellNet.Auth
import Network.Mail.Mime
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString as S
import qualified Data.Text.Lazy as LT
import qualified Data.Text as T
data SMTPConnection = SMTPC { SMTPConnection -> BSStream
bsstream :: !BSStream, SMTPConnection -> [ByteString]
_response :: ![ByteString] }
data Command = HELO String
| EHLO String
| MAIL String
| RCPT String
| DATA ByteString
| EXPN String
| VRFY String
| HELP String
| AUTH AuthType UserName Password
| NOOP
| RSET
| QUIT
deriving (Int -> Command -> ShowS
[Command] -> ShowS
Command -> String
(Int -> Command -> ShowS)
-> (Command -> String) -> ([Command] -> ShowS) -> Show Command
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Command] -> ShowS
$cshowList :: [Command] -> ShowS
show :: Command -> String
$cshow :: Command -> String
showsPrec :: Int -> Command -> ShowS
$cshowsPrec :: Int -> Command -> ShowS
Show, Command -> Command -> Bool
(Command -> Command -> Bool)
-> (Command -> Command -> Bool) -> Eq Command
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Command -> Command -> Bool
$c/= :: Command -> Command -> Bool
== :: Command -> Command -> Bool
$c== :: Command -> Command -> Bool
Eq)
type ReplyCode = Int
data Response = Ok
| SystemStatus
| HelpMessage
| ServiceReady
| ServiceClosing
| UserNotLocal
| CannotVerify
| StartMailInput
| ServiceNotAvailable
| MailboxUnavailable
| ErrorInProcessing
| InsufficientSystemStorage
| SyntaxError
| ParameterError
| CommandNotImplemented
| BadSequence
| ParameterNotImplemented
| MailboxUnavailableError
| UserNotLocalError
| ExceededStorage
| MailboxNotAllowed
| TransactionFailed
deriving (Int -> Response -> ShowS
[Response] -> ShowS
Response -> String
(Int -> Response -> ShowS)
-> (Response -> String) -> ([Response] -> ShowS) -> Show Response
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Response] -> ShowS
$cshowList :: [Response] -> ShowS
show :: Response -> String
$cshow :: Response -> String
showsPrec :: Int -> Response -> ShowS
$cshowsPrec :: Int -> Response -> ShowS
Show, Response -> Response -> Bool
(Response -> Response -> Bool)
-> (Response -> Response -> Bool) -> Eq Response
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Response -> Response -> Bool
$c/= :: Response -> Response -> Bool
== :: Response -> Response -> Bool
$c== :: Response -> Response -> Bool
Eq)
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
>>= 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
tryCommand :: SMTPConnection -> Command -> Int -> [ReplyCode]
-> IO ByteString
tryCommand :: SMTPConnection -> Command -> Int -> [Int] -> IO ByteString
tryCommand SMTPConnection
conn Command
cmd Int
tries [Int]
expectedReplies = do
(Int
code, ByteString
msg) <- SMTPConnection -> Command -> IO (Int, ByteString)
sendCommand SMTPConnection
conn Command
cmd
case () of
()
_ | Int
code Int -> [Int] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int]
expectedReplies -> ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
msg
()
_ | Int
tries Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 ->
SMTPConnection -> Command -> Int -> [Int] -> IO ByteString
tryCommand SMTPConnection
conn Command
cmd (Int
tries Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [Int]
expectedReplies
| Bool
otherwise -> do
BSStream -> IO ()
bsClose (SMTPConnection -> BSStream
bsstream SMTPConnection
conn)
String -> IO ByteString
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO ByteString) -> String -> IO ByteString
forall a b. (a -> b) -> a -> b
$ String
"cannot execute command " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Command -> String
forall a. Show a => a -> String
show Command
cmd String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
", " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Int] -> String
prettyExpected [Int]
expectedReplies String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
", " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> ByteString -> String
prettyReceived Int
code ByteString
msg
where
prettyReceived :: Int -> ByteString -> String
prettyReceived :: Int -> ByteString -> String
prettyReceived Int
co ByteString
ms = String
"but received" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
co String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
BS.unpack ByteString
ms String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
prettyExpected :: [ReplyCode] -> String
prettyExpected :: [Int] -> String
prettyExpected [Int
x] = String
"expected reply code of " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
x
prettyExpected [Int]
xs = String
"expected any reply code of " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Int] -> String
forall a. Show a => a -> String
show [Int]
xs
connectStream :: BSStream -> IO SMTPConnection
connectStream :: BSStream -> IO SMTPConnection
connectStream BSStream
st =
do (Int
code1, ByteString
_) <- BSStream -> IO (Int, ByteString)
parseResponse BSStream
st
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Int
code1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
220) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
do BSStream -> IO ()
bsClose BSStream
st
String -> IO ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"cannot connect to the server"
String
senderHost <- IO String
getHostName
ByteString
msg <- SMTPConnection -> Command -> Int -> [Int] -> IO ByteString
tryCommand (BSStream -> [ByteString] -> SMTPConnection
SMTPC BSStream
st []) (String -> Command
EHLO String
senderHost) Int
3 [Int
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))
parseResponse :: BSStream -> IO (ReplyCode, ByteString)
parseResponse :: BSStream -> IO (Int, ByteString)
parseResponse BSStream
st =
do (ByteString
code, [ByteString]
bdy) <- IO (ByteString, [ByteString])
readLines
(Int, ByteString) -> IO (Int, ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Int
forall a. Read a => String -> a
read (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ ByteString -> String
BS.unpack ByteString
code, [ByteString] -> ByteString
BS.unlines [ByteString]
bdy)
where readLines :: IO (ByteString, [ByteString])
readLines =
do ByteString
l <- BSStream -> IO ByteString
bsGetLine BSStream
st
let (ByteString
c, ByteString
bdy) = (Char -> Bool) -> ByteString -> (ByteString, ByteString)
BS.span Char -> Bool
isDigit ByteString
l
if Bool -> Bool
not (ByteString -> Bool
BS.null ByteString
bdy) Bool -> Bool -> Bool
&& ByteString -> Char
BS.head ByteString
bdy Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-'
then do (ByteString
c2, [ByteString]
ls) <- IO (ByteString, [ByteString])
readLines
(ByteString, [ByteString]) -> IO (ByteString, [ByteString])
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
c2, ByteString -> ByteString
BS.tail ByteString
bdyByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[ByteString]
ls)
else (ByteString, [ByteString]) -> IO (ByteString, [ByteString])
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
c, [ByteString -> ByteString
BS.tail ByteString
bdy])
sendCommand :: SMTPConnection -> Command -> IO (ReplyCode, ByteString)
sendCommand :: SMTPConnection -> Command -> IO (Int, ByteString)
sendCommand (SMTPC BSStream
conn [ByteString]
_) (DATA ByteString
dat) =
do BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString
BS.pack String
"DATA"
(Int
code, ByteString
msg) <- BSStream -> IO (Int, ByteString)
parseResponse BSStream
conn
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Int
code Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
354) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"this server cannot accept any data. code: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
code String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", msg: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
BS.unpack ByteString
msg
(ByteString -> IO ()) -> [ByteString] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (ByteString -> IO ()
sendLine (ByteString -> IO ())
-> (ByteString -> ByteString) -> ByteString -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
stripCR) ([ByteString] -> IO ()) -> [ByteString] -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
BS.lines ByteString
dat [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [String -> ByteString
BS.pack String
"."]
BSStream -> IO (Int, ByteString)
parseResponse BSStream
conn
where sendLine :: ByteString -> IO ()
sendLine = BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn
stripCR :: ByteString -> ByteString
stripCR ByteString
bs = case ByteString -> Maybe (ByteString, Char)
BS.unsnoc ByteString
bs of
Just (ByteString
line, Char
'\r') -> ByteString
line
Maybe (ByteString, Char)
_ -> ByteString
bs
sendCommand (SMTPC BSStream
conn [ByteString]
_) (AUTH AuthType
LOGIN String
username String
password) =
do BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn ByteString
command
(Int
_, ByteString
_) <- BSStream -> IO (Int, ByteString)
parseResponse BSStream
conn
BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString
BS.pack String
userB64
(Int
_, ByteString
_) <- BSStream -> IO (Int, ByteString)
parseResponse BSStream
conn
BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString
BS.pack String
passB64
BSStream -> IO (Int, ByteString)
parseResponse BSStream
conn
where command :: ByteString
command = String -> ByteString
BS.pack String
"AUTH LOGIN"
(String
userB64, String
passB64) = String -> String -> (String, String)
login String
username String
password
sendCommand (SMTPC BSStream
conn [ByteString]
_) (AUTH AuthType
at String
username String
password) =
do BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn ByteString
command
(Int
code, ByteString
msg) <- BSStream -> IO (Int, ByteString)
parseResponse BSStream
conn
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Int
code Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
334) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"authentication failed. code: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
code String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", msg: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
BS.unpack ByteString
msg
BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString
BS.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ AuthType -> String -> String -> ShowS
auth AuthType
at (ByteString -> String
BS.unpack ByteString
msg) String
username String
password
BSStream -> IO (Int, ByteString)
parseResponse BSStream
conn
where command :: ByteString
command = String -> ByteString
BS.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords [String
"AUTH", AuthType -> String
forall a. Show a => a -> String
show AuthType
at]
sendCommand (SMTPC BSStream
conn [ByteString]
_) Command
meth =
do BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString
BS.pack String
command
BSStream -> IO (Int, ByteString)
parseResponse BSStream
conn
where command :: String
command = case Command
meth of
(HELO String
param) -> String
"HELO " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
param
(EHLO String
param) -> String
"EHLO " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
param
(MAIL String
param) -> String
"MAIL FROM:<" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
param String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
">"
(RCPT String
param) -> String
"RCPT TO:<" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
param String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
">"
(EXPN String
param) -> String
"EXPN " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
param
(VRFY String
param) -> String
"VRFY " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
param
(HELP String
msg) -> if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
msg
then String
"HELP\r\n"
else String
"HELP " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg
Command
NOOP -> String
"NOOP"
Command
RSET -> String
"RSET"
Command
QUIT -> String
"QUIT"
(DATA ByteString
_) ->
ShowS
forall a. HasCallStack => String -> a
error String
"BUG: DATA pattern should be matched by sendCommand patterns"
(AUTH {}) ->
ShowS
forall a. HasCallStack => String -> a
error String
"BUG: AUTH pattern should be matched by sendCommand patterns"
closeSMTP :: SMTPConnection -> IO ()
closeSMTP :: SMTPConnection -> IO ()
closeSMTP (SMTPC BSStream
conn [ByteString]
_) = BSStream -> IO ()
bsClose BSStream
conn
authenticate :: AuthType -> UserName -> Password -> SMTPConnection -> IO Bool
authenticate :: AuthType -> String -> String -> SMTPConnection -> IO Bool
authenticate AuthType
at String
username String
password SMTPConnection
conn = do
(Int
code, ByteString
_) <- SMTPConnection -> Command -> IO (Int, ByteString)
sendCommand SMTPConnection
conn (Command -> IO (Int, ByteString))
-> Command -> IO (Int, 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 (Int
code Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
235)
sendMail :: String
-> [String]
-> ByteString
-> SMTPConnection
-> IO ()
sendMail :: String -> [String] -> ByteString -> SMTPConnection -> IO ()
sendMail String
sender [String]
receivers ByteString
dat SMTPConnection
conn = do
Command -> IO ByteString
sendAndCheck (String -> Command
MAIL String
sender)
(String -> IO ByteString) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Command -> IO ByteString
sendAndCheck (Command -> IO ByteString)
-> (String -> Command) -> String -> IO ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Command
RCPT) [String]
receivers
Command -> IO ByteString
sendAndCheck (ByteString -> Command
DATA ByteString
dat)
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
where
sendAndCheck :: Command -> IO ByteString
sendAndCheck Command
cmd = SMTPConnection -> Command -> Int -> [Int] -> IO ByteString
tryCommand SMTPConnection
conn Command
cmd Int
1 [Int
250, Int
251]
doSMTPPort :: String -> PortNumber -> (SMTPConnection -> IO a) -> IO a
doSMTPPort :: String -> PortNumber -> (SMTPConnection -> IO a) -> IO a
doSMTPPort String
host PortNumber
port =
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) SMTPConnection -> IO ()
closeSMTP
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 = IO SMTPConnection
-> (SMTPConnection -> IO ()) -> (SMTPConnection -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (BSStream -> IO SMTPConnection
connectStream BSStream
s) SMTPConnection -> IO ()
closeSMTP
sendPlainTextMail :: String
-> String
-> String
-> LT.Text
-> SMTPConnection
-> IO ()
sendPlainTextMail :: String -> String -> String -> Text -> SMTPConnection -> IO ()
sendPlainTextMail String
to String
from String
subject Text
body SMTPConnection
con = do
ByteString
renderedMail <- Mail -> IO ByteString
renderMail' Mail
myMail
String -> [String] -> ByteString -> SMTPConnection -> IO ()
sendMail String
from [String
to] (ByteString -> ByteString
lazyToStrict ByteString
renderedMail) SMTPConnection
con
where
myMail :: Mail
myMail = Address -> Address -> Text -> Text -> Mail
simpleMail' (String -> Address
address String
to) (String -> Address
address String
from) (String -> Text
T.pack String
subject) Text
body
address :: String -> Address
address = Maybe Text -> Text -> Address
Address Maybe Text
forall a. Maybe a
Nothing (Text -> Address) -> (String -> Text) -> String -> Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
sendMimeMail :: String
-> String
-> String
-> LT.Text
-> LT.Text
-> [(T.Text, FilePath)]
-> SMTPConnection
-> IO ()
sendMimeMail :: String
-> String
-> String
-> Text
-> Text
-> [(Text, String)]
-> SMTPConnection
-> IO ()
sendMimeMail String
to String
from String
subject Text
plainBody Text
htmlBody [(Text, String)]
attachments SMTPConnection
con = do
Mail
myMail <- Address
-> Address -> Text -> Text -> Text -> [(Text, String)] -> IO Mail
simpleMail (String -> Address
address String
to) (String -> Address
address String
from) (String -> Text
T.pack String
subject)
Text
plainBody Text
htmlBody [(Text, String)]
attachments
ByteString
renderedMail <- Mail -> IO ByteString
renderMail' Mail
myMail
String -> [String] -> ByteString -> SMTPConnection -> IO ()
sendMail String
from [String
to] (ByteString -> ByteString
lazyToStrict ByteString
renderedMail) SMTPConnection
con
where
address :: String -> Address
address = Maybe Text -> Text -> Address
Address Maybe Text
forall a. Maybe a
Nothing (Text -> Address) -> (String -> Text) -> String -> Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
sendMimeMail' :: String
-> String
-> String
-> LT.Text
-> LT.Text
-> [(T.Text, T.Text, B.ByteString)]
-> SMTPConnection
-> IO ()
sendMimeMail' :: String
-> String
-> String
-> Text
-> Text
-> [(Text, Text, ByteString)]
-> SMTPConnection
-> IO ()
sendMimeMail' String
to String
from String
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 (String -> Address
address String
to) (String -> Address
address String
from) (String -> Text
T.pack String
subject)
Text
plainBody Text
htmlBody [(Text, Text, ByteString)]
attachments
Mail -> SMTPConnection -> IO ()
sendMimeMail2 Mail
myMail SMTPConnection
con
where
address :: String -> Address
address = Maybe Text -> Text -> Address
Address Maybe Text
forall a. Maybe a
Nothing (Text -> Address) -> (String -> Text) -> String -> Address
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
sendMimeMail2 :: Mail -> SMTPConnection -> IO ()
sendMimeMail2 :: Mail -> SMTPConnection -> IO ()
sendMimeMail2 Mail
mail SMTPConnection
con = do
let (Address Maybe Text
_ Text
from) = Mail -> Address
mailFrom Mail
mail
recps :: [String]
recps = (Address -> String) -> [Address] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> String
T.unpack (Text -> String) -> (Address -> Text) -> Address -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address -> Text
addressEmail)
([Address] -> [String]) -> [Address] -> [String]
forall a b. (a -> b) -> a -> b
$ (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 ([String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
recps) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"no receiver specified."
ByteString
renderedMail <- Mail -> IO ByteString
renderMail' (Mail -> IO ByteString) -> Mail -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Mail
mail { mailBcc :: [Address]
mailBcc = [] }
String -> [String] -> ByteString -> SMTPConnection -> IO ()
sendMail (Text -> String
T.unpack Text
from) [String]
recps (ByteString -> ByteString
lazyToStrict ByteString
renderedMail) SMTPConnection
con
lazyToStrict :: B.ByteString -> S.ByteString
lazyToStrict :: ByteString -> ByteString
lazyToStrict = ByteString -> ByteString
B.toStrict
crlf :: BS.ByteString
crlf :: ByteString
crlf = String -> ByteString
BS.pack String
"\r\n"
bsPutCrLf :: BSStream -> ByteString -> IO ()
bsPutCrLf :: BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
h ByteString
s = BSStream -> ByteString -> IO ()
bsPut BSStream
h ByteString
s IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BSStream -> ByteString -> IO ()
bsPut BSStream
h ByteString
crlf IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BSStream -> IO ()
bsFlush BSStream
h