Safe Haskell | None |
---|---|
Language | Haskell98 |
Types for Gitit modules.
- data PageType
- data FileStoreType
- data MathMethod
- data AuthenticationLevel
- data Config = Config {
- repositoryPath :: FilePath
- repositoryType :: FileStoreType
- defaultPageType :: PageType
- defaultExtension :: String
- mathMethod :: MathMethod
- defaultLHS :: Bool
- showLHSBirdTracks :: Bool
- withUser :: Handler -> Handler
- requireAuthentication :: AuthenticationLevel
- authHandler :: Handler
- userFile :: FilePath
- sessionTimeout :: Int
- templatesDir :: FilePath
- logFile :: FilePath
- logLevel :: Priority
- staticDir :: FilePath
- pluginModules :: [String]
- tableOfContents :: Bool
- maxUploadSize :: Integer
- maxPageSize :: Integer
- address :: String
- portNumber :: Int
- debugMode :: Bool
- frontPage :: String
- noEdit :: [String]
- noDelete :: [String]
- defaultSummary :: String
- accessQuestion :: Maybe (String, [String])
- useRecaptcha :: Bool
- recaptchaPublicKey :: String
- recaptchaPrivateKey :: String
- rpxDomain :: String
- rpxKey :: String
- compressResponses :: Bool
- useCache :: Bool
- cacheDir :: FilePath
- mimeMap :: Map String String
- mailCommand :: String
- resetPasswordMessage :: String
- markupHelp :: String
- useFeed :: Bool
- baseUrl :: String
- useAbsoluteUrls :: Bool
- wikiTitle :: String
- feedDays :: Integer
- feedRefreshTime :: Integer
- pdfExport :: Bool
- pandocUserData :: Maybe FilePath
- xssSanitize :: Bool
- recentActivityDays :: Int
- githubAuth :: GithubConfig
- data Page = Page {}
- type SessionKey = Integer
- data SessionData
- sessionData :: String -> SessionData
- sessionDataGithubState :: String -> SessionData
- sessionUser :: SessionData -> Maybe String
- sessionGithubState :: SessionData -> Maybe String
- data User = User {}
- data Sessions a = Sessions {
- unsession :: Map SessionKey a
- data Password = Password {}
- data GititState = GititState {
- sessions :: Sessions SessionData
- users :: Map String User
- templatesPath :: FilePath
- renderPage :: PageLayout -> Html -> Handler
- plugins :: [Plugin]
- class Monad m => HasContext m where
- getContext :: m Context
- modifyContext :: (Context -> Context) -> m ()
- type ContentTransformer = StateT Context GititServerPart
- data Plugin
- = PageTransform (Pandoc -> PluginM Pandoc)
- | PreParseTransform (String -> PluginM String)
- | PreCommitTransform (String -> PluginM String)
- data PluginData = PluginData {}
- 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)]
- 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
- data Recaptcha = Recaptcha {}
- 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
- data Command = Command (Maybe String)
- data WikiState = WikiState {}
- type GititServerPart = ServerPartT (ReaderT WikiState IO)
- type Handler = GititServerPart Response
- fromEntities :: String -> String
- data GithubConfig
- oAuth2 :: GithubConfig -> OAuth2
- org :: GithubConfig -> Maybe Text
- githubConfig :: OAuth2 -> Maybe Text -> GithubConfig
Documentation
data MathMethod Source
Data structure for information read from config file.
Config | |
|
Data for rendering a wiki page.
type SessionKey = Integer Source
sessionData :: String -> SessionData Source
sessionUser :: SessionData -> Maybe String Source
Sessions | |
|
data GititState Source
Common state for all gitit wikis in an application.
GititState | |
|
class Monad m => HasContext m where Source
getContext :: m Context Source
modifyContext :: (Context -> Context) -> m () Source
runPluginM :: PluginM a -> PluginData -> Context -> IO (a, Context) Source
Context | |
|
data PageLayout Source
Abstract representation of page layout (tabs, scripts, etc.)
PageLayout | |
|
Params | |
|
State for a single wiki.
type GititServerPart = ServerPartT (ReaderT WikiState IO) Source
type Handler = GititServerPart Response Source
fromEntities :: String -> String Source
data GithubConfig Source
oAuth2 :: GithubConfig -> OAuth2 Source
org :: GithubConfig -> Maybe Text Source
githubConfig :: OAuth2 -> Maybe Text -> GithubConfig Source