{-# LANGUAGE ScopedTypeVariables #-}
module Network.Gitit.Framework (
withUserFromSession
, withUserFromHTTPAuth
, authenticateUserThat
, authenticate
, getLoggedInUser
, unlessNoEdit
, unlessNoDelete
, guardCommand
, guardPath
, guardIndex
, guardBareBase
, getPath
, getPage
, getReferer
, getWikiBase
, uriPath
, isPage
, isPageFile
, isDiscussPage
, isDiscussPageFile
, isNotDiscussPageFile
, isSourceCode
, withMessages
, 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)
import Control.Monad (mzero, liftM, unless)
import qualified Data.Map as M
import qualified Data.ByteString.UTF8 as UTF8
import qualified Data.ByteString.Lazy.UTF8 as LazyUTF8
import Skylighting (syntaxesByFilename, defaultSyntaxMap)
import Data.Maybe (fromJust, fromMaybe)
import Data.List (intercalate, isPrefixOf, isInfixOf)
import System.FilePath ((<.>), takeExtension, takeFileName)
import Text.ParserCombinators.Parsec
import Network.URL (decString, encString)
import Network.URI (isUnescapedInURI)
import Data.ByteString.Base64 (decodeLenient)
import Network.HTTP (urlEncodeVars)
authenticate :: AuthenticationLevel -> Handler -> Handler
authenticate = authenticateUserThat (const True)
authenticateUserThat :: (User -> Bool) -> AuthenticationLevel -> Handler -> Handler
authenticateUserThat predicate level handler = do
cfg <- getConfig
if level <= requireAuthentication cfg
then 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."
else handler
withUserFromSession :: Handler -> Handler
withUserFromSession handler = withData $ \(sk :: Maybe SessionKey) -> do
mbSd <- maybe (return Nothing) getSession sk
cfg <- getConfig
mbUser <- case mbSd of
Nothing -> return Nothing
Just sd -> do
addCookie (MaxAge $ sessionTimeout cfg) (mkCookie "sid" (show $ fromJust sk))
case sessionUser sd of
Nothing -> return Nothing
Just user -> getUser user
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 "" (UTF8.toString authHeader) of
Left _ -> ""
Right u -> u
localRq (setHeader "REMOTE_USER" user) handler
getLoggedInUser :: GititServerPart (Maybe User)
getLoggedInUser = do
req <- askRq
case maybe "" UTF8.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 (/=':') $ UTF8.toString
$ decodeLenient $ UTF8.fromString result'
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 (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 UTF8.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 -> GititServerPart Bool
isPageFile f = do
cfg <- getConfig
return $ takeExtension f == "." ++ (defaultExtension cfg)
isDiscussPage :: String -> Bool
isDiscussPage ('@':xs) = isPage xs
isDiscussPage _ = False
isDiscussPageFile :: FilePath -> GititServerPart Bool
isDiscussPageFile ('@':xs) = isPageFile xs
isDiscussPageFile _ = return False
isNotDiscussPageFile :: FilePath -> GititServerPart Bool
isNotDiscussPageFile ('@':_) = return False
isNotDiscussPageFile _ = return True
isSourceCode :: String -> Bool
isSourceCode path' =
let langs = syntaxesByFilename defaultSyntaxMap $ takeFileName path'
ext = takeExtension path'
in not (null langs || ext == ".svg" || ext == ".eps")
urlForPage :: String -> String
urlForPage page = '/' : encString False isUnescapedInURI page
pathForPage :: String -> String -> FilePath
pathForPage page ext = page <.> ext
getMimeTypeForExtension :: String -> GititServerPart String
getMimeTypeForExtension ext = do
mimes <- liftM mimeMap getConfig
return $ fromMaybe "application/octet-stream"
(M.lookup (dropWhile (== '.') $ map toLower ext) mimes)
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'
unless (length localpath > 1 && lastNote "guardIndex" uri' == '/')
mzero
guardBareBase :: GititServerPart ()
guardBareBase = do
base' <- getWikiBase
uri' <- liftM rqUri askRq
unless (not (null base') && base' == uri')
mzero
withMessages :: ServerMonad m => [String] -> m a -> m a
withMessages messages handler = do
req <- askRq
let inps = filter (\(n,_) -> n /= "message") $ rqInputsQuery req
let newInp msg = ("message", Input {
inputValue = Right
$ LazyUTF8.fromString msg
, inputFilename = Nothing
, inputContentType = ContentType {
ctType = "text"
, ctSubtype = "plain"
, ctParameters = [] }
})
localRq (\rq -> rq{ rqInputsQuery = map newInp messages ++ inps }) handler
filestoreFromConfig :: Config -> FileStore
filestoreFromConfig conf =
case repositoryType conf of
Git -> gitFileStore $ repositoryPath conf
Darcs -> darcsFileStore $ repositoryPath conf
Mercurial -> mercurialFileStore $ repositoryPath conf