{- This module was generated from data in the Kate syntax highlighting file texinfo.xml, version 0.2, by Daniel Franke (franke.daniel@gmail.com) -} module Text.Highlighting.Kate.Syntax.Texinfo ( highlight, parseExpression, syntaxName, syntaxExtensions ) where import Text.Highlighting.Kate.Definitions import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Alert import Text.ParserCombinators.Parsec import Control.Monad (when) import Data.Map (fromList) import Data.Maybe (fromMaybe, maybeToList) -- | Full name of language. syntaxName :: String syntaxName = "Texinfo" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.texi" -- | 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 = "Texinfo" } context <- currentContext <|> (pushContext "Normal Text" >> 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 [("Texinfo",["Normal Text"])], synStLanguage = "Texinfo", synStCurrentLine = "", synStCharsParsedInLine = 0, synStPrevChar = '\n', synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} parseSourceLine = manyTill parseExpressionInternal pEndLine pEndLine = do lookAhead $ newline <|> (eof >> return '\n') context <- currentContext case context of "Normal Text" -> return () >> pHandleEndLine "singleLineComment" -> (popContext) >> pEndLine "multiLineComment" -> return () >> pHandleEndLine "nodeFolding" -> return () >> pHandleEndLine "folding" -> 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 = [("Comment","co"),("Command","fu")] parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes)) regex_'40c'28omment'29'3f'5cb = compileRegex "@c(omment)?\\b" regex_'40ignore'5cb = compileRegex "@ignore\\b" regex_'40node'5cb = compileRegex "@node\\b" regex_'40'28menu'7csmallexample'7ctable'7cmultitable'29'5cb = compileRegex "@(menu|smallexample|table|multitable)\\b" regex_'40'5b'5cw'5d'2b'28'5c'7b'28'5b'5cw'5d'2b'5b'5cs'5d'2a'29'2b'5c'7d'29'3f = compileRegex "@[\\w]+(\\{([\\w]+[\\s]*)+\\})?" regex_'40end_'28menu'7csmallexample'7ctable'7cmultitable'29'5cb = compileRegex "@end (menu|smallexample|table|multitable)\\b" defaultAttributes = [("Normal Text","Normal Text"),("singleLineComment","Comment"),("multiLineComment","Comment"),("nodeFolding","Normal Text"),("folding","Normal Text")] parseRules "Normal Text" = do (attr, result) <- (((pRegExpr regex_'40c'28omment'29'3f'5cb >>= withAttribute "Comment") >>~ pushContext "singleLineComment") <|> ((pRegExpr regex_'40ignore'5cb >>= withAttribute "Comment") >>~ pushContext "multiLineComment") <|> ((pRegExpr regex_'40node'5cb >>= withAttribute "Command") >>~ pushContext "nodeFolding") <|> ((pRegExpr regex_'40'28menu'7csmallexample'7ctable'7cmultitable'29'5cb >>= withAttribute "Command") >>~ pushContext "folding") <|> ((pRegExpr regex_'40'5b'5cw'5d'2b'28'5c'7b'28'5b'5cw'5d'2b'5b'5cs'5d'2a'29'2b'5c'7d'29'3f >>= withAttribute "Command"))) return (attr, result) parseRules "singleLineComment" = do (attr, result) <- ((Text.Highlighting.Kate.Syntax.Alert.parseExpression)) return (attr, result) parseRules "multiLineComment" = do (attr, result) <- (((pString False "@end ignore" >>= withAttribute "Comment") >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression))) return (attr, result) parseRules "nodeFolding" = do (attr, result) <- (((lookAhead (pRegExpr regex_'40node'5cb) >> return ([],"") ) >>~ (popContext)) <|> ((parseRules "Normal Text"))) return (attr, result) parseRules "folding" = do (attr, result) <- (((pRegExpr regex_'40end_'28menu'7csmallexample'7ctable'7cmultitable'29'5cb >>= withAttribute "Command") >>~ (popContext)) <|> ((parseRules "Normal Text"))) return (attr, result) parseRules "" = parseRules "Normal Text" parseRules x = fail $ "Unknown context" ++ x