gitit-0.7.3.4: Wiki using happstack, git or darcs, and pandoc.Source codeContentsIndex
Network.Gitit.Types
Description
Types for Gitit modules.
Synopsis
data PageType
= Markdown
| RST
| LaTeX
| HTML
data FileStoreType
= Git
| Darcs
| Mercurial
data MathMethod
= MathML
| JsMathScript
| RawTeX
data Config = Config {
repositoryPath :: FilePath
repositoryType :: FileStoreType
defaultPageType :: PageType
mathMethod :: MathMethod
defaultLHS :: Bool
showLHSBirdTracks :: Bool
withUser :: Handler -> Handler
authHandler :: Handler
userFile :: FilePath
sessionTimeout :: Int
templatesDir :: FilePath
logFile :: FilePath
logLevel :: Priority
staticDir :: FilePath
pluginModules :: [String]
tableOfContents :: Bool
maxUploadSize :: Integer
maxPageSize :: Integer
portNumber :: Int
debugMode :: Bool
frontPage :: String
noEdit :: [String]
noDelete :: [String]
defaultSummary :: String
accessQuestion :: Maybe (String, [String])
useRecaptcha :: Bool
recaptchaPublicKey :: String
recaptchaPrivateKey :: String
compressResponses :: Bool
useCache :: Bool
cacheDir :: FilePath
mimeMap :: Map String String
mailCommand :: String
resetPasswordMessage :: String
markupHelp :: String
useFeed :: Bool
baseUrl :: String
wikiTitle :: String
feedDays :: Integer
feedRefreshTime :: Integer
pdfExport :: Bool
pandocUserData :: Maybe FilePath
}
data Page = Page {
pageName :: String
pageFormat :: PageType
pageLHS :: Bool
pageTOC :: Bool
pageTitle :: String
pageCategories :: [String]
pageText :: String
pageMeta :: [(String, String)]
}
type SessionKey = Integer
data SessionData = SessionData {
sessionUser :: String
}
data Sessions a = Sessions {
unsession :: Map SessionKey a
}
data Password = Password {
pSalt :: String
pHashed :: String
}
data User = User {
uUsername :: String
uPassword :: Password
uEmail :: String
}
data GititState = GititState {
sessions :: Sessions SessionData
users :: 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)
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 ()
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
data Recaptcha = Recaptcha {
recaptchaChallengeField :: String
recaptchaResponseField :: String
}
data Params = Params {
pUsername :: String
pPassword :: String
pPassword2 :: String
pRevision :: Maybe String
pDestination :: String
pForUser :: Maybe String
pSince :: Maybe DateTime
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
pFileContents :: ByteString
pConfirm :: Bool
pSessionKey :: Maybe SessionKey
pRecaptcha :: Recaptcha
pResetCode :: String
}
data Command = Command (Maybe String)
data WikiState = WikiState {
wikiConfig :: Config
wikiFileStore :: FileStore
}
type GititServerPart = ServerPartT (ReaderT WikiState IO)
type Handler = GititServerPart Response
Documentation
data PageType Source
Constructors
Markdown
RST
LaTeX
HTML
show/hide Instances
data FileStoreType Source
Constructors
Git
Darcs
Mercurial
show/hide Instances
data MathMethod Source
Constructors
MathML
JsMathScript
RawTeX
show/hide Instances
data Config Source
Data structure for information read from config file.
Constructors
Config
repositoryPath :: FilePathPath of repository containing filestore
repositoryType :: FileStoreTypeType of repository
defaultPageType :: PageTypeDefault page markup type for this wiki
mathMethod :: MathMethodHow to handle LaTeX math in pages?
defaultLHS :: BoolTreat as literate haskell by default?
showLHSBirdTracks :: BoolShow Haskell code with bird tracks
withUser :: Handler -> HandlerCombinator to set REMOTE_USER request header
authHandler :: HandlerHandler for login, logout, register, etc.
userFile :: FilePathPath of users database
sessionTimeout :: IntSeconds of inactivity before session expires
templatesDir :: FilePathDirectory containing page templates
logFile :: FilePathPath of server log file
logLevel :: PrioritySeverity filter for log messages (DEBUG, INFO, NOTICE, WARNING, ERROR, CRITICAL, ALERT, EMERGENCY)
staticDir :: FilePathPath of static directory
pluginModules :: [String]Names of plugin modules to load
tableOfContents :: BoolShow table of contents on each page?
maxUploadSize :: IntegerMax size of file uploads
maxPageSize :: IntegerMax size of page uploads
portNumber :: IntPort number to serve content on
debugMode :: BoolPrint debug info to the console?
frontPage :: StringThe front page of the wiki
noEdit :: [String]Pages that cannot be edited via web
noDelete :: [String]Pages that cannot be deleted via web
defaultSummary :: StringDefault 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 :: BoolUse ReCAPTCHA for user registration.
recaptchaPublicKey :: String
recaptchaPrivateKey :: String
compressResponses :: BoolShould responses be compressed?
useCache :: BoolShould responses be cached?
cacheDir :: FilePathDirectory to hold cached pages
mimeMap :: Map String StringMap associating mime types with file extensions
mailCommand :: StringCommand to send notification emails
resetPasswordMessage :: StringText of password reset email
markupHelp :: StringMarkup syntax help for edit sidebar
useFeed :: BoolProvide an atom feed?
baseUrl :: StringBase URL of wiki, for use in feed
wikiTitle :: StringTitle of wiki, used in feed
feedDays :: IntegerNumber of days history to be included in feed
feedRefreshTime :: IntegerNumber of minutes to cache feeds before refreshing
pdfExport :: BoolAllow PDF export?
pandocUserData :: Maybe FilePathDirectory to search for pandoc customizations
data Page Source
Data for rendering a wiki page.
Constructors
Page
pageName :: String
pageFormat :: PageType
pageLHS :: Bool
pageTOC :: Bool
pageTitle :: String
pageCategories :: [String]
pageText :: String
pageMeta :: [(String, String)]
show/hide Instances
type SessionKey = IntegerSource
data SessionData Source
Constructors
SessionData
sessionUser :: String
show/hide Instances
data Sessions a Source
Constructors
Sessions
unsession :: Map SessionKey a
show/hide Instances
Eq a => Eq (Sessions a)
Read a => Read (Sessions a)
Show a => Show (Sessions a)
data Password Source
Constructors
Password
pSalt :: String
pHashed :: String
show/hide Instances
data User Source
Constructors
User
uUsername :: String
uPassword :: Password
uEmail :: String
show/hide Instances
data GititState Source
Common state for all gitit wikis in an application.
Constructors
GititState
sessions :: Sessions SessionData
users :: Map String User
templatesPath :: FilePath
renderPage :: PageLayout -> Html -> Handler
plugins :: [Plugin]
type ContentTransformer = StateT Context GititServerPartSource
data Plugin Source
Constructors
PageTransform (Pandoc -> PluginM Pandoc)
PreParseTransform (String -> PluginM String)
PreCommitTransform (String -> PluginM String)
data PluginData Source
Constructors
PluginData
pluginConfig :: Config
pluginUser :: Maybe User
pluginRequest :: Request
pluginFileStore :: FileStore
type PluginM = ReaderT PluginData (StateT Context IO)Source
runPluginM :: PluginM a -> PluginData -> Context -> IO (a, Context)Source
data Context Source
Constructors
Context
ctxFile :: String
ctxLayout :: PageLayout
ctxCacheable :: Bool
ctxTOC :: Bool
ctxBirdTracks :: Bool
ctxCategories :: [String]
ctxMeta :: [(String, String)]
class Monad m => HasContext m whereSource
Methods
getContext :: m ContextSource
modifyContext :: (Context -> Context) -> m ()Source
show/hide Instances
data PageLayout Source
Abstract representation of page layout (tabs, scripts, etc.)
Constructors
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 Source
Constructors
ViewTab
EditTab
HistoryTab
DiscussTab
DiffTab
show/hide Instances
data Recaptcha Source
Constructors
Recaptcha
recaptchaChallengeField :: String
recaptchaResponseField :: String
show/hide Instances
data Params Source
Constructors
Params
pUsername :: String
pPassword :: String
pPassword2 :: String
pRevision :: Maybe String
pDestination :: String
pForUser :: Maybe String
pSince :: Maybe DateTime
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
pFileContents :: ByteString
pConfirm :: Bool
pSessionKey :: Maybe SessionKey
pRecaptcha :: Recaptcha
pResetCode :: String
show/hide Instances
data Command Source
Constructors
Command (Maybe String)
show/hide Instances
data WikiState Source
State for a single wiki.
Constructors
WikiState
wikiConfig :: Config
wikiFileStore :: FileStore
type GititServerPart = ServerPartT (ReaderT WikiState IO)Source
type Handler = GititServerPart ResponseSource
Produced by Haddock version 2.7.2