gitit-0.10.7: Wiki using happstack, git or darcs, and pandoc.

Safe HaskellNone
LanguageHaskell98

Network.Gitit

Contents

Description

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)

Synopsis

Wiki handlers

wiki :: Config -> ServerPart Response Source

Happstack handler for a gitit wiki.

reloadTemplates :: ServerPart Response Source

Recompiles the gitit templates.

runHandler :: WikiState -> Handler -> ServerPart Response Source

Converts a gitit Handler into a standard happstack ServerPart.

Initialization

Configuration

Types

Tools for building handlers

stringToPage :: Config -> String -> String -> Page Source

Read a string (the contents of a page file) and produce a Page object, using defaults except when overridden by metadata.

pageToString :: Config -> Page -> String Source

Write a string (the contents of a page file) corresponding to a Page object, using explicit metadata only when needed.

readCategories :: FilePath -> IO [String] Source

Read categories from metadata strictly.