{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DerivingStrategies #-}
module Network.HaskellNet.SMTP.Internal
( SMTPConnection(..)
, Command(..)
, SMTPException(..)
, ReplyCode
, tryCommand
, parseResponse
, sendCommand
, sendMailData
, closeSMTP
, gracefullyCloseSMTP
, quitSMTP
, Address(..)
) where
import Control.Exception
import Control.Monad (unless)
import Data.Char (isDigit)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Typeable
import Network.HaskellNet.Auth
import Network.HaskellNet.BSStream
import Network.Mail.Mime
import Prelude
data SMTPConnection = SMTPC {
SMTPConnection -> BSStream
bsstream :: !BSStream,
SMTPConnection -> [ByteString]
_response :: ![ByteString]
}
data Command
=
HELO T.Text
|
EHLO T.Text
|
MAIL T.Text
|
RCPT T.Text
|
DATA ByteString
|
EXPN T.Text
|
VRFY T.Text
|
HELP T.Text
|
AUTH AuthType UserName Password
|
NOOP
|
RSET
|
QUIT
deriving (ReplyCode -> Command -> ShowS
[Command] -> ShowS
Command -> String
forall a.
(ReplyCode -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Command] -> ShowS
$cshowList :: [Command] -> ShowS
show :: Command -> String
$cshow :: Command -> String
showsPrec :: ReplyCode -> Command -> ShowS
$cshowsPrec :: ReplyCode -> Command -> ShowS
Show, Command -> Command -> Bool
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 SMTPException
=
UnexpectedReply Command [ReplyCode] ReplyCode BS.ByteString
| NotConfirmed ReplyCode BS.ByteString
| AuthNegotiationFailed ReplyCode BS.ByteString
| NoRecipients Mail
| UnexpectedGreeting ReplyCode
deriving (ReplyCode -> SMTPException -> ShowS
[SMTPException] -> ShowS
SMTPException -> String
forall a.
(ReplyCode -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SMTPException] -> ShowS
$cshowList :: [SMTPException] -> ShowS
show :: SMTPException -> String
$cshow :: SMTPException -> String
showsPrec :: ReplyCode -> SMTPException -> ShowS
$cshowsPrec :: ReplyCode -> SMTPException -> ShowS
Show)
deriving (Typeable)
instance Exception SMTPException where
displayException :: SMTPException -> String
displayException (UnexpectedReply Command
cmd [ReplyCode]
expected ReplyCode
code ByteString
msg) =
String
"Cannot execute command " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Command
cmd forall a. [a] -> [a] -> [a]
++
String
", " forall a. [a] -> [a] -> [a]
++ [ReplyCode] -> String
prettyExpected [ReplyCode]
expected forall a. [a] -> [a] -> [a]
++
String
", " forall a. [a] -> [a] -> [a]
++ ReplyCode -> ByteString -> String
prettyReceived ReplyCode
code ByteString
msg
where
prettyReceived :: Int -> ByteString -> String
prettyReceived :: ReplyCode -> ByteString -> String
prettyReceived ReplyCode
co ByteString
ms = String
"but received" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show ReplyCode
co forall a. [a] -> [a] -> [a]
++ String
" (" forall a. [a] -> [a] -> [a]
++ ByteString -> String
BS.unpack ByteString
ms forall a. [a] -> [a] -> [a]
++ String
")"
prettyExpected :: [ReplyCode] -> String
prettyExpected :: [ReplyCode] -> String
prettyExpected [ReplyCode
x] = String
"expected reply code of " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show ReplyCode
x
prettyExpected [ReplyCode]
xs = String
"expected any reply code of " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show [ReplyCode]
xs
displayException (NotConfirmed ReplyCode
code ByteString
msg) =
String
"This server cannot accept any data. code: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show ReplyCode
code forall a. [a] -> [a] -> [a]
++ String
", msg: " forall a. [a] -> [a] -> [a]
++ ByteString -> String
BS.unpack ByteString
msg
displayException (AuthNegotiationFailed ReplyCode
code ByteString
msg) =
String
"Authentication failed. code: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show ReplyCode
code forall a. [a] -> [a] -> [a]
++ String
", msg: " forall a. [a] -> [a] -> [a]
++ ByteString -> String
BS.unpack ByteString
msg
displayException (NoRecipients Mail
_mail) =
String
"No recipients were specified"
displayException (UnexpectedGreeting ReplyCode
code) =
String
"Expected greeting from the server, but got: " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show ReplyCode
code
tryCommand
:: SMTPConnection
-> Command
-> Int
-> [ReplyCode]
-> IO ByteString
tryCommand :: SMTPConnection
-> Command -> ReplyCode -> [ReplyCode] -> IO ByteString
tryCommand SMTPConnection
conn Command
cmd ReplyCode
tries [ReplyCode]
expectedReplies = do
(ReplyCode
code, ByteString
msg) <- SMTPConnection -> Command -> IO (ReplyCode, ByteString)
sendCommand SMTPConnection
conn Command
cmd
case () of
()
_ | ReplyCode
code forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ReplyCode]
expectedReplies -> forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
msg
()
_ | ReplyCode
tries forall a. Ord a => a -> a -> Bool
> ReplyCode
1 ->
SMTPConnection
-> Command -> ReplyCode -> [ReplyCode] -> IO ByteString
tryCommand SMTPConnection
conn Command
cmd (ReplyCode
tries forall a. Num a => a -> a -> a
- ReplyCode
1) [ReplyCode]
expectedReplies
| Bool
otherwise ->
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Command -> [ReplyCode] -> ReplyCode -> ByteString -> SMTPException
UnexpectedReply Command
cmd [ReplyCode]
expectedReplies ReplyCode
code ByteString
msg
parseResponse :: BSStream -> IO (ReplyCode, ByteString)
parseResponse :: BSStream -> IO (ReplyCode, ByteString)
parseResponse BSStream
st =
do (ByteString
code, [ByteString]
bdy) <- IO (ByteString, [ByteString])
readLines
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Read a => String -> a
read 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 forall a. Eq a => a -> a -> Bool
== Char
'-'
then do (ByteString
c2, [ByteString]
ls) <- IO (ByteString, [ByteString])
readLines
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
c2, HasCallStack => ByteString -> ByteString
BS.tail ByteString
bdyforall a. a -> [a] -> [a]
:[ByteString]
ls)
else forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
c, [HasCallStack => ByteString -> ByteString
BS.tail ByteString
bdy])
sendCommand
:: SMTPConnection
-> Command
-> IO (ReplyCode, ByteString)
sendCommand :: SMTPConnection -> Command -> IO (ReplyCode, ByteString)
sendCommand (SMTPC BSStream
conn [ByteString]
_) (DATA ByteString
dat) =
do BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn ByteString
"DATA"
(ReplyCode
code, ByteString
msg) <- BSStream -> IO (ReplyCode, ByteString)
parseResponse BSStream
conn
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ReplyCode
code forall a. Eq a => a -> a -> Bool
== ReplyCode
354) forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ ReplyCode -> ByteString -> SMTPException
NotConfirmed ReplyCode
code ByteString
msg
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (ByteString -> IO ()
sendLine forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
stripCR) forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString]
BS.lines ByteString
dat forall a. [a] -> [a] -> [a]
++ [String -> ByteString
BS.pack String
"."]
BSStream -> IO (ReplyCode, 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
(ReplyCode
_, ByteString
_) <- BSStream -> IO (ReplyCode, ByteString)
parseResponse BSStream
conn
BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn forall a b. (a -> b) -> a -> b
$ String -> ByteString
BS.pack String
userB64
(ReplyCode
_, ByteString
_) <- BSStream -> IO (ReplyCode, ByteString)
parseResponse BSStream
conn
BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn forall a b. (a -> b) -> a -> b
$ String -> ByteString
BS.pack String
passB64
BSStream -> IO (ReplyCode, ByteString)
parseResponse BSStream
conn
where command :: ByteString
command = ByteString
"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 forall a b. (a -> b) -> a -> b
$ Text -> ByteString
T.encodeUtf8 Text
command
(ReplyCode
code, ByteString
msg) <- BSStream -> IO (ReplyCode, ByteString)
parseResponse BSStream
conn
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ReplyCode
code forall a. Eq a => a -> a -> Bool
== ReplyCode
334) forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ ReplyCode -> ByteString -> SMTPException
AuthNegotiationFailed ReplyCode
code ByteString
msg
BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn forall a b. (a -> b) -> a -> b
$ String -> ByteString
BS.pack 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 (ReplyCode, ByteString)
parseResponse BSStream
conn
where command :: Text
command = [Text] -> Text
T.unwords [Text
"AUTH", String -> Text
T.pack (forall a. Show a => a -> String
show AuthType
at)]
sendCommand (SMTPC BSStream
conn [ByteString]
_) Command
meth =
do BSStream -> ByteString -> IO ()
bsPutCrLf BSStream
conn forall a b. (a -> b) -> a -> b
$! Text -> ByteString
T.encodeUtf8 Text
command
BSStream -> IO (ReplyCode, ByteString)
parseResponse BSStream
conn
where command :: Text
command = case Command
meth of
(HELO Text
param) -> Text
"HELO " forall a. Semigroup a => a -> a -> a
<> Text
param
(EHLO Text
param) -> Text
"EHLO " forall a. Semigroup a => a -> a -> a
<> Text
param
(MAIL Text
param) -> Text
"MAIL FROM:<" forall a. Semigroup a => a -> a -> a
<> Text
param forall a. Semigroup a => a -> a -> a
<> Text
">"
(RCPT Text
param) -> Text
"RCPT TO:<" forall a. Semigroup a => a -> a -> a
<> Text
param forall a. Semigroup a => a -> a -> a
<> Text
">"
(EXPN Text
param) -> Text
"EXPN " forall a. Semigroup a => a -> a -> a
<> Text
param
(VRFY Text
param) -> Text
"VRFY " forall a. Semigroup a => a -> a -> a
<> Text
param
(HELP Text
msg) -> if Text -> Bool
T.null Text
msg
then Text
"HELP\r\n"
else Text
"HELP " forall a. Semigroup a => a -> a -> a
<> Text
msg
Command
NOOP -> Text
"NOOP"
Command
RSET -> Text
"RSET"
Command
QUIT -> Text
"QUIT"
(DATA ByteString
_) ->
forall a. HasCallStack => String -> a
error String
"BUG: DATA pattern should be matched by sendCommand patterns"
(AUTH {}) ->
forall a. HasCallStack => String -> a
error String
"BUG: AUTH pattern should be matched by sendCommand patterns"
quitSMTP :: SMTPConnection -> IO ()
quitSMTP :: SMTPConnection -> IO ()
quitSMTP SMTPConnection
c = do
ByteString
_ <- SMTPConnection
-> Command -> ReplyCode -> [ReplyCode] -> IO ByteString
tryCommand SMTPConnection
c Command
QUIT ReplyCode
1 [ReplyCode
221]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
closeSMTP :: SMTPConnection -> IO ()
closeSMTP :: SMTPConnection -> IO ()
closeSMTP (SMTPC BSStream
conn [ByteString]
_) = BSStream -> IO ()
bsClose BSStream
conn
gracefullyCloseSMTP :: SMTPConnection -> IO ()
gracefullyCloseSMTP :: SMTPConnection -> IO ()
gracefullyCloseSMTP c :: SMTPConnection
c@(SMTPC BSStream
conn [ByteString]
_) = SMTPConnection -> IO ()
quitSMTP SMTPConnection
c forall a b. IO a -> IO b -> IO a
`finally` BSStream -> IO ()
bsClose BSStream
conn
sendMailData :: Address
-> [Address]
-> ByteString
-> SMTPConnection
-> IO ()
sendMailData :: Address -> [Address] -> ByteString -> SMTPConnection -> IO ()
sendMailData Address
sender [Address]
receivers ByteString
dat SMTPConnection
conn = do
Command -> IO ByteString
sendAndCheck (Text -> Command
MAIL (Address -> Text
addressEmail Address
sender))
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Command -> IO ByteString
sendAndCheck forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Command
RCPT forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address -> Text
addressEmail) [Address]
receivers
Command -> IO ByteString
sendAndCheck (ByteString -> Command
DATA ByteString
dat)
forall (m :: * -> *) a. Monad m => a -> m a
return ()
where
sendAndCheck :: Command -> IO ByteString
sendAndCheck Command
cmd = SMTPConnection
-> Command -> ReplyCode -> [ReplyCode] -> IO ByteString
tryCommand SMTPConnection
conn Command
cmd ReplyCode
1 [ReplyCode
250, ReplyCode
251]
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 forall a. Semigroup a => a -> a -> a
<> ByteString
crlf)