gitit-0.12.2.1/data/0000755000000000000000000000000012777115425012165 5ustar0000000000000000gitit-0.12.2.1/data/markupHelp/0000755000000000000000000000000012765540066014275 5ustar0000000000000000gitit-0.12.2.1/data/s5/0000755000000000000000000000000012765540066012514 5ustar0000000000000000gitit-0.12.2.1/data/s5/default/0000755000000000000000000000000012765540066014140 5ustar0000000000000000gitit-0.12.2.1/data/static/0000755000000000000000000000000012765540066013454 5ustar0000000000000000gitit-0.12.2.1/data/static/css/0000755000000000000000000000000012765540066014244 5ustar0000000000000000gitit-0.12.2.1/data/static/img/0000755000000000000000000000000012765540066014230 5ustar0000000000000000gitit-0.12.2.1/data/static/img/icons/0000755000000000000000000000000012765540066015343 5ustar0000000000000000gitit-0.12.2.1/data/static/js/0000755000000000000000000000000012765540066014070 5ustar0000000000000000gitit-0.12.2.1/data/templates/0000755000000000000000000000000012765540066014163 5ustar0000000000000000gitit-0.12.2.1/plugins/0000755000000000000000000000000013050577750012733 5ustar0000000000000000gitit-0.12.2.1/src/0000755000000000000000000000000012765540066012043 5ustar0000000000000000gitit-0.12.2.1/src/Network/0000755000000000000000000000000012765540066013474 5ustar0000000000000000gitit-0.12.2.1/src/Network/Gitit/0000755000000000000000000000000013050602400014527 5ustar0000000000000000gitit-0.12.2.1/src/Network/Gitit/Authentication/0000755000000000000000000000000012765540066017533 5ustar0000000000000000gitit-0.12.2.1/src/Network/Gitit/Compat/0000755000000000000000000000000012765540066015777 5ustar0000000000000000gitit-0.12.2.1/src/Network/Gitit.hs0000644000000000000000000002044512765540066015115 0ustar0000000000000000{- Copyright (C) 2009 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Functions for embedding a gitit wiki into a Happstack application. The following is a minimal standalone wiki program: > import Network.Gitit > import Happstack.Server.SimpleHTTP > > main = do > conf <- getDefaultConfig > createStaticIfMissing conf > createTemplateIfMissing conf > createRepoIfMissing conf > initializeGititState conf > simpleHTTP nullConf{port = 5001} $ wiki conf Here is a more complex example, which serves different wikis under different paths, and uses a custom authentication scheme: > import Network.Gitit > import Control.Monad > import Text.XHtml hiding (dir) > import Happstack.Server.SimpleHTTP > > type WikiSpec = (String, FileStoreType, PageType) > > wikis = [ ("markdownWiki", Git, Markdown) > , ("latexWiki", Darcs, LaTeX) ] > > -- custom authentication > myWithUser :: Handler -> Handler > myWithUser handler = do > -- replace the following with a function that retrieves > -- the logged in user for your happstack app: > user <- return "testuser" > localRq (setHeader "REMOTE_USER" user) handler > > myAuthHandler = msum > [ dir "_login" $ seeOther "/your/login/url" $ toResponse () > , dir "_logout" $ seeOther "/your/logout/url" $ toResponse () ] > > handlerFor :: Config -> WikiSpec -> ServerPart Response > handlerFor conf (path', fstype, pagetype) = dir path' $ > wiki conf{ repositoryPath = path' > , repositoryType = fstype > , defaultPageType = pagetype} > > indexPage :: ServerPart Response > indexPage = ok $ toResponse $ > (p << "Wiki index") +++ > ulist << map (\(path', _, _) -> li << hotlink (path' ++ "/") << path') wikis > > main = do > conf <- getDefaultConfig > let conf' = conf{authHandler = myAuthHandler, withUser = myWithUser} > forM wikis $ \(path', fstype, pagetype) -> do > let conf'' = conf'{ repositoryPath = path' > , repositoryType = fstype > , defaultPageType = pagetype > } > createStaticIfMissing conf'' > createRepoIfMissing conf'' > createTemplateIfMissing conf' > initializeGititState conf' > simpleHTTP nullConf{port = 5001} $ > (nullDir >> indexPage) `mplus` msum (map (handlerFor conf') wikis) -} module Network.Gitit ( -- * Wiki handlers wiki , reloadTemplates , runHandler -- * Initialization , module Network.Gitit.Initialize -- * Configuration , module Network.Gitit.Config , loginUserForm -- * Types , module Network.Gitit.Types -- * Tools for building handlers , module Network.Gitit.Framework , module Network.Gitit.Layout , module Network.Gitit.ContentTransformer , module Network.Gitit.Page , getFileStore , getUser , getConfig , queryGititState , updateGititState ) where import Network.Gitit.Types import Network.Gitit.Server import Network.Gitit.Framework import Network.Gitit.Handlers import Network.Gitit.Initialize import Network.Gitit.Config import Network.Gitit.Layout import Network.Gitit.State (getFileStore, getUser, getConfig, queryGititState, updateGititState) import Network.Gitit.ContentTransformer import Network.Gitit.Page import Network.Gitit.Authentication (loginUserForm) import Paths_gitit (getDataFileName) import Control.Monad.Reader import Prelude hiding (readFile) import qualified Data.ByteString.Char8 as B import System.FilePath (()) import System.Directory (getTemporaryDirectory) import Safe -- | Happstack handler for a gitit wiki. wiki :: Config -> ServerPart Response wiki conf = do tempDir <- liftIO getTemporaryDirectory let maxSize = fromIntegral $ maxUploadSize conf decodeBody $ defaultBodyPolicy tempDir maxSize maxSize maxSize let static = staticDir conf defaultStatic <- liftIO $ getDataFileName $ "data" "static" -- if file not found in staticDir, we check also in the data/static -- directory, which contains defaults let staticHandler = withExpiresHeaders $ serveDirectory' static `mplus` serveDirectory' defaultStatic let debugHandler' = msum [debugHandler | debugMode conf] let handlers = debugHandler' `mplus` authHandler conf `mplus` authenticate ForRead (msum wikiHandlers) let fs = filestoreFromConfig conf let ws = WikiState { wikiConfig = conf, wikiFileStore = fs } if compressResponses conf then compressedResponseFilter else return "" staticHandler `mplus` runHandler ws (withUser conf handlers) -- | Like 'serveDirectory', but if file is not found, fail instead of -- returning a 404 error. serveDirectory' :: FilePath -> ServerPart Response serveDirectory' p = do rq <- askRq resp' <- serveDirectory EnableBrowsing [] p if rsCode resp' == 404 || lastNote "fileServeStrict'" (rqUri rq) == '/' then mzero -- pass through if not found or directory index else -- turn off compresion filter unless it's text case getHeader "Content-Type" resp' of Just ct | B.pack "text/" `B.isPrefixOf` ct -> return resp' _ -> ignoreFilters >> return resp' wikiHandlers :: [Handler] wikiHandlers = [ -- redirect /wiki -> /wiki/ when gitit is being served at /wiki -- so that relative wikilinks on the page will work properly: guardBareBase >> getWikiBase >>= \b -> movedPermanently (b ++ "/") (toResponse ()) , dir "_activity" showActivity , dir "_go" goToPage , method GET >> dir "_search" searchResults , dir "_upload" $ do guard =<< return . uploadsAllowed =<< getConfig msum [ method GET >> authenticate ForModify uploadForm , method POST >> authenticate ForModify uploadFile ] , dir "_random" $ method GET >> randomPage , dir "_index" indexPage , dir "_feed" feedHandler , dir "_category" categoryPage , dir "_categories" categoryListPage , dir "_expire" expireCache , dir "_showraw" $ msum [ showRawPage , guardPath isSourceCode >> showFileAsText ] , dir "_history" $ msum [ showPageHistory , guardPath isSourceCode >> showFileHistory ] , dir "_edit" $ authenticate ForModify (unlessNoEdit editPage showPage) , dir "_diff" $ msum [ showPageDiff , guardPath isSourceCode >> showFileDiff ] , dir "_discuss" discussPage , dir "_delete" $ msum [ method GET >> authenticate ForModify (unlessNoDelete confirmDelete showPage) , method POST >> authenticate ForModify (unlessNoDelete deletePage showPage) ] , dir "_preview" preview , guardIndex >> indexPage , guardCommand "export" >> exportPage , method POST >> guardCommand "cancel" >> showPage , method POST >> guardCommand "update" >> authenticate ForModify (unlessNoEdit updatePage showPage) , showPage , guardPath isSourceCode >> method GET >> showHighlightedSource , handleAny , notFound =<< (guardPath isPage >> createPage) ] -- | Recompiles the gitit templates. reloadTemplates :: ServerPart Response reloadTemplates = do liftIO recompilePageTemplate ok $ toResponse "Page templates have been recompiled." -- | Converts a gitit Handler into a standard happstack ServerPart. runHandler :: WikiState -> Handler -> ServerPart Response runHandler = mapServerPartT . unpackReaderT unpackReaderT :: s -> UnWebT (ReaderT s IO) a -> UnWebT IO a unpackReaderT st uw = runReaderT uw st gitit-0.12.2.1/src/Network/Gitit/ContentTransformer.hs0000644000000000000000000007225213050600344020735 0ustar0000000000000000{-# LANGUAGE CPP #-} {- Copyright (C) 2009 John MacFarlane , Anton van Straaten This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- Functions for content conversion. -} module Network.Gitit.ContentTransformer ( -- * ContentTransformer runners runPageTransformer , runFileTransformer -- * Gitit responders , showRawPage , showFileAsText , showPage , exportPage , showHighlightedSource , showFile , preview , applyPreCommitPlugins -- * Cache support for transformers , cacheHtml , cachedHtml -- * Content retrieval combinators , rawContents -- * Response-generating combinators , textResponse , mimeFileResponse , mimeResponse , exportPandoc , applyWikiTemplate -- * Content-type transformation combinators , pageToWikiPandoc , pageToPandoc , pandocToHtml , highlightSource -- * Content or context augmentation combinators , applyPageTransforms , wikiDivify , addPageTitleToPandoc , addMathSupport , addScripts -- * ContentTransformer context API , getFileName , getPageName , getLayout , getParams , getCacheable -- * Pandoc and wiki content conversion support , inlinesToURL , inlinesToString ) where import qualified Control.Exception as E import Control.Monad.State import Control.Monad.Reader (ask) import Data.Foldable (traverse_) import Data.List (stripPrefix) import Data.Maybe (isNothing, mapMaybe) import Network.Gitit.Cache (lookupCache, cacheContents) import Network.Gitit.Export (exportFormats) import Network.Gitit.Framework hiding (uriPath) import Network.Gitit.Layout import Network.Gitit.Page (stringToPage) import Network.Gitit.Server import Network.Gitit.State import Network.Gitit.Types import Network.HTTP (urlDecode) import Network.URI (isUnescapedInURI) import Network.URL (encString) import System.FilePath import qualified Text.Pandoc.Builder as B import Text.HTML.SanitizeXSS (sanitizeBalance) import Text.Highlighting.Kate import Text.Pandoc hiding (MathML, WebTeX, MathJax) import Text.XHtml hiding ( (), dir, method, password, rev ) import Text.XHtml.Strict (stringToHtmlString) #if MIN_VERSION_blaze_html(0,5,0) import Text.Blaze.Html.Renderer.String as Blaze ( renderHtml ) #else import Text.Blaze.Renderer.String as Blaze ( renderHtml ) #endif import qualified Data.Text as T import qualified Data.Set as Set import qualified Data.ByteString as S (concat) import qualified Data.ByteString.Char8 as SC (unpack) import qualified Data.ByteString.Lazy as L (toChunks, fromChunks) import qualified Data.FileStore as FS import qualified Text.Pandoc as Pandoc import Text.URI (parseURI, URI(..), uriQueryItems) #if MIN_VERSION_pandoc(1,14,0) import Text.Pandoc.Error (handleError) #else handleError :: Pandoc -> Pandoc handleError = id #endif -- -- ContentTransformer runners -- runPageTransformer :: ToMessage a => ContentTransformer a -> GititServerPart a runPageTransformer xform = withData $ \params -> do page <- getPage cfg <- getConfig evalStateT xform Context{ ctxFile = pathForPage page (defaultExtension cfg) , ctxLayout = defaultPageLayout{ pgPageName = page , pgTitle = page , pgPrintable = pPrintable params , pgMessages = pMessages params , pgRevision = pRevision params , pgLinkToFeed = useFeed cfg } , ctxCacheable = True , ctxTOC = tableOfContents cfg , ctxBirdTracks = showLHSBirdTracks cfg , ctxCategories = [] , ctxMeta = [] } runFileTransformer :: ToMessage a => ContentTransformer a -> GititServerPart a runFileTransformer xform = withData $ \params -> do page <- getPage cfg <- getConfig evalStateT xform Context{ ctxFile = id page , ctxLayout = defaultPageLayout{ pgPageName = page , pgTitle = page , pgPrintable = pPrintable params , pgMessages = pMessages params , pgRevision = pRevision params , pgLinkToFeed = useFeed cfg } , ctxCacheable = True , ctxTOC = tableOfContents cfg , ctxBirdTracks = showLHSBirdTracks cfg , ctxCategories = [] , ctxMeta = [] } -- | Converts a @ContentTransformer@ into a @GititServerPart@; -- specialized to wiki pages. -- runPageTransformer :: ToMessage a -- => ContentTransformer a -- -> GititServerPart a -- runPageTransformer = runTransformer pathForPage -- | Converts a @ContentTransformer@ into a @GititServerPart@; -- specialized to non-pages. -- runFileTransformer :: ToMessage a -- => ContentTransformer a -- -> GititServerPart a -- runFileTransformer = runTransformer id -- -- Gitit responders -- -- | Responds with raw page source. showRawPage :: Handler showRawPage = runPageTransformer rawTextResponse -- | Responds with raw source (for non-pages such as source -- code files). showFileAsText :: Handler showFileAsText = runFileTransformer rawTextResponse -- | Responds with rendered wiki page. showPage :: Handler showPage = runPageTransformer htmlViaPandoc -- | Responds with page exported into selected format. exportPage :: Handler exportPage = runPageTransformer exportViaPandoc -- | Responds with highlighted source code. showHighlightedSource :: Handler showHighlightedSource = runFileTransformer highlightRawSource -- | Responds with non-highlighted source code. showFile :: Handler showFile = runFileTransformer (rawContents >>= mimeFileResponse) -- | Responds with rendered page derived from form data. preview :: Handler preview = runPageTransformer $ liftM (filter (/= '\r') . pRaw) getParams >>= contentsToPage >>= pageToWikiPandoc >>= pandocToHtml >>= return . toResponse . renderHtmlFragment -- | Applies pre-commit plugins to raw page source, possibly -- modifying it. applyPreCommitPlugins :: String -> GititServerPart String applyPreCommitPlugins = runPageTransformer . applyPreCommitTransforms -- -- Top level, composed transformers -- -- | Responds with raw source. rawTextResponse :: ContentTransformer Response rawTextResponse = rawContents >>= textResponse -- | Responds with a wiki page in the format specified -- by the @format@ parameter. exportViaPandoc :: ContentTransformer Response exportViaPandoc = rawContents >>= maybe mzero return >>= contentsToPage >>= pageToWikiPandoc >>= exportPandoc -- | Responds with a wiki page. Uses the cache when -- possible and caches the rendered page when appropriate. htmlViaPandoc :: ContentTransformer Response htmlViaPandoc = cachedHtml `mplus` (rawContents >>= maybe mzero return >>= contentsToPage >>= handleRedirects >>= either return (pageToWikiPandoc >=> addMathSupport >=> pandocToHtml >=> wikiDivify >=> applyWikiTemplate >=> cacheHtml)) -- | Responds with highlighted source code in a wiki -- page template. Uses the cache when possible and -- caches the rendered page when appropriate. highlightRawSource :: ContentTransformer Response highlightRawSource = cachedHtml `mplus` (updateLayout (\l -> l { pgTabs = [ViewTab,HistoryTab] }) >> rawContents >>= highlightSource >>= applyWikiTemplate >>= cacheHtml) -- -- Cache support for transformers -- -- | Caches a response (actually just the response body) on disk, -- unless the context indicates that the page is not cacheable. cacheHtml :: Response -> ContentTransformer Response cacheHtml resp' = do params <- getParams file <- getFileName cacheable <- getCacheable cfg <- lift getConfig when (useCache cfg && cacheable && isNothing (pRevision params) && not (pPrintable params)) $ lift $ cacheContents file $ S.concat $ L.toChunks $ rsBody resp' return resp' -- | Returns cached page if available, otherwise mzero. cachedHtml :: ContentTransformer Response cachedHtml = do file <- getFileName params <- getParams cfg <- lift getConfig if useCache cfg && not (pPrintable params) && isNothing (pRevision params) then do mbCached <- lift $ lookupCache file let emptyResponse = setContentType "text/html; charset=utf-8" . toResponse $ () maybe mzero (\(_modtime, contents) -> lift . ok $ emptyResponse{rsBody = L.fromChunks [contents]}) mbCached else mzero -- -- Content retrieval combinators -- -- | Returns raw file contents. rawContents :: ContentTransformer (Maybe String) rawContents = do params <- getParams file <- getFileName fs <- lift getFileStore let rev = pRevision params liftIO $ E.catch (liftM Just $ FS.retrieve fs file rev) (\e -> if e == FS.NotFound then return Nothing else E.throwIO e) -- -- Response-generating combinators -- -- | Converts raw contents to a text/plain response. textResponse :: Maybe String -> ContentTransformer Response textResponse Nothing = mzero -- fail quietly if file not found textResponse (Just c) = mimeResponse c "text/plain; charset=utf-8" -- | Converts raw contents to a response that is appropriate with -- a mime type derived from the page's extension. mimeFileResponse :: Maybe String -> ContentTransformer Response mimeFileResponse Nothing = error "Unable to retrieve file contents." mimeFileResponse (Just c) = mimeResponse c =<< lift . getMimeTypeForExtension . takeExtension =<< getFileName mimeResponse :: Monad m => String -- ^ Raw contents for response body -> String -- ^ Mime type -> m Response mimeResponse c mimeType = return . setContentType mimeType . toResponse $ c -- | Converts Pandoc to response using format specified in parameters. exportPandoc :: Pandoc -> ContentTransformer Response exportPandoc doc = do params <- getParams page <- getPageName cfg <- lift getConfig let format = pFormat params case lookup format (exportFormats cfg) of Nothing -> error $ "Unknown export format: " ++ format Just writer -> lift (writer page doc) -- | Adds the sidebar, page tabs, and other elements of the wiki page -- layout to the raw content. applyWikiTemplate :: Html -> ContentTransformer Response applyWikiTemplate c = do Context { ctxLayout = layout } <- get lift $ formattedPage layout c -- -- Content-type transformation combinators -- -- | Converts Page to Pandoc, applies page transforms, and adds page -- title. pageToWikiPandoc :: Page -> ContentTransformer Pandoc pageToWikiPandoc page' = pageToWikiPandoc' page' >>= addPageTitleToPandoc (pageTitle page') pageToWikiPandoc' :: Page -> ContentTransformer Pandoc pageToWikiPandoc' = applyPreParseTransforms >=> pageToPandoc >=> applyPageTransforms -- | Converts source text to Pandoc using default page type. pageToPandoc :: Page -> ContentTransformer Pandoc pageToPandoc page' = do modifyContext $ \ctx -> ctx{ ctxTOC = pageTOC page' , ctxCategories = pageCategories page' , ctxMeta = pageMeta page' } return $ readerFor (pageFormat page') (pageLHS page') (pageText page') -- | Detects if the page is a redirect page and handles accordingly. The exact -- behaviour is as follows: -- -- If the page is /not/ a redirect page (the most common case), then check the -- referer to see if the client came to this page as a result of a redirect -- from another page. If so, then add a notice to the messages to notify the -- user that they were redirected from another page, and provide a link back -- to the original page, with an extra parameter to disable redirection -- (e.g., to allow the original page to be edited). -- -- If the page /is/ a redirect page, then check the query string for the -- @redirect@ parameter. This can modify the behaviour of the redirect as -- follows: -- -- 1. If the @redirect@ parameter is unset, then check the referer to see if -- client came to this page as a result of a redirect from another page. If -- so, then do not redirect, and add a notice to the messages explaining -- that this page is a redirect page, that would have redirected to the -- destination given in the metadata (and provide a link thereto), but this -- was stopped because a double-redirect was detected. This is a simple way -- to prevent cyclical redirects and other abuses enabled by redirects. -- redirect to the same page. If the client did /not/ come to this page as -- a result of a redirect, then redirect back to the same page, except with -- the redirect parameter set to @\"yes\"@. -- -- 2. If the @redirect@ parameter is set to \"yes\", then redirect to the -- destination specificed in the metadata. This uses a client-side (meta -- refresh + javascript backup) redirect to make sure the referer is set to -- this URL. -- -- 3. If the @redirect@ parameter is set to \"no\", then do not redirect, but -- add a notice to the messages that this page /would/ have redirected to -- the destination given in the metadata had it not been disabled, and -- provide a link to the destination given in the metadata. This behaviour -- is the @revision@ parameter is present in the query string. handleRedirects :: Page -> ContentTransformer (Either Response Page) handleRedirects page = case lookup "redirect" (pageMeta page) of Nothing -> isn'tRedirect Just destination -> isRedirect destination where addMessage message = modifyContext $ \context -> context { ctxLayout = (ctxLayout context) { pgMessages = pgMessages (ctxLayout context) ++ [message] } } redirectedFrom source = do (url, html) <- processSource source return $ concat [ "Redirected from " , html , "" ] doubleRedirect source destination = do (url, html) <- processSource source (url', html') <- processDestination destination return $ concat [ "This page normally redirects to " , html' , ", but as you were already redirected from " , html , "" , ", this was stopped to prevent a double-redirect." ] cancelledRedirect destination = do (url', html') <- processDestination destination return $ concat [ "This page redirects to " , html' , "." ] processSource source = do base' <- getWikiBase let url = stringToHtmlString $ base' ++ urlForPage source let html = stringToHtmlString source return (url, html) processDestination destination = do base' <- getWikiBase let (page', fragment) = break (== '#') destination let url = stringToHtmlString $ concat [ base' , urlForPage page' , fragment ] let html = stringToHtmlString page' return (url, html) getSource = do cfg <- lift getConfig base' <- getWikiBase request <- askRq return $ do uri <- getHeader "referer" request >>= parseURI . SC.unpack let params = uriQueryItems uri redirect' <- lookup "redirect" params guard $ redirect' == "yes" path' <- stripPrefix (base' ++ "/") (uriPath uri) let path'' = if null path' then frontPage cfg else urlDecode path' guard $ isPage path'' return path'' withBody = setContentType "text/html; charset=utf-8" . toResponse isn'tRedirect = do getSource >>= traverse_ (redirectedFrom >=> addMessage) return (Right page) isRedirect destination = do params <- getParams case maybe (pRedirect params) (\_ -> Just False) (pRevision params) of Nothing -> do source <- getSource case source of Just source' -> do doubleRedirect source' destination >>= addMessage return (Right page) Nothing -> fmap Left $ do base' <- getWikiBase let url' = concat [ base' , urlForPage (pageName page) , "?redirect=yes" ] lift $ seeOther url' $ withBody $ concat [ "307 Redirect" , "

You are being redirected.

" ] Just True -> fmap Left $ do (url', html') <- processDestination destination lift $ ok $ withBody $ concat [ "Redirecting to " , html' , "

Redirecting to " , html' , "...

" ] Just False -> do cancelledRedirect destination >>= addMessage return (Right page) -- | Converts contents of page file to Page object. contentsToPage :: String -> ContentTransformer Page contentsToPage s = do cfg <- lift getConfig pn <- getPageName return $ stringToPage cfg pn s -- | Converts pandoc document to HTML. pandocToHtml :: Pandoc -> ContentTransformer Html pandocToHtml pandocContents = do base' <- lift getWikiBase toc <- liftM ctxTOC get bird <- liftM ctxBirdTracks get cfg <- lift getConfig let tpl = "$if(toc)$
\n$toc$\n
\n$endif$\n$body$" return $ primHtml $ T.unpack . (if xssSanitize cfg then sanitizeBalance else id) . T.pack $ writeHtmlString def{ #if MIN_VERSION_pandoc(1,19,0) writerTemplate = Just tpl #else writerStandalone = True , writerTemplate = tpl #endif , writerHTMLMathMethod = case mathMethod cfg of MathML -> Pandoc.MathML Nothing WebTeX u -> Pandoc.WebTeX u MathJax u -> Pandoc.MathJax u _ -> JsMath (Just $ base' ++ "/js/jsMath/easy/load.js") , writerTableOfContents = toc , writerHighlight = True , writerExtensions = if bird then Set.insert Ext_literate_haskell $ writerExtensions def else writerExtensions def -- note: javascript obfuscation gives problems on preview , writerEmailObfuscation = ReferenceObfuscation } pandocContents -- | Returns highlighted source code. highlightSource :: Maybe String -> ContentTransformer Html highlightSource Nothing = mzero highlightSource (Just source) = do file <- getFileName let formatOpts = defaultFormatOpts { numberLines = True, lineAnchors = True } case languagesByExtension $ takeExtension file of [] -> mzero (l:_) -> return $ primHtml $ Blaze.renderHtml $ formatHtmlBlock formatOpts $! highlightAs l $ filter (/='\r') source -- -- Plugin combinators -- getPageTransforms :: ContentTransformer [Pandoc -> PluginM Pandoc] getPageTransforms = liftM (mapMaybe pageTransform) $ queryGititState plugins where pageTransform (PageTransform x) = Just x pageTransform _ = Nothing getPreParseTransforms :: ContentTransformer [String -> PluginM String] getPreParseTransforms = liftM (mapMaybe preParseTransform) $ queryGititState plugins where preParseTransform (PreParseTransform x) = Just x preParseTransform _ = Nothing getPreCommitTransforms :: ContentTransformer [String -> PluginM String] getPreCommitTransforms = liftM (mapMaybe preCommitTransform) $ queryGititState plugins where preCommitTransform (PreCommitTransform x) = Just x preCommitTransform _ = Nothing -- | @applyTransform a t@ applies the transform @t@ to input @a@. applyTransform :: a -> (a -> PluginM a) -> ContentTransformer a applyTransform inp transform = do context <- get conf <- lift getConfig user <- lift getLoggedInUser fs <- lift getFileStore req <- lift askRq let pluginData = PluginData{ pluginConfig = conf , pluginUser = user , pluginRequest = req , pluginFileStore = fs } (result', context') <- liftIO $ runPluginM (transform inp) pluginData context put context' return result' -- | Applies all the page transform plugins to a Pandoc document. applyPageTransforms :: Pandoc -> ContentTransformer Pandoc applyPageTransforms c = do xforms <- getPageTransforms foldM applyTransform c (wikiLinksTransform : xforms) -- | Applies all the pre-parse transform plugins to a Page object. applyPreParseTransforms :: Page -> ContentTransformer Page applyPreParseTransforms page' = getPreParseTransforms >>= foldM applyTransform (pageText page') >>= (\t -> return page'{ pageText = t }) -- | Applies all the pre-commit transform plugins to a raw string. applyPreCommitTransforms :: String -> ContentTransformer String applyPreCommitTransforms c = getPreCommitTransforms >>= foldM applyTransform c -- -- Content or context augmentation combinators -- -- | Puts rendered page content into a wikipage div, adding -- categories. wikiDivify :: Html -> ContentTransformer Html wikiDivify c = do categories <- liftM ctxCategories get base' <- lift getWikiBase let categoryLink ctg = li (anchor ! [href $ base' ++ "/_category/" ++ ctg] << ctg) let htmlCategories = if null categories then noHtml else thediv ! [identifier "categoryList"] << ulist << map categoryLink categories return $ thediv ! [identifier "wikipage"] << [c, htmlCategories] -- | Adds page title to a Pandoc document. addPageTitleToPandoc :: String -> Pandoc -> ContentTransformer Pandoc addPageTitleToPandoc title' (Pandoc _ blocks) = do updateLayout $ \layout -> layout{ pgTitle = title' } return $ if null title' then Pandoc nullMeta blocks else Pandoc (B.setMeta "title" (B.str title') nullMeta) blocks -- | Adds javascript links for math support. addMathSupport :: a -> ContentTransformer a addMathSupport c = do conf <- lift getConfig updateLayout $ \l -> case mathMethod conf of JsMathScript -> addScripts l ["jsMath/easy/load.js"] MathML -> addScripts l ["MathMLinHTML.js"] WebTeX _ -> l MathJax u -> addScripts l [u] RawTeX -> l return c -- | Adds javascripts to page layout. addScripts :: PageLayout -> [String] -> PageLayout addScripts layout scriptPaths = layout{ pgScripts = scriptPaths ++ pgScripts layout } -- -- ContentTransformer context API -- getParams :: ContentTransformer Params getParams = lift (withData return) getFileName :: ContentTransformer FilePath getFileName = liftM ctxFile get getPageName :: ContentTransformer String getPageName = liftM (pgPageName . ctxLayout) get getLayout :: ContentTransformer PageLayout getLayout = liftM ctxLayout get getCacheable :: ContentTransformer Bool getCacheable = liftM ctxCacheable get -- | Updates the layout with the result of applying f to the current layout updateLayout :: (PageLayout -> PageLayout) -> ContentTransformer () updateLayout f = do ctx <- get let l = ctxLayout ctx put ctx { ctxLayout = f l } -- -- Pandoc and wiki content conversion support -- readerFor :: PageType -> Bool -> String -> Pandoc readerFor pt lhs = let defPS = def{ readerSmart = True , readerExtensions = if lhs then Set.insert Ext_literate_haskell $ readerExtensions def else readerExtensions def , readerParseRaw = True } in handleError . case pt of RST -> readRST defPS Markdown -> readMarkdown defPS #if MIN_VERSION_pandoc(1,14,0) CommonMark -> readCommonMark defPS #else CommonMark -> error "CommonMark input requires pandoc 1.14" #endif LaTeX -> readLaTeX defPS HTML -> readHtml defPS Textile -> readTextile defPS Org -> readOrg defPS DocBook -> readDocBook defPS MediaWiki -> readMediaWiki defPS wikiLinksTransform :: Pandoc -> PluginM Pandoc wikiLinksTransform pandoc = do cfg <- liftM pluginConfig ask -- Can't use askConfig from Interface due to circular dependencies. return (bottomUp (convertWikiLinks cfg) pandoc) -- | Convert links with no URL to wikilinks. convertWikiLinks :: Config -> Inline -> Inline #if MIN_VERSION_pandoc(1,16,0) convertWikiLinks cfg (Link attr ref ("", "")) | useAbsoluteUrls cfg = Link attr ref ("/" baseUrl cfg inlinesToURL ref, "Go to wiki page") convertWikiLinks _cfg (Link attr ref ("", "")) = Link attr ref (inlinesToURL ref, "Go to wiki page") #else convertWikiLinks cfg (Link ref ("", "")) | useAbsoluteUrls cfg = Link ref ("/" baseUrl cfg inlinesToURL ref, "Go to wiki page") convertWikiLinks _cfg (Link ref ("", "")) = Link ref (inlinesToURL ref, "Go to wiki page") #endif convertWikiLinks _cfg x = x -- | Derives a URL from a list of Pandoc Inline elements. inlinesToURL :: [Inline] -> String inlinesToURL = encString False isUnescapedInURI . inlinesToString -- | Convert a list of inlines into a string. inlinesToString :: [Inline] -> String inlinesToString = concatMap go where go x = case x of Str s -> s Emph xs -> concatMap go xs Strong xs -> concatMap go xs Strikeout xs -> concatMap go xs Superscript xs -> concatMap go xs Subscript xs -> concatMap go xs SmallCaps xs -> concatMap go xs Quoted DoubleQuote xs -> '"' : (concatMap go xs ++ "\"") Quoted SingleQuote xs -> '\'' : (concatMap go xs ++ "'") Cite _ xs -> concatMap go xs Code _ s -> s Space -> " " #if MIN_VERSION_pandoc(1,16,0) SoftBreak -> " " #endif LineBreak -> " " Math DisplayMath s -> "$$" ++ s ++ "$$" Math InlineMath s -> "$" ++ s ++ "$" RawInline (Format "tex") s -> s RawInline _ _ -> "" #if MIN_VERSION_pandoc(1,16,0) Link _ xs _ -> concatMap go xs Image _ xs _ -> concatMap go xs #else Link xs _ -> concatMap go xs Image xs _ -> concatMap go xs #endif Note _ -> "" Span _ xs -> concatMap go xs gitit-0.12.2.1/src/Network/Gitit/Types.hs0000644000000000000000000004473312765540066016227 0ustar0000000000000000{-# LANGUAGE TypeSynonymInstances, ScopedTypeVariables, FlexibleInstances #-} {- Copyright (C) 2009 John MacFarlane , Anton van Straaten This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Types for Gitit modules. -} module Network.Gitit.Types ( PageType(..) , FileStoreType(..) , MathMethod(..) , AuthenticationLevel(..) , Config(..) , Page(..) , SessionKey -- we do not export SessionData constructors, in case we need to extend SessionData with other data in the future , SessionData , sessionData , sessionDataGithubState , sessionUser , sessionGithubState , User(..) , Sessions(..) , Password(..) , GititState(..) , HasContext , modifyContext , getContext , ContentTransformer , Plugin(..) , PluginData(..) , PluginM , runPluginM , Context(..) , PageLayout(..) , Tab(..) , Recaptcha(..) , Params(..) , Command(..) , WikiState(..) , GititServerPart , Handler , fromEntities , GithubConfig , oAuth2 , org , githubConfig) where import Control.Monad.Reader (ReaderT, runReaderT, mplus) import Control.Monad.State (StateT, runStateT, get, modify) import Control.Monad (liftM) import System.Log.Logger (Priority(..)) import Text.Pandoc.Definition (Pandoc) import Text.XHtml (Html) import qualified Data.Map as M import Data.Text (Text) import Data.List (intersect) import Data.Time (parseTime) #if MIN_VERSION_time(1,5,0) import Data.Time (defaultTimeLocale) #else import System.Locale (defaultTimeLocale) #endif import Data.FileStore.Types import Network.Gitit.Server import Text.HTML.TagSoup.Entity (lookupEntity) import Data.Char (isSpace) import Network.OAuth.OAuth2 data PageType = Markdown | CommonMark | RST | LaTeX | HTML | Textile | Org | DocBook | MediaWiki deriving (Read, Show, Eq) data FileStoreType = Git | Darcs | Mercurial deriving Show data MathMethod = MathML | JsMathScript | WebTeX String | RawTeX | MathJax String deriving (Read, Show, Eq) data AuthenticationLevel = Never | ForModify | ForRead deriving (Read, Show, Eq, Ord) -- | Data structure for information read from config file. data Config = Config { -- | Path of repository containing filestore repositoryPath :: FilePath, -- | Type of repository repositoryType :: FileStoreType, -- | Default page markup type for this wiki defaultPageType :: PageType, -- | Default file extension for pages in this wiki defaultExtension :: String, -- | How to handle LaTeX math in pages? mathMethod :: MathMethod, -- | Treat as literate haskell by default? defaultLHS :: Bool, -- | Show Haskell code with bird tracks showLHSBirdTracks :: Bool, -- | Combinator to set @REMOTE_USER@ request header withUser :: Handler -> Handler, -- | Handler for login, logout, register, etc. requireAuthentication :: AuthenticationLevel, -- | Specifies which actions require authentication. authHandler :: Handler, -- | Path of users database userFile :: FilePath, -- | Seconds of inactivity before session expires sessionTimeout :: Int, -- | Directory containing page templates templatesDir :: FilePath, -- | Path of server log file logFile :: FilePath, -- | Severity filter for log messages (DEBUG, INFO, -- NOTICE, WARNING, ERROR, CRITICAL, ALERT, EMERGENCY) logLevel :: Priority, -- | Path of static directory staticDir :: FilePath, -- | Names of plugin modules to load pluginModules :: [String], -- | Show table of contents on each page? tableOfContents :: Bool, -- | Max size of file uploads maxUploadSize :: Integer, -- | Max size of page uploads maxPageSize :: Integer, -- | IP address to bind to address :: String, -- | Port number to serve content on portNumber :: Int, -- | Print debug info to the console? debugMode :: Bool, -- | The front page of the wiki frontPage :: String, -- | Pages that cannot be edited via web noEdit :: [String], -- | Pages that cannot be deleted via web noDelete :: [String], -- | Default summary if description left blank defaultSummary :: String, -- | Delete summary deleteSummary :: String, -- | @Nothing@ = anyone can register. -- @Just (prompt, answers)@ = a user will -- be given the prompt and must give -- one of the answers to register. accessQuestion :: Maybe (String, [String]), -- | Use ReCAPTCHA for user registration. useRecaptcha :: Bool, recaptchaPublicKey :: String, recaptchaPrivateKey :: String, -- | RPX domain and key rpxDomain :: String, rpxKey :: String, -- | Should responses be compressed? compressResponses :: Bool, -- | Should responses be cached? useCache :: Bool, -- | Directory to hold cached pages cacheDir :: FilePath, -- | Map associating mime types with file extensions mimeMap :: M.Map String String, -- | Command to send notification emails mailCommand :: String, -- | Text of password reset email resetPasswordMessage :: String, -- | Markup syntax help for edit sidebar markupHelp :: String, -- | Provide an atom feed? useFeed :: Bool, -- | Base URL of wiki, for use in feed baseUrl :: String, -- | Title of wiki, used in feed useAbsoluteUrls :: Bool, -- | Should WikiLinks be absolute w.r.t. the base URL? wikiTitle :: String, -- | Number of days history to be included in feed feedDays :: Integer, -- | Number of minutes to cache feeds before refreshing feedRefreshTime :: Integer, -- | Allow PDF export? pdfExport :: Bool, -- | Directory to search for pandoc customizations pandocUserData :: Maybe FilePath, -- | Filter HTML through xss-sanitize xssSanitize :: Bool, -- | The default number of days in the past to look for \"recent\" activity recentActivityDays :: Int, -- | Github client data for authentication (id, secret, callback, -- authorize endpoint, access token endpoint) githubAuth :: GithubConfig } -- | Data for rendering a wiki page. data Page = Page { pageName :: String , pageFormat :: PageType , pageLHS :: Bool , pageTOC :: Bool , pageTitle :: String , pageCategories :: [String] , pageText :: String , pageMeta :: [(String, String)] } deriving (Read, Show) type SessionKey = Integer data SessionData = SessionData { sessionUser :: Maybe String, sessionGithubState :: Maybe String } deriving (Read,Show,Eq) sessionData :: String -> SessionData sessionData user = SessionData (Just user) Nothing sessionDataGithubState :: String -> SessionData sessionDataGithubState githubState = SessionData Nothing (Just githubState) data Sessions a = Sessions {unsession::M.Map SessionKey a} deriving (Read,Show,Eq) -- Password salt hashedPassword data Password = Password { pSalt :: String, pHashed :: String } deriving (Read,Show,Eq) data User = User { uUsername :: String, uPassword :: Password, uEmail :: String } deriving (Show,Read) -- | Common state for all gitit wikis in an application. data GititState = GititState { sessions :: Sessions SessionData, users :: M.Map String User, templatesPath :: FilePath, renderPage :: PageLayout -> Html -> Handler, plugins :: [Plugin] } type ContentTransformer = StateT Context GititServerPart data Plugin = PageTransform (Pandoc -> PluginM Pandoc) | PreParseTransform (String -> PluginM String) | PreCommitTransform (String -> PluginM String) data PluginData = PluginData { pluginConfig :: Config , pluginUser :: Maybe User , pluginRequest :: Request , pluginFileStore :: FileStore } type PluginM = ReaderT PluginData (StateT Context IO) runPluginM :: PluginM a -> PluginData -> Context -> IO (a, Context) runPluginM plugin = runStateT . runReaderT plugin data Context = Context { ctxFile :: String , ctxLayout :: PageLayout , ctxCacheable :: Bool , ctxTOC :: Bool , ctxBirdTracks :: Bool , ctxCategories :: [String] , ctxMeta :: [(String, String)] } class (Monad m) => HasContext m where getContext :: m Context modifyContext :: (Context -> Context) -> m () instance HasContext ContentTransformer where getContext = get modifyContext = modify instance HasContext PluginM where getContext = get modifyContext = modify -- | Abstract representation of page layout (tabs, scripts, etc.) data PageLayout = PageLayout { pgPageName :: String , pgRevision :: Maybe String , pgPrintable :: Bool , pgMessages :: [String] , pgTitle :: String , pgScripts :: [String] , pgShowPageTools :: Bool , pgShowSiteNav :: Bool , pgMarkupHelp :: Maybe String , pgTabs :: [Tab] , pgSelectedTab :: Tab , pgLinkToFeed :: Bool } data Tab = ViewTab | EditTab | HistoryTab | DiscussTab | DiffTab deriving (Eq, Show) data Recaptcha = Recaptcha { recaptchaChallengeField :: String , recaptchaResponseField :: String } deriving (Read, Show) instance FromData SessionKey where fromData = readCookieValue "sid" data Params = Params { pUsername :: String , pPassword :: String , pPassword2 :: String , pRevision :: Maybe String , pDestination :: String , pForUser :: Maybe String , pSince :: Maybe UTCTime , pRaw :: String , pLimit :: Int , pPatterns :: [String] , pGotoPage :: String , pFileToDelete :: String , pEditedText :: Maybe String , pMessages :: [String] , pFrom :: Maybe String , pTo :: Maybe String , pFormat :: String , pSHA1 :: String , pLogMsg :: String , pEmail :: String , pFullName :: String , pAccessCode :: String , pWikiname :: String , pPrintable :: Bool , pOverwrite :: Bool , pFilename :: String , pFilePath :: FilePath , pConfirm :: Bool , pSessionKey :: Maybe SessionKey , pRecaptcha :: Recaptcha , pResetCode :: String , pRedirect :: Maybe Bool } deriving Show instance FromReqURI [String] where fromReqURI s = case fromReqURI s of Just (s' :: String) -> case reads s' of ((xs,""):_) -> xs _ -> Nothing Nothing -> Nothing instance FromData Params where fromData = do let look' = look un <- look' "username" `mplus` return "" pw <- look' "password" `mplus` return "" p2 <- look' "password2" `mplus` return "" rv <- (look' "revision" >>= \s -> return (if null s then Nothing else Just s)) `mplus` return Nothing fu <- liftM Just (look' "forUser") `mplus` return Nothing si <- liftM (parseTime defaultTimeLocale "%Y-%m-%d") (look' "since") `mplus` return Nothing -- YYYY-mm-dd format ds <- look' "destination" `mplus` return "" ra <- look' "raw" `mplus` return "" lt <- lookRead "limit" `mplus` return 100 pa <- look' "patterns" `mplus` return "" gt <- look' "gotopage" `mplus` return "" ft <- look' "filetodelete" `mplus` return "" me <- looks "message" fm <- liftM Just (look' "from") `mplus` return Nothing to <- liftM Just (look' "to") `mplus` return Nothing et <- liftM (Just . filter (/='\r')) (look' "editedText") `mplus` return Nothing fo <- look' "format" `mplus` return "" sh <- look' "sha1" `mplus` return "" lm <- look' "logMsg" `mplus` return "" em <- look' "email" `mplus` return "" na <- look' "full_name_1" `mplus` return "" wn <- look' "wikiname" `mplus` return "" pr <- (look' "printable" >> return True) `mplus` return False ow <- liftM (=="yes") (look' "overwrite") `mplus` return False fileparams <- liftM Just (lookFile "file") `mplus` return Nothing let (fp, fn) = case fileparams of Just (x,y,_) -> (x,y) Nothing -> ("","") ac <- look' "accessCode" `mplus` return "" cn <- (look' "confirm" >> return True) `mplus` return False sk <- liftM Just (readCookieValue "sid") `mplus` return Nothing rc <- look' "recaptcha_challenge_field" `mplus` return "" rr <- look' "recaptcha_response_field" `mplus` return "" rk <- look' "reset_code" `mplus` return "" rd <- (look' "redirect" >>= \r -> return (case r of "yes" -> Just True "no" -> Just False _ -> Nothing)) `mplus` return Nothing return Params { pUsername = un , pPassword = pw , pPassword2 = p2 , pRevision = rv , pForUser = fu , pSince = si , pDestination = ds , pRaw = ra , pLimit = lt , pPatterns = words pa , pGotoPage = gt , pFileToDelete = ft , pMessages = me , pFrom = fm , pTo = to , pEditedText = et , pFormat = fo , pSHA1 = sh , pLogMsg = lm , pEmail = em , pFullName = na , pWikiname = wn , pPrintable = pr , pOverwrite = ow , pFilename = fn , pFilePath = fp , pAccessCode = ac , pConfirm = cn , pSessionKey = sk , pRecaptcha = Recaptcha { recaptchaChallengeField = rc, recaptchaResponseField = rr } , pResetCode = rk , pRedirect = rd } data Command = Command (Maybe String) deriving Show instance FromData Command where fromData = do pairs <- lookPairs return $ case map fst pairs `intersect` commandList of [] -> Command Nothing (c:_) -> Command $ Just c where commandList = ["update", "cancel", "export"] -- | State for a single wiki. data WikiState = WikiState { wikiConfig :: Config , wikiFileStore :: FileStore } type GititServerPart = ServerPartT (ReaderT WikiState IO) type Handler = GititServerPart Response -- Unescapes XML entities fromEntities :: String -> String fromEntities ('&':xs) = case lookupEntity ent of Just c -> c ++ fromEntities rest Nothing -> '&' : fromEntities xs where (ent, rest) = case break (\c -> isSpace c || c == ';') xs of (zs,';':ys) -> (zs,ys) _ -> ("",xs) fromEntities (x:xs) = x : fromEntities xs fromEntities [] = [] data GithubConfig = GithubConfig { oAuth2 :: OAuth2 , org :: Maybe Text } githubConfig :: OAuth2 -> Maybe Text -> GithubConfig githubConfig = GithubConfig gitit-0.12.2.1/src/Network/Gitit/Framework.hs0000644000000000000000000003353012765540066017051 0ustar0000000000000000{-# LANGUAGE ScopedTypeVariables #-} {- Copyright (C) 2009 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Useful functions for defining wiki handlers. -} module Network.Gitit.Framework ( -- * Combinators for dealing with users withUserFromSession , withUserFromHTTPAuth , authenticateUserThat , authenticate , getLoggedInUser -- * Combinators to exclude certain actions , unlessNoEdit , unlessNoDelete -- * Guards for routing , guardCommand , guardPath , guardIndex , guardBareBase -- * Functions to get info from the request , getPath , getPage , getReferer , getWikiBase , uriPath -- * Useful predicates , isPage , isPageFile , isDiscussPage , isDiscussPageFile , isNotDiscussPageFile , isSourceCode -- * Combinators that change the request locally , withMessages -- * Miscellaneous , 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 Data.Maybe (fromJust, fromMaybe) import Data.List (intercalate, isPrefixOf, isInfixOf) import System.FilePath ((<.>), takeExtension, takeFileName) import Text.Highlighting.Kate import Text.ParserCombinators.Parsec import Network.URL (decString, encString) import Network.URI (isUnescapedInURI) import Data.ByteString.Base64 (decodeLenient) import Network.HTTP (urlEncodeVars) -- | Require a logged in user if the authentication level demands it. -- Run the handler if a user is logged in, otherwise redirect -- to login page. authenticate :: AuthenticationLevel -> Handler -> Handler authenticate = authenticateUserThat (const True) -- | Like 'authenticate', but with a predicate that the user must satisfy. 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 -- | Run the handler after setting @REMOTE_USER@ with the user from -- the session. 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)) -- refresh timeout case sessionUser sd of Nothing -> return Nothing Just user -> getUser user let user = maybe "" uUsername mbUser localRq (setHeader "REMOTE_USER" user) handler -- | Run the handler after setting @REMOTE_USER@ from the "authorization" -- header. Works with simple HTTP authentication or digest authentication. 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 -- | Returns @Just@ logged in user or @Nothing@. 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 responder fallback@ runs @responder@ unless the -- page has been designated not editable in configuration; in that -- case, runs @fallback@. 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 responder fallback@ runs @responder@ unless the -- page has been designated not deletable in configuration; in that -- case, runs @fallback@. 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 -- | Returns the current path (subtracting initial commands like @\/_edit@). getPath :: ServerMonad m => m String getPath = liftM (intercalate "/" . rqPaths) askRq -- | Returns the current page name (derived from the path). 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 -- fail if not valid page name -- | Returns the contents of the "referer" header. 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' -- | Returns the base URL of the wiki in the happstack server. -- So, if the wiki handlers are behind a @dir 'foo'@, getWikiBase will -- return @\/foo/@. getWikiBase doesn't know anything about HTTP -- proxies, so if you use proxies to map a gitit wiki to @\/foo/@, -- you'll still need to follow the instructions in README. 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') -- | The pure core of 'getWikiBase'. 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 -- a path like _feed is not part of the base... 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 -- | Returns path portion of URI, without initial @\/@. -- Consecutive spaces are collapsed. We don't want to distinguish -- @Hi There@ and @Hi There@. 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) -- for now, we disallow @*@ and @?@ in page names, because git filestore -- does not deal with them properly, and darcs filestore disallows them. 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 = languagesByFilename $ takeFileName path' ext = takeExtension path' in not (null langs || ext == ".svg" || ext == ".eps") -- allow svg or eps to be served as image -- | Returns encoded URL path for the page with the given name, relative to -- the wiki base. urlForPage :: String -> String urlForPage page = '/' : encString False isUnescapedInURI page -- | Returns the filestore path of the file containing the page's source. pathForPage :: String -> String -> FilePath pathForPage page ext = page <.> ext -- | Retrieves a mime type based on file extension. getMimeTypeForExtension :: String -> GititServerPart String getMimeTypeForExtension ext = do mimes <- liftM mimeMap getConfig return $ fromMaybe "application/octet-stream" (M.lookup (dropWhile (== '.') $ map toLower ext) mimes) -- | Simple helper for validation of forms. validate :: [(Bool, String)] -- ^ list of conditions and error messages -> [String] -- ^ list of error messages 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) -- | Succeeds if path is an index path: e.g. @\/foo\/bar/@. guardIndex :: GititServerPart () guardIndex = do base <- getWikiBase uri' <- liftM rqUri askRq let localpath = drop (length base) uri' unless (length localpath > 1 && lastNote "guardIndex" uri' == '/') mzero -- Guard against a path like @\/wiki@ when the wiki is being -- served at @\/wiki@. guardBareBase :: GititServerPart () guardBareBase = do base' <- getWikiBase uri' <- liftM rqUri askRq unless (not (null base') && base' == uri') mzero -- | Runs a server monad in a local context after setting -- the "message" request header. 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 -- | Returns a filestore object derived from the -- repository path and filestore type specified in configuration. filestoreFromConfig :: Config -> FileStore filestoreFromConfig conf = case repositoryType conf of Git -> gitFileStore $ repositoryPath conf Darcs -> darcsFileStore $ repositoryPath conf Mercurial -> mercurialFileStore $ repositoryPath conf gitit-0.12.2.1/src/Network/Gitit/Initialize.hs0000644000000000000000000002317713050600376017210 0ustar0000000000000000{-# LANGUAGE CPP #-} {- Copyright (C) 2009 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Functions for initializing a Gitit wiki. -} module Network.Gitit.Initialize ( initializeGititState , recompilePageTemplate , compilePageTemplate , createStaticIfMissing , createRepoIfMissing , createDefaultPages , createTemplateIfMissing ) where import System.FilePath ((), (<.>)) import Data.FileStore import qualified Data.Map as M import qualified Data.Set as Set import Network.Gitit.Util (readFileUTF8) import Network.Gitit.Types import Network.Gitit.State import Network.Gitit.Framework import Network.Gitit.Plugins import Network.Gitit.Layout (defaultRenderPage) import Paths_gitit (getDataFileName) import Control.Exception (throwIO, try) import System.Directory (copyFile, createDirectoryIfMissing, doesDirectoryExist, doesFileExist) import Control.Monad (unless, forM_, liftM) import Text.Pandoc import System.Log.Logger (logM, Priority(..)) import qualified Text.StringTemplate as T #if MIN_VERSION_pandoc(1,14,0) import Text.Pandoc.Error (handleError) #else handleError :: Pandoc -> Pandoc handleError = id #endif -- | Initialize Gitit State. initializeGititState :: Config -> IO () initializeGititState conf = do let userFile' = userFile conf pluginModules' = pluginModules conf plugins' <- loadPlugins pluginModules' userFileExists <- doesFileExist userFile' users' <- if userFileExists then liftM (M.fromList . read) $ readFileUTF8 userFile' else return M.empty templ <- compilePageTemplate (templatesDir conf) updateGititState $ \s -> s { sessions = Sessions M.empty , users = users' , templatesPath = templatesDir conf , renderPage = defaultRenderPage templ , plugins = plugins' } -- | Recompile the page template. recompilePageTemplate :: IO () recompilePageTemplate = do tempsDir <- queryGititState templatesPath ct <- compilePageTemplate tempsDir updateGititState $ \st -> st{renderPage = defaultRenderPage ct} --- | Compile a master page template named @page.st@ in the directory specified. compilePageTemplate :: FilePath -> IO (T.StringTemplate String) compilePageTemplate tempsDir = do defaultGroup <- getDataFileName ("data" "templates") >>= T.directoryGroup customExists <- doesDirectoryExist tempsDir combinedGroup <- if customExists -- default templates from data directory will be "shadowed" -- by templates from the user's template dir then do customGroup <- T.directoryGroup tempsDir return $ T.mergeSTGroups customGroup defaultGroup else do logM "gitit" WARNING $ "Custom template directory not found" return defaultGroup case T.getStringTemplate "page" combinedGroup of Just t -> return t Nothing -> error "Could not get string template" -- | Create templates dir if it doesn't exist. createTemplateIfMissing :: Config -> IO () createTemplateIfMissing conf' = do templateExists <- doesDirectoryExist (templatesDir conf') unless templateExists $ do createDirectoryIfMissing True (templatesDir conf') templatePath <- getDataFileName $ "data" "templates" -- templs <- liftM (filter (`notElem` [".",".."])) $ -- getDirectoryContents templatePath -- Copy footer.st, since this is the component users -- are most likely to want to customize: forM_ ["footer.st"] $ \t -> do copyFile (templatePath t) (templatesDir conf' t) logM "gitit" WARNING $ "Created " ++ (templatesDir conf' t) -- | Create page repository unless it exists. createRepoIfMissing :: Config -> IO () createRepoIfMissing conf = do let fs = filestoreFromConfig conf repoExists <- try (initialize fs) >>= \res -> case res of Right _ -> do logM "gitit" WARNING $ "Created repository in " ++ repositoryPath conf return False Left RepositoryExists -> return True Left e -> throwIO e >> return False unless repoExists $ createDefaultPages conf createDefaultPages :: Config -> IO () createDefaultPages conf = do let fs = filestoreFromConfig conf pt = defaultPageType conf toPandoc = handleError . readMarkdown def{ readerSmart = True } defOpts = def{ writerHTMLMathMethod = JsMath (Just "/js/jsMath/easy/load.js") , writerExtensions = if showLHSBirdTracks conf then Set.insert Ext_literate_haskell $ writerExtensions def else writerExtensions def } -- note: we convert this (markdown) to the default page format converter = case pt of Markdown -> id LaTeX -> writeLaTeX defOpts . toPandoc HTML -> writeHtmlString defOpts . toPandoc RST -> writeRST defOpts . toPandoc Textile -> writeTextile defOpts . toPandoc Org -> writeOrg defOpts . toPandoc DocBook -> writeDocbook defOpts . toPandoc MediaWiki -> writeMediaWiki defOpts . toPandoc #if MIN_VERSION_pandoc(1,14,0) CommonMark -> writeCommonMark defOpts . toPandoc #else CommonMark -> error "CommonMark support requires pandoc >= 1.14" #endif welcomepath <- getDataFileName $ "data" "FrontPage" <.> "page" welcomecontents <- liftM converter $ readFileUTF8 welcomepath helppath <- getDataFileName $ "data" "Help" <.> "page" helpcontentsInitial <- liftM converter $ readFileUTF8 helppath markuppath <- getDataFileName $ "data" "markup" <.> show pt helpcontentsMarkup <- liftM converter $ readFileUTF8 markuppath let helpcontents = helpcontentsInitial ++ "\n\n" ++ helpcontentsMarkup usersguidepath <- getDataFileName "README.markdown" usersguidecontents <- liftM converter $ readFileUTF8 usersguidepath -- include header in case user changes default format: let header = "---\nformat: " ++ show pt ++ (if defaultLHS conf then "+lhs" else "") ++ "\n...\n\n" -- add front page, help page, and user's guide let auth = Author "Gitit" "" createIfMissing fs (frontPage conf <.> defaultExtension conf) auth "Default front page" $ header ++ welcomecontents createIfMissing fs ("Help" <.> defaultExtension conf) auth "Default help page" $ header ++ helpcontents createIfMissing fs ("Gitit User’s Guide" <.> defaultExtension conf) auth "User’s guide (README)" $ header ++ usersguidecontents createIfMissing :: FileStore -> FilePath -> Author -> Description -> String -> IO () createIfMissing fs p a comm cont = do res <- try $ create fs p a comm cont case res of Right _ -> logM "gitit" WARNING ("Added " ++ p ++ " to repository") Left ResourceExists -> return () Left e -> throwIO e >> return () -- | Create static directory unless it exists. createStaticIfMissing :: Config -> IO () createStaticIfMissing conf = do let staticdir = staticDir conf staticExists <- doesDirectoryExist staticdir unless staticExists $ do let cssdir = staticdir "css" createDirectoryIfMissing True cssdir cssDataDir <- getDataFileName $ "data" "static" "css" -- cssFiles <- liftM (filter (\f -> takeExtension f == ".css")) $ getDirectoryContents cssDataDir forM_ ["custom.css"] $ \f -> do copyFile (cssDataDir f) (cssdir f) logM "gitit" WARNING $ "Created " ++ (cssdir f) {- let icondir = staticdir "img" "icons" createDirectoryIfMissing True icondir iconDataDir <- getDataFileName $ "data" "static" "img" "icons" iconFiles <- liftM (filter (\f -> takeExtension f == ".png")) $ getDirectoryContents iconDataDir forM_ iconFiles $ \f -> do copyFile (iconDataDir f) (icondir f) logM "gitit" WARNING $ "Created " ++ (icondir f) -} logopath <- getDataFileName $ "data" "static" "img" "logo.png" createDirectoryIfMissing True $ staticdir "img" copyFile logopath $ staticdir "img" "logo.png" logM "gitit" WARNING $ "Created " ++ (staticdir "img" "logo.png") {- let jsdir = staticdir "js" createDirectoryIfMissing True jsdir jsDataDir <- getDataFileName $ "data" "static" "js" javascripts <- liftM (filter (`notElem` [".", ".."])) $ getDirectoryContents jsDataDir forM_ javascripts $ \f -> do copyFile (jsDataDir f) (jsdir f) logM "gitit" WARNING $ "Created " ++ (jsdir f) -} gitit-0.12.2.1/src/Network/Gitit/Config.hs0000644000000000000000000003762112765540066016326 0ustar0000000000000000{-# LANGUAGE CPP, FlexibleContexts, ScopedTypeVariables #-} {- Copyright (C) 2009 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Functions for parsing command line options and reading the config file. -} module Network.Gitit.Config ( getConfigFromFile , getConfigFromFiles , getDefaultConfig , readMimeTypesFile ) where import Network.Gitit.Types import Network.Gitit.Server (mimeTypes) import Network.Gitit.Framework import Network.Gitit.Authentication (formAuthHandlers, rpxAuthHandlers, httpAuthHandlers, githubAuthHandlers) import Network.Gitit.Util (parsePageType, readFileUTF8) import System.Log.Logger (logM, Priority(..)) import qualified Data.Map as M import Data.ConfigFile hiding (readfile) import Data.List (intercalate) import Data.Char (toLower, toUpper, isDigit) import Data.Text (pack) import Paths_gitit (getDataFileName) import System.FilePath (()) import Text.Pandoc hiding (MathML, WebTeX, MathJax) import qualified Control.Exception as E import Network.OAuth.OAuth2 import qualified Data.ByteString.Char8 as BS import Network.Gitit.Compat.Except import Control.Monad import Control.Monad.Trans #if MIN_VERSION_pandoc(1,14,0) import Text.Pandoc.Error (handleError) #else handleError :: Pandoc -> Pandoc handleError = id #endif forceEither :: Show e => Either e a -> a forceEither = either (error . show) id -- | Get configuration from config file. getConfigFromFile :: FilePath -> IO Config getConfigFromFile fname = do cp <- getDefaultConfigParser readfile cp fname >>= extractConfig . forceEither -- | Get configuration from config files. getConfigFromFiles :: [FilePath] -> IO Config getConfigFromFiles fnames = do config <- getConfigParserFromFiles fnames extractConfig config getConfigParserFromFiles :: [FilePath] -> IO ConfigParser getConfigParserFromFiles (fname:fnames) = do cp <- getConfigParserFromFiles fnames config <- readfile cp fname return $ forceEither config getConfigParserFromFiles [] = getDefaultConfigParser -- | A version of readfile that treats the file as UTF-8. readfile :: MonadError CPError m => ConfigParser -> FilePath -> IO (m ConfigParser) readfile cp path' = do contents <- readFileUTF8 path' return $ readstring cp contents extractConfig :: ConfigParser -> IO Config extractConfig cp = do config' <- runExceptT $ do cfRepositoryType <- get cp "DEFAULT" "repository-type" cfRepositoryPath <- get cp "DEFAULT" "repository-path" cfDefaultPageType <- get cp "DEFAULT" "default-page-type" cfDefaultExtension <- get cp "DEFAULT" "default-extension" cfMathMethod <- get cp "DEFAULT" "math" cfMathjaxScript <- get cp "DEFAULT" "mathjax-script" cfShowLHSBirdTracks <- get cp "DEFAULT" "show-lhs-bird-tracks" cfRequireAuthentication <- get cp "DEFAULT" "require-authentication" cfAuthenticationMethod <- get cp "DEFAULT" "authentication-method" cfUserFile <- get cp "DEFAULT" "user-file" cfSessionTimeout <- get cp "DEFAULT" "session-timeout" cfTemplatesDir <- get cp "DEFAULT" "templates-dir" cfLogFile <- get cp "DEFAULT" "log-file" cfLogLevel <- get cp "DEFAULT" "log-level" cfStaticDir <- get cp "DEFAULT" "static-dir" cfPlugins <- get cp "DEFAULT" "plugins" cfTableOfContents <- get cp "DEFAULT" "table-of-contents" cfMaxUploadSize <- get cp "DEFAULT" "max-upload-size" cfMaxPageSize <- get cp "DEFAULT" "max-page-size" cfAddress <- get cp "DEFAULT" "address" cfPort <- get cp "DEFAULT" "port" cfDebugMode <- get cp "DEFAULT" "debug-mode" cfFrontPage <- get cp "DEFAULT" "front-page" cfNoEdit <- get cp "DEFAULT" "no-edit" cfNoDelete <- get cp "DEFAULT" "no-delete" cfDefaultSummary <- get cp "DEFAULT" "default-summary" cfDeleteSummary <- get cp "DEFAULT" "delete-summary" cfAccessQuestion <- get cp "DEFAULT" "access-question" cfAccessQuestionAnswers <- get cp "DEFAULT" "access-question-answers" cfUseRecaptcha <- get cp "DEFAULT" "use-recaptcha" cfRecaptchaPublicKey <- get cp "DEFAULT" "recaptcha-public-key" cfRecaptchaPrivateKey <- get cp "DEFAULT" "recaptcha-private-key" cfRPXDomain <- get cp "DEFAULT" "rpx-domain" cfRPXKey <- get cp "DEFAULT" "rpx-key" cfCompressResponses <- get cp "DEFAULT" "compress-responses" cfUseCache <- get cp "DEFAULT" "use-cache" cfCacheDir <- get cp "DEFAULT" "cache-dir" cfMimeTypesFile <- get cp "DEFAULT" "mime-types-file" cfMailCommand <- get cp "DEFAULT" "mail-command" cfResetPasswordMessage <- get cp "DEFAULT" "reset-password-message" cfUseFeed <- get cp "DEFAULT" "use-feed" cfBaseUrl <- get cp "DEFAULT" "base-url" cfAbsoluteUrls <- get cp "DEFAULT" "absolute-urls" cfWikiTitle <- get cp "DEFAULT" "wiki-title" cfFeedDays <- get cp "DEFAULT" "feed-days" cfFeedRefreshTime <- get cp "DEFAULT" "feed-refresh-time" cfPDFExport <- get cp "DEFAULT" "pdf-export" cfPandocUserData <- get cp "DEFAULT" "pandoc-user-data" cfXssSanitize <- get cp "DEFAULT" "xss-sanitize" cfRecentActivityDays <- get cp "DEFAULT" "recent-activity-days" let (pt, lhs) = parsePageType cfDefaultPageType let markupHelpFile = show pt ++ if lhs then "+LHS" else "" markupHelpPath <- liftIO $ getDataFileName $ "data" "markupHelp" markupHelpFile markupHelpText <- liftM (writeHtmlString def . handleError . readMarkdown def) $ liftIO $ readFileUTF8 markupHelpPath mimeMap' <- liftIO $ readMimeTypesFile cfMimeTypesFile let authMethod = map toLower cfAuthenticationMethod let stripTrailingSlash = reverse . dropWhile (=='/') . reverse let repotype' = case map toLower cfRepositoryType of "git" -> Git "darcs" -> Darcs "mercurial" -> Mercurial x -> error $ "Unknown repository type: " ++ x when (authMethod == "rpx" && cfRPXDomain == "") $ liftIO $ logM "gitit" WARNING "rpx-domain is not set" ghConfig <- extractGithubConfig cp when (null cfUserFile) $ liftIO $ logM "gitit" ERROR "user-file is empty" return Config{ repositoryPath = cfRepositoryPath , repositoryType = repotype' , defaultPageType = pt , defaultExtension = cfDefaultExtension , mathMethod = case map toLower cfMathMethod of "jsmath" -> JsMathScript "mathml" -> MathML "mathjax" -> MathJax cfMathjaxScript "google" -> WebTeX "http://chart.apis.google.com/chart?cht=tx&chl=" _ -> RawTeX , defaultLHS = lhs , showLHSBirdTracks = cfShowLHSBirdTracks , withUser = case authMethod of "form" -> withUserFromSession "github" -> withUserFromSession "http" -> withUserFromHTTPAuth "rpx" -> withUserFromSession _ -> id , requireAuthentication = case map toLower cfRequireAuthentication of "none" -> Never "modify" -> ForModify "read" -> ForRead _ -> ForModify , authHandler = case authMethod of "form" -> msum formAuthHandlers "github" -> msum $ githubAuthHandlers ghConfig "http" -> msum httpAuthHandlers "rpx" -> msum rpxAuthHandlers _ -> mzero , userFile = cfUserFile , sessionTimeout = readNumber "session-timeout" cfSessionTimeout * 60 -- convert minutes -> seconds , templatesDir = cfTemplatesDir , logFile = cfLogFile , logLevel = let levelString = map toUpper cfLogLevel levels = ["DEBUG", "INFO", "NOTICE", "WARNING", "ERROR", "CRITICAL", "ALERT", "EMERGENCY"] in if levelString `elem` levels then read levelString else error $ "Invalid log-level.\nLegal values are: " ++ intercalate ", " levels , staticDir = cfStaticDir , pluginModules = splitCommaList cfPlugins , tableOfContents = cfTableOfContents , maxUploadSize = readSize "max-upload-size" cfMaxUploadSize , maxPageSize = readSize "max-page-size" cfMaxPageSize , address = cfAddress , portNumber = readNumber "port" cfPort , debugMode = cfDebugMode , frontPage = cfFrontPage , noEdit = splitCommaList cfNoEdit , noDelete = splitCommaList cfNoDelete , defaultSummary = cfDefaultSummary , deleteSummary = cfDeleteSummary , accessQuestion = if null cfAccessQuestion then Nothing else Just (cfAccessQuestion, splitCommaList cfAccessQuestionAnswers) , useRecaptcha = cfUseRecaptcha , recaptchaPublicKey = cfRecaptchaPublicKey , recaptchaPrivateKey = cfRecaptchaPrivateKey , rpxDomain = cfRPXDomain , rpxKey = cfRPXKey , compressResponses = cfCompressResponses , useCache = cfUseCache , cacheDir = cfCacheDir , mimeMap = mimeMap' , mailCommand = cfMailCommand , resetPasswordMessage = fromQuotedMultiline cfResetPasswordMessage , markupHelp = markupHelpText , useFeed = cfUseFeed , baseUrl = stripTrailingSlash cfBaseUrl , useAbsoluteUrls = cfAbsoluteUrls , wikiTitle = cfWikiTitle , feedDays = readNumber "feed-days" cfFeedDays , feedRefreshTime = readNumber "feed-refresh-time" cfFeedRefreshTime , pdfExport = cfPDFExport , pandocUserData = if null cfPandocUserData then Nothing else Just cfPandocUserData , xssSanitize = cfXssSanitize , recentActivityDays = cfRecentActivityDays , githubAuth = ghConfig } case config' of Left (ParseError e, e') -> error $ "Parse error: " ++ e ++ "\n" ++ e' Left e -> error (show e) Right c -> return c extractGithubConfig :: (Functor m, MonadError CPError m) => ConfigParser -> m GithubConfig extractGithubConfig cp = do cfOauthClientId <- getGithubProp "oauthClientId" cfOauthClientSecret <- getGithubProp "oauthClientSecret" cfOauthCallback <- getGithubProp "oauthCallback" cfOauthOAuthorizeEndpoint <- getGithubProp "oauthOAuthorizeEndpoint" cfOauthAccessTokenEndpoint <- getGithubProp "oauthAccessTokenEndpoint" cfOrg <- if hasGithubProp "github-org" then fmap Just (getGithubProp "github-org") else return Nothing let cfgOAuth2 = OAuth2 { oauthClientId = BS.pack cfOauthClientId , oauthClientSecret = BS.pack cfOauthClientSecret , oauthCallback = Just $ BS.pack cfOauthCallback , oauthOAuthorizeEndpoint = BS.pack cfOauthOAuthorizeEndpoint , oauthAccessTokenEndpoint = BS.pack cfOauthAccessTokenEndpoint } return $ githubConfig cfgOAuth2 $ fmap pack cfOrg where getGithubProp = get cp "Github" hasGithubProp = has_option cp "Github" fromQuotedMultiline :: String -> String fromQuotedMultiline = unlines . map doline . lines . dropWhile (`elem` " \t\n") where doline = dropWhile (`elem` " \t") . dropGt dropGt ('>':' ':xs) = xs dropGt ('>':xs) = xs dropGt x = x readNumber :: (Num a, Read a) => String -> String -> a readNumber _ x | all isDigit x = read x readNumber opt _ = error $ opt ++ " must be a number." readSize :: (Num a, Read a) => String -> String -> a readSize opt x = case reverse x of ('K':_) -> readNumber opt (init x) * 1000 ('M':_) -> readNumber opt (init x) * 1000000 ('G':_) -> readNumber opt (init x) * 1000000000 _ -> readNumber opt x splitCommaList :: String -> [String] splitCommaList l = let (first,rest) = break (== ',') l first' = lrStrip first in case rest of [] -> if null first' then [] else [first'] (_:rs) -> first' : splitCommaList rs lrStrip :: String -> String lrStrip = reverse . dropWhile isWhitespace . reverse . dropWhile isWhitespace where isWhitespace = (`elem` " \t\n") getDefaultConfigParser :: IO ConfigParser getDefaultConfigParser = do cp <- getDataFileName "data/default.conf" >>= readfile emptyCP return $ forceEither cp -- | Returns the default gitit configuration. getDefaultConfig :: IO Config getDefaultConfig = getDefaultConfigParser >>= extractConfig -- | Read a file associating mime types with extensions, and return a -- map from extensions to types. Each line of the file consists of a -- mime type, followed by space, followed by a list of zero or more -- extensions, separated by spaces. Example: text/plain txt text readMimeTypesFile :: FilePath -> IO (M.Map String String) readMimeTypesFile f = E.catch (liftM (foldr (go . words) M.empty . lines) $ readFileUTF8 f) handleMimeTypesFileNotFound where go [] m = m -- skip blank lines go (x:xs) m = foldr (`M.insert` x) m xs handleMimeTypesFileNotFound (e :: E.SomeException) = do logM "gitit" WARNING $ "Could not read mime types file: " ++ f ++ "\n" ++ show e ++ "\n" ++ "Using defaults instead." return mimeTypes {- -- | Ready collection of common mime types. (Copied from -- Happstack.Server.HTTP.FileServe.) mimeTypes :: M.Map String String mimeTypes = M.fromList [("xml","application/xml") ,("xsl","application/xml") ,("js","text/javascript") ,("html","text/html") ,("htm","text/html") ,("css","text/css") ,("gif","image/gif") ,("jpg","image/jpeg") ,("png","image/png") ,("txt","text/plain") ,("doc","application/msword") ,("exe","application/octet-stream") ,("pdf","application/pdf") ,("zip","application/zip") ,("gz","application/x-gzip") ,("ps","application/postscript") ,("rtf","application/rtf") ,("wav","application/x-wav") ,("hs","text/plain")] -} gitit-0.12.2.1/src/Network/Gitit/Layout.hs0000644000000000000000000001707212765540066016374 0ustar0000000000000000{-# LANGUAGE FlexibleContexts #-} {- Copyright (C) 2009 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- Functions and data structures for wiki page layout. -} module Network.Gitit.Layout ( defaultPageLayout , defaultRenderPage , formattedPage , filledPageTemplate , uploadsAllowed ) where import Network.Gitit.Server import Network.Gitit.Framework import Network.Gitit.State import Network.Gitit.Types import Network.Gitit.Export (exportFormats) import Network.HTTP (urlEncodeVars) import qualified Text.StringTemplate as T import Text.XHtml hiding ( (), dir, method, password, rev ) import Text.XHtml.Strict ( stringToHtmlString ) import Data.Maybe (isNothing, isJust, fromJust) defaultPageLayout :: PageLayout defaultPageLayout = PageLayout { pgPageName = "" , pgRevision = Nothing , pgPrintable = False , pgMessages = [] , pgTitle = "" , pgScripts = [] , pgShowPageTools = True , pgShowSiteNav = True , pgMarkupHelp = Nothing , pgTabs = [ViewTab, EditTab, HistoryTab, DiscussTab] , pgSelectedTab = ViewTab , pgLinkToFeed = False } -- | Returns formatted page formattedPage :: PageLayout -> Html -> Handler formattedPage layout htmlContents = do renderer <- queryGititState renderPage renderer layout htmlContents -- | Given a compiled string template, returns a page renderer. defaultRenderPage :: T.StringTemplate String -> PageLayout -> Html -> Handler defaultRenderPage templ layout htmlContents = do cfg <- getConfig base' <- getWikiBase ok . setContentType "text/html; charset=utf-8" . toResponse . T.render . filledPageTemplate base' cfg layout htmlContents $ templ -- | Returns a page template with gitit variables filled in. filledPageTemplate :: String -> Config -> PageLayout -> Html -> T.StringTemplate String -> T.StringTemplate String filledPageTemplate base' cfg layout htmlContents templ = let rev = pgRevision layout page = pgPageName layout prefixedScript x = case x of 'h':'t':'t':'p':_ -> x _ -> base' ++ "/js/" ++ x scripts = ["jquery-1.2.6.min.js", "jquery-ui-combined-1.6rc2.min.js", "footnotes.js"] ++ pgScripts layout scriptLink x = script ! [src (prefixedScript x), thetype "text/javascript"] << noHtml javascriptlinks = renderHtmlFragment $ concatHtml $ map scriptLink scripts article = if isDiscussPage page then drop 1 page else page discussion = '@':article tabli tab = if tab == pgSelectedTab layout then li ! [theclass "selected"] else li tabs' = [x | x <- pgTabs layout, not (x == EditTab && page `elem` noEdit cfg)] tabs = ulist ! [theclass "tabs"] << map (linkForTab tabli base' page rev) tabs' setStrAttr attr = T.setAttribute attr . stringToHtmlString setBoolAttr attr test = if test then T.setAttribute attr "true" else id in T.setAttribute "base" base' . T.setAttribute "feed" (pgLinkToFeed layout) . setStrAttr "wikititle" (wikiTitle cfg) . setStrAttr "pagetitle" (pgTitle layout) . T.setAttribute "javascripts" javascriptlinks . setStrAttr "pagename" page . setStrAttr "articlename" article . setStrAttr "discussionname" discussion . setStrAttr "pageUrl" (urlForPage page) . setStrAttr "articleUrl" (urlForPage article) . setStrAttr "discussionUrl" (urlForPage discussion) . setBoolAttr "ispage" (isPage page) . setBoolAttr "isarticlepage" (isPage page && not (isDiscussPage page)) . setBoolAttr "isdiscusspage" (isDiscussPage page) . setBoolAttr "pagetools" (pgShowPageTools layout) . setBoolAttr "sitenav" (pgShowSiteNav layout) . maybe id (T.setAttribute "markuphelp") (pgMarkupHelp layout) . setBoolAttr "printable" (pgPrintable layout) . maybe id (T.setAttribute "revision") rev . T.setAttribute "exportbox" (renderHtmlFragment $ exportBox base' cfg page rev) . (if null (pgTabs layout) then id else T.setAttribute "tabs" (renderHtmlFragment tabs)) . (\f x xs -> if null xs then x else f xs) (T.setAttribute "messages") id (pgMessages layout) . T.setAttribute "usecache" (useCache cfg) . T.setAttribute "content" (renderHtmlFragment htmlContents) . setBoolAttr "wikiupload" ( uploadsAllowed cfg) $ templ exportBox :: String -> Config -> String -> Maybe String -> Html exportBox base' cfg page rev | not (isSourceCode page) = gui (base' ++ urlForPage page) ! [identifier "exportbox"] << ([ textfield "revision" ! [thestyle "display: none;", value (fromJust rev)] | isJust rev ] ++ [ select ! [name "format"] << map ((\f -> option ! [value f] << f) . fst) (exportFormats cfg) , primHtmlChar "nbsp" , submit "export" "Export" ]) exportBox _ _ _ _ = noHtml -- auxiliary functions: linkForTab :: (Tab -> Html -> Html) -> String -> String -> Maybe String -> Tab -> Html linkForTab tabli base' page _ HistoryTab = tabli HistoryTab << anchor ! [href $ base' ++ "/_history" ++ urlForPage page] << "history" linkForTab tabli _ _ _ DiffTab = tabli DiffTab << anchor ! [href ""] << "diff" linkForTab tabli base' page rev ViewTab = let origPage s = if isDiscussPage s then drop 1 s else s in if isDiscussPage page then tabli DiscussTab << anchor ! [href $ base' ++ urlForPage (origPage page)] << "page" else tabli ViewTab << anchor ! [href $ base' ++ urlForPage page ++ case rev of Just r -> "?revision=" ++ r Nothing -> ""] << "view" linkForTab tabli base' page _ DiscussTab = tabli (if isDiscussPage page then ViewTab else DiscussTab) << anchor ! [href $ base' ++ if isDiscussPage page then "" else "/_discuss" ++ urlForPage page] << "discuss" linkForTab tabli base' page rev EditTab = tabli EditTab << anchor ! [href $ base' ++ "/_edit" ++ urlForPage page ++ case rev of Just r -> "?revision=" ++ r ++ "&" ++ urlEncodeVars [("logMsg", "Revert to " ++ r)] Nothing -> ""] << if isNothing rev then "edit" else "revert" uploadsAllowed :: Config -> Bool uploadsAllowed = (0 <) . maxUploadSize gitit-0.12.2.1/src/Network/Gitit/Authentication.hs0000644000000000000000000005605112765540066020076 0ustar0000000000000000{-# LANGUAGE ScopedTypeVariables, FlexibleContexts #-} {- Copyright (C) 2009 John MacFarlane , Henry Laxen This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- Handlers for registering and authenticating users. -} module Network.Gitit.Authentication ( loginUserForm , formAuthHandlers , httpAuthHandlers , rpxAuthHandlers , githubAuthHandlers) where import Network.Gitit.State import Network.Gitit.Types import Network.Gitit.Framework import Network.Gitit.Layout import Network.Gitit.Server import Network.Gitit.Util import Network.Gitit.Authentication.Github import Network.Captcha.ReCaptcha (captchaFields, validateCaptcha) import Text.XHtml hiding ( (), dir, method, password, rev ) import qualified Text.XHtml as X ( password ) import System.Process (readProcessWithExitCode) import Control.Monad (unless, liftM, mplus) import Control.Monad.Trans (liftIO) import System.Exit import System.Log.Logger (logM, Priority(..)) import Data.Char (isAlphaNum, isAlpha) import qualified Data.Map as M import Text.Pandoc.Shared (substitute) import Data.Maybe (isJust, fromJust, isNothing, fromMaybe) import Network.URL (exportURL, add_param, importURL) import Network.BSD (getHostName) import qualified Text.StringTemplate as T import Network.HTTP (urlEncodeVars, urlDecode, urlEncode) import Codec.Binary.UTF8.String (encodeString) import Data.ByteString.UTF8 (toString) import Network.Gitit.Rpxnow as R data ValidationType = Register | ResetPassword deriving (Show,Read) registerUser :: Params -> Handler registerUser params = do result' <- sharedValidation Register params case result' of Left errors -> registerForm >>= formattedPage defaultPageLayout{ pgMessages = errors, pgShowPageTools = False, pgTabs = [], pgTitle = "Register for an account" } Right (uname, email, pword) -> do user <- liftIO $ mkUser uname email pword addUser uname user loginUser params{ pUsername = uname, pPassword = pword, pEmail = email } resetPasswordRequestForm :: Params -> Handler resetPasswordRequestForm _ = do let passwordForm = gui "" ! [identifier "resetPassword"] << fieldset << [ label ! [thefor "username"] << "Username: " , textfield "username" ! [size "20", intAttr "tabindex" 1], stringToHtml " " , submit "resetPassword" "Reset Password" ! [intAttr "tabindex" 2]] cfg <- getConfig let contents = if null (mailCommand cfg) then p << "Sorry, password reset not available." else passwordForm formattedPage defaultPageLayout{ pgShowPageTools = False, pgTabs = [], pgTitle = "Reset your password" } contents resetPasswordRequest :: Params -> Handler resetPasswordRequest params = do let uname = pUsername params mbUser <- getUser uname let errors = case mbUser of Nothing -> ["Unknown user. Please re-register " ++ "or press the Back button to try again."] Just u -> ["Since you did not register with " ++ "an email address, we can't reset your password." | null (uEmail u) ] if null errors then do let response = p << [ stringToHtml "An email has been sent to " , bold $ stringToHtml . uEmail $ fromJust mbUser , br , stringToHtml "Please click on the enclosed link to reset your password." ] sendReregisterEmail (fromJust mbUser) formattedPage defaultPageLayout{ pgShowPageTools = False, pgTabs = [], pgTitle = "Resetting your password" } response else registerForm >>= formattedPage defaultPageLayout{ pgMessages = errors, pgShowPageTools = False, pgTabs = [], pgTitle = "Register for an account" } resetLink :: String -> User -> String resetLink base' user = exportURL $ foldl add_param (fromJust . importURL $ base' ++ "/_doResetPassword") [("username", uUsername user), ("reset_code", take 20 (pHashed (uPassword user)))] sendReregisterEmail :: User -> GititServerPart () sendReregisterEmail user = do cfg <- getConfig hostname <- liftIO getHostName base' <- getWikiBase let messageTemplate = T.newSTMP $ resetPasswordMessage cfg let filledTemplate = T.render . T.setAttribute "username" (uUsername user) . T.setAttribute "useremail" (uEmail user) . T.setAttribute "hostname" hostname . T.setAttribute "port" (show $ portNumber cfg) . T.setAttribute "resetlink" (resetLink base' user) $ messageTemplate let (mailcommand:args) = words $ substitute "%s" (uEmail user) (mailCommand cfg) (exitCode, _pOut, pErr) <- liftIO $ readProcessWithExitCode mailcommand args filledTemplate liftIO $ logM "gitit" WARNING $ "Sent reset password email to " ++ uUsername user ++ " at " ++ uEmail user unless (exitCode == ExitSuccess) $ liftIO $ logM "gitit" WARNING $ mailcommand ++ " failed. " ++ pErr validateReset :: Params -> (User -> Handler) -> Handler validateReset params postValidate = do let uname = pUsername params user <- getUser uname let knownUser = isJust user let resetCodeMatches = take 20 (pHashed (uPassword (fromJust user))) == pResetCode params let errors = case (knownUser, resetCodeMatches) of (True, True) -> [] (True, False) -> ["Your reset code is invalid"] (False, _) -> ["User " ++ renderHtmlFragment (stringToHtml uname) ++ " is not known"] if null errors then postValidate (fromJust user) else registerForm >>= formattedPage defaultPageLayout{ pgMessages = errors, pgShowPageTools = False, pgTabs = [], pgTitle = "Register for an account" } resetPassword :: Params -> Handler resetPassword params = validateReset params $ \user -> resetPasswordForm (Just user) >>= formattedPage defaultPageLayout{ pgShowPageTools = False, pgTabs = [], pgTitle = "Reset your registration info" } doResetPassword :: Params -> Handler doResetPassword params = validateReset params $ \user -> do result' <- sharedValidation ResetPassword params case result' of Left errors -> resetPasswordForm (Just user) >>= formattedPage defaultPageLayout{ pgMessages = errors, pgShowPageTools = False, pgTabs = [], pgTitle = "Reset your registration info" } Right (uname, email, pword) -> do user' <- liftIO $ mkUser uname email pword adjustUser uname user' liftIO $ logM "gitit" WARNING $ "Successfully reset password and email for " ++ uUsername user' loginUser params{ pUsername = uname, pPassword = pword, pEmail = email } registerForm :: GititServerPart Html registerForm = sharedForm Nothing resetPasswordForm :: Maybe User -> GititServerPart Html resetPasswordForm = sharedForm -- synonym for now sharedForm :: Maybe User -> GititServerPart Html sharedForm mbUser = withData $ \params -> do cfg <- getConfig dest <- case pDestination params of "" -> getReferer x -> return x let accessQ = case mbUser of Just _ -> noHtml Nothing -> case accessQuestion cfg of Nothing -> noHtml Just (prompt, _) -> label ! [thefor "accessCode"] << prompt +++ br +++ X.password "accessCode" ! [size "15", intAttr "tabindex" 1] +++ br let captcha = if useRecaptcha cfg then captchaFields (recaptchaPublicKey cfg) Nothing else noHtml let initField field = case mbUser of Nothing -> "" Just user -> field user let userNameField = case mbUser of Nothing -> label ! [thefor "username"] << "Username (at least 3 letters or digits):" +++ br +++ textfield "username" ! [size "20", intAttr "tabindex" 2] +++ br Just user -> label ! [thefor "username"] << ("Username (cannot be changed): " ++ uUsername user) +++ br let submitField = case mbUser of Nothing -> submit "register" "Register" Just _ -> submit "resetPassword" "Reset Password" return $ gui "" ! [identifier "loginForm"] << fieldset << [ accessQ , userNameField , label ! [thefor "email"] << "Email (optional, will not be displayed on the Wiki):" , br , textfield "email" ! [size "20", intAttr "tabindex" 3, value (initField uEmail)] , br ! [theclass "req"] , textfield "full_name_1" ! [size "20", theclass "req"] , br , label ! [thefor "password"] << ("Password (at least 6 characters," ++ " including at least one non-letter):") , br , X.password "password" ! [size "20", intAttr "tabindex" 4] , stringToHtml " " , br , label ! [thefor "password2"] << "Confirm Password:" , br , X.password "password2" ! [size "20", intAttr "tabindex" 5] , stringToHtml " " , br , captcha , textfield "destination" ! [thestyle "display: none;", value dest] , submitField ! [intAttr "tabindex" 6]] sharedValidation :: ValidationType -> Params -> GititServerPart (Either [String] (String,String,String)) sharedValidation validationType params = do let isValidUsernameChar c = isAlphaNum c || c == ' ' let isValidUsername u = length u >= 3 && all isValidUsernameChar u let isValidPassword pw = length pw >= 6 && not (all isAlpha pw) let accessCode = pAccessCode params let uname = pUsername params let pword = pPassword params let pword2 = pPassword2 params let email = pEmail params let fakeField = pFullName params let recaptcha = pRecaptcha params taken <- isUser uname cfg <- getConfig let optionalTests Register = [(taken, "Sorry, that username is already taken.")] optionalTests ResetPassword = [] let isValidAccessCode = case validationType of ResetPassword -> True Register -> case accessQuestion cfg of Nothing -> True Just (_, answers) -> accessCode `elem` answers let isValidEmail e = length (filter (=='@') e) == 1 peer <- liftM (fst . rqPeer) askRq captchaResult <- if useRecaptcha cfg then if null (recaptchaChallengeField recaptcha) || null (recaptchaResponseField recaptcha) -- no need to bother captcha.net in this case then return $ Left "missing-challenge-or-response" else liftIO $ do mbIPaddr <- lookupIPAddr peer let ipaddr = fromMaybe (error $ "Could not find ip address for " ++ peer) mbIPaddr ipaddr `seq` validateCaptcha (recaptchaPrivateKey cfg) ipaddr (recaptchaChallengeField recaptcha) (recaptchaResponseField recaptcha) else return $ Right () let (validCaptcha, captchaError) = case captchaResult of Right () -> (True, Nothing) Left err -> (False, Just err) let errors = validate $ optionalTests validationType ++ [ (not isValidAccessCode, "Incorrect response to access prompt.") , (not (isValidUsername uname), "Username must be at least 3 characters, all letters or digits.") , (not (isValidPassword pword), "Password must be at least 6 characters, " ++ "and must contain at least one non-letter.") , (not (null email) && not (isValidEmail email), "Email address appears invalid.") , (pword /= pword2, "Password does not match confirmation.") , (not validCaptcha, "Failed CAPTCHA (" ++ fromJust captchaError ++ "). Are you really human?") , (not (null fakeField), -- fakeField is hidden in CSS (honeypot) "You do not seem human enough. If you're sure you are human, " ++ "try turning off form auto-completion in your browser.") ] return $ if null errors then Right (uname, email, pword) else Left errors -- user authentication loginForm :: String -> GititServerPart Html loginForm dest = do cfg <- getConfig base' <- getWikiBase return $ gui (base' ++ "/_login") ! [identifier "loginForm"] << fieldset << [ label ! [thefor "username"] << "Username " , textfield "username" ! [size "15", intAttr "tabindex" 1] , stringToHtml " " , label ! [thefor "password"] << "Password " , X.password "password" ! [size "15", intAttr "tabindex" 2] , stringToHtml " " , textfield "destination" ! [thestyle "display: none;", value dest] , submit "login" "Login" ! [intAttr "tabindex" 3] ] +++ p << [ stringToHtml "If you do not have an account, " , anchor ! [href $ base' ++ "/_register?" ++ urlEncodeVars [("destination", encodeString dest)]] << "click here to get one." ] +++ if null (mailCommand cfg) then noHtml else p << [ stringToHtml "If you forgot your password, " , anchor ! [href $ base' ++ "/_resetPassword"] << "click here to get a new one." ] loginUserForm :: Handler loginUserForm = withData $ \params -> do dest <- case pDestination params of "" -> getReferer x -> return x loginForm dest >>= formattedPage defaultPageLayout{ pgShowPageTools = False, pgTabs = [], pgTitle = "Login", pgMessages = pMessages params } loginUser :: Params -> Handler loginUser params = do let uname = pUsername params let pword = pPassword params let destination = pDestination params allowed <- authUser uname pword cfg <- getConfig if allowed then do key <- newSession (sessionData uname) addCookie (MaxAge $ sessionTimeout cfg) (mkCookie "sid" (show key)) seeOther (encUrl destination) $ toResponse $ p << ("Welcome, " ++ renderHtmlFragment (stringToHtml uname)) else withMessages ["Invalid username or password."] loginUserForm logoutUser :: Params -> Handler logoutUser params = do let key = pSessionKey params dest <- case pDestination params of "" -> getReferer x -> return x case key of Just k -> do delSession k expireCookie "sid" Nothing -> return () seeOther (encUrl dest) $ toResponse "You have been logged out." registerUserForm :: Handler registerUserForm = registerForm >>= formattedPage defaultPageLayout{ pgShowPageTools = False, pgTabs = [], pgTitle = "Register for an account" } formAuthHandlers :: [Handler] formAuthHandlers = [ dir "_register" $ method GET >> registerUserForm , dir "_register" $ method POST >> withData registerUser , dir "_login" $ method GET >> loginUserForm , dir "_login" $ method POST >> withData loginUser , dir "_logout" $ method GET >> withData logoutUser , dir "_resetPassword" $ method GET >> withData resetPasswordRequestForm , dir "_resetPassword" $ method POST >> withData resetPasswordRequest , dir "_doResetPassword" $ method GET >> withData resetPassword , dir "_doResetPassword" $ method POST >> withData doResetPassword , dir "_user" currentUser ] loginUserHTTP :: Params -> Handler loginUserHTTP params = do base' <- getWikiBase let destination = pDestination params `orIfNull` (base' ++ "/") seeOther (encUrl destination) $ toResponse () logoutUserHTTP :: Handler logoutUserHTTP = unauthorized $ toResponse () -- will this work? httpAuthHandlers :: [Handler] httpAuthHandlers = [ dir "_logout" logoutUserHTTP , dir "_login" $ withData loginUserHTTP , dir "_user" currentUser ] oauthGithubCallback :: GithubConfig -> GithubCallbackPars -- ^ Authentication code gained after authorization -> Handler oauthGithubCallback ghConfig githubCallbackPars = withData $ \(sk :: Maybe SessionKey) -> do mbSd <- maybe (return Nothing) getSession sk mbGititState <- case mbSd of Nothing -> return Nothing Just sd -> return $ sessionGithubState sd let gititState = fromMaybe (error "No Github state found in session (is it the same domain?)") mbGititState mUser <- getGithubUser ghConfig githubCallbackPars gititState base' <- getWikiBase let destination = base' ++ "/" case mUser of Right user -> do let userEmail = uEmail user updateGititState $ \s -> s { users = M.insert userEmail user (users s) } addUser (uUsername user) user key <- newSession (sessionData userEmail) cfg <- getConfig addCookie (MaxAge $ sessionTimeout cfg) (mkCookie "sid" (show key)) seeOther (encUrl destination) $ toResponse () Left err -> do liftIO $ logM "gitit" WARNING $ "Login Failed: " ++ ghUserMessage err ++ maybe "" (". Github response" ++) (ghDetails err) cfg <- getConfig let destination' | requireAuthentication cfg >= ForRead = base' ++ "/_loginFailure" | otherwise = destination let url = destination' ++ "?message=" ++ ghUserMessage err seeOther (encUrl url) $ toResponse () githubAuthHandlers :: GithubConfig -> [Handler] githubAuthHandlers ghConfig = [ dir "_logout" $ withData logoutUser , dir "_login" $ loginGithubUser $ oAuth2 ghConfig , dir "_loginFailure" $ githubLoginFailure , dir "_githubCallback" $ withData $ oauthGithubCallback ghConfig , dir "_user" currentUser ] githubLoginFailure :: Handler githubLoginFailure = withData $ \params -> formattedPage (pageLayout (pMessages params)) noHtml >>= forbidden where pageLayout msgs = defaultPageLayout{ pgShowPageTools = False, pgTabs = [], pgTitle = "Login failure", pgMessages = msgs } -- Login using RPX (see RPX development docs at https://rpxnow.com/docs) loginRPXUser :: RPars -- ^ The parameters passed by the RPX callback call (after authentication has taken place -> Handler loginRPXUser params = do cfg <- getConfig ref <- getReferer let mtoken = rToken params if isNothing mtoken then do let url = baseUrl cfg ++ "/_login?destination=" ++ fromMaybe ref (rDestination params) if null (rpxDomain cfg) then error "rpx-domain is not set." else do let rpx = "https://" ++ rpxDomain cfg ++ ".rpxnow.com/openid/v2/signin?token_url=" ++ urlEncode url see rpx else do -- We got an answer from RPX, this might also return an exception. uid' :: Either String R.Identifier <- liftIO $ R.authenticate (rpxKey cfg) $ fromJust mtoken uid <- case uid' of Right u -> return u Left err -> error err liftIO $ logM "gitit.loginRPXUser" DEBUG $ "uid:" ++ show uid -- We need to get an unique identifier for the user -- The 'identifier' is always present but can be rather cryptic -- The 'verifiedEmail' is also unique and is a more readable choice -- so we use it if present. let userId = R.userIdentifier uid let email = prop "verifiedEmail" uid user <- liftIO $ mkUser (fromMaybe userId email) (fromMaybe "" email) "none" updateGititState $ \s -> s { users = M.insert userId user (users s) } key <- newSession (sessionData userId) addCookie (MaxAge $ sessionTimeout cfg) (mkCookie "sid" (show key)) see $ fromJust $ rDestination params where prop pname info = lookup pname $ R.userData info see url = seeOther (encUrl url) $ toResponse noHtml -- The parameters passed by the RPX callback call. data RPars = RPars { rToken :: Maybe String , rDestination :: Maybe String } deriving Show instance FromData RPars where fromData = do vtoken <- liftM Just (look "token") `mplus` return Nothing vDestination <- liftM (Just . urlDecode) (look "destination") `mplus` return Nothing return RPars { rToken = vtoken , rDestination = vDestination } rpxAuthHandlers :: [Handler] rpxAuthHandlers = [ dir "_logout" $ method GET >> withData logoutUser , dir "_login" $ withData loginRPXUser , dir "_user" currentUser ] -- | Returns username of logged in user or null string if nobody logged in. currentUser :: Handler currentUser = do req <- askRq ok $ toResponse $ maybe "" toString (getHeader "REMOTE_USER" req) gitit-0.12.2.1/src/Network/Gitit/Authentication/Github.hs0000644000000000000000000001447212765540066021321 0ustar0000000000000000{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-} module Network.Gitit.Authentication.Github ( loginGithubUser , getGithubUser , GithubCallbackPars , GithubLoginError , ghUserMessage , ghDetails) where import Network.Gitit.Types import Network.Gitit.Server import Network.Gitit.State import qualified Data.ByteString.Char8 as BS import qualified Data.ByteString.Lazy as BSL import Network.HTTP.Conduit import Network.HTTP.Client.TLS import Network.OAuth.OAuth2 import Control.Monad (liftM, mplus, mzero) import Data.Maybe import Data.Aeson import Data.Text (Text, pack, unpack) import Data.Text.Encoding (encodeUtf8) import Control.Applicative import Control.Monad.Trans (liftIO) import Data.UUID (toString) import Data.UUID.V4 (nextRandom) import qualified Control.Exception as E import Prelude loginGithubUser :: OAuth2 -> Handler loginGithubUser githubKey = do state <- liftIO $ fmap toString nextRandom key <- newSession (sessionDataGithubState state) cfg <- getConfig addCookie (MaxAge $ sessionTimeout cfg) (mkCookie "sid" (show key)) let usingOrg = isJust $ org $ githubAuth cfg let scopes = "user:email" ++ if usingOrg then ",read:org" else "" let url = authorizationUrl githubKey `appendQueryParam` [("state", BS.pack state), ("scope", BS.pack scopes)] seeOther (BS.unpack url) $ toResponse ("redirecting to github" :: String) data GithubLoginError = GithubLoginError { ghUserMessage :: String , ghDetails :: Maybe String } getGithubUser :: GithubConfig -- ^ Oauth2 configuration (client secret) -> GithubCallbackPars -- ^ Authentication code gained after authorization -> String -- ^ Github state, we expect the state we sent in loginGithubUser -> GititServerPart (Either GithubLoginError User) -- ^ user email and name (password 'none') getGithubUser ghConfig githubCallbackPars githubState = withManagerSettings tlsManagerSettings getUserInternal where getUserInternal mgr = liftIO $ do let (Just state) = rState githubCallbackPars if state == githubState then do let (Just code) = rCode githubCallbackPars ifSuccess "No access token found yet" (fetchAccessToken mgr (oAuth2 ghConfig) (sToBS code)) (\at -> ifSuccess "User Authentication failed" (userInfo mgr at) (\githubUser -> ifSuccess ("No email for user " ++ unpack (gLogin githubUser) ++ " returned by Github") (mailInfo mgr at) (\githubUserMail -> do let gitLogin = gLogin githubUser user <- mkUser (unpack gitLogin) (unpack $ email $ head (filter primary githubUserMail)) "none" let mbOrg = org ghConfig case mbOrg of Nothing -> return $ Right user Just githuborg -> ifSuccess ("Membership check failed: the user " ++ unpack gitLogin ++ " is required to be a member of the organization " ++ unpack githuborg ++ ".") (orgInfo gitLogin githuborg mgr at) (\_ -> return $ Right user)))) else return $ Left $ GithubLoginError ("The state sent to github is not the same as the state received: " ++ state ++ ", but expected sent state: " ++ githubState) Nothing ifSuccess errMsg failableAction successAction = E.catch (do Right outcome <- failableAction successAction outcome) (\exception -> liftIO $ return $ Left $ GithubLoginError errMsg (Just $ show (exception :: E.SomeException))) data GithubCallbackPars = GithubCallbackPars { rCode :: Maybe String , rState :: Maybe String } deriving Show instance FromData GithubCallbackPars where fromData = do vCode <- liftM Just (look "code") `mplus` return Nothing vState <- liftM Just (look "state") `mplus` return Nothing return GithubCallbackPars {rCode = vCode, rState = vState} userInfo :: Manager -> AccessToken -> IO (OAuth2Result GithubUser) userInfo mgr token = authGetJSON mgr token "https://api.github.com/user" mailInfo :: Manager -> AccessToken -> IO (OAuth2Result [GithubUserMail]) mailInfo mgr token = authGetJSON mgr token "https://api.github.com/user/emails" orgInfo :: Text -> Text -> Manager -> AccessToken -> IO (OAuth2Result BSL.ByteString) orgInfo gitLogin githubOrg mgr token = do let url = "https://api.github.com/orgs/" `BS.append` encodeUtf8 githubOrg `BS.append` "/members/" `BS.append` encodeUtf8 gitLogin authGetBS mgr token url data GithubUser = GithubUser { gLogin :: Text } deriving (Show, Eq) instance FromJSON GithubUser where parseJSON (Object o) = GithubUser <$> o .: "login" parseJSON _ = mzero data GithubUserMail = GithubUserMail { email :: Text , primary :: Bool } deriving (Show, Eq) instance FromJSON GithubUserMail where parseJSON (Object o) = GithubUserMail <$> o .: "email" <*> o .: "primary" parseJSON _ = mzero sToBS :: String -> BS.ByteString sToBS = encodeUtf8 . pack gitit-0.12.2.1/src/Network/Gitit/Util.hs0000644000000000000000000000747112765540066016036 0ustar0000000000000000{-# LANGUAGE CPP, ScopedTypeVariables #-} {- Copyright (C) 2009 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- Utility functions for Gitit. -} module Network.Gitit.Util ( readFileUTF8 , inDir , withTempDir , orIfNull , splitCategories , trim , yesOrNo , parsePageType , encUrl ) where import System.Directory import Control.Exception (bracket) import System.FilePath ((), (<.>)) import System.IO.Error (isAlreadyExistsError) import Control.Monad.Trans (liftIO) import Data.Char (toLower, isAscii) import Network.Gitit.Types import qualified Control.Exception as E import qualified Text.Pandoc.UTF8 as UTF8 import Network.URL (encString) -- | Read file as UTF-8 string. Encode filename as UTF-8. readFileUTF8 :: FilePath -> IO String readFileUTF8 = UTF8.readFile -- | Perform a function a directory and return to working directory. inDir :: FilePath -> IO a -> IO a inDir d action = do w <- getCurrentDirectory setCurrentDirectory d result <- action setCurrentDirectory w return result -- | Perform a function in a temporary directory and clean up. withTempDir :: FilePath -> (FilePath -> IO a) -> IO a withTempDir baseName f = do oldDir <- getCurrentDirectory bracket (createTempDir 0 baseName) (\tmp -> setCurrentDirectory oldDir >> removeDirectoryRecursive tmp) f -- | Create a temporary directory with a unique name. createTempDir :: Integer -> FilePath -> IO FilePath createTempDir num baseName = do sysTempDir <- getTemporaryDirectory let dirName = sysTempDir baseName <.> show num liftIO $ E.catch (createDirectory dirName >> return dirName) $ \e -> if isAlreadyExistsError e then createTempDir (num + 1) baseName else ioError e -- | Returns a list, if it is not null, or a backup, if it is. orIfNull :: [a] -> [a] -> [a] orIfNull lst backup = if null lst then backup else lst -- | Split a string containing a list of categories. splitCategories :: String -> [String] splitCategories = words . map puncToSpace . trim where puncToSpace x | x `elem` ".,;:" = ' ' puncToSpace x = x -- | Trim leading and trailing spaces. trim :: String -> String trim = reverse . trimLeft . reverse . trimLeft where trimLeft = dropWhile (`elem` " \t") -- | Show Bool as "yes" or "no". yesOrNo :: Bool -> String yesOrNo True = "yes" yesOrNo False = "no" parsePageType :: String -> (PageType, Bool) parsePageType s = case map toLower s of "markdown" -> (Markdown,False) "markdown+lhs" -> (Markdown,True) "commonmark" -> (CommonMark,False) "rst" -> (RST,False) "rst+lhs" -> (RST,True) "html" -> (HTML,False) "textile" -> (Textile,False) "latex" -> (LaTeX,False) "latex+lhs" -> (LaTeX,True) "org" -> (Org,False) "mediawiki" -> (MediaWiki,False) x -> error $ "Unknown page type: " ++ x encUrl :: String -> String encUrl = encString True isAscii gitit-0.12.2.1/src/Network/Gitit/Server.hs0000644000000000000000000000465212765540066016365 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {- Copyright (C) 2008 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- Re-exports Happstack functions needed by gitit, including replacements for Happstack functions that don't handle UTF-8 properly, and new functions for setting headers and zipping contents and for looking up IP addresses. -} module Network.Gitit.Server ( module Happstack.Server , withExpiresHeaders , setContentType , setFilename , lookupIPAddr , getHost , compressedResponseFilter ) where import Happstack.Server import Happstack.Server.Compression (compressedResponseFilter) import Network.Socket (getAddrInfo, defaultHints, addrAddress) import Control.Monad.Reader import Data.ByteString.UTF8 as U hiding (lines) withExpiresHeaders :: ServerMonad m => m Response -> m Response withExpiresHeaders = liftM (setHeader "Cache-Control" "max-age=21600") setContentType :: String -> Response -> Response setContentType = setHeader "Content-Type" setFilename :: String -> Response -> Response setFilename = setHeader "Content-Disposition" . \fname -> "attachment; filename=\"" ++ fname ++ "\"" -- IP lookup lookupIPAddr :: String -> IO (Maybe String) lookupIPAddr hostname = do addrs <- getAddrInfo (Just defaultHints) (Just hostname) Nothing if null addrs then return Nothing else return $ Just $ takeWhile (/=':') $ show $ addrAddress $ case addrs of -- head addrs [] -> error "lookupIPAddr, no addrs" (x:_) -> x getHost :: ServerMonad m => m (Maybe String) getHost = liftM (maybe Nothing (Just . U.toString)) $ getHeaderM "Host" gitit-0.12.2.1/src/Network/Gitit/Cache.hs0000644000000000000000000000603112765540066016113 0ustar0000000000000000{-# LANGUAGE CPP #-} {- Copyright (C) 2008 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- Functions for maintaining user list and session state. -} module Network.Gitit.Cache ( expireCachedFile , lookupCache , cacheContents ) where import qualified Data.ByteString as B (ByteString, readFile, writeFile) import System.FilePath import System.Directory (doesFileExist, removeFile, createDirectoryIfMissing, getModificationTime) import Data.Time.Clock (UTCTime) #if MIN_VERSION_directory(1,2,0) #else import System.Time (ClockTime(..)) import Data.Time.Clock.POSIX (posixSecondsToUTCTime) #endif import Network.Gitit.State import Network.Gitit.Types import Control.Monad import Control.Monad.Trans (liftIO) import Text.Pandoc.UTF8 (encodePath) -- | Expire a cached file, identified by its filename in the filestore. -- If there is an associated exported PDF, expire it too. -- Returns () after deleting a file from the cache, fails if no cached file. expireCachedFile :: String -> GititServerPart () expireCachedFile file = do cfg <- getConfig let target = encodePath $ cacheDir cfg file exists <- liftIO $ doesFileExist target when exists $ liftIO $ do liftIO $ removeFile target expireCachedPDF target (defaultExtension cfg) expireCachedPDF :: String -> String -> IO () expireCachedPDF file ext = when (takeExtension file == "." ++ ext) $ do let pdfname = file ++ ".export.pdf" exists <- doesFileExist pdfname when exists $ removeFile pdfname lookupCache :: String -> GititServerPart (Maybe (UTCTime, B.ByteString)) lookupCache file = do cfg <- getConfig let target = encodePath $ cacheDir cfg file exists <- liftIO $ doesFileExist target if exists then liftIO $ do #if MIN_VERSION_directory(1,2,0) modtime <- getModificationTime target #else TOD secs _ <- getModificationTime target let modtime = posixSecondsToUTCTime $ fromIntegral secs #endif contents <- B.readFile target return $ Just (modtime, contents) else return Nothing cacheContents :: String -> B.ByteString -> GititServerPart () cacheContents file contents = do cfg <- getConfig let target = encodePath $ cacheDir cfg file let targetDir = takeDirectory target liftIO $ do createDirectoryIfMissing True targetDir B.writeFile target contents expireCachedPDF target (defaultExtension cfg) gitit-0.12.2.1/src/Network/Gitit/State.hs0000644000000000000000000001211412765540066016167 0ustar0000000000000000{- Copyright (C) 2008 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- Functions for maintaining user list and session state. -} module Network.Gitit.State where import qualified Control.Exception as E import qualified Data.Map as M import System.Random (randomRIO) import Data.Digest.Pure.SHA (sha512, showDigest) import qualified Data.ByteString.Lazy.UTF8 as L (fromString) import Data.IORef import System.IO.Unsafe (unsafePerformIO) import Control.Monad.Reader import Data.FileStore import Data.List (intercalate) import System.Log.Logger (Priority(..), logM) import Network.Gitit.Types gititstate :: IORef GititState gititstate = unsafePerformIO $ newIORef GititState { sessions = undefined , users = undefined , templatesPath = undefined , renderPage = undefined , plugins = undefined } updateGititState :: MonadIO m => (GititState -> GititState) -> m () updateGititState fn = liftIO $! atomicModifyIORef gititstate $ \st -> (fn st, ()) queryGititState :: MonadIO m => (GititState -> a) -> m a queryGititState fn = liftM fn $ liftIO $! readIORef gititstate debugMessage :: String -> GititServerPart () debugMessage msg = liftIO $ logM "gitit" DEBUG msg mkUser :: String -- username -> String -- email -> String -- unhashed password -> IO User mkUser uname email pass = do salt <- genSalt return User { uUsername = uname, uPassword = Password { pSalt = salt, pHashed = hashPassword salt pass }, uEmail = email } genSalt :: IO String genSalt = replicateM 32 $ randomRIO ('0','z') hashPassword :: String -> String -> String hashPassword salt pass = showDigest $ sha512 $ L.fromString $ salt ++ pass authUser :: String -> String -> GititServerPart Bool authUser name pass = do users' <- queryGititState users case M.lookup name users' of Just u -> do let salt = pSalt $ uPassword u let hashed = pHashed $ uPassword u return $ hashed == hashPassword salt pass Nothing -> return False isUser :: String -> GititServerPart Bool isUser name = liftM (M.member name) $ queryGititState users addUser :: String -> User -> GititServerPart () addUser uname user = updateGititState (\s -> s { users = M.insert uname user (users s) }) >> getConfig >>= liftIO . writeUserFile adjustUser :: String -> User -> GititServerPart () adjustUser uname user = updateGititState (\s -> s { users = M.adjust (const user) uname (users s) }) >> getConfig >>= liftIO . writeUserFile delUser :: String -> GititServerPart () delUser uname = updateGititState (\s -> s { users = M.delete uname (users s) }) >> getConfig >>= liftIO . writeUserFile writeUserFile :: Config -> IO () writeUserFile conf = do usrs <- queryGititState users E.handle handleWriteError $ writeFile (userFile conf) $ "[" ++ intercalate "\n," (map show $ M.toList usrs) ++ "\n]" where handleWriteError :: E.SomeException -> IO () handleWriteError e = logM "gitit" ERROR $ "Error writing user file " ++ show (userFile conf) ++ "\n" ++ show e getUser :: String -> GititServerPart (Maybe User) getUser uname = liftM (M.lookup uname) $ queryGititState users isSession :: MonadIO m => SessionKey -> m Bool isSession key = liftM (M.member key . unsession) $ queryGititState sessions setSession :: MonadIO m => SessionKey -> SessionData -> m () setSession key u = updateGititState $ \s -> s { sessions = Sessions . M.insert key u . unsession $ sessions s } newSession :: MonadIO m => SessionData -> m SessionKey newSession u = do key <- liftIO $ randomRIO (0, 1000000000) setSession key u return key delSession :: MonadIO m => SessionKey -> m () delSession key = updateGititState $ \s -> s { sessions = Sessions . M.delete key . unsession $ sessions s } getSession :: MonadIO m => SessionKey -> m (Maybe SessionData) getSession key = queryGititState $ M.lookup key . unsession . sessions getConfig :: GititServerPart Config getConfig = liftM wikiConfig ask getFileStore :: GititServerPart FileStore getFileStore = liftM wikiFileStore ask getDefaultPageType :: GititServerPart PageType getDefaultPageType = liftM defaultPageType getConfig getDefaultLHS :: GititServerPart Bool getDefaultLHS = liftM defaultLHS getConfig gitit-0.12.2.1/src/Network/Gitit/Export.hs0000644000000000000000000003346113050602400016353 0ustar0000000000000000{-# LANGUAGE CPP #-} {- Copyright (C) 2009 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- Functions for exporting wiki pages in various formats. -} module Network.Gitit.Export ( exportFormats ) where import Text.Pandoc hiding (HTMLMathMethod(..)) import qualified Text.Pandoc as Pandoc import Text.Pandoc.PDF (makePDF) import Text.Pandoc.SelfContained as SelfContained import Text.Pandoc.Shared (readDataFileUTF8) import qualified Text.Pandoc.UTF8 as UTF8 import Network.Gitit.Server import Network.Gitit.Framework (pathForPage, getWikiBase) import Network.Gitit.State (getConfig) import Network.Gitit.Types import Network.Gitit.Cache (cacheContents, lookupCache) import Control.Monad.Trans (liftIO) import Control.Monad (unless) import Text.XHtml (noHtml) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as L import System.FilePath ((), takeDirectory) import Control.Exception (throwIO) import System.Directory (doesFileExist) import Text.HTML.SanitizeXSS import Text.Pandoc.Writers.RTF (writeRTFWithEmbeddedImages) import qualified Data.Text as T import Data.List (isPrefixOf) import Text.Highlighting.Kate (styleToCss, pygments) import Paths_gitit (getDataFileName) defaultRespOptions :: WriterOptions defaultRespOptions = def { writerHighlight = True } respond :: String -> String -> (Pandoc -> IO L.ByteString) -> String -> Pandoc -> Handler respond mimetype ext fn page doc = liftIO (fn doc) >>= ok . setContentType mimetype . (if null ext then id else setFilename (page ++ "." ++ ext)) . toResponseBS B.empty respondX :: String -> String -> String -> (WriterOptions -> Pandoc -> IO L.ByteString) -> WriterOptions -> String -> Pandoc -> Handler respondX templ mimetype ext fn opts page doc = do cfg <- getConfig template' <- liftIO $ getDefaultTemplate (pandocUserData cfg) templ template <- case template' of Right t -> return t Left e -> liftIO $ throwIO e doc' <- if ext `elem` ["odt","pdf","beamer","epub","docx","rtf"] then fixURLs page doc else return doc respond mimetype ext (fn opts{ #if MIN_VERSION_pandoc(1,19,0) writerTemplate = Just template #else writerTemplate = template ,writerStandalone = True #endif ,writerUserDataDir = pandocUserData cfg}) page doc' respondS :: String -> String -> String -> (WriterOptions -> Pandoc -> String) -> WriterOptions -> String -> Pandoc -> Handler respondS templ mimetype ext fn = respondX templ mimetype ext (\o d -> return $ UTF8.fromStringLazy $ fn o d) respondSlides :: String -> HTMLSlideVariant -> String -> Pandoc -> Handler respondSlides templ slideVariant page doc = do cfg <- getConfig base' <- getWikiBase let math = case mathMethod cfg of MathML -> Pandoc.MathML Nothing WebTeX u -> Pandoc.WebTeX u JsMathScript -> Pandoc.JsMath (Just $ base' ++ "/js/jsMath/easy/load.js") _ -> Pandoc.PlainMath let opts' = defaultRespOptions { writerSlideVariant = slideVariant ,writerIncremental = True ,writerHtml5 = templ == "dzslides" ,writerHTMLMathMethod = math} -- We sanitize the body only, to protect against XSS attacks. -- (Sanitizing the whole HTML page would strip out javascript -- needed for the slides.) We then pass the body into the -- slide template using the 'body' variable. Pandoc meta blocks <- fixURLs page doc let body' = writeHtmlString opts' (Pandoc meta blocks) -- just body let body'' = T.unpack $ (if xssSanitize cfg then sanitizeBalance else id) $ T.pack body' variables' <- if mathMethod cfg == MathML then do s <- liftIO $ readDataFileUTF8 (pandocUserData cfg) "MathMLinHTML.js" return [("mathml-script", s)] else return [] template' <- liftIO $ getDefaultTemplate (pandocUserData cfg) templ template <- case template' of Right t -> return t Left e -> liftIO $ throwIO e dzcore <- if templ == "dzslides" then do dztempl <- liftIO $ readDataFileUTF8 (pandocUserData cfg) $ "dzslides" "template.html" return $ unlines $ dropWhile (not . isPrefixOf "
$userbox()$ $tabs$ $content()$ $footer()$
$javascripts$ $expire()$ $getuser()$ gitit-0.12.2.1/data/templates/content.st0000644000000000000000000000043112765540066016203 0ustar0000000000000000
$if(revision)$

Revision $revision$ (click the page title to view the current version)

$endif$

$pagetitle$

$if(messages)$ $messages()$ $endif$ $content$
gitit-0.12.2.1/data/templates/userbox.st0000644000000000000000000000050412765540066016221 0ustar0000000000000000 gitit-0.12.2.1/data/templates/footer.st0000644000000000000000000000013712765540066016032 0ustar0000000000000000 gitit-0.12.2.1/data/templates/logo.st0000644000000000000000000000017012765540066015471 0ustar0000000000000000 gitit-0.12.2.1/data/templates/markuphelp.st0000644000000000000000000000005712765540066016705 0ustar0000000000000000
$markuphelp$
gitit-0.12.2.1/data/templates/pagetools.st0000644000000000000000000000120412765540066016525 0ustar0000000000000000
This page $exportbox$
gitit-0.12.2.1/data/templates/sitenav.st0000644000000000000000000000212412765540066016203 0ustar0000000000000000 gitit-0.12.2.1/data/templates/messages.st0000644000000000000000000000006412765540066016342 0ustar0000000000000000
    $messages:listitem()$
gitit-0.12.2.1/data/templates/listitem.st0000644000000000000000000000001612765540066016362 0ustar0000000000000000
  • $it$
  • gitit-0.12.2.1/data/templates/expire.st0000644000000000000000000000047112765540066016031 0ustar0000000000000000$if(usecache)$ $endif$ gitit-0.12.2.1/data/templates/getuser.st0000644000000000000000000000057412765540066016217 0ustar0000000000000000 gitit-0.12.2.1/data/markupHelp/Markdown0000644000000000000000000000135112765540066016002 0ustar0000000000000000~~~~~~~~ # Section heading ## Subsection Formatting: *italics*, **bold**, super^script^, sub~script~, ~~strikeout~~. A line break can be forced with two spaces at the end of the line. > Indented quotation Links: [external](http://google.com), [Wiki Link](), ![image](/img/logo.png), [to heading](#section-heading). Indented code block: #include Or use a delimited code block: ~~~ { .haskell } let a = 1:a in head a ~~~ - bulleted - list * * * * * 1. ordered 2. list a. sublist (indent 4 spaces) b. another 3. item three term : definition orange : orange fruit ~~~~~~~~ For more: [markdown syntax](http://daringfireball.net/projects/markdown), [pandoc extensions](http://pandoc.org/README.html). gitit-0.12.2.1/data/markupHelp/Markdown+LHS0000644000000000000000000000164312765540066016430 0ustar0000000000000000~~~~~~~~ # Section heading ## Subsection Formatting: *italics*, **bold**, super^script^, sub~script~, ~~strikeout~~. A line break can be forced with two spaces at the end of the line. > Indented quotation: > note: the '>' must not > be flush with the margin > or what follows will be > treated as Haskell code > -- bird-tracks Haskell: > fibs = 0 : 1 : > zipWith (+) fibs (tail fibs) Links: [external](http://google.com), [Wiki Link](), ![image](/img/logo.png), [to heading](#section-heading). Indented code block: #include Or use a delimited code block: ~~~ { .haskell } let a = 1:a in head a ~~~ - bulleted - list * * * * * 1. ordered 2. list a. sublist (indent 4 spaces) b. another 3. item three term : definition orange : orange fruit ~~~~~~~~ For more: [markdown syntax](http://daringfireball.net/projects/markdown), [pandoc extensions](http://pandoc.org/README.html). gitit-0.12.2.1/data/markupHelp/RST0000644000000000000000000000125012765540066014666 0ustar0000000000000000~~~~~~~~ Section heading =============== Subsection ---------- Formatting: *italics*, **bold**. Indented quotation Links: `external `_, `Wiki Link <>`_, |image|, `heading <#subsection>`_. .. |image| image:: /img/logo.png :: let a = 1:a in head a - bulleted - list --------------- 1. ordered 2. list a. sublist (indent 4 spaces) b. another 3. item three term definition orange orange fruit ~~~~~~~~ For more: [reST primer], [quick reference guide]. [reST primer]: http://docutils.sourceforge.net/docs/user/rst/quickstart.html [quick reference guide]: http://docutils.sourceforge.net/docs/user/rst/quickref.html gitit-0.12.2.1/data/markupHelp/RST+LHS0000644000000000000000000000135612765540066015317 0ustar0000000000000000~~~~~~~~ Section heading =============== Subsection ---------- Formatting: *italics*, **bold**. Indented quotation Links: `external `_, `Wiki Link <>`_, |image|, `heading <#subsection>`_. .. |image| image:: /img/logo.png :: let a = 1:a in head a > -- bird-style Haskell > fibs = 1 : 1 : zipWith (+) > fibs (tail fibs) - bulleted - list -------------- - ordered - list a. sublist (indent 4 spaces) b. another - item three term definition orange orange fruit ~~~~~~~~ For more: [reST primer], [quick reference guide]. [reST primer]: http://docutils.sourceforge.net/docs/user/rst/quickstart.html [quick reference guide]: http://docutils.sourceforge.net/docs/user/rst/quickref.html gitit-0.12.2.1/data/markupHelp/LaTeX0000644000000000000000000000156212765540066015201 0ustar0000000000000000~~~~~~~~ \section{Section heading} \subsection{Subsection} Formatting: \emph{italics}, \textbf{bold}, super\textsuperscript{script}, sub\textsubscr{script}, \sout{strikeout}. A line break\\ can be forced with \\ at the end of the line. \begin{quote} Indented quotation \end{quote} Links: \href{http://foo.bar}{external}, \href{}{Wiki Link}, \includegraphics{/img/banner.png}, \href{#subsection}{to heading}. \begin{verbatim} #include \end{verbatim} \begin{itemize} \item bulleted \item list \end{itemize} \begin{enumerate} \item ordered \item list \begin{enumerate}[a.] \item sublist \item another \end{enumerate} \item item three \end{enumerate} \begin{description} \item[term] definition \item[orange] orange fruit \end{description} ~~~~~~~~ For more: [LaTeX], [pandoc]. [LaTeX]: http://www.latex-project.org/ [pandoc]: http://pandoc.org/README.html gitit-0.12.2.1/data/markupHelp/LaTeX+LHS0000644000000000000000000000171012765540066015616 0ustar0000000000000000~~~~~~~~ \section{Section heading} \subsection{Subsection} Formatting: \emph{italics}, \textbf{bold}, super\textsuperscript{script}, sub\textsubscr{script}, \sout{strikeout}. A line break\\ can be forced with \\ at the end of the line. \begin{quote} Indented quotation \end{quote} Links: \href{http://foo.bar}{external}, \href{}{Wiki Link}, \includegraphics{/img/banner.png}, \href{#subsection}{to heading}. \begin{verbatim} #include \end{verbatim} Haskell code: \begin{code} fibs = 1 : 1 : zipWith (+) fibs (tail fibs) \end{code} \begin{itemize} \item bulleted \item list \end{itemize} \begin{enumerate} \item ordered \item list \begin{enumerate}[a.] \item sublist \item another \end{enumerate} \item item three \end{enumerate} \begin{description} \item[term] definition \item[orange] orange fruit \end{description} ~~~~~~~~ For more: [LaTeX], [pandoc]. [LaTeX]: http://www.latex-project.org/ [pandoc]: http://pandoc.org/README.html gitit-0.12.2.1/data/markupHelp/HTML0000644000000000000000000000141012765540066014760 0ustar0000000000000000~~~~~~~~

    Section heading

    Subsection

    Formatting: italics, bold, superscript, subscript, line
    break.

    Indented quotation

    Links: external, Wiki Link, image,

    Indented code block:

    
    #include <stdbool.h>
    
    • bulleted
    • list

    1. ordered
    2. list
      1. sublist
      2. another
    3. item three
    term
    definition
    orange
    orange fruit
    ~~~~~~~~ For more: [xhtml tutorial](http://www.w3schools.com/Xhtml/), [pandoc](http://pandoc.org/README.html). gitit-0.12.2.1/data/markupHelp/Org0000644000000000000000000000146112765540066014751 0ustar0000000000000000 * Section heading ** Subsection Formatting: /italics/, *bold*, super^{script}, sub_{script}, +strikeout+. A line break\\ can be forced with two backslashes at the end of the line. #+BEGIN_QUOTE Indented quotation #+END_QUOTE Links: [[http://google.com][external]], [[][Wiki Link]], [[/img/logo.png]], [[#section-heading][to heading]]. Indented code block: #+BEGIN_EXAMPLE #include #+END_EXAMPLE Or #+BEGIN_SRC haskell let a = 1:a in head a #+END_SRC - bulleted - list -------------- 1. ordered 2. list 1. sublist (indent 4 spaces) 2. another 3. item three - term :: definition - orange :: orange fruit For more: [org-mode manual](http://orgmode.org/manual/) gitit-0.12.2.1/plugins/CapitalizeEmphasis.hs0000644000000000000000000000107512765540066017053 0ustar0000000000000000module CapitalizeEmphasis (plugin) where -- This plugin converts emphasized text to ALL CAPS. -- Not a very useful feature, but useful as an example -- of how to write a plugin. import Network.Gitit.Interface import Data.Char (toUpper) plugin :: Plugin plugin = mkPageTransform capsTransform capsTransform :: [Inline] -> [Inline] capsTransform (Emph x : xs) = processWith capStr x ++ capsTransform xs capsTransform (x:xs) = x : capsTransform xs capsTransform [] = [] capStr :: Inline -> Inline capStr (Str x) = Str (map toUpper x) capStr x = x gitit-0.12.2.1/plugins/PigLatin.hs0000644000000000000000000000174712765540066015011 0ustar0000000000000000module PigLatin (plugin) where -- This plugin converts a page to pig latin if the 'language' metadata -- field is set to 'pig latin'. This demonstrates how to get access to -- metadata in a plugin. import Network.Gitit.Interface import Data.Char (toLower, toUpper, isLower, isUpper, isLetter) plugin :: Plugin plugin = PageTransform $ \doc -> do meta <- askMeta case lookup "language" meta of Just s | map toLower s == "pig latin" -> return $ processWith pigLatinStr doc _ -> return doc pigLatinStr :: Inline -> Inline pigLatinStr (Str "") = Str "" pigLatinStr (Str (c:cs)) | isLower c && isConsonant c = Str (cs ++ (c : "ay")) pigLatinStr (Str (c:cs)) | isUpper c && isConsonant c = Str (capitalize cs ++ (toLower c : "ay")) pigLatinStr (Str x@(c:_)) | isLetter c = Str (x ++ "yay") pigLatinStr x = x isConsonant :: Char -> Bool isConsonant c = c `notElem` "aeiouAEIOU" capitalize :: String -> String capitalize "" = "" capitalize (c:cs) = toUpper c : cs gitit-0.12.2.1/plugins/Dot.hs0000644000000000000000000000315313050577750014017 0ustar0000000000000000module Dot (plugin) where -- This plugin allows you to include a graphviz dot diagram -- in a page like this: -- -- ~~~ {.dot name="diagram1"} -- digraph G {Hello->World} -- ~~~ -- -- The "dot" executable must be in the path. -- The generated png file will be saved in the static img directory. -- If no name is specified, a unique name will be generated from a hash -- of the file contents. import Network.Gitit.Interface import System.Process (readProcessWithExitCode) import System.Exit (ExitCode(ExitSuccess)) -- from the utf8-string package on HackageDB: import Data.ByteString.Lazy.UTF8 (fromString) -- from the SHA package on HackageDB: import Data.Digest.Pure.SHA (sha1, showDigest) import System.FilePath (()) plugin :: Plugin plugin = mkPageTransformM transformBlock transformBlock :: Block -> PluginM Block transformBlock (CodeBlock (_, classes, namevals) contents) | "dot" `elem` classes = do cfg <- askConfig let (name, outfile) = case lookup "name" namevals of Just fn -> ([Str fn], fn ++ ".png") Nothing -> ([], uniqueName contents ++ ".png") liftIO $ do (ec, _out, err) <- readProcessWithExitCode "dot" ["-Tpng", "-o", staticDir cfg "img" outfile] contents let attr = ("image", [], []) if ec == ExitSuccess then return $ Para [Image attr name ("/img" outfile, "")] else error $ "dot returned an error status: " ++ err transformBlock x = return x -- | Generate a unique filename given the file's contents. uniqueName :: String -> String uniqueName = showDigest . sha1 . fromString gitit-0.12.2.1/plugins/ImgTex.hs0000644000000000000000000000405412765540066014471 0ustar0000000000000000module ImgTex (plugin) where {- This plugin provides a clear math LaTeX output. (* latex and dvipng executable must be in the path.) like this: ~~~ {.dvipng} \nabla \times \bm{V} = \frac{1}{h_1 h_2 h_3} \begin{vmatrix} h_1 e_1 & h_2 e_2 & h_3 e_3 \\ \frac{\partial}{\partial q_{1}} & \frac{\partial}{\partial q_{2}} & \frac{\partial}{\partial q_{3}} \\ h_1 V_1 & h_2 V_2 & h_3 V_3 \end{vmatrix} ~~~ License: GPL written by Kohei OZAKI modified by John MacFarlane to use withTempDir -} import Network.Gitit.Interface import System.Process (system) import System.Directory import Data.ByteString.Lazy.UTF8 (fromString) import Data.Digest.Pure.SHA import System.FilePath import Control.Monad.Trans (liftIO) plugin :: Plugin plugin = mkPageTransformM transformBlock templateHeader, templateFooter :: String templateHeader = concat [ "\\documentclass[12pt]{article}\n" , "\\usepackage{amsmath,amssymb,bm}\n" , "\\begin{document}\n" , "\\thispagestyle{empty}\n" , "\\[\n"] templateFooter = "\n" ++ "\\]\n" ++ "\\end{document}\n" transformBlock :: Block -> PluginM Block transformBlock (CodeBlock (_, classes, namevals) contents) | "dvipng" `elem` classes = do cfg <- askConfig let (name, outfile) = case lookup "name" namevals of Just fn -> ([Str fn], fn ++ ".png") Nothing -> ([], uniqueName contents ++ ".png") curr <- liftIO getCurrentDirectory liftIO $ withTempDir "gitit-imgtex" $ \tmpdir -> do setCurrentDirectory tmpdir writeFile (outfile ++ ".tex") (templateHeader ++ contents ++ templateFooter) system $ "latex " ++ outfile ++ ".tex > /dev/null" setCurrentDirectory curr system $ "dvipng -T tight -bd 1000 -freetype0 -Q 5 --gamma 1.3 " ++ (tmpdir outfile <.> "dvi") ++ " -o " ++ (staticDir cfg "img" outfile) return $ Para [Image name ("/img" outfile, "")] transformBlock x = return x uniqueName :: String -> String uniqueName = showDigest . sha1 . fromString gitit-0.12.2.1/plugins/Interwiki.hs0000644000000000000000000007366012765540066015252 0ustar0000000000000000{- | This plugin causes link URLs of the form wikiname!articlename to be treated as interwiki links. So, for example, > [The Emperor Palpatine](!Wookieepedia "Emperor Palpatine") links to the article on "Emperor Palpatine" in Wookieepedia (). This module also supports a shorter syntax, for when the link text is identical to the article name. Example: > [Emperor Palpatine](!Wookieepedia) will link to the right place, same as the previous example. (Written by Gwern Branwen; put in public domain, 2009) -} module Interwiki (plugin) where import Network.Gitit.Interface import qualified Data.Map as M (fromList, lookup, Map) import Network.URI (escapeURIString, isAllowedInURI, unEscapeString) plugin :: Plugin plugin = mkPageTransform convertInterwikiLinks {- | A good interwiki link looks like '!Wookieepedia "Emperor Palpatine"'. So we check for a leading '!'. We strip it off, and now we have the canonical sitename (in this case, "Wookieepedia" and we look it up in our database. The database should return the URL for that site; we only need append the (escaped) article name to that, and we have the full URL! If there isn't one there, then we look back at the link-text for the article name; this is how we support the shortened syntax (see module description). If there isn't a leading '!', we get back a Nothing (the database doesn't know the site), we just return the Link unchanged. -} convertInterwikiLinks :: Inline -> Inline convertInterwikiLinks (Link ref (interwiki, article)) = case interwiki of ('!':interwiki') -> case M.lookup interwiki' interwikiMap of Just url -> case article of "" -> Link ref (url ++ inlinesToURL ref, summary $ unEscapeString $ inlinesToURL ref) _ -> Link ref (interwikiurl article url, summary article) Nothing -> Link ref (interwiki, article) where -- 'http://starwars.wikia.com/wiki/Emperor_Palpatine' interwikiurl a u = escapeURIString isAllowedInURI $ u ++ a -- 'Wookieepedia: Emperor Palpatine' summary a = interwiki' ++ ": " ++ a _ -> Link ref (interwiki, article) convertInterwikiLinks x = x -- | Large table of constants; this is a mapping from shortcuts to a URL. The URL can be used by -- appending to it the article name (suitably URL-escaped, of course). interwikiMap :: M.Map String String interwikiMap = M.fromList $ wpInterwikiMap ++ customInterwikiMap wpInterwikiMap, customInterwikiMap :: [(String, String)] customInterwikiMap = [("Hackage", "http://hackage.haskell.org/package/"), ("Hawiki", "http://haskell.org/haskellwiki/"), ("Hayoo", "http://holumbus.fh-wedel.de/hayoo/hayoo.html#0:"), ("Hoogle", "http://www.haskell.org/hoogle/?hoogle=")] -- This mapping is derived from -- as of 6:12 PM, 6 February 2013. wpInterwikiMap = [ ("AbbeNormal", "http://johnabbe.wagn.org/"), ("Acronym", "http://www.acronymfinder.com/af-query.asp?String=exact&Acronym="), ("Advisory", "http://advisory.wikimedia.org/wiki/"), ("Advogato", "http://www.advogato.org/"), ("Aew", "http://wiki.arabeyes.org/"), ("AllWiki", "http://allwiki.com/index.php/"), ("Appropedia", "http://www.appropedia.org/"), ("AquariumWiki", "http://www.theaquariumwiki.com/"), ("AspieNetWiki", "http://aspie.mela.de/index.php/"), ("AtmWiki", "http://www.otterstedt.de/wiki/index.php/"), ("BCNbio", "http://historiapolitica.bcn.cl/resenas_parlamentarias/wiki/"), ("BLW", "http://britainloveswikipedia.org/wiki/"), ("BattlestarWiki", "http://en.battlestarwiki.org/wiki/"), ("BibleWiki", "http://bible.tmtm.com/wiki/"), ("BluWiki", "http://bluwiki.com/go/"), ("Botwiki", "http://botwiki.sno.cc/wiki/"), ("Boxrec", "http://www.boxrec.com/media/index.php?"), ("BrickWiki", "http://lego.wikia.com/index.php?title="), ("Bytesmiths", "http://www.Bytesmiths.com/wiki/"), ("C2", "http://c2.com/cgi/wiki?"), ("C2find", "http://c2.com/cgi/wiki?FindPage&value="), ("CKWiss", "http://ck-wissen.de/ckwiki/index.php?title="), ("Cache", "http://www.google.com/search?q=cache:"), ("CellWiki", "http://cell.wikia.com/wiki/"), ("CentralWikia", "http://community.wikia.com/wiki/"), ("ChEJ", "http://esperanto.blahus.cz/cxej/vikio/index.php/"), ("ChoralWiki", "http://www.cpdl.org/wiki/index.php/"), ("Citizendium", "http://en.citizendium.org/wiki/"), ("Comixpedia", "http://www.comixpedia.org/index.php/"), ("Commons", "http://commons.wikimedia.org/wiki/"), ("CommunityScheme", "http://community.schemewiki.org/?c=s&key="), ("CommunityWiki", "http://www.communitywiki.org/"), ("CorpKnowPedia", "http://corpknowpedia.org/wiki/index.php/"), ("CrazyHacks", "http://www.crazy-hacks.org/wiki/index.php?title="), ("CreativeCommons", "http://www.creativecommons.org/licenses/"), ("CreativeCommonsWiki", "http://wiki.creativecommons.org/"), ("CreaturesWiki", "http://creatures.wikia.com/wiki/"), ("CxEJ", "http://esperanto.blahus.cz/cxej/vikio/index.php/"), ("DCDatabase", "http://dc.wikia.com/"), ("DCMA", "http://www.christian-morgenstern.de/dcma/"), ("DOI", "http://dx.doi.org/"), ("DRAE", "http://lema.rae.es/drae/?val="), ("DWJWiki", "http://www.suberic.net/cgi-bin/dwj/wiki.cgi?"), ("Dcc", "http://www.dccwiki.com/"), ("DejaNews", "http://www.deja.com/=dnc/getdoc.xp?AN="), ("Delicious", "http://www.delicious.com/tag/"), ("Devmo", "https://developer.mozilla.org/en/docs/"), ("Dict", "http://www.dict.org/bin/Dict?Database=*&Form=Dict1&Strategy=*&Query="), ("Dictionary", "http://www.dict.org/bin/Dict?Database=*&Form=Dict1&Strategy=*&Query="), ("Disinfopedia", "http://www.sourcewatch.org/wiki.phtml?title="), ("DocBook", "http://wiki.docbook.org/topic/"), ("Donate", "http://donate.wikimedia.org/wiki/"), ("Dreamhost", "http://wiki.dreamhost.com/index.php/"), ("DrumCorpsWiki", "http://www.drumcorpswiki.com/index.php/"), ("ELibre", "http://enciclopedia.us.es/index.php/"), ("EcoReality", "http://www.EcoReality.org/wiki/"), ("EcxeI", "http://www.ikso.net/cgi-bin/wiki.pl?"), ("EmacsWiki", "http://www.emacswiki.org/cgi-bin/wiki.pl?"), ("Encyc", "http://encyc.org/wiki/"), ("EnergieWiki", "http://www.netzwerk-energieberater.de/wiki/index.php/"), ("EoKulturCentro", "http://esperanto.toulouse.free.fr/nova/wikini/wakka.php?wiki="), ("Etherpad", "http://etherpad.wikimedia.org/"), ("Ethnologue", "http://www.ethnologue.com/show_language.asp?code="), ("EthnologueFamily", "http://www.ethnologue.com/show_family.asp?subid="), ("EvoWiki", "http://wiki.cotch.net/index.php/"), ("Exotica", "http://www.exotica.org.uk/wiki/"), ("EĉeI", "http://www.ikso.net/cgi-bin/wiki.pl?"), ("FanimutationWiki", "http://wiki.animutationportal.com/index.php/"), ("FinalEmpire", "http://final-empire.sourceforge.net/cgi-bin/wiki.pl?"), ("FinalFantasy", "http://finalfantasy.wikia.com/wiki/"), ("Finnix", "http://www.finnix.org/"), ("FlickrPhoto", "http://www.flickr.com/photo.gne?id="), ("FlickrUser", "http://www.flickr.com/people/"), ("FloralWIKI", "http://www.floralwiki.co.uk/wiki/"), ("FlyerWiki-de", "http://de.flyerwiki.net/index.php/"), ("Foldoc", "http://foldoc.org/"), ("ForthFreak", "http://wiki.forthfreak.net/index.cgi?"), ("Foundation", "http://wikimediafoundation.org/wiki/"), ("FoxWiki", "http://fox.wikis.com/wc.dll?Wiki~"), ("FreeBSDman", "http://www.FreeBSD.org/cgi/man.cgi?apropos=1&query="), ("FreeBio", "http://freebiology.org/wiki/"), ("FreeCultureWiki", "http://wiki.freeculture.org/index.php/"), ("FreeFeel", "http://freefeel.org/wiki/"), ("Freedomdefined", "http://freedomdefined.org/"), ("FreekiWiki", "http://wiki.freegeek.org/index.php/"), ("Freenode", "http://ganfyd.org/index.php?title="), ("Gardenology", "http://www.gardenology.org/wiki/"), ("GaussWiki", "http://gauss.ffii.org/"), ("GenWiki", "http://wiki.genealogy.net/index.php/"), ("Gentoo-Wiki", "http://gentoo-wiki.com/"), ("Gerrit", "https://gerrit.wikimedia.org/r/"), ("Git", "https://gerrit.wikimedia.org/r/gitweb?p=mediawiki/a=log;h=refs/heads/master;"), ("GlobalVoices", "http://cyber.law.harvard.edu/dyn/globalvoices/wiki/"), ("GlossarWiki", "http://glossar.hs-augsburg.de/"), ("GlossaryWiki", "http://glossary.hs-augsburg.de/"), ("Google", "http://www.google.com/search?q="), ("GoogleDefine", "http://www.google.com/search?q=define:"), ("GoogleGroups", "http://groups.google.com/groups?q="), ("GotAMac", "http://www.got-a-mac.org/"), ("GreatLakesWiki", "http://greatlakeswiki.org/index.php/"), ("GuildWarsWiki", "http://www.wiki.guildwars.com/wiki/"), ("Guildwiki", "http://guildwars.wikia.com/wiki/"), ("H2Wiki", "http://halowiki.net/p/"), ("HRFWiki", "http://fanstuff.hrwiki.org/index.php/"), ("HRWiki", "http://www.hrwiki.org/index.php/"), ("HammondWiki", "http://www.dairiki.org/HammondWiki/index.php3?"), ("HupWiki", "http://wiki.hup.hu/index.php/"), ("IMDbCharacter", "http://www.imdb.com/character/ch/"), ("IMDbCompany", "http://www.imdb.com/company/co/"), ("IMDbName", "http://www.imdb.com/name/nm/"), ("IMDbTitle", "http://www.imdb.com/title/tt/"), ("IRC", "http://www.sil.org/iso639-3/documentation.asp?id="), ("ISSN", "http://www.worldcat.org/issn/"), ("Incubator", "http://incubator.wikimedia.org/wiki/"), ("Infosecpedia", "http://infosecpedia.org/wiki/"), ("Infosphere", "http://theinfosphere.org/"), ("Iuridictum", "http://iuridictum.pecina.cz/w/"), ("JEFO", "http://esperanto-jeunes.org/wiki/"), ("JSTOR", "http://www.jstor.org/journals/"), ("JamesHoward", "http://jameshoward.us/"), ("JavaNet", "http://wiki.java.net/bin/view/Main/"), ("Javapedia", "http://wiki.java.net/bin/view/Javapedia/"), ("JiniWiki", "http://www.cdegroot.com/cgi-bin/jini?"), ("Jira", "https://jira.toolserver.org/browse/"), ("JspWiki", "http://www.ecyrd.com/JSPWiki/Wiki.jsp?page="), ("Kamelo", "http://kamelopedia.mormo.org/index.php/"), ("Karlsruhe", "http://ka.stadtwiki.net/"), ("KerimWiki", "http://wiki.oxus.net/"), ("KinoWiki", "http://kino.skripov.com/index.php/"), ("KmWiki", "http://kmwiki.wikispaces.com/"), ("KontuWiki", "http://kontu.merri.net/wiki/"), ("KoslarWiki", "http://wiki.koslar.de/index.php/"), ("Kpopwiki", "http://www.kpopwiki.com/"), ("LISWiki", "http://liswiki.org/wiki/"), ("LQWiki", "http://wiki.linuxquestions.org/wiki/"), ("LinguistList", "http://linguistlist.org/forms/langs/LLDescription.cfm?code="), ("LinuxWiki", "http://www.linuxwiki.de/"), ("LinuxWikiDe", "http://www.linuxwiki.de/"), ("LiteratePrograms", "http://en.literateprograms.org/"), ("Livepedia", "http://www.livepedia.gr/index.php?title="), ("Lojban", "http://www.lojban.org/tiki/tiki-index.php?page="), ("Lostpedia", "http://lostpedia.wikia.com/wiki/"), ("LugKR", "http://lug-kr.sourceforge.net/cgi-bin/lugwiki.pl?"), ("Luxo", "http://toolserver.org/~luxo/contributions/contributions.php?user="), ("MW", "http://www.mediawiki.org/wiki/"), ("MWOD", "http://www.merriam-webster.com/cgi-bin/dictionary?book=Dictionary&va="), ("MWOT", "http://www.merriam-webster.com/cgi-bin/thesaurus?book=Thesaurus&va="), ("Mail", "https://lists.wikimedia.org/mailman/listinfo/"), ("Mariowiki", "http://www.mariowiki.com/"), ("MarvelDatabase", "http://www.marveldatabase.com/wiki/index.php/"), ("MeatBall", "http://meatballwiki.org/wiki/"), ("MediaWikiWiki", "http://www.mediawiki.org/wiki/"), ("MediaZilla", "https://bugzilla.wikimedia.org/"), ("MemoryAlpha", "http://memory-alpha.org/wiki/"), ("MetaWiki", "http://sunir.org/apps/meta.pl?"), ("MetaWikiPedia", "http://meta.wikimedia.org/wiki/"), ("Mineralienatlas", "http://www.mineralienatlas.de/lexikon/index.php/"), ("MoinMoin", "http://moinmo.in/"), ("Monstropedia", "http://www.monstropedia.org/?title="), ("MosaPedia", "http://mosapedia.de/wiki/index.php/"), ("MozCom", "http://mozilla.wikia.com/wiki/"), ("MozillaWiki", "https://wiki.mozilla.org/"), ("MozillaZineKB", "http://kb.mozillazine.org/"), ("MusicBrainz", "http://musicbrainz.org/doc/"), ("NARA", "http://research.archives.gov/description/"), ("NKcells", "http://www.nkcells.info/wiki/index.php/"), ("NoSmoke", "http://no-smok.net/nsmk/"), ("Nost", "http://nostalgia.wikipedia.org/wiki/"), ("OEIS", "http://oeis.org/"), ("OLPC", "http://wiki.laptop.org/go/"), ("OSI", "http://wiki.tigma.ee/index.php/"), ("OSMwiki", "http://wiki.openstreetmap.org/wiki/"), ("OTRS", "https://ticket.wikimedia.org/otrs/index.pl?Action=AgentTicketZoom&TicketID="), ("OTRSwiki", "http://otrs-wiki.wikimedia.org/wiki/"), ("OldWikisource", "http://wikisource.org/wiki/"), ("OneLook", "http://www.onelook.com/?ls=b&w="), ("OpenFacts", "http://openfacts.berlios.de/index-en.phtml?title="), ("OpenWetWare", "http://openwetware.org/wiki/"), ("OpenWiki", "http://openwiki.com/?"), ("Openlibrary", "http://openlibrary.org/"), ("Openstreetmap", "http://wiki.openstreetmap.org/wiki/"), ("Opera7Wiki", "http://operawiki.info/"), ("OrganicDesign", "http://www.organicdesign.co.nz/"), ("OrthodoxWiki", "http://orthodoxwiki.org/"), ("OurMedia", "https://www.socialtext.net/ourmedia/index.cgi?"), ("Outreach", "http://outreach.wikimedia.org/wiki/"), ("OutreachWiki", "http://outreach.wikimedia.org/wiki/"), ("PHWiki", "http://wiki.pocketheaven.com/"), ("PMEG", "http://www.bertilow.com/pmeg/"), ("Panawiki", "http://wiki.alairelibre.net/index.php?title="), ("PatWIKI", "http://gauss.ffii.org/"), ("PerlNet", "http://perl.net.au/wiki/"), ("PersonalTelco", "http://www.personaltelco.net/"), ("PhpWiki", "http://phpwiki.sourceforge.net/phpwiki/index.php?"), ("PlanetMath", "http://planetmath.org/?op=getobj&from=objects&id="), ("PyWiki", "http://c2.com/cgi/wiki?"), ("PythonInfo", "http://www.python.org/cgi-bin/moinmoin/"), ("PythonWiki", "http://www.pythonwiki.de/"), ("Quality", "http://quality.wikimedia.org/wiki/"), ("RFC", "http://tools.ietf.org/html/rfc"), ("ReVo", "http://purl.org/NET/voko/revo/art/.html"), ("ReutersWiki", "http://glossary.reuters.com/index.php/"), ("RheinNeckar", "http://rhein-neckar-wiki.de/"), ("RoWiki", "http://wiki.rennkuckuck.de/index.php/"), ("RoboWiki", "http://robowiki.net/?"), ("SLWiki", "http://wiki.secondlife.com/wiki/"), ("SMikipedia", "http://www.smiki.de/"), ("SVGWiki", "http://wiki.svg.org/index.php/"), ("Scholar", "http://scholar.google.com/scholar?q="), ("SchoolsWP", "http://schools-wikipedia.org/wiki/"), ("Scores", "http://imslp.org/wiki/"), ("Scoutwiki", "http://en.scoutwiki.org/"), ("Scramble", "http://www.scramble.nl/wiki/index.php?title="), ("SeaPig", "http://www.seapig.org/"), ("SeattleWiki", "http://seattlewiki.org/wiki/"), ("SeattleWireless", "http://seattlewireless.net/?"), ("SenseisLibrary", "http://senseis.xmp.net/?"), ("Slashdot", "http://slashdot.org/article.pl?sid="), ("SourceForge", "http://sourceforge.net/"), ("Species", "http://species.wikimedia.org/wiki/"), ("Squeak", "http://wiki.squeak.org/squeak/"), ("Stewardry", "http://toolserver.org/~pathoschild/stewardry/?wiki="), ("Strategy", "http://strategy.wikimedia.org/wiki/"), ("StrategyWiki", "http://strategywiki.org/wiki/"), ("Sulutil", "http://toolserver.org/~quentinv57/sulinfo/"), ("SwinBrain", "http://mercury.it.swin.edu.au/swinbrain/index.php/"), ("SwingWiki", "http://www.swingwiki.org/"), ("Swtrain", "http://train.spottingworld.com/"), ("TESOLTaiwan", "http://www.tesol-taiwan.org/wiki/index.php/"), ("TMBW", "http://tmbw.net/wiki/"), ("TMwiki", "http://www.EasyTopicMaps.com/?page="), ("TVIV", "http://tviv.org/wiki/"), ("TVtropes", "http://www.tvtropes.org/pmwiki/pmwiki.php/Main/"), ("TWiki", "http://twiki.org/cgi-bin/view/"), ("TabWiki", "http://www.tabwiki.com/index.php/"), ("Tavi", "http://tavi.sourceforge.net/"), ("TclersWiki", "http://wiki.tcl.tk/"), ("Technorati", "http://www.technorati.com/search/"), ("Tenwiki", "http://ten.wikipedia.org/wiki/"), ("Test2wiki", "//test2.wikipedia.org/wiki/"), ("Testwiki", "http://test.wikipedia.org/wiki/"), ("Thelemapedia", "http://www.thelemapedia.org/index.php/"), ("Theopedia", "http://www.theopedia.com/"), ("ThinkWiki", "http://www.thinkwiki.org/wiki/"), ("TibiaWiki", "http://tibia.erig.net/"), ("Ticket", "https://ticket.wikimedia.org/otrs/index.pl?Action=AgentTicketZoom&TicketNumber="), ("TmNet", "http://www.technomanifestos.net/?"), ("Tools", "http://toolserver.org/"), ("Turismo", "http://www.tejo.org/turismo/"), ("TyvaWiki", "http://www.tyvawiki.org/wiki/"), ("USEJ", "http://www.tejo.org/usej/"), ("Uncyclopedia", "http://uncyclopedia.org/wiki/"), ("Unreal", "http://wiki.beyondunreal.com/wiki/"), ("Urbandict", "http://www.urbandictionary.com/define.php?term="), ("UseMod", "http://www.usemod.com/cgi-bin/wiki.pl?"), ("VIAF", "http://viaf.org/viaf/"), ("VKoL", "http://kol.coldfront.net/thekolwiki/index.php/"), ("VLOS", "http://www.thuvienkhoahoc.com/tusach/"), ("Vinismo", "http://vinismo.com/en/"), ("VoIPinfo", "http://www.voip-info.org/wiki/view/"), ("WLUG", "http://www.wlug.org.nz/"), ("WMDEblog", "//blog.wikimedia.de/"), ("WMF", "http://wikimediafoundation.org/wiki/"), ("WMFblog", "http://blog.wikimedia.org/"), ("Webisodes", "http://www.webisodes.org/"), ("Wiki", "http://c2.com/cgi/wiki?"), ("WikiChristian", "http://www.wikichristian.org/index.php?title="), ("WikiF1", "http://www.wikif1.org/"), ("WikiFur", "http://en.wikifur.com/wiki/"), ("WikiIndex", "http://wikiindex.org/"), ("WikiLemon", "http://wiki.illemonati.com/"), ("WikiMac-de", "http://apfelwiki.de/wiki/Main/"), ("WikiSkripta", "http://www.wikiskripta.eu/index.php/"), ("WikiTI", "http://wikiti.denglend.net/index.php?title="), ("WikiTravel", "http://wikitravel.org/en/"), ("WikiTree", "http://wikitree.org/index.php?title="), ("WikiWeet", "http://wikiweet.nl/wiki/"), ("WikiWikiWeb", "http://c2.com/cgi/wiki?"), ("Wikia", "http://www.wikia.com/wiki/c:"), ("WikiaSite", "http://www.wikia.com/wiki/c:"), ("Wikibooks", "http://en.wikibooks.org/wiki/"), ("Wikichat", "http://www.wikichat.org/"), ("Wikicities", "http://www.wikia.com/wiki/"), ("Wikicity", "http://www.wikia.com/wiki/c:"), ("Wikidata", "//wikidata.org/wiki/"), ("Wikilivres", "http://wikilivres.ca/wiki/"), ("Wikimedia", "http://wikimediafoundation.org/wiki/"), ("Wikinews", "http://en.wikinews.org/wiki/"), ("Wikinfo", "http://www.wikinfo.org/index.php/"), ("Wikinvest", "http://www.wikinvest.com/"), ("Wikipaltz", "http://www.wikipaltz.com/wiki/"), ("Wikipedia", "http://en.wikipedia.org/wiki/"), ("WikipediaWikipedia", "http://en.wikipedia.org/wiki/Wikipedia:"), ("Wikiquote", "http://en.wikiquote.org/wiki/"), ("Wikischool", "http://www.wikischool.de/wiki/"), ("Wikisource", "http://en.wikisource.org/wiki/"), ("Wikispecies", "http://species.wikimedia.org/wiki/"), ("Wikispot", "http://wikispot.org/?action=gotowikipage&v="), ("Wikitech", "http://wikitech.wikimedia.org/view/"), ("Wikiversity", "http://en.wikiversity.org/wiki/"), ("Wikivoyage", "//en.wikivoyage.org/wiki/"), ("Wiktionary", "http://en.wiktionary.org/wiki/"), ("Wipipedia", "http://www.londonfetishscene.com/wipi/index.php/"), ("Wm2005", "http://wikimania2005.wikimedia.org/wiki/"), ("Wm2006", "http://wikimania2006.wikimedia.org/wiki/"), ("Wm2007", "http://wikimania2007.wikimedia.org/wiki/"), ("Wm2008", "http://wikimania2008.wikimedia.org/wiki/"), ("Wm2009", "http://wikimania2009.wikimedia.org/wiki/"), ("Wm2010", "http://wikimania2010.wikimedia.org/wiki/"), ("Wm2011", "http://wikimania2011.wikimedia.org/wiki/"), ("Wm2011", "http://wikimania2011.wikimedia.org/wiki/"), ("Wm2013", "//wikimania2013.wikimedia.org/wiki/"), ("Wmania", "http://wikimania.wikimedia.org/wiki/"), ("Wmteam", "http://wikimaniateam.wikimedia.org/wiki/"), ("WoWWiki", "http://www.wowwiki.com/"), ("Wookieepedia", "http://starwars.wikia.com/wiki/"), ("Wqy", "http://wqy.sourceforge.net/cgi-bin/index.cgi?"), ("WurmPedia", "http://www.wurmonline.com/wiki/index.php/"), ("ZRHwiki", "http://www.zrhwiki.ch/wiki/"), ("ZUM", "http://wiki.zum.de/"), ("ZWiki", "http://www.zwiki.org/"), ("arXiv", "http://arxiv.org/abs/"), ("betawiki", "http://translatewiki.net/wiki/"), ("betawikiversity", "http://beta.wikiversity.org/wiki/"), ("bugzilla", "https://bugzilla.wikimedia.org/show_bug.cgi?id="), ("bulba", "http://bulbapedia.bulbagarden.net/wiki/"), ("buzztard", "http://buzztard.org/index.php/"), ("comune", "http://rete.comuni-italiani.it/wiki/"), ("dbdump", "http://download.wikimedia.org//latest/"), ("distributedproofreaders", "http://www.pgdp.net/wiki/"), ("distributedproofreadersca", "http://www.pgdpcanada.net/wiki/index.php/"), ("dmoz", "http://www.dmoz.org/"), ("dmozs", "http://www.dmoz.org/cgi-bin/search?search="), ("doom_wiki", "http://doom.wikia.com/wiki/"), ("download", "http://download.wikimedia.org/"), ("gutenberg", "http://www.gutenberg.org/etext/"), ("gutenbergwiki", "http://www.gutenberg.org/wiki/"), ("heroeswiki", "http://heroeswiki.com/"), ("infoAnarchy", "http://www.infoanarchy.org/en/"), ("labsconsole", "https://labsconsole.wikimedia.org/wiki/"), ("lyricwiki", "http://lyrics.wikia.com/"), ("mailarchive", "http://lists.wikimedia.org/pipermail/"), ("nostalgia", "http://nostalgia.wikipedia.org/wiki/"), ("psycle", "http://psycle.sourceforge.net/wiki/"), ("pyrev", "http://www.mediawiki.org/wiki/Special:Code/pywikipedia/"), ("qcwiki", "http://wiki.quantumchemistry.net/index.php/"), ("rev", "http://www.mediawiki.org/wiki/Special:Code/MediaWiki/"), ("rtfm", "http://s23.org/wiki/"), ("securewikidc", "https://secure.wikidc.org/"), ("semantic-mw", "http://www.semantic-mediawiki.org/wiki/"), ("silcode", "http://www.sil.org/iso639-3/documentation.asp?id="), ("spcom", "http://spcom.wikimedia.org/wiki/"), ("stats", "http://stats.wikimedia.org/"), ("svn", "http://svn.wikimedia.org/viewvc/mediawiki/?view=log"), ("translatewiki", "http://translatewiki.net/wiki/"), ("tswiki", "http://wiki.toolserver.org/view/"), ("usability", "http://usability.wikimedia.org/wiki/"), ("wg", "http://wg.en.wikipedia.org/wiki/"), ("wikiHow", "http://www.wikihow.com/"), ("wikisophia", "http://wikisophia.org/index.php?title="), ("wmar", "http://www.wikimedia.org.ar/wiki/"), ("wmau", "http://wikimedia.org.au/wiki/"), ("wmbd", "//bd.wikimedia.org/wiki/"), ("wmbe", "http://be.wikimedia.org/wiki/"), ("wmbr", "http://br.wikimedia.org/wiki/"), ("wmca", "http://wikimedia.ca/wiki/"), ("wmch", "http://www.wikimedia.ch/"), ("wmcl", "http://www.wikimediachile.cl/index.php?title="), ("wmco", "//co.wikimedia.org/wiki/"), ("wmcz", "http://meta.wikimedia.org/wiki/Wikimedia_Czech_Republic/"), ("wmdc", "http://wikimediadc.org/wiki/"), ("wmde", "http://wikimedia.de/wiki/"), ("wmdk", "//dk.wikimedia.org/wiki/"), ("wmee", "//et.wikimedia.org/wiki/"), ("wmet", "//et.wikimedia.org/wiki/"), ("wmfi", "http://fi.wikimedia.org/wiki/"), ("wmfr", "http://wikimedia.fr/"), ("wmhk", "http://wikimedia.hk/index.php/"), ("wmhu", "http://wiki.media.hu/wiki/"), ("wmid", "http://www.wikimedia.or.id/wiki/"), ("wmil", "http://www.wikimedia.org.il/"), ("wmin", "http://wiki.wikimedia.in/"), ("wmit", "http://wiki.wikimedia.it/wiki/"), ("wmke", "http://wikimedia.or.ke/"), ("wmmk", "//mk.wikimedia.org/wiki/"), ("wmmx", "http://mx.wikimedia.org/wiki/"), ("wmnl", "http://nl.wikimedia.org/wiki/"), ("wmno", "http://no.wikimedia.org/wiki/"), ("wmnyc", "http://nyc.wikimedia.org/wiki/"), ("wmpa-us", "http://pa.us.wikimedia.org/wiki/"), ("wmph", "http://www.wikimedia.ph/wmph/index.php?title="), ("wmpl", "http://pl.wikimedia.org/wiki/"), ("wmpt", "http://wikimedia.pt/"), ("wmrs", "http://rs.wikimedia.org/wiki/"), ("wmru", "http://ru.wikimedia.org/wiki/"), ("wmse", "http://se.wikimedia.org/wiki/"), ("wmtr", "//tr.wikimedia.org/wiki/"), ("wmtw", "http://wikimedia.tw/wiki/index.php5/"), ("wmua", "//ua.wikimedia.org/wiki/"), ("wmuk", "http://uk.wikimedia.org/wiki/"), ("wmve", "http://wikimedia.org.ve/index.php/"), ("wmza", "http://wikimedia.org.za/wiki/"), ("ĈEJ", "http://esperanto.blahus.cz/cxej/vikio/index.php/"), ("ZZZ", "http://wiki.zzz.ee/index.php/") ] gitit-0.12.2.1/plugins/Deprofanizer.hs0000644000000000000000000000072112765540066015721 0ustar0000000000000000module Deprofanizer (plugin) where -- This plugin replaces profane words with "XXXXX". import Network.Gitit.Interface import Data.Char (toLower) plugin :: Plugin plugin = mkPageTransform deprofanize deprofanize :: Inline -> Inline deprofanize (Str x) | isBadWord x = Str "XXXXX" deprofanize x = x isBadWord :: String -> Bool isBadWord x = map toLower x `elem` ["darn", "blasted", "stinker"] -- there are more, but this is a family program gitit-0.12.2.1/plugins/WebArchiver.hs0000644000000000000000000000375512765540066015504 0ustar0000000000000000{-| Scans page of Markdown looking for http links. When it finds them, it submits them to webcitation.org / https://secure.wikimedia.org/wikipedia/en/wiki/WebCite (It will also submit them to Alexa (the source for the Internet Archive), but Alexa says that its bots take weeks to visit and may not ever.) This module employs the archiver daemon as a library; `cabal install archiver` will install it. Limitations: * Only parses Markdown, not ReST or any other format; this is because 'readMarkdown' is hardwired into it. * No rate limitation or choking; will fire off all requests as fast as possible. If pages have more than 20 external links or so, this may result in your IP being temporarily banned by WebCite. To avoid this, you can use WebArchiverBot.hs instead, which will parse & dump URLs into a file processed by the archiver daemon (which *is* rate-limited). By: Gwern Branwen; placed in the public domain -} module WebArchiver (plugin) where import Control.Concurrent (forkIO) import Network.URL.Archiver as A (checkArchive) import Network.Gitit.Interface (askUser, bottomUpM, liftIO, uEmail, Plugin(PreCommitTransform), Inline(Link)) import Text.Pandoc (defaultParserState, readMarkdown) plugin :: Plugin plugin = PreCommitTransform archivePage -- archivePage :: String -> ReaderT PluginData (StateT Context IO) String archivePage x = do mbUser <- askUser let email = case mbUser of Nothing -> "nobody@mailinator.com" Just u -> uEmail u let p = readMarkdown defaultParserState x -- force evaluation and archiving side-effects _p' <- liftIO $ bottomUpM (archiveLinks email) p return x -- note: this is read-only - don't actually change page! archiveLinks :: String -> Inline -> IO Inline archiveLinks e x@(Link _ (uln, _)) = forkIO (A.checkArchive e uln) >> return x archiveLinks _ x = return x gitit-0.12.2.1/plugins/ShowUser.hs0000644000000000000000000000104212765540066015045 0ustar0000000000000000module ShowUser (plugin) where -- This plugin replaces $USER$ with the name of the currently logged in -- user, or the empty string if no one is logged in. import Network.Gitit.Interface plugin :: Plugin plugin = mkPageTransformM showuser showuser :: Inline -> PluginM Inline showuser (Math InlineMath x) | x == "USER" = do doNotCache -- tell gitit not to cache this page, as it has dynamic content mbUser <- askUser case mbUser of Nothing -> return $ Str "" Just u -> return $ Str $ uUsername u showuser x = return x gitit-0.12.2.1/plugins/Signature.hs0000644000000000000000000000135112765540066015232 0ustar0000000000000000module Signature (plugin) where -- This plugin replaces $SIG$ with the username and timestamp -- of the last edit, prior to saving the page in the repository. import Network.Gitit.Interface import Data.DateTime (getCurrentTime, formatDateTime) plugin :: Plugin plugin = PreCommitTransform replacedate replacedate :: String -> PluginM String replacedate [] = return "" replacedate ('$':'S':'I':'G':'$':xs) = do datetime <- liftIO getCurrentTime mbuser <- askUser let username = case mbuser of Nothing -> "???" Just u -> uUsername u let sig = concat ["-- ", username, " (", formatDateTime "%c" datetime, ")"] fmap (sig ++ ) $ replacedate xs replacedate (x:xs) = fmap (x : ) $ replacedate xs gitit-0.12.2.1/plugins/Subst.hs0000644000000000000000000000350213050577750014367 0ustar0000000000000000{-# LANGUAGE PackageImports #-} -- Usage: a paragraph containing just [My page](!subst) -- will be replaced by the contents of My page. -- -- Limitations: it is assumed that My page is -- formatted with markdown, and contains no metadata. module Subst (plugin) where --import "MonadCatchIO-mtl" Control.Monad.CatchIO (try) import Control.Monad.Catch (try) import Data.FileStore (FileStoreError, retrieve) import Text.Pandoc (def, readMarkdown) import Network.Gitit.ContentTransformer (inlinesToString) import Network.Gitit.Interface import Network.Gitit.Framework (filestoreFromConfig) plugin :: Plugin plugin = mkPageTransformM substituteIntoBlock substituteIntoBlock :: [Block] -> PluginM [Block] substituteIntoBlock ((Para [Link attr ref ("!subst", _)]):xs) = do let target = inlinesToString ref cfg <- askConfig let fs = filestoreFromConfig cfg article <- try $ liftIO (retrieve fs (target ++ ".page") Nothing) case article :: Either FileStoreError String of Left _ -> let txt = Str ("[" ++ target ++ "](!subst)") alt = "'" ++ target ++ "' doesn't exist. Click here to create it." lnk = Para [Link attr [txt] (target,alt)] in (lnk :) `fmap` substituteIntoBlock xs -- Right a -> let (Pandoc _ content) = readMarkdown def a -- in (content ++) `fmap` substituteIntoBlock xs Right a -> case readMarkdown def a of Left err -> let content = [Para $ [Str "Error parsing markdown in subst?"]] in (content ++) `fmap` substituteIntoBlock xs Right (Pandoc _ content) -> (content ++) `fmap` substituteIntoBlock xs substituteIntoBlock (x:xs) = (x:) `fmap` substituteIntoBlock xs substituteIntoBlock [] = return [] gitit-0.12.2.1/CHANGES0000644000000000000000000011471313050604177012246 0ustar0000000000000000Version 0.12.2.1 released 14 Feb 2017 * Bump version bounds for time, pandoc, blaze-html, aeson. * Added MTable plugin (Simon Heath). Adds simple but easy-to-use variable-width table syntax. * Fixed Subst plugin (Simon Heath, #548). * Fixed Dot plugin (Simon Heath, #568). Version 0.12.2 released 09 Nov 2016 * Allow pandoc 1.18, tagsoup 0.14, aeson, 1.x. Version 0.12.1.1 released 22 Mar 2016 * Allow pandoc 1.17 (Phil Ruffwind). * Allow aeson 0.11. Version 0.12.1 released 17 Feb 2016 * Use fmap instead of <$> so ghc 7.8 won't fail. * Allow latest hoauth2 * Fix typo (Chas Leichner). * Allow compiling with pandoc 1.16.x. * Add page for login failure when authorization is required for reading (Phil Ruffwind). When authorization is required to read the wiki, the error message from a failed GitHub login cannot be displayed. Instead it will redirect to GitHub for another OAuth authentication, which can lead to a redirect loop. To avoid this, the user is now redirected to a special landing page to display the login failure. Note: no changes are made for the case where authorization is not required to read the wiki. * Improve error message of GitHub membership check (Phil Ruffwind). * Add delete-summary config variable (Phil Ruffwind). Used to change the commit message when a page is deleted. * Use primary GitHub email rather than just the first (Phil Ruffwind). The order in which user emails are returned via the GitHub API is not specified, so the first may not be the one that the user prefers, i.e. the so-called "primary" email. To fix this problem, we eliminate all emails except for the one marked as "primary". * Make default theme responsive (Lincoln Mullen, #450). This commit makes the default theme responsive. For smaller browsers, it will move the sidebar below the main content div and make the sidebar three columns. On phones, it will also collapse the sidebar into a single column. * README: Tell how to enable rtsopts for disabling GC (norpol). Version 0.12.0.1 released 24 Aug 2015 * Revert change of curly to straight quote for starting User's Guide page (Wouter Oosterveld). * stack.yaml: removed pandoc flag setting. Version 0.12 released 19 Aug 2015 * Export all modules. * Make executable builds depend on the library in cabal file. * Moved library files to src directory. * Added stack.yaml. * Updated README with stack install instructions. Version 0.11.1.1 released 14 Aug 2015 * Fixed Network.Gitit.Initialize so it compiles with older pandoc (#506). * Removed extra import of liftIO in Dot.hs plugin. Version 0.11.1 released 23 Jul 2015 * Allow `commonmark` as a page type. * Handle CommonMark page type on initialization. Version 0.11 released 02 Jun 2015 * Allow page extensions to be configurable (not just `.page`) (Caleb McDaniel). - Added `page-extension` option in config file (Caleb McDaniel). - Added new type for `defaultExtension` - Changed `isPageFile` to get extension from config - New function `isNotDiscussPageFile` - `pathForPage` must be passed extension as String - `isPageFile` now returns GititServerPart Bool instead of just Bool. * Reverted some changes to Plugins that caused excessive memory use. * Allow pandoc 1.15. * Added missing `
    ` tag in form on registration page (Vaughn Iverson). * Show page diffs in feed (Imuli). * Display commit messages in feed entry titles (Imuli). * Fix preview button for modern jQuery (Imuli). * Feed titles reflect site and page names (Imuli). * Present feed in canonical order (recent first, Imuli). * https support for base-url config option (Imuli). Version 0.10.7 released 02 Jun 2015 * Fixes to allow building with pandoc 1.14. `CommonMark` added as a constructor of `PageType`. CommonMark can now be used as a page format and is also available for page export. * Plugins: added some recommended option flags. * Allow `---` as well as `...` to end metadata (#493). * README: changed dead links (Rick Hanson). Version 0.10.6.3 released 08 May 2015 * README: use shortcut style markdown links. * Fixed profiling options. * Added .travis.yml. * Allow both time >= 1.5.0.0 and time < 1.5.0.0 with old-locale (Michal Antkiewicz) Version 0.10.6.2 released 02 April 2015 * Bumped upper version bounds. * Fix typos in README.markdown (Igor Vuk). * Update bug tracker link (Waldir Pimenta). Version 0.10.6.1 released 28 October 2014 * Added Network.Gitit.Compat.Except to cabal module list. Version 0.10.6 released 28 October 2014 * Escape HTML characters in user name when showing it on a web page. This addresses a security flaw in previous versions, pointed out by Davy Stoffel. A fake password reset email could be provided to users, with the link: http://gitit.net/_doResetPassword?reset_code=azeaze&username= davy%3Cscript%3Ealert%281%29%3C/script%3E If the person clicked the link, the unknown username would be displayed (unescaped), and the javascript would run. This fix addresses the flaw, not by preventing the funny user name, but by ensuring that the HTML tags are escaped when the user name is shown on the page. * Network.Gitit.Initialize: Allow mediawiki for default pages. * Enable readerParseRaw for all formats. This will enable things like script and iframe tags to get parsed from HTML sources, and unrecognized latex tags from LaTeX. * Refined github login (Freiric Barral). * Include jquery sources in sdist tarballs (Anthony Towns). * Add support for `mediawiki` as a page format (Raymond Gauthier). Version 0.10.5.1 released 21 September 2014 * Added markup help for org mode. Closes #449. * Utils.parsePageType: Added case for "org". * Allow newer versions of dependencies. Version 0.10.5 released 23 August 2014 * Added github login option (Freiric Barral). * Change default math display to mathjax. * Relaxed package bounds, fixed compiler warnings. Added Network.Gitit.Compat.Except module for compatibility with earlier and later mtl versions. * Added network-uri flag to accommodate network-uri/network split. * Fixed failure when loading the Subst plugin (Glenn Searby). * Added Makefile, for use in installing on server. * Include takeBaseName in System.FilePath import (Caleb McDaniel). * Update README.markdown on Apache installation (Peter Gallagher). * Add full versions of minified JavaScript (#400) (Peter Gallagher). * Enable highlighting of patterns that start or end with punctuation (Caleb McDaniel). * Moved oauth secret to separate config file (Freiric Barral). * Corrected MathJax CDN URL (Maciek Makowski). Version 0.10.4 released 30 Jun 2014 * Updated package bounds for happstack (#382), pandoc, blaze-html, network. * Display EPS as image, not code. * Fixed recent activity page for binary files (Sergey Koposov). * Use normal spaces instead of nbsp in activity page (Sergey Koposov). * Display a delete link next to uploads in file list (rekado). * Change _search to use HTTP GET, so searches can be linked and refreshed (Joe Hillenbrand). * Document mod_proxy_html setting in README. Added a mod_proxy_html configuration directive to insert a DOCTYPE string (Johann Visagie). * Added new template variables `isdiscusspage`, `isarticleUrl`, `discussionUrl`. This makes it possible to treat discussion pages specially in templates, and insert appropriate links (Shane O'Brien). * Added template variables `articlename`, `discussionname`, `isarticlepage` (Shane O'Brien). * Added redirects (#233). You can now create a redirect page by adding a `redirect` field to the metadata of a page (Shane O'Brien). - When a user visits a redirect page, they are redirected to the destination page. - At the destination page, a message is displayed telling the user that they have been redirected from the source page. A link is provided back to the source page, with a parameter to disable the redirect (so that it can be edited). - Gitit will detects circular redirects and explain to the user what is going on in such cases. * Added "search for pages containing..." option to `createPage`. Changed "page not found" page to give the option of searching for the page name or creating a page with that name (Shane O'Brien). * Set `pgTitle` in `showDiff` (Shane O'Brien). * Made the default "since" for the activity page configurable (Shane O'Brien). * Only set the `tabs` template variable if there are tabs (Shane O'Brien). * Removed access question from password reset form. It's only needed for the register form (Shane O'Brien). * Added `for` attribute to all labels on forms (Shane O'Brien). * Updated `pageToString` to use new metadata format (Shane O'Brien). * Handlers: Fixed duplicate function defn for `fileAnchor`. * Added `Org` and `BocBook` to `PageType` (API change). Pages may now be written in Ord mode or DocBook syntax. * Allow multiple categories, separated by commas, in a `_category` URL (Caleb McDaniel). The pages in all listed categories will be returned. * Added filter links for `_category` pages (Cabel McDaniel). * Fixed image exports in Docx, RTF, slides, PDF (#399, #353). * Restored inline syntax highlighting. * Fixed highlighting in exports (#356). * Added `ICML` and `beamer` as export formats (#391). * Added github-style backgrounds to code blocks (Joe Hillenbrand). * Lighter heading border (like wikimedia) (Joe Hillenbrand). * Fixed links on activity page (Shane O'Brien). * Added markup help for Textile, Org, DocBook (#434). * Modified plugins/Subst.hs to work with latest pandoc (Tianyi Cui). * Fixed wiki links when `base-url` is empty and `absolute-urls` yes (Tianyi Cui). * README: document that changes to templates require a restart (Raphael). Version 0.10.3.1 released 19 Mar 2013 * Fixed filename encoding problem affecting caching, for gitit compiled with GHC 7.4 or later. * Fixed padding on some buttons (akerbos). * Specify correct format in header for initial pages (benmachine). Version 0.10.3 released 09 Mar 2013 * Allow latest versions of pandoc, blaze-html, HStringTemplate. * Fixed duplicate ids in user box. * Added `mathjax-script` option, specifies the mathjax script to use. (Dmitry Gerasimov.) * Set focus on editedText on page load. (Mathieu Larose.) * Added `address` config option. (Matieu Larose.) Version 0.10.2 released 09 Feb 2013 * Updated to work with pandoc 1.10. * Fixed path for MathMLInHTML.js script. Closes #345. Thanks to tstgruby. * Updated interwiki plugin (gwern). * Made it possible to export pages with images stored in the repository itself (as opposed to the static directory). Thanks to Claudio Bley for the patch. Version 0.10.1.2 released 11 Jan 2013 * Fixed regression in option parsing. An earlier patch caused the '-f' option not to work. Closes #336. Version 0.10.1.1 released 01 Jan 2013 * Allow compilation with directory < 1.2. Version 0.10.1 released 31 Dec 2012 * Fixed duplicate dropExtension on categoryPage. (atsuo yamada) This created problems with categories containing periods. * Fixed duplicate unescaping of HTML entities. (atsuo yamada) * Supply $revision$ at _diff if "Changes from beginning to..." (atsuo yamada) * MathJax rendering is now working in edit preview mode (Dmitry Gerasimov). * Upgrade directory package dependency to 1.2, and fix compilation issue with GHC 7.6.1 (Bin Jin). * Allow metadata keys to include digits, _, -. Closes #328. * Don't read config for --help or --version (Ben Millwood). Also involves a refactor of options into those that make the program quit immediately, and those that just alter the configuration. * Updated to use filestore 0.6 (new diff API). Thanks to markwright for partial patch. * Include format metadata in default installed pages. This allows them to continue working when the user changes the default page format. Closes #329. * Added explicit path to Gitit User's Guide in default front page. * Fix Gitit User's Guide link on front page. Previously it was broken due to "smart punctuation." * Fixed validation messages. Switched from using lookRead "messages" to using looks "message" for messages. Closes #294. Version 0.10.0.2 released 02 Nov 2012 * Raised version bounds for dependencies. * Updated post-update script to use new forms of git commands. Closes #317. * Fixed withTempDir so it returns to old directory. Closes #303. This is a slightly different solution than the one proposed by tstgruby, but it has the advantage that only withTempDir itself needs to be changed. * Added nginx example for proxy setup (README) (Andre Kelpe). Version 0.10.0.1 released 07 Jun 2012 * Fixed double-encoding bug for unicode page names (Alexander Vershilov). * Require happstack-server >= 7. Version 0.10 released 30 May 2012 * Changed 'readFileUTF8' so it doesn't encode filename on ghc 7.4. * Upgraded for compatibility with blaze-html 0.5. Closes #299. * Improved categories. Files are now read strictly to avoid a 'too many open files' error. 'Page' now exports 'readCategories' instead of 'extractCategories'. * Require filestore 0.5. This brings in (a) correct handling of unicode paths when compiled under GHC 7.4, and (b) a 'limit' parameter for 'history'. The limit parameter is essential when gitit is used with very large repositories; otherwise history commands would have to parse the entire log. Handler functions that use 'history' have been updated to use the optional 'limit' parameter. * Atom feeds are now limited to 200 entries, to prevent server overload. * Indicate size of default logo picture in README. Closes #291. * Added a README section on restricting access. Closes #292. Version 0.9.0.1 released 15 Feb 2012 * Fixed bug in fromEntities that caused text to be lost in the page source after semicolons. Thanks to Perry Wagle for reporting the bug. * Updated code to run on happstack 7. * Removed dependency on happstack-util; depend on base64-bytestring instead. * Updated gitit.cabal to include footnotes.js (Ben Sinclair). Version 0.9 released 29 Feb 2012 * Gitit now uses the latest pandoc (1.9.x) and happstack-server (6.6.x), and compiles on ghc 7.4.1. * Added Docx, AsciiDoc, and DZSlides as export formats. * HTML slide show exports are now "self-contained": they embed all required js, css, and images, so they can be used offline. * Allow spaces in usernames (Juraj Hercek). * Improve PDF/RTF exports containing images in the wiki. Wikidata paths are translated to absolute ones, so pandoc/pdflatex can find them (Juraj Hercek). * Protect against XSS in slide show exports. Previous versions of gitit sanitized wikipages, but not HTML slide shows. * Table of contents is now in a div with ID `TOC`, so it can be styled. * Removed letter and word spacing from print.css. * Added s5 directory to static. This is needed by pandoc 1.9. * Updated Interwiki plugin (gwern). * Added `fromEntities` to `Types`, since `decodeCharacterReferences` is no longer exported from Pandoc. Added dependency on tagsoup. * Provided `FromReqURI` instance for `[String]`, since this is not automatic with recent happstack. Version 0.8.1 released 02 Sep 2011 * Support mathjax as a math option. Added MathJax as MathMethod, and mathjax as an option in the 'math' config field. Resolves GoogleCode 122. * Added xss-sanitize configuaration option. Setting it to 'no' turns off sanitization, enabling file:// URLs and other things that get filtered out by xss-sanitize. * Listen interface explanation on help file could be more clear (#266) (andyring) * Add the new configuration option 'absolute-urls'. When turned on, this makes wikilinks absolute w.r.t. the base-url. By default, they are relative. So, for example, in a wiki served at the path 'wiki', on a page Sub/Page, the wikilink '[Cactus]()' will produce a link to '/wiki/Cactus' if absolute-urls is on, and otherwise the relative link 'Cactus'. Patch due to lemmih. * Change default listen address to 0.0.0.0. * Serve svg file as image, not source code! * Page history: use 'limit' instead of restricting to past year. limit defaults to 100. If 100 are displayed, you'll get a "Show more..." link that will increase the limit. Also fixed bug that caused a 404 when no history was returned. * Require pandoc >= 1.8.2. * Allow build with happstack-server 6.2. * Updated for use with xss-sanitize 0.3, which uses Text. New dependency on text. Version 0.8.0.1 released 07 Jun 2011 * Fixed file upload problem with recent versions of directory package. (Thanks to Oliver Braun.) * Relaxed some version upper bounds. Version 0.8 released 13 May 2011 * Uses happstack 6. * Added textile and org export formats, textile page format. * Added support for RPXNow authentication, based on a patch from Pasqualino Titto Assini. * Added `authentication-required` field in config. * If set to 'modify', authentication is required to modify the wiki. * If set to 'read', atuhentication is required to view the wiki. * If set to 'none', authentication is never required, and pages can be edited anonymously. API changes: * currentUser moved to Authentication module * requireAuthentication added to Config * Added AuthenticationLevel type * requireUser renamed authenticate, parameter for AuthenticationLevel added; requireUserThat renamed authenticateUserThat * MathML and jsMath now work in the preview pane (Sean Seefried). * Use footnotes.js for fancy footnote styling (gwern). * Added a `--listen` parameter to specify the listen device (Timo B. Hübel). * Removed withInput. * Replaced fileContents with filePath in Params. * Fixed bug in uploadForm.js which caused a prefix to be added in the default wikiname. Version 0.7.3.12 released 01 Feb 2011 * Use pandoc 1.8. * New export formats: textile, org. * New page form: textile. Version 0.7.3.11 released 28 Jan 2011 * Allow time 1.2. Version 0.7.3.10 released 26 Jan 2011 * Updated for filestore-0.4.0.2. Gitit should now compile with ghc 7. Note: It may be necessary to supply the --disable-library-for-ghci flag to 'cabal install highlighting-kate'. Version 0.7.3.9 released 25 Jan 2011 * Removed dependency on cautious-file. It no longer seems to be actively maintained, and the current configuration does not compile on windows. * Removed dependency on datetime package. It is no longer maintained. Everything can be done just as well with the time package. * Depend on filestore >= 0.4 (without datetime dependency). * Bump version bounds on hslogger, network and HTTP. * Support for GHC 7.0 in Plugins (thanks to Max Bollingbroke). * Use xss-sanitize for sanitizing HTML. Previously pandoc's sanitization was used, but this will be removed in the next pandoc release. xss-sanitize is a more complete solution, and also prevents people from messing up layout by inserting unbalanced . * Updated Feed module to make it decouplable from gitit. * jQuery.load wasn't working on Safari. Use jQuery.post instead. Also, the convert function was not always in scope. (It is only in scope when MathML is enabled?) We check if it is defined before calling it. (Thanks to Sean Seefried.) * Export Page module. * Templates are in data directory * Fixed bug in Subst plugin (Lars Petersen). Subst plugin could not deal with non-existing pages, resulting in an server error when trying to substitute with an absent file. This patch now creates a link to the page in order to create it. * Added alt attribute to logo. Version 0.7.3.8 released 24 July 2010 * Fixed MathML in Slidy and S5 exports. * Use languagesByFilename instead of languagesByExtension in isSource. Version 0.7.3.7 released 24 July 2010 * Depend on pandoc >= 1.6, highlighting-kate >= 0.2.7.1 * Added epub and slidy export formats. * Require happstack >= 0.5. * Added google math option (uses google charts api). Slightly modified from a patch by lpeterse. * Made WebArchiver plugin more parallel (gwern). * Fixed Dot plugin to work with GHC 6.12. We were having string encoding issues reading the output of dot with readProcess. Solution is to pass dot an output filename so we don't have to read its output. Version 0.7.3.6 released 05 May 2010 * Fixed ODT/PDF export for files in subdirectories. Resolves Issue #81. * Fix image URLs before calling the ODT or PDF processors * Added plain text export format. * Raised upper bound for datetime, parsec, and happstack dependencies. * Fix wikilinks to they don't get a leading slash. This reverts a bug introduced by 2128afb070b7, which added leading slashes to wikilinks, breaking them for people using gitit as a library on a path other than /. Version 0.7.3.5 released 21 Mar 2010 * Returned to using pandoc's MathML writer option. This is fixed in pandoc 1.5.0.1. Depend on pandoc >= 1.5.0.1. Version 0.7.3.4 released 21 Mar 2010 * Use custom readFileUTF8 (exported in Network.Gitit.Util) instead of broken System.IO.UTF8. This way we have a uniform solution for GHC 6.10 and 6.12, and don't have to use CPP tricks. This change fixes categories on GHC 6.12. Resolves Issue #98. Version 0.7.3.3 released 21 Mar 2010 * Reverted to handling math in MathML mode in the old way, using a transform, rather than relying on pandoc's MathML writer option. The latter was causing amazing CPU and memory usage, for reasons I don't yet understand. This should fix the problem for now. * Fixed caching for unicode page names. * Added max-page-size config option. Thanks to Jinjing Wang for the patch. * Prevented _expire/ from failing if the page is not cached. * Fixed URL encoding for pages. (Note: Don't use + for spaces; that breaks the Ctrl-R cache expiration.) Version 0.7.3.2 released 20 Mar 2010 * Fixed editing of pages when max-upload-size=0. max-upload-size should not double as max-page-size. Resolves Issue #96. Version 0.7.3.1 released 20 Mar 2010 * Changed "In" to "in" in MathMLinJS.js link. Version 0.7.3 released 20 Mar 2010 * Added PDF export option and pdf-export config field. (Based on a patch by gwern.) * Added markdown export. * Use pandoc's new MathML math mode for more efficient MathML. * Improved multi-wiki example code in haddocks. * Added session-timeout config setting. * Config module: Added readSize (recognizing K,M,G suffix). Previously readNumber always recognized K,M,G suffixes, but these only make sense in some contexts (not e.g. for times). * Added Subst plugin (thanks to gwern). * Added notes on PDF caching and idle. * Fixed table of contents in wiki pages (resolving Issue #91). * Added pandoc-user-data config option, allowing the user to specify a directory with e.g. templates that override the defaults used for exported pages. * Fix filesToClean GHC panic when loading plugins on GHC HEAD * Fixed problem with doubled // in updir links. Resolves Issue #88. * Updated interwiki plugin. * Fixed caching for feeds. Thanks to brian.sniffen for pointing out the need to normalize the time diff. Resolves Issue #87. * Improved Feed module (gwern). * Use line anchors from highlighting-source, so that you can link directly to a particular line in a source file. * Disable upload functionality if maxUploadSize is 0. * Exported queryGititState, updateGititState, Network.Gitit.Layout. Exported filledPageTemplate. (Thanks to tphyahoo.) Split off and expose createDefaultPages. Exposed compilePageTemplate. * Use charset=utf-8 on output from Layout. * Use isUnescapedInURI with escapeURIString rather than isAllowedInURI. The latter does not escape % signs. Version 0.7.2 released 02 Jan 2010 * Now compiles with GHC 6.12. Version 0.7.1 released 02 Jan 2010 * Updated exports to work with pandoc 1.4. * Began updating to work with GHC 6.12. (Still untested; there may be further issues involving filestore.) Version 0.7 released 20 Dec 2009 * Updated cabal file to allow happstack 0.4. * Added support for the new mercurial filestore backend. (Depending on filestore >= 0.3.4.) * Depend on xml >= 1.3.5. This fixes a bug in the display of mathml. Previously the self-closed tags in matrices with empty cells confused browsers and caused them to construct the DOM incorrectly. The problem is fixed by using xml's new ppcElement function to render the MathML without self-closed tags. * Depend on pandoc >= 1.3. * Properly handle UTF-8 in config files. * Moved option parsing code from Config module to main program. The Config module now exports getConfigFromFile instead of getConfigFromOpts. This should be more useful for those using gitit as a library. * Use wikiTitle config field in default HTML title. * Improved search results: + Highlight search terms in search results. Partially resolves Issue #76. + Made search results message uniform when no results. + Search: don't match page name against empty patterns. + Allow search matches on subdirectory part of page name. + Search: catch error status from filestore search. Filestore <= 0.3.3 does not properly handle the error status returned by later versions of 'git grep' when no match is found. The problem has been fixed in darcs filestore. * CSS tweaks: + Removed base-min.css, folded necessary styles into screen.css. + Removed 'text-align: left' for th from CSS reset. * Feed improvements: + Modified feed handling so that feeds validate. + Perform proper escaping in Feed.hs (thanks to gwern). + Don't reveal author email in feeds. + Sitewide feed is /_feed/ (with trailing slash). + Add "http://" to base-url config option if needed. * Use + for spaces in URLs linking to wiki pages and folders. * Updated plugins: + Updated Interwiki plugin (gwern). + Modified WebArchiver plugin to make Alexa requests (gwern). Version 0.6.6 released 06 Nov 2009 * Require filestore >= 0.3.3, which closes a security vulnerability. * Don't allow web file uploads to the static or templates directory, even if these are subdirectories of the repository directory. We don't want users uploading new CSS, javascript, or templates that might break the site. * Renamed gitit-dog.png -> logo.png in data/static/img. This way the logo will show up even without a local img directory. Thanks to Thomas Hartmann for the patch. * Return 404 when page not found. Thanks to Richard Fergie. * Improved layout of Export button. * Added links for atom feeds to sitenav.st and pagetools.st, to make the feeds more discoverable. * Minor code safety improvements. * Check for commit messages consisting of whitespace. Commit messages consisting only of whitespace characters are rejected by Git as empty. Gitit should behave similarly. * Allow gitit to start up if custom template directory not found. Thanks to Thomas Hartmann. * Fixed incorrect usage of nullGroup (a debugging function). Thanks to Thomas Hartmann. Version 0.6.5 released 06 Oct 2009 * Added metadata to Page and Context, provided askMeta for plugins. This patch gives plugins access to all of the key/value pairs in the page metadata block. Thanks to Dan Cook. * Added PigLatin plugin to demonstrate use of askMeta. * Display informative message on authentication failure. * Fixed library stanza in cabal file so plugins are properly enabled. Version 0.6.4 released 28 Sep 2009 * Fixed preview javascript so that tex math works properly in preview. Version 0.6.3 released 27 Sep 2009 * Fixed MathML conversion so it doesn't happen when exporting to non-HTML output formats. * Fixed shadowing on page templates: previously page.st was always taken from the defaults, even if a modified version existed in templates/. * Modified YUI CSS reset so that ordered list enumerators can be styled properly. * Modified showPage to work with both POST and GET requests. Version 0.6.2 released 25 Aug 2009 * Use "reference obfuscation" for emails, rather than javascript obfuscation, which seems to interfere with preview. Resolves Issue #59. Version 0.6.1 released 25 Aug 2009 Instructions for upgrading from 0.5.3: - If you were using a Haskell configuration file, you will need to create a new configuration file. 'gitit --print-default-config' will print a self-documenting default configuration file in the new format, which you can modify. - If your wiki contains discuss pages of the form 'foo:discuss.page', rename them to '@foo.page'. - Delete template.html and the static directory so that these will be replaced by the newest versions when you run gitit. If you have customized these, you should back them up first, then merge your changes into the new versions after they are created. (Note that template.html will be replaced by a templates/ directory.) Summary of main changes: * Added support for plugins -- dynamically loaded Haskell programs that transform pages. See the haddock documentation for Gitit.Interface for plugin documentation. The plugins directory contains several sample plugins. * Gitit's configuration file is now a text file with key-value pairs, rather than a Haskell file. The default configuration file (which can be printed using `gitit --print-default-config` contains comments that document all of the options. * Pages may now be written in (limited dialects of) LaTeX or HTML, as well as markdown and reStructuredText. The default format is determined by a configuration option, but can be overridden on a per-page basis using metadata (see below). The default Front Page and Help page are created in the default format specified by the configuration file. In addition, syntax help is now displayed to the left of the editing box when a page is being edited. * Pages may be written in literate Haskell, using either bird style with markdown or reStructuredText, or LaTeX style with LaTeX. Literate Haskell can be made the default or specified on a per-page basis. * Gitit now exports a library, Network.Gitit, that makes it easy for any happstack application to embed a gitit wiki. * Added optional atom feeds, for whole site (at /_feed) and for individual pages (at /_feed/path/to/page). Feeds are cached with a configurable expiration time. * Completely new caching system. Caching is turned off by default and can be enabled by a configuration option. Complete pages are cached on disk and expired when pages are revised through the web interface. When pages are modified directly through a VCS, the cache must be refreshed manually, either by pressing Ctrl-R while viewing a page, or by sending an HTTP request to /_expire/path/to/page, or by using the included program expireGititPath. The new system is much faster than the old in-memory cache, because it avoids the considerable overhead of filestore calls to get the current revision id. * To make whole-page caching possible, the user login/out box has been made into an ajax request to /_user. jQuery is now loaded on every page. * Math is converted to MathML by default (using the texmath library), and a javascript is linked in that renders it correctly in IE+mathplayer, Firefox, and Opera. The 'math' configuration setting can alternatively be set to 'jsMath' (to use jsMath javascript, which is more portable but ugly and slower) or 'raw' (plain LaTeX code). * Routing changes for better handling of web spiders. Instead of "/foo?history" we now have "/_history/foo"; instead of "/foo?edit" we haev "/_edit/foo"; etc. This makes it possible to exclude web spiders from non-cached pages by excluding URLs that start with '/_'. A default robots.txt file is now provided. Users need not do anything special for this to be enabled. * The authentication system has been revised and made much more flexible. In the configuration file, you can specify either 'form', 'http', or 'generic' as authentication-method. Form authentication is the old form-based gitit authentication system. HTTP authentication presupposes that the wiki pages are locked down under HTTP authentication; the gitit user will be set to the username used for HTTP authentication. Generic authentication takes the username from the REMOTE_USER request header. When gitit is being used as a library, one can specify a custom withUser filter (which determines the logged in user and sets REMOTE_USER accordingly) and a custom authHandler (including handlers for /_login, /_logout, and whatever else is needed). * Security fix: Gitit did not verify that a change password request is genuine when it receives the final POST. It has been changed to re-verify the reset code, otherwise an attacker could simply steal anyone's account by spoofing a POST request. (Thanks to Robin Green.) * template.html has now been replaced by a directory, templates/, with separate templates for each component of a page. * Added /_reloadTemplates action that recompiles the templates. (By default the templates are compiled only on startup.) * Gitit's form-based authentication now includes a "password reset" email. Slightly modified from a patch from Henry Laxen. * The naming scheme for discussion pages has changed: the discussion page for foo is now @foo, not foo:discuss. Reason: Windows, and thus darcs, does not like colons in filenames. * Improved logging, with configurable verbosity. * Major code reorganization and cleanup. Gitit has been moved under the Network namespace. The old WebT handlers are replaced by new ones in ServerPartT. 'handle' has been removed; instead, we use happstack's routing combinators. Configuration and filestores are now passed around in a reader monad, in WikiState. (This also allows different wikis to have different configurations.) Most handlers have been simplified so that they no longer require Page and Params arguments. A new function, 'withInput', is used to avoid the need to pass Params between handlers. * The static handler now "falls back" to the cabal data directory if the requested file is not in "static" (or staticDir). So the user need no longer have a copy of the standard gitit CSS, javascript, and image files in "static" (unless these are to be overridden). This should make updates easier. By default only 'custom.css' and 'logo.png' are put in the user's static directory. * Similarly, the templates in "templates" "fall back" to defaults in the cabal data directory. By default only 'footer.st' is put in the user's static directory. * Gitit State now includes a renderPage function. This is more flexible than storing a page template, since the user may want to use a custom page rendering function, even one not based on string templates. * Added Network.Gitit.ContentTransformer module (thanks to Anton van Straaten). The ContentTransformer module replaces Gitit.Convert. It defines a number of single-purpose combinators that can be combined to yield various kinds of content conversions. These are used to define showPage, preview, showHighlightedSource, and other handlers that used to be defined in Gitit.hs. * Verify in delete POST requests that filetodelete parameter matches page. * Fixed revert when called from diff pages. Revert now reverts to the older of the two revisions being compared. * Revamped auto-merging: user must now verify an edited page after a merge, even if there were no conflicts. * Fixed Content-Disposition header on export so that filenames have proper extensions. * Updated for happstack-server-0.3.3. Since this version of happstack supports UTF-8, gitit's old manual decoding and encoding were removed. * Use fileServeStrict instead of fileServe. Resolves Issue #57. * 'limit' is no longer used in search. The way it worked before was confusing, since it limited total matches (usually to just a few files) rather than limiting the number of matches in each file. * rdgreen's cautious-file library is now used to write the gitit-users file. This makes it less likely that the file will be corrupted on a power outage or hardware failure. * Redirects set properly after account creation. If users go from the Login form to the Register form, they are no longer redirected back to the Login form after creating an account. * indexPage now uses filestore's new 'directory' function. It shows one directory at a time. Subdirectories link to further index pages. This improves on the old javascript folding interface, which did not preserve state. (Thanks to Thomas Hartman for suggestions.) * URLs of the form /a/b/ are now equivalent to /_index/a/b. * Improvements and bug fixes to deleting. Deleting a non-page now works. You get a nice informative message if you try to delete a nonexistent page or file. * Page names containing "..", "?", or "*", and '_' at beginning are disallowed. Page names may now contain periods. * The "Permanent link" link has been removed. It relied on the sha1 parameter always being set, but we've changed that for performance reasons. * Gitit can now be proxied to a subdirectory path. Thanks to Henry Laxen for the idea and patches. See README for instructions. * Performance improvements (mostly due to Gwern Branwen): Pages can be compressed (configurable); unneeded filestore calls removed; cache-control: max-age used. * Moved sidebar to end of HTML to make things easier for screen readers. * Moved search box and go box to templates. * Yahoo YUI CSS framework is now used for better consistency across browsers. CSS cleaned up. Icons for page types removed. * Fixed handling of 'forUser' parameter in 'recent activity'. * Made default maxUploadSize 10 Mb. * Renamed AppState -> GititState. Version 0.5.3 released 1 Feb 2009 * Fixed bug which caused jsMath not to load. Version 0.5.2 released 1 Feb 2009 * Fixed cookie problem caused by empty value fields. Version 0.5.1 released 1 Feb 2009 * Major code reorganization, making gitit more modular. * Gitit can now optionally be built using Happstack instead of HAppS (just use -fhappstack when cabal installing). * Fixed bug with directories that had the same names as pages. * Added code from HAppS-Extra to fix cookie parsing problems. * New command-line options for --port, --debug. * New debug feature prints the date, the raw request, and the processed request data to standard output on each request. * Files with ".page" extension can no longer be uploaded. * Apostrophes and quotation marks now allowed in page names. gitit-0.12.2.1/README.markdown0000644000000000000000000005336013050577750013762 0ustar0000000000000000Gitit ===== Gitit is a wiki program written in Haskell. It uses [Happstack] for the web server and [pandoc] for markup processing. Pages and uploaded files are stored in a [git], [darcs], or [mercurial] repository and may be modified either by using the VCS's command-line tools or through the wiki's web interface. By default, pandoc's extended version of markdown is used as a markup language, but reStructuredText, LaTeX, HTML, DocBook, or Emacs Org-mode markup can also be used. Pages can be exported in a number of different formats, including LaTeX, RTF, OpenOffice ODT, and MediaWiki markup. Gitit can be configured to display TeX math (using [texmath]) and highlighted source code (using [highlighting-kate]). Other features include * plugins: dynamically loaded page transformations written in Haskell (see "Network.Gitit.Interface") * categories * TeX math * syntax highlighting of source code files and code snippets (using highlighting-kate) * caching * Atom feeds (site-wide and per-page) * a library, "Network.Gitit", that makes it simple to include a gitit wiki in any happstack application [git]: http://git.or.cz [darcs]: http://darcs.net [mercurial]: http://mercurial.selenic.com/ [pandoc]: http://pandoc.org [Happstack]: http://happstack.com [highlighting-kate]: http://johnmacfarlane.net/highlighting-kate/ [texmath]: http://github.com/jgm/texmath/tree/master Getting started =============== Compiling and installing gitit ------------------------------ The most reliable way to install gitit from source is to get the [stack] tool. Then clone the gitit repository and use stack to install: git clone https://github.com/jgm/gitit cd gitit stack install Alternatively, instead of using [stack], you can get the [Haskell Platform] and do the following: cabal update cabal install gitit This will install the latest released version of gitit. To install a version of gitit checked out from the repository, change to the gitit directory and type: cabal install The `cabal` tool will automatically install all of the required haskell libraries. If all goes well, by the end of this process, the latest release of gitit will be installed in your local `.cabal` directory. You can check this by trying: gitit --version If that doesn't work, check to see that `gitit` is in your local cabal-install executable directory (usually `~/.cabal/bin`). And make sure `~/.cabal/bin` is in your system path. [stack]: https://github.com/commercialhaskell/stack [Haskell Platform]: https://www.haskell.org/platform/ Running gitit ------------- To run gitit, you'll need `git` in your system path. (Or `darcs` or `hg`, if you're using darcs or mercurial to store the wiki data.) Gitit assumes that the page files (stored in the git repository) are encoded as UTF-8. Even page names may be UTF-8 if the file system supports this. So you should make sure that you are using a UTF-8 locale when running gitit. (To check this, type `locale`.) Switch to the directory where you want to run gitit. This should be a directory where you have write access, since three directories, `static`, `templates`, and `wikidata`, and two files, `gitit-users` and `gitit.log`, will be created here. To start gitit, just type: gitit If all goes well, gitit will do the following: 1. Create a git repository, `wikidata`, and add a default front page. 2. Create a `static` directory containing files to be treated as static files by gitit. 3. Create a `templates` directory containing HStringTemplate templates for wiki pages. 4. Start a web server on port 5001. Check that it worked: open a web browser and go to . You can control the port that gitit runs on using the `-p` option: `gitit -p 4000` will start gitit on port 4000. Additional runtime options are described by `gitit -h`. Using gitit =========== Wiki links and formatting ------------------------- For instructions on editing pages and creating links, see the "Help" page. Gitit interprets links with empty URLs as wikilinks. Thus, in markdown pages, `[Front Page]()` creates an internal wikilink to the page `Front Page`. In reStructuredText pages, `` `Front Page <>`_ `` has the same effect. If you want to link to a directory listing for a subdirectory, use a trailing slash: `[foo/bar/]()` creates a link to the directory for `foo/bar`. Page metadata ------------- Pages may optionally begin with a metadata block. Here is an example: --- format: latex+lhs categories: haskell math toc: no title: Haskell and Category Theory ... \section{Why Category Theory?} The metadata block consists of a list of key-value pairs, each on a separate line. If needed, the value can be continued on one or more additional line, which must begin with a space. (This is illustrated by the "title" example above.) The metadata block must begin with a line `---` and end with a line `...` optionally followed by one or more blank lines. (The metadata block is a valid YAML document, though not all YAML documents will be valid metadata blocks.) Currently the following keys are supported: format : Overrides the default page type as specified in the configuration file. Possible values are `markdown`, `rst`, `latex`, `html`, `markdown+lhs`, `rst+lhs`, `latex+lhs`. (Capitalization is ignored, so you can also use `LaTeX`, `HTML`, etc.) The `+lhs` variants indicate that the page is to be interpreted as literate Haskell. If this field is missing, the default page type will be used. categories : A space or comma separated list of categories to which the page belongs. toc : Overrides default setting for table-of-contents in the configuration file. Values can be `yes`, `no`, `true`, or `false` (capitalization is ignored). title : By default the displayed page title is the page name. This metadata element overrides that default. Highlighted source code ----------------------- If gitit was compiled against a version of pandoc that has highlighting support (see above), you can get highlighted source code by using [delimited code blocks]: ~~~ {.haskell .numberLines} qsort [] = [] qsort (x:xs) = qsort (filter (< x) xs) ++ [x] ++ qsort (filter (>= x) xs) ~~~ To see what languages your pandoc was compiled to highlight: pandoc -v [delimited code blocks]: http://pandoc.org/README.html#delimited-code-blocks Configuring and customizing gitit ================================= Configuration options --------------------- Use the option `-f [filename]` to specify a configuration file: gitit -f my.conf The configuration can be split between several files: gitit -f my.conf -f additional.conf One use case is to keep sensible part of the configuration outside of a SCM (oauth client secret for example). If this option is not used, gitit will use a default configuration. To get a copy of the default configuration file, which you can customize, just type: gitit --print-default-config > my.conf The default configuration file is documented with comments throughout. The `static` directory ---------------------- On receiving a request, gitit always looks first in the `static` directory (or in whatever directory is specified for `static-dir` in the configuration file). If a file corresponding to the request is found there, it is served immediately. If the file is not found in `static`, gitit next looks in the `static` subdirectory of gitit's data file (`$CABALDIR/share/gitit-x.y.z/data`). This is where default css, images, and javascripts are stored. If the file is not found there either, gitit treats the request as a request for a wiki page or wiki command. So, you can throw anything you want to be served statically (for example, a `robots.txt` file or `favicon.ico`) in the `static` directory. You can override any of gitit's default css, javascript, or image files by putting a file with the same relative path in `static`. Note that gitit has a default `robots.txt` file that excludes all URLs beginning with `/_`. Note: if you set `static-dir` to be a subdirectory of `repository-path`, and then add the files in the static directory to your repository, you can ensure that others who clone your wiki repository get these files as well. It will not be possible to modify these files using the web interface, but they will be modifiable via git. Using a VCS other than git -------------------------- By default, gitit will store wiki pages in a git repository in the `wikidata` directory. If you'd prefer to use darcs instead of git, you need to add the following field to the configuration file: repository-type: Darcs If you'd prefer to use mercurial, add: repository-type: Mercurial This program may be called "darcsit" instead of "gitit" when a darcs backend is used. Note: we recommend that you use gitit/darcsit with darcs version 2.3.0 or greater. If you must use an older version of darcs, then you need to compile the filestore library without the (default) maxcount flag, before (re)installing gitit: cabal install --reinstall filestore -f-maxcount cabal install --reinstall gitit Otherwise you will get an error when you attempt to access your repository. Changing the theme ------------------ To change the look of the wiki, you can modify `custom.css` in `static/css`. To change the look of printed pages, copy gitit's default `print.css` to `static/css` and modify it. The logo picture can be changed by copying a new PNG file to `static/img/logo.png`. The default logo is 138x155 pixels. To change the footer, modify `templates/footer.st`. For more radical changes, you can override any of the default templates in `$CABALDIR/share/gitit-x.y.z/data/templates` by copying the file into `templates`, modifying it, and restarting gitit. The `page.st` template is the master template; it includes the others. Interpolated variables are surrounded by `$`s, so `literal $` must be backslash-escaped. Adding support for math ----------------------- To write math on a markdown-formatted wiki page, just enclose it in dollar signs, as in LaTeX: Here is a formula: $\frac{1}{\sqrt{c^2}}$ You can write display math by enclosing it in double dollar signs: $$\frac{1}{\sqrt{c^2}}$$ Gitit can display TeX math in three different ways, depending on the setting of `math` in the configuration file: 1. `mathml` (default): Math will be converted to MathML using [texmath]. This method works with IE+mathplayer, Firefox, and Opera, but not Safari. 2. `jsMath`: Math will be rendered using the [jsMath] javascript. If you want to use this method, download `jsMath` and `jsMath Image Fonts` from the [jsMath download page]. You'll have two `.zip` archives. Unzip them both in the `static/js` directory (a new subdirectory, `jsMath`, will be created). This works with all browsers, but is slower and not as nice looking as MathML. 3. `raw`: Math will be rendered as raw LaTeX codes. [jsMath]: http://www.math.union.edu/~dpvc/jsmath/ [jsMath download page]: http://sourceforge.net/project/showfiles.php?group_id=172663 Restricting access ------------------ If you want to limit account creation on your wiki, the easiest way to do this is to provide an `access-question` in your configuration file. (See the commented default configuration file.) Nobody will be able to create an account without knowing the answer to the access question. Another approach is to use HTTP authentication. (See the config file comments on `authentication-method`.) Authentication through github ----------------------------- If you want to authenticate the user from github through oauth2, you need to register your app with github to obtain a OAuth client secret and add the following section to your configuration file: ``` [Github] oauthclientid: 01239456789abcdef012 oauthclientsecret: 01239456789abcdef01239456789abcdef012394 oauthcallback: http://mysite/_githubCallback oauthoauthorizeendpoint: https://github.com/login/oauth/authorize oauthaccesstokenendpoint: https://github.com/login/oauth/access_token ## Uncomment if you are checking membership against an organization and change ## gitit-testorg to this organization: # github-org: gitit-testorg ``` The github authentication uses the scope `user:email`. This way, gitit gets the email of the user, and the commit can be assigned to the right author if the wikidata repository is pushed to github. Additionally, it uses `read:org` if you uses the option `github-org` to check membership against an organization. To push your repository to gitub after each commit, you can add the file `post-commit` with the content below in the .git/hooks directory of your wikidata repository. ``` #!/bin/sh git push origin master 2>> logit ``` Plugins ======= Plugins are small Haskell programs that transform a wiki page after it has been converted from Markdown or another source format. See the example plugins in the `plugins` directory. To enable a plugin, include the path to the plugin (or its module name) in the `plugins` field of the configuration file. (If the plugin name starts with `Network.Gitit.Plugin.`, gitit will assume that the plugin is an installed module and will not look for a source file.) Plugin support is enabled by default. However, plugin support makes the gitit executable considerably larger and more memory-hungry. If you don't need plugins, you may want to compile gitit without plugin support. To do this, unset the `plugins` Cabal flag: cabal install --reinstall gitit -f-plugins Note also that if you compile gitit for executable profiling, attempts to load plugins will result in "internal error: PAP object entered!" Accessing the wiki through git ============================== All the pages and uploaded files are stored in a git repository. By default, this lives in the `wikidata` directory (though this can be changed through configuration options). So you can interact with the wiki using git command line tools: git clone ssh://my.server.edu/path/of/wiki/wikidata cd wikidata vim Front\ Page.page # edit the page git commit -m "Added message about wiki etiquette" Front\ Page.page git push If you now look at the Front Page on the wiki, you should see your changes reflected there. Note that the pages all have the extension `.page`. If you are using the darcs or mercurial backend, the commands will be slightly different. See the documentation for your VCS for details. Performance =========== Caching ------- By default, gitit does not cache content. If your wiki receives a lot of traffic or contains pages that are slow to render, you may want to activate caching. To do this, set the configuration option `use-cache` to `yes`. By default, rendered pages, highlighted source files, and exported PDFs will be cached in the `cache` directory. (Another directory can be specified by setting the `cache-dir` configuration option.) Cached pages are updated when pages are modified using the web interface. They are not updated when pages are modified directly through git or darcs. However, the cache can be refreshed manually by pressing Ctrl-R when viewing a page, or by sending an HTTP GET or POST request to `/_expire/path/to/page`, where `path/to/page` is the name of the page to be expired. Users who frequently update pages using git or darcs may wish to add a hook to the repository that makes the appropriate HTTP request to expire pages when they are updated. To facilitate such hooks, the gitit cabal package includes an executable `expireGititCache`. Assuming you are running gitit at port 5001 on localhost, and the environment variable `CHANGED_FILES` contains a list of the files that have changed, you can expire their cached versions using expireGititCache http://localhost:5001 $CHANGED_FILES Or you can specify the files directly: expireGititCache http://localhost:5001 "Front Page.page" foo/bar/baz.c This program will return a success status (0) if the page has been successfully expired (or if it was never cached in the first place), and a failure status (> 0) otherwise. The cache is persistent through restarts of gitit. To expire all cached pages, simply remove the `cache` directory. Idle ---- By default, GHC's runtime will repeatedly attempt to collect garbage when an executable like Gitit is idle. This means that gitit will, after the first page request, never use 0% CPU time and sleep, but will use ~1%. This can be bad for battery life, among other things. To fix this, one can disable the idle-time GC with the runtime flag `-I0`: gitit -f my.conf +RTS -I0 -RTS Note: To enable RTS, cabal needs to pass the compile flag `-rtsopts` to GHC while installing. cabal install --reinstall gitit --ghc-options="-rtsopts" Using gitit with apache ======================= Most users who run a public-facing gitit will want gitit to appear at a nice URL like `http://wiki.mysite.com` or `http://mysite.com/wiki` rather than `http://mysite.com:5001`. This can be achieved using apache's `mod_proxy`. Proxying to `http://wiki.mysite.com` ------------------------------------ Set up your DNS so that `http://wiki.mysite.com` maps to your server's IP address. Make sure that the `mod_proxy`, `mod_proxy_http` and `mod_rewrite` modules are loaded, and set up a virtual host with the following configuration: ServerName wiki.mysite.com DocumentRoot /var/www/ RewriteEngine On ProxyPreserveHost On ProxyRequests Off Order deny,allow Allow from all ProxyPassReverse / http://127.0.0.1:5001 RewriteRule ^(.*) http://127.0.0.1:5001$1 [P] ErrorLog /var/log/apache2/error.log LogLevel warn CustomLog /var/log/apache2/access.log combined ServerSignature On Reload your apache configuration and you should be all set. Using nginx to achieve the same ------------------------------- Drop a file called `wiki.example.com.conf` into `/etc/nginx/conf.d` (or where ever your distribution puts it). server { listen 80; server_name wiki.example.com location / { proxy_pass http://127.0.0.1:5001/; proxy_set_header X-Real-IP $remote_addr; proxy_redirect off; } access_log /var/log/nginx/wiki.example.com.log main; } Reload your nginx config and you should be all set. Proxying to `http://mysite.com/wiki` ------------------------------------ Make sure the `mod_proxy`, `mod_headers`, `mod_proxy_http`, and `mod_proxy_html` modules are loaded. `mod_proxy_html` is an external module, which can be obtained [here] (http://apache.webthing.com/mod_proxy_html/). It rewrites URLs that occur in web pages. Here we will use it to rewrite gitit's links so that they all begin with `/wiki/`. First, tell gitit not to compress pages, since `mod_proxy_html` needs uncompressed pages to parse. You can do this by setting the gitit configuration option compress-responses: no Second, modify the link in the `reset-password-message` in the configuration file: instead of http://$hostname$:$port$$resetlink$ set it to http://$hostname$/wiki$resetlink$ Restart gitit. Now add the following lines to the apache configuration file for the `mysite.com` server: # These commands will proxy /wiki/ to port 5001 ProxyRequests Off Order deny,allow Allow from all ProxyPass /wiki/ http://127.0.0.1:5001/ SetOutputFilter proxy-html ProxyPassReverse / ProxyHTMLURLMap / /wiki/ ProxyHTMLDocType "" XHTML RequestHeader unset Accept-Encoding Reload your apache configuration and you should be set. For further information on the use of `mod_proxy_http` to rewrite URLs, see the [`mod_proxy_html` guide]. [`mod_proxy_html` guide]: http://apache.webthing.com/mod_proxy_html/guide.html Using gitit as a library ======================== By importing the module `Network.Gitit`, you can include a gitit wiki (or several of them) in another happstack application. There are some simple examples in the haddock documentation for `Network.Gitit`. Reporting bugs ============== Bugs may be reported (and feature requests filed) at . There is a mailing list for users and developers at . Acknowledgements ================ A number of people have contributed patches: - Gwern Branwen helped to optimize gitit and wrote the InterwikiPlugin. He also helped with the Feed module. - Simon Michael contributed the patch adding RST support. - Henry Laxen added support for password resets and helped with the apache proxy instructions. - Anton van Straaten made the process of page generation more modular by adding Gitit.ContentTransformer. - Robin Green helped improve the plugin API and interface, and fixed a security problem with the reset password code. - Thomas Hartman helped improve the index page, making directory browsing persistent, and fixed a bug in template recompilation. - Justin Bogner improved the appearance of the preview button. - Kohei Ozaki contributed the ImgTexPlugin. - Michael Terepeta improved validation of change descriptions. - mightybyte suggested making gitit available as a library, and contributed a patch to ifLoggedIn that was needed to make gitit usable with a custom authentication scheme. I am especially grateful to the darcs team for using darcsit for their public-facing wiki. This has helped immensely in identifying issues and improving performance. Gitit's default visual layout is shamelessly borrowed from Wikipedia. The stylesheets are influenced by Wikipedia's stylesheets and by the bluetrip CSS framework (see BLUETRIP-LICENSE). Some of the icons in `img/icons` come from bluetrip as well. gitit-0.12.2.1/YUI-LICENSE0000644000000000000000000000305712765540066012732 0ustar0000000000000000Software License Agreement (BSD License) Copyright (c) 2009, Yahoo! Inc. All rights reserved. Redistribution and use of this software in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of Yahoo! Inc. nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission of Yahoo! Inc. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. gitit-0.12.2.1/BLUETRIP-LICENSE0000644000000000000000000004055412765540066013515 0ustar0000000000000000Blueprint CSS Framework License ---------------------------------------------------------------- Copyright (c) 2007-2008 Olav Bjorkoy (olav at bjorkoy.com) The Blueprint CSS Framework is available for use in all personal or commercial projects, under both the (modified) MIT and the GPL license. You may choose the one that fits your project. The (modified) MIT License ---------------------------------------------------------------- Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sub-license, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice, and every other copyright notice found in this software, and all the attributions in every file, and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NON-INFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. The GPL License ---------------------------------------------------------------- GNU GENERAL PUBLIC LICENSE Version 2, June 1991 Copyright (C) 1989, 1991 Free Software Foundation, Inc. 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. Preamble The licenses for most software are designed to take away your freedom to share and change it. By contrast, the GNU General Public License is intended to guarantee your freedom to share and change free software--to make sure the software is free for all its users. This General Public License applies to most of the Free Software Foundation's software and to any other program whose authors commit to using it. (Some other Free Software Foundation software is covered by the GNU Lesser General Public License instead.) You can apply it to your programs, too. When we speak of free software, we are referring to freedom, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for this service if you wish), that you receive source code or can get it if you want it, that you can change the software or use pieces of it in new free programs; and that you know you can do these things. To protect your rights, we need to make restrictions that forbid anyone to deny you these rights or to ask you to surrender the rights. These restrictions translate to certain responsibilities for you if you distribute copies of the software, or if you modify it. For example, if you distribute copies of such a program, whether gratis or for a fee, you must give the recipients all the rights that you have. You must make sure that they, too, receive or can get the source code. And you must show them these terms so they know their rights. We protect your rights with two steps: (1) copyright the software, and (2) offer you this license which gives you legal permission to copy, distribute and/or modify the software. Also, for each author's protection and ours, we want to make certain that everyone understands that there is no warranty for this free software. If the software is modified by someone else and passed on, we want its recipients to know that what they have is not the original, so that any problems introduced by others will not reflect on the original authors' reputations. Finally, any free program is threatened constantly by software patents. We wish to avoid the danger that redistributors of a free program will individually obtain patent licenses, in effect making the program proprietary. To prevent this, we have made it clear that any patent must be licensed for everyone's free use or not licensed at all. The precise terms and conditions for copying, distribution and modification follow. GNU GENERAL PUBLIC LICENSE TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION 0. This License applies to any program or other work which contains a notice placed by the copyright holder saying it may be distributed under the terms of this General Public License. The "Program", below, refers to any such program or work, and a "work based on the Program" means either the Program or any derivative work under copyright law: that is to say, a work containing the Program or a portion of it, either verbatim or with modifications and/or translated into another language. (Hereinafter, translation is included without limitation in the term "modification".) Each licensee is addressed as "you". Activities other than copying, distribution and modification are not covered by this License; they are outside its scope. The act of running the Program is not restricted, and the output from the Program is covered only if its contents constitute a work based on the Program (independent of having been made by running the Program). Whether that is true depends on what the Program does. 1. You may copy and distribute verbatim copies of the Program's source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice and disclaimer of warranty; keep intact all the notices that refer to this License and to the absence of any warranty; and give any other recipients of the Program a copy of this License along with the Program. You may charge a fee for the physical act of transferring a copy, and you may at your option offer warranty protection in exchange for a fee. 2. You may modify your copy or copies of the Program or any portion of it, thus forming a work based on the Program, and copy and distribute such modifications or work under the terms of Section 1 above, provided that you also meet all of these conditions: a) You must cause the modified files to carry prominent notices stating that you changed the files and the date of any change. b) You must cause any work that you distribute or publish, that in whole or in part contains or is derived from the Program or any part thereof, to be licensed as a whole at no charge to all third parties under the terms of this License. c) If the modified program normally reads commands interactively when run, you must cause it, when started running for such interactive use in the most ordinary way, to print or display an announcement including an appropriate copyright notice and a notice that there is no warranty (or else, saying that you provide a warranty) and that users may redistribute the program under these conditions, and telling the user how to view a copy of this License. (Exception: if the Program itself is interactive but does not normally print such an announcement, your work based on the Program is not required to print an announcement.) These requirements apply to the modified work as a whole. If identifiable sections of that work are not derived from the Program, and can be reasonably considered independent and separate works in themselves, then this License, and its terms, do not apply to those sections when you distribute them as separate works. But when you distribute the same sections as part of a whole which is a work based on the Program, the distribution of the whole must be on the terms of this License, whose permissions for other licensees extend to the entire whole, and thus to each and every part regardless of who wrote it. Thus, it is not the intent of this section to claim rights or contest your rights to work written entirely by you; rather, the intent is to exercise the right to control the distribution of derivative or collective works based on the Program. In addition, mere aggregation of another work not based on the Program with the Program (or with a work based on the Program) on a volume of a storage or distribution medium does not bring the other work under the scope of this License. 3. You may copy and distribute the Program (or a work based on it, under Section 2) in object code or executable form under the terms of Sections 1 and 2 above provided that you also do one of the following: a) Accompany it with the complete corresponding machine-readable source code, which must be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, b) Accompany it with a written offer, valid for at least three years, to give any third party, for a charge no more than your cost of physically performing source distribution, a complete machine-readable copy of the corresponding source code, to be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, c) Accompany it with the information you received as to the offer to distribute corresponding source code. (This alternative is allowed only for noncommercial distribution and only if you received the program in object code or executable form with such an offer, in accord with Subsection b above.) The source code for a work means the preferred form of the work for making modifications to it. For an executable work, complete source code means all the source code for all modules it contains, plus any associated interface definition files, plus the scripts used to control compilation and installation of the executable. However, as a special exception, the source code distributed need not include anything that is normally distributed (in either source or binary form) with the major components (compiler, kernel, and so on) of the operating system on which the executable runs, unless that component itself accompanies the executable. If distribution of executable or object code is made by offering access to copy from a designated place, then offering equivalent access to copy the source code from the same place counts as distribution of the source code, even though third parties are not compelled to copy the source along with the object code. 4. You may not copy, modify, sublicense, or distribute the Program except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense or distribute the Program is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance. 5. You are not required to accept this License, since you have not signed it. However, nothing else grants you permission to modify or distribute the Program or its derivative works. These actions are prohibited by law if you do not accept this License. Therefore, by modifying or distributing the Program (or any work based on the Program), you indicate your acceptance of this License to do so, and all its terms and conditions for copying, distributing or modifying the Program or works based on it. 6. Each time you redistribute the Program (or any work based on the Program), the recipient automatically receives a license from the original licensor to copy, distribute or modify the Program subject to these terms and conditions. You may not impose any further restrictions on the recipients' exercise of the rights granted herein. You are not responsible for enforcing compliance by third parties to this License. 7. If, as a consequence of a court judgment or allegation of patent infringement or for any other reason (not limited to patent issues), conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot distribute so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not distribute the Program at all. For example, if a patent license would not permit royalty-free redistribution of the Program by all those who receive copies directly or indirectly through you, then the only way you could satisfy both it and this License would be to refrain entirely from distribution of the Program. If any portion of this section is held invalid or unenforceable under any particular circumstance, the balance of the section is intended to apply and the section as a whole is intended to apply in other circumstances. It is not the purpose of this section to induce you to infringe any patents or other property right claims or to contest validity of any such claims; this section has the sole purpose of protecting the integrity of the free software distribution system, which is implemented by public license practices. Many people have made generous contributions to the wide range of software distributed through that system in reliance on consistent application of that system; it is up to the author/donor to decide if he or she is willing to distribute software through any other system and a licensee cannot impose that choice. This section is intended to make thoroughly clear what is believed to be a consequence of the rest of this License. 8. If the distribution and/or use of the Program is restricted in certain countries either by patents or by copyrighted interfaces, the original copyright holder who places the Program under this License may add an explicit geographical distribution limitation excluding those countries, so that distribution is permitted only in or among countries not thus excluded. In such case, this License incorporates the limitation as if written in the body of this License. 9. The Free Software Foundation may publish revised and/or new versions of the General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Program specifies a version number of this License which applies to it and "any later version", you have the option of following the terms and conditions either of that version or of any later version published by the Free Software Foundation. If the Program does not specify a version number of this License, you may choose any version ever published by the Free Software Foundation. 10. If you wish to incorporate parts of the Program into other free programs whose distribution conditions are different, write to the author to ask for permission. For software which is copyrighted by the Free Software Foundation, write to the Free Software Foundation; we sometimes make exceptions for this. Our decision will be guided by the two goals of preserving the free status of all derivatives of our free software and of promoting the sharing and reuse of software generally. NO WARRANTY 11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES.gitit-0.12.2.1/TANGOICONS0000644000000000000000000003371512765540066012654 0ustar0000000000000000Creative Commons Attribution-ShareAlike 2.5 License Agreement CREATIVE COMMONS CORPORATION IS NOT A LAW FIRM AND DOES NOT PROVIDE LEGAL SERVICES. DISTRIBUTION OF THIS LICENSE DOES NOT CREATE AN ATTORNEY-CLIENT RELATIONSHIP. CREATIVE COMMONS PROVIDES THIS INFORMATION ON AN "AS-IS" BASIS. CREATIVE COMMONS MAKES NO WARRANTIES REGARDING THE INFORMATION PROVIDED, AND DISCLAIMS LIABILITY FOR DAMAGES RESULTING FROM ITS USE. License THE WORK (AS DEFINED BELOW) IS PROVIDED UNDER THE TERMS OF THIS CREATIVE COMMONS PUBLIC LICENSE ("CCPL" OR "LICENSE"). THE WORK IS PROTECTED BY COPYRIGHT AND/OR OTHER APPLICABLE LAW. ANY USE OF THE WORK OTHER THAN AS AUTHORIZED UNDER THIS LICENSE OR COPYRIGHT LAW IS PROHIBITED. BY EXERCISING ANY RIGHTS TO THE WORK PROVIDED HERE, YOU ACCEPT AND AGREE TO BE BOUND BY THE TERMS OF THIS LICENSE. THE LICENSOR GRANTS YOU THE RIGHTS CONTAINED HERE IN CONSIDERATION OF YOUR ACCEPTANCE OF SUCH TERMS AND CONDITIONS. 1. Definitions 1. "Collective Work" means a work, such as a periodical issue, anthology or encyclopedia, in which the Work in its entirety in unmodified form, along with a number of other contributions, constituting separate and independent works in themselves, are assembled into a collective whole. A work that constitutes a Collective Work will not be considered a Derivative Work (as defined below) for the purposes of this License. 2. "Derivative Work" means a work based upon the Work or upon the Work and other pre-existing works, such as a translation, musical arrangement, dramatization, fictionalization, motion picture version, sound recording, art reproduction, abridgment, condensation, or any other form in which the Work may be recast, transformed, or adapted, except that a work that constitutes a Collective Work will not be considered a Derivative Work for the purpose of this License. For the avoidance of doubt, where the Work is a musical composition or sound recording, the synchronization of the Work in timed-relation with a moving image ("synching") will be considered a Derivative Work for the purpose of this License. 3. "Licensor" means the individual or entity that offers the Work under the terms of this License. 4. "Original Author" means the individual or entity who created the Work. 5. "Work" means the copyrightable work of authorship offered under the terms of this License. 6. "You" means an individual or entity exercising rights under this License who has not previously violated the terms of this License with respect to the Work, or who has received express permission from the Licensor to exercise rights under this License despite a previous violation. 7. "License Elements" means the following high-level license attributes as selected by Licensor and indicated in the title of this License: Attribution, ShareAlike. 2. Fair Use Rights. Nothing in this license is intended to reduce, limit, or restrict any rights arising from fair use, first sale or other limitations on the exclusive rights of the copyright owner under copyright law or other applicable laws. 3. License Grant. Subject to the terms and conditions of this License, Licensor hereby grants You a worldwide, royalty-free, non-exclusive, perpetual (for the duration of the applicable copyright) license to exercise the rights in the Work as stated below: 1. to reproduce the Work, to incorporate the Work into one or more Collective Works, and to reproduce the Work as incorporated in the Collective Works; 2. to create and reproduce Derivative Works; 3. to distribute copies or phonorecords of, display publicly, perform publicly, and perform publicly by means of a digital audio transmission the Work including as incorporated in Collective Works; 4. to distribute copies or phonorecords of, display publicly, perform publicly, and perform publicly by means of a digital audio transmission Derivative Works. 5. For the avoidance of doubt, where the work is a musical composition: 1. Performance Royalties Under Blanket Licenses. Licensor waives the exclusive right to collect, whether individually or via a performance rights society (e.g. ASCAP, BMI, SESAC), royalties for the public performance or public digital performance (e.g. webcast) of the Work. 2. Mechanical Rights and Statutory Royalties. Licensor waives the exclusive right to collect, whether individually or via a music rights society or designated agent (e.g. Harry Fox Agency), royalties for any phonorecord You create from the Work ("cover version") and distribute, subject to the compulsory license created by 17 USC Section 115 of the US Copyright Act (or the equivalent in other jurisdictions). 6. Webcasting Rights and Statutory Royalties. For the avoidance of doubt, where the Work is a sound recording, Licensor waives the exclusive right to collect, whether individually or via a performance-rights society (e.g. SoundExchange), royalties for the public digital performance (e.g. webcast) of the Work, subject to the compulsory license created by 17 USC Section 114 of the US Copyright Act (or the equivalent in other jurisdictions). The above rights may be exercised in all media and formats whether now known or hereafter devised. The above rights include the right to make such modifications as are technically necessary to exercise the rights in other media and formats. All rights not expressly granted by Licensor are hereby reserved. 4. Restrictions.The license granted in Section 3 above is expressly made subject to and limited by the following restrictions: 1. You may distribute, publicly display, publicly perform, or publicly digitally perform the Work only under the terms of this License, and You must include a copy of, or the Uniform Resource Identifier for, this License with every copy or phonorecord of the Work You distribute, publicly display, publicly perform, or publicly digitally perform. You may not offer or impose any terms on the Work that alter or restrict the terms of this License or the recipients' exercise of the rights granted hereunder. You may not sublicense the Work. You must keep intact all notices that refer to this License and to the disclaimer of warranties. You may not distribute, publicly display, publicly perform, or publicly digitally perform the Work with any technological measures that control access or use of the Work in a manner inconsistent with the terms of this License Agreement. The above applies to the Work as incorporated in a Collective Work, but this does not require the Collective Work apart from the Work itself to be made subject to the terms of this License. If You create a Collective Work, upon notice from any Licensor You must, to the extent practicable, remove from the Collective Work any credit as required by clause 4(c), as requested. If You create a Derivative Work, upon notice from any Licensor You must, to the extent practicable, remove from the Derivative Work any credit as required by clause 4(c), as requested. 2. You may distribute, publicly display, publicly perform, or publicly digitally perform a Derivative Work only under the terms of this License, a later version of this License with the same License Elements as this License, or a Creative Commons iCommons license that contains the same License Elements as this License (e.g. Attribution-ShareAlike 2.5 Japan). You must include a copy of, or the Uniform Resource Identifier for, this License or other license specified in the previous sentence with every copy or phonorecord of each Derivative Work You distribute, publicly display, publicly perform, or publicly digitally perform. You may not offer or impose any terms on the Derivative Works that alter or restrict the terms of this License or the recipients' exercise of the rights granted hereunder, and You must keep intact all notices that refer to this License and to the disclaimer of warranties. You may not distribute, publicly display, publicly perform, or publicly digitally perform the Derivative Work with any technological measures that control access or use of the Work in a manner inconsistent with the terms of this License Agreement. The above applies to the Derivative Work as incorporated in a Collective Work, but this does not require the Collective Work apart from the Derivative Work itself to be made subject to the terms of this License. 3. If you distribute, publicly display, publicly perform, or publicly digitally perform the Work or any Derivative Works or Collective Works, You must keep intact all copyright notices for the Work and provide, reasonable to the medium or means You are utilizing: (i) the name of the Original Author (or pseudonym, if applicable) if supplied, and/or (ii) if the Original Author and/or Licensor designate another party or parties (e.g. a sponsor institute, publishing entity, journal) for attribution in Licensor's copyright notice, terms of service or by other reasonable means, the name of such party or parties; the title of the Work if supplied; to the extent reasonably practicable, the Uniform Resource Identifier, if any, that Licensor specifies to be associated with the Work, unless such URI does not refer to the copyright notice or licensing information for the Work; and in the case of a Derivative Work, a credit identifying the use of the Work in the Derivative Work (e.g., "French translation of the Work by Original Author," or "Screenplay based on original Work by Original Author"). Such credit may be implemented in any reasonable manner; provided, however, that in the case of a Derivative Work or Collective Work, at a minimum such credit will appear where any other comparable authorship credit appears and in a manner at least as prominent as such other comparable authorship credit. 5. Representations, Warranties and Disclaimer UNLESS OTHERWISE AGREED TO BY THE PARTIES IN WRITING, LICENSOR OFFERS THE WORK AS-IS AND MAKES NO REPRESENTATIONS OR WARRANTIES OF ANY KIND CONCERNING THE MATERIALS, EXPRESS, IMPLIED, STATUTORY OR OTHERWISE, INCLUDING, WITHOUT LIMITATION, WARRANTIES OF TITLE, MERCHANTIBILITY, FITNESS FOR A PARTICULAR PURPOSE, NONINFRINGEMENT, OR THE ABSENCE OF LATENT OR OTHER DEFECTS, ACCURACY, OR THE PRESENCE OF ABSENCE OF ERRORS, WHETHER OR NOT DISCOVERABLE. SOME JURISDICTIONS DO NOT ALLOW THE EXCLUSION OF IMPLIED WARRANTIES, SO SUCH EXCLUSION MAY NOT APPLY TO YOU. 6. Limitation on Liability. EXCEPT TO THE EXTENT REQUIRED BY APPLICABLE LAW, IN NO EVENT WILL LICENSOR BE LIABLE TO YOU ON ANY LEGAL THEORY FOR ANY SPECIAL, INCIDENTAL, CONSEQUENTIAL, PUNITIVE OR EXEMPLARY DAMAGES ARISING OUT OF THIS LICENSE OR THE USE OF THE WORK, EVEN IF LICENSOR HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. 7. Termination 1. This License and the rights granted hereunder will terminate automatically upon any breach by You of the terms of this License. Individuals or entities who have received Derivative Works or Collective Works from You under this License, however, will not have their licenses terminated provided such individuals or entities remain in full compliance with those licenses. Sections 1, 2, 5, 6, 7, and 8 will survive any termination of this License. 2. Subject to the above terms and conditions, the license granted here is perpetual (for the duration of the applicable copyright in the Work). Notwithstanding the above, Licensor reserves the right to release the Work under different license terms or to stop distributing the Work at any time; provided, however that any such election will not serve to withdraw this License (or any other license that has been, or is required to be, granted under the terms of this License), and this License will continue in full force and effect unless terminated as stated above. 8. Miscellaneous 1. Each time You distribute or publicly digitally perform the Work or a Collective Work, the Licensor offers to the recipient a license to the Work on the same terms and conditions as the license granted to You under this License. 2. Each time You distribute or publicly digitally perform a Derivative Work, Licensor offers to the recipient a license to the original Work on the same terms and conditions as the license granted to You under this License. 3. If any provision of this License is invalid or unenforceable under applicable law, it shall not affect the validity or enforceability of the remainder of the terms of this License, and without further action by the parties to this agreement, such provision shall be reformed to the minimum extent necessary to make such provision valid and enforceable. 4. No term or provision of this License shall be deemed waived and no breach consented to unless such waiver or consent shall be in writing and signed by the party to be charged with such waiver or consent. 5. This License constitutes the entire agreement between the parties with respect to the Work licensed here. There are no understandings, agreements or representations with respect to the Work not specified here. Licensor shall not be bound by any additional provisions that may appear in any communication from You. This License may not be modified without the mutual written agreement of the Licensor and You. Creative Commons is not a party to this License, and makes no warranty whatsoever in connection with the Work. Creative Commons will not be liable to You or any party on any legal theory for any damages whatsoever, including without limitation any general, special, incidental or consequential damages arising in connection to this license. Notwithstanding the foregoing two (2) sentences, if Creative Commons has expressly identified itself as the Licensor hereunder, it shall have all rights and obligations of Licensor. Except for the limited purpose of indicating to the public that the Work is licensed under the CCPL, neither party will use the trademark "Creative Commons" or any related trademark or logo of Creative Commons without the prior written consent of Creative Commons. Any permitted use will be in compliance with Creative Commons' then-current trademark usage guidelines, as may be published on its website or otherwise made available upon request from time to time. Creative Commons may be contacted at http://creativecommons.org/. gitit-0.12.2.1/LICENSE0000644000000000000000000004316012765540066012265 0ustar0000000000000000 GNU GENERAL PUBLIC LICENSE Version 2, June 1991 Copyright (C) 1989, 1991 Free Software Foundation, Inc. 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. Preamble The licenses for most software are designed to take away your freedom to share and change it. By contrast, the GNU General Public License is intended to guarantee your freedom to share and change free software--to make sure the software is free for all its users. This General Public License applies to most of the Free Software Foundation's software and to any other program whose authors commit to using it. (Some other Free Software Foundation software is covered by the GNU Library General Public License instead.) You can apply it to your programs, too. When we speak of free software, we are referring to freedom, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for this service if you wish), that you receive source code or can get it if you want it, that you can change the software or use pieces of it in new free programs; and that you know you can do these things. To protect your rights, we need to make restrictions that forbid anyone to deny you these rights or to ask you to surrender the rights. These restrictions translate to certain responsibilities for you if you distribute copies of the software, or if you modify it. For example, if you distribute copies of such a program, whether gratis or for a fee, you must give the recipients all the rights that you have. You must make sure that they, too, receive or can get the source code. And you must show them these terms so they know their rights. We protect your rights with two steps: (1) copyright the software, and (2) offer you this license which gives you legal permission to copy, distribute and/or modify the software. Also, for each author's protection and ours, we want to make certain that everyone understands that there is no warranty for this free software. If the software is modified by someone else and passed on, we want its recipients to know that what they have is not the original, so that any problems introduced by others will not reflect on the original authors' reputations. Finally, any free program is threatened constantly by software patents. We wish to avoid the danger that redistributors of a free program will individually obtain patent licenses, in effect making the program proprietary. To prevent this, we have made it clear that any patent must be licensed for everyone's free use or not licensed at all. The precise terms and conditions for copying, distribution and modification follow. GNU GENERAL PUBLIC LICENSE TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION 0. This License applies to any program or other work which contains a notice placed by the copyright holder saying it may be distributed under the terms of this General Public License. The "Program", below, refers to any such program or work, and a "work based on the Program" means either the Program or any derivative work under copyright law: that is to say, a work containing the Program or a portion of it, either verbatim or with modifications and/or translated into another language. (Hereinafter, translation is included without limitation in the term "modification".) Each licensee is addressed as "you". Activities other than copying, distribution and modification are not covered by this License; they are outside its scope. The act of running the Program is not restricted, and the output from the Program is covered only if its contents constitute a work based on the Program (independent of having been made by running the Program). Whether that is true depends on what the Program does. 1. You may copy and distribute verbatim copies of the Program's source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice and disclaimer of warranty; keep intact all the notices that refer to this License and to the absence of any warranty; and give any other recipients of the Program a copy of this License along with the Program. You may charge a fee for the physical act of transferring a copy, and you may at your option offer warranty protection in exchange for a fee. 2. You may modify your copy or copies of the Program or any portion of it, thus forming a work based on the Program, and copy and distribute such modifications or work under the terms of Section 1 above, provided that you also meet all of these conditions: a) You must cause the modified files to carry prominent notices stating that you changed the files and the date of any change. b) You must cause any work that you distribute or publish, that in whole or in part contains or is derived from the Program or any part thereof, to be licensed as a whole at no charge to all third parties under the terms of this License. c) If the modified program normally reads commands interactively when run, you must cause it, when started running for such interactive use in the most ordinary way, to print or display an announcement including an appropriate copyright notice and a notice that there is no warranty (or else, saying that you provide a warranty) and that users may redistribute the program under these conditions, and telling the user how to view a copy of this License. (Exception: if the Program itself is interactive but does not normally print such an announcement, your work based on the Program is not required to print an announcement.) These requirements apply to the modified work as a whole. If identifiable sections of that work are not derived from the Program, and can be reasonably considered independent and separate works in themselves, then this License, and its terms, do not apply to those sections when you distribute them as separate works. But when you distribute the same sections as part of a whole which is a work based on the Program, the distribution of the whole must be on the terms of this License, whose permissions for other licensees extend to the entire whole, and thus to each and every part regardless of who wrote it. Thus, it is not the intent of this section to claim rights or contest your rights to work written entirely by you; rather, the intent is to exercise the right to control the distribution of derivative or collective works based on the Program. In addition, mere aggregation of another work not based on the Program with the Program (or with a work based on the Program) on a volume of a storage or distribution medium does not bring the other work under the scope of this License. 3. You may copy and distribute the Program (or a work based on it, under Section 2) in object code or executable form under the terms of Sections 1 and 2 above provided that you also do one of the following: a) Accompany it with the complete corresponding machine-readable source code, which must be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, b) Accompany it with a written offer, valid for at least three years, to give any third party, for a charge no more than your cost of physically performing source distribution, a complete machine-readable copy of the corresponding source code, to be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, c) Accompany it with the information you received as to the offer to distribute corresponding source code. (This alternative is allowed only for noncommercial distribution and only if you received the program in object code or executable form with such an offer, in accord with Subsection b above.) The source code for a work means the preferred form of the work for making modifications to it. For an executable work, complete source code means all the source code for all modules it contains, plus any associated interface definition files, plus the scripts used to control compilation and installation of the executable. However, as a special exception, the source code distributed need not include anything that is normally distributed (in either source or binary form) with the major components (compiler, kernel, and so on) of the operating system on which the executable runs, unless that component itself accompanies the executable. If distribution of executable or object code is made by offering access to copy from a designated place, then offering equivalent access to copy the source code from the same place counts as distribution of the source code, even though third parties are not compelled to copy the source along with the object code. 4. You may not copy, modify, sublicense, or distribute the Program except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense or distribute the Program is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance. 5. You are not required to accept this License, since you have not signed it. However, nothing else grants you permission to modify or distribute the Program or its derivative works. These actions are prohibited by law if you do not accept this License. Therefore, by modifying or distributing the Program (or any work based on the Program), you indicate your acceptance of this License to do so, and all its terms and conditions for copying, distributing or modifying the Program or works based on it. 6. Each time you redistribute the Program (or any work based on the Program), the recipient automatically receives a license from the original licensor to copy, distribute or modify the Program subject to these terms and conditions. You may not impose any further restrictions on the recipients' exercise of the rights granted herein. You are not responsible for enforcing compliance by third parties to this License. 7. If, as a consequence of a court judgment or allegation of patent infringement or for any other reason (not limited to patent issues), conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot distribute so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not distribute the Program at all. For example, if a patent license would not permit royalty-free redistribution of the Program by all those who receive copies directly or indirectly through you, then the only way you could satisfy both it and this License would be to refrain entirely from distribution of the Program. If any portion of this section is held invalid or unenforceable under any particular circumstance, the balance of the section is intended to apply and the section as a whole is intended to apply in other circumstances. It is not the purpose of this section to induce you to infringe any patents or other property right claims or to contest validity of any such claims; this section has the sole purpose of protecting the integrity of the free software distribution system, which is implemented by public license practices. Many people have made generous contributions to the wide range of software distributed through that system in reliance on consistent application of that system; it is up to the author/donor to decide if he or she is willing to distribute software through any other system and a licensee cannot impose that choice. This section is intended to make thoroughly clear what is believed to be a consequence of the rest of this License. 8. If the distribution and/or use of the Program is restricted in certain countries either by patents or by copyrighted interfaces, the original copyright holder who places the Program under this License may add an explicit geographical distribution limitation excluding those countries, so that distribution is permitted only in or among countries not thus excluded. In such case, this License incorporates the limitation as if written in the body of this License. 9. The Free Software Foundation may publish revised and/or new versions of the General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Program specifies a version number of this License which applies to it and "any later version", you have the option of following the terms and conditions either of that version or of any later version published by the Free Software Foundation. If the Program does not specify a version number of this License, you may choose any version ever published by the Free Software Foundation. 10. If you wish to incorporate parts of the Program into other free programs whose distribution conditions are different, write to the author to ask for permission. For software which is copyrighted by the Free Software Foundation, write to the Free Software Foundation; we sometimes make exceptions for this. Our decision will be guided by the two goals of preserving the free status of all derivatives of our free software and of promoting the sharing and reuse of software generally. NO WARRANTY 11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. END OF TERMS AND CONDITIONS How to Apply These Terms to Your New Programs If you develop a new program, and you want it to be of the greatest possible use to the public, the best way to achieve this is to make it free software which everyone can redistribute and change under these terms. To do so, attach the following notices to the program. It is safest to attach them to the start of each source file to most effectively convey the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found. Copyright (C) This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 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 General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA Also add information on how to contact you by electronic and paper mail. If the program is interactive, make it output a short notice like this when it starts in an interactive mode: Gnomovision version 69, Copyright (C) year name of author Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'. This is free software, and you are welcome to redistribute it under certain conditions; type `show c' for details. The hypothetical commands `show w' and `show c' should show the appropriate parts of the General Public License. Of course, the commands you use may be called something other than `show w' and `show c'; they could even be mouse-clicks or menu items--whatever suits your program. You should also get your employer (if you work as a programmer) or your school, if any, to sign a "copyright disclaimer" for the program, if necessary. Here is a sample; alter the names: Yoyodyne, Inc., hereby disclaims all copyright interest in the program `Gnomovision' (which makes passes at compilers) written by James Hacker. , 1 April 1989 Ty Coon, President of Vice This General Public License does not permit incorporating your program into proprietary programs. If your program is a subroutine library, you may consider it more useful to permit linking proprietary applications with the library. If this is what you want to do, use the GNU Library General Public License instead of this License. gitit-0.12.2.1/Setup.lhs0000644000000000000000000000011412765540066013060 0ustar0000000000000000#!/usr/bin/env runhaskell > import Distribution.Simple > main = defaultMain gitit-0.12.2.1/gitit.cabal0000644000000000000000000002351713050604010013342 0ustar0000000000000000name: gitit version: 0.12.2.1 Cabal-version: >= 1.8 build-type: Simple synopsis: Wiki using happstack, git or darcs, and pandoc. description: Gitit is a wiki backed by a git, darcs, or mercurial filestore. Pages and uploaded files can be modified either directly via the VCS's command-line tools or through the wiki's web interface. Pandoc is used for markup processing, so pages may be written in (extended) markdown, reStructuredText, LaTeX, HTML, or literate Haskell, and exported in ten different formats, including LaTeX, ConTeXt, DocBook, RTF, OpenOffice ODT, and MediaWiki markup. . Notable features include . * plugins: dynamically loaded page transformations written in Haskell (see "Network.Gitit.Interface") . * conversion of TeX math to MathML for display in web browsers . * syntax highlighting of source code files and code snippets . * Atom feeds (site-wide and per-page) . * a library, "Network.Gitit", that makes it simple to include a gitit wiki in any happstack application . You can see a running demo at . . For usage information: @gitit --help@ category: Network license: GPL license-file: LICENSE author: John MacFarlane maintainer: jgm@berkeley.edu bug-reports: http://github.com/jgm/gitit/issues homepage: http://gitit.net stability: experimental extra-source-files: data/static/js/jquery-1.2.6.js data/static/js/jquery.hotkeys-0.7.9.js data/static/js/jquery-ui.core-1.6rc2.js data/static/js/jquery-ui.droppable-1.6rc2.js data/static/js/jquery-ui.draggable-1.6rc2.js data/static/js/jquery-ui.tabs-1.6rc2.js data-files: data/static/css/screen.css, data/static/css/print.css, data/static/css/ie.css, data/static/css/hk-pyg.css, data/static/css/reset-fonts-grids.css, data/static/css/custom.css, data/static/img/logo.png, data/static/img/icons/feed.png, data/static/img/icons/folder.png, data/static/img/icons/page.png, data/static/js/dragdiff.js, data/static/js/jquery-1.2.6.min.js, data/static/js/uploadForm.js, data/static/js/jquery-ui-combined-1.6rc2.min.js, data/static/js/jquery.hotkeys-0.7.9.min.js, data/static/js/preview.js, data/static/js/search.js, data/static/js/MathMLinHTML.js, data/static/js/footnotes.js, data/static/robots.txt, data/s5/default/blank.gif, data/s5/default/bodybg.gif, data/s5/default/framing.css, data/s5/default/iepngfix.htc, data/s5/default/opera.css, data/s5/default/outline.css, data/s5/default/pretty.css, data/s5/default/print.css, data/s5/default/s5-core.css, data/s5/default/slides.css, data/s5/default/slides.js, data/s5/default/slides.min.js, data/post-update, data/FrontPage.page, data/Help.page, data/markup.Markdown, data/markup.RST, data/markup.Textile, data/markup.Org, data/markup.DocBook, data/markup.HTML, data/markup.LaTeX, data/default.conf, data/templates/page.st, data/templates/content.st, data/templates/userbox.st, data/templates/footer.st, data/templates/logo.st, data/templates/markuphelp.st, data/templates/pagetools.st, data/templates/sitenav.st, data/templates/messages.st, data/templates/listitem.st, data/templates/expire.st, data/templates/getuser.st, data/markupHelp/Markdown, data/markupHelp/Markdown+LHS, data/markupHelp/RST, data/markupHelp/RST+LHS, data/markupHelp/LaTeX, data/markupHelp/LaTeX+LHS, data/markupHelp/HTML, data/markupHelp/Org, plugins/CapitalizeEmphasis.hs, plugins/PigLatin.hs, plugins/Dot.hs, plugins/ImgTex.hs, plugins/Interwiki.hs, plugins/Deprofanizer.hs, plugins/WebArchiver.hs, plugins/ShowUser.hs, plugins/Signature.hs, plugins/Subst.hs, CHANGES, README.markdown, YUI-LICENSE, BLUETRIP-LICENSE, TANGOICONS Source-repository head type: git location: git://github.com/jgm/gitit.git Flag network-uri Description: Get Network.URI from the network-uri package Default: True Flag plugins description: Compile in support for plugins. This will increase the size of the executable and the memory it uses, so those who will not need plugins should disable this flag. default: True Library hs-source-dirs: src exposed-modules: Network.Gitit, Network.Gitit.ContentTransformer, Network.Gitit.Types, Network.Gitit.Framework, Network.Gitit.Initialize, Network.Gitit.Config, Network.Gitit.Layout, Network.Gitit.Authentication, Network.Gitit.Authentication.Github, Network.Gitit.Util, Network.Gitit.Server Network.Gitit.Cache, Network.Gitit.State, Paths_gitit, Network.Gitit.Export, Network.Gitit.Handlers, Network.Gitit.Plugins, Network.Gitit.Rpxnow, Network.Gitit.Page, Network.Gitit.Feed, Network.Gitit.Compat.Except build-depends: base >= 3 && < 5, filepath, safe, parsec, pretty, xhtml, containers, process, filepath, directory, mtl, old-time, pandoc >= 1.12.4 && < 1.20, pandoc-types >= 1.12.3 && < 1.18, highlighting-kate >= 0.5.0.1 && < 0.7, bytestring, text, random, utf8-string >= 0.3 && < 1.1, SHA > 1 && < 1.7, HTTP >= 4000.0 && < 4000.4, HStringTemplate >= 0.6 && < 0.9, old-locale >= 1, time >= 1.1 && < 1.8, recaptcha >= 0.1, filestore >= 0.6 && < 0.7, zlib >= 0.5 && < 0.7, url >= 2.1 && < 2.2, happstack-server >= 7.0 && < 7.5, base64-bytestring >= 0.1 && < 1.1, xml >= 1.3.5, hslogger >= 1 && < 1.3, ConfigFile >= 1 && < 1.2, feed >= 0.3.6 && < 0.4, xss-sanitize >= 0.3 && < 0.4, tagsoup >= 0.13 && < 0.15, blaze-html >= 0.4 && < 0.10, json >= 0.4 && < 0.10, uri >= 0.1 && < 0.2, split, hoauth2 >= 0.4.2 && < 0.6, http-conduit >= 2.1.4 && < 2.3, http-client-tls >= 0.2.2 && < 0.4, aeson >= 0.7 && < 1.2, uuid >= 1.3 && < 1.4 if impl(ghc >= 6.10) build-depends: base >= 4, syb if flag(network-uri) build-depends: network-uri >= 2.6 && < 2.7, network >= 2.6 else build-depends: network >= 2 && < 2.6 if flag(plugins) exposed-modules: Network.Gitit.Interface build-depends: ghc, ghc-paths cpp-options: -D_PLUGINS extensions: CPP if impl(ghc >= 6.12) ghc-options: -Wall -fno-warn-unused-do-bind else ghc-options: -Wall ghc-prof-options: -fprof-auto-exported Executable gitit hs-source-dirs: . main-is: gitit.hs build-depends: base >=3 && < 5, gitit, mtl, hslogger, bytestring, utf8-string, directory if flag(network-uri) build-depends: network-uri >= 2.6 && < 2.7, network >= 2.6 else build-depends: network >= 2 && < 2.6 extensions: CPP if impl(ghc >= 6.12) ghc-options: -Wall -threaded -fno-warn-unused-do-bind else ghc-options: -Wall -threaded ghc-prof-options: -fprof-auto-exported -rtsopts Executable expireGititCache hs-source-dirs: . main-is: expireGititCache.hs build-depends: base >=3 && < 5, HTTP, url, filepath if flag(network-uri) build-depends: network-uri >= 2.6 && < 2.7, network >= 2.6 else build-depends: network >= 2 && < 2.6 if impl(ghc >= 6.10) build-depends: base >= 4, syb ghc-options: -Wall