{-# LANGUAGE TypeSynonymInstances, ScopedTypeVariables, FlexibleInstances #-}
module Network.Gitit.Types (
PageType(..)
, FileStoreType(..)
, MathMethod(..)
, AuthenticationLevel(..)
, Config(..)
, Page(..)
, SessionKey
, SessionData
, SessionGithubData
, sessionData
, sessionGithubData
, sessionDataGithubStateUrl
, sessionUser
, sessionGithubState
, sessionGithubDestination
, User(..)
, Sessions(..)
, Password(..)
, GititState(..)
, HasContext
, modifyContext
, getContext
, ContentTransformer
, Plugin(..)
, PluginData(..)
, PluginM
, runPluginM
, Context(..)
, PageLayout(..)
, Tab(..)
, Recaptcha(..)
, Params(..)
, Command(..)
, WikiState(..)
, GititServerPart
, Handler
, fromEntities
, GithubConfig
, oAuth2
, org
, githubConfig) where
import Control.Monad.Reader (ReaderT, runReaderT, mplus)
import Control.Monad.State (StateT, runStateT, get, modify)
import Control.Monad (liftM)
import System.Log.Logger (Priority(..))
import Text.Pandoc.Definition (Pandoc)
import Text.XHtml (Html)
import qualified Data.Map as M
import Data.Text (Text)
import Data.List (intersect)
import Data.Time (parseTimeM)
#if MIN_VERSION_time(1,5,0)
import Data.Time (defaultTimeLocale)
#else
import System.Locale (defaultTimeLocale)
#endif
import Data.FileStore.Types
import Network.Gitit.Server
import Text.HTML.TagSoup.Entity (lookupEntity)
import Data.Char (isSpace)
import Network.OAuth.OAuth2
data PageType = Markdown
| CommonMark
| RST
| LaTeX
| HTML
| Textile
| Org
| DocBook
| MediaWiki
deriving (Read, Show, Eq)
data FileStoreType = Git | Darcs | Mercurial deriving Show
data MathMethod = MathML | WebTeX String | RawTeX | MathJax String
deriving (Read, Show, Eq)
data AuthenticationLevel = Never | ForModify | ForRead
deriving (Read, Show, Eq, Ord)
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]),
useRecaptcha :: Bool,
recaptchaPublicKey :: String,
recaptchaPrivateKey :: String,
rpxDomain :: String,
rpxKey :: String,
compressResponses :: Bool,
useCache :: Bool,
cacheDir :: FilePath,
mimeMap :: M.Map String String,
mailCommand :: String,
resetPasswordMessage :: String,
markupHelp :: Text,
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 {
pageName :: String
, pageFormat :: PageType
, pageLHS :: Bool
, pageTOC :: Bool
, pageTitle :: String
, pageCategories :: [String]
, pageText :: String
, pageMeta :: [(String, String)]
} deriving (Read, Show)
type SessionKey = Integer
data SessionData = SessionData {
sessionUser :: Maybe String,
sessionGithubData :: Maybe SessionGithubData
} deriving (Read,Show,Eq)
data SessionGithubData = SessionGithubData {
sessionGithubState :: String,
sessionGithubDestination :: String
} deriving (Read, Show, Eq)
sessionData :: String -> SessionData
sessionData user = SessionData (Just user) Nothing
sessionDataGithubStateUrl :: String -> String -> SessionData
sessionDataGithubStateUrl githubState destination = SessionData Nothing (Just $ SessionGithubData githubState destination)
data Sessions a = Sessions {unsession::M.Map SessionKey a}
deriving (Read,Show,Eq)
data Password = Password { pSalt :: String, pHashed :: String }
deriving (Read,Show,Eq)
data User = User {
uUsername :: String,
uPassword :: Password,
uEmail :: String
} deriving (Show,Read)
data GititState = GititState {
sessions :: Sessions SessionData,
users :: M.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)
runPluginM plugin = runStateT . runReaderT plugin
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 ()
instance HasContext ContentTransformer where
getContext = get
modifyContext = modify
instance HasContext PluginM where
getContext = get
modifyContext = modify
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 = ViewTab
| EditTab
| HistoryTab
| DiscussTab
| DiffTab
deriving (Eq, Show)
data Recaptcha = Recaptcha {
recaptchaChallengeField :: String
, recaptchaResponseField :: String
} deriving (Read, Show)
instance FromData SessionKey where
fromData = readCookieValue "sid"
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
} deriving Show
instance FromReqURI [String] where
fromReqURI s = case fromReqURI s of
Just (s' :: String) ->
case reads s' of
((xs,""):_) -> xs
_ -> Nothing
Nothing -> Nothing
instance FromData Params where
fromData = do
let look' = look
un <- look' "username" `mplus` return ""
pw <- look' "password" `mplus` return ""
p2 <- look' "password2" `mplus` return ""
rv <- (look' "revision" >>= \s ->
return (if null s then Nothing else Just s))
`mplus` return Nothing
fu <- liftM Just (look' "forUser") `mplus` return Nothing
si <- liftM (parseTimeM True defaultTimeLocale "%Y-%m-%d") (look' "since")
`mplus` return Nothing
ds <- look' "destination" `mplus` return ""
ra <- look' "raw" `mplus` return ""
lt <- lookRead "limit" `mplus` return 100
pa <- look' "patterns" `mplus` return ""
gt <- look' "gotopage" `mplus` return ""
ft <- look' "filetodelete" `mplus` return ""
me <- looks "message"
fm <- liftM Just (look' "from") `mplus` return Nothing
to <- liftM Just (look' "to") `mplus` return Nothing
et <- liftM (Just . filter (/='\r')) (look' "editedText")
`mplus` return Nothing
fo <- look' "format" `mplus` return ""
sh <- look' "sha1" `mplus` return ""
lm <- look' "logMsg" `mplus` return ""
em <- look' "email" `mplus` return ""
na <- look' "full_name_1" `mplus` return ""
wn <- look' "wikiname" `mplus` return ""
pr <- (look' "printable" >> return True) `mplus` return False
ow <- liftM (=="yes") (look' "overwrite") `mplus` return False
fileparams <- liftM Just (lookFile "file") `mplus` return Nothing
let (fp, fn) = case fileparams of
Just (x,y,_) -> (x,y)
Nothing -> ("","")
ac <- look' "accessCode" `mplus` return ""
cn <- (look' "confirm" >> return True) `mplus` return False
sk <- liftM Just (readCookieValue "sid") `mplus` return Nothing
rc <- look' "recaptcha_challenge_field" `mplus` return ""
rr <- look' "recaptcha_response_field" `mplus` return ""
rk <- look' "reset_code" `mplus` return ""
rd <- (look' "redirect" >>= \r -> return (case r of
"yes" -> Just True
"no" -> Just False
_ -> Nothing)) `mplus` return Nothing
return Params { pUsername = un
, pPassword = pw
, pPassword2 = p2
, pRevision = rv
, pForUser = fu
, pSince = si
, pDestination = ds
, pRaw = ra
, pLimit = lt
, pPatterns = words pa
, pGotoPage = gt
, pFileToDelete = ft
, pMessages = me
, pFrom = fm
, pTo = to
, pEditedText = et
, pFormat = fo
, pSHA1 = sh
, pLogMsg = lm
, pEmail = em
, pFullName = na
, pWikiname = wn
, pPrintable = pr
, pOverwrite = ow
, pFilename = fn
, pFilePath = fp
, pAccessCode = ac
, pConfirm = cn
, pSessionKey = sk
, pRecaptcha = Recaptcha {
recaptchaChallengeField = rc,
recaptchaResponseField = rr }
, pResetCode = rk
, pRedirect = rd
}
data Command = Command (Maybe String) deriving Show
instance FromData Command where
fromData = do
pairs <- lookPairs
return $ case map fst pairs `intersect` commandList of
[] -> Command Nothing
(c:_) -> Command $ Just c
where commandList = ["update", "cancel", "export"]
data WikiState = WikiState {
wikiConfig :: Config
, wikiFileStore :: FileStore
}
type GititServerPart = ServerPartT (ReaderT WikiState IO)
type Handler = GititServerPart Response
fromEntities :: String -> String
fromEntities ('&':xs) =
case lookupEntity ent of
Just c -> c ++ fromEntities rest
Nothing -> '&' : fromEntities xs
where (ent, rest) = case break (\c -> isSpace c || c == ';') xs of
(zs,';':ys) -> (zs,ys)
_ -> ("",xs)
fromEntities (x:xs) = x : fromEntities xs
fromEntities [] = []
data GithubConfig = GithubConfig { oAuth2 :: OAuth2
, org :: Maybe Text
}
githubConfig :: OAuth2 -> Maybe Text -> GithubConfig
githubConfig = GithubConfig