{-# LANGUAGE CPP, OverloadedStrings, RecordWildCards #-}
module Network.Mail.Mime
    ( 
      Boundary (..)
    , Mail (..)
    , emptyMail
    , Address (..)
    , Alternatives
    , Part (..)
    , PartContent (..)
    , Disposition (..)
    , Encoding (..)
    , InlineImage(..)
    , ImageContent(..)
    , Headers
      
    , renderMail
    , renderMail'
      
    , sendmail
    , sendmailCustom
    , sendmailCustomCaptureOutput
    , renderSendMail
    , renderSendMailCustom
      
    , simpleMail
    , simpleMail'
    , simpleMailInMemory
    , simpleMailWithImages
      
    , addPart
    , addAttachment
    , addAttachments
    , addAttachmentBS
    , addAttachmentsBS
    , renderAddress
    , htmlPart
    , plainPart
    , filePart
    , filePartBS
    , randomString
    , quotedPrintable
    , relatedPart
    , addImage
    , mkImageParts
    ) where
import qualified Data.ByteString.Lazy as L
import Blaze.ByteString.Builder.Char.Utf8
import Blaze.ByteString.Builder
import Control.Concurrent (forkIO, putMVar, takeMVar, newEmptyMVar)
import Data.Monoid
import System.Random
import Control.Arrow
import System.Process
import System.IO
import System.Exit
import System.FilePath (takeFileName)
import qualified Data.ByteString.Base64 as Base64
import Control.Monad ((<=<), (>=>), foldM, void)
import Control.Exception (throwIO, ErrorCall (ErrorCall))
import Data.List (intersperse)
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Encoding as LT
import Data.ByteString.Char8 ()
import Data.Bits ((.&.), shiftR)
import Data.Char (isAscii, isControl)
import Data.Word (Word8)
import Data.String (IsString(..))
import qualified Data.ByteString as S
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
randomString :: RandomGen d => Int -> d -> (String, d)
randomString len =
    first (map toChar) . sequence' (replicate len (randomR (0, 61)))
  where
    sequence' [] g = ([], g)
    sequence' (f:fs) g =
        let (f', g') = f g
            (fs', g'') = sequence' fs g'
         in (f' : fs', g'')
    toChar i
        | i < 26 = toEnum $ i + fromEnum 'A'
        | i < 52 = toEnum $ i + fromEnum 'a' - 26
        | otherwise = toEnum $ i + fromEnum '0' - 52
newtype Boundary = Boundary { unBoundary :: Text }
  deriving (Eq, Show)
instance Random Boundary where
    randomR = const random
    random = first (Boundary . T.pack) . randomString 10
data Mail = Mail
    { mailFrom :: Address
    , mailTo   :: [Address]
    , mailCc   :: [Address]
    , mailBcc  :: [Address]
    
    , mailHeaders :: Headers
    
    
    
    
    
    
    , mailParts :: [Alternatives]
    }
  deriving Show
emptyMail :: Address -> Mail
emptyMail from = Mail
    { mailFrom    = from
    , mailTo      = []
    , mailCc      = []
    , mailBcc     = []
    , mailHeaders = []
    , mailParts   = []
    }
data Address = Address
    { addressName  :: Maybe Text
    , addressEmail :: Text
    }
  deriving (Eq, Show)
instance IsString Address where
    fromString = Address Nothing . Data.String.fromString
data Encoding = None | Base64 | QuotedPrintableText | QuotedPrintableBinary
  deriving (Eq, Show)
type Alternatives = [Part]
data Part = Part
    { partType :: Text 
    , partEncoding :: Encoding
    
    
    , partDisposition :: Disposition
    , partHeaders :: Headers
    , partContent :: PartContent
    }
  deriving (Eq, Show)
data PartContent = PartContent L.ByteString | NestedParts [Part]
  deriving (Eq, Show)
data Disposition = AttachmentDisposition Text
                 | InlineDisposition Text
                 | DefaultDisposition
                 deriving (Show, Eq)
type Headers = [(S.ByteString, Text)]
data Pair = Pair (Headers, Builder)
          | CompoundPair (Headers, [Pair])
partToPair :: Part -> Pair
partToPair (Part contentType encoding disposition headers (PartContent content)) =
    Pair (headers', builder)
  where
    headers' =
        ((:) ("Content-Type", contentType))
      $ (case encoding of
            None -> id
            Base64 -> (:) ("Content-Transfer-Encoding", "base64")
            QuotedPrintableText ->
                (:) ("Content-Transfer-Encoding", "quoted-printable")
            QuotedPrintableBinary ->
                (:) ("Content-Transfer-Encoding", "quoted-printable"))
      $ (case disposition of
            AttachmentDisposition fn ->
                (:) ("Content-Disposition", "attachment; filename=" `T.append` fn)
            InlineDisposition cid ->
                (:) ("Content-Disposition", "inline; filename=" `T.append` cid) . (:) ("Content-ID", "<" <> cid <> ">") . (:) ("Content-Location", cid)
            DefaultDisposition -> id
        )
      $ headers
    builder =
        case encoding of
            None -> fromWriteList writeByteString $ L.toChunks content
            Base64 -> base64 content
            QuotedPrintableText -> quotedPrintable True content
            QuotedPrintableBinary -> quotedPrintable False content
partToPair (Part contentType encoding disposition headers (NestedParts parts)) =
    CompoundPair (headers', pairs)
  where
    headers' = ("Content-Type", contentType):headers
    pairs = map partToPair parts
showPairs :: RandomGen g
          => Text 
          -> [Pair]
          -> g
          -> (Pair, g)
showPairs _ [] _ = error "renderParts called with null parts"
showPairs _ [pair] gen = (pair, gen)
showPairs mtype parts gen =
    (Pair (headers, builder), gen')
  where
    (Boundary b, gen') = random gen
    headers =
        [ ("Content-Type", T.concat
            [ "multipart/"
            , mtype
            , "; boundary=\""
            , b
            , "\""
            ])
        ]
    builder = mconcat
        [ mconcat $ intersperse (fromByteString "\n")
                  $ map (showBoundPart $ Boundary b) parts
        , showBoundEnd $ Boundary b
        ]
flattenCompoundPair :: RandomGen g => Pair -> g -> (Pair, g)
flattenCompoundPair pair@(Pair _) gen = (pair, gen)
flattenCompoundPair (CompoundPair (hs, pairs)) gen =
       (Pair (headers, builder), gen')
  where
    (Boundary b, gen') = random gen
    headers =
        [ ("Content-Type", T.concat
            [ "multipart/related" , "; boundary=\"" , b , "\"" ])
        ]
    builder = mconcat
        [ mconcat $ intersperse (fromByteString "\n")
                  $ map (showBoundPart $ Boundary b) pairs
        , showBoundEnd $ Boundary b
        ]
renderMail :: RandomGen g => g -> Mail -> (L.ByteString, g)
renderMail g0 (Mail from to cc bcc headers parts) =
    (toLazyByteString builder, g'')
  where
    addressHeaders = map showAddressHeader [("From", [from]), ("To", to), ("Cc", cc), ("Bcc", bcc)]
    
    
    pairs :: [[Pair]]
    pairs = map (map partToPair) (reverse parts)
    (pairs1, g1) = helper2 g0 $ map (map flattenCompoundPair) pairs
    (pairs', g') = helper g1 $ map (showPairs "alternative") pairs1
    helper :: g -> [g -> (x, g)] -> ([x], g)
    helper g [] = ([], g)
    helper g (x:xs) =
        let (b, g_) = x g
            (bs, g__) = helper g_ xs
         in (b : bs, g__)
    
    helper2 :: g -> [[g -> (x, g)]] -> ([[x]], g)
    helper2 g [] = ([], g)
    helper2 g (x:xs) =
        let (b, g_) = helper g x  
            (bs, g__) = helper2 g_ xs
         in (b : bs, g__)
    (Pair (finalHeaders, finalBuilder), g'') = showPairs "mixed" pairs' g'
    builder = mconcat
        [ mconcat addressHeaders
        , mconcat $ map showHeader headers
        , showHeader ("MIME-Version", "1.0")
        , mconcat $ map showHeader finalHeaders
        , fromByteString "\n"
        , finalBuilder
        ]
renderAddress :: Address -> Text
renderAddress address =
    TE.decodeUtf8 $ toByteString $ showAddress address
sanitizeFieldName :: S.ByteString -> S.ByteString
sanitizeFieldName = S.filter (\w -> w >= 33 && w <= 126 && w /= 58)
showHeader :: (S.ByteString, Text) -> Builder
showHeader (k, v) = mconcat
    [ fromByteString (sanitizeFieldName k)
    , fromByteString ": "
    , encodeIfNeeded (sanitizeHeader v)
    , fromByteString "\n"
    ]
showAddressHeader :: (S.ByteString, [Address]) -> Builder
showAddressHeader (k, as) =
  if null as
  then mempty
  else mconcat
    [ fromByteString k
    , fromByteString ": "
    , mconcat (intersperse (fromByteString ", ") . map showAddress $ as)
    , fromByteString "\n"
    ]
showAddress :: Address -> Builder
showAddress a = mconcat
    [ maybe mempty ((<> fromByteString " ") . encodedWord) (addressName a)
    , fromByteString "<"
    , fromText (sanitizeHeader $ addressEmail a)
    , fromByteString ">"
    ]
sanitizeHeader :: Text -> Text
sanitizeHeader = T.filter (not . isControl)
showBoundPart :: Boundary -> Pair -> Builder
showBoundPart (Boundary b) (Pair (headers, content)) = mconcat
    [ fromByteString "--"
    , fromText b
    , fromByteString "\n"
    , mconcat $ map showHeader headers
    , fromByteString "\n"
    , content
    ]
showBoundEnd :: Boundary -> Builder
showBoundEnd (Boundary b) = mconcat
    [ fromByteString "\n--"
    , fromText b
    , fromByteString "--"
    ]
renderMail' :: Mail -> IO L.ByteString
renderMail' m = do
    g <- getStdGen
    let (lbs, g') = renderMail g m
    setStdGen g'
    return lbs
sendmail :: L.ByteString -> IO ()
sendmail = sendmailCustom sendmailPath ["-t"]
sendmailPath :: String
#ifdef MIME_MAIL_SENDMAIL_PATH
sendmailPath = MIME_MAIL_SENDMAIL_PATH
#else
sendmailPath = "/usr/sbin/sendmail"
#endif
renderSendMail :: Mail -> IO ()
renderSendMail = sendmail <=< renderMail'
sendmailCustom :: FilePath        
                  -> [String]     
                  -> L.ByteString 
                  -> IO ()
sendmailCustom sm opts lbs = void $ sendmailCustomAux False sm opts lbs
sendmailCustomCaptureOutput :: FilePath
                               -> [String]
                               -> L.ByteString
                               -> IO (S.ByteString, S.ByteString)
sendmailCustomCaptureOutput sm opts lbs = sendmailCustomAux True sm opts lbs
sendmailCustomAux :: Bool
                     -> FilePath
                     -> [String]
                     -> L.ByteString
                     -> IO (S.ByteString, S.ByteString)
sendmailCustomAux captureOut sm opts lbs = do
    let baseOpts = (proc sm opts) { std_in = CreatePipe }
        pOpts = if captureOut
                    then baseOpts { std_out = CreatePipe
                                  , std_err = CreatePipe
                                  }
                    else baseOpts
    (Just hin, mHOut, mHErr, phandle) <- createProcess pOpts
    L.hPut hin lbs
    hClose hin
    errMVar <- newEmptyMVar
    outMVar <- newEmptyMVar
    case (mHOut, mHErr) of
        (Nothing, Nothing) -> return ()
        (Just hOut, Just hErr) -> do
            void . forkIO $ S.hGetContents hOut >>= putMVar outMVar
            void . forkIO $ S.hGetContents hErr >>= putMVar errMVar
        _ -> error "error in sendmailCustomAux: missing a handle"
    exitCode <- waitForProcess phandle
    case exitCode of
        ExitSuccess -> if captureOut
            then do
                errOutput <- takeMVar errMVar
                outOutput <- takeMVar outMVar
                return (outOutput, errOutput)
            else return (S.empty, S.empty)
        _ -> throwIO $ ErrorCall ("sendmail exited with error code " ++ show exitCode)
renderSendMailCustom :: FilePath    
                        -> [String] 
                        -> Mail     
                        -> IO ()
renderSendMailCustom sm opts = sendmailCustom sm opts <=< renderMail'
simpleMail :: Address 
           -> Address 
           -> Text 
           -> LT.Text 
           -> LT.Text 
           -> [(Text, FilePath)] 
           -> IO Mail
simpleMail to from subject plainBody htmlBody attachments =
      addAttachments attachments
    . addPart [plainPart plainBody, htmlPart htmlBody]
    $ mailFromToSubject from to subject
simpleMail' :: Address 
            -> Address 
            -> Text 
            -> LT.Text 
            -> Mail
simpleMail' to from subject body = addPart [plainPart body]
                                 $ mailFromToSubject from to subject
simpleMailInMemory :: Address 
           -> Address 
           -> Text 
           -> LT.Text 
           -> LT.Text 
           -> [(Text, Text, L.ByteString)] 
           -> Mail
simpleMailInMemory to from subject plainBody htmlBody attachments =
      addAttachmentsBS attachments
    . addPart [plainPart plainBody, htmlPart htmlBody]
    $ mailFromToSubject from to subject
data InlineImage = InlineImage {
      imageContentType :: Text
    , imageContent :: ImageContent
    , imageCID :: Text
    } deriving Show
data ImageContent = ImageFilePath FilePath | ImageByteString L.ByteString
  deriving Show
simpleMailWithImages :: [Address] 
           -> Address 
           -> Text 
           -> LT.Text 
           -> LT.Text 
           -> [InlineImage]
           -> [(Text, FilePath)] 
           -> IO Mail
simpleMailWithImages to from subject plainBody htmlBody images attachments = do
    inlineImageParts <- mkImageParts images
    addAttachments attachments
      . addPart [ plainPart plainBody
                , relatedPart ((htmlPart htmlBody):inlineImageParts) ]
      $ (emptyMail from) { mailTo = to, mailHeaders = [("Subject", subject)] }
mailFromToSubject :: Address 
                  -> Address 
                  -> Text 
                  -> Mail
mailFromToSubject from to subject =
    (emptyMail from) { mailTo = [to]
                     , mailHeaders = [("Subject", subject)]
                     }
addPart :: Alternatives -> Mail -> Mail
addPart alt mail = mail { mailParts = alt : mailParts mail }
relatedPart :: [Part] -> Part
relatedPart parts =
   Part "multipart/related" None DefaultDisposition [] (NestedParts parts)
plainPart :: LT.Text -> Part
plainPart body = Part cType QuotedPrintableText DefaultDisposition []
    $ PartContent (LT.encodeUtf8 body)
  where cType = "text/plain; charset=utf-8"
htmlPart :: LT.Text -> Part
htmlPart body = Part cType QuotedPrintableText DefaultDisposition []
    $ PartContent (LT.encodeUtf8 body)
  where cType = "text/html; charset=utf-8"
filePart :: Text -> FilePath -> IO Part
filePart ct fn = do
    content <- L.readFile fn
    return $ filePartBS ct (T.pack (takeFileName fn)) content
filePartBS :: Text -> Text -> L.ByteString -> Part
filePartBS ct filename content = Part ct Base64 (AttachmentDisposition filename) [] (PartContent content)
addAttachment :: Text -> FilePath -> Mail -> IO Mail
addAttachment ct fn mail = do
    part <- filePart ct fn
    return $ addPart [part] mail
addAttachments :: [(Text, FilePath)] -> Mail -> IO Mail
addAttachments xs mail = foldM fun mail xs
  where fun m (c, f) = addAttachment c f m
addImage :: InlineImage -> IO Part
addImage InlineImage{..} = do
    content <- case imageContent of
                ImageFilePath fn -> L.readFile fn
                ImageByteString bs -> return bs
    return
      $ Part imageContentType Base64 (InlineDisposition imageCID) [] (PartContent content)
mkImageParts :: [InlineImage] -> IO [Part]
mkImageParts xs =
    mapM addImage xs
addAttachmentBS :: Text 
                -> Text 
                -> L.ByteString 
                -> Mail -> Mail
addAttachmentBS ct fn content mail = addPart [filePartBS ct fn content] mail
addAttachmentsBS :: [(Text, Text, L.ByteString)] -> Mail -> Mail
addAttachmentsBS xs mail = foldl fun mail xs
  where fun m (ct, fn, content) = addAttachmentBS ct fn content m
data QP = QPPlain S.ByteString
        | QPNewline
        | QPTab
        | QPSpace
        | QPEscape S.ByteString
data QPC = QPCCR
         | QPCLF
         | QPCSpace
         | QPCTab
         | QPCPlain
         | QPCEscape
    deriving Eq
toQP :: Bool 
     -> L.ByteString
     -> [QP]
toQP isText =
    go
  where
    go lbs =
        case L.uncons lbs of
            Nothing -> []
            Just (c, rest) ->
                case toQPC c of
                    QPCCR -> go rest
                    QPCLF -> QPNewline : go rest
                    QPCSpace -> QPSpace : go rest
                    QPCTab -> QPTab : go rest
                    QPCPlain ->
                        let (x, y) = L.span ((== QPCPlain) . toQPC) lbs
                         in QPPlain (toStrict x) : go y
                    QPCEscape ->
                        let (x, y) = L.span ((== QPCEscape) . toQPC) lbs
                         in QPEscape (toStrict x) : go y
    toStrict = S.concat . L.toChunks
    toQPC :: Word8 -> QPC
    toQPC 13 | isText = QPCCR
    toQPC 10 | isText = QPCLF
    toQPC 9 = QPCTab
    toQPC 0x20 = QPCSpace
    toQPC 46 = QPCEscape
    toQPC 61 = QPCEscape
    toQPC w
        | 33 <= w && w <= 126 = QPCPlain
        | otherwise = QPCEscape
buildQPs :: [QP] -> Builder
buildQPs =
    go (0 :: Int)
  where
    go _ [] = mempty
    go currLine (qp:qps) =
        case qp of
            QPNewline -> copyByteString "\r\n" `mappend` go 0 qps
            QPTab -> wsHelper (copyByteString "=09") (fromWord8 9)
            QPSpace -> wsHelper (copyByteString "=20") (fromWord8 0x20)
            QPPlain bs ->
                let toTake = 75 - currLine
                    (x, y) = S.splitAt toTake bs
                    rest
                        | S.null y = qps
                        | otherwise = QPPlain y : qps
                 in helper (S.length x) (copyByteString x) (S.null y) rest
            QPEscape bs ->
                let toTake = (75 - currLine) `div` 3
                    (x, y) = S.splitAt toTake bs
                    rest
                        | S.null y = qps
                        | otherwise = QPEscape y : qps
                 in if toTake == 0
                        then copyByteString "=\r\n" `mappend` go 0 (qp:qps)
                        else helper (S.length x * 3) (escape x) (S.null y) rest
      where
        escape =
            S.foldl' add mempty
          where
            add builder w =
                builder `mappend` escaped
              where
                escaped = fromWord8 61 `mappend` hex (w `shiftR` 4)
                                       `mappend` hex (w .&. 15)
        helper added builder noMore rest =
            builder' `mappend` go newLine rest
           where
             (newLine, builder')
                | not noMore || (added + currLine) >= 75 =
                    (0, builder `mappend` copyByteString "=\r\n")
                | otherwise = (added + currLine, builder)
        wsHelper enc raw
            | null qps =
                if currLine <= 73
                    then enc
                    else copyByteString "\r\n=" `mappend` enc
            | otherwise = helper 1 raw (currLine < 76) qps
quotedPrintable :: Bool -> L.ByteString -> Builder
quotedPrintable isText = buildQPs . toQP isText
hex :: Word8 -> Builder
hex x
    | x < 10 = fromWord8 $ x + 48
    | otherwise = fromWord8 $ x + 55
encodeIfNeeded :: Text -> Builder
encodeIfNeeded t =
  if needsEncodedWord t
  then encodedWord t
  else fromText t
needsEncodedWord :: Text -> Bool
needsEncodedWord = not . T.all isAscii
encodedWord :: Text -> Builder
encodedWord t = mconcat
    [ fromByteString "=?utf-8?Q?"
    , S.foldl' go mempty $ TE.encodeUtf8 t
    , fromByteString "?="
    ]
  where
    go front w = front `mappend` go' w
    go' 32 = fromWord8 95 
    go' 95 = go'' 95 
    go' 63 = go'' 63 
    go' 61 = go'' 61 
    
    
    
    go' 34 = go'' 34 
    go' 40 = go'' 40 
    go' 41 = go'' 41 
    go' 44 = go'' 44 
    go' 46 = go'' 46 
    go' 58 = go'' 58 
    go' 59 = go'' 59 
    go' 60 = go'' 60 
    go' 62 = go'' 62 
    go' 64 = go'' 64 
    go' 91 = go'' 91 
    go' 92 = go'' 92 
    go' 93 = go'' 93 
    go' w
        | 33 <= w && w <= 126 = fromWord8 w
        | otherwise = go'' w
    go'' w = fromWord8 61 `mappend` hex (w `shiftR` 4)
                          `mappend` hex (w .&. 15)
base64 :: L.ByteString -> Builder
base64 lbs
    | L.null lbs = mempty
    | otherwise = fromByteString x64 `mappend`
                  fromByteString "\r\n" `mappend`
                  base64 y
  where
    (x', y) = L.splitAt 57 lbs
    x = S.concat $ L.toChunks x'
    x64 = Base64.encode x