module Text.Highlighting.Kate.Syntax.Latex
(highlight, parseExpression, syntaxName, syntaxExtensions)
where
import Text.Highlighting.Kate.Types
import Text.Highlighting.Kate.Common
import qualified Text.Highlighting.Kate.Syntax.Cpp
import qualified Text.Highlighting.Kate.Syntax.Python
import Text.ParserCombinators.Parsec hiding (State)
import Control.Monad.State
import Data.Char (isSpace)
syntaxName :: String
syntaxName = "LaTeX"
syntaxExtensions :: String
syntaxExtensions = "*.tex;*.ltx;*.dtx;*.sty;*.cls;*.bbx;*.cbx;*.lbx;*.tikz"
highlight :: String -> [SourceLine]
highlight input = evalState (mapM parseSourceLine $ lines input) startingState
parseSourceLine :: String -> State SyntaxState SourceLine
parseSourceLine = mkParseSourceLine (parseExpression Nothing)
parseExpression :: Maybe (String,String)
-> KateParser Token
parseExpression mbcontext = do
(lang,cont) <- maybe currentContext return mbcontext
result <- parseRules (lang,cont)
optional $ do eof
updateState $ \st -> st{ synStPrevChar = '\n' }
pEndLine
return result
startingState = SyntaxState {synStContexts = [("LaTeX","Normal Text")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStContinuation = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []}
pEndLine = do
updateState $ \st -> st{ synStPrevNonspace = False }
context <- currentContext
contexts <- synStContexts `fmap` getState
st <- getState
if length contexts >= 2
then case context of
_ | synStContinuation st -> updateState $ \st -> st{ synStContinuation = False }
("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","MintParam") -> return ()
("LaTeX","Verb") -> (popContext >> popContext) >> pEndLine
("LaTeX","VerbEnd") -> (popContext >> popContext >> popContext) >> pEndLine
("LaTeX","Lstinline") -> (popContext >> popContext) >> pEndLine
("LaTeX","LstinlineEnd") -> (popContext >> popContext >> popContext) >> pEndLine
("LaTeX","LstinlineParameter") -> return ()
("LaTeX","Label") -> return ()
("LaTeX","LabelOption") -> return ()
("LaTeX","LabelParameter") -> return ()
("LaTeX","FancyLabel") -> return ()
("LaTeX","FancyLabelParameter") -> return ()
("LaTeX","FancyLabelOption") -> return ()
("LaTeX","FancyLabelRoundBrackets") -> return ()
("LaTeX","SpecialCommand") -> return ()
("LaTeX","SpecialCommandParameterOption") -> 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","ListingsEnvParam") -> return ()
("LaTeX","MintedEnvParam") -> return ()
("LaTeX","HighlightningSelector") -> return ()
("LaTeX","HighlightningCommon") -> return ()
("LaTeX","HighlightningBeginC++") -> return ()
("LaTeX","HighlightningC++") -> return ()
("LaTeX","HighlightningBeginPython") -> return ()
("LaTeX","HighlightningPython") -> 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 ()
else 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 True "\\\\begin(?=[^a-zA-Z])"
regex_'5c'5cend'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex True "\\\\end(?=[^a-zA-Z])"
regex_'5c'5c'28cite'7ccitet'7ccitep'7cparencite'7cautocite'7cAutocite'7ccitetitle'29'5c'2a'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex True "\\\\(cite|citet|citep|parencite|autocite|Autocite|citetitle)\\*(?=[^a-zA-Z])"
regex_'5c'5c'28documentclass'7cincludegraphics'7cinclude'7cusepackage'7cbibliography'7cbibliographystyle'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex True "\\\\(documentclass|includegraphics|include|usepackage|bibliography|bibliographystyle)(?=[^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 True "\\\\(cites|Cites|parencites|Parencites|autocites|Autocites|supercites|footcites|Footcites)(?=[^a-zA-Z])"
regex_'5c'5c'28cite'7ccitet'7ccitep'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 True "\\\\(cite|citet|citep|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 True "\\\\(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 True "\\\\(part|chapter|section|subsection|subsubsection|paragraph|subparagraph)\\*?\\s*(?=[\\{\\[])"
regex_'5c'5c'28input'7chspace'7chspace'5c'2a'7cvspace'7cvspace'5c'2a'7crule'7cspecial'7csetlength'7cnewboolean'7csetboolean'7csetcounter'7cgeometry'7ctextcolor'7cdefinecolor'7ccolumn'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex True "\\\\(input|hspace|hspace\\*|vspace|vspace\\*|rule|special|setlength|newboolean|setboolean|setcounter|geometry|textcolor|definecolor|column)(?=[^a-zA-Z])"
regex_'5c'5c'28footnote'29'5c'2a'3f'5cs'2a'28'3f'3d'5b'5c'7b'5c'5b'5d'29 = compileRegex True "\\\\(footnote)\\*?\\s*(?=[\\{\\[])"
regex_'5c'5c'28renewcommand'7cprovidenewcommand'7cnewcommand'29'5c'2a'3f'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex True "\\\\(renewcommand|providenewcommand|newcommand)\\*?(?=[^a-zA-Z])"
regex_'5c'5c'28e'7cg'7cx'29'3fdef'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex True "\\\\(e|g|x)?def(?=[^a-zA-Z])"
regex_'3c'3c'2e'2a'3e'3e'3d = compileRegex True "<<.*>>="
regex_'25'5cs'2aBEGIN'2e'2a'24 = compileRegex True "%\\s*BEGIN.*$"
regex_'25'5cs'2aEND'2e'2a'24 = compileRegex True "%\\s*END.*$"
regex_'5cs'2a'40'5cs'2a = compileRegex True "\\s*@\\s*"
regex_'5c'5b'5b'5e'5c'5d'5d'2a'5c'5d = compileRegex True "\\[[^\\]]*\\]"
regex_'5ba'2dzA'2dZ'5d'2b'28'5c'2b'3f'7c'5c'2a'7b0'2c3'7d'29 = compileRegex True "[a-zA-Z]+(\\+?|\\*{0,3})"
regex_'5b'5ea'2dzA'2dZ'5d = compileRegex True "[^a-zA-Z]"
regex_'5ba'2dzA'2dZ'5d'2b'5c'2a'3f = compileRegex True "[a-zA-Z]+\\*?"
regex_'5cs'2a'5c'7b'5cs'2a = compileRegex True "\\s*\\{\\s*"
regex_'5cs'2a'28'5c'5b'5cd'5c'5d'28'5c'5b'5b'5e'5c'5d'5d'2a'5c'5d'29'3f'29'3f'5c'7b = compileRegex True "\\s*(\\[\\d\\](\\[[^\\]]*\\])?)?\\{"
regex_'5cs'2a'5c'5c'5ba'2dzA'2dZ'5d'2b'5b'5e'5c'7b'5d'2a'5c'7b = compileRegex True "\\s*\\\\[a-zA-Z]+[^\\{]*\\{"
regex_'5c'5c'2e = compileRegex True "\\\\."
regex_'28Verb'7cverb'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex True "(Verb|verb)(?=[^a-zA-Z])"
regex_'28lstinline'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex True "(lstinline)(?=[^a-zA-Z])"
regex_mint'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex True "mint(?=[^a-zA-Z])"
regex_'5ba'2dzA'2dZ'40'5d'2b'28'5c'2b'3f'7c'5c'2a'7b0'2c3'7d'29 = compileRegex True "[a-zA-Z@]+(\\+?|\\*{0,3})"
regex_'5cs'2a'5c'5b'5cs'2a = compileRegex True "\\s*\\[\\s*"
regex_'5cs'2a'5c'7d'5cs'2a = compileRegex True "\\s*\\}\\s*"
regex_'5b'5e'5c'5b'5c'7b'5d'2b = compileRegex True "[^\\[\\{]+"
regex_'5cs'2a'5c'5d'5cs'2a = compileRegex True "\\s*\\]\\s*"
regex_'5cs'2a'5c'28'5cs'2a = compileRegex True "\\s*\\(\\s*"
regex_'5cs'2a'5c'29'5cs'2a = compileRegex True "\\s*\\)\\s*"
regex_'5cS = compileRegex True "\\S"
regex_'5ba'2dzA'2dZ'5d = compileRegex True "[a-zA-Z]"
regex_'5cs'2b = compileRegex True "\\s+"
regex_'5ba'2dzA'2dZ'5d'2b'28'5c'2a'29'3f = compileRegex True "[a-zA-Z]+(\\*)?"
regex_'28'28B'7cL'29'3fVerbatim'29 = compileRegex True "((B|L)?Verbatim)"
regex_'28verbatim'7cboxedverbatim'29 = compileRegex True "(verbatim|boxedverbatim)"
regex_comment = compileRegex True "comment"
regex_'28alignat'7cxalignat'7cxxalignat'29 = compileRegex True "(alignat|xalignat|xxalignat)"
regex_'28equation'7cdisplaymath'7ceqnarray'7csubeqnarray'7cmath'7cmultline'7cgather'7calign'7cflalign'7cIEEEeqnarray'7cIEEEeqnarraybox'7csmallmatrix'7cpmatrix'7cbmatrix'7cBmatrix'7cvmatrix'7cVmatrix'7ccases'29 = compileRegex True "(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|IEEEeqnarray|IEEEeqnarraybox|smallmatrix|pmatrix|bmatrix|Bmatrix|vmatrix|Vmatrix|cases)"
regex_'28tabularx'7ctabular'7csupertabular'7cmpsupertabular'7cxtabular'7cmpxtabular'7clongtable'29 = compileRegex True "(tabularx|tabular|supertabular|mpsupertabular|xtabular|mpxtabular|longtable)"
regex_'5b'5ea'2dzA'2dZ'5cxd7'5d = compileRegex True "[^a-zA-Z\\xd7]"
regex_'5ba'2dzA'2dZ'5d'2b = compileRegex True "[a-zA-Z]+"
regex_language'5cs'2a'3d'5cs'2a'28'3f'3d'5b'5e'2c'5d'2b'29 = compileRegex True "language\\s*=\\s*(?=[^,]+)"
regex_'2e'2a'28'3f'3d'5c'7d'7c'5c'5d'29 = compileRegex True ".*(?=\\}|\\])"
regex_'5c'5cend'5cs'2a'5c'7b'28lstlisting'7cminted'29'5c'2a'3f'5c'7d = compileRegex True "\\\\end\\s*\\{(lstlisting|minted)\\*?\\}"
regex_'2e'2a'28'5c'7d'7c'5c'5d'29 = compileRegex True ".*(\\}|\\])"
regex_'5c'5cend'28'3f'3d'5cs'2a'5c'7b'28verbatim'7clstlisting'7cboxedverbatim'7c'28B'7cL'29'3fVerbatim'7cminted'29'5c'2a'3f'5c'7d'29 = compileRegex True "\\\\end(?=\\s*\\{(verbatim|lstlisting|boxedverbatim|(B|L)?Verbatim|minted)\\*?\\})"
regex_'5cs'2a'5c'7b = compileRegex True "\\s*\\{"
regex_'28verbatim'7clstlisting'7cboxedverbatim'7c'28B'7cL'29'3fVerbatim'7cminted'29'5c'2a'3f = compileRegex True "(verbatim|lstlisting|boxedverbatim|(B|L)?Verbatim|minted)\\*?"
regex_'5c'5cend'28'3f'3d'5cs'2a'5c'7bcomment'5c'2a'3f'5c'7d'29 = compileRegex True "\\\\end(?=\\s*\\{comment\\*?\\})"
regex_comment'5c'2a'3f = compileRegex True "comment\\*?"
regex_'5c'7d'5c'7b'5b'5e'5c'7d'5d'2a'5c'7d = compileRegex True "\\}\\{[^\\}]*\\}"
regex_'5c'2a'28'3f'3d'5c'7d'29 = compileRegex True "\\*(?=\\})"
regex_'5c'2a'5b'5e'5c'7d'5d'2a = compileRegex True "\\*[^\\}]*"
regex_'5b'5ea'2dzA'2dZ'5cxd7'5d'5b'5e'5c'7d'5d'2a = compileRegex True "[^a-zA-Z\\xd7][^\\}]*"
regex_'5c'5c'28text'7cintertext'7cmbox'29'5cs'2a'28'3f'3d'5c'7b'29 = compileRegex True "\\\\(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'7ccases'29'5c'2a'3f = compileRegex True "(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|alignat|xalignat|xxalignat|IEEEeqnarray|IEEEeqnarraybox|smallmatrix|pmatrix|bmatrix|Bmatrix|vmatrix|Vmatrix|cases)\\*?"
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 True "\\\\end(?=\\s*\\{(tabularx|tabular|supertabular|mpsupertabular|xtabular|mpxtabular|longtable)\\*?\\})"
regex_'2e = compileRegex True "."
regex_'28tabularx'7ctabular'7csupertabular'7cmpsupertabular'7cxtabular'7cmpxtabular'7clongtable'29'5c'2a'3f = compileRegex True "(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 True "\\\\(begin|end)\\s*\\{(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|alignat|xalignat|xxalignat|IEEEeqnarray)\\*?\\}"
regex_'5c'24'2e'2a'5c'24 = compileRegex True "\\$.*\\$"
regex_'28FIXME'7cTODO'29'3a'3f = compileRegex True "(FIXME|TODO):?"
parseRules ("LaTeX","Normal Text") =
(((pRegExpr regex_'5c'5cbegin'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute KeywordTok) >>~ pushContext ("LaTeX","FindBeginEnvironment"))
<|>
((pRegExpr regex_'5c'5cend'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute KeywordTok) >>~ pushContext ("LaTeX","FindEndEnvironment"))
<|>
((pRegExpr regex_'5c'5c'28cite'7ccitet'7ccitep'7cparencite'7cautocite'7cAutocite'7ccitetitle'29'5c'2a'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute KeywordTok) >>~ pushContext ("LaTeX","Label"))
<|>
((pRegExpr regex_'5c'5c'28documentclass'7cincludegraphics'7cinclude'7cusepackage'7cbibliography'7cbibliographystyle'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute BuiltInTok) >>~ pushContext ("LaTeX","FancyLabel"))
<|>
((pRegExpr regex_'5c'5c'28cites'7cCites'7cparencites'7cParencites'7cautocites'7cAutocites'7csupercites'7cfootcites'7cFootcites'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute KeywordTok) >>~ pushContext ("LaTeX","FancyLabel"))
<|>
((pRegExpr regex_'5c'5c'28cite'7ccitet'7ccitep'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 KeywordTok) >>~ 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 KeywordTok) >>~ 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 KeywordTok) >>~ pushContext ("LaTeX","Sectioning"))
<|>
((pRegExpr regex_'5c'5c'28input'7chspace'7chspace'5c'2a'7cvspace'7cvspace'5c'2a'7crule'7cspecial'7csetlength'7cnewboolean'7csetboolean'7csetcounter'7cgeometry'7ctextcolor'7cdefinecolor'7ccolumn'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","SpecialCommand"))
<|>
((pRegExpr regex_'5c'5c'28footnote'29'5c'2a'3f'5cs'2a'28'3f'3d'5b'5c'7b'5c'5b'5d'29 >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","Footnoting"))
<|>
((pRegExpr regex_'5c'5c'28renewcommand'7cprovidenewcommand'7cnewcommand'29'5c'2a'3f'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","NewCommand"))
<|>
((pRegExpr regex_'5c'5c'28e'7cg'7cx'29'3fdef'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","DefCommand"))
<|>
((pRegExpr regex_'3c'3c'2e'2a'3e'3e'3d >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","NoWeb"))
<|>
((pString False "\\(" >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathMode"))
<|>
((pString False "\\[" >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathModeEquation"))
<|>
((pString False "\\iffalse" >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Multiline Comment"))
<|>
((pString False "\\ensuremath{" >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathModeEnsure"))
<|>
((pDetectChar False '\\' >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","ContrSeq"))
<|>
((pString False "$$" >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathModeDisplay"))
<|>
((pDetectChar False '$' >>= withAttribute SpecialStringTok) >>~ 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 InformationTok))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","Normal Text")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","NoWeb") =
(((pColumn 0 >> pRegExpr regex_'5cs'2a'40'5cs'2a >>= withAttribute NormalTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","NoWeb")) >> pDefault >>= withAttribute NormalTok))
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 SpecialStringTok) >>~ pushContext ("LaTeX","SectioningMathMode"))
<|>
((pDetectChar False '\\' >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","SectioningContrSeq"))
<|>
((pDetectChar False '$' >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","SectioningMathMode"))
<|>
((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","SectioningInside")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","SectioningContrSeq") =
(((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b'28'5c'2b'3f'7c'5c'2a'7b0'2c3'7d'29 >>= withAttribute FunctionTok) >>~ (popContext))
<|>
((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute FunctionTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","SectioningContrSeq")) >> pDefault >>= withAttribute FunctionTok))
parseRules ("LaTeX","SectioningMathMode") =
(((pString False "$$" >>= withAttribute ErrorTok))
<|>
((pDetectChar False '$' >>= withAttribute SpecialStringTok) >>~ (popContext))
<|>
((pDetect2Chars False '\\' ')' >>= withAttribute SpecialStringTok) >>~ (popContext))
<|>
((pDetect2Chars False '\\' ']' >>= withAttribute ErrorTok))
<|>
((pDetectChar False '\\' >>= withAttribute SpecialCharTok) >>~ pushContext ("LaTeX","SectioningMathContrSeq"))
<|>
((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","SectioningMathMode")) >> pDefault >>= withAttribute SpecialStringTok))
parseRules ("LaTeX","SectioningMathContrSeq") =
(((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b'5c'2a'3f >>= withAttribute SpecialCharTok) >>~ (popContext))
<|>
((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute SpecialCharTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","SectioningMathContrSeq")) >> pDefault >>= withAttribute SpecialCharTok))
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 SpecialStringTok) >>~ pushContext ("LaTeX","FootnotingMathMode"))
<|>
((pDetectChar False '$' >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","FootnotingMathMode"))
<|>
((parseRules ("LaTeX","Normal Text")))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","FootnotingInside")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","FootnotingMathMode") =
(((pString False "$$" >>= withAttribute ErrorTok))
<|>
((pDetectChar False '$' >>= withAttribute SpecialStringTok) >>~ (popContext))
<|>
((pDetect2Chars False '\\' ')' >>= withAttribute SpecialStringTok) >>~ (popContext))
<|>
((pDetect2Chars False '\\' ']' >>= withAttribute ErrorTok))
<|>
((parseRules ("LaTeX","MathMode")))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","FootnotingMathMode")) >> pDefault >>= withAttribute SpecialStringTok))
parseRules ("LaTeX","NewCommand") =
(((pRegExpr regex_'5cs'2a'5c'7b'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","LabelParameter"))
<|>
((pRegExpr regex_'5cs'2a'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","LabelParameter"))
<|>
((pDetectChar False '}' >>= withAttribute ErrorTok) >>~ (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 ErrorTok) >>~ (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"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","CommandParameterStart")) >> pDefault >>= withAttribute NormalTok))
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"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","CommandParameter")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","ContrSeq") =
(((pString False "verb*" >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","Verb"))
<|>
((pRegExpr regex_'28Verb'7cverb'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","Verb"))
<|>
((pRegExpr regex_'28lstinline'29'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","Lstinline"))
<|>
((pRegExpr regex_mint'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","MintParam"))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5ba'2dzA'2dZ'40'5d'2b'28'5c'2b'3f'7c'5c'2a'7b0'2c3'7d'29 >>= withAttribute FunctionTok) >>~ (popContext))
<|>
((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute FunctionTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","ContrSeq")) >> pDefault >>= withAttribute FunctionTok))
parseRules ("LaTeX","ToEndOfLine") =
(currentContext >>= \x -> guard (x == ("LaTeX","ToEndOfLine")) >> pDefault >>= withAttribute NormalTok)
parseRules ("LaTeX","MintParam") =
(((pDetect2Chars False '}' '[' >>= withAttribute NormalTok))
<|>
((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Verb"))
<|>
((pDetectChar False ']' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Verb"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MintParam")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","Verb") =
(((pRegExprDynamic "(.)" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","VerbEnd"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","Verb")) >> pDefault >>= withAttribute VerbatimStringTok))
parseRules ("LaTeX","VerbEnd") =
(((pString True "%1" >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExprDynamic "[^%1\\xd7]*" >>= withAttribute VerbatimStringTok))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","VerbEnd")) >> pDefault >>= withAttribute VerbatimStringTok))
parseRules ("LaTeX","Lstinline") =
(((pRegExpr regex_'5cs'2a'5c'5b'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FancyLabelOption"))
<|>
((pRegExpr regex_'5cs'2a'5c'7b'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","LstinlineParameter"))
<|>
((pRegExprDynamic "(.)" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","LstinlineEnd"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","Lstinline")) >> pDefault >>= withAttribute VerbatimStringTok))
parseRules ("LaTeX","LstinlineEnd") =
(((pString True "%1" >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExprDynamic "[^%1\\xd7]*" >>= withAttribute VerbatimStringTok))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","LstinlineEnd")) >> pDefault >>= withAttribute VerbatimStringTok))
parseRules ("LaTeX","LstinlineParameter") =
(((pRegExpr regex_'5cs'2a'5c'7d'5cs'2a >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","LstinlineParameter")) >> pDefault >>= withAttribute VerbatimStringTok))
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 ErrorTok))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","Label")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","LabelOption") =
(((pString False "\\(" >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathMode"))
<|>
((pDetectChar False '\\' >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","ContrSeq"))
<|>
((pDetectChar False '$' >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathMode"))
<|>
((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5cs'2a'5c'5d'5cs'2a >>= withAttribute NormalTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","LabelOption")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","LabelParameter") =
(((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5cs'2a'5c'7d'5cs'2a >>= withAttribute NormalTok) >>~ (popContext >> popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","LabelParameter")) >> pDefault >>= withAttribute ExtensionTok))
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","FancyLabelOption"))
<|>
((pRegExpr regex_'5cs'2a'5c'28'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","FancyLabelRoundBrackets"))
<|>
((popContext) >> currentContext >>= parseRules))
parseRules ("LaTeX","FancyLabelParameter") =
(((pString False "\\(" >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathMode"))
<|>
((pDetectChar False '\\' >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","ContrSeq"))
<|>
((pDetectChar False '$' >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathMode"))
<|>
((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5cs'2a'5c'7d'5cs'2a >>= withAttribute NormalTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","FancyLabelParameter")) >> pDefault >>= withAttribute ExtensionTok))
parseRules ("LaTeX","FancyLabelOption") =
(((pString False "\\(" >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathMode"))
<|>
((pDetectChar False '\\' >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","ContrSeq"))
<|>
((pDetectChar False '$' >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathMode"))
<|>
((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5cs'2a'5c'5d'5cs'2a >>= withAttribute NormalTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","FancyLabelOption")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","FancyLabelRoundBrackets") =
(((pString False "\\(" >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathMode"))
<|>
((pDetectChar False '\\' >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","ContrSeq"))
<|>
((pDetectChar False '$' >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathMode"))
<|>
((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5cs'2a'5c'29'5cs'2a >>= withAttribute NormalTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","FancyLabelRoundBrackets")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","SpecialCommand") =
(((pRegExpr regex_'5cs'2a'5c'7b'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","SpecialCommandParameterOption"))
<|>
((popContext) >> currentContext >>= parseRules))
parseRules ("LaTeX","SpecialCommandParameterOption") =
(((pString False "\\(" >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathMode"))
<|>
((pDetectChar False '\\' >>= withAttribute FunctionTok) >>~ pushContext ("LaTeX","ContrSeq"))
<|>
((pDetectChar False '$' >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathMode"))
<|>
((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5cs'2a'5c'7d'5cs'2a >>= withAttribute NormalTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","SpecialCommandParameterOption")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","FindEndEnvironment") =
(((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","EndEnvironment"))
<|>
((pRegExpr regex_'5cS >>= withAttribute NormalTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","FindEndEnvironment")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","EndEnvironment") =
(((pRegExpr regex_'5ba'2dzA'2dZ'5d >>= withAttribute ExtensionTok) >>~ pushContext ("LaTeX","EndLatexEnv"))
<|>
((pRegExpr regex_'5cs'2b >>= withAttribute ErrorTok) >>~ (popContext))
<|>
((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute ErrorTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","EndEnvironment")) >> pDefault >>= withAttribute ExtensionTok))
parseRules ("LaTeX","EndLatexEnv") =
(((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext))
<|>
((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b'28'5c'2a'29'3f >>= withAttribute ExtensionTok))
<|>
((pRegExpr regex_'5cs'2b >>= withAttribute ErrorTok))
<|>
((pRegExpr regex_'5ba'2dzA'2dZ'5d >>= withAttribute ErrorTok) >>~ (popContext >> popContext >> popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","EndLatexEnv")) >> pDefault >>= withAttribute ExtensionTok))
parseRules ("LaTeX","FindBeginEnvironment") =
(((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","BeginEnvironment"))
<|>
((pRegExpr regex_'5cS >>= withAttribute NormalTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","FindBeginEnvironment")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","BeginEnvironment") =
(((pString False "lstlisting" >>= withAttribute ExtensionTok) >>~ pushContext ("LaTeX","ListingsEnvParam"))
<|>
((pString False "minted" >>= withAttribute ExtensionTok) >>~ pushContext ("LaTeX","MintedEnvParam"))
<|>
((pRegExpr regex_'28'28B'7cL'29'3fVerbatim'29 >>= withAttribute ExtensionTok) >>~ pushContext ("LaTeX","VerbatimEnvParam"))
<|>
((pRegExpr regex_'28verbatim'7cboxedverbatim'29 >>= withAttribute ExtensionTok) >>~ pushContext ("LaTeX","VerbatimEnv"))
<|>
((pRegExpr regex_comment >>= withAttribute ExtensionTok) >>~ pushContext ("LaTeX","CommentEnv"))
<|>
((pRegExpr regex_'28alignat'7cxalignat'7cxxalignat'29 >>= withAttribute ExtensionTok) >>~ pushContext ("LaTeX","MathEnvParam"))
<|>
((pRegExpr regex_'28equation'7cdisplaymath'7ceqnarray'7csubeqnarray'7cmath'7cmultline'7cgather'7calign'7cflalign'7cIEEEeqnarray'7cIEEEeqnarraybox'7csmallmatrix'7cpmatrix'7cbmatrix'7cBmatrix'7cvmatrix'7cVmatrix'7ccases'29 >>= withAttribute ExtensionTok) >>~ pushContext ("LaTeX","MathEnv"))
<|>
((pRegExpr regex_'28tabularx'7ctabular'7csupertabular'7cmpsupertabular'7cxtabular'7cmpxtabular'7clongtable'29 >>= withAttribute ExtensionTok) >>~ pushContext ("LaTeX","TabEnv"))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5ba'2dzA'2dZ'5d >>= withAttribute ExtensionTok) >>~ pushContext ("LaTeX","LatexEnv"))
<|>
((pRegExpr regex_'5cs'2b >>= withAttribute ErrorTok) >>~ (popContext))
<|>
((pRegExpr regex_'5b'5ea'2dzA'2dZ'5cxd7'5d >>= withAttribute ErrorTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","BeginEnvironment")) >> pDefault >>= withAttribute ExtensionTok))
parseRules ("LaTeX","LatexEnv") =
(((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext))
<|>
((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b >>= withAttribute ExtensionTok))
<|>
((pRegExpr regex_'5cs'2b >>= withAttribute ErrorTok))
<|>
((parseRules ("LaTeX","EnvCommon")))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","LatexEnv")) >> pDefault >>= withAttribute ExtensionTok))
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"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","VerbatimEnvParam")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","ListingsEnvParam") =
(((pDetect2Chars False '}' '[' >>= withAttribute NormalTok))
<|>
((pRegExpr regex_language'5cs'2a'3d'5cs'2a'28'3f'3d'5b'5e'2c'5d'2b'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","HighlightningSelector"))
<|>
((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Verbatim"))
<|>
((pDetectChar False ']' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Verbatim"))
<|>
(pushContext ("LaTeX","Verbatim") >> currentContext >>= parseRules))
parseRules ("LaTeX","MintedEnvParam") =
(((pDetect2Chars False '}' '[' >>= withAttribute NormalTok))
<|>
((pDetect2Chars False '}' '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","HighlightningSelector"))
<|>
((pDetect2Chars False ']' '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","HighlightningSelector"))
<|>
((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","Verbatim"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MintedEnvParam")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","HighlightningSelector") =
(((pString False "C++" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","HighlightningBeginC++"))
<|>
((pString False "Python" >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","HighlightningBeginPython"))
<|>
((pRegExpr regex_'2e'2a'28'3f'3d'5c'7d'7c'5c'5d'29 >>= withAttribute NormalTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","HighlightningSelector")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","HighlightningCommon") =
(((lookAhead (pRegExpr regex_'5c'5cend'5cs'2a'5c'7b'28lstlisting'7cminted'29'5c'2a'3f'5c'7d) >> (popContext >> popContext >> popContext >> popContext >> popContext >> popContext) >> currentContext >>= parseRules))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","HighlightningCommon")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","HighlightningBeginC++") =
(((pRegExpr regex_'2e'2a'28'5c'7d'7c'5c'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","HighlightningC++"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","HighlightningBeginC++")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","HighlightningC++") =
(((parseRules ("LaTeX","HighlightningCommon")))
<|>
((Text.Highlighting.Kate.Syntax.Cpp.parseExpression (Just ("C++",""))))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","HighlightningC++")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","HighlightningBeginPython") =
(((pRegExpr regex_'2e'2a'28'5c'7d'7c'5c'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","HighlightningPython"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","HighlightningBeginPython")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","HighlightningPython") =
(((parseRules ("LaTeX","HighlightningCommon")))
<|>
((Text.Highlighting.Kate.Syntax.Python.parseExpression (Just ("Python",""))))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","HighlightningPython")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","Verbatim") =
(((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5c'5cend'28'3f'3d'5cs'2a'5c'7b'28verbatim'7clstlisting'7cboxedverbatim'7c'28B'7cL'29'3fVerbatim'7cminted'29'5c'2a'3f'5c'7d'29 >>= withAttribute KeywordTok) >>~ pushContext ("LaTeX","VerbFindEnd"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","Verbatim")) >> pDefault >>= withAttribute VerbatimStringTok))
parseRules ("LaTeX","VerbFindEnd") =
(((pRegExpr regex_'5cs'2a'5c'7b >>= withAttribute NormalTok))
<|>
((pRegExpr regex_'28verbatim'7clstlisting'7cboxedverbatim'7c'28B'7cL'29'3fVerbatim'7cminted'29'5c'2a'3f >>= withAttribute ExtensionTok))
<|>
((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 InformationTok))
<|>
((pRegExpr regex_'5c'5cend'28'3f'3d'5cs'2a'5c'7bcomment'5c'2a'3f'5c'7d'29 >>= withAttribute KeywordTok) >>~ pushContext ("LaTeX","CommFindEnd"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","BlockComment")) >> pDefault >>= withAttribute CommentTok))
parseRules ("LaTeX","CommFindEnd") =
(((pRegExpr regex_'5cs'2a'5c'7b >>= withAttribute NormalTok))
<|>
((pRegExpr regex_comment'5c'2a'3f >>= withAttribute ExtensionTok))
<|>
((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")))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathEnv")) >> pDefault >>= withAttribute ExtensionTok))
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")))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathEnvParam")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","EnvCommon") =
(((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5c'2a'28'3f'3d'5c'7d'29 >>= withAttribute ExtensionTok))
<|>
((pRegExpr regex_'5c'2a'5b'5e'5c'7d'5d'2a >>= withAttribute ErrorTok) >>~ (popContext >> popContext >> popContext))
<|>
((pRegExpr regex_'5b'5ea'2dzA'2dZ'5cxd7'5d'5b'5e'5c'7d'5d'2a >>= withAttribute ErrorTok) >>~ (popContext >> popContext >> popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","EnvCommon")) >> pDefault >>= withAttribute ExtensionTok))
parseRules ("LaTeX","MathModeEnv") =
(((pRegExpr regex_'5c'5cbegin'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute KeywordTok) >>~ pushContext ("LaTeX","FindBeginEnvironment"))
<|>
((pRegExpr regex_'5c'5cend'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute KeywordTok) >>~ pushContext ("LaTeX","MathFindEnd"))
<|>
((pString False "\\(" >>= withAttribute ErrorTok))
<|>
((pString False "\\[" >>= withAttribute ErrorTok))
<|>
((pString False "\\)" >>= withAttribute ErrorTok))
<|>
((pString False "\\]" >>= withAttribute ErrorTok))
<|>
((pRegExpr regex_'5c'5c'28text'7cintertext'7cmbox'29'5cs'2a'28'3f'3d'5c'7b'29 >>= withAttribute SpecialCharTok) >>~ pushContext ("LaTeX","MathModeText"))
<|>
((pDetectChar False '\\' >>= withAttribute SpecialCharTok) >>~ pushContext ("LaTeX","MathContrSeq"))
<|>
((pString False "$$" >>= withAttribute ErrorTok))
<|>
((pDetectChar False '$' >>= withAttribute ErrorTok))
<|>
((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pFirstNonSpace >> pRegExpr regex_'25'5cs'2aBEGIN'2e'2a'24 >>= withAttribute RegionMarkerTok))
<|>
((pFirstNonSpace >> pRegExpr regex_'25'5cs'2aEND'2e'2a'24 >>= withAttribute RegionMarkerTok))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathModeEnv")) >> pDefault >>= withAttribute SpecialStringTok))
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'7ccases'29'5c'2a'3f >>= withAttribute ExtensionTok))
<|>
((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 OperatorTok))
<|>
((pString False "@{" >>= withAttribute CharTok) >>~ 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 KeywordTok) >>~ pushContext ("LaTeX","TabFindEnd"))
<|>
((parseRules ("LaTeX","Normal Text")))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","Tab")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","Column Separator") =
(((pDetectChar False '{' >>= withAttribute CharTok) >>~ pushContext ("LaTeX","Column Separator"))
<|>
((pDetectChar False '}' >>= withAttribute CharTok) >>~ (popContext))
<|>
((pRegExpr regex_'2e >>= withAttribute CharTok))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","Column Separator")) >> pDefault >>= withAttribute CharTok))
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 ExtensionTok))
<|>
((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext >> popContext >> popContext))
<|>
((popContext) >> currentContext >>= parseRules))
parseRules ("LaTeX","MathMode") =
(((pString False "$$" >>= withAttribute ErrorTok))
<|>
((pDetectChar False '$' >>= withAttribute SpecialStringTok) >>~ (popContext))
<|>
((pDetect2Chars False '\\' ')' >>= withAttribute SpecialStringTok) >>~ (popContext))
<|>
((pDetect2Chars False '\\' ']' >>= withAttribute ErrorTok))
<|>
((parseRules ("LaTeX","MathModeCommon")))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathMode")) >> pDefault >>= withAttribute SpecialStringTok))
parseRules ("LaTeX","MathModeDisplay") =
(((pString False "$$" >>= withAttribute SpecialStringTok) >>~ (popContext))
<|>
((pDetectChar False '$' >>= withAttribute ErrorTok))
<|>
((pDetect2Chars False '\\' ']' >>= withAttribute ErrorTok))
<|>
((pDetect2Chars False '\\' ')' >>= withAttribute ErrorTok))
<|>
((parseRules ("LaTeX","MathModeCommon")))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathModeDisplay")) >> pDefault >>= withAttribute SpecialStringTok))
parseRules ("LaTeX","MathModeEquation") =
(((pDetect2Chars False '\\' ']' >>= withAttribute SpecialStringTok) >>~ (popContext))
<|>
((pString False "$$" >>= withAttribute ErrorTok))
<|>
((pDetectChar False '$' >>= withAttribute ErrorTok))
<|>
((pDetect2Chars False '\\' ')' >>= withAttribute ErrorTok))
<|>
((parseRules ("LaTeX","MathModeCommon")))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathModeEquation")) >> pDefault >>= withAttribute SpecialStringTok))
parseRules ("LaTeX","MathModeEnsure") =
(((pDetectChar False '{' >>= withAttribute SpecialStringTok) >>~ pushContext ("LaTeX","MathModeEnsure"))
<|>
((pDetectChar False '}' >>= withAttribute SpecialStringTok) >>~ (popContext))
<|>
((parseRules ("LaTeX","MathModeCommon")))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathModeEnsure")) >> pDefault >>= withAttribute SpecialStringTok))
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 ErrorTok))
<|>
((pRegExpr regex_'5c'5cbegin'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute SpecialCharTok))
<|>
((pRegExpr regex_'5c'5cend'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute SpecialCharTok))
<|>
((pRegExpr regex_'5c'5c'28text'7cintertext'7cmbox'29'5cs'2a'28'3f'3d'5c'7b'29 >>= withAttribute SpecialCharTok) >>~ pushContext ("LaTeX","MathModeText"))
<|>
((pDetectChar False '\\' >>= withAttribute SpecialCharTok) >>~ 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 InformationTok))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathModeCommon")) >> pDefault >>= withAttribute SpecialStringTok))
parseRules ("LaTeX","MathContrSeq") =
(((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b'5c'2a'3f >>= withAttribute SpecialCharTok) >>~ (popContext))
<|>
((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute SpecialCharTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathContrSeq")) >> pDefault >>= withAttribute SpecialCharTok))
parseRules ("LaTeX","MathModeText") =
(((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeTextParameterStart"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathModeText")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","MathModeTextParameterStart") =
(((pRegExpr regex_'5c'5c'2e >>= withAttribute NormalTok))
<|>
((pDetectChar False '\215' >>= withAttribute InformationTok))
<|>
((pRegExpr regex_'5c'24'2e'2a'5c'24 >>= withAttribute SpecialStringTok))
<|>
((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("LaTeX","MathModeTextParameter"))
<|>
((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext))
<|>
((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathModeTextParameterStart")) >> pDefault >>= withAttribute NormalTok))
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 InformationTok))
<|>
((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("LaTeX","Comment"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","MathModeTextParameter")) >> pDefault >>= withAttribute NormalTok))
parseRules ("LaTeX","Multiline Comment") =
(((pString False "\\fi" >>= withAttribute CommentTok) >>~ (popContext))
<|>
((pString False "\\else" >>= withAttribute CommentTok) >>~ (popContext))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","Multiline Comment")) >> pDefault >>= withAttribute CommentTok))
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"))
<|>
(currentContext >>= \x -> guard (x == ("LaTeX","Comment")) >> pDefault >>= withAttribute CommentTok))
parseRules ("C++", _) = Text.Highlighting.Kate.Syntax.Cpp.parseExpression Nothing
parseRules ("Python", _) = Text.Highlighting.Kate.Syntax.Python.parseExpression Nothing
parseRules x = parseRules ("LaTeX","Normal Text") <|> fail ("Unknown context" ++ show x)