module Network.Gitit.Framework (
                               
                                 withUserFromSession
                               , withUserFromHTTPAuth
                               , requireUserThat
                               , requireUser
                               , getLoggedInUser
                               , sessionTime
                               
                               , unlessNoEdit
                               , unlessNoDelete
                               
                               , guardCommand
                               , guardPath
                               , guardIndex
                               , guardBareBase
                               
                               , getPath
                               , getPage
                               , getReferer
                               , getWikiBase
                               , uriPath
                               
                               , isPage
                               , isPageFile
                               , isDiscussPage
                               , isDiscussPageFile
                               , isSourceCode
                               
                               , withMessages
                               , withInput
                               
                               , urlForPage
                               , pathForPage
                               , getMimeTypeForExtension
                               , validate
                               , filestoreFromConfig
                               )
where
import Safe
import Network.Gitit.Server
import Network.Gitit.State
import Network.Gitit.Types
import Data.FileStore
import Data.Char (toLower, isAscii)
import Control.Monad (mzero, liftM, MonadPlus)
import qualified Data.Map as M
import Data.ByteString.UTF8 (toString)
import Data.ByteString.Lazy.UTF8 (fromString)
import Data.Maybe (fromJust)
import Data.List (intercalate, isPrefixOf, isInfixOf, (\\))
import System.FilePath ((<.>), takeExtension)
import Text.Highlighting.Kate
import Text.ParserCombinators.Parsec
import Network.URL (decString, encString)
import Happstack.Crypto.Base64 (decode)
import Network.HTTP (urlEncodeVars)
requireUser :: Handler -> Handler 
requireUser = requireUserThat (const True)
requireUserThat :: (User -> Bool) -> Handler -> Handler
requireUserThat predicate handler = do
  mbUser <- getLoggedInUser
  rq <- askRq
  let url = rqUri rq ++ rqQuery rq
  case mbUser of
       Nothing   -> tempRedirect ("/_login?" ++ urlEncodeVars [("destination", url)]) $ toResponse ()
       Just u    -> if predicate u
                       then handler
                       else error "Not authorized."
withUserFromSession :: Handler -> Handler
withUserFromSession handler = withData $ \(sk :: Maybe SessionKey) -> do
  mbSd <- maybe (return Nothing) getSession sk
  mbUser <- case mbSd of
            Nothing    -> return Nothing
            Just sd    -> do
              addCookie sessionTime (mkCookie "sid" (show $ fromJust sk))  
              getUser $! sessionUser sd
  let user = maybe "" uUsername mbUser
  localRq (setHeader "REMOTE_USER" user) handler
withUserFromHTTPAuth :: Handler -> Handler
withUserFromHTTPAuth handler = do
  req <- askRq
  let user = case (getHeader "authorization" req) of
              Nothing         -> ""
              Just authHeader -> case parse pAuthorizationHeader "" (toString authHeader) of
                                  Left _  -> ""
                                  Right u -> u
  localRq (setHeader "REMOTE_USER" user) handler
getLoggedInUser :: GititServerPart (Maybe User)
getLoggedInUser = do
  req <- askRq
  case maybe "" toString (getHeader "REMOTE_USER" req) of
        "" -> return Nothing
        u  -> do
          mbUser <- getUser u
          case mbUser of
               Just user -> return $ Just user
               Nothing   -> return $ Just User{uUsername = u, uEmail = "", uPassword = undefined}
pAuthorizationHeader :: GenParser Char st String
pAuthorizationHeader = try pBasicHeader <|> pDigestHeader
pDigestHeader :: GenParser Char st String
pDigestHeader = do
  string "Digest username=\""
  result' <- many (noneOf "\"")
  char '"'
  return result'
pBasicHeader :: GenParser Char st String
pBasicHeader = do
  string "Basic "
  result' <- many (noneOf " \t\n")
  return $ takeWhile (/=':') $ decode result'
sessionTime :: Int
sessionTime = 60 * 60     
unlessNoEdit :: Handler
             -> Handler
             -> Handler
unlessNoEdit responder fallback = withData $ \(params :: Params) -> do
  cfg <- getConfig
  page <- getPage
  if page `elem` noEdit cfg
     then withMessages ("Page is locked." : pMessages params) fallback
     else responder
unlessNoDelete :: Handler
               -> Handler
               -> Handler
unlessNoDelete responder fallback = withData $ \(params :: Params) -> do
  cfg <- getConfig
  page <- getPage
  if page `elem` noDelete cfg
     then withMessages ("Page cannot be deleted." : pMessages params) fallback
     else responder
getPath :: ServerMonad m => m String
getPath = liftM (fromJust . decString True . intercalate "/" . rqPaths) askRq
getPage :: GititServerPart String
getPage = do
  conf <- getConfig
  path' <- getPath
  if null path'
     then return (frontPage conf)
     else if isPage path'
             then return path'
             else mzero  
getReferer :: ServerMonad m => m String
getReferer = do
  req <- askRq
  base' <- getWikiBase
  return $ case getHeader "referer" req of
                 Just r  -> case toString r of
                                 ""  -> base'
                                 s   -> s
                 Nothing -> base'
getWikiBase :: ServerMonad m => m String
getWikiBase = do
  path' <- getPath
  uri' <- liftM (fromJust . decString True . rqUri) askRq
  case calculateWikiBase path' uri' of
       Just b    -> return b
       Nothing   -> error $ "Could not getWikiBase: (path, uri) = " ++ show (path',uri')
calculateWikiBase :: String -> String -> Maybe String
calculateWikiBase path' uri' =
  let revpaths = reverse . filter (not . null) $ splitOn '/' path'
      revuris  = reverse . filter (not . null) $ splitOn '/' uri'
  in  if revpaths `isPrefixOf` revuris
         then let revbase = drop (length revpaths) revuris
                  
                  revbase' = case revbase of
                             (x:xs) | startsWithUnderscore x -> xs
                             xs                              -> xs
                  base'    = intercalate "/" $ reverse revbase'
              in  Just $ if null base' then "" else '/' : base'
          else Nothing
startsWithUnderscore :: String -> Bool
startsWithUnderscore ('_':_) = True
startsWithUnderscore _ = False
splitOn :: Eq a => a -> [a] -> [[a]]
splitOn c cs =
  let (next, rest) = break (==c) cs
  in case rest of
         []     -> [next]
         (_:rs) -> next : splitOn c rs 
uriPath :: String -> String
uriPath = unwords . words . drop 1 . takeWhile (/='?')
isPage :: String -> Bool
isPage "" = False
isPage ('_':_) = False
isPage s = all (`notElem` "*?") s && not (".." `isInfixOf` s) && not ("/_" `isInfixOf` s)
isPageFile :: FilePath -> Bool
isPageFile f = takeExtension f == ".page"
isDiscussPage :: String -> Bool
isDiscussPage ('@':xs) = isPage xs
isDiscussPage _ = False
isDiscussPageFile :: FilePath -> Bool
isDiscussPageFile ('@':xs) = isPageFile xs
isDiscussPageFile _ = False
isSourceCode :: String -> Bool
isSourceCode path' =
  let ext   = map toLower $ takeExtension path'
      langs = languagesByExtension ext \\ ["Postscript"]
  in  not . null $ langs
urlForPage :: String -> String
urlForPage page = "/" ++
  encString True (\c -> isAscii c && (c `notElem` "?&")) (map spaceToPlus page)
    where spaceToPlus ' ' = '+'
          spaceToPlus c   = c
pathForPage :: String -> FilePath
pathForPage page = page <.> "page"
getMimeTypeForExtension :: String -> GititServerPart String
getMimeTypeForExtension ext = do
  mimes <- liftM mimeMap getConfig
  return $ case M.lookup (dropWhile (=='.') $ map toLower ext) mimes of
                Nothing -> "application/octet-stream"
                Just t  -> t
validate :: [(Bool, String)]   
         -> [String]           
validate = foldl go []
   where go errs (condition, msg) = if condition then msg:errs else errs
guardCommand :: String -> GititServerPart ()
guardCommand command = withData $ \(com :: Command) ->
  case com of
       Command (Just c) | c == command -> return ()
       _                               -> mzero
guardPath :: (String -> Bool) -> GititServerPart ()
guardPath pred' = guardRq (pred' . rqUri)
guardIndex :: GititServerPart ()
guardIndex = do
  base <- getWikiBase
  uri' <- liftM rqUri askRq
  let localpath = drop (length base) uri'
  if length localpath > 1 && lastNote "guardIndex" uri' == '/'
     then return ()
     else mzero
guardBareBase :: GititServerPart ()
guardBareBase = do
  base' <- getWikiBase
  uri' <- liftM rqUri askRq
  if not (null base') && base' == uri'
     then return ()
     else mzero
withMessages :: ServerMonad m => [String] -> m a -> m a
withMessages = withInput "messages" . show
withInput :: ServerMonad m => String -> String -> m a -> m a
withInput name val handler = do
  req <- askRq
  let inps = filter (\(n,_) -> n /= name) $ rqInputs req
  let newInp = (name, Input { inputValue = fromString val
                            , inputFilename = Nothing
                            , inputContentType = ContentType {
                                    ctType = "text"
                                  , ctSubtype = "plain"
                                  , ctParameters = [] }
                            })
  localRq (\rq -> rq{ rqInputs = newInp : inps }) handler
filestoreFromConfig :: Config -> FileStore
filestoreFromConfig conf =
  case repositoryType conf of
         Git       -> gitFileStore       $ repositoryPath conf
         Darcs     -> darcsFileStore     $ repositoryPath conf
         Mercurial -> mercurialFileStore $ repositoryPath conf