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

Safe HaskellSafe-Infered

Network.Gitit.Interface

Description

Interface for plugins.

A plugin is a Haskell module that is dynamically loaded by gitit.

There are three kinds of plugins: PageTransforms, PreParseTransforms, and PreCommitTransforms. These plugins differ chiefly in where they are applied. PreCommitTransform plugins are applied just before changes to a page are saved and may transform the raw source that is saved. PreParseTransform plugins are applied when a page is viewed and may alter the raw page source before it is parsed as a Pandoc document. Finally, PageTransform plugins modify the Pandoc document that results after a page's source is parsed, but before it is converted to HTML:

                 +--------------------------+
                 | edited text from browser |
                 +--------------------------+
                              ||         <----  PreCommitTransform plugins
                              \/
                              ||         <----  saved to repository
                              \/
              +---------------------------------+
              | raw page source from repository |
              +---------------------------------+
                              ||         <----  PreParseTransform plugins
                              \/
                              ||         <----  markdown or RST reader
                              \/
                     +-----------------+
                     | Pandoc document |
                     +-----------------+
                              ||         <---- PageTransform plugins
                              \/
                   +---------------------+
                   | new Pandoc document |
                   +---------------------+
                              ||         <---- HTML writer
                              \/
                   +----------------------+
                   | HTML version of page |
                   +----------------------+

Note that PreParseTransform and PageTransform plugins do not alter the page source stored in the repository. They only affect what is visible on the website. Only PreCommitTransform plugins can alter what is stored in the repository.

Note also that PreParseTransform and PageTransform plugins will not be run when the cached version of a page is used. Plugins can use the doNotCache command to prevent a page from being cached, if their behavior is sensitive to things that might change from one time to another (such as the time or currently logged-in user).

You can use the helper functions mkPageTransform and mkPageTransformM to create PageTransform plugins from a transformation of any of the basic types used by Pandoc (for example, Inline, Block, [Inline], even String). Here is a simple (if silly) example:

 -- Deprofanizer.hs
 module 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

Further examples can be found in the plugins directory in the source distribution. If you have installed gitit using Cabal, you can also find them in the directory CABALDIR/share/gitit-X.Y.Z/plugins, where CABALDIR is the cabal install directory and X.Y.Z is the version number of gitit.

Synopsis

Documentation

mkPageTransform :: Data a => (a -> a) -> PluginSource

Lifts a function from a -> a (for example, Inline -> Inline, Block -> Block, [Inline] -> [Inline], or String -> String) to a PageTransform plugin.

mkPageTransformM :: Data a => (a -> PluginM a) -> PluginSource

Monadic version of mkPageTransform. Lifts a function from a -> m a to a PageTransform plugin.

data Config Source

Data structure for information read from config file.

Constructors

Config 

Fields

repositoryPath :: FilePath

Path of repository containing filestore

repositoryType :: FileStoreType

Type of repository

defaultPageType :: PageType

Default page markup type for this wiki

mathMethod :: MathMethod

How to handle LaTeX math in pages?

defaultLHS :: Bool

Treat as literate haskell by default?

showLHSBirdTracks :: Bool

Show Haskell code with bird tracks

withUser :: Handler -> Handler

Combinator to set REMOTE_USER request header

requireAuthentication :: AuthenticationLevel

Handler for login, logout, register, etc.

authHandler :: Handler

Specifies which actions require authentication.

userFile :: FilePath

Path of users database

sessionTimeout :: Int

Seconds of inactivity before session expires

templatesDir :: FilePath

Directory containing page templates

logFile :: FilePath

Path of server log file

logLevel :: Priority

Severity filter for log messages (DEBUG, INFO, NOTICE, WARNING, ERROR, CRITICAL, ALERT, EMERGENCY)

staticDir :: FilePath

Path of static directory

pluginModules :: [String]

Names of plugin modules to load

tableOfContents :: Bool

Show table of contents on each page?

maxUploadSize :: Integer

Max size of file uploads

maxPageSize :: Integer

Max size of page uploads

portNumber :: Int

Port number to serve content on

debugMode :: Bool

Print debug info to the console?

frontPage :: String

The front page of the wiki

noEdit :: [String]

Pages that cannot be edited via web

noDelete :: [String]

Pages that cannot be deleted via web

defaultSummary :: String

Default summary if description left blank

accessQuestion :: Maybe (String, [String])

Nothing = anyone can register. Just (prompt, answers) = a user will be given the prompt and must give one of the answers to register.

useRecaptcha :: Bool

Use ReCAPTCHA for user registration.

recaptchaPublicKey :: String
 
recaptchaPrivateKey :: String
 
rpxDomain :: String

RPX domain and key

rpxKey :: String
 
compressResponses :: Bool

Should responses be compressed?

useCache :: Bool

Should responses be cached?

cacheDir :: FilePath

Directory to hold cached pages

mimeMap :: Map String String

Map associating mime types with file extensions

mailCommand :: String

Command to send notification emails

resetPasswordMessage :: String

Text of password reset email

markupHelp :: String

Markup syntax help for edit sidebar

useFeed :: Bool

Provide an atom feed?

baseUrl :: String

Base URL of wiki, for use in feed

useAbsoluteUrls :: Bool

Title of wiki, used in feed

wikiTitle :: String

Should WikiLinks be absolute w.r.t. the base URL?

feedDays :: Integer

Number of days history to be included in feed

feedRefreshTime :: Integer

Number of minutes to cache feeds before refreshing

pdfExport :: Bool

Allow PDF export?

pandocUserData :: Maybe FilePath

Directory to search for pandoc customizations

xssSanitize :: Bool

Filter HTML through xss-sanitize

data Request

an HTTP request

Constructors

Request 

Fields

rqSecure :: Bool

request uses https://

rqMethod :: Method

request method

rqPaths :: [String]

the uri, split on /, and then decoded

rqUri :: String

the raw rqUri

rqQuery :: String

the QUERY_STRING

rqInputsQuery :: [(String, Input)]

the QUERY_STRING decoded as key/value pairs

rqInputsBody :: MVar [(String, Input)]

the request body decoded as key/value pairs (when appropriate)

rqCookies :: [(String, Cookie)]

cookies

rqVersion :: HttpVersion

HTTP version

rqHeaders :: Headers

the HTTP request headers

rqBody :: MVar RqBody

the raw, undecoded request body

rqPeer :: Host

(hostname, port) of the client making the request

Instances

data User Source

Constructors

User 

Instances

data PageLayout Source

Abstract representation of page layout (tabs, scripts, etc.)

askConfig :: PluginM ConfigSource

Returns the current wiki configuration.

askUser :: PluginM (Maybe User)Source

Returns Just the logged in user, or Nothing if nobody is logged in.

askRequest :: PluginM RequestSource

Returns the complete HTTP request.

askFileStore :: PluginM FileStoreSource

Returns the wiki filestore.

askMeta :: PluginM [(String, String)]Source

Returns the page meta data

doNotCache :: PluginM ()Source

Indicates that the current page or file is not to be cached.

inlinesToURL :: [Inline] -> StringSource

Derives a URL from a list of Pandoc Inline elements.

inlinesToString :: [Inline] -> StringSource

Convert a list of inlines into a string.

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

withTempDir :: FilePath -> (FilePath -> IO a) -> IO aSource

Perform a function in a temporary directory and clean up.