{- This module was generated from data in the Kate syntax highlighting file latex.xml, version 1.48, by Jeroen Wijnhout (Jeroen.Wijnhout@kdemail.net)+Holger Danielsson (holger.danielsson@versanet.de)+Michel Ludwig (michel.ludwig@kdemail.net)+Thomas Braun (thomas.braun@virtuell-zuhause.de) -} module Text.Highlighting.Kate.Syntax.Latex (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import Text.ParserCombinators.Parsec hiding (State) import Control.Monad.State import Data.Char (isSpace) import Data.Maybe (fromMaybe) -- | Full name of language. syntaxName :: String syntaxName = "LaTeX" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.tex;*.ltx;*.dtx;*.sty;*.cls;*.bbx;*.cbx;*.lbx;" -- | Highlight source code using this syntax definition. highlight :: String -> [SourceLine] highlight input = evalState (mapM parseSourceLine $ lines input) startingState parseSourceLine :: String -> State SyntaxState SourceLine parseSourceLine = mkParseSourceLine parseExpression -- | Parse an expression using appropriate local context. parseExpression :: KateParser Token parseExpression = do (lang,cont) <- currentContext let defAttr = fromMaybe NormalTok $ lookup (lang,cont) defaultAttributes result <- if lang == "LaTeX" then parseRules (lang,cont) <|> (pDefault >>= withAttribute defAttr) else parseRules ("LaTeX","Normal Text") optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("LaTeX","Normal Text")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext case context of ("LaTeX","Normal Text") -> return () ("LaTeX","NoWeb") -> return () ("LaTeX","Sectioning") -> return () ("LaTeX","SectioningInside") -> return () ("LaTeX","SectioningContrSeq") -> (popContext) >> pEndLine ("LaTeX","SectioningMathMode") -> return () ("LaTeX","SectioningMathContrSeq") -> (popContext) >> pEndLine ("LaTeX","Footnoting") -> return () ("LaTeX","FootnotingInside") -> return () ("LaTeX","FootnotingMathMode") -> return () ("LaTeX","NewCommand") -> return () ("LaTeX","DefCommand") -> return () ("LaTeX","CommandParameterStart") -> return () ("LaTeX","CommandParameter") -> return () ("LaTeX","ContrSeq") -> (popContext) >> pEndLine ("LaTeX","ToEndOfLine") -> (popContext) >> pEndLine ("LaTeX","Verb") -> (popContext >> popContext) >> pEndLine ("LaTeX","VerbEnd") -> (popContext >> popContext >> popContext) >> pEndLine ("LaTeX","Label") -> return () ("LaTeX","LabelOption") -> return () ("LaTeX","LabelParameter") -> return () ("LaTeX","FancyLabel") -> return () ("LaTeX","FancyLabelParameter") -> return () ("LaTeX","FancyLabelRoundBrackets") -> return () ("LaTeX","FindEndEnvironment") -> return () ("LaTeX","EndEnvironment") -> return () ("LaTeX","EndLatexEnv") -> return () ("LaTeX","FindBeginEnvironment") -> return () ("LaTeX","BeginEnvironment") -> return () ("LaTeX","LatexEnv") -> return () ("LaTeX","VerbatimEnv") -> return () ("LaTeX","VerbatimEnvParam") -> return () ("LaTeX","Verbatim") -> return () ("LaTeX","VerbFindEnd") -> (popContext) >> pEndLine ("LaTeX","CommentEnv") -> return () ("LaTeX","BlockComment") -> return () ("LaTeX","CommFindEnd") -> (popContext) >> pEndLine ("LaTeX","MathEnv") -> return () ("LaTeX","MathEnvParam") -> return () ("LaTeX","EnvCommon") -> return () ("LaTeX","MathModeEnv") -> return () ("LaTeX","MathFindEnd") -> (popContext) >> pEndLine ("LaTeX","TabEnv") -> return () ("LaTeX","Tab") -> return () ("LaTeX","Column Separator") -> return () ("LaTeX","TabFindEnd") -> (popContext) >> pEndLine ("LaTeX","MathMode") -> return () ("LaTeX","MathModeDisplay") -> return () ("LaTeX","MathModeEquation") -> return () ("LaTeX","MathModeEnsure") -> return () ("LaTeX","MathModeCommon") -> return () ("LaTeX","MathContrSeq") -> (popContext) >> pEndLine ("LaTeX","MathModeText") -> return () ("LaTeX","MathModeTextParameterStart") -> return () ("LaTeX","MathModeTextParameter") -> return () ("LaTeX","Multiline Comment") -> return () ("LaTeX","Comment") -> (popContext) >> pEndLine _ -> return () withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" updateState $ \st -> st { synStPrevChar = last txt , synStPrevNonspace = synStPrevNonspace st || not (all isSpace txt) } return (attr, txt) regex_'5c'5cbegin'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex "\\\\begin(?=[^a-zA-Z])" regex_'5c'5cend'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex "\\\\end(?=[^a-zA-Z])" regex_'5c'5c'28cite'7cparencite'7cautocite'7cAutocite'7ccitetitle'29'5c'2a'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex "\\\\(cite|parencite|autocite|Autocite|citetitle)\\*(?=[^a-zA-Z])" regex_'5c'5c'28cites'7cCites'7cparencites'7cParencites'7cautocites'7cAutocites'7csupercites'7cfootcites'7cFootcites'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex "\\\\(cites|Cites|parencites|Parencites|autocites|Autocites|supercites|footcites|Footcites)(?=[^a-zA-Z])" regex_'5c'5c'28cite'7cnocite'7cCite'7cparencite'7cParencite'7cfootcite'7cFootcite'7ctextcite'7cTextcite'7csupercite'7cautocite'7cAutocite'7cciteauthor'7cCiteauthor'7ccitetitle'7cciteyear'7cciteurl'7cnocite'7cfullcite'7cfootfullcite'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex "\\\\(cite|nocite|Cite|parencite|Parencite|footcite|Footcite|textcite|Textcite|supercite|autocite|Autocite|citeauthor|Citeauthor|citetitle|citeyear|citeurl|nocite|fullcite|footfullcite)(?=[^a-zA-Z])" regex_'5c'5c'28subref'5c'2a'3f'7ccref'5c'2a'3f'7clabel'7cpageref'7cautoref'7cref'7cvpageref'7cvref'7cpagecite'7ceqref'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex "\\\\(subref\\*?|cref\\*?|label|pageref|autoref|ref|vpageref|vref|pagecite|eqref)(?=[^a-zA-Z])" regex_'5c'5c'28part'7cchapter'7csection'7csubsection'7csubsubsection'7cparagraph'7csubparagraph'29'5c'2a'3f'5cs'2a'28'3f'3d'5b'5c'7b'5c'5b'5d'29 = compileRegex "\\\\(part|chapter|section|subsection|subsubsection|paragraph|subparagraph)\\*?\\s*(?=[\\{\\[])" regex_'5c'5c'28footnote'29'5c'2a'3f'5cs'2a'28'3f'3d'5b'5c'7b'5c'5b'5d'29 = compileRegex "\\\\(footnote)\\*?\\s*(?=[\\{\\[])" regex_'5c'5c'28renewcommand'7cprovidenewcommand'7cnewcommand'29'5c'2a'3f'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex "\\\\(renewcommand|providenewcommand|newcommand)\\*?(?=[^a-zA-Z])" regex_'5c'5c'28e'7cg'7cx'29'3fdef'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex "\\\\(e|g|x)?def(?=[^a-zA-Z])" regex_'3c'3c'2e'2a'3e'3e'3d = compileRegex "<<.*>>=" regex_'25'5cs'2aBEGIN'2e'2a'24 = compileRegex "%\\s*BEGIN.*$" regex_'25'5cs'2aEND'2e'2a'24 = compileRegex "%\\s*END.*$" regex_'5cs'2a'40'5cs'2a = compileRegex "\\s*@\\s*" regex_'5c'5b'5b'5e'5c'5d'5d'2a'5c'5d = compileRegex "\\[[^\\]]*\\]" regex_'5ba'2dzA'2dZ'5d'2b'28'5c'2b'3f'7c'5c'2a'7b0'2c3'7d'29 = compileRegex "[a-zA-Z]+(\\+?|\\*{0,3})" regex_'5b'5ea'2dzA'2dZ'5d = compileRegex "[^a-zA-Z]" regex_'5ba'2dzA'2dZ'5d'2b'5c'2a'3f = compileRegex "[a-zA-Z]+\\*?" regex_'5cs'2a'5c'7b'5cs'2a'5c'5c'5ba'2dzA'2dZ'5d'2b'5cs'2a'5c'7d'28'5c'5b'5cd'5c'5d'28'5c'5b'5b'5e'5c'5d'5d'2a'5c'5d'29'3f'29'3f'5c'7b = compileRegex "\\s*\\{\\s*\\\\[a-zA-Z]+\\s*\\}(\\[\\d\\](\\[[^\\]]*\\])?)?\\{" regex_'5cs'2a'5c'5c'5ba'2dzA'2dZ'5d'2b'5b'5e'5c'7b'5d'2a'5c'7b = compileRegex "\\s*\\\\[a-zA-Z]+[^\\{]*\\{" regex_'5c'5c'2e = compileRegex "\\\\." regex_'28Verb'7cverb'7clstinline'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex "(Verb|verb|lstinline)(?=[^a-zA-Z])" regex_'5ba'2dzA'2dZ'40'5d'2b'28'5c'2b'3f'7c'5c'2a'7b0'2c3'7d'29 = compileRegex "[a-zA-Z@]+(\\+?|\\*{0,3})" regex_'5cs'2a'5c'7b'5cs'2a = compileRegex "\\s*\\{\\s*" regex_'5cs'2a'5c'5b'5cs'2a = compileRegex "\\s*\\[\\s*" regex_'5b'5e'5c'5b'5c'7b'5d'2b = compileRegex "[^\\[\\{]+" regex_'5cs'2a'5c'5d'5cs'2a = compileRegex "\\s*\\]\\s*" regex_'5cs'2a'5c'7d'5cs'2a = compileRegex "\\s*\\}\\s*" regex_'5cs'2a'5c'28'5cs'2a = compileRegex "\\s*\\(\\s*" regex_'5cs'2a'5c'29'5cs'2a = compileRegex "\\s*\\)\\s*" regex_'5cS = compileRegex "\\S" regex_'5ba'2dzA'2dZ'5d = compileRegex "[a-zA-Z]" regex_'5cs'2b = compileRegex "\\s+" regex_'5ba'2dzA'2dZ'5d'2b'28'5c'2a'29'3f = compileRegex "[a-zA-Z]+(\\*)?" regex_'28lstlisting'7c'28B'7cL'29'3fVerbatim'29 = compileRegex "(lstlisting|(B|L)?Verbatim)" regex_'28verbatim'7cboxedverbatim'29 = compileRegex "(verbatim|boxedverbatim)" regex_comment = compileRegex "comment" regex_'28alignat'7cxalignat'7cxxalignat'29 = compileRegex "(alignat|xalignat|xxalignat)" regex_'28equation'7cdisplaymath'7ceqnarray'7csubeqnarray'7cmath'7cmultline'7cgather'7calign'7cflalign'7cIEEEeqnarray'7cIEEEeqnarraybox'7csmallmatrix'7cpmatrix'7cbmatrix'7cBmatrix'7cvmatrix'7cVmatrix'29 = compileRegex "(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|IEEEeqnarray|IEEEeqnarraybox|smallmatrix|pmatrix|bmatrix|Bmatrix|vmatrix|Vmatrix)" regex_'28tabularx'7ctabular'7csupertabular'7cmpsupertabular'7cxtabular'7cmpxtabular'7clongtable'29 = compileRegex "(tabularx|tabular|supertabular|mpsupertabular|xtabular|mpxtabular|longtable)" regex_'5b'5ea'2dzA'2dZ'5cxd7'5d = compileRegex "[^a-zA-Z\\xd7]" regex_'5ba'2dzA'2dZ'5d'2b = compileRegex "[a-zA-Z]+" regex_'5c'5cend'28'3f'3d'5cs'2a'5c'7b'28verbatim'7clstlisting'7cboxedverbatim'7c'28B'7cL'29'3fVerbatim'29'5c'2a'3f'5c'7d'29 = compileRegex "\\\\end(?=\\s*\\{(verbatim|lstlisting|boxedverbatim|(B|L)?Verbatim)\\*?\\})" regex_'5cs'2a'5c'7b = compileRegex "\\s*\\{" regex_'28verbatim'7clstlisting'7cboxedverbatim'7c'28B'7cL'29'3fVerbatim'29'5c'2a'3f = compileRegex "(verbatim|lstlisting|boxedverbatim|(B|L)?Verbatim)\\*?" regex_'5c'5cend'28'3f'3d'5cs'2a'5c'7bcomment'5c'2a'3f'5c'7d'29 = compileRegex "\\\\end(?=\\s*\\{comment\\*?\\})" regex_comment'5c'2a'3f = compileRegex "comment\\*?" regex_'5c'7d'5c'7b'5b'5e'5c'7d'5d'2a'5c'7d = compileRegex "\\}\\{[^\\}]*\\}" regex_'5c'2a'28'3f'3d'5c'7d'29 = compileRegex "\\*(?=\\})" regex_'5c'2a'5b'5e'5c'7d'5d'2a = compileRegex "\\*[^\\}]*" regex_'5b'5ea'2dzA'2dZ'5cxd7'5d'5b'5e'5c'7d'5d'2a = compileRegex "[^a-zA-Z\\xd7][^\\}]*" regex_'5c'5c'28text'7cintertext'7cmbox'29'5cs'2a'28'3f'3d'5c'7b'29 = compileRegex "\\\\(text|intertext|mbox)\\s*(?=\\{)" regex_'28equation'7cdisplaymath'7ceqnarray'7csubeqnarray'7cmath'7cmultline'7cgather'7calign'7cflalign'7calignat'7cxalignat'7cxxalignat'7cIEEEeqnarray'7cIEEEeqnarraybox'7csmallmatrix'7cpmatrix'7cbmatrix'7cBmatrix'7cvmatrix'7cVmatrix'29'5c'2a'3f = compileRegex "(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|alignat|xalignat|xxalignat|IEEEeqnarray|IEEEeqnarraybox|smallmatrix|pmatrix|bmatrix|Bmatrix|vmatrix|Vmatrix)\\*?" regex_'5c'5cend'28'3f'3d'5cs'2a'5c'7b'28tabularx'7ctabular'7csupertabular'7cmpsupertabular'7cxtabular'7cmpxtabular'7clongtable'29'5c'2a'3f'5c'7d'29 = compileRegex "\\\\end(?=\\s*\\{(tabularx|tabular|supertabular|mpsupertabular|xtabular|mpxtabular|longtable)\\*?\\})" regex_'2e = compileRegex "." regex_'28tabularx'7ctabular'7csupertabular'7cmpsupertabular'7cxtabular'7cmpxtabular'7clongtable'29'5c'2a'3f = compileRegex "(tabularx|tabular|supertabular|mpsupertabular|xtabular|mpxtabular|longtable)\\*?" regex_'5c'5c'28begin'7cend'29'5cs'2a'5c'7b'28equation'7cdisplaymath'7ceqnarray'7csubeqnarray'7cmath'7cmultline'7cgather'7calign'7cflalign'7calignat'7cxalignat'7cxxalignat'7cIEEEeqnarray'29'5c'2a'3f'5c'7d = compileRegex "\\\\(begin|end)\\s*\\{(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|alignat|xalignat|xxalignat|IEEEeqnarray)\\*?\\}" regex_'5c'24'2e'2a'5c'24 = compileRegex "\\$.*\\$" regex_'28FIXME'7cTODO'29'3a'3f = compileRegex "(FIXME|TODO):?" defaultAttributes = [(("LaTeX","Normal Text"),NormalTok),(("LaTeX","NoWeb"),NormalTok),(("LaTeX","Sectioning"),NormalTok),(("LaTeX","SectioningInside"),NormalTok),(("LaTeX","SectioningContrSeq"),NormalTok),(("LaTeX","SectioningMathMode"),NormalTok),(("LaTeX","SectioningMathContrSeq"),NormalTok),(("LaTeX","Footnoting"),NormalTok),(("LaTeX","FootnotingInside"),NormalTok),(("LaTeX","FootnotingMathMode"),NormalTok),(("LaTeX","NewCommand"),NormalTok),(("LaTeX","DefCommand"),NormalTok),(("LaTeX","CommandParameterStart"),NormalTok),(("LaTeX","CommandParameter"),NormalTok),(("LaTeX","ContrSeq"),NormalTok),(("LaTeX","ToEndOfLine"),NormalTok),(("LaTeX","Verb"),NormalTok),(("LaTeX","VerbEnd"),NormalTok),(("LaTeX","Label"),NormalTok),(("LaTeX","LabelOption"),NormalTok),(("LaTeX","LabelParameter"),NormalTok),(("LaTeX","FancyLabel"),NormalTok),(("LaTeX","FancyLabelParameter"),NormalTok),(("LaTeX","FancyLabelRoundBrackets"),NormalTok),(("LaTeX","FindEndEnvironment"),NormalTok),(("LaTeX","EndEnvironment"),NormalTok),(("LaTeX","EndLatexEnv"),NormalTok),(("LaTeX","FindBeginEnvironment"),NormalTok),(("LaTeX","BeginEnvironment"),NormalTok),(("LaTeX","LatexEnv"),NormalTok),(("LaTeX","VerbatimEnv"),NormalTok),(("LaTeX","VerbatimEnvParam"),NormalTok),(("LaTeX","Verbatim"),NormalTok),(("LaTeX","VerbFindEnd"),NormalTok),(("LaTeX","CommentEnv"),NormalTok),(("LaTeX","BlockComment"),CommentTok),(("LaTeX","CommFindEnd"),NormalTok),(("LaTeX","MathEnv"),NormalTok),(("LaTeX","MathEnvParam"),NormalTok),(("LaTeX","EnvCommon"),NormalTok),(("LaTeX","MathModeEnv"),NormalTok),(("LaTeX","MathFindEnd"),NormalTok),(("LaTeX","TabEnv"),NormalTok),(("LaTeX","Tab"),NormalTok),(("LaTeX","Column Separator"),NormalTok),(("LaTeX","TabFindEnd"),NormalTok),(("LaTeX","MathMode"),NormalTok),(("LaTeX","MathModeDisplay"),NormalTok),(("LaTeX","MathModeEquation"),NormalTok),(("LaTeX","MathModeEnsure"),NormalTok),(("LaTeX","MathModeCommon"),NormalTok),(("LaTeX","MathContrSeq"),NormalTok),(("LaTeX","MathModeText"),NormalTok),(("LaTeX","MathModeTextParameterStart"),NormalTok),(("LaTeX","MathModeTextParameter"),NormalTok),(("LaTeX","Multiline Comment"),CommentTok),(("LaTeX","Comment"),CommentTok)] parseRules ("LaTeX","Normal Text") = (((pRegExpr regex_'5c'5cbegin'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FindBeginEnvironment")) <|> ((pRegExpr regex_'5c'5cend'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FindEndEnvironment")) <|> ((pRegExpr regex_'5c'5c'28cite'7cparencite'7cautocite'7cAutocite'7ccitetitle'29'5c'2a'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Label")) <|> ((pRegExpr regex_'5c'5c'28cites'7cCites'7cparencites'7cParencites'7cautocites'7cAutocites'7csupercites'7cfootcites'7cFootcites'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FancyLabel")) <|> ((pRegExpr regex_'5c'5c'28cite'7cnocite'7cCite'7cparencite'7cParencite'7cfootcite'7cFootcite'7ctextcite'7cTextcite'7csupercite'7cautocite'7cAutocite'7cciteauthor'7cCiteauthor'7ccitetitle'7cciteyear'7cciteurl'7cnocite'7cfullcite'7cfootfullcite'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Label")) <|> ((pRegExpr regex_'5c'5c'28subref'5c'2a'3f'7ccref'5c'2a'3f'7clabel'7cpageref'7cautoref'7cref'7cvpageref'7cvref'7cpagecite'7ceqref'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Label")) <|> ((pRegExpr regex_'5c'5c'28part'7cchapter'7csection'7csubsection'7csubsubsection'7cparagraph'7csubparagraph'29'5c'2a'3f'5cs'2a'28'3f'3d'5b'5c'7b'5c'5b'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Sectioning")) <|> ((pRegExpr regex_'5c'5c'28footnote'29'5c'2a'3f'5cs'2a'28'3f'3d'5b'5c'7b'5c'5b'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Footnoting")) <|> ((pRegExpr regex_'5c'5c'28renewcommand'7cprovidenewcommand'7cnewcommand'29'5c'2a'3f'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","NewCommand")) <|> ((pRegExpr regex_'5c'5c'28e'7cg'7cx'29'3fdef'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","DefCommand")) <|> ((pRegExpr regex_'3c'3c'2e'2a'3e'3e'3d >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","NoWeb")) <|> ((pString False "\\(" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathMode")) <|> ((pString False "\\[" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeEquation")) <|> ((pString False "\\iffalse" >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Multiline Comment")) <|> ((pString False "\\ensuremath{" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeEnsure")) <|> ((pDetectChar False '\\' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","ContrSeq")) <|> ((pString False "$$" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeDisplay")) <|> ((pDetectChar False '$' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathMode")) <|> ((pFirstNonSpace >> pRegExpr regex_'25'5cs'2aBEGIN'2e'2a'24 >>= withAttribute RegionMarkerTok)) <|> ((pFirstNonSpace >> pRegExpr regex_'25'5cs'2aEND'2e'2a'24 >>= withAttribute RegionMarkerTok)) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment")) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok))) parseRules ("LaTeX","NoWeb") = ((pColumn 0 >> pRegExpr regex_'5cs'2a'40'5cs'2a >>= withAttribute NormalTok) >>~ (popContext)) parseRules ("LaTeX","Sectioning") = (((pRegExpr regex_'5c'5b'5b'5e'5c'5d'5d'2a'5c'5d >>= withAttribute NormalTok)) <|> ((pDetectChar False ' ' >>= withAttribute NormalTok)) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","SectioningInside")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment")) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","SectioningInside") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","SectioningInside")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pString False "\\(" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","SectioningMathMode")) <|> ((pDetectChar False '\\' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","SectioningContrSeq")) <|> ((pDetectChar False '$' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","SectioningMathMode")) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment")) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok))) parseRules ("LaTeX","SectioningContrSeq") = (((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b'28'5c'2b'3f'7c'5c'2a'7b0'2c3'7d'29 >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute NormalTok) >>~ (popContext))) parseRules ("LaTeX","SectioningMathMode") = (((pString False "$$" >>= withAttribute AlertTok)) <|> ((pDetectChar False '$' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute AlertTok)) <|> ((pDetectChar False '\\' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","SectioningMathContrSeq")) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment")) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok))) parseRules ("LaTeX","SectioningMathContrSeq") = (((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b'5c'2a'3f >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute NormalTok) >>~ (popContext))) parseRules ("LaTeX","Footnoting") = (((pRegExpr regex_'5c'5b'5b'5e'5c'5d'5d'2a'5c'5d >>= withAttribute NormalTok)) <|> ((pDetectChar False ' ' >>= withAttribute NormalTok)) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FootnotingInside")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment")) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","FootnotingInside") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FootnotingInside")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pString False "\\(" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FootnotingMathMode")) <|> ((pDetectChar False '$' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FootnotingMathMode")) <|> ((parseRules ("LaTeX","Normal Text")))) parseRules ("LaTeX","FootnotingMathMode") = (((pString False "$$" >>= withAttribute AlertTok)) <|> ((pDetectChar False '$' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute AlertTok)) <|> ((parseRules ("LaTeX","MathMode")))) parseRules ("LaTeX","NewCommand") = (((pRegExpr regex_'5cs'2a'5c'7b'5cs'2a'5c'5c'5ba'2dzA'2dZ'5d'2b'5cs'2a'5c'7d'28'5c'5b'5cd'5c'5d'28'5c'5b'5b'5e'5c'5d'5d'2a'5c'5d'29'3f'29'3f'5c'7b >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","CommandParameterStart")) <|> ((pDetectChar False '}' >>= withAttribute AlertTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","DefCommand") = (((pRegExpr regex_'5cs'2a'5c'5c'5ba'2dzA'2dZ'5d'2b'5b'5e'5c'7b'5d'2a'5c'7b >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","CommandParameterStart")) <|> ((pDetectChar False '}' >>= withAttribute AlertTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","CommandParameterStart") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","CommandParameter")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((pRegExpr regex_'5c'5c'2e >>= withAttribute NormalTok)) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))) parseRules ("LaTeX","CommandParameter") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","CommandParameter")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5c'2e >>= withAttribute NormalTok)) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))) parseRules ("LaTeX","ContrSeq") = (((pString False "verb*" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Verb")) <|> ((pRegExpr regex_'28Verb'7cverb'7clstinline'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Verb")) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'40'5d'2b'28'5c'2b'3f'7c'5c'2a'7b0'2c3'7d'29 >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute NormalTok) >>~ (popContext))) parseRules ("LaTeX","ToEndOfLine") = pzero parseRules ("LaTeX","Verb") = ((pRegExprDynamic "(.)" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","VerbEnd")) parseRules ("LaTeX","VerbEnd") = (((pString True "%1" >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext)) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExprDynamic "[^%1\\xd7]*" >>= withAttribute NormalTok))) parseRules ("LaTeX","Label") = (((pRegExpr regex_'5cs'2a'5c'7b'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","LabelParameter")) <|> ((pRegExpr regex_'5cs'2a'5c'5b'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","LabelOption")) <|> ((pRegExpr regex_'5b'5e'5c'5b'5c'7b'5d'2b >>= withAttribute AlertTok))) parseRules ("LaTeX","LabelOption") = (((pString False "\\(" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathMode")) <|> ((pDetectChar False '\\' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","ContrSeq")) <|> ((pDetectChar False '$' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathMode")) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment")) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cs'2a'5c'5d'5cs'2a >>= withAttribute NormalTok) >>~ (popContext))) parseRules ("LaTeX","LabelParameter") = (((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cs'2a'5c'7d'5cs'2a >>= withAttribute NormalTok) >>~ (popContext >> popContext))) parseRules ("LaTeX","FancyLabel") = (((pRegExpr regex_'5cs'2a'5c'7b'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FancyLabelParameter")) <|> ((pRegExpr regex_'5cs'2a'5c'5b'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","LabelOption")) <|> ((pRegExpr regex_'5cs'2a'5c'28'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FancyLabelRoundBrackets")) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","FancyLabelParameter") = (((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cs'2a'5c'7d'5cs'2a >>= withAttribute NormalTok) >>~ (popContext))) parseRules ("LaTeX","FancyLabelRoundBrackets") = (((pString False "\\(" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathMode")) <|> ((pDetectChar False '\\' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","ContrSeq")) <|> ((pDetectChar False '$' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathMode")) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment")) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cs'2a'5c'29'5cs'2a >>= withAttribute NormalTok) >>~ (popContext))) parseRules ("LaTeX","FindEndEnvironment") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","EndEnvironment")) <|> ((pRegExpr regex_'5cS >>= withAttribute NormalTok) >>~ (popContext))) parseRules ("LaTeX","EndEnvironment") = (((pRegExpr regex_'5ba'2dzA'2dZ'5d >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","EndLatexEnv")) <|> ((pRegExpr regex_'5cs'2b >>= withAttribute AlertTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute AlertTok) >>~ (popContext))) parseRules ("LaTeX","EndLatexEnv") = (((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b'28'5c'2a'29'3f >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cs'2b >>= withAttribute AlertTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5d >>= withAttribute AlertTok) >>~ (popContext >> popContext >> popContext))) parseRules ("LaTeX","FindBeginEnvironment") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","BeginEnvironment")) <|> ((pRegExpr regex_'5cS >>= withAttribute NormalTok) >>~ (popContext))) parseRules ("LaTeX","BeginEnvironment") = (((pRegExpr regex_'28lstlisting'7c'28B'7cL'29'3fVerbatim'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","VerbatimEnvParam")) <|> ((pRegExpr regex_'28verbatim'7cboxedverbatim'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","VerbatimEnv")) <|> ((pRegExpr regex_comment >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","CommentEnv")) <|> ((pRegExpr regex_'28alignat'7cxalignat'7cxxalignat'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathEnvParam")) <|> ((pRegExpr regex_'28equation'7cdisplaymath'7ceqnarray'7csubeqnarray'7cmath'7cmultline'7cgather'7calign'7cflalign'7cIEEEeqnarray'7cIEEEeqnarraybox'7csmallmatrix'7cpmatrix'7cbmatrix'7cBmatrix'7cvmatrix'7cVmatrix'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathEnv")) <|> ((pRegExpr regex_'28tabularx'7ctabular'7csupertabular'7cmpsupertabular'7cxtabular'7cmpxtabular'7clongtable'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","TabEnv")) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5d >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","LatexEnv")) <|> ((pRegExpr regex_'5cs'2b >>= withAttribute AlertTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b'5ea'2dzA'2dZ'5cxd7'5d >>= withAttribute AlertTok) >>~ (popContext))) parseRules ("LaTeX","LatexEnv") = (((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cs'2b >>= withAttribute AlertTok)) <|> ((parseRules ("LaTeX","EnvCommon")))) parseRules ("LaTeX","VerbatimEnv") = (((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Verbatim")) <|> ((lookAhead (pRegExpr regex_'5ba'2dzA'2dZ'5d) >> (popContext) >> currentContext >>= parseRules)) <|> ((parseRules ("LaTeX","EnvCommon"))) <|> ((popContext >> popContext >> popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","VerbatimEnvParam") = (((pDetect2Chars False '}' '[' >>= withAttribute NormalTok)) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Verbatim")) <|> ((pDetectChar False ']' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Verbatim"))) parseRules ("LaTeX","Verbatim") = (((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'5cend'28'3f'3d'5cs'2a'5c'7b'28verbatim'7clstlisting'7cboxedverbatim'7c'28B'7cL'29'3fVerbatim'29'5c'2a'3f'5c'7d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","VerbFindEnd"))) parseRules ("LaTeX","VerbFindEnd") = (((pRegExpr regex_'5cs'2a'5c'7b >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28verbatim'7clstlisting'7cboxedverbatim'7c'28B'7cL'29'3fVerbatim'29'5c'2a'3f >>= withAttribute NormalTok)) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext >> popContext >> popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","CommentEnv") = (((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","BlockComment")) <|> ((lookAhead (pRegExpr regex_'5ba'2dzA'2dZ'5d) >> (popContext) >> currentContext >>= parseRules)) <|> ((parseRules ("LaTeX","EnvCommon"))) <|> ((popContext >> popContext >> popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","BlockComment") = (((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'5cend'28'3f'3d'5cs'2a'5c'7bcomment'5c'2a'3f'5c'7d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","CommFindEnd"))) parseRules ("LaTeX","CommFindEnd") = (((pRegExpr regex_'5cs'2a'5c'7b >>= withAttribute NormalTok)) <|> ((pRegExpr regex_comment'5c'2a'3f >>= withAttribute NormalTok)) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext >> popContext >> popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","MathEnv") = (((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeEnv")) <|> ((lookAhead (pRegExpr regex_'5ba'2dzA'2dZ'5d) >> (popContext) >> currentContext >>= parseRules)) <|> ((parseRules ("LaTeX","EnvCommon")))) parseRules ("LaTeX","MathEnvParam") = (((pRegExpr regex_'5c'7d'5c'7b'5b'5e'5c'7d'5d'2a'5c'7d >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeEnv")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeEnv")) <|> ((lookAhead (pRegExpr regex_'5ba'2dzA'2dZ'5d) >> (popContext) >> currentContext >>= parseRules)) <|> ((parseRules ("LaTeX","EnvCommon")))) parseRules ("LaTeX","EnvCommon") = (((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'2a'28'3f'3d'5c'7d'29 >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'2a'5b'5e'5c'7d'5d'2a >>= withAttribute AlertTok) >>~ (popContext >> popContext >> popContext)) <|> ((pRegExpr regex_'5b'5ea'2dzA'2dZ'5cxd7'5d'5b'5e'5c'7d'5d'2a >>= withAttribute AlertTok) >>~ (popContext >> popContext >> popContext))) parseRules ("LaTeX","MathModeEnv") = (((pRegExpr regex_'5c'5cbegin'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FindBeginEnvironment")) <|> ((pRegExpr regex_'5c'5cend'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathFindEnd")) <|> ((pString False "\\(" >>= withAttribute AlertTok)) <|> ((pString False "\\[" >>= withAttribute AlertTok)) <|> ((pString False "\\)" >>= withAttribute AlertTok)) <|> ((pString False "\\]" >>= withAttribute AlertTok)) <|> ((pRegExpr regex_'5c'5c'28text'7cintertext'7cmbox'29'5cs'2a'28'3f'3d'5c'7b'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeText")) <|> ((pDetectChar False '\\' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathContrSeq")) <|> ((pString False "$$" >>= withAttribute AlertTok)) <|> ((pDetectChar False '$' >>= withAttribute AlertTok)) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment")) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pFirstNonSpace >> pRegExpr regex_'25'5cs'2aBEGIN'2e'2a'24 >>= withAttribute RegionMarkerTok)) <|> ((pFirstNonSpace >> pRegExpr regex_'25'5cs'2aEND'2e'2a'24 >>= withAttribute RegionMarkerTok))) parseRules ("LaTeX","MathFindEnd") = (((pRegExpr regex_'5cs'2a'5c'7b >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28equation'7cdisplaymath'7ceqnarray'7csubeqnarray'7cmath'7cmultline'7cgather'7calign'7cflalign'7calignat'7cxalignat'7cxxalignat'7cIEEEeqnarray'7cIEEEeqnarraybox'7csmallmatrix'7cpmatrix'7cbmatrix'7cBmatrix'7cvmatrix'7cVmatrix'29'5c'2a'3f >>= withAttribute NormalTok)) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext >> popContext >> popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","TabEnv") = (((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Tab")) <|> ((lookAhead (pRegExpr regex_'5ba'2dzA'2dZ'5d) >> (popContext) >> currentContext >>= parseRules)) <|> ((parseRules ("LaTeX","EnvCommon"))) <|> ((popContext >> popContext >> popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","Tab") = (((pDetectChar False '&' >>= withAttribute NormalTok)) <|> ((pString False "@{" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Column Separator")) <|> ((pRegExpr regex_'5c'5cend'28'3f'3d'5cs'2a'5c'7b'28tabularx'7ctabular'7csupertabular'7cmpsupertabular'7cxtabular'7cmpxtabular'7clongtable'29'5c'2a'3f'5c'7d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","TabFindEnd")) <|> ((parseRules ("LaTeX","Normal Text")))) parseRules ("LaTeX","Column Separator") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Column Separator")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pRegExpr regex_'2e >>= withAttribute NormalTok))) parseRules ("LaTeX","TabFindEnd") = (((pRegExpr regex_'5cs'2a'5c'7b >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28tabularx'7ctabular'7csupertabular'7cmpsupertabular'7cxtabular'7cmpxtabular'7clongtable'29'5c'2a'3f >>= withAttribute NormalTok)) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext >> popContext >> popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("LaTeX","MathMode") = (((pString False "$$" >>= withAttribute AlertTok)) <|> ((pDetectChar False '$' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute AlertTok)) <|> ((parseRules ("LaTeX","MathModeCommon")))) parseRules ("LaTeX","MathModeDisplay") = (((pString False "$$" >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetectChar False '$' >>= withAttribute AlertTok)) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute AlertTok)) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute AlertTok)) <|> ((parseRules ("LaTeX","MathModeCommon")))) parseRules ("LaTeX","MathModeEquation") = (((pDetect2Chars False '\\' ']' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pString False "$$" >>= withAttribute AlertTok)) <|> ((pDetectChar False '$' >>= withAttribute AlertTok)) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute AlertTok)) <|> ((parseRules ("LaTeX","MathModeCommon")))) parseRules ("LaTeX","MathModeEnsure") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeEnsure")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((parseRules ("LaTeX","MathModeCommon")))) parseRules ("LaTeX","MathModeCommon") = (((pRegExpr regex_'5c'5c'28begin'7cend'29'5cs'2a'5c'7b'28equation'7cdisplaymath'7ceqnarray'7csubeqnarray'7cmath'7cmultline'7cgather'7calign'7cflalign'7calignat'7cxalignat'7cxxalignat'7cIEEEeqnarray'29'5c'2a'3f'5c'7d >>= withAttribute AlertTok)) <|> ((pRegExpr regex_'5c'5cbegin'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'5cend'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'5c'28text'7cintertext'7cmbox'29'5cs'2a'28'3f'3d'5c'7b'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeText")) <|> ((pDetectChar False '\\' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathContrSeq")) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment")) <|> ((pFirstNonSpace >> pRegExpr regex_'25'5cs'2aBEGIN'2e'2a'24 >>= withAttribute RegionMarkerTok)) <|> ((pFirstNonSpace >> pRegExpr regex_'25'5cs'2aEND'2e'2a'24 >>= withAttribute RegionMarkerTok)) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok))) parseRules ("LaTeX","MathContrSeq") = (((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b'5c'2a'3f >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute NormalTok) >>~ (popContext))) parseRules ("LaTeX","MathModeText") = ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeTextParameterStart")) parseRules ("LaTeX","MathModeTextParameterStart") = (((pRegExpr regex_'5c'5c'2e >>= withAttribute NormalTok)) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'24'2e'2a'5c'24 >>= withAttribute NormalTok)) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeTextParameter")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))) parseRules ("LaTeX","MathModeTextParameter") = (((pRegExpr regex_'5c'5c'2e >>= withAttribute NormalTok)) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeTextParameter")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))) parseRules ("LaTeX","Multiline Comment") = (((pString False "\\fi" >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pString False "\\else" >>= withAttribute CommentTok) >>~ (popContext))) parseRules ("LaTeX","Comment") = (((pRegExpr regex_'28FIXME'7cTODO'29'3a'3f >>= withAttribute AlertTok)) <|> ((pString False "\\KileResetHL" >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Normal Text")) <|> ((pString False "\\KateResetHL" >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Normal Text"))) parseRules x = fail $ "Unknown context" ++ show x