{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Latex (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex syntax :: Syntax syntax = Syntax { sName = "LaTeX" , sFilename = "latex.xml" , sShortname = "Latex" , sContexts = fromList [ ( "BeginEnvironment" , Context { cName = "BeginEnvironment" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "lstlisting" , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "ListingsEnvParam" ) ] } , Rule { rMatcher = StringDetect "minted" , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MintedEnvParam" ) ] } , Rule { rMatcher = RegExpr RE { reString = "((B|L)?Verbatim)" , reCompiled = Just (compileRegex True "((B|L)?Verbatim)") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "VerbatimEnvParam" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(verbatim|boxedverbatim)" , reCompiled = Just (compileRegex True "(verbatim|boxedverbatim)") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "VerbatimEnv" ) ] } , Rule { rMatcher = RegExpr RE { reString = "comment" , reCompiled = Just (compileRegex True "comment") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "CommentEnv" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(alignat|xalignat|xxalignat)" , reCompiled = Just (compileRegex True "(alignat|xalignat|xxalignat)") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathEnvParam" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|IEEEeqnarray|IEEEeqnarraybox|smallmatrix|pmatrix|bmatrix|Bmatrix|vmatrix|Vmatrix|cases)" , reCompiled = Just (compileRegex True "(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|IEEEeqnarray|IEEEeqnarraybox|smallmatrix|pmatrix|bmatrix|Bmatrix|vmatrix|Vmatrix|cases)") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathEnv" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(tabularx|tabular|supertabular|mpsupertabular|xtabular|mpxtabular|longtable)" , reCompiled = Just (compileRegex True "(tabularx|tabular|supertabular|mpsupertabular|xtabular|mpxtabular|longtable)") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "TabEnv" ) ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]" , reCompiled = Just (compileRegex True "[a-zA-Z]") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "LatexEnv" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s+" , reCompiled = Just (compileRegex True "\\s+") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[^a-zA-Z\\xd7]" , reCompiled = Just (compileRegex True "[^a-zA-Z\\xd7]") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "BlockComment" , Context { cName = "BlockComment" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\end(?=\\s*\\{comment\\*?\\})" , reCompiled = Just (compileRegex True "\\\\end(?=\\s*\\{comment\\*?\\})") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "CommFindEnd" ) ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Column Separator" , Context { cName = "Column Separator" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '{' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Column Separator" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "." , reCompiled = Just (compileRegex True ".") , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = CharTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "CommFindEnd" , Context { cName = "CommFindEnd" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\{" , reCompiled = Just (compileRegex True "\\s*\\{") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "comment\\*?" , reCompiled = Just (compileRegex True "comment\\*?") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop , Pop , Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "CommandParameter" , Context { cName = "CommandParameter" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "CommandParameter" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\." , reCompiled = Just (compileRegex True "\\\\.") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "CommandParameterStart" , Context { cName = "CommandParameterStart" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "CommandParameter" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\." , reCompiled = Just (compileRegex True "\\\\.") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Comment" , Context { cName = "Comment" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "(FIXME|TODO):?" , reCompiled = Just (compileRegex True "(FIXME|TODO):?") , reCaseSensitive = True } , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "\\KileResetHL" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Normal Text" ) ] } , Rule { rMatcher = StringDetect "\\KateResetHL" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Normal Text" ) ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "CommentEnv" , Context { cName = "CommentEnv" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "BlockComment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]" , reCompiled = Just (compileRegex True "[a-zA-Z]") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "EnvCommon" ) , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop , Pop , Pop ] , cDynamic = False } ) , ( "ContrSeq" , Context { cName = "ContrSeq" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "verb*" , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Verb" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(Verb|verb)(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "(Verb|verb)(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Verb" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(lstinline)(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "(lstinline)(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Lstinline" ) ] } , Rule { rMatcher = RegExpr RE { reString = "mint(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "mint(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MintParam" ) ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z@]+(\\+?|\\*{0,3})" , reCompiled = Just (compileRegex True "[a-zA-Z@]+(\\+?|\\*{0,3})") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[^a-zA-Z]" , reCompiled = Just (compileRegex True "[^a-zA-Z]") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = FunctionTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "DefCommand" , Context { cName = "DefCommand" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\\\[a-zA-Z]+[^\\{]*\\{" , reCompiled = Just (compileRegex True "\\s*\\\\[a-zA-Z]+[^\\{]*\\{") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "CommandParameterStart" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "EndEnvironment" , Context { cName = "EndEnvironment" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]" , reCompiled = Just (compileRegex True "[a-zA-Z]") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "EndLatexEnv" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s+" , reCompiled = Just (compileRegex True "\\s+") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[^a-zA-Z]" , reCompiled = Just (compileRegex True "[^a-zA-Z]") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "EndLatexEnv" , Context { cName = "EndLatexEnv" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]+(\\*)?" , reCompiled = Just (compileRegex True "[a-zA-Z]+(\\*)?") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s+" , reCompiled = Just (compileRegex True "\\s+") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]" , reCompiled = Just (compileRegex True "[a-zA-Z]") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "EnvCommon" , Context { cName = "EnvCommon" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\*(?=\\})" , reCompiled = Just (compileRegex True "\\*(?=\\})") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\*[^\\}]*" , reCompiled = Just (compileRegex True "\\*[^\\}]*") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[^a-zA-Z\\xd7][^\\}]*" , reCompiled = Just (compileRegex True "[^a-zA-Z\\xd7][^\\}]*") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FancyLabel" , Context { cName = "FancyLabel" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\{\\s*" , reCompiled = Just (compileRegex True "\\s*\\{\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FancyLabelParameter" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\[\\s*" , reCompiled = Just (compileRegex True "\\s*\\[\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FancyLabelOption" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\(\\s*" , reCompiled = Just (compileRegex True "\\s*\\(\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FancyLabelRoundBrackets" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "FancyLabelOption" , Context { cName = "FancyLabelOption" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "\\(" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = DetectChar '\\' , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "ContrSeq" ) ] } , Rule { rMatcher = DetectChar '$' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\]\\s*" , reCompiled = Just (compileRegex True "\\s*\\]\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FancyLabelParameter" , Context { cName = "FancyLabelParameter" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "\\(" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = DetectChar '\\' , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "ContrSeq" ) ] } , Rule { rMatcher = DetectChar '$' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\}\\s*" , reCompiled = Just (compileRegex True "\\s*\\}\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FancyLabelRoundBrackets" , Context { cName = "FancyLabelRoundBrackets" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "\\(" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = DetectChar '\\' , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "ContrSeq" ) ] } , Rule { rMatcher = DetectChar '$' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\)\\s*" , reCompiled = Just (compileRegex True "\\s*\\)\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindBeginEnvironment" , Context { cName = "FindBeginEnvironment" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "BeginEnvironment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindEndEnvironment" , Context { cName = "FindEndEnvironment" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "EndEnvironment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Footnoting" , Context { cName = "Footnoting" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\[[^\\]]*\\]" , reCompiled = Just (compileRegex True "\\[[^\\]]*\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar ' ' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FootnotingInside" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "FootnotingInside" , Context { cName = "FootnotingInside" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FootnotingInside" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = StringDetect "\\(" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FootnotingMathMode" ) ] } , Rule { rMatcher = DetectChar '$' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FootnotingMathMode" ) ] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "Normal Text" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FootnotingMathMode" , Context { cName = "FootnotingMathMode" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "$$" , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '$' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = Detect2Chars '\\' ')' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = Detect2Chars '\\' ']' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "MathMode" ) , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "HighlightningBeginC++" , Context { cName = "HighlightningBeginC++" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = ".*(\\}|\\])" , reCompiled = Just (compileRegex True ".*(\\}|\\])") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "HighlightningC++" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "HighlightningBeginPython" , Context { cName = "HighlightningBeginPython" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = ".*(\\}|\\])" , reCompiled = Just (compileRegex True ".*(\\}|\\])") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "HighlightningPython" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "HighlightningC++" , Context { cName = "HighlightningC++" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = IncludeRules ( "LaTeX" , "HighlightningCommon" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "C++" , "" ) , rAttribute = NormalTok , rIncludeAttribute = True , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "HighlightningCommon" , Context { cName = "HighlightningCommon" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\\\end\\s*\\{(lstlisting|minted)\\*?\\}" , reCompiled = Just (compileRegex True "\\\\end\\s*\\{(lstlisting|minted)\\*?\\}") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop , Pop , Pop , Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "HighlightningPython" , Context { cName = "HighlightningPython" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = IncludeRules ( "LaTeX" , "HighlightningCommon" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "HighlightningSelector" , Context { cName = "HighlightningSelector" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "C++" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "HighlightningBeginC++" ) ] } , Rule { rMatcher = StringDetect "Python" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "HighlightningBeginPython" ) ] } , Rule { rMatcher = RegExpr RE { reString = ".*(?=\\}|\\])" , reCompiled = Just (compileRegex True ".*(?=\\}|\\])") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Label" , Context { cName = "Label" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\{\\s*" , reCompiled = Just (compileRegex True "\\s*\\{\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "LabelParameter" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\[\\s*" , reCompiled = Just (compileRegex True "\\s*\\[\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "LabelOption" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[^\\[\\{]+" , reCompiled = Just (compileRegex True "[^\\[\\{]+") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "LabelOption" , Context { cName = "LabelOption" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "\\(" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = DetectChar '\\' , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "ContrSeq" ) ] } , Rule { rMatcher = DetectChar '$' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\]\\s*" , reCompiled = Just (compileRegex True "\\s*\\]\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "LabelParameter" , Context { cName = "LabelParameter" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\}\\s*" , reCompiled = Just (compileRegex True "\\s*\\}\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "LatexEnv" , Context { cName = "LatexEnv" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]+" , reCompiled = Just (compileRegex True "[a-zA-Z]+") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s+" , reCompiled = Just (compileRegex True "\\s+") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "EnvCommon" ) , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ListingsEnvParam" , Context { cName = "ListingsEnvParam" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = Detect2Chars '}' '[' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "language\\s*=\\s*(?=[^,]+)" , reCompiled = Just (compileRegex True "language\\s*=\\s*(?=[^,]+)") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "HighlightningSelector" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Verbatim" ) ] } , Rule { rMatcher = DetectChar ']' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Verbatim" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Push ( "LaTeX" , "Verbatim" ) ] , cDynamic = False } ) , ( "Lstinline" , Context { cName = "Lstinline" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\[\\s*" , reCompiled = Just (compileRegex True "\\s*\\[\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FancyLabelOption" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\{\\s*" , reCompiled = Just (compileRegex True "\\s*\\{\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "LstinlineParameter" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(.)" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "LstinlineEnd" ) ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [ Pop , Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "LstinlineEnd" , Context { cName = "LstinlineEnd" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "%1" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[^%1\\xd7]*" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [ Pop , Pop , Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "LstinlineParameter" , Context { cName = "LstinlineParameter" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\}\\s*" , reCompiled = Just (compileRegex True "\\s*\\}\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathContrSeq" , Context { cName = "MathContrSeq" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]+\\*?" , reCompiled = Just (compileRegex True "[a-zA-Z]+\\*?") , reCaseSensitive = True } , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[^a-zA-Z]" , reCompiled = Just (compileRegex True "[^a-zA-Z]") , reCaseSensitive = True } , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = SpecialCharTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathEnv" , Context { cName = "MathEnv" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeEnv" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]" , reCompiled = Just (compileRegex True "[a-zA-Z]") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "EnvCommon" ) , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathEnvParam" , Context { cName = "MathEnvParam" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\}\\{[^\\}]*\\}" , reCompiled = Just (compileRegex True "\\}\\{[^\\}]*\\}") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeEnv" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeEnv" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]" , reCompiled = Just (compileRegex True "[a-zA-Z]") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "EnvCommon" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathFindEnd" , Context { cName = "MathFindEnd" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\{" , reCompiled = Just (compileRegex True "\\s*\\{") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|alignat|xalignat|xxalignat|IEEEeqnarray|IEEEeqnarraybox|smallmatrix|pmatrix|bmatrix|Bmatrix|vmatrix|Vmatrix|cases)\\*?" , reCompiled = Just (compileRegex True "(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|alignat|xalignat|xxalignat|IEEEeqnarray|IEEEeqnarraybox|smallmatrix|pmatrix|bmatrix|Bmatrix|vmatrix|Vmatrix|cases)\\*?") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop , Pop , Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "MathMode" , Context { cName = "MathMode" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "$$" , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '$' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = Detect2Chars '\\' ')' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = Detect2Chars '\\' ']' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "MathModeCommon" ) , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathModeCommon" , Context { cName = "MathModeCommon" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\\\(begin|end)\\s*\\{(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|alignat|xalignat|xxalignat|IEEEeqnarray)\\*?\\}" , reCompiled = Just (compileRegex True "\\\\(begin|end)\\s*\\{(equation|displaymath|eqnarray|subeqnarray|math|multline|gather|align|flalign|alignat|xalignat|xxalignat|IEEEeqnarray)\\*?\\}") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\begin(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\begin(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\end(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\end(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(text|intertext|mbox)\\s*(?=\\{)" , reCompiled = Just (compileRegex True "\\\\(text|intertext|mbox)\\s*(?=\\{)") , reCaseSensitive = True } , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeText" ) ] } , Rule { rMatcher = DetectChar '\\' , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathContrSeq" ) ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "%\\s*BEGIN.*$" , reCompiled = Just (compileRegex True "%\\s*BEGIN.*$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "%\\s*END.*$" , reCompiled = Just (compileRegex True "%\\s*END.*$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathModeDisplay" , Context { cName = "MathModeDisplay" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "$$" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '$' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' ']' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' ')' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "MathModeCommon" ) , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathModeEnsure" , Context { cName = "MathModeEnsure" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '{' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeEnsure" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "MathModeCommon" ) , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathModeEnv" , Context { cName = "MathModeEnv" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\\\begin(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\begin(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FindBeginEnvironment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\end(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\end(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathFindEnd" ) ] } , Rule { rMatcher = StringDetect "\\(" , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "\\[" , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "\\)" , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "\\]" , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(text|intertext|mbox)\\s*(?=\\{)" , reCompiled = Just (compileRegex True "\\\\(text|intertext|mbox)\\s*(?=\\{)") , reCaseSensitive = True } , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeText" ) ] } , Rule { rMatcher = DetectChar '\\' , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathContrSeq" ) ] } , Rule { rMatcher = StringDetect "$$" , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '$' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "%\\s*BEGIN.*$" , reCompiled = Just (compileRegex True "%\\s*BEGIN.*$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "%\\s*END.*$" , reCompiled = Just (compileRegex True "%\\s*END.*$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathModeEquation" , Context { cName = "MathModeEquation" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = Detect2Chars '\\' ']' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = StringDetect "$$" , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '$' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' ')' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "MathModeCommon" ) , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathModeText" , Context { cName = "MathModeText" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeTextParameterStart" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathModeTextParameter" , Context { cName = "MathModeTextParameter" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\\\." , reCompiled = Just (compileRegex True "\\\\.") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeTextParameter" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MathModeTextParameterStart" , Context { cName = "MathModeTextParameterStart" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\\\." , reCompiled = Just (compileRegex True "\\\\.") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\$.*\\$" , reCompiled = Just (compileRegex True "\\$.*\\$") , reCaseSensitive = True } , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeTextParameter" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MintParam" , Context { cName = "MintParam" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = Detect2Chars '}' '[' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Verb" ) ] } , Rule { rMatcher = DetectChar ']' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Verb" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "MintedEnvParam" , Context { cName = "MintedEnvParam" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = Detect2Chars '}' '[' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '}' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "HighlightningSelector" ) ] } , Rule { rMatcher = Detect2Chars ']' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "HighlightningSelector" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Verbatim" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Multiline Comment" , Context { cName = "Multiline Comment" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "\\fi" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = StringDetect "\\else" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "NewCommand" , Context { cName = "NewCommand" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\{\\s*" , reCompiled = Just (compileRegex True "\\s*\\{\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "LabelParameter" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*(\\[\\d\\](\\[[^\\]]*\\])?)?\\{" , reCompiled = Just (compileRegex True "\\s*(\\[\\d\\](\\[[^\\]]*\\])?)?\\{") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "LabelParameter" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "NoWeb" , Context { cName = "NoWeb" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*@\\s*" , reCompiled = Just (compileRegex True "\\s*@\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Normal Text" , Context { cName = "Normal Text" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\\\begin(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\begin(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FindBeginEnvironment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\end(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\end(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FindEndEnvironment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(cite|citet|citep|parencite|autocite|Autocite|citetitle)\\*(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\(cite|citet|citep|parencite|autocite|Autocite|citetitle)\\*(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Label" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(documentclass|includegraphics|include|usepackage|bibliography|bibliographystyle)(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\(documentclass|includegraphics|include|usepackage|bibliography|bibliographystyle)(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = BuiltInTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FancyLabel" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(cites|Cites|parencites|Parencites|autocites|Autocites|supercites|footcites|Footcites)(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\(cites|Cites|parencites|Parencites|autocites|Autocites|supercites|footcites|Footcites)(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "FancyLabel" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(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])" , reCompiled = Just (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])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Label" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(subref\\*?|cref\\*?|label|pageref|autoref|ref|vpageref|vref|pagecite|eqref)(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\(subref\\*?|cref\\*?|label|pageref|autoref|ref|vpageref|vref|pagecite|eqref)(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Label" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(part|chapter|section|subsection|subsubsection|paragraph|subparagraph)\\*?\\s*(?=[\\{\\[])" , reCompiled = Just (compileRegex True "\\\\(part|chapter|section|subsection|subsubsection|paragraph|subparagraph)\\*?\\s*(?=[\\{\\[])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Sectioning" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(input|hspace|hspace\\*|vspace|vspace\\*|rule|special|setlength|newboolean|setboolean|setcounter|geometry|textcolor|definecolor|column)(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\(input|hspace|hspace\\*|vspace|vspace\\*|rule|special|setlength|newboolean|setboolean|setcounter|geometry|textcolor|definecolor|column)(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "SpecialCommand" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(footnote)\\*?\\s*(?=[\\{\\[])" , reCompiled = Just (compileRegex True "\\\\(footnote)\\*?\\s*(?=[\\{\\[])") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Footnoting" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(renewcommand|providenewcommand|newcommand)\\*?(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\(renewcommand|providenewcommand|newcommand)\\*?(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "NewCommand" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(e|g|x)?def(?=[^a-zA-Z])" , reCompiled = Just (compileRegex True "\\\\(e|g|x)?def(?=[^a-zA-Z])") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "DefCommand" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<<.*>>=" , reCompiled = Just (compileRegex True "<<.*>>=") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "NoWeb" ) ] } , Rule { rMatcher = StringDetect "\\(" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = StringDetect "\\[" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeEquation" ) ] } , Rule { rMatcher = StringDetect "\\iffalse" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Multiline Comment" ) ] } , Rule { rMatcher = StringDetect "\\ensuremath{" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeEnsure" ) ] } , Rule { rMatcher = DetectChar '\\' , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "ContrSeq" ) ] } , Rule { rMatcher = StringDetect "$$" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathModeDisplay" ) ] } , Rule { rMatcher = DetectChar '$' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = RegExpr RE { reString = "%\\s*BEGIN.*$" , reCompiled = Just (compileRegex True "%\\s*BEGIN.*$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "%\\s*END.*$" , reCompiled = Just (compileRegex True "%\\s*END.*$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Sectioning" , Context { cName = "Sectioning" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\[[^\\]]*\\]" , reCompiled = Just (compileRegex True "\\[[^\\]]*\\]") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar ' ' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "SectioningInside" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "SectioningContrSeq" , Context { cName = "SectioningContrSeq" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]+(\\+?|\\*{0,3})" , reCompiled = Just (compileRegex True "[a-zA-Z]+(\\+?|\\*{0,3})") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[^a-zA-Z]" , reCompiled = Just (compileRegex True "[^a-zA-Z]") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = FunctionTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SectioningInside" , Context { cName = "SectioningInside" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "SectioningInside" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = StringDetect "\\(" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "SectioningMathMode" ) ] } , Rule { rMatcher = DetectChar '\\' , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "SectioningContrSeq" ) ] } , Rule { rMatcher = DetectChar '$' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "SectioningMathMode" ) ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SectioningMathContrSeq" , Context { cName = "SectioningMathContrSeq" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]+\\*?" , reCompiled = Just (compileRegex True "[a-zA-Z]+\\*?") , reCaseSensitive = True } , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[^a-zA-Z]" , reCompiled = Just (compileRegex True "[^a-zA-Z]") , reCaseSensitive = True } , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = SpecialCharTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SectioningMathMode" , Context { cName = "SectioningMathMode" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "$$" , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '$' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = Detect2Chars '\\' ')' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = Detect2Chars '\\' ']' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '\\' , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "SectioningMathContrSeq" ) ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SpecialCommand" , Context { cName = "SpecialCommand" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\{\\s*" , reCompiled = Just (compileRegex True "\\s*\\{\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "SpecialCommandParameterOption" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "SpecialCommandParameterOption" , Context { cName = "SpecialCommandParameterOption" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "\\(" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = DetectChar '\\' , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "ContrSeq" ) ] } , Rule { rMatcher = DetectChar '$' , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "MathMode" ) ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Comment" ) ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\}\\s*" , reCompiled = Just (compileRegex True "\\s*\\}\\s*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Tab" , Context { cName = "Tab" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '&' , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "@{" , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Column Separator" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\end(?=\\s*\\{(tabularx|tabular|supertabular|mpsupertabular|xtabular|mpxtabular|longtable)\\*?\\})" , reCompiled = Just (compileRegex True "\\\\end(?=\\s*\\{(tabularx|tabular|supertabular|mpsupertabular|xtabular|mpxtabular|longtable)\\*?\\})") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "TabFindEnd" ) ] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "Normal Text" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "TabEnv" , Context { cName = "TabEnv" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Tab" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]" , reCompiled = Just (compileRegex True "[a-zA-Z]") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "EnvCommon" ) , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop , Pop , Pop ] , cDynamic = False } ) , ( "TabFindEnd" , Context { cName = "TabFindEnd" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\{" , reCompiled = Just (compileRegex True "\\s*\\{") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(tabularx|tabular|supertabular|mpsupertabular|xtabular|mpxtabular|longtable)\\*?" , reCompiled = Just (compileRegex True "(tabularx|tabular|supertabular|mpsupertabular|xtabular|mpxtabular|longtable)\\*?") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop , Pop , Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "ToEndOfLine" , Context { cName = "ToEndOfLine" , cSyntax = "LaTeX" , cRules = [] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Verb" , Context { cName = "Verb" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "(.)" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "VerbEnd" ) ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [ Pop , Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "VerbEnd" , Context { cName = "VerbEnd" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = StringDetect "%1" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } , Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[^%1\\xd7]*" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [ Pop , Pop , Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "VerbFindEnd" , Context { cName = "VerbFindEnd" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\{" , reCompiled = Just (compileRegex True "\\s*\\{") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(verbatim|lstlisting|boxedverbatim|(B|L)?Verbatim|minted)\\*?" , reCompiled = Just (compileRegex True "(verbatim|lstlisting|boxedverbatim|(B|L)?Verbatim|minted)\\*?") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop , Pop , Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "Verbatim" , Context { cName = "Verbatim" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '\215' , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\end(?=\\s*\\{(verbatim|lstlisting|boxedverbatim|(B|L)?Verbatim|minted)\\*?\\})" , reCompiled = Just (compileRegex True "\\\\end(?=\\s*\\{(verbatim|lstlisting|boxedverbatim|(B|L)?Verbatim|minted)\\*?\\})") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "VerbFindEnd" ) ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "VerbatimEnv" , Context { cName = "VerbatimEnv" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Verbatim" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z]" , reCompiled = Just (compileRegex True "[a-zA-Z]") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "LaTeX" , "EnvCommon" ) , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop , Pop , Pop ] , cDynamic = False } ) , ( "VerbatimEnvParam" , Context { cName = "VerbatimEnvParam" , cSyntax = "LaTeX" , cRules = [ Rule { rMatcher = Detect2Chars '}' '[' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Verbatim" ) ] } , Rule { rMatcher = DetectChar ']' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "LaTeX" , "Verbatim" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "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)" , sVersion = "2" , sLicense = "LGPL" , sExtensions = [ "*.tex" , "*.ltx" , "*.dtx" , "*.sty" , "*.cls" , "*.bbx" , "*.cbx" , "*.lbx" , "*.tikz" ] , sStartingContext = "Normal Text" }