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
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 { bsstream :: !BSStream, _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 (Show, 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 (Show, Eq)
connectSMTPPort :: String     
                -> PortNumber 
                -> IO SMTPConnection
connectSMTPPort hostname port =
    (handleToStream <$> connectTo hostname (PortNumber port))
    >>= connectStream
connectSMTP :: String     
            -> IO SMTPConnection
connectSMTP = flip connectSMTPPort 25
tryCommand :: SMTPConnection -> Command -> Int -> ReplyCode
           -> IO ByteString
tryCommand conn cmd tries expectedReply = do
  (code, msg) <- sendCommand conn cmd
  case () of
    _ | code == expectedReply   -> return msg
    _ | tries > 1               ->
          tryCommand conn cmd (tries  1) expectedReply
      | otherwise               -> do
          bsClose (bsstream conn)
          fail $ "cannot execute command " ++ show cmd ++
                 ", expected reply code " ++ show expectedReply ++
                 ", but received " ++ show code ++ " " ++ BS.unpack msg
connectStream :: BSStream -> IO SMTPConnection
connectStream st =
    do (code1, _) <- parseResponse st
       unless (code1 == 220) $
              do bsClose st
                 fail "cannot connect to the server"
       senderHost <- getHostName
       msg <- tryCommand (SMTPC st []) (EHLO senderHost) 3 250
       return (SMTPC st (tail $ BS.lines msg))
parseResponse :: BSStream -> IO (ReplyCode, ByteString)
parseResponse st =
    do (code, bdy) <- readLines
       return (read $ BS.unpack code, BS.unlines bdy)
    where readLines =
              do l <- bsGetLine st
                 let (c, bdy) = BS.span isDigit l
                 if not (BS.null bdy) && BS.head bdy == '-'
                    then do (c2, ls) <- readLines
                            return (c2, BS.tail bdy:ls)
                    else return (c, [BS.tail bdy])
sendCommand :: SMTPConnection -> Command -> IO (ReplyCode, ByteString)
sendCommand (SMTPC conn _) (DATA dat) =
    do bsPutCrLf conn $ BS.pack "DATA"
       (code, _) <- parseResponse conn
       unless (code == 354) $ fail "this server cannot accept any data."
       mapM_ (sendLine . stripCR) $ BS.lines dat ++ [BS.pack "."]
       parseResponse conn
    where sendLine = bsPutCrLf conn
          stripCR bs = case BS.unsnoc bs of
                         Just (line, '\r') -> line
                         _                 -> bs
sendCommand (SMTPC conn _) (AUTH LOGIN username password) =
    do bsPutCrLf conn command
       (_, _) <- parseResponse conn
       bsPutCrLf conn $ BS.pack userB64
       (_, _) <- parseResponse conn
       bsPutCrLf conn $ BS.pack passB64
       parseResponse conn
    where command = BS.pack "AUTH LOGIN"
          (userB64, passB64) = login 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 $ BS.pack $ auth at (BS.unpack msg) username password
       parseResponse conn
    where command = BS.pack $ unwords ["AUTH", show at]
sendCommand (SMTPC conn _) meth =
    do bsPutCrLf conn $ BS.pack 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 null msg
                                        then "HELP\r\n"
                                        else "HELP " ++ msg
                      NOOP         -> "NOOP"
                      RSET         -> "RSET"
                      QUIT         -> "QUIT"
                      (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 (SMTPC conn _) = bsClose conn
authenticate :: AuthType -> UserName -> Password -> SMTPConnection -> IO Bool
authenticate at username password conn  = do
        (code, _) <- sendCommand conn $ AUTH at username password
        return (code == 235)
sendMail :: String     
         -> [String]   
         -> ByteString 
         -> SMTPConnection
         -> IO ()
sendMail sender receivers dat conn = do
                 sendAndCheck (MAIL sender)
                 mapM_ (sendAndCheck . RCPT) receivers
                 sendAndCheck (DATA dat)
                 return ()
  where
    
    sendAndCheck cmd = tryCommand conn cmd 1 250
doSMTPPort :: String -> PortNumber -> (SMTPConnection -> IO a) -> IO a
doSMTPPort host port =
    bracket (connectSMTPPort host port) closeSMTP
doSMTP :: String -> (SMTPConnection -> IO a) -> IO a
doSMTP host = doSMTPPort host 25
doSMTPStream :: BSStream -> (SMTPConnection -> IO a) -> IO a
doSMTPStream s = bracket (connectStream s) closeSMTP
sendPlainTextMail :: String  
                  -> String  
                  -> String  
                  -> LT.Text 
                  -> SMTPConnection 
                  -> IO ()
sendPlainTextMail to from subject body con = do
    renderedMail <- renderMail' myMail
    sendMail from [to] (lazyToStrict renderedMail) con
    where
        myMail = simpleMail' (address to) (address from) (T.pack subject) body
        address = Address Nothing . T.pack
sendMimeMail :: String               
             -> String               
             -> String               
             -> LT.Text              
             -> LT.Text              
             -> [(T.Text, FilePath)] 
             -> SMTPConnection
             -> IO ()
sendMimeMail to from subject plainBody htmlBody attachments con = do
  myMail <- simpleMail (address to) (address from) (T.pack subject)
            plainBody htmlBody attachments
  renderedMail <- renderMail' myMail
  sendMail from [to] (lazyToStrict renderedMail) con
  where
    address = Address Nothing . T.pack
sendMimeMail' :: String                         
              -> String                         
              -> String                         
              -> LT.Text                        
              -> LT.Text                        
              -> [(T.Text, T.Text, B.ByteString)] 
              -> SMTPConnection
              -> IO ()
sendMimeMail' to from subject plainBody htmlBody attachments con = do
  let myMail = simpleMailInMemory (address to) (address from) (T.pack subject)
                                  plainBody htmlBody attachments
  sendMimeMail2 myMail con
  where
    address = Address Nothing . T.pack
sendMimeMail2 :: Mail -> SMTPConnection -> IO ()
sendMimeMail2 mail con = do
    let (Address _ from) = mailFrom mail
        recps = map (T.unpack . addressEmail)
                     $ (mailTo mail ++ mailCc mail ++ mailBcc mail)
    when (null recps) $ fail "no receiver specified."
    renderedMail <- renderMail' $ mail { mailBcc = [] }
    sendMail (T.unpack from) recps (lazyToStrict renderedMail) con
lazyToStrict :: B.ByteString -> S.ByteString
lazyToStrict = S.concat . B.toChunks
crlf :: BS.ByteString
crlf = BS.pack "\r\n"
bsPutCrLf :: BSStream -> ByteString -> IO ()
bsPutCrLf h s = bsPut h s >> bsPut h crlf >> bsFlush h