{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.C (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "C" , sFilename = "c.xml" , sShortname = "C" , sContexts = fromList [ ( "AfterHash" , Context { cName = "AfterHash" , cSyntax = "C" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "#\\s*(?:include|include_next)" , reCompiled = Just (compileRegex False "#\\s*(?:include|include_next)") , reCaseSensitive = False } , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Include" ) ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*if(?:def|ndef)?(?=\\s+\\S)" , reCompiled = Just (compileRegex False "#\\s*if(?:def|ndef)?(?=\\s+\\S)") , reCaseSensitive = False } , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Preprocessor" ) ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*endif" , reCompiled = Just (compileRegex False "#\\s*endif") , reCaseSensitive = False } , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Preprocessor" ) ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*define.*((?=\\\\))" , reCompiled = Just (compileRegex False "#\\s*define.*((?=\\\\))") , reCaseSensitive = False } , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Define" ) ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*pragma\\s+mark\\s+-\\s*$" , reCompiled = Just (compileRegex False "#\\s*pragma\\s+mark\\s+-\\s*$") , reCaseSensitive = False } , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Preprocessor" ) ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*pragma\\s+mark" , reCompiled = Just (compileRegex False "#\\s*pragma\\s+mark") , reCaseSensitive = False } , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Preprocessor" ) ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*(?:el(?:se|if)|define|undef|line|error|warning|pragma)" , reCompiled = Just (compileRegex False "#\\s*(?:el(?:se|if)|define|undef|line|error|warning|pragma)") , reCaseSensitive = False } , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Preprocessor" ) ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s+[0-9]+" , reCompiled = Just (compileRegex False "#\\s+[0-9]+") , reCaseSensitive = False } , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Preprocessor" ) ] } ] , cAttribute = ErrorTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Commentar 1" , Context { cName = "Commentar 1" , cSyntax = "C" , cRules = [ Rule { rMatcher = LineContinue , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Alerts" , "" ) , rAttribute = CommentTok , 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 } ) , ( "Commentar 2" , Context { cName = "Commentar 2" , cSyntax = "C" , cRules = [ 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 = [] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Commentar/Preprocessor" , Context { cName = "Commentar/Preprocessor" , cSyntax = "C" , cRules = [ Rule { rMatcher = Detect2Chars '*' '/' , 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 } ) , ( "Define" , Context { cName = "Define" , cSyntax = "C" , cRules = [ Rule { rMatcher = LineContinue , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = PreprocessorTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Include" , Context { cName = "Include" , cSyntax = "C" , cRules = [ Rule { rMatcher = LineContinue , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RangeDetect '"' '"' , rAttribute = ImportTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RangeDetect '<' '>' , rAttribute = ImportTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "C" , "Preprocessor" ) , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = PreprocessorTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Normal" , Context { cName = "Normal" , cSyntax = "C" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*if\\s+0\\s*$" , reCompiled = Just (compileRegex True "#\\s*if\\s+0\\s*$") , reCaseSensitive = True } , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Outscoped" ) ] } , Rule { rMatcher = DetectChar '#' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "AfterHash" ) ] } , Rule { rMatcher = StringDetect "//BEGIN" , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Region Marker" ) ] } , Rule { rMatcher = StringDetect "//END" , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Region Marker" ) ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !\"%&'()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "break" , "case" , "continue" , "default" , "do" , "else" , "for" , "goto" , "if" , "return" , "switch" , "while" ]) , rAttribute = ControlFlowTok , 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 [ "enum" , "extern" , "inline" , "sizeof" , "struct" , "typedef" , "union" ]) , rAttribute = KeywordTok , 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 [ "_Bool" , "_Complex" , "_Imaginary" , "auto" , "char" , "const" , "double" , "float" , "int" , "int16_t" , "int32_t" , "int64_t" , "int8_t" , "int_fast16_t" , "int_fast32_t" , "int_fast64_t" , "int_fast8_t" , "int_least16_t" , "int_least32_t" , "int_least64_t" , "int_least8_t" , "intmax_t" , "intptr_t" , "long" , "ptrdiff_t" , "register" , "restrict" , "short" , "sig_atomic_t" , "signed" , "size_t" , "ssize_t" , "static" , "uint16_t" , "uint32_t" , "uint64_t" , "uint8_t" , "uint_fast16_t" , "uint_fast32_t" , "uint_fast64_t" , "uint_fast8_t" , "uint_least16_t" , "uint_least32_t" , "uint_least64_t" , "uint_least8_t" , "uintmax_t" , "uintptr_t" , "unsigned" , "void" , "volatile" , "wchar_t" , "wint_t" ]) , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectIdentifier , 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 = [] } , Rule { rMatcher = Float , rAttribute = FloatTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [ Rule { rMatcher = AnyChar "fF" , rAttribute = FloatTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCOct , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCHex , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "0b[01]+[ul]{0,3}" , reCompiled = Just (compileRegex False "0b[01]+[ul]{0,3}") , reCaseSensitive = False } , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [ Rule { rMatcher = StringDetect "ULL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LUL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LLU" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "UL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LU" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "U" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "L" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCChar , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "String" ) ] } , Rule { rMatcher = IncludeRules ( "Doxygen" , "" ) , rAttribute = NormalTok , 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 = [ Push ( "C" , "Commentar 1" ) ] } , Rule { rMatcher = Detect2Chars '/' '*' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Commentar 2" ) ] } , Rule { rMatcher = AnyChar ":!%&()+,-/.*<=>?[]|~^;" , 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 } ) , ( "Outscoped" , Context { cName = "Outscoped" , cSyntax = "C" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Alerts" , "" ) , rAttribute = CommentTok , 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 = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "String" ) ] } , Rule { rMatcher = IncludeRules ( "Doxygen" , "" ) , 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 = [ Push ( "C" , "Commentar 1" ) ] } , Rule { rMatcher = Detect2Chars '/' '*' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Commentar 2" ) ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*if" , reCompiled = Just (compileRegex True "#\\s*if") , reCaseSensitive = True } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Outscoped intern" ) ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*el(?:se|if)" , reCompiled = Just (compileRegex True "#\\s*el(?:se|if)") , reCaseSensitive = True } , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*endif" , reCompiled = Just (compileRegex True "#\\s*endif") , reCaseSensitive = True } , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Outscoped intern" , Context { cName = "Outscoped intern" , cSyntax = "C" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Alerts" , "" ) , rAttribute = CommentTok , 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 = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "String" ) ] } , Rule { rMatcher = IncludeRules ( "Doxygen" , "" ) , 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 = [ Push ( "C" , "Commentar 1" ) ] } , Rule { rMatcher = Detect2Chars '/' '*' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Commentar 2" ) ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*if" , reCompiled = Just (compileRegex True "#\\s*if") , reCaseSensitive = True } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Outscoped intern" ) ] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*endif" , reCompiled = Just (compileRegex True "#\\s*endif") , reCaseSensitive = True } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Preprocessor" , Context { cName = "Preprocessor" , cSyntax = "C" , cRules = [ Rule { rMatcher = LineContinue , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Doxygen" , "" ) , rAttribute = PreprocessorTok , 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 = [ Push ( "C" , "Commentar/Preprocessor" ) ] } , Rule { rMatcher = Detect2Chars '/' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "C" , "Commentar 1" ) ] } ] , cAttribute = PreprocessorTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Region Marker" , Context { cName = "Region Marker" , cSyntax = "C" , cRules = [] , cAttribute = RegionMarkerTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "String" , Context { cName = "String" , cSyntax = "C" , cRules = [ Rule { rMatcher = LineContinue , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCStringChar , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "" , sVersion = "2" , sLicense = "" , sExtensions = [ "*.c" , "*.C" , "*.h" ] , sStartingContext = "Normal" }