module Network.Mail.SMTP.SMTP (
SMTP
, smtp
, command
, bytes
, expect
, expectCode
, SMTPContext
, smtpContext
, getSMTPServerHostName
, getSMTPClientHostName
, startTLS
, SMTPError(..)
) where
import Control.Exception
import Control.Monad
import Control.Applicative
import Control.Monad.IO.Class
import Control.Monad.Trans.Class
import Control.Monad.Trans.Except
import Control.Monad.Trans.State
import Network
import Network.BSD
import Network.Mail.SMTP.Types
import Network.Mail.SMTP.ReplyLine
import Network.Mail.SMTP.SMTPRaw
import Network.Mail.SMTP.SMTPParameters
import Network.TLS
import Network.TLS.Extra.Cipher (ciphersuite_all)
import System.X509 (getSystemCertificateStore)
import Data.X509.CertificateStore (CertificateStore)
import Data.ByteString.Char8 (pack)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import Crypto.Random
import System.IO
newtype SMTP a = SMTP {
runSMTP :: ExceptT SMTPError (StateT SMTPContext IO) a
} deriving (Functor, Applicative, Monad, MonadIO)
smtp :: SMTPParameters -> SMTP a -> IO (Either SMTPError a)
smtp smtpParameters smtpValue = do
smtpContext <- makeSMTPContext smtpParameters
case smtpContext of
Left err -> return $ Left err
Right smtpContext -> do
x <- evalStateT (runExceptT (runSMTP smtpValue)) smtpContext
closeSMTPContext smtpContext
return x
makeSMTPContext :: SMTPParameters -> IO (Either SMTPError SMTPContext)
makeSMTPContext smtpParameters = do
clientHostname <- getHostName
result <- liftIO $ try (smtpConnect serverHostname (fromIntegral port))
return $ case result :: Either SomeException (SMTPRaw, Maybe Greeting) of
Left err -> Left ConnectionFailure
Right (smtpRaw, _) -> Right $ SMTPContext smtpRaw serverHostname clientHostname debug
where
serverHostname = smtpHost smtpParameters
port = smtpPort smtpParameters
debug = if smtpVerbose smtpParameters
then putStrLn
else const (return ())
closeSMTPContext :: SMTPContext -> IO ()
closeSMTPContext smtpContext = hClose (smtpHandle (smtpRaw smtpContext))
command :: Command -> SMTP ()
command cmd = SMTP $ do
ctxt <- lift get
liftIO $ (smtpDebug ctxt ("Send command: " ++ show (toByteString cmd)))
result <- liftIO $ try ((smtpSendCommand (smtpRaw ctxt) cmd))
case result :: Either SomeException () of
Left err -> throwE UnknownError
Right () -> return ()
bytes :: B.ByteString -> SMTP ()
bytes bs = SMTP $ do
ctxt <- lift get
liftIO $ (smtpDebug ctxt ("Send bytes: " ++ show bs))
result <- liftIO $ try ((smtpSendRaw (smtpRaw ctxt) (B.append bs crlf)))
case result :: Either SomeException () of
Left err -> throwE UnknownError
Right () -> return ()
where
crlf = pack "\r\n"
expect :: ([ReplyLine] -> Maybe SMTPError) -> SMTP ()
expect ok = SMTP $ do
ctxt <- lift get
let smtpraw = smtpRaw ctxt
reply <- liftIO $ smtpGetReplyLines smtpraw
liftIO $ (smtpDebug ctxt ("Receive response: " ++ show reply))
case reply of
Nothing -> throwE UnexpectedResponse
Just reply -> case ok reply of
Just err -> throwE err
Nothing -> return ()
expectCode :: ReplyCode -> SMTP ()
expectCode code = expect hasCode
where
hasCode [] = Just UnexpectedResponse
hasCode (reply : _) =
if replyCode reply == code
then Nothing
else Just UnexpectedResponse
smtpContext :: SMTP SMTPContext
smtpContext = SMTP $ lift get
startTLS :: SMTP ()
startTLS = do
context <- tlsContext
command STARTTLS
expectCode 220
tlsUpgrade context
ctxt <- smtpContext
command (EHLO (pack $ getSMTPClientHostName ctxt))
expectCode 250
tlsContext :: SMTP Context
tlsContext = SMTP $ do
ctxt <- lift get
tlsContext <- liftIO $ try (makeTLSContext (getSMTPHandle ctxt) (getSMTPServerHostName ctxt))
case tlsContext :: Either SomeException Context of
Left err -> throwE EncryptionError
Right context -> return context
tlsUpgrade :: Context -> SMTP ()
tlsUpgrade context = SMTP $ do
result <- liftIO $ try (handshake context)
case result :: Either SomeException () of
Left err -> throwE EncryptionError
Right () -> do
let push = sendData context . BL.fromStrict
let pull = recvData context
let close = contextClose context
lift $ modify (\ctx ->
ctx { smtpRaw = SMTPRaw push pull close (smtpHandle (smtpRaw ctx)) }
)
makeTLSContext :: Handle -> HostName -> IO Context
makeTLSContext handle hostname = do
rng <- (createEntropyPool >>= return . cprgCreate) :: IO SystemRNG
certStore <- getSystemCertificateStore
let params = tlsClientParams hostname certStore
contextNew handle params rng
tlsClientParams :: HostName -> CertificateStore -> ClientParams
tlsClientParams hostname certStore = dflt {
clientSupported = supported
, clientShared = shared
}
where
dflt = defaultParamsClient hostname ""
shared = (clientShared dflt) { sharedCAStore = certStore }
supported = (clientSupported dflt) { supportedCiphers = ciphersuite_all }
data SMTPError
= UnexpectedResponse
| ConnectionFailure
| EncryptionError
| UnknownError
deriving (Show, Eq)
data SMTPContext = SMTPContext {
smtpRaw :: SMTPRaw
, smtpServerHostName :: HostName
, smtpClientHostName :: HostName
, smtpDebug :: String -> IO ()
}
getSMTPHandle :: SMTPContext -> Handle
getSMTPHandle = smtpHandle . smtpRaw
getSMTPServerHostName :: SMTPContext -> HostName
getSMTPServerHostName = smtpServerHostName
getSMTPClientHostName :: SMTPContext -> HostName
getSMTPClientHostName = smtpClientHostName