{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Perl (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"Perl\", sFilename = \"perl.xml\", sShortname = \"Perl\", sContexts = fromList [(\"Backticked\",Context {cName = \"Backticked\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '`', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"comment\",Context {cName = \"comment\", cSyntax = \"Perl\", 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 = []}], cAttribute = CommentTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"data_handle\",Context {cName = \"data_handle\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\=(?:head[1-6]|over|back|item|for|begin|end|pod)\\\\s+.*\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Push (\"Perl\",\"pod\")]},Rule {rMatcher = StringDetect \"__END__\", rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = True, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"normal\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"end_handle\",Context {cName = \"end_handle\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\=(?:head[1-6]|over|back|item|for|begin|end|pod)\\\\s*.*\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Push (\"Perl\",\"pod\")]},Rule {rMatcher = StringDetect \"__DATA__\", rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = True, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"data_handle\")]}], cAttribute = CommentTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"find_here_document\",Context {cName = \"find_here_document\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"(\\\\w+)\\\\s*;?\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"here_document\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*\\\"([^\\\"]+)\\\"\\\\s*;?\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"here_document\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*`([^`]+)`\\\\s*;?\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"here_document\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*'([^']+)'\\\\s*;?\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"here_document_dumb\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"find_pattern\",Context {cName = \"find_pattern\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\s+#.*\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"pattern_brace\")]},Rule {rMatcher = DetectChar '(', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"pattern_paren\")]},Rule {rMatcher = DetectChar '[', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"pattern_bracket\")]},Rule {rMatcher = DetectChar '\\'', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"pattern_sq\")]},Rule {rMatcher = RegExpr (RE {reString = \"([^\\\\w\\\\s])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"pattern\")]}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"find_qqx\",Context {cName = \"find_qqx\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectChar '(', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"ip_string_2\")]},Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"ip_string_3\")]},Rule {rMatcher = DetectChar '[', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"ip_string_4\")]},Rule {rMatcher = DetectChar '<', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"ip_string_5\")]},Rule {rMatcher = RegExpr (RE {reString = \"([^a-zA-Z0-9_\\\\s[\\\\]{}()])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"ip_string_6\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s+#.*\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"find_quoted\",Context {cName = \"find_quoted\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"x\\\\s*(')\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"string_6\")]},Rule {rMatcher = AnyChar \"qx\", rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"find_qqx\")]},Rule {rMatcher = DetectChar 'w', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"find_qw\")]},Rule {rMatcher = DetectChar '(', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"string_2\")]},Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"string_3\")]},Rule {rMatcher = DetectChar '[', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"string_4\")]},Rule {rMatcher = DetectChar '<', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"string_5\")]},Rule {rMatcher = RegExpr (RE {reString = \"([^a-zA-Z0-9_\\\\s[\\\\]{}()])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"string_6\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s+#.*\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"find_qw\",Context {cName = \"find_qw\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectChar '(', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"quote_word_paren\")]},Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"quote_word_brace\")]},Rule {rMatcher = DetectChar '[', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"quote_word_bracket\")]},Rule {rMatcher = RegExpr (RE {reString = \"([^a-zA-Z0-9_\\\\s[\\\\]{}()])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"quote_word\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s+#.*\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"find_subst\",Context {cName = \"find_subst\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\s+#.*\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_curlybrace_pattern\")]},Rule {rMatcher = DetectChar '(', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_paren_pattern\")]},Rule {rMatcher = DetectChar '[', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_bracket_pattern\")]},Rule {rMatcher = DetectChar '\\'', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_sq_pattern\")]},Rule {rMatcher = RegExpr (RE {reString = \"([^\\\\w\\\\s[\\\\]{}()])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_slash_pattern\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"find_variable\",Context {cName = \"find_variable\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\$[0-9]+\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect\")]},Rule {rMatcher = RegExpr (RE {reString = \"[@\\\\$](?:[\\\\+\\\\-_]\\\\B|ARGV\\\\b|INC\\\\b)\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect\")]},Rule {rMatcher = RegExpr (RE {reString = \"[%\\\\$](?:INC\\\\b|ENV\\\\b|SIG\\\\b)\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$\\\\$[\\\\$\\\\w_]\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$[#_][\\\\w_]\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$+::\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$[^a-zA-Z0-9\\\\s{][A-Z]?\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect\")]},Rule {rMatcher = RegExpr (RE {reString = \"[\\\\$@%]\\\\{[\\\\w_]+\\\\}\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect\")]},Rule {rMatcher = AnyChar \"$@%\", rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\*[a-zA-Z_]+\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\*[^a-zA-Z0-9\\\\s{][A-Z]?\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = AnyChar \"$@%*\", rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = DataTypeTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"find_variable_unsafe\",Context {cName = \"find_variable_unsafe\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\$[0-9]+\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect_unsafe\")]},Rule {rMatcher = RegExpr (RE {reString = \"[@\\\\$](?:[\\\\+\\\\-_]\\\\B|ARGV\\\\b|INC\\\\b)\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect_unsafe\")]},Rule {rMatcher = RegExpr (RE {reString = \"[%\\\\$](?:INC\\\\b|ENV\\\\b|SIG\\\\b)\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect_unsafe\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$\\\\$[\\\\$\\\\w_]\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect_unsafe\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$[#_][\\\\w_]\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect_unsafe\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$+::\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect_unsafe\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$[^a-zA-Z0-9\\\\s{][A-Z]?\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[\\\\$@%]\\\\{[\\\\w_]+\\\\}\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect_unsafe\")]},Rule {rMatcher = RegExpr (RE {reString = \"[\\\\$@%]\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect_unsafe\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\*\\\\w+\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"var_detect_unsafe\")]},Rule {rMatcher = AnyChar \"$@%*\", rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = DataTypeTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"here_document\",Context {cName = \"here_document\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"%1\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Pop,Pop]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\=\\\\s*<<\\\\s*[\\\"']?([A-Z0-9_\\\\-]+)[\\\"']?\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"here_document\")]},Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = True}),(\"here_document_dumb\",Context {cName = \"here_document_dumb\", cSyntax = \"Perl\", 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 = \"%1\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Pop,Pop]},Rule {rMatcher = DetectIdentifier, 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 = True}),(\"ip_string\",Context {cName = \"ip_string\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectChar '\"', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"ip_string_2\",Context {cName = \"ip_string_2\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RangeDetect '(' ')', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar ')', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"ip_string_3\",Context {cName = \"ip_string_3\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RangeDetect '{' '}', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"ip_string_4\",Context {cName = \"ip_string_4\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RangeDetect '[' ']', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar ']', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"ip_string_5\",Context {cName = \"ip_string_5\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RangeDetect '<' '>', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '>', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"ip_string_6\",Context {cName = \"ip_string_6\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\%1\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '1', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = True}),(\"ipstring_internal\",Context {cName = \"ipstring_internal\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectIdentifier, rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[UuLlEtnaefr]\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\.\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(?:[\\\\$@]\\\\S|%[\\\\w{])\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"find_variable_unsafe\")]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"normal\",Context {cName = \"normal\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"#!\\\\/.*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = []},Rule {rMatcher = StringDetect \"__DATA__\", rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = True, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"data_handle\")]},Rule {rMatcher = StringDetect \"__END__\", rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = True, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\bsub\\\\s+\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"sub_name_def\")]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"BEGIN\",\"END\",\"__DATA__\",\"__END__\",\"__FILE__\",\"__LINE__\",\"__PACKAGE__\",\"break\",\"continue\",\"default\",\"do\",\"each\",\"else\",\"elsif\",\"for\",\"foreach\",\"given\",\"if\",\"last\",\"local\",\"my\",\"next\",\"our\",\"package\",\"return\",\"state\",\"sub\",\"unless\",\"until\",\"when\",\"while\"])), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"!=\",\"%\",\"&\",\"&&\",\"&&=\",\"&=\",\"*\",\"**=\",\"*=\",\"+\",\"+=\",\",\",\"-\",\"-=\",\"->\",\".\",\"//\",\"//=\",\"/=\",\"::\",\";\",\"<\",\"<<\",\"=\",\"=>\",\">\",\">>\",\"?=\",\"\\\\\",\"^\",\"and\",\"cmp\",\"eq\",\"ge\",\"gt\",\"le\",\"lt\",\"ne\",\"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 = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"abs\",\"accept\",\"alarm\",\"atan2\",\"bind\",\"binmode\",\"bless\",\"caller\",\"chdir\",\"chmod\",\"chomp\",\"chop\",\"chown\",\"chr\",\"chroot\",\"close\",\"closedir\",\"connect\",\"cos\",\"crypt\",\"dbmclose\",\"dbmopen\",\"defined\",\"delete\",\"die\",\"dump\",\"endgrent\",\"endhostent\",\"endnetent\",\"endprotoent\",\"endpwent\",\"endservent\",\"eof\",\"eval\",\"exec\",\"exists\",\"exit\",\"exp\",\"fcntl\",\"fileno\",\"flock\",\"fork\",\"format\",\"formline\",\"getc\",\"getgrent\",\"getgrgid\",\"getgrnam\",\"gethostbyaddr\",\"gethostbyname\",\"gethostent\",\"getlogin\",\"getnetbyaddr\",\"getnetbyname\",\"getnetent\",\"getpeername\",\"getpgrp\",\"getppid\",\"getpriority\",\"getprotobyname\",\"getprotobynumber\",\"getprotoent\",\"getpwent\",\"getpwnam\",\"getpwuid\",\"getservbyname\",\"getservbyport\",\"getservent\",\"getsockname\",\"getsockopt\",\"glob\",\"gmtime\",\"goto\",\"grep\",\"hex\",\"import\",\"index\",\"int\",\"ioctl\",\"join\",\"keys\",\"kill\",\"last\",\"lc\",\"lcfirst\",\"length\",\"link\",\"listen\",\"localtime\",\"lock\",\"log\",\"lstat\",\"map\",\"mkdir\",\"msgctl\",\"msgget\",\"msgrcv\",\"msgsnd\",\"no\",\"oct\",\"open\",\"opendir\",\"ord\",\"pack\",\"package\",\"pipe\",\"pop\",\"pos\",\"print\",\"printf\",\"prototype\",\"push\",\"quotemeta\",\"rand\",\"read\",\"readdir\",\"readline\",\"readlink\",\"recv\",\"redo\",\"ref\",\"rename\",\"require\",\"reset\",\"return\",\"reverse\",\"rewinddir\",\"rindex\",\"rmdir\",\"scalar\",\"seek\",\"seekdir\",\"select\",\"semctl\",\"semget\",\"semop\",\"send\",\"setgrent\",\"sethostent\",\"setnetent\",\"setpgrp\",\"setpriority\",\"setprotoent\",\"setpwent\",\"setservent\",\"setsockopt\",\"shift\",\"shmctl\",\"shmget\",\"shmread\",\"shmwrite\",\"shutdown\",\"sin\",\"sleep\",\"socket\",\"socketpair\",\"sort\",\"splice\",\"split\",\"sprintf\",\"sqrt\",\"srand\",\"stat\",\"study\",\"sub\",\"substr\",\"symlink\",\"syscall\",\"sysread\",\"sysseek\",\"system\",\"syswrite\",\"tell\",\"telldir\",\"tie\",\"time\",\"times\",\"truncate\",\"uc\",\"ucfirst\",\"umask\",\"undef\",\"unlink\",\"unpack\",\"unshift\",\"untie\",\"use\",\"utime\",\"values\",\"vec\",\"wait\",\"waitpid\",\"wantarray\",\"warn\",\"write\"])), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"bytes\",\"constant\",\"diagnostics\",\"english\",\"filetest\",\"integer\",\"less\",\"locale\",\"open\",\"sigtrap\",\"strict\",\"subs\",\"utf8\",\"vars\",\"warnings\"])), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\=\\\\w+(\\\\s|$)\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Push (\"Perl\",\"pod\")]},Rule {rMatcher = DetectSpaces, 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 (\"Perl\",\"comment\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b\\\\-?0[xX]([0-9a-fA-F]|_[0-9a-fA-F])+\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"slash_safe_escape\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b\\\\-?0[bB]([01]|_[01])+\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"slash_safe_escape\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b\\\\-?0[1-7]([0-7]|_[0-7])*\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"slash_safe_escape\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b\\\\-?[0-9]([0-9]|_[0-9])*\\\\.[0-9]([0-9]|_[0-9])*([eE]\\\\-?[1-9]([0-9]|_[0-9])*(\\\\.[0-9]*)?)?\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"slash_safe_escape\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b\\\\-?[1-9]([0-9]|_[0-9])*\\\\b\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"slash_safe_escape\")]},Rule {rMatcher = Int, rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"slash_safe_escape\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\([\\\"'])[^\\\\1]\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '&' '\\'', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '\"', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"ip_string\")]},Rule {rMatcher = DetectChar '\\'', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"string\")]},Rule {rMatcher = DetectChar '`', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"Backticked\")]},Rule {rMatcher = RegExpr (RE {reString = \"(?:[$@]\\\\S|%[\\\\w{]|\\\\*[^\\\\d\\\\*{\\\\$@%=(])\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"find_variable\")]},Rule {rMatcher = RegExpr (RE {reString = \"<[A-Z0-9_]+>\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*<<(?=\\\\w+|\\\\s*[\\\"'])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"find_here_document\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*\\\\}\\\\s*/{1,2}\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*[)\\\\]]\\\\s*/{1,2}\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\w+::\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"sub_name_def\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\w+[=]\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\bq(?=[qwx]?\\\\s*[^\\\\w\\\\s])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"find_quoted\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\bs(?=\\\\s*[^\\\\w\\\\s\\\\]})])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"find_subst\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(?:tr|y)\\\\s*(?=[^\\\\w\\\\s\\\\]})])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"tr\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(?:m|qr)(?=\\\\s*[^\\\\w\\\\s\\\\]})])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"find_pattern\")]},Rule {rMatcher = RegExpr (RE {reString = \"[\\\\w_]+\\\\s*/\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[<>\\\"':]/\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '/', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"pattern_slash\")]},Rule {rMatcher = RegExpr (RE {reString = \"-[rwxoRWXOeszfdlpSbctugkTBMAC]\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, 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 = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"package_qualified_blank\",Context {cName = \"package_qualified_blank\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"[\\\\w_]+\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"pat_char_class\",Context {cName = \"pat_char_class\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectChar '^', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '\\\\', rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' ']', rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\[:\\\\^?[a-z]+:\\\\]\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar ']', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = BaseNTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"pat_ext\",Context {cName = \"pat_ext\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\#[^)]*\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"[:=!><]+\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar ')', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = CharTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"pattern\",Context {cName = \"pattern\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\$(?=%1)\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"%1[cgimosx]*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_ip\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$(?=\\\\\\\\%1)\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = True}),(\"pattern_brace\",Context {cName = \"pattern_brace\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\}[cgimosx]*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_ip\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"pattern_bracket\",Context {cName = \"pattern_bracket\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\][cgimosx]*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_ip\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"pattern_paren\",Context {cName = \"pattern_paren\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\)[cgimosx]*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_ip\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"pattern_slash\",Context {cName = \"pattern_slash\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\$(?=/)\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_ip\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"/[cgimosx]*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"pattern_sq\",Context {cName = \"pattern_sq\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"'[cgimosx]*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"pod\",Context {cName = \"pod\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectSpaces, 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 = RegExpr (RE {reString = \"\\\\=(?:head[1-6]|over|back|item|for|begin|end|pod)\\\\s*.*\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\=cut.*$\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Pop]}], cAttribute = CommentTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"quote_word\",Context {cName = \"quote_word\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, 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 = RegExpr (RE {reString = \"\\\\\\\\%1\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '1', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = True}),(\"quote_word_brace\",Context {cName = \"quote_word_brace\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, 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 = Detect2Chars '\\\\' '}', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"quote_word_bracket\",Context {cName = \"quote_word_bracket\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, 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 = Detect2Chars '\\\\' ']', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar ']', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"quote_word_paren\",Context {cName = \"quote_word_paren\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, 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 = Detect2Chars '\\\\' ')', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar ')', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"regex_pattern_internal\",Context {cName = \"regex_pattern_internal\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_rules_1\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_rules_2\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"regex_pattern_internal_ip\",Context {cName = \"regex_pattern_internal_ip\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_rules_1\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[$@][^]\\\\s{}()|>']\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"find_variable_unsafe\")]},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_rules_2\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"regex_pattern_internal_rules_1\",Context {cName = \"regex_pattern_internal_rules_1\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"#.*$\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = True, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[anDdSsWw]\", reCaseSensitive = True}), rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[ABbEGLlNUuQdQZz]\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[\\\\d]+\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\.\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"regex_pattern_internal_rules_2\",Context {cName = \"regex_pattern_internal_rules_2\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = Detect2Chars '(' '?', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"pat_ext\")]},Rule {rMatcher = DetectChar '[', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"pat_char_class\")]},Rule {rMatcher = RegExpr (RE {reString = \"[()?^*+|]\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\{[\\\\d, ]+\\\\}\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '$', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s{3,}#.*$\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"slash_safe_escape\",Context {cName = \"slash_safe_escape\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*\\\\}\\\\s*/{1,2}\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*[)\\\\]]?\\\\s*/{1,2}\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"BEGIN\",\"END\",\"__DATA__\",\"__END__\",\"__FILE__\",\"__LINE__\",\"__PACKAGE__\",\"break\",\"continue\",\"default\",\"do\",\"each\",\"else\",\"elsif\",\"for\",\"foreach\",\"given\",\"if\",\"last\",\"local\",\"my\",\"next\",\"our\",\"package\",\"return\",\"state\",\"sub\",\"unless\",\"until\",\"when\",\"while\"])), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"string\",Context {cName = \"string\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectIdentifier, rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '\\'', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '\\\\', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '\\'', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"string_2\",Context {cName = \"string_2\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectIdentifier, rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' ')', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '\\\\', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RangeDetect '(' ')', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar ')', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"string_3\",Context {cName = \"string_3\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectIdentifier, rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '}', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '\\\\', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RangeDetect '{' '}', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"string_4\",Context {cName = \"string_4\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectIdentifier, rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' ']', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '\\\\', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RangeDetect '[' ']', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar ']', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"string_5\",Context {cName = \"string_5\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectIdentifier, rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '<', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '\\\\', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '>', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RangeDetect '<' '>', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '>', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"string_6\",Context {cName = \"string_6\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectIdentifier, rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '\\\\' '\\\\', rAttribute = CharTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\%1\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '1', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = True}),(\"sub_arg_definition\",Context {cName = \"sub_arg_definition\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = AnyChar \"*$@%\", rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = AnyChar \"&\\\\[];\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar ')', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"slash_safe_escape\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop,Pop], cDynamic = False}),(\"sub_name_def\",Context {cName = \"sub_name_def\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\w+\", reCaseSensitive = True}), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$\\\\S\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"find_variable\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*\\\\(\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"sub_arg_definition\")]},Rule {rMatcher = Detect2Chars ':' ':', 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}),(\"subst_bracket_pattern\",Context {cName = \"subst_bracket_pattern\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\s+#.*$\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_ip\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar ']', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_bracket_replace\")]}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"subst_bracket_replace\",Context {cName = \"subst_bracket_replace\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '[', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\][cegimosx]*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"subst_curlybrace_middle\",Context {cName = \"subst_curlybrace_middle\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"#.*$\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '{', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_curlybrace_replace\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"subst_curlybrace_pattern\",Context {cName = \"subst_curlybrace_pattern\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\s+#.*$\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_ip\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_curlybrace_middle\")]}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"subst_curlybrace_replace\",Context {cName = \"subst_curlybrace_replace\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '{', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_curlybrace_replace_recursive\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\}[cegimosx]*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop,Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"subst_curlybrace_replace_recursive\",Context {cName = \"subst_curlybrace_replace_recursive\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_curlybrace_replace_recursive\")]},Rule {rMatcher = DetectChar '}', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"subst_paren_pattern\",Context {cName = \"subst_paren_pattern\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\s+#.*$\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_ip\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_paren_replace\")]}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"subst_paren_replace\",Context {cName = \"subst_paren_replace\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '(', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\)[cegimosx]*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"subst_slash_pattern\",Context {cName = \"subst_slash_pattern\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\$(?=%1)\", reCaseSensitive = True}), rAttribute = CharTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"(%1)\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_slash_replace\")]},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal_ip\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = True}),(\"subst_slash_replace\",Context {cName = \"subst_slash_replace\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"%1[cegimosx]*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]},Rule {rMatcher = IncludeRules (\"Perl\",\"ipstring_internal\"), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = True}),(\"subst_sq_pattern\",Context {cName = \"subst_sq_pattern\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\s+#.*$\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Perl\",\"regex_pattern_internal\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '\\'', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Perl\",\"subst_sq_replace\")]}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"subst_sq_replace\",Context {cName = \"subst_sq_replace\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"'[cegimosx]*\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]}], cAttribute = StringTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"tr\",Context {cName = \"tr\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\([^)]*\\\\)\\\\s*\\\\(?:[^)]*\\\\)\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\{[^}]*\\\\}\\\\s*\\\\{[^}]*\\\\}\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\[[^]]*\\\\]\\\\s*\\\\[[^\\\\]]*\\\\]\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"([^a-zA-Z0-9_\\\\s[\\\\]{}()]).*\\\\1.*\\\\1\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"var_detect\",Context {cName = \"var_detect\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = IncludeRules (\"Perl\",\"var_detect_rules\"), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Perl\",\"slash_safe_escape\"), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = DataTypeTok, cLineEmptyContext = [], cLineEndContext = [Pop,Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop,Pop], cDynamic = False}),(\"var_detect_rules\",Context {cName = \"var_detect_rules\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"[\\\\w_]+\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars ':' ':', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '\\'', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '-' '>', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '+' '+', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '-' '-', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = DataTypeTok, cLineEmptyContext = [], cLineEndContext = [Pop,Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"var_detect_unsafe\",Context {cName = \"var_detect_unsafe\", cSyntax = \"Perl\", cRules = [Rule {rMatcher = IncludeRules (\"Perl\",\"var_detect_rules\"), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = DataTypeTok, cLineEmptyContext = [], cLineEndContext = [Pop,Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop,Pop], cDynamic = False})], sAuthor = \"Anders Lund (anders@alweb.dk)\", sVersion = \"3\", sLicense = \"LGPLv2\", sExtensions = [\"*.pl\",\"*.PL\",\"*.pm\"], sStartingContext = \"normal\"}"