| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Network.Gitit.Types
Description
Types for Gitit modules.
Synopsis
- 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
- deleteSummary :: String
- accessQuestion :: Maybe (String, [String])
- disableRegistration :: Bool
- 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 :: Text
- useFeed :: Bool
- baseUrl :: String
- useAbsoluteUrls :: Bool
- wikiTitle :: String
- feedDays :: Integer
- feedRefreshTime :: Integer
- pandocUserData :: Maybe FilePath
- xssSanitize :: Bool
- recentActivityDays :: Int
- githubAuth :: GithubConfig
 
- data Page = Page {}
- newtype SessionKey = SessionKey Integer
- data SessionData
- data SessionGithubData
- sessionData :: String -> SessionData
- sessionGithubData :: SessionData -> Maybe SessionGithubData
- sessionDataGithubStateUrl :: String -> String -> SessionData
- sessionUser :: SessionData -> Maybe String
- sessionGithubState :: SessionGithubData -> String
- sessionGithubDestination :: SessionGithubData -> 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
- modifyContext :: HasContext m => (Context -> Context) -> m ()
- getContext :: HasContext m => m Context
- 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 Text
- 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 FileStoreType Source #
Instances
| Show FileStoreType Source # | |
| Defined in Network.Gitit.Types Methods showsPrec :: Int -> FileStoreType -> ShowS # show :: FileStoreType -> String # showList :: [FileStoreType] -> ShowS # | |
data MathMethod Source #
Instances
| Read MathMethod Source # | |
| Defined in Network.Gitit.Types Methods readsPrec :: Int -> ReadS MathMethod # readList :: ReadS [MathMethod] # readPrec :: ReadPrec MathMethod # readListPrec :: ReadPrec [MathMethod] # | |
| Show MathMethod Source # | |
| Defined in Network.Gitit.Types Methods showsPrec :: Int -> MathMethod -> ShowS # show :: MathMethod -> String # showList :: [MathMethod] -> ShowS # | |
| Eq MathMethod Source # | |
| Defined in Network.Gitit.Types | |
data AuthenticationLevel Source #
Instances
Data structure for information read from config file.
Constructors
| Config | |
| Fields 
 | |
newtype SessionKey Source #
Constructors
| SessionKey Integer | 
Instances
| Read SessionKey Source # | |
| Defined in Network.Gitit.Types Methods readsPrec :: Int -> ReadS SessionKey # readList :: ReadS [SessionKey] # readPrec :: ReadPrec SessionKey # readListPrec :: ReadPrec [SessionKey] # | |
| Show SessionKey Source # | |
| Defined in Network.Gitit.Types Methods showsPrec :: Int -> SessionKey -> ShowS # show :: SessionKey -> String # showList :: [SessionKey] -> ShowS # | |
| Eq SessionKey Source # | |
| Defined in Network.Gitit.Types | |
| Ord SessionKey Source # | |
| Defined in Network.Gitit.Types Methods compare :: SessionKey -> SessionKey -> Ordering # (<) :: SessionKey -> SessionKey -> Bool # (<=) :: SessionKey -> SessionKey -> Bool # (>) :: SessionKey -> SessionKey -> Bool # (>=) :: SessionKey -> SessionKey -> Bool # max :: SessionKey -> SessionKey -> SessionKey # min :: SessionKey -> SessionKey -> SessionKey # | |
| FromReqURI SessionKey Source # | |
| Defined in Network.Gitit.Types Methods fromReqURI :: String -> Maybe SessionKey # | |
| FromData SessionKey Source # | |
| Defined in Network.Gitit.Types Methods | |
data SessionData Source #
Instances
| Read SessionData Source # | |
| Defined in Network.Gitit.Types Methods readsPrec :: Int -> ReadS SessionData # readList :: ReadS [SessionData] # readPrec :: ReadPrec SessionData # readListPrec :: ReadPrec [SessionData] # | |
| Show SessionData Source # | |
| Defined in Network.Gitit.Types Methods showsPrec :: Int -> SessionData -> ShowS # show :: SessionData -> String # showList :: [SessionData] -> ShowS # | |
| Eq SessionData Source # | |
| Defined in Network.Gitit.Types | |
data SessionGithubData Source #
Instances
| Read SessionGithubData Source # | |
| Defined in Network.Gitit.Types Methods readsPrec :: Int -> ReadS SessionGithubData # readList :: ReadS [SessionGithubData] # | |
| Show SessionGithubData Source # | |
| Defined in Network.Gitit.Types Methods showsPrec :: Int -> SessionGithubData -> ShowS # show :: SessionGithubData -> String # showList :: [SessionGithubData] -> ShowS # | |
| Eq SessionGithubData Source # | |
| Defined in Network.Gitit.Types Methods (==) :: SessionGithubData -> SessionGithubData -> Bool # (/=) :: SessionGithubData -> SessionGithubData -> Bool # | |
sessionData :: String -> SessionData Source #
sessionDataGithubStateUrl :: String -> String -> SessionData Source #
sessionUser :: SessionData -> Maybe String Source #
Constructors
| Sessions | |
| Fields 
 | |
data GititState Source #
Common state for all gitit wikis in an application.
Constructors
| GititState | |
| Fields 
 | |
class Monad m => HasContext m Source #
Minimal complete definition
Instances
| HasContext ContentTransformer Source # | |
| Defined in Network.Gitit.Types Methods getContext :: ContentTransformer Context Source # modifyContext :: (Context -> Context) -> ContentTransformer () Source # | |
| HasContext PluginM Source # | |
| Defined in Network.Gitit.Types | |
modifyContext :: HasContext m => (Context -> Context) -> m () Source #
getContext :: HasContext m => m Context Source #
Constructors
| PageTransform (Pandoc -> PluginM Pandoc) | |
| PreParseTransform (String -> PluginM String) | |
| PreCommitTransform (String -> PluginM String) | 
data PluginData Source #
Constructors
| PluginData | |
| Fields | |
Instances
| HasContext PluginM Source # | |
| Defined in Network.Gitit.Types | |
runPluginM :: PluginM a -> PluginData -> Context -> IO (a, Context) Source #
Constructors
| Context | |
| Fields 
 | |
Instances
| HasContext ContentTransformer Source # | |
| Defined in Network.Gitit.Types Methods getContext :: ContentTransformer Context Source # modifyContext :: (Context -> Context) -> ContentTransformer () Source # | |
| HasContext PluginM Source # | |
| Defined in Network.Gitit.Types | |
data PageLayout Source #
Abstract representation of page layout (tabs, scripts, etc.)
Constructors
| PageLayout | |
| Fields 
 | |
Constructors
| ViewTab | |
| EditTab | |
| HistoryTab | |
| DiscussTab | |
| DiffTab | 
Constructors
| Params | |
| Fields 
 | |
State for a single wiki.
Constructors
| WikiState | |
| Fields | |
Instances
| HasContext ContentTransformer Source # | |
| Defined in Network.Gitit.Types Methods getContext :: ContentTransformer Context Source # modifyContext :: (Context -> Context) -> ContentTransformer () Source # | |
type GititServerPart = ServerPartT (ReaderT WikiState IO) Source #
type Handler = GititServerPart Response Source #
fromEntities :: String -> String Source #
data GithubConfig Source #
oAuth2 :: GithubConfig -> OAuth2 Source #
githubConfig :: OAuth2 -> Maybe Text -> GithubConfig Source #