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

Safe HaskellNone
LanguageHaskell98

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) -> Plugin Source #

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) -> Plugin Source #

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

data Request #

an HTTP request

Constructors

Request 

Fields

Instances
Show Request 
Instance details

Defined in Happstack.Server.Internal.Types

HasHeaders Request 
Instance details

Defined in Happstack.Server.Internal.Types

data User Source #

Constructors

User 
Instances
Read User Source # 
Instance details

Defined in Network.Gitit.Types

Show User Source # 
Instance details

Defined in Network.Gitit.Types

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

data PageLayout Source #

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

askConfig :: PluginM Config Source #

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 Request Source #

Returns the complete HTTP request.

askFileStore :: PluginM FileStore Source #

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] -> String Source #

Derives a URL from a list of Pandoc Inline elements.

inlinesToString :: [Inline] -> String Source #

Convert a list of inlines into a string.

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad.

withTempDir :: FilePath -> (FilePath -> IO a) -> IO a Source #

Perform a function in a temporary directory and clean up.