{- Copyright (C) 2013 John Lenz This program is free software: you can redistribute it and/or modify it under the terms of the GNU Affero General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more details. You should have received a copy of the GNU Affero General Public License along with this program. If not, see . -} module Handler.Compose (getComposeR, postComposeR, getReplyR, getReplyAllR) where import Import import Settings import Network.Mail.Mime import Data.Time import System.Locale import System.Random (randomIO) import System.FilePath (()) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL import qualified Data.Conduit.List as CL import qualified Data.Text as T import qualified Data.Text.Encoding as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Encoding as TL import qualified Data.Text.Lazy.IO as TL import qualified Text.Email.Validate as E import qualified Data.Map as M import qualified Data.CaseInsensitive as CI import Data.Attoparsec.Text import Data.String (fromString) import NotmuchCmd -- | Parse an email address in angle brackets emailInBrackets :: Parser T.Text emailInBrackets = do void $ char '<' y <- takeTill (=='>') "Email address" void (char '>' "Expecting '>'") skipSpace return y -- | Parses an email address, which can either just be a direct email -- address or can be an address in the form "Name " address :: Parser Address address = do x <- T.strip <$> takeTill (\c -> c == '<' || c == ',') y <- Just <$> emailInBrackets <|> return Nothing case y of Just e -> return $ Address (Just x) e Nothing -> return $ Address Nothing x -- | Parse a list of addresses seperated by commas addresses :: Parser [Address] addresses = do as <- sepBy address (char ',') endOfInput "Expecting ',' or '>'" return as -- | A version of parseOnly which includes the context of the failure. parseOnly' :: Parser a -> T.Text -> Either String a parseOnly' p t = checkRes (parse p t) where checkRes result = case result of Fail _ ctx err -> Left $ show ctx ++ " " ++ err Partial f -> checkRes $ f "" Done _ x -> Right $ x parseAddresses :: T.Text -> Either (SomeMessage App) (Maybe [Address]) parseAddresses t = case parseOnly' addresses t of Left err -> Left $ fromString err Right [] -> Right $ Nothing Right addrs -> Just <$> mapM checkAddr addrs where checkAddr a@(Address _ e) | E.isValid (T.unpack e) = Right a checkAddr (Address _ e) | otherwise = Left $ SomeMessage $ MsgInvalidEmail e showAddresses :: [Address] -> T.Text showAddresses as = T.intercalate ", " $ map showA as where showA (Address {addressName = Just name, addressEmail = e}) = T.concat [name, " <", e, ">"] showA (Address {addressName = Nothing, addressEmail = e}) = e addressField :: Field s App [Address] addressField = Field { fieldParse = \x _ -> case x of [] -> return $ Right Nothing ("":_) -> return $ Right Nothing (n:_) -> return $ parseAddresses n , fieldView = \theId name attrs val isReq -> [whamlet| |] , fieldEnctype = UrlEncoded } header :: Parser (B.ByteString, T.Text) header = do k <- takeWhile1 (\c -> not (isEndOfLine c) && c /= ':') void $ char ':' skipSpace v <- takeTill isEndOfLine return (T.encodeUtf8 k, v) headers :: Parser [(B.ByteString, T.Text)] headers = sepBy header endOfLine "Headers" parseHeaders :: T.Text -> Either (SomeMessage App) (Maybe [(B.ByteString,T.Text)]) parseHeaders t = case parseOnly' headers t of Left err -> Left $ fromString err Right [] -> Right $ Nothing Right h -> Right $ Just h showHeaders :: [(B.ByteString, T.Text)] -> T.Text showHeaders hs = T.intercalate "\n" $ map showH hs where showH (x,y) = T.concat [T.decodeUtf8 x, ": ", y] headerField :: Field s App [(B.ByteString,T.Text)] headerField = Field { fieldParse = \x _ -> case x of [] -> return $ Right Nothing ("":_) -> return $ Right Nothing (n:_) -> return $ parseHeaders n , fieldView = \theId name attrs val isReq -> [whamlet|