{- This module was generated from data in the Kate syntax highlighting file perl.xml, version 1.25, by Anders Lund (anders@alweb.dk) -} module Text.Highlighting.Kate.Syntax.Perl (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Alert import Text.ParserCombinators.Parsec hiding (State) import Data.Map (fromList) import Control.Monad.State import Data.Char (isSpace) import Data.Maybe (fromMaybe) import qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "Perl" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.pl;*.pm" -- | Highlight source code using this syntax definition. highlight :: String -> [SourceLine] highlight input = evalState (mapM parseSourceLine $ lines input) startingState parseSourceLine :: String -> State SyntaxState SourceLine parseSourceLine = mkParseSourceLine parseExpressionInternal pEndLine -- | Parse an expression using appropriate local context. parseExpression :: KateParser Token parseExpression = do st <- getState let oldLang = synStLanguage st setState $ st { synStLanguage = "Perl" } context <- currentContext <|> (pushContext "normal" >> currentContext) result <- parseRules context optional $ eof >> pEndLine updateState $ \st -> st { synStLanguage = oldLang } return result startingState = SyntaxState {synStContexts = fromList [("Perl",["normal"])], synStLanguage = "Perl", synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext case context of "normal" -> return () "find_quoted" -> return () "find_qqx" -> return () "find_qw" -> return () "ipstring_internal" -> return () "ip_string" -> return () "ip_string_2" -> return () "ip_string_3" -> return () "ip_string_4" -> return () "ip_string_5" -> return () "ip_string_6" -> return () "string" -> return () "string_2" -> return () "string_3" -> return () "string_4" -> return () "string_5" -> return () "string_6" -> return () "find_subst" -> return () "subst_curlybrace_pattern" -> return () "subst_curlybrace_middle" -> return () "subst_curlybrace_replace" -> return () "subst_curlybrace_replace_recursive" -> return () "subst_paren_pattern" -> return () "subst_paren_replace" -> return () "subst_bracket_pattern" -> return () "subst_bracket_replace" -> return () "subst_slash_pattern" -> return () "subst_slash_replace" -> return () "subst_sq_pattern" -> return () "subst_sq_replace" -> return () "tr" -> (popContext) >> pEndLine "find_pattern" -> return () "pattern_slash" -> return () "pattern" -> return () "pattern_brace" -> return () "pattern_bracket" -> return () "pattern_paren" -> return () "pattern_sq" -> return () "regex_pattern_internal_rules_1" -> return () "regex_pattern_internal_rules_2" -> return () "regex_pattern_internal" -> return () "regex_pattern_internal_ip" -> return () "pat_ext" -> return () "pat_char_class" -> return () "find_variable" -> (popContext) >> pEndLine "find_variable_unsafe" -> (popContext) >> pEndLine "var_detect" -> (popContext >> popContext) >> pEndLine "var_detect_unsafe" -> (popContext >> popContext) >> pEndLine "var_detect_rules" -> (popContext >> popContext) >> pEndLine "quote_word" -> return () "quote_word_paren" -> return () "quote_word_brace" -> return () "quote_word_bracket" -> return () "find_here_document" -> (popContext) >> pEndLine "here_document" -> return () "here_document_dumb" -> return () "data_handle" -> return () "end_handle" -> return () "Backticked" -> return () "slash_safe_escape" -> (popContext) >> pEndLine "package_qualified_blank" -> return () "sub_name_def" -> (popContext) >> pEndLine "sub_arg_definition" -> return () "pod" -> return () "comment" -> (popContext) >> pEndLine _ -> return () withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" updateState $ \st -> st { synStPrevChar = last txt , synStPrevNonspace = synStPrevNonspace st || not (all isSpace txt) } return (attr, txt) parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe NormalTok $ lookup context defaultAttributes)) list_keywords = Set.fromList $ words $ "if unless else elsif while until for each foreach next last break continue return use no require my our local BEGIN END require package sub do __END__ __DATA__ __FILE__ __LINE__ __PACKAGE__" list_operators = Set.fromList $ words $ "= != ~= += -= *= /= **= |= ||= //= &= &&= ?= + - * % || // && | & < << > >> ^ -> => . , ; :: \\ and or not eq ne lt gt le ge cmp" list_functions = Set.fromList $ words $ "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 oct open opendir ord pack package pipe pop pos print printf prototype push quotemeta rand read readdir readline readlink recv redo ref rename 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 utime values vec wait waitpid wantarray warn write" list_pragmas = Set.fromList $ words $ "strict english warnings vars subs utf8 sigtrap locale open less integer filetest constant bytes diagnostics" regex_'23'21'5c'2f'2e'2a = compileRegex "#!\\/.*" regex_'5cbsub'5cs'2b = compileRegex "\\bsub\\s+" regex_'5c'3d'28'3f'3ahead'5b1'2d6'5d'7cover'7cback'7citem'7cfor'7cbegin'7cend'7cpod'29'28'5cs'7c'24'29 = compileRegex "\\=(?:head[1-6]|over|back|item|for|begin|end|pod)(\\s|$)" regex_'5c'5c'28'5b'22'27'5d'29'5b'5e'5c1'5d = compileRegex "\\\\([\"'])[^\\1]" regex_'28'3f'3a'5b'24'40'5d'5cS'7c'25'5b'5cw'7b'5d'7c'5c'2a'5b'5e'5cd'5c'2a'7b'5c'24'40'25'3d'28'5d'29 = compileRegex "(?:[$@]\\S|%[\\w{]|\\*[^\\d\\*{\\$@%=(])" regex_'3c'5bA'2dZ0'2d9'5f'5d'2b'3e = compileRegex "<[A-Z0-9_]+>" regex_'5cs'2a'3c'3c'28'3f'3d'5cw'2b'7c'5cs'2a'5b'22'27'5d'29 = compileRegex "\\s*<<(?=\\w+|\\s*[\"'])" regex_'5cs'2a'5c'7d'5cs'2a'2f'7b1'2c2'7d = compileRegex "\\s*\\}\\s*/{1,2}" regex_'5cs'2a'5b'29'5c'5d'5d'5cs'2a'2f'7b1'2c2'7d = compileRegex "\\s*[)\\]]\\s*/{1,2}" regex_'5cw'2b'3a'3a = compileRegex "\\w+::" regex_'5cw'2b'5b'3d'5d = compileRegex "\\w+[=]" regex_'5cbq'28'3f'3d'5bqwx'5d'3f'5cs'2a'5b'5e'5cw'5cs'5d'29 = compileRegex "\\bq(?=[qwx]?\\s*[^\\w\\s])" regex_'5cbs'28'3f'3d'5cs'2a'5b'5e'5cw'5cs'5c'5d'7d'29'5d'29 = compileRegex "\\bs(?=\\s*[^\\w\\s\\]})])" regex_'5cb'28'3f'3atr'7cy'29'5cs'2a'28'3f'3d'5b'5e'5cw'5cs'5c'5d'7d'29'5d'29 = compileRegex "\\b(?:tr|y)\\s*(?=[^\\w\\s\\]})])" regex_'5cb'28'3f'3am'7cqr'29'28'3f'3d'5cs'2a'5b'5e'5cw'5cs'5c'5d'7d'29'5d'29 = compileRegex "\\b(?:m|qr)(?=\\s*[^\\w\\s\\]})])" regex_'5b'5cw'5f'5d'2b'5cs'2a'2f = compileRegex "[\\w_]+\\s*/" regex_'5b'3c'3e'22'27'3a'5d'2f = compileRegex "[<>\"':]/" regex_'2d'5brwxoRWXOeszfdlpSbctugkTBMAC'5d = compileRegex "-[rwxoRWXOeszfdlpSbctugkTBMAC]" regex_x'5cs'2a'28'27'29 = compileRegex "x\\s*(')" regex_'28'5b'5ea'2dzA'2dZ0'2d9'5f'5cs'5b'5c'5d'7b'7d'28'29'5d'29 = compileRegex "([^a-zA-Z0-9_\\s[\\]{}()])" regex_'5cs'2b'23'2e'2a = compileRegex "\\s+#.*" regex_'5c'5c'5bUuLlEtnaefr'5d = compileRegex "\\\\[UuLlEtnaefr]" regex_'5c'5c'2e = compileRegex "\\\\." regex_'28'3f'3a'5b'5c'24'40'5d'5cS'7c'25'5b'5cw'7b'5d'29 = compileRegex "(?:[\\$@]\\S|%[\\w{])" regex_'28'5b'5e'5cw'5cs'5b'5c'5d'7b'7d'28'29'5d'29 = compileRegex "([^\\w\\s[\\]{}()])" regex_'5cs'2b'23'2e'2a'24 = compileRegex "\\s+#.*$" regex_'23'2e'2a'24 = compileRegex "#.*$" regex_'5c'7d'5bcegimosx'5d'2a = compileRegex "\\}[cegimosx]*" regex_'5c'29'5bcegimosx'5d'2a = compileRegex "\\)[cegimosx]*" regex_'5c'5d'5bcegimosx'5d'2a = compileRegex "\\][cegimosx]*" regex_'27'5bcegimosx'5d'2a = compileRegex "'[cegimosx]*" regex_'5c'28'5b'5e'29'5d'2a'5c'29'5cs'2a'5c'28'3f'3a'5b'5e'29'5d'2a'5c'29 = compileRegex "\\([^)]*\\)\\s*\\(?:[^)]*\\)" regex_'7b'5b'5e'7d'5d'2a'5c'7d'5cs'2a'5c'7b'5b'5e'7d'5d'2a'5c'7d = compileRegex "{[^}]*\\}\\s*\\{[^}]*\\}" regex_'5c'5b'5b'5e'7d'5d'2a'5c'5d'5cs'2a'5c'5b'5b'5e'5c'5d'5d'2a'5c'5d = compileRegex "\\[[^}]*\\]\\s*\\[[^\\]]*\\]" regex_'28'5b'5ea'2dzA'2dZ0'2d9'5f'5cs'5b'5c'5d'7b'7d'28'29'5d'29'2e'2a'5c1'2e'2a'5c1 = compileRegex "([^a-zA-Z0-9_\\s[\\]{}()]).*\\1.*\\1" regex_'28'5b'5e'5cw'5cs'5d'29 = compileRegex "([^\\w\\s])" regex_'5c'24'28'3f'3d'2f'29 = compileRegex "\\$(?=/)" regex_'2f'5bcgimosx'5d'2a = compileRegex "/[cgimosx]*" regex_'5c'7d'5bcgimosx'5d'2a = compileRegex "\\}[cgimosx]*" regex_'5c'5d'5bcgimosx'5d'2a = compileRegex "\\][cgimosx]*" regex_'5c'29'5bcgimosx'5d'2a = compileRegex "\\)[cgimosx]*" regex_'27'5bcgimosx'5d'2a = compileRegex "'[cgimosx]*" regex_'5c'5c'5banDdSsWw'5d = compileRegex "\\\\[anDdSsWw]" regex_'5c'5c'5bABbEGLlNUuQdQZz'5d = compileRegex "\\\\[ABbEGLlNUuQdQZz]" regex_'5c'5c'5b'5cd'5d'2b = compileRegex "\\\\[\\d]+" regex_'5b'28'29'3f'5c'5e'2a'2b'7c'5d = compileRegex "[()?\\^*+|]" regex_'5c'7b'5b'5cd'2c_'5d'2b'5c'7d = compileRegex "\\{[\\d, ]+\\}" regex_'5cs'7b3'2c'7d'23'2e'2a'24 = compileRegex "\\s{3,}#.*$" regex_'5b'24'40'5d'5b'5e'5c'5d'5cs'7b'7d'28'29'7c'3e'27'5d = compileRegex "[$@][^\\]\\s{}()|>']" regex_'5c'23'5b'5e'29'5d'2a = compileRegex "\\#[^)]*" regex_'5b'3a'3d'21'3e'3c'5d'2b = compileRegex "[:=!><]+" regex_'5c'5b'3a'5c'5e'3f'5ba'2dz'5d'2b'3a'5c'5d = compileRegex "\\[:\\^?[a-z]+:\\]" regex_'5c'24'5b0'2d9'5d'2b = compileRegex "\\$[0-9]+" regex_'5b'40'5c'24'5d'28'3f'3a'5b'5c'2b'5c'2d'5f'5d'5cB'7cARGV'5cb'7cINC'5cb'29 = compileRegex "[@\\$](?:[\\+\\-_]\\B|ARGV\\b|INC\\b)" regex_'5b'25'5c'24'5d'28'3f'3aINC'5cb'7cENV'5cb'7cSIG'5cb'29 = compileRegex "[%\\$](?:INC\\b|ENV\\b|SIG\\b)" regex_'5c'24'5c'24'5b'5c'24'5cw'5f'5d = compileRegex "\\$\\$[\\$\\w_]" regex_'5c'24'5b'23'5f'5d'5b'5cw'5f'5d = compileRegex "\\$[#_][\\w_]" regex_'5c'24'2b'3a'3a = compileRegex "\\$+::" regex_'5c'24'5b'5ea'2dzA'2dZ0'2d9'5cs'7b'5d'5bA'2dZ'5d'3f = compileRegex "\\$[^a-zA-Z0-9\\s{][A-Z]?" regex_'5b'5c'24'40'25'5d'5c'7b'5b'5cw'5f'5d'2b'5c'7d = compileRegex "[\\$@%]\\{[\\w_]+\\}" regex_'5c'2a'5ba'2dzA'2dZ'5f'5d'2b = compileRegex "\\*[a-zA-Z_]+" regex_'5c'2a'5b'5ea'2dzA'2dZ0'2d9'5cs'7b'5d'5bA'2dZ'5d'3f = compileRegex "\\*[^a-zA-Z0-9\\s{][A-Z]?" regex_'5b'5c'24'40'25'5d = compileRegex "[\\$@%]" regex_'5c'2a'5cw'2b = compileRegex "\\*\\w+" regex_'5b'5cw'5f'5d'2b = compileRegex "[\\w_]+" regex_'28'5cw'2b'29'5cs'2a'3b'3f = compileRegex "(\\w+)\\s*;?" regex_'5cs'2a'22'28'5b'5e'22'5d'2b'29'22'5cs'2a'3b'3f = compileRegex "\\s*\"([^\"]+)\"\\s*;?" regex_'5cs'2a'60'28'5b'5e'60'5d'2b'29'60'5cs'2a'3b'3f = compileRegex "\\s*`([^`]+)`\\s*;?" regex_'5cs'2a'27'28'5b'5e'27'5d'2b'29'27'5cs'2a'3b'3f = compileRegex "\\s*'([^']+)'\\s*;?" regex_'5c'3d'5cs'2a'3c'3c'5cs'2a'5b'22'27'5d'3f'28'5bA'2dZ0'2d9'5f'5c'2d'5d'2b'29'5b'22'27'5d'3f = compileRegex "\\=\\s*<<\\s*[\"']?([A-Z0-9_\\-]+)[\"']?" regex_'5c'3d'28'3f'3ahead'5b1'2d6'5d'7cover'7cback'7citem'7cfor'7cbegin'7cend'7cpod'29'5cs'2b'2e'2a = compileRegex "\\=(?:head[1-6]|over|back|item|for|begin|end|pod)\\s+.*" regex_'5c'3d'28'3f'3ahead'5b1'2d6'5d'7cover'7cback'7citem'7cfor'7cbegin'7cend'7cpod'29'5cs'2a'2e'2a = compileRegex "\\=(?:head[1-6]|over|back|item|for|begin|end|pod)\\s*.*" regex_'5cs'2a'5b'29'5c'5d'5d'3f'5cs'2a'2f'7b1'2c2'7d = compileRegex "\\s*[)\\]]?\\s*/{1,2}" regex_'5cw'2b = compileRegex "\\w+" regex_'5c'24'5cS = compileRegex "\\$\\S" regex_'5cs'2a'5c'28 = compileRegex "\\s*\\(" regex_'5c'3dcut'2e'2a'24 = compileRegex "\\=cut.*$" defaultAttributes = [("normal",NormalTok),("find_quoted",NormalTok),("find_qqx",NormalTok),("find_qw",NormalTok),("ipstring_internal",StringTok),("ip_string",StringTok),("ip_string_2",StringTok),("ip_string_3",StringTok),("ip_string_4",StringTok),("ip_string_5",StringTok),("ip_string_6",StringTok),("string",StringTok),("string_2",StringTok),("string_3",StringTok),("string_4",StringTok),("string_5",StringTok),("string_6",StringTok),("find_subst",NormalTok),("subst_curlybrace_pattern",OtherTok),("subst_curlybrace_middle",NormalTok),("subst_curlybrace_replace",StringTok),("subst_curlybrace_replace_recursive",StringTok),("subst_paren_pattern",OtherTok),("subst_paren_replace",StringTok),("subst_bracket_pattern",OtherTok),("subst_bracket_replace",StringTok),("subst_slash_pattern",OtherTok),("subst_slash_replace",StringTok),("subst_sq_pattern",OtherTok),("subst_sq_replace",StringTok),("tr",OtherTok),("find_pattern",OtherTok),("pattern_slash",OtherTok),("pattern",OtherTok),("pattern_brace",OtherTok),("pattern_bracket",OtherTok),("pattern_paren",OtherTok),("pattern_sq",OtherTok),("regex_pattern_internal_rules_1",NormalTok),("regex_pattern_internal_rules_2",NormalTok),("regex_pattern_internal",OtherTok),("regex_pattern_internal_ip",OtherTok),("pat_ext",CharTok),("pat_char_class",BaseNTok),("find_variable",DataTypeTok),("find_variable_unsafe",DataTypeTok),("var_detect",DataTypeTok),("var_detect_unsafe",DataTypeTok),("var_detect_rules",DataTypeTok),("quote_word",NormalTok),("quote_word_paren",NormalTok),("quote_word_brace",NormalTok),("quote_word_bracket",NormalTok),("find_here_document",NormalTok),("here_document",StringTok),("here_document_dumb",NormalTok),("data_handle",NormalTok),("end_handle",CommentTok),("Backticked",StringTok),("slash_safe_escape",NormalTok),("package_qualified_blank",NormalTok),("sub_name_def",NormalTok),("sub_arg_definition",NormalTok),("pod",CommentTok),("comment",CommentTok)] parseRules "normal" = (((pColumn 0 >> pRegExpr regex_'23'21'5c'2f'2e'2a >>= withAttribute KeywordTok)) <|> ((pFirstNonSpace >> pString False "__DATA__" >>= withAttribute KeywordTok) >>~ pushContext "data_handle") <|> ((pFirstNonSpace >> pString False "__END__" >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbsub'5cs'2b >>= withAttribute KeywordTok) >>~ pushContext "sub_name_def") <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_operators >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_functions >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_pragmas >>= withAttribute KeywordTok)) <|> ((pColumn 0 >> pRegExpr regex_'5c'3d'28'3f'3ahead'5b1'2d6'5d'7cover'7cback'7citem'7cfor'7cbegin'7cend'7cpod'29'28'5cs'7c'24'29 >>= withAttribute CommentTok) >>~ pushContext "pod") <|> ((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext "comment") <|> ((pHlCOct >>= withAttribute BaseNTok) >>~ pushContext "slash_safe_escape") <|> ((pHlCHex >>= withAttribute BaseNTok) >>~ pushContext "slash_safe_escape") <|> ((pFloat >>= withAttribute FloatTok) >>~ pushContext "slash_safe_escape") <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext "slash_safe_escape") <|> ((pRegExpr regex_'5c'5c'28'5b'22'27'5d'29'5b'5e'5c1'5d >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '&' '\'' >>= withAttribute NormalTok)) <|> ((pDetectChar False '"' >>= withAttribute KeywordTok) >>~ pushContext "ip_string") <|> ((pDetectChar False '\'' >>= withAttribute KeywordTok) >>~ pushContext "string") <|> ((pDetectChar False '`' >>= withAttribute KeywordTok) >>~ pushContext "Backticked") <|> ((lookAhead (pRegExpr regex_'28'3f'3a'5b'24'40'5d'5cS'7c'25'5b'5cw'7b'5d'7c'5c'2a'5b'5e'5cd'5c'2a'7b'5c'24'40'25'3d'28'5d'29) >> pushContext "find_variable" >> currentContext >>= parseRules)) <|> ((pRegExpr regex_'3c'5bA'2dZ0'2d9'5f'5d'2b'3e >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cs'2a'3c'3c'28'3f'3d'5cw'2b'7c'5cs'2a'5b'22'27'5d'29 >>= withAttribute KeywordTok) >>~ pushContext "find_here_document") <|> ((pRegExpr regex_'5cs'2a'5c'7d'5cs'2a'2f'7b1'2c2'7d >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cs'2a'5b'29'5c'5d'5d'5cs'2a'2f'7b1'2c2'7d >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cw'2b'3a'3a >>= withAttribute FunctionTok) >>~ pushContext "sub_name_def") <|> ((pRegExpr regex_'5cw'2b'5b'3d'5d >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cbq'28'3f'3d'5bqwx'5d'3f'5cs'2a'5b'5e'5cw'5cs'5d'29 >>= withAttribute KeywordTok) >>~ pushContext "find_quoted") <|> ((pRegExpr regex_'5cbs'28'3f'3d'5cs'2a'5b'5e'5cw'5cs'5c'5d'7d'29'5d'29 >>= withAttribute KeywordTok) >>~ pushContext "find_subst") <|> ((pRegExpr regex_'5cb'28'3f'3atr'7cy'29'5cs'2a'28'3f'3d'5b'5e'5cw'5cs'5c'5d'7d'29'5d'29 >>= withAttribute KeywordTok) >>~ pushContext "tr") <|> ((pRegExpr regex_'5cb'28'3f'3am'7cqr'29'28'3f'3d'5cs'2a'5b'5e'5cw'5cs'5c'5d'7d'29'5d'29 >>= withAttribute KeywordTok) >>~ pushContext "find_pattern") <|> ((pRegExpr regex_'5b'5cw'5f'5d'2b'5cs'2a'2f >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5b'3c'3e'22'27'3a'5d'2f >>= withAttribute NormalTok)) <|> ((pDetectChar False '/' >>= withAttribute KeywordTok) >>~ pushContext "pattern_slash") <|> ((pRegExpr regex_'2d'5brwxoRWXOeszfdlpSbctugkTBMAC'5d >>= withAttribute KeywordTok)) <|> ((pDetectChar False '{' >>= withAttribute NormalTok)) <|> ((pDetectChar False '}' >>= withAttribute NormalTok))) parseRules "find_quoted" = (((pRegExpr regex_x'5cs'2a'28'27'29 >>= withAttribute KeywordTok) >>~ pushContext "string_6") <|> ((pAnyChar "qx" >>= withAttribute KeywordTok) >>~ pushContext "find_qqx") <|> ((pDetectChar False 'w' >>= withAttribute KeywordTok) >>~ pushContext "find_qw") <|> ((pDetectChar False '(' >>= withAttribute KeywordTok) >>~ pushContext "string_2") <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext "string_3") <|> ((pDetectChar False '[' >>= withAttribute KeywordTok) >>~ pushContext "string_4") <|> ((pDetectChar False '<' >>= withAttribute KeywordTok) >>~ pushContext "string_5") <|> ((pRegExpr regex_'28'5b'5ea'2dzA'2dZ0'2d9'5f'5cs'5b'5c'5d'7b'7d'28'29'5d'29 >>= withAttribute KeywordTok) >>~ pushContext "string_6") <|> ((pRegExpr regex_'5cs'2b'23'2e'2a >>= withAttribute CommentTok))) parseRules "find_qqx" = (((pDetectChar False '(' >>= withAttribute KeywordTok) >>~ pushContext "ip_string_2") <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext "ip_string_3") <|> ((pDetectChar False '[' >>= withAttribute KeywordTok) >>~ pushContext "ip_string_4") <|> ((pDetectChar False '<' >>= withAttribute KeywordTok) >>~ pushContext "ip_string_5") <|> ((pRegExpr regex_'28'5b'5ea'2dzA'2dZ0'2d9'5f'5cs'5b'5c'5d'7b'7d'28'29'5d'29 >>= withAttribute KeywordTok) >>~ pushContext "ip_string_6") <|> ((pRegExpr regex_'5cs'2b'23'2e'2a >>= withAttribute CommentTok))) parseRules "find_qw" = (((pDetectChar False '(' >>= withAttribute KeywordTok) >>~ pushContext "quote_word_paren") <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext "quote_word_brace") <|> ((pDetectChar False '[' >>= withAttribute KeywordTok) >>~ pushContext "quote_word_bracket") <|> ((pRegExpr regex_'28'5b'5ea'2dzA'2dZ0'2d9'5f'5cs'5b'5c'5d'7b'7d'28'29'5d'29 >>= withAttribute KeywordTok) >>~ pushContext "quote_word") <|> ((pRegExpr regex_'5cs'2b'23'2e'2a >>= withAttribute CommentTok))) parseRules "ipstring_internal" = (((pDetectIdentifier >>= withAttribute StringTok)) <|> ((pRegExpr regex_'5c'5c'5bUuLlEtnaefr'5d >>= withAttribute CharTok)) <|> ((pRegExpr regex_'5c'5c'2e >>= withAttribute StringTok)) <|> ((lookAhead (pRegExpr regex_'28'3f'3a'5b'5c'24'40'5d'5cS'7c'25'5b'5cw'7b'5d'29) >> pushContext "find_variable_unsafe" >> currentContext >>= parseRules))) parseRules "ip_string" = (((pDetectChar False '"' >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((parseRules "ipstring_internal"))) parseRules "ip_string_2" = (((pRangeDetect '(' ')' >>= withAttribute StringTok)) <|> ((pDetectChar False ')' >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext)) <|> ((parseRules "ipstring_internal"))) parseRules "ip_string_3" = (((pRangeDetect '{' '}' >>= withAttribute StringTok)) <|> ((pDetectChar False '}' >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext)) <|> ((parseRules "ipstring_internal"))) parseRules "ip_string_4" = (((pRangeDetect '[' ']' >>= withAttribute StringTok)) <|> ((pDetectChar False ']' >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext)) <|> ((parseRules "ipstring_internal"))) parseRules "ip_string_5" = (((pRangeDetect '<' '>' >>= withAttribute StringTok)) <|> ((pDetectChar False '>' >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext)) <|> ((parseRules "ipstring_internal"))) parseRules "ip_string_6" = (((pRegExprDynamic "\\%1" >>= withAttribute StringTok)) <|> ((pDetectChar True '1' >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext)) <|> ((parseRules "ipstring_internal"))) parseRules "string" = (((pDetectIdentifier >>= withAttribute StringTok)) <|> ((pDetect2Chars False '\\' '\'' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok)) <|> ((pDetectChar False '\'' >>= withAttribute KeywordTok) >>~ (popContext))) parseRules "string_2" = (((pDetectIdentifier >>= withAttribute StringTok)) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok)) <|> ((pRangeDetect '(' ')' >>= withAttribute StringTok)) <|> ((pDetectChar False ')' >>= withAttribute KeywordTok) >>~ (popContext >> popContext))) parseRules "string_3" = (((pDetectIdentifier >>= withAttribute StringTok)) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok)) <|> ((pRangeDetect '{' '}' >>= withAttribute StringTok)) <|> ((pDetectChar False '}' >>= withAttribute KeywordTok) >>~ (popContext >> popContext))) parseRules "string_4" = (((pDetectIdentifier >>= withAttribute StringTok)) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok)) <|> ((pRangeDetect '[' ']' >>= withAttribute StringTok)) <|> ((pDetectChar False ']' >>= withAttribute KeywordTok) >>~ (popContext >> popContext))) parseRules "string_5" = (((pDetectIdentifier >>= withAttribute StringTok)) <|> ((pDetect2Chars False '\\' '<' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '>' >>= withAttribute StringTok)) <|> ((pRangeDetect '<' '>' >>= withAttribute StringTok)) <|> ((pDetectChar False '>' >>= withAttribute KeywordTok) >>~ (popContext >> popContext))) parseRules "string_6" = (((pDetectIdentifier >>= withAttribute StringTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok)) <|> ((pRegExprDynamic "\\%1" >>= withAttribute CharTok)) <|> ((pDetectChar True '1' >>= withAttribute KeywordTok) >>~ (popContext >> popContext))) parseRules "find_subst" = (((pRegExpr regex_'5cs'2b'23'2e'2a >>= withAttribute CommentTok)) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext "subst_curlybrace_pattern") <|> ((pDetectChar False '(' >>= withAttribute KeywordTok) >>~ pushContext "subst_paren_pattern") <|> ((pDetectChar False '[' >>= withAttribute KeywordTok) >>~ pushContext "subst_bracket_pattern") <|> ((pDetectChar False '\'' >>= withAttribute KeywordTok) >>~ pushContext "subst_sq_pattern") <|> ((pRegExpr regex_'28'5b'5e'5cw'5cs'5b'5c'5d'7b'7d'28'29'5d'29 >>= withAttribute KeywordTok) >>~ pushContext "subst_slash_pattern")) parseRules "subst_curlybrace_pattern" = (((pRegExpr regex_'5cs'2b'23'2e'2a'24 >>= withAttribute CommentTok)) <|> ((parseRules "regex_pattern_internal_ip")) <|> ((pDetectChar False '}' >>= withAttribute KeywordTok) >>~ pushContext "subst_curlybrace_middle")) parseRules "subst_curlybrace_middle" = (((pRegExpr regex_'23'2e'2a'24 >>= withAttribute CommentTok)) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext "subst_curlybrace_replace")) parseRules "subst_curlybrace_replace" = (((parseRules "ipstring_internal")) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext "subst_curlybrace_replace_recursive") <|> ((pRegExpr regex_'5c'7d'5bcegimosx'5d'2a >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext >> popContext))) parseRules "subst_curlybrace_replace_recursive" = (((pDetectChar False '{' >>= withAttribute StringTok) >>~ pushContext "subst_curlybrace_replace_recursive") <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((parseRules "ipstring_internal"))) parseRules "subst_paren_pattern" = (((pRegExpr regex_'5cs'2b'23'2e'2a'24 >>= withAttribute CommentTok)) <|> ((parseRules "regex_pattern_internal_ip")) <|> ((pDetectChar False '}' >>= withAttribute KeywordTok) >>~ pushContext "subst_paren_replace")) parseRules "subst_paren_replace" = (((parseRules "ipstring_internal")) <|> ((pDetectChar False '(' >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5c'29'5bcegimosx'5d'2a >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext))) parseRules "subst_bracket_pattern" = (((pRegExpr regex_'5cs'2b'23'2e'2a'24 >>= withAttribute CommentTok)) <|> ((parseRules "regex_pattern_internal_ip")) <|> ((pDetectChar False ']' >>= withAttribute KeywordTok) >>~ pushContext "subst_bracket_replace")) parseRules "subst_bracket_replace" = (((parseRules "ipstring_internal")) <|> ((pDetectChar False '[' >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5c'5d'5bcegimosx'5d'2a >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext))) parseRules "subst_slash_pattern" = (((pRegExprDynamic "\\$(?=%1)" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "(%1)" >>= withAttribute KeywordTok) >>~ pushContext "subst_slash_replace") <|> ((parseRules "regex_pattern_internal_ip"))) parseRules "subst_slash_replace" = (((pRegExprDynamic "%1[cegimosx]*" >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext)) <|> ((parseRules "ipstring_internal"))) parseRules "subst_sq_pattern" = (((pRegExpr regex_'5cs'2b'23'2e'2a'24 >>= withAttribute CommentTok)) <|> ((parseRules "regex_pattern_internal")) <|> ((pDetectChar False '\'' >>= withAttribute KeywordTok) >>~ pushContext "subst_sq_replace")) parseRules "subst_sq_replace" = ((pRegExpr regex_'27'5bcegimosx'5d'2a >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext)) parseRules "tr" = (((pRegExpr regex_'5c'28'5b'5e'29'5d'2a'5c'29'5cs'2a'5c'28'3f'3a'5b'5e'29'5d'2a'5c'29 >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pRegExpr regex_'7b'5b'5e'7d'5d'2a'5c'7d'5cs'2a'5c'7b'5b'5e'7d'5d'2a'5c'7d >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5b'5b'5e'7d'5d'2a'5c'5d'5cs'2a'5c'5b'5b'5e'5c'5d'5d'2a'5c'5d >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pRegExpr regex_'28'5b'5ea'2dzA'2dZ0'2d9'5f'5cs'5b'5c'5d'7b'7d'28'29'5d'29'2e'2a'5c1'2e'2a'5c1 >>= withAttribute OtherTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules "find_pattern" = (((pRegExpr regex_'5cs'2b'23'2e'2a >>= withAttribute CommentTok)) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext "pattern_brace") <|> ((pDetectChar False '(' >>= withAttribute KeywordTok) >>~ pushContext "pattern_paren") <|> ((pDetectChar False '[' >>= withAttribute KeywordTok) >>~ pushContext "pattern_bracket") <|> ((pDetectChar False '\'' >>= withAttribute KeywordTok) >>~ pushContext "pattern_sq") <|> ((pRegExpr regex_'28'5b'5e'5cw'5cs'5d'29 >>= withAttribute KeywordTok) >>~ pushContext "pattern")) parseRules "pattern_slash" = (((pRegExpr regex_'5c'24'28'3f'3d'2f'29 >>= withAttribute CharTok)) <|> ((parseRules "regex_pattern_internal_ip")) <|> ((pRegExpr regex_'2f'5bcgimosx'5d'2a >>= withAttribute KeywordTok) >>~ (popContext))) parseRules "pattern" = (((pRegExprDynamic "\\$(?=%1)" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "%1[cgimosx]*" >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((parseRules "regex_pattern_internal_ip")) <|> ((pRegExprDynamic "\\$(?=\\%1)" >>= withAttribute CharTok))) parseRules "pattern_brace" = (((pRegExpr regex_'5c'7d'5bcgimosx'5d'2a >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((parseRules "regex_pattern_internal_ip"))) parseRules "pattern_bracket" = (((pRegExpr regex_'5c'5d'5bcgimosx'5d'2a >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((parseRules "regex_pattern_internal_ip"))) parseRules "pattern_paren" = (((pRegExpr regex_'5c'29'5bcgimosx'5d'2a >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((parseRules "regex_pattern_internal_ip"))) parseRules "pattern_sq" = (((pRegExpr regex_'27'5bcgimosx'5d'2a >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((parseRules "regex_pattern_internal"))) parseRules "regex_pattern_internal_rules_1" = (((pFirstNonSpace >> pRegExpr regex_'23'2e'2a'24 >>= withAttribute CommentTok)) <|> ((pRegExpr regex_'5c'5c'5banDdSsWw'5d >>= withAttribute BaseNTok)) <|> ((pRegExpr regex_'5c'5c'5bABbEGLlNUuQdQZz'5d >>= withAttribute CharTok)) <|> ((pRegExpr regex_'5c'5c'5b'5cd'5d'2b >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5c'5c'2e >>= withAttribute OtherTok))) parseRules "regex_pattern_internal_rules_2" = (((pDetect2Chars False '(' '?' >>= withAttribute CharTok) >>~ pushContext "pat_ext") <|> ((pDetectChar False '[' >>= withAttribute CharTok) >>~ pushContext "pat_char_class") <|> ((pRegExpr regex_'5b'28'29'3f'5c'5e'2a'2b'7c'5d >>= withAttribute CharTok)) <|> ((pRegExpr regex_'5c'7b'5b'5cd'2c_'5d'2b'5c'7d >>= withAttribute CharTok)) <|> ((pDetectChar False '$' >>= withAttribute CharTok)) <|> ((pRegExpr regex_'5cs'7b3'2c'7d'23'2e'2a'24 >>= withAttribute CommentTok))) parseRules "regex_pattern_internal" = (((parseRules "regex_pattern_internal_rules_1")) <|> ((parseRules "regex_pattern_internal_rules_2"))) parseRules "regex_pattern_internal_ip" = (((parseRules "regex_pattern_internal_rules_1")) <|> ((lookAhead (pRegExpr regex_'5b'24'40'5d'5b'5e'5c'5d'5cs'7b'7d'28'29'7c'3e'27'5d) >> pushContext "find_variable_unsafe" >> currentContext >>= parseRules)) <|> ((parseRules "regex_pattern_internal_rules_2"))) parseRules "pat_ext" = (((pRegExpr regex_'5c'23'5b'5e'29'5d'2a >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b'3a'3d'21'3e'3c'5d'2b >>= withAttribute CharTok) >>~ (popContext)) <|> ((pDetectChar False ')' >>= withAttribute CharTok) >>~ (popContext))) parseRules "pat_char_class" = (((pDetectChar False '^' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute BaseNTok)) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute BaseNTok)) <|> ((pRegExpr regex_'5c'5b'3a'5c'5e'3f'5ba'2dz'5d'2b'3a'5c'5d >>= withAttribute BaseNTok)) <|> ((pDetectChar False ']' >>= withAttribute CharTok) >>~ (popContext))) parseRules "find_variable" = (((pRegExpr regex_'5c'24'5b0'2d9'5d'2b >>= withAttribute DataTypeTok) >>~ pushContext "var_detect") <|> ((pRegExpr regex_'5b'40'5c'24'5d'28'3f'3a'5b'5c'2b'5c'2d'5f'5d'5cB'7cARGV'5cb'7cINC'5cb'29 >>= withAttribute DataTypeTok) >>~ pushContext "var_detect") <|> ((pRegExpr regex_'5b'25'5c'24'5d'28'3f'3aINC'5cb'7cENV'5cb'7cSIG'5cb'29 >>= withAttribute DataTypeTok) >>~ pushContext "var_detect") <|> ((pRegExpr regex_'5c'24'5c'24'5b'5c'24'5cw'5f'5d >>= withAttribute DataTypeTok) >>~ pushContext "var_detect") <|> ((pRegExpr regex_'5c'24'5b'23'5f'5d'5b'5cw'5f'5d >>= withAttribute DataTypeTok) >>~ pushContext "var_detect") <|> ((pRegExpr regex_'5c'24'2b'3a'3a >>= withAttribute DataTypeTok) >>~ pushContext "var_detect") <|> ((pRegExpr regex_'5c'24'5b'5ea'2dzA'2dZ0'2d9'5cs'7b'5d'5bA'2dZ'5d'3f >>= withAttribute DataTypeTok) >>~ pushContext "var_detect") <|> ((pRegExpr regex_'5b'5c'24'40'25'5d'5c'7b'5b'5cw'5f'5d'2b'5c'7d >>= withAttribute DataTypeTok) >>~ pushContext "var_detect") <|> ((pAnyChar "$@%" >>= withAttribute DataTypeTok) >>~ pushContext "var_detect") <|> ((pRegExpr regex_'5c'2a'5ba'2dzA'2dZ'5f'5d'2b >>= withAttribute DataTypeTok) >>~ pushContext "var_detect") <|> ((pRegExpr regex_'5c'2a'5b'5ea'2dzA'2dZ0'2d9'5cs'7b'5d'5bA'2dZ'5d'3f >>= withAttribute DataTypeTok)) <|> ((pAnyChar "$@%*" >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules "find_variable_unsafe" = (((pRegExpr regex_'5c'24'5b0'2d9'5d'2b >>= withAttribute DataTypeTok) >>~ pushContext "var_detect_unsafe") <|> ((pRegExpr regex_'5b'40'5c'24'5d'28'3f'3a'5b'5c'2b'5c'2d'5f'5d'5cB'7cARGV'5cb'7cINC'5cb'29 >>= withAttribute DataTypeTok) >>~ pushContext "var_detect_unsafe") <|> ((pRegExpr regex_'5b'25'5c'24'5d'28'3f'3aINC'5cb'7cENV'5cb'7cSIG'5cb'29 >>= withAttribute DataTypeTok) >>~ pushContext "var_detect_unsafe") <|> ((pRegExpr regex_'5c'24'5c'24'5b'5c'24'5cw'5f'5d >>= withAttribute DataTypeTok) >>~ pushContext "var_detect_unsafe") <|> ((pRegExpr regex_'5c'24'5b'23'5f'5d'5b'5cw'5f'5d >>= withAttribute DataTypeTok) >>~ pushContext "var_detect_unsafe") <|> ((pRegExpr regex_'5c'24'2b'3a'3a >>= withAttribute DataTypeTok) >>~ pushContext "var_detect_unsafe") <|> ((pRegExpr regex_'5c'24'5b'5ea'2dzA'2dZ0'2d9'5cs'7b'5d'5bA'2dZ'5d'3f >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5b'5c'24'40'25'5d'5c'7b'5b'5cw'5f'5d'2b'5c'7d >>= withAttribute DataTypeTok) >>~ pushContext "var_detect_unsafe") <|> ((pRegExpr regex_'5b'5c'24'40'25'5d >>= withAttribute DataTypeTok) >>~ pushContext "var_detect_unsafe") <|> ((pRegExpr regex_'5c'2a'5cw'2b >>= withAttribute DataTypeTok) >>~ pushContext "var_detect_unsafe") <|> ((pAnyChar "$@%*" >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules "var_detect" = (((parseRules "var_detect_rules")) <|> ((parseRules "slash_safe_escape")) <|> ((popContext >> popContext) >> currentContext >>= parseRules)) parseRules "var_detect_unsafe" = (((parseRules "var_detect_rules")) <|> ((popContext >> popContext) >> currentContext >>= parseRules)) parseRules "var_detect_rules" = (((pRegExpr regex_'5b'5cw'5f'5d'2b >>= withAttribute DataTypeTok)) <|> ((pDetect2Chars False ':' ':' >>= withAttribute NormalTok)) <|> ((pDetectChar False '\'' >>= withAttribute KeywordTok)) <|> ((pDetect2Chars False '-' '>' >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '+' '+' >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '-' '-' >>= withAttribute NormalTok))) parseRules "quote_word" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute NormalTok)) <|> ((pDetectChar True '1' >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext))) parseRules "quote_word_paren" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute NormalTok)) <|> ((pDetectChar False ')' >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext))) parseRules "quote_word_brace" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute NormalTok)) <|> ((pDetectChar False '}' >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext))) parseRules "quote_word_bracket" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute NormalTok)) <|> ((pDetectChar False ']' >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext))) parseRules "find_here_document" = (((pRegExpr regex_'28'5cw'2b'29'5cs'2a'3b'3f >>= withAttribute KeywordTok) >>~ pushContext "here_document") <|> ((pRegExpr regex_'5cs'2a'22'28'5b'5e'22'5d'2b'29'22'5cs'2a'3b'3f >>= withAttribute KeywordTok) >>~ pushContext "here_document") <|> ((pRegExpr regex_'5cs'2a'60'28'5b'5e'60'5d'2b'29'60'5cs'2a'3b'3f >>= withAttribute KeywordTok) >>~ pushContext "here_document") <|> ((pRegExpr regex_'5cs'2a'27'28'5b'5e'27'5d'2b'29'27'5cs'2a'3b'3f >>= withAttribute KeywordTok) >>~ pushContext "here_document_dumb")) parseRules "here_document" = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pColumn 0 >> pRegExprDynamic "%1" >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((pRegExpr regex_'5c'3d'5cs'2a'3c'3c'5cs'2a'5b'22'27'5d'3f'28'5bA'2dZ0'2d9'5f'5c'2d'5d'2b'29'5b'22'27'5d'3f >>= withAttribute KeywordTok) >>~ pushContext "here_document") <|> ((parseRules "ipstring_internal"))) parseRules "here_document_dumb" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pColumn 0 >> pRegExprDynamic "%1" >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((pDetectIdentifier >>= withAttribute NormalTok))) parseRules "data_handle" = (((pColumn 0 >> pRegExpr regex_'5c'3d'28'3f'3ahead'5b1'2d6'5d'7cover'7cback'7citem'7cfor'7cbegin'7cend'7cpod'29'5cs'2b'2e'2a >>= withAttribute CommentTok) >>~ pushContext "pod") <|> ((pFirstNonSpace >> pString False "__END__" >>= withAttribute KeywordTok) >>~ pushContext "normal")) parseRules "end_handle" = (((pColumn 0 >> pRegExpr regex_'5c'3d'28'3f'3ahead'5b1'2d6'5d'7cover'7cback'7citem'7cfor'7cbegin'7cend'7cpod'29'5cs'2a'2e'2a >>= withAttribute CommentTok) >>~ pushContext "pod") <|> ((pFirstNonSpace >> pString False "__DATA__" >>= withAttribute KeywordTok) >>~ pushContext "data_handle")) parseRules "Backticked" = (((parseRules "ipstring_internal")) <|> ((pDetectChar False '`' >>= withAttribute KeywordTok) >>~ (popContext))) parseRules "slash_safe_escape" = (((pRegExpr regex_'5cs'2a'5c'7d'5cs'2a'2f'7b1'2c2'7d >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pRegExpr regex_'5cs'2a'5b'29'5c'5d'5d'3f'5cs'2a'2f'7b1'2c2'7d >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules "package_qualified_blank" = ((pRegExpr regex_'5b'5cw'5f'5d'2b >>= withAttribute NormalTok) >>~ (popContext)) parseRules "sub_name_def" = (((pRegExpr regex_'5cw'2b >>= withAttribute FunctionTok)) <|> ((lookAhead (pRegExpr regex_'5c'24'5cS) >> pushContext "find_variable" >> currentContext >>= parseRules)) <|> ((pRegExpr regex_'5cs'2a'5c'28 >>= withAttribute NormalTok) >>~ pushContext "sub_arg_definition") <|> ((pDetect2Chars False ':' ':' >>= withAttribute NormalTok)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules "sub_arg_definition" = (((pAnyChar "*$@%" >>= withAttribute DataTypeTok)) <|> ((pAnyChar "&\\[];" >>= withAttribute NormalTok)) <|> ((pDetectChar False ')' >>= withAttribute NormalTok) >>~ pushContext "slash_safe_escape") <|> ((popContext >> popContext) >> currentContext >>= parseRules)) parseRules "pod" = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((pDetectIdentifier >>= withAttribute CommentTok)) <|> ((pColumn 0 >> pRegExpr regex_'5c'3d'28'3f'3ahead'5b1'2d6'5d'7cover'7cback'7citem'7cfor'7cbegin'7cend'7cpod'29'5cs'2a'2e'2a >>= withAttribute CommentTok)) <|> ((pColumn 0 >> pRegExpr regex_'5c'3dcut'2e'2a'24 >>= withAttribute CommentTok) >>~ (popContext))) parseRules "comment" = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression >>= ((withAttribute CommentTok) . snd))) <|> ((pDetectIdentifier >>= withAttribute CommentTok))) parseRules "" = parseRules "normal" parseRules x = fail $ "Unknown context" ++ x