{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Python (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "Python" , sFilename = "python.xml" , sShortname = "Python" , sContexts = fromList [ ( "#CheckForString" , Context { cName = "#CheckForString" , cSyntax = "Python" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = LineContinue , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "CheckForStringNext" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "CheckForStringNext" , Context { cName = "CheckForStringNext" , cSyntax = "Python" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = LineContinue , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "CheckForStringNext" ) ] } , Rule { rMatcher = IncludeRules ( "Python" , "StringVariants" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "CommentVariants" , Context { cName = "CommentVariants" , cSyntax = "Python" , 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 = "u?'''" , reCompiled = Just (compileRegex False "u?'''") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Triple A-comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "u?\"\"\"" , reCompiled = Just (compileRegex False "u?\"\"\"") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Triple Q-comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "u?'" , reCompiled = Just (compileRegex False "u?'") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Single A-comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "u?\"" , reCompiled = Just (compileRegex False "u?\"") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Single Q-comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(u?r|ru)'''" , reCompiled = Just (compileRegex False "(u?r|ru)'''") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Triple A-comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(u?r|ru)\"\"\"" , reCompiled = Just (compileRegex False "(u?r|ru)\"\"\"") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Triple Q-comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(u?r|ru)'" , reCompiled = Just (compileRegex False "(u?r|ru)'") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Single A-comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(u?r|ru)\"" , reCompiled = Just (compileRegex False "(u?r|ru)\"") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Single Q-comment" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Dictionary" , Context { cName = "Dictionary" , cSyntax = "Python" , cRules = [ Rule { rMatcher = DetectSpaces , 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 = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Python" , "StringVariants" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "Normal" ) , 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 } ) , ( "Hash comment" , Context { cName = "Hash comment" , cSyntax = "Python" , cRules = [ Rule { rMatcher = IncludeRules ( "Alerts" , "" ) , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Modelines" , "" ) , 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 } ) , ( "List" , Context { cName = "List" , cSyntax = "Python" , cRules = [ Rule { rMatcher = DetectSpaces , 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 = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Python" , "StringVariants" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "Normal" ) , 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 } ) , ( "Normal" , Context { cName = "Normal" , cSyntax = "Python" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !#%&'()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "as" , "from" , "import" ]) , rAttribute = ImportTok , 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 [ "class" , "def" , "del" , "global" , "lambda" , "nonlocal" ]) , 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 [ "and" , "in" , "is" , "not" , "or" ]) , 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 [ "assert" , "async" , "await" , "break" , "continue" , "elif" , "else" , "except" , "finally" , "for" , "if" , "pass" , "raise" , "return" , "try" , "while" , "with" , "yield" ]) , 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 [ "__import__" , "abs" , "all" , "any" , "apply" , "ascii" , "basestring" , "bin" , "bool" , "buffer" , "bytearray" , "bytes" , "callable" , "chr" , "classmethod" , "cmp" , "coerce" , "compile" , "complex" , "delattr" , "dict" , "dir" , "divmod" , "enumerate" , "eval" , "exec" , "execfile" , "file" , "filter" , "float" , "format" , "frozenset" , "getattr" , "globals" , "hasattr" , "hash" , "help" , "hex" , "id" , "input" , "int" , "intern" , "isinstance" , "issubclass" , "iter" , "len" , "list" , "locals" , "long" , "map" , "max" , "memoryview" , "min" , "next" , "object" , "oct" , "open" , "ord" , "pow" , "print" , "property" , "range" , "raw_input" , "reduce" , "reload" , "repr" , "reversed" , "round" , "set" , "setattr" , "slice" , "sorted" , "staticmethod" , "str" , "sum" , "super" , "tuple" , "type" , "unichr" , "unicode" , "vars" , "xrange" , "zip" ]) , rAttribute = BuiltInTok , 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 [ "Ellipsis" , "False" , "None" , "NotImplemented" , "True" , "__debug__" , "__file__" , "__name__" , "self" ]) , rAttribute = VariableTok , 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 [ "SIGNAL" , "SLOT" , "connect" ]) , rAttribute = ExtensionTok , 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 [ "ArithmeticError" , "AssertionError" , "AttributeError" , "BaseException" , "BlockingIOError" , "BrokenPipeError" , "BufferError" , "BytesWarning" , "ChildProcessError" , "ConnectionAbortedError" , "ConnectionError" , "ConnectionRefusedError" , "ConnectionResetError" , "DeprecationWarning" , "EOFError" , "EnvironmentError" , "Exception" , "FileExistsError" , "FileNotFoundError" , "FloatingPointError" , "FutureWarning" , "GeneratorExit" , "IOError" , "ImportError" , "ImportWarning" , "IndentationError" , "IndexError" , "InterruptedError" , "IsADirectoryError" , "KeyError" , "KeyboardInterrupt" , "LookupError" , "MemoryError" , "NameError" , "NotADirectoryError" , "NotImplementedError" , "OSError" , "OverflowError" , "PendingDeprecationWarning" , "PermissionError" , "ProcessLookupError" , "ReferenceError" , "ResourceWarning" , "RuntimeError" , "RuntimeWarning" , "StandardError" , "StopIteration" , "SyntaxError" , "SyntaxWarning" , "SystemError" , "SystemExit" , "TabError" , "TimeoutError" , "TypeError" , "UnboundLocalError" , "UnicodeDecodeError" , "UnicodeEncodeError" , "UnicodeError" , "UnicodeTranslateError" , "UnicodeWarning" , "UserWarning" , "ValueError" , "Warning" , "WindowsError" , "ZeroDivisionError" ]) , rAttribute = PreprocessorTok , 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 [ "__abs__" , "__add__" , "__aenter__" , "__aexit__" , "__aiter__" , "__and__" , "__anext__" , "__await__" , "__bytes__" , "__call__" , "__cmp__" , "__coerce__" , "__complex__" , "__contains__" , "__del__" , "__delattr__" , "__delete__" , "__delitem__" , "__delslice__" , "__dir__" , "__div__" , "__divmod__" , "__enter__" , "__eq__" , "__exit__" , "__float__" , "__floordiv__" , "__format__" , "__ge__" , "__get__" , "__getattr__" , "__getattribute__" , "__getitem__" , "__getslice__" , "__gt__" , "__hash__" , "__hex__" , "__iadd__" , "__iand__" , "__idiv__" , "__ifloordiv__" , "__ilshift__" , "__imod__" , "__imul__" , "__index__" , "__init__" , "__int__" , "__invert__" , "__ior__" , "__ipow__" , "__irshift__" , "__isub__" , "__iter__" , "__itruediv__" , "__ixor__" , "__le__" , "__len__" , "__long__" , "__lshift__" , "__lt__" , "__mod__" , "__mul__" , "__ne__" , "__neg__" , "__new__" , "__next__" , "__nonzero__" , "__oct__" , "__or__" , "__pos__" , "__pow__" , "__radd__" , "__rand__" , "__rcmp__" , "__rdiv__" , "__rdivmod__" , "__repr__" , "__reversed__" , "__rfloordiv__" , "__rlshift__" , "__rmod__" , "__rmul__" , "__ror__" , "__rpow__" , "__rrshift__" , "__rshift__" , "__rsub__" , "__rtruediv__" , "__rxor__" , "__set__" , "__setattr__" , "__setitem__" , "__setslice__" , "__str__" , "__sub__" , "__truediv__" , "__unicode__" , "__xor__" ]) , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[a-zA-Z_][a-zA-Z_0-9]{2,}" , reCompiled = Just (compileRegex True "[a-zA-Z_][a-zA-Z_0-9]{2,}") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = " ((([0-9]*\\.[0-9]+|[0-9]+\\.)|([0-9]+|([0-9]*\\.[0-9]+|[0-9]+\\.))[eE](\\+|-)?[0-9]+)|[0-9]+)[jJ]" , reCompiled = Just (compileRegex True " ((([0-9]*\\.[0-9]+|[0-9]+\\.)|([0-9]+|([0-9]*\\.[0-9]+|[0-9]+\\.))[eE](\\+|-)?[0-9]+)|[0-9]+)[jJ]") , reCaseSensitive = True } , rAttribute = OtherTok , 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 = [] , 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 = HlCOct , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [ 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 = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Dictionary" ) ] } , Rule { rMatcher = DetectChar '[' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "List" ) ] } , Rule { rMatcher = DetectChar '(' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Tuple" ) ] } , Rule { rMatcher = IncludeRules ( "Python" , "CommentVariants" ) , 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 ( "Python" , "Hash comment" ) ] } , Rule { rMatcher = IncludeRules ( "Python" , "StringVariants" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "@[_a-zA-Z][\\._a-zA-Z0-9]*" , reCompiled = Just (compileRegex True "@[_a-zA-Z][\\._a-zA-Z0-9]*") , reCaseSensitive = True } , rAttribute = AttributeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = AnyChar "+*/%\\|=;\\!<>!^&~-@" , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Raw A-F-String" , Context { cName = "Raw A-F-String" , cSyntax = "Python" , cRules = [ Rule { rMatcher = HlCStringChar , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringinterpolation" ) , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '\'' , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Raw A-string" , Context { cName = "Raw A-string" , cSyntax = "Python" , cRules = [ Rule { rMatcher = HlCStringChar , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringformat" ) , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '\'' , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Raw Q-F-String" , Context { cName = "Raw Q-F-String" , cSyntax = "Python" , cRules = [ Rule { rMatcher = HlCStringChar , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringinterpolation" ) , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '"' , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Raw Q-string" , Context { cName = "Raw Q-string" , cSyntax = "Python" , cRules = [ Rule { rMatcher = HlCStringChar , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringformat" ) , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '"' , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Raw Triple A-F-String" , Context { cName = "Raw Triple A-F-String" , cSyntax = "Python" , cRules = [ Rule { rMatcher = HlCStringChar , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringinterpolation" ) , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "'''" , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Raw Triple A-string" , Context { cName = "Raw Triple A-string" , cSyntax = "Python" , cRules = [ Rule { rMatcher = HlCStringChar , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringformat" ) , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "'''" , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Raw Triple Q-F-String" , Context { cName = "Raw Triple Q-F-String" , cSyntax = "Python" , cRules = [ Rule { rMatcher = HlCStringChar , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringinterpolation" ) , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "\"\"\"" , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Raw Triple Q-string" , Context { cName = "Raw Triple Q-string" , cSyntax = "Python" , cRules = [ Rule { rMatcher = HlCStringChar , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringformat" ) , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "\"\"\"" , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = VerbatimStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Single A-F-String" , Context { cName = "Single A-F-String" , cSyntax = "Python" , cRules = [ Rule { rMatcher = IncludeRules ( "Python" , "stringescape" ) , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringinterpolation" ) , rAttribute = SpecialStringTok , 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 , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Single A-comment" , Context { cName = "Single A-comment" , cSyntax = "Python" , cRules = [ Rule { rMatcher = HlCStringChar , rAttribute = CommentTok , 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 = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Alerts_indent" , "" ) , 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 } ) , ( "Single A-string" , Context { cName = "Single A-string" , cSyntax = "Python" , cRules = [ Rule { rMatcher = IncludeRules ( "Python" , "stringescape" ) , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringformat" ) , rAttribute = StringTok , 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 , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Single Q-F-String" , Context { cName = "Single Q-F-String" , cSyntax = "Python" , cRules = [ Rule { rMatcher = IncludeRules ( "Python" , "stringescape" ) , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringinterpolation" ) , rAttribute = SpecialStringTok , 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 , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Single Q-comment" , Context { cName = "Single Q-comment" , cSyntax = "Python" , cRules = [ Rule { rMatcher = HlCStringChar , rAttribute = CommentTok , 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 = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Alerts_indent" , "" ) , 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 } ) , ( "Single Q-string" , Context { cName = "Single Q-string" , cSyntax = "Python" , cRules = [ Rule { rMatcher = IncludeRules ( "Python" , "stringescape" ) , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringformat" ) , rAttribute = StringTok , 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 , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "String Interpolation" , Context { cName = "String Interpolation" , cSyntax = "Python" , cRules = [ Rule { rMatcher = DetectChar '\\' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "(![rs])?(:([^}]?[<>=^])?[ +-]?#?0?[0-9]*(\\.[0-9]+)?[bcdeEfFgGnosxX%]?)?\\}" , reCompiled = Just (compileRegex True "(![rs])?(:([^}]?[<>=^])?[ +-]?#?0?[0-9]*(\\.[0-9]+)?[bcdeEfFgGnosxX%]?)?\\}") , reCaseSensitive = True } , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Python" , "Normal" ) , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = SpecialCharTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "StringVariants" , Context { cName = "StringVariants" , cSyntax = "Python" , 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 = "u?'''" , reCompiled = Just (compileRegex False "u?'''") , reCaseSensitive = False } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Triple A-string" ) ] } , Rule { rMatcher = RegExpr RE { reString = "u?\"\"\"" , reCompiled = Just (compileRegex False "u?\"\"\"") , reCaseSensitive = False } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Triple Q-string" ) ] } , Rule { rMatcher = RegExpr RE { reString = "u?'" , reCompiled = Just (compileRegex False "u?'") , reCaseSensitive = False } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Single A-string" ) ] } , Rule { rMatcher = RegExpr RE { reString = "u?\"" , reCompiled = Just (compileRegex False "u?\"") , reCaseSensitive = False } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Single Q-string" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(u?r|ru)'''" , reCompiled = Just (compileRegex False "(u?r|ru)'''") , reCaseSensitive = False } , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Raw Triple A-string" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(u?r|ru)\"\"\"" , reCompiled = Just (compileRegex False "(u?r|ru)\"\"\"") , reCaseSensitive = False } , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Raw Triple Q-string" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(u?r|ru)'" , reCompiled = Just (compileRegex False "(u?r|ru)'") , reCaseSensitive = False } , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Raw A-string" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(u?r|ru)\"" , reCompiled = Just (compileRegex False "(u?r|ru)\"") , reCaseSensitive = False } , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Raw Q-string" ) ] } , Rule { rMatcher = StringDetect "f'''" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Triple A-F-String" ) ] } , Rule { rMatcher = StringDetect "f\"\"\"" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Triple Q-F-String" ) ] } , Rule { rMatcher = StringDetect "f'" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Single A-F-String" ) ] } , Rule { rMatcher = StringDetect "f\"" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Single Q-F-String" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(fr|rf)'''" , reCompiled = Just (compileRegex False "(fr|rf)'''") , reCaseSensitive = False } , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Raw Triple A-F-String" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(fr|rf)\"\"\"" , reCompiled = Just (compileRegex False "(fr|rf)\"\"\"") , reCaseSensitive = False } , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Raw Triple Q-F-String" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(fr|rf)'" , reCompiled = Just (compileRegex False "(fr|rf)'") , reCaseSensitive = False } , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Raw A-F-String" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(fr|rf)\"" , reCompiled = Just (compileRegex False "(fr|rf)\"") , reCaseSensitive = False } , rAttribute = VerbatimStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Python" , "Raw Q-F-String" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Triple A-F-String" , Context { cName = "Triple A-F-String" , cSyntax = "Python" , cRules = [ Rule { rMatcher = IncludeRules ( "Python" , "stringescape" ) , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringinterpolation" ) , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "'''" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Triple A-comment" , Context { cName = "Triple A-comment" , cSyntax = "Python" , cRules = [ Rule { rMatcher = StringDetect "'''" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Alerts_indent" , "" ) , 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 } ) , ( "Triple A-string" , Context { cName = "Triple A-string" , cSyntax = "Python" , cRules = [ Rule { rMatcher = IncludeRules ( "Python" , "stringescape" ) , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringformat" ) , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "'''" , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Triple Q-F-String" , Context { cName = "Triple Q-F-String" , cSyntax = "Python" , cRules = [ Rule { rMatcher = IncludeRules ( "Python" , "stringescape" ) , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringinterpolation" ) , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "\"\"\"" , rAttribute = SpecialStringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Triple Q-comment" , Context { cName = "Triple Q-comment" , cSyntax = "Python" , cRules = [ Rule { rMatcher = HlCChar , 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 ] } , Rule { rMatcher = IncludeRules ( "Alerts_indent" , "" ) , 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 } ) , ( "Triple Q-string" , Context { cName = "Triple Q-string" , cSyntax = "Python" , cRules = [ Rule { rMatcher = IncludeRules ( "Python" , "stringescape" ) , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "stringformat" ) , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "\"\"\"" , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Push ( "Python" , "#CheckForString" ) ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Tuple" , Context { cName = "Tuple" , cSyntax = "Python" , cRules = [ Rule { rMatcher = DetectSpaces , 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 = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Python" , "StringVariants" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Python" , "Normal" ) , 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 } ) , ( "stringescape" , Context { cName = "stringescape" , cSyntax = "Python" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\\\[\\\\'\"abfnrtv]" , reCompiled = Just (compileRegex True "\\\\[\\\\'\"abfnrtv]") , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\[0-7]{1,3}" , reCompiled = Just (compileRegex True "\\\\[0-7]{1,3}") , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\x[0-9A-Fa-f]{2}" , reCompiled = Just (compileRegex True "\\\\x[0-9A-Fa-f]{2}") , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\u[0-9A-Fa-f]{4}" , reCompiled = Just (compileRegex True "\\\\u[0-9A-Fa-f]{4}") , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\U[0-9A-Fa-f]{8}" , reCompiled = Just (compileRegex True "\\\\U[0-9A-Fa-f]{8}") , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\N\\{[a-zA-Z0-9\\- ]+\\}" , reCompiled = Just (compileRegex True "\\\\N\\{[a-zA-Z0-9\\- ]+\\}") , 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 } ) , ( "stringformat" , Context { cName = "stringformat" , cSyntax = "Python" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "%((\\([a-zA-Z0-9_]+\\))?[#0\\- +]?([1-9][0-9]*|\\*)?(\\.([1-9][0-9]*|\\*))?[hlL]?[crsdiouxXeEfFgG%]|prog|default)" , reCompiled = Just (compileRegex True "%((\\([a-zA-Z0-9_]+\\))?[#0\\- +]?([1-9][0-9]*|\\*)?(\\.([1-9][0-9]*|\\*))?[hlL]?[crsdiouxXeEfFgG%]|prog|default)") , reCaseSensitive = True } , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\{(([a-zA-Z0-9_]+|[0-9]+)(\\.[a-zA-Z0-9_]+|\\[[^ \\]]+\\])*)?(![rs])?(:([^}]?[<>=^])?[ +-]?#?0?[0-9]*(\\.[0-9]+)?[bcdeEfFgGnosxX%]?)?\\}" , reCompiled = Just (compileRegex True "\\{(([a-zA-Z0-9_]+|[0-9]+)(\\.[a-zA-Z0-9_]+|\\[[^ \\]]+\\])*)?(![rs])?(:([^}]?[<>=^])?[ +-]?#?0?[0-9]*(\\.[0-9]+)?[bcdeEfFgGnosxX%]?)?\\}") , reCaseSensitive = True } , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '{' '{' , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '}' '}' , rAttribute = SpecialCharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = SpecialCharTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "stringinterpolation" , Context { cName = "stringinterpolation" , cSyntax = "Python" , cRules = [ Rule { rMatcher = Detect2Chars '{' '{' , rAttribute = CharTok , 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 ( "Python" , "String Interpolation" ) ] } ] , cAttribute = SpecialStringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Michael Bueker" , sVersion = "4" , sLicense = "" , sExtensions = [ "*.py" , "*.pyw" , "SConstruct" , "SConscript" ] , sStartingContext = "Normal" }