{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Doxygen (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "Doxygen" , sFilename = "doxygen.xml" , sShortname = "Doxygen" , sContexts = fromList [ ( "BlockComment" , Context { cName = "BlockComment" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '*' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Alerts" , "" ) , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '@' '{' , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '@' '}' , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Doxygen" , "SL_DetectEnv" ) , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[]^{|}" } (makeWordSet True [ "@\"" , "@#" , "@$" , "@%" , "@&" , "@--" , "@---" , "@." , "@::" , "@<" , "@>" , "@@" , "@\\" , "@arg" , "@author" , "@authors" , "@brief" , "@callergraph" , "@callgraph" , "@date" , "@deprecated" , "@details" , "@docbookonly" , "@else" , "@endcond" , "@enddocbookonly" , "@endhtmlonly" , "@endif" , "@endinternal" , "@endlatexonly" , "@endlink" , "@endmanonly" , "@endparblock" , "@endrtfonly" , "@endsecreflist" , "@endxmlonly" , "@f$" , "@f[" , "@f]" , "@hideinitializer" , "@htmlonly" , "@internal" , "@invariant" , "@latexonly" , "@li" , "@manonly" , "@n" , "@nosubgrouping" , "@only" , "@parblock" , "@pivate" , "@pivatesection" , "@post" , "@pre" , "@protected" , "@protectedsection" , "@public" , "@publicsection" , "@pure" , "@remark" , "@remarks" , "@result" , "@return" , "@returns" , "@rtfonly" , "@sa" , "@secreflist" , "@see" , "@short" , "@showinitializer" , "@since" , "@static" , "@tableofcontents" , "@test" , "@version" , "@xmlonly" , "@~" , "\\\"" , "\\#" , "\\$" , "\\%" , "\\&" , "\\--" , "\\---" , "\\." , "\\::" , "\\<" , "\\>" , "\\@" , "\\\\" , "\\arg" , "\\author" , "\\authors" , "\\brief" , "\\callergraph" , "\\callgraph" , "\\date" , "\\deprecated" , "\\details" , "\\docbookonly" , "\\else" , "\\endcond" , "\\enddocbookonly" , "\\endhtmlonly" , "\\endif" , "\\endinternal" , "\\endlatexonly" , "\\endlink" , "\\endmanonly" , "\\endparblock" , "\\endrtfonly" , "\\endsecreflist" , "\\endxmlonly" , "\\f$" , "\\f[" , "\\f]" , "\\hideinitializer" , "\\htmlonly" , "\\internal" , "\\invariant" , "\\latexonly" , "\\li" , "\\manonly" , "\\n" , "\\nosubgrouping" , "\\only" , "\\parblock" , "\\post" , "\\pre" , "\\private" , "\\privatesection" , "\\protected" , "\\protectedsection" , "\\public" , "\\publicsection" , "\\pure" , "\\remark" , "\\remarks" , "\\result" , "\\return" , "\\returns" , "\\rtfonly" , "\\sa" , "\\secreflist" , "\\see" , "\\short" , "\\showinitializer" , "\\since" , "\\static" , "\\tableofcontents" , "\\test" , "\\version" , "\\xmlonly" , "\\~" ]) , rAttribute = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[]^{|}" } (makeWordSet True [ "@a" , "@anchor" , "@b" , "@c" , "@cite" , "@cond" , "@copybrief" , "@copydetails" , "@copydoc" , "@def" , "@dir" , "@dontinclude" , "@e" , "@elseif" , "@em" , "@enum" , "@example" , "@exception" , "@exceptions" , "@extends" , "@file" , "@htmlinclude" , "@idlexcept" , "@if" , "@ifnot" , "@implements" , "@include" , "@includelineno" , "@latexinclude" , "@link" , "@memberof" , "@namespace" , "@p" , "@package" , "@property" , "@related" , "@relatedalso" , "@relates" , "@relatesalso" , "@retval" , "@throw" , "@throws" , "@verbinclude" , "@version" , "@xrefitem" , "\\a" , "\\anchor" , "\\b" , "\\c" , "\\cite" , "\\cond" , "\\copybrief" , "\\copydetails" , "\\copydoc" , "\\def" , "\\dir" , "\\dontinclude" , "\\e" , "\\elseif" , "\\em" , "\\enum" , "\\example" , "\\exception" , "\\exceptions" , "\\extends" , "\\file" , "\\htmlinclude" , "\\idlexcept" , "\\if" , "\\ifnot" , "\\implements" , "\\include" , "\\includelineno" , "\\latexinclude" , "\\link" , "\\memberof" , "\\namespace" , "\\p" , "\\package" , "\\property" , "\\related" , "\\relatedalso" , "\\relates" , "\\relatesalso" , "\\retval" , "\\throw" , "\\throws" , "\\verbinclude" , "\\version" , "\\xrefitem" ]) , rAttribute = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "ML_TagWord" ) ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[]^{|}" } (makeWordSet True [ "@param" , "@tparam" , "\\param" , "\\tparam" ]) , rAttribute = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "ML_TagParam" ) ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[]^{|}" } (makeWordSet True [ "@image" , "\\image" ]) , rAttribute = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "ML_TagWordWord" ) ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[]^{|}" } (makeWordSet True [ "@addindex" , "@copyright" , "@fn" , "@ingroup" , "@line" , "@mainpage" , "@name" , "@overload" , "@par" , "@skip" , "@skipline" , "@typedef" , "@until" , "@var" , "@vhdlflow" , "\\addindex" , "\\copyright" , "\\fn" , "\\ingroup" , "\\line" , "\\mainpage" , "\\name" , "\\overload" , "\\par" , "\\skip" , "\\skipline" , "\\typedef" , "\\until" , "\\var" , "\\vhdlflow" ]) , rAttribute = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "ML_TagString" ) ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[]^{|}" } (makeWordSet True [ "@addtogroup" , "@category" , "@class" , "@defgroup" , "@diafile" , "@dotfile" , "@headerfile" , "@interface" , "@mscfile" , "@page" , "@paragraph" , "@prtocol" , "@ref" , "@section" , "@snippet" , "@struct" , "@subpage" , "@subsection" , "@subsubsection" , "@union" , "@weakgroup" , "\\addtogroup" , "\\category" , "\\class" , "\\defgroup" , "\\diafile" , "\\dotfile" , "\\headerfile" , "\\interface" , "\\mscfile" , "\\page" , "\\paragraph" , "\\protocol" , "\\ref" , "\\section" , "\\snippet" , "\\struct" , "\\subpage" , "\\subsection" , "\\subsubsection" , "\\union" , "\\weakgroup" ]) , rAttribute = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "ML_TagWordString" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[@\\\\]([^@\\\\ \\t\\*]|\\*(?!/))+" , reCompiled = Just (compileRegex True "[@\\\\]([^@\\\\ \\t\\*]|\\*(?!/))+") , reCaseSensitive = True } , rAttribute = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectIdentifier , rAttribute = CommentTok , 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 = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '<' '<' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "<\\/?[\\w0-9._:-@]+" , reCompiled = Just (compileRegex True "<\\/?[\\w0-9._:-@]+") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "ML_htmltag" ) ] } , Rule { rMatcher = StringDetect "" , 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 } ) , ( "ML_htmltag" , Context { cName = "ML_htmltag" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = Detect2Chars '*' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = Detect2Chars '/' '>' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '>' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*=\\s*" , reCompiled = Just (compileRegex True "\\s*=\\s*") , reCaseSensitive = True } , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "ML_identifiers" ) ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ML_identifiers" , Context { cName = "ML_identifiers" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = Detect2Chars '*' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*#?[a-zA-Z0-9]*" , reCompiled = Just (compileRegex True "\\s*#?[a-zA-Z0-9]*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '\'' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "ML_types1" ) ] } , Rule { rMatcher = DetectChar '"' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "ML_types2" ) ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ML_types1" , Context { cName = "ML_types1" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = Detect2Chars '*' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '\'' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ML_types2" , Context { cName = "ML_types2" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = Detect2Chars '*' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '"' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Msc" , Context { cName = "Msc" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = IncludeRules ( "Doxygen" , "SL_DetectComment" ) , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[@\\\\]endmsc\\b" , reCompiled = Just (compileRegex True "[@\\\\]endmsc\\b") , reCaseSensitive = True } , rAttribute = AnnotationTok , 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 } ) , ( "Normal" , Context { cName = "Normal" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "//(!|(/(?=[^/]|$)))?[]^{|}" } (makeWordSet True [ "@note" , "\\note" ]) , rAttribute = InformationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[]^{|}" } (makeWordSet True [ "@warning" , "\\warning" ]) , rAttribute = WarningTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[]^{|}" } (makeWordSet True [ "@attention" , "@bug" , "\\attention" , "\\bug" ]) , rAttribute = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[]^{|}" } (makeWordSet True [ "@todo" , "\\todo" ]) , rAttribute = AnnotationTok , 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 = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SL_Tag2ndWord" , Context { cName = "SL_Tag2ndWord" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = CommentTok , 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 = CommentVarTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = CommentVarTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop , Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SL_TagParam" , Context { cName = "SL_TagParam" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "[in]" , rAttribute = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "SL_Tag2ndWord" ) ] } , Rule { rMatcher = StringDetect "[out]" , rAttribute = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "SL_Tag2ndWord" ) ] } , Rule { rMatcher = StringDetect "[in,out]" , rAttribute = AnnotationTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "SL_Tag2ndWord" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S(?=([][,?;()]|\\.$|\\.?\\s))" , reCompiled = Just (compileRegex True "\\S(?=([][,?;()]|\\.$|\\.?\\s))") , reCaseSensitive = True } , rAttribute = CommentVarTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = CommentVarTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SL_TagString" , Context { cName = "SL_TagString" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SL_htmltag" , Context { cName = "SL_htmltag" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = Detect2Chars '/' '>' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '>' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*=\\s*" , reCompiled = Just (compileRegex True "\\s*=\\s*") , reCaseSensitive = True } , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "SL_identifiers" ) ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SL_identifiers" , Context { cName = "SL_identifiers" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*#?[a-zA-Z0-9]*" , reCompiled = Just (compileRegex True "\\s*#?[a-zA-Z0-9]*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '\'' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "SL_types1" ) ] } , Rule { rMatcher = DetectChar '"' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Doxygen" , "SL_types2" ) ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SL_types1" , Context { cName = "SL_types1" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = DetectChar '\'' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SL_types2" , Context { cName = "SL_types2" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = DetectChar '"' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Verbatim" , Context { cName = "Verbatim" , cSyntax = "Doxygen" , cRules = [ Rule { rMatcher = IncludeRules ( "Doxygen" , "SL_DetectComment" ) , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[@\\\\]endverbatim\\b" , reCompiled = Just (compileRegex True "[@\\\\]endverbatim\\b") , reCaseSensitive = True } , rAttribute = AnnotationTok , 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 } ) ] , sAuthor = "Dominik Haumann (dhdev@gmx.de)" , sVersion = "3" , sLicense = "LGPLv2+" , sExtensions = [ "*.dox" , "*.doxygen" ] , sStartingContext = "Normal" }