{- This module was generated from data in the Kate syntax highlighting file mediawiki.xml, version 1.02, by -} module Text.Highlighting.Kate.Syntax.Mediawiki ( highlight, parseExpression, syntaxName, syntaxExtensions ) where import Text.Highlighting.Kate.Definitions import Text.Highlighting.Kate.Common import Text.ParserCombinators.Parsec import Control.Monad (when) import Data.Map (fromList) import Data.Maybe (fromMaybe, maybeToList) -- | Full name of language. syntaxName :: String syntaxName = "MediaWiki" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "" -- | Highlight source code using this syntax definition. highlight :: String -> Either String [SourceLine] highlight input = case runParser parseSource startingState "source" input of Left err -> Left $ show err Right result -> Right result -- | Parse an expression using appropriate local context. parseExpression :: GenParser Char SyntaxState LabeledSource parseExpression = do st <- getState let oldLang = synStLanguage st setState $ st { synStLanguage = "MediaWiki" } context <- currentContext <|> (pushContext "normal" >> currentContext) result <- parseRules context updateState $ \st -> st { synStLanguage = oldLang } return result parseSource = do lineContents <- lookAhead wholeLine updateState $ \st -> st { synStCurrentLine = lineContents } result <- manyTill parseSourceLine eof return $ map normalizeHighlighting result startingState = SyntaxState {synStContexts = fromList [("MediaWiki",["normal"])], synStLanguage = "MediaWiki", synStCurrentLine = "", synStCharsParsedInLine = 0, synStPrevChar = '\n', synStCaseSensitive = True, synStKeywordCaseSensitive = False, synStCaptures = []} parseSourceLine = manyTill parseExpressionInternal pEndLine pEndLine = do lookAhead $ newline <|> (eof >> return '\n') context <- currentContext case context of "normal" -> return () >> pHandleEndLine "Table" -> return () >> pHandleEndLine "comment" -> return () >> pHandleEndLine "URL" -> return () >> pHandleEndLine "WikiLink" -> return () >> pHandleEndLine "WikiLinkDescription" -> return () >> pHandleEndLine "Link" -> return () >> pHandleEndLine "Error" -> (popContext) >> pEndLine "Template" -> return () >> pHandleEndLine "NoWiki" -> return () >> pHandleEndLine "Unformatted" -> (popContext) >> pEndLine "Pre" -> return () >> pHandleEndLine _ -> pHandleEndLine withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" let labs = attr : maybeToList (lookup attr styles) st <- getState let oldCharsParsed = synStCharsParsedInLine st let prevchar = if null txt then '\n' else last txt updateState $ \st -> st { synStCharsParsedInLine = oldCharsParsed + length txt, synStPrevChar = prevchar } return (labs, txt) styles = [("Link","ot"),("URL","ot"),("Comment","co"),("Section","kw"),("HTML-Entity","dv"),("HTML-Tag","kw"),("Wiki-Tag","dv"),("Error","er")] parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes)) regex_'28'5b'3d'5d'7b2'2c2'7d'5b'5e'3d'5d'2b'5b'3d'5d'7b2'2c2'7d'7c'5b'3d'5d'7b3'2c3'7d'5b'5e'3d'5d'2b'5b'3d'5d'7b3'2c3'7d'7c'5b'3d'5d'7b4'2c4'7d'5b'5e'3d'5d'2b'5b'3d'5d'7b4'2c4'7d'7c'5b'3d'5d'7b5'2c5'7d'5b'5e'3d'5d'2b'5b'3d'5d'7b5'2c5'7d'29 = compileRegex "([=]{2,2}[^=]+[=]{2,2}|[=]{3,3}[^=]+[=]{3,3}|[=]{4,4}[^=]+[=]{4,4}|[=]{5,5}[^=]+[=]{5,5})" regex_'5b'7e'5d'7b3'2c4'7d = compileRegex "[~]{3,4}" regex_'5b'2a'23'3b'3a'5cs'5d'2a'5b'2a'23'3a'5d'2b = compileRegex "[*#;:\\s]*[*#:]+" regex_'5b'5b'5d'28'3f'21'5b'5b'5d'29 = compileRegex "[[](?![[])" regex_'28http'3a'7cftp'3a'7cmailto'3a'29'5b'5cS'5d'2a'28'24'7c'5b'5cs'5d'29 = compileRegex "(http:|ftp:|mailto:)[\\S]*($|[\\s])" regex_'5b'27'5d'7b2'2c'7d = compileRegex "[']{2,}" regex_'5b'3c'5d'5b'5e'3e'5d'2b'5b'3e'5d = compileRegex "[<][^>]+[>]" regex_'5b'5cs'5d = compileRegex "[\\s]" regex_'5b'2d'5d'7b4'2c'7d = compileRegex "[-]{4,}" regex_'3c'21'2d'2d'5b'5e'2d'5d'2a'2d'2d'3e = compileRegex "" defaultAttributes = [("normal","Normal"),("Table","Normal"),("comment","Comment"),("URL","Link"),("WikiLink","Link"),("WikiLinkDescription","Link"),("Link","Template"),("Error","Error"),("Template","Link"),("NoWiki","NoWiki"),("Unformatted","Unformatted"),("Pre","NoWiki")] parseRules "normal" = do (attr, result) <- (((pString False "" >>= withAttribute "Comment") >>~ (popContext)) return (attr, result) parseRules "URL" = do (attr, result) <- (((pDetectChar False ']' >>= withAttribute "Wiki-Tag") >>~ (popContext)) <|> ((pDetectChar False '\'' >>= withAttribute "Error") >>~ pushContext "Error")) return (attr, result) parseRules "WikiLink" = do (attr, result) <- (((pDetectChar False '|' >>= withAttribute "Wiki-Tag") >>~ pushContext "WikiLinkDescription") <|> ((pDetect2Chars False ']' ']' >>= withAttribute "Wiki-Tag") >>~ (popContext)) <|> ((pDetectChar False '\'' >>= withAttribute "Error") >>~ pushContext "Error")) return (attr, result) parseRules "WikiLinkDescription" = do (attr, result) <- ((lookAhead (pDetect2Chars False ']' ']') >> return ([],"") ) >>~ (popContext)) return (attr, result) parseRules "Link" = do (attr, result) <- (((pDetect2Chars False '}' '}' >>= withAttribute "Wiki-Tag") >>~ (popContext)) <|> ((pAnyChar "'[]" >>= withAttribute "Error") >>~ pushContext "Error")) return (attr, result) parseRules "Error" = pzero parseRules "Template" = do (attr, result) <- (((pDetect2Chars False '}' '}' >>= withAttribute "Wiki-Tag") >>~ (popContext)) <|> ((pDetectChar False '\'' >>= withAttribute "Error") >>~ pushContext "Error")) return (attr, result) parseRules "NoWiki" = do (attr, result) <- (((pRegExpr regex_'3c'21'2d'2d'5b'5e'2d'5d'2a'2d'2d'3e >>= withAttribute "NoWiki")) <|> ((pString False "" >>= withAttribute "Wiki-Tag") >>~ (popContext)) <|> ((pRegExpr regex_'5b'3c'5d'5b'5e'3e'5d'2b'5b'3e'5d >>= withAttribute "HTML-Tag")) <|> ((pString False "
" >>= withAttribute "HTML-Tag") >>~ pushContext "Pre"))
     return (attr, result)

parseRules "Unformatted" = 
  pzero

parseRules "Pre" = 
  do (attr, result) <- ((pString False "
" >>= withAttribute "Wiki-Tag") >>~ (popContext)) return (attr, result) parseRules "" = parseRules "normal" parseRules x = fail $ "Unknown context" ++ x