{- This module was generated from data in the Kate syntax highlighting file ruby.xml, version 1.24, by Stefan Lang (langstefan@gmx.at), Sebastian Vuorinen (sebastian.vuorinen@helsinki.fi), Robin Pedersen (robinpeder@gmail.com), Miquel Sabaté (mikisabate@gmail.com) -} module Text.Highlighting.Kate.Syntax.Ruby (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 = "Ruby" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.rb;*.rjs;*.rxml;*.xml.erb;*.js.erb;*.rake;Rakefile;Gemfile;*.gemspec" -- | 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 = "Ruby" } context <- currentContext <|> (pushContext "Normal" >> currentContext) result <- parseRules context optional $ eof >> pEndLine updateState $ \st -> st { synStLanguage = oldLang } return result startingState = SyntaxState {synStContexts = fromList [("Ruby",["Normal"])], synStLanguage = "Ruby", synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do context <- currentContext case context of "Normal" -> return () "check_div_1" -> (popContext) >> pEndLine "check_div_1_pop" -> (popContext >> popContext) >> pEndLine "check_div_2" -> (popContext) >> pEndLine "check_div_2_internal" -> (popContext >> popContext) >> pEndLine "check_div_2_pop" -> (popContext >> popContext) >> pEndLine "check_div_2_pop_internal" -> (popContext >> popContext >> popContext) >> pEndLine "Line Continue" -> (popContext) >> pEndLine "Find closing block brace" -> return () "Quoted String" -> return () "Apostrophed String" -> return () "Command String" -> return () "Embedded documentation" -> return () "RegEx 1" -> return () "Subst" -> return () "Short Subst" -> (popContext) >> pEndLine "Member Access" -> (popContext) >> pEndLine "Comment Line" -> (popContext) >> pEndLine "General Comment" -> (popContext) >> pEndLine "RDoc Label" -> (popContext) >> pEndLine "find_heredoc" -> (popContext) >> pEndLine "find_indented_heredoc" -> (popContext) >> pEndLine "indented_heredoc" -> return () "apostrophed_indented_heredoc" -> return () "normal_heredoc" -> return () "apostrophed_normal_heredoc" -> return () "heredoc_rules" -> return () "find_gdl_input" -> (popContext) >> pEndLine "gdl_dq_string_1" -> return () "gdl_dq_string_1_nested" -> return () "gdl_dq_string_2" -> return () "gdl_dq_string_2_nested" -> return () "gdl_dq_string_3" -> return () "gdl_dq_string_3_nested" -> return () "gdl_dq_string_4" -> return () "gdl_dq_string_4_nested" -> return () "gdl_dq_string_5" -> return () "dq_string_rules" -> return () "gdl_token_array_1" -> return () "gdl_token_array_1_nested" -> return () "gdl_token_array_2" -> return () "gdl_token_array_2_nested" -> return () "gdl_token_array_3" -> return () "gdl_token_array_3_nested" -> return () "gdl_token_array_4" -> return () "gdl_token_array_4_nested" -> return () "gdl_token_array_5" -> return () "token_array_rules" -> return () "gdl_apostrophed_1" -> return () "gdl_apostrophed_1_nested" -> return () "gdl_apostrophed_2" -> return () "gdl_apostrophed_2_nested" -> return () "gdl_apostrophed_3" -> return () "gdl_apostrophed_3_nested" -> return () "gdl_apostrophed_4" -> return () "gdl_apostrophed_4_nested" -> return () "gdl_apostrophed_5" -> return () "apostrophed_rules" -> return () "gdl_shell_command_1" -> return () "gdl_shell_command_1_nested" -> return () "gdl_shell_command_2" -> return () "gdl_shell_command_2_nested" -> return () "gdl_shell_command_3" -> return () "gdl_shell_command_3_nested" -> return () "gdl_shell_command_4" -> return () "gdl_shell_command_4_nested" -> return () "gdl_shell_command_5" -> return () "shell_command_rules" -> return () "gdl_regexpr_1" -> return () "gdl_regexpr_1_nested" -> return () "gdl_regexpr_2" -> return () "gdl_regexpr_2_nested" -> return () "gdl_regexpr_3" -> return () "gdl_regexpr_3_nested" -> return () "gdl_regexpr_4" -> return () "gdl_regexpr_4_nested" -> return () "gdl_regexpr_5" -> return () "regexpr_rules" -> return () "DATA" -> return () _ -> 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 $ "BEGIN END and begin break case defined? do else elsif end ensure for if in include next not or redo rescue retry return then unless until when yield" list_access'2dcontrol = Set.fromList $ words $ "private_class_method private protected public_class_method public" list_attribute'2ddefinitions = Set.fromList $ words $ "attr_reader attr_writer attr_accessor" list_definitions = Set.fromList $ words $ "alias module class def undef" list_pseudo'2dvariables = Set.fromList $ words $ "self super nil false true caller __FILE__ __LINE__" list_default'2dglobals = Set.fromList $ words $ "$stdout $defout $stderr $deferr $stdin" list_kernel'2dmethods = Set.fromList $ words $ "abort at_exit autoload autoload? binding block_given? callcc caller catch chomp chomp! chop chop! eval exec exit exit! fail fork format getc gets global_variables gsub gsub! iterator? lambda load local_variables loop method_missing open p print printf proc putc puts raise rand readline readlines require require_relative scan select set_trace_func sleep split sprintf srand sub sub! syscall system test throw trace_var trap untrace_var warn" regex_'5f'5fEND'5f'5f'24 = compileRegex "__END__$" regex_'23'21'5c'2f'2e'2a = compileRegex "#!\\/.*" regex_'28'5c'3d'7c'5c'28'7c'5c'5b'7c'5c'7b'29'5cs'2a'28if'7cunless'7cwhile'7cuntil'29'5cb = compileRegex "(\\=|\\(|\\[|\\{)\\s*(if|unless|while|until)\\b" regex_'28while'7cuntil'29'5cb'28'3f'21'2e'2a'5cbdo'5cb'29 = compileRegex "(while|until)\\b(?!.*\\bdo\\b)" regex_'5c'3b'5cs'2a'28while'7cuntil'29'5cb'28'3f'21'2e'2a'5cbdo'5cb'29 = compileRegex "\\;\\s*(while|until)\\b(?!.*\\bdo\\b)" regex_'28if'7cunless'29'5cb = compileRegex "(if|unless)\\b" regex_'5c'3b'5cs'2a'28if'7cunless'29'5cb = compileRegex "\\;\\s*(if|unless)\\b" regex_'5cbclass'5cb = compileRegex "\\bclass\\b" regex_'5cbmodule'5cb = compileRegex "\\bmodule\\b" regex_'5cbbegin'5cb = compileRegex "\\bbegin\\b" regex_'5cbfor'5cb'28'3f'21'2e'2a'5cbdo'5cb'29 = compileRegex "\\bfor\\b(?!.*\\bdo\\b)" regex_'5cbcase'5cb = compileRegex "\\bcase\\b" regex_'5cbdo'5cb = compileRegex "\\bdo\\b" regex_'5cbdef'5cb = compileRegex "\\bdef\\b" regex_'5cbend'5cb = compileRegex "\\bend\\b" regex_'5cb'28else'7celsif'7crescue'7censure'29'5cb = compileRegex "\\b(else|elsif|rescue|ensure)\\b" regex_'5c'2e'5b'5fa'2dz'5d'5b'5fa'2dzA'2dZ0'2d9'5d'2a'28'5c'3f'7c'5c'21'7c'5cb'29 = compileRegex "\\.[_a-z][_a-zA-Z0-9]*(\\?|\\!|\\b)" regex_'5cs'5c'3f'28'5c'5cM'5c'2d'29'3f'28'5c'5cC'5c'2d'29'3f'5c'5c'3f'5cS = compileRegex "\\s\\?(\\\\M\\-)?(\\\\C\\-)?\\\\?\\S" regex_'5c'24'5ba'2dzA'2dZ'5f0'2d9'5d'2b = compileRegex "\\$[a-zA-Z_0-9]+" regex_'5c'24'5c'2d'5ba'2dzA'2dz'5f'5d'5cb = compileRegex "\\$\\-[a-zA-z_]\\b" regex_'5c'24'5b'5cd'5f'2a'60'5c'21'3a'3f'27'2f'5c'5c'5c'2d'5c'26'22'5d = compileRegex "\\$[\\d_*`\\!:?'/\\\\\\-\\&\"]" regex_'5cb'5b'5fA'2dZ'5d'2b'5bA'2dZ'5f0'2d9'5d'2b'5cb = compileRegex "\\b[_A-Z]+[A-Z_0-9]+\\b" regex_'5cb'5bA'2dZ'5d'2b'5f'2a'28'5b0'2d9'5d'7c'5ba'2dz'5d'29'5b'5fa'2dzA'2dZ0'2d9'5d'2a'5cb = compileRegex "\\b[A-Z]+_*([0-9]|[a-z])[_a-zA-Z0-9]*\\b" regex_'5cb'5c'2d'3f0'5bxX'5d'5b'5f0'2d9a'2dfA'2dF'5d'2b = compileRegex "\\b\\-?0[xX][_0-9a-fA-F]+" regex_'5cb'5c'2d'3f0'5bbB'5d'5b'5f01'5d'2b = compileRegex "\\b\\-?0[bB][_01]+" regex_'5cb'5c'2d'3f0'5b1'2d7'5d'5b'5f0'2d7'5d'2a = compileRegex "\\b\\-?0[1-7][_0-7]*" regex_'5cb'5c'2d'3f'5b0'2d9'5d'5b0'2d9'5f'5d'2a'5c'2e'5b0'2d9'5d'5b0'2d9'5f'5d'2a'28'5beE'5d'5c'2d'3f'5b1'2d9'5d'5b0'2d9'5d'2a'28'5c'2e'5b0'2d9'5d'2a'29'3f'29'3f = compileRegex "\\b\\-?[0-9][0-9_]*\\.[0-9][0-9_]*([eE]\\-?[1-9][0-9]*(\\.[0-9]*)?)?" regex_'5cb'5c'2d'3f'5b1'2d9'5d'5b0'2d9'5f'5d'2a'5cb = compileRegex "\\b\\-?[1-9][0-9_]*\\b" regex_'3dbegin'28'3f'3a'5cs'7c'24'29 = compileRegex "=begin(?:\\s|$)" regex_'5cs'2a'3c'3c'2d'28'3f'3d'5cw'2b'7c'5b'22'27'5d'29 = compileRegex "\\s*<<-(?=\\w+|[\"'])" regex_'5cs'2a'3c'3c'28'3f'3d'5cw'2b'7c'5b'22'27'5d'29 = compileRegex "\\s*<<(?=\\w+|[\"'])" regex_'5cs'5b'5c'3f'5c'3a'5c'25'5d'5cs = compileRegex "\\s[\\?\\:\\%]\\s" regex_'5b'7c'26'3c'3e'5c'5e'5c'2b'2a'7e'5c'2d'3d'5d'2b = compileRegex "[|&<>\\^\\+*~\\-=]+" regex_'5cs'21 = compileRegex "\\s!" regex_'2f'3d'5cs = compileRegex "/=\\s" regex_'3a'28'40'7b1'2c2'7d'7c'5c'24'29'3f'5ba'2dzA'2dZ'5f'5d'5ba'2dzA'2dZ0'2d9'5f'5d'2a'5b'3d'3f'21'5d'3f = compileRegex ":(@{1,2}|\\$)?[a-zA-Z_][a-zA-Z0-9_]*[=?!]?" regex_'3a'5c'5b'5c'5d'3d'3f = compileRegex ":\\[\\]=?" regex_'23'5cs'2aBEGIN'2e'2a'24 = compileRegex "#\\s*BEGIN.*$" regex_'23'5cs'2aEND'2e'2a'24 = compileRegex "#\\s*END.*$" regex_'40'5ba'2dzA'2dZ'5f0'2d9'5d'2b = compileRegex "@[a-zA-Z_0-9]+" regex_'40'40'5ba'2dzA'2dZ'5f0'2d9'5d'2b = compileRegex "@@[a-zA-Z_0-9]+" regex_'5cs'2a'5b'25'5d'28'3f'3d'5bQqxwW'5d'3f'5b'5e'5cs'5d'29 = compileRegex "\\s*[%](?=[QqxwW]?[^\\s])" regex_'5cs'2a = compileRegex "\\s*" regex_'5cs'2b = compileRegex "\\s+" regex_'5b'2f'25'5d'28'3f'3d'5cs'29 = compileRegex "[/%](?=\\s)" regex_'2f'28'3f'3d'5cs'29 = compileRegex "/(?=\\s)" regex_'5c'5c'5c'22 = compileRegex "\\\\\\\"" regex_'23'40'7b1'2c2'7d = compileRegex "#@{1,2}" regex_'5c'5c'5c'27 = compileRegex "\\\\\\'" regex_'5c'5c'5c'60 = compileRegex "\\\\\\`" regex_'3dend'28'3f'3a'5cs'2e'2a'7c'24'29 = compileRegex "=end(?:\\s.*|$)" regex_'5c'5c'5c'2f = compileRegex "\\\\\\/" regex_'2f'5buiomxn'5d'2a = compileRegex "/[uiomxn]*" regex_'5cw'28'3f'21'5cw'29 = compileRegex "\\w(?!\\w)" regex_'5c'2e'3f'5b'5fa'2dz'5d'5cw'2a'28'5c'3f'7c'5c'21'29'3f'28'3f'3d'5b'5e'5cw'5cd'5c'2e'5c'3a'5d'29 = compileRegex "\\.?[_a-z]\\w*(\\?|\\!)?(?=[^\\w\\d\\.\\:])" regex_'5c'2e'3f'5b'5fa'2dz'5d'5cw'2a'28'5c'3f'7c'5c'21'29'3f = compileRegex "\\.?[_a-z]\\w*(\\?|\\!)?" regex_'5bA'2dZ'5d'2b'5f'2a'28'5cd'7c'5ba'2dz'5d'29'5cw'2a'28'3f'3d'5b'5e'5cw'5cd'5c'2e'5c'3a'5d'29 = compileRegex "[A-Z]+_*(\\d|[a-z])\\w*(?=[^\\w\\d\\.\\:])" regex_'5bA'2dZ'5d'2b'5f'2a'28'5b0'2d9'5d'7c'5ba'2dz'5d'29'5cw'2a = compileRegex "[A-Z]+_*([0-9]|[a-z])\\w*" regex_'5b'5fA'2dZ'5d'5b'5fA'2dZ0'2d9'5d'2a'28'3f'3d'5b'5e'5cw'5cd'5c'2e'5c'3a'5d'29 = compileRegex "[_A-Z][_A-Z0-9]*(?=[^\\w\\d\\.\\:])" regex_'5b'5fA'2dZ'5d'5b'5fA'2dZ0'2d9'5d'2a = compileRegex "[_A-Z][_A-Z0-9]*" regex_'5cW = compileRegex "\\W" regex_'5cw'5c'3a'5c'3a'5cs = compileRegex "\\w\\:\\:\\s" regex_'27'28'5cw'2b'29'27 = compileRegex "'(\\w+)'" regex_'22'3f'28'5cw'2b'29'22'3f = compileRegex "\"?(\\w+)\"?" regex_w'5c'28 = compileRegex "w\\(" regex_w'5c'7b = compileRegex "w\\{" regex_w'5c'5b = compileRegex "w\\[" regex_w'3c = compileRegex "w<" regex_w'28'5b'5e'5cs'5cw'5d'29 = compileRegex "w([^\\s\\w])" regex_W'5c'28 = compileRegex "W\\(" regex_W'5c'7b = compileRegex "W\\{" regex_W'5c'5b = compileRegex "W\\[" regex_W'3c = compileRegex "W<" regex_W'28'5b'5e'5cs'5cw'5d'29 = compileRegex "W([^\\s\\w])" regex_q'5c'28 = compileRegex "q\\(" regex_q'5c'7b = compileRegex "q\\{" regex_q'5c'5b = compileRegex "q\\[" regex_q'3c = compileRegex "q<" regex_q'28'5b'5e'5cs'5cw'5d'29 = compileRegex "q([^\\s\\w])" regex_x'5c'28 = compileRegex "x\\(" regex_x'5c'7b = compileRegex "x\\{" regex_x'5c'5b = compileRegex "x\\[" regex_x'3c = compileRegex "x<" regex_x'28'5b'5e'5cs'5cw'5d'29 = compileRegex "x([^\\s\\w])" regex_r'5c'28 = compileRegex "r\\(" regex_r'5c'7b = compileRegex "r\\{" regex_r'5c'5b = compileRegex "r\\[" regex_r'3c = compileRegex "r<" regex_r'28'5b'5e'5cs'5cw'5d'29 = compileRegex "r([^\\s\\w])" regex_Q'3f'5c'28 = compileRegex "Q?\\(" regex_Q'3f'5c'7b = compileRegex "Q?\\{" regex_Q'3f'5c'5b = compileRegex "Q?\\[" regex_Q'3f'3c = compileRegex "Q?<" regex_Q'3f'28'5b'5e'5cs'5cw'5d'29 = compileRegex "Q?([^\\s\\w])" regex_'5c'29'5buiomxn'5d'2a = compileRegex "\\)[uiomxn]*" regex_'5c'7d'5buiomxn'5d'2a = compileRegex "\\}[uiomxn]*" regex_'5c'5d'5buiomxn'5d'2a = compileRegex "\\][uiomxn]*" regex_'3e'5buiomxn'5d'2a = compileRegex ">[uiomxn]*" defaultAttributes = [("Normal",NormalTok),("check_div_1",NormalTok),("check_div_1_pop",NormalTok),("check_div_2",NormalTok),("check_div_2_internal",NormalTok),("check_div_2_pop",NormalTok),("check_div_2_pop_internal",NormalTok),("Line Continue",NormalTok),("Find closing block brace",NormalTok),("Quoted String",StringTok),("Apostrophed String",StringTok),("Command String",StringTok),("Embedded documentation",CommentTok),("RegEx 1",OtherTok),("Subst",NormalTok),("Short Subst",OtherTok),("Member Access",NormalTok),("Comment Line",CommentTok),("General Comment",CommentTok),("RDoc Label",OtherTok),("find_heredoc",NormalTok),("find_indented_heredoc",NormalTok),("indented_heredoc",OtherTok),("apostrophed_indented_heredoc",OtherTok),("normal_heredoc",OtherTok),("apostrophed_normal_heredoc",OtherTok),("heredoc_rules",NormalTok),("find_gdl_input",NormalTok),("gdl_dq_string_1",StringTok),("gdl_dq_string_1_nested",StringTok),("gdl_dq_string_2",StringTok),("gdl_dq_string_2_nested",StringTok),("gdl_dq_string_3",StringTok),("gdl_dq_string_3_nested",StringTok),("gdl_dq_string_4",StringTok),("gdl_dq_string_4_nested",StringTok),("gdl_dq_string_5",StringTok),("dq_string_rules",StringTok),("gdl_token_array_1",StringTok),("gdl_token_array_1_nested",StringTok),("gdl_token_array_2",StringTok),("gdl_token_array_2_nested",StringTok),("gdl_token_array_3",StringTok),("gdl_token_array_3_nested",StringTok),("gdl_token_array_4",StringTok),("gdl_token_array_4_nested",StringTok),("gdl_token_array_5",StringTok),("token_array_rules",StringTok),("gdl_apostrophed_1",StringTok),("gdl_apostrophed_1_nested",StringTok),("gdl_apostrophed_2",StringTok),("gdl_apostrophed_2_nested",StringTok),("gdl_apostrophed_3",StringTok),("gdl_apostrophed_3_nested",StringTok),("gdl_apostrophed_4",StringTok),("gdl_apostrophed_4_nested",StringTok),("gdl_apostrophed_5",StringTok),("apostrophed_rules",StringTok),("gdl_shell_command_1",StringTok),("gdl_shell_command_1_nested",StringTok),("gdl_shell_command_2",StringTok),("gdl_shell_command_2_nested",StringTok),("gdl_shell_command_3",StringTok),("gdl_shell_command_3_nested",StringTok),("gdl_shell_command_4",StringTok),("gdl_shell_command_4_nested",StringTok),("gdl_shell_command_5",StringTok),("shell_command_rules",StringTok),("gdl_regexpr_1",OtherTok),("gdl_regexpr_1_nested",OtherTok),("gdl_regexpr_2",OtherTok),("gdl_regexpr_2_nested",OtherTok),("gdl_regexpr_3",OtherTok),("gdl_regexpr_3_nested",OtherTok),("gdl_regexpr_4",OtherTok),("gdl_regexpr_4_nested",OtherTok),("gdl_regexpr_5",OtherTok),("regexpr_rules",OtherTok),("DATA",NormalTok)] parseRules "Normal" = (((pLineContinue >>= withAttribute NormalTok) >>~ pushContext "Line Continue") <|> ((pColumn 0 >> pRegExpr regex_'5f'5fEND'5f'5f'24 >>= withAttribute KeywordTok) >>~ pushContext "DATA") <|> ((pColumn 0 >> pRegExpr regex_'23'21'5c'2f'2e'2a >>= withAttribute KeywordTok)) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext "Find closing block brace") <|> ((pRegExpr regex_'28'5c'3d'7c'5c'28'7c'5c'5b'7c'5c'7b'29'5cs'2a'28if'7cunless'7cwhile'7cuntil'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'28while'7cuntil'29'5cb'28'3f'21'2e'2a'5cbdo'5cb'29 >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5c'3b'5cs'2a'28while'7cuntil'29'5cb'28'3f'21'2e'2a'5cbdo'5cb'29 >>= withAttribute KeywordTok)) <|> ((pFirstNonSpace >> pRegExpr regex_'28if'7cunless'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5c'3b'5cs'2a'28if'7cunless'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbclass'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbmodule'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbbegin'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbfor'5cb'28'3f'21'2e'2a'5cbdo'5cb'29 >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbcase'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbdo'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbdef'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbend'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cb'28else'7celsif'7crescue'7censure'29'5cb >>= withAttribute KeywordTok)) <|> ((pString False "..." >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '.' '.' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'2e'5b'5fa'2dz'5d'5b'5fa'2dzA'2dZ0'2d9'5d'2a'28'5c'3f'7c'5c'21'7c'5cb'29 >>= withAttribute NormalTok) >>~ pushContext "check_div_2") <|> ((pRegExpr regex_'5cs'5c'3f'28'5c'5cM'5c'2d'29'3f'28'5c'5cC'5c'2d'29'3f'5c'5c'3f'5cS >>= withAttribute DecValTok) >>~ pushContext "check_div_1") <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_attribute'2ddefinitions >>= withAttribute OtherTok) >>~ pushContext "check_div_2") <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_access'2dcontrol >>= withAttribute KeywordTok) >>~ pushContext "check_div_2") <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_definitions >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_pseudo'2dvariables >>= withAttribute DecValTok) >>~ pushContext "check_div_1") <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_default'2dglobals >>= withAttribute DataTypeTok) >>~ pushContext "check_div_2") <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_kernel'2dmethods >>= withAttribute NormalTok) >>~ pushContext "check_div_2") <|> ((pRegExpr regex_'5c'24'5ba'2dzA'2dZ'5f0'2d9'5d'2b >>= withAttribute DataTypeTok) >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5c'24'5c'2d'5ba'2dzA'2dz'5f'5d'5cb >>= withAttribute DataTypeTok) >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5c'24'5b'5cd'5f'2a'60'5c'21'3a'3f'27'2f'5c'5c'5c'2d'5c'26'22'5d >>= withAttribute DataTypeTok) >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5cb'5b'5fA'2dZ'5d'2b'5bA'2dZ'5f0'2d9'5d'2b'5cb >>= withAttribute DataTypeTok) >>~ pushContext "check_div_2") <|> ((pRegExpr regex_'5cb'5bA'2dZ'5d'2b'5f'2a'28'5b0'2d9'5d'7c'5ba'2dz'5d'29'5b'5fa'2dzA'2dZ0'2d9'5d'2a'5cb >>= withAttribute DataTypeTok) >>~ pushContext "check_div_2") <|> ((pRegExpr regex_'5cb'5c'2d'3f0'5bxX'5d'5b'5f0'2d9a'2dfA'2dF'5d'2b >>= withAttribute BaseNTok) >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5cb'5c'2d'3f0'5bbB'5d'5b'5f01'5d'2b >>= withAttribute BaseNTok) >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5cb'5c'2d'3f0'5b1'2d7'5d'5b'5f0'2d7'5d'2a >>= withAttribute BaseNTok) >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5cb'5c'2d'3f'5b0'2d9'5d'5b0'2d9'5f'5d'2a'5c'2e'5b0'2d9'5d'5b0'2d9'5f'5d'2a'28'5beE'5d'5c'2d'3f'5b1'2d9'5d'5b0'2d9'5d'2a'28'5c'2e'5b0'2d9'5d'2a'29'3f'29'3f >>= withAttribute FloatTok) >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5cb'5c'2d'3f'5b1'2d9'5d'5b0'2d9'5f'5d'2a'5cb >>= withAttribute DecValTok) >>~ pushContext "check_div_1") <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext "check_div_1") <|> ((pHlCChar >>= withAttribute CharTok) >>~ pushContext "check_div_1") <|> ((pColumn 0 >> pRegExpr regex_'3dbegin'28'3f'3a'5cs'7c'24'29 >>= withAttribute CommentTok) >>~ pushContext "Embedded documentation") <|> ((pRegExpr regex_'5cs'2a'3c'3c'2d'28'3f'3d'5cw'2b'7c'5b'22'27'5d'29 >>= withAttribute NormalTok) >>~ pushContext "find_indented_heredoc") <|> ((pRegExpr regex_'5cs'2a'3c'3c'28'3f'3d'5cw'2b'7c'5b'22'27'5d'29 >>= withAttribute NormalTok) >>~ pushContext "find_heredoc") <|> ((pDetectChar False '.' >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '&' '&' >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '|' '|' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cs'5b'5c'3f'5c'3a'5c'25'5d'5cs >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5b'7c'26'3c'3e'5c'5e'5c'2b'2a'7e'5c'2d'3d'5d'2b >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cs'21 >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'2f'3d'5cs >>= withAttribute NormalTok)) <|> ((pString False "%=" >>= withAttribute NormalTok)) <|> ((pDetect2Chars False ':' ':' >>= withAttribute NormalTok) >>~ pushContext "Member Access") <|> ((pRegExpr regex_'3a'28'40'7b1'2c2'7d'7c'5c'24'29'3f'5ba'2dzA'2dZ'5f'5d'5ba'2dzA'2dZ0'2d9'5f'5d'2a'5b'3d'3f'21'5d'3f >>= withAttribute StringTok) >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'3a'5c'5b'5c'5d'3d'3f >>= withAttribute StringTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext "Quoted String") <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext "Apostrophed String") <|> ((pDetectChar False '`' >>= withAttribute StringTok) >>~ pushContext "Command String") <|> ((pString False "?#" >>= withAttribute NormalTok)) <|> ((pColumn 0 >> pRegExpr regex_'23'5cs'2aBEGIN'2e'2a'24 >>= withAttribute CommentTok)) <|> ((pColumn 0 >> pRegExpr regex_'23'5cs'2aEND'2e'2a'24 >>= withAttribute CommentTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext "General Comment") <|> ((pDetectChar False '[' >>= withAttribute NormalTok)) <|> ((pDetectChar False ']' >>= withAttribute NormalTok) >>~ pushContext "check_div_1") <|> ((pDetectChar False '{' >>= withAttribute NormalTok)) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'40'5ba'2dzA'2dZ'5f0'2d9'5d'2b >>= withAttribute OtherTok) >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'40'40'5ba'2dzA'2dZ'5f0'2d9'5d'2b >>= withAttribute OtherTok) >>~ pushContext "check_div_1") <|> ((pDetectChar False '/' >>= withAttribute OtherTok) >>~ pushContext "RegEx 1") <|> ((pRegExpr regex_'5cs'2a'5b'25'5d'28'3f'3d'5bQqxwW'5d'3f'5b'5e'5cs'5d'29 >>= withAttribute OtherTok) >>~ pushContext "find_gdl_input") <|> ((pDetectChar False ')' >>= withAttribute NormalTok) >>~ pushContext "check_div_1") <|> ((pDetectIdentifier >>= withAttribute NormalTok) >>~ pushContext "check_div_2")) parseRules "check_div_1" = (((pRegExpr regex_'5cs'2a >>= withAttribute NormalTok)) <|> ((pAnyChar "/%" >>= withAttribute NormalTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules "check_div_1_pop" = (((pRegExpr regex_'5cs'2a >>= withAttribute NormalTok)) <|> ((pAnyChar "/%" >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((popContext >> popContext) >> currentContext >>= parseRules)) parseRules "check_div_2" = (((pAnyChar "/%" >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pRegExpr regex_'5cs'2b >>= withAttribute NormalTok) >>~ pushContext "check_div_2_internal") <|> ((popContext) >> currentContext >>= parseRules)) parseRules "check_div_2_internal" = (((pRegExpr regex_'5b'2f'25'5d'28'3f'3d'5cs'29 >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((popContext >> popContext) >> currentContext >>= parseRules)) parseRules "check_div_2_pop" = (((pAnyChar "/%" >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((pRegExpr regex_'5cs'2b >>= withAttribute NormalTok) >>~ pushContext "check_div_2_pop_internal") <|> ((popContext >> popContext) >> currentContext >>= parseRules)) parseRules "check_div_2_pop_internal" = (((pDetectChar False '%' >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext)) <|> ((pRegExpr regex_'2f'28'3f'3d'5cs'29 >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext)) <|> ((popContext >> popContext >> popContext) >> currentContext >>= parseRules)) parseRules "Line Continue" = (((pFirstNonSpace >> pRegExpr regex_'28while'7cuntil'29'5cb'28'3f'21'2e'2a'5cbdo'5cb'29 >>= withAttribute KeywordTok)) <|> ((pFirstNonSpace >> pRegExpr regex_'28if'7cunless'29'5cb >>= withAttribute KeywordTok)) <|> ((parseRules "Normal"))) parseRules "Find closing block brace" = (((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext "check_div_1_pop") <|> ((parseRules "Normal"))) parseRules "Quoted String" = (((pString False "\\\\" >>= withAttribute StringTok)) <|> ((pRegExpr regex_'5c'5c'5c'22 >>= withAttribute StringTok)) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute OtherTok) >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute OtherTok) >>~ pushContext "Subst") <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext "check_div_1_pop")) parseRules "Apostrophed String" = (((pString False "\\\\" >>= withAttribute StringTok)) <|> ((pRegExpr regex_'5c'5c'5c'27 >>= withAttribute StringTok)) <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext "check_div_1_pop")) parseRules "Command String" = (((pString False "\\\\" >>= withAttribute StringTok)) <|> ((pRegExpr regex_'5c'5c'5c'60 >>= withAttribute StringTok)) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute OtherTok) >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute OtherTok) >>~ pushContext "Subst") <|> ((pDetectChar False '`' >>= withAttribute StringTok) >>~ pushContext "check_div_1_pop")) parseRules "Embedded documentation" = (((pColumn 0 >> pRegExpr regex_'3dend'28'3f'3a'5cs'2e'2a'7c'24'29 >>= withAttribute CommentTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression >>= ((withAttribute CommentTok) . snd)))) parseRules "RegEx 1" = (((pRegExpr regex_'5c'5c'5c'2f >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute OtherTok) >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute OtherTok) >>~ pushContext "Subst") <|> ((pRegExpr regex_'2f'5buiomxn'5d'2a >>= withAttribute OtherTok) >>~ pushContext "check_div_1_pop")) parseRules "Subst" = (((pDetectChar False '}' >>= withAttribute OtherTok) >>~ (popContext)) <|> ((parseRules "Normal"))) parseRules "Short Subst" = (((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'5cw'28'3f'21'5cw'29 >>= withAttribute OtherTok) >>~ (popContext))) parseRules "Member Access" = (((pRegExpr regex_'5c'2e'3f'5b'5fa'2dz'5d'5cw'2a'28'5c'3f'7c'5c'21'29'3f'28'3f'3d'5b'5e'5cw'5cd'5c'2e'5c'3a'5d'29 >>= withAttribute NormalTok) >>~ pushContext "check_div_2_pop") <|> ((pRegExpr regex_'5c'2e'3f'5b'5fa'2dz'5d'5cw'2a'28'5c'3f'7c'5c'21'29'3f >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5bA'2dZ'5d'2b'5f'2a'28'5cd'7c'5ba'2dz'5d'29'5cw'2a'28'3f'3d'5b'5e'5cw'5cd'5c'2e'5c'3a'5d'29 >>= withAttribute DataTypeTok) >>~ pushContext "check_div_2_pop") <|> ((pRegExpr regex_'5bA'2dZ'5d'2b'5f'2a'28'5b0'2d9'5d'7c'5ba'2dz'5d'29'5cw'2a >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5b'5fA'2dZ'5d'5b'5fA'2dZ0'2d9'5d'2a'28'3f'3d'5b'5e'5cw'5cd'5c'2e'5c'3a'5d'29 >>= withAttribute DataTypeTok) >>~ pushContext "check_div_2_pop") <|> ((pRegExpr regex_'5b'5fA'2dZ'5d'5b'5fA'2dZ0'2d9'5d'2a >>= withAttribute DataTypeTok)) <|> ((pDetect2Chars False ':' ':' >>= withAttribute NormalTok)) <|> ((pDetectChar False '.' >>= withAttribute NormalTok)) <|> ((pAnyChar "=+-*/%|&[]{}~" >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pAnyChar "()\\" >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pRegExpr regex_'5cW >>= withAttribute NormalTok) >>~ (popContext))) parseRules "Comment Line" = (((pRegExpr regex_'5cw'5c'3a'5c'3a'5cs >>= withAttribute CommentTok) >>~ pushContext "RDoc Label") <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression >>= ((withAttribute CommentTok) . snd)))) parseRules "General Comment" = ((Text.Highlighting.Kate.Syntax.Alert.parseExpression >>= ((withAttribute CommentTok) . snd))) parseRules "RDoc Label" = pzero parseRules "find_heredoc" = (((pRegExpr regex_'27'28'5cw'2b'29'27 >>= withAttribute KeywordTok) >>~ pushContext "apostrophed_normal_heredoc") <|> ((pRegExpr regex_'22'3f'28'5cw'2b'29'22'3f >>= withAttribute KeywordTok) >>~ pushContext "normal_heredoc")) parseRules "find_indented_heredoc" = (((pRegExpr regex_'27'28'5cw'2b'29'27 >>= withAttribute KeywordTok) >>~ pushContext "apostrophed_indented_heredoc") <|> ((pRegExpr regex_'22'3f'28'5cw'2b'29'22'3f >>= withAttribute KeywordTok) >>~ pushContext "indented_heredoc")) parseRules "indented_heredoc" = (((pFirstNonSpace >> pRegExprDynamic "%1$" >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((parseRules "heredoc_rules"))) parseRules "apostrophed_indented_heredoc" = ((pFirstNonSpace >> pRegExprDynamic "%1$" >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) parseRules "normal_heredoc" = (((pColumn 0 >> pRegExprDynamic "%1$" >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((parseRules "heredoc_rules"))) parseRules "apostrophed_normal_heredoc" = ((pColumn 0 >> pRegExprDynamic "%1$" >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) parseRules "heredoc_rules" = (((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute OtherTok) >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute OtherTok) >>~ pushContext "Subst")) parseRules "find_gdl_input" = (((pRegExpr regex_w'5c'28 >>= withAttribute OtherTok) >>~ pushContext "gdl_token_array_1") <|> ((pRegExpr regex_w'5c'7b >>= withAttribute OtherTok) >>~ pushContext "gdl_token_array_2") <|> ((pRegExpr regex_w'5c'5b >>= withAttribute OtherTok) >>~ pushContext "gdl_token_array_3") <|> ((pRegExpr regex_w'3c >>= withAttribute OtherTok) >>~ pushContext "gdl_token_array_4") <|> ((pRegExpr regex_w'28'5b'5e'5cs'5cw'5d'29 >>= withAttribute OtherTok) >>~ pushContext "gdl_token_array_5") <|> ((pRegExpr regex_W'5c'28 >>= withAttribute OtherTok) >>~ pushContext "gdl_token_array_1") <|> ((pRegExpr regex_W'5c'7b >>= withAttribute OtherTok) >>~ pushContext "gdl_token_array_2") <|> ((pRegExpr regex_W'5c'5b >>= withAttribute OtherTok) >>~ pushContext "gdl_token_array_3") <|> ((pRegExpr regex_W'3c >>= withAttribute OtherTok) >>~ pushContext "gdl_token_array_4") <|> ((pRegExpr regex_W'28'5b'5e'5cs'5cw'5d'29 >>= withAttribute OtherTok) >>~ pushContext "gdl_token_array_5") <|> ((pRegExpr regex_q'5c'28 >>= withAttribute OtherTok) >>~ pushContext "gdl_apostrophed_1") <|> ((pRegExpr regex_q'5c'7b >>= withAttribute OtherTok) >>~ pushContext "gdl_apostrophed_2") <|> ((pRegExpr regex_q'5c'5b >>= withAttribute OtherTok) >>~ pushContext "gdl_apostrophed_3") <|> ((pRegExpr regex_q'3c >>= withAttribute OtherTok) >>~ pushContext "gdl_apostrophed_4") <|> ((pRegExpr regex_q'28'5b'5e'5cs'5cw'5d'29 >>= withAttribute OtherTok) >>~ pushContext "gdl_apostrophed_5") <|> ((pRegExpr regex_x'5c'28 >>= withAttribute OtherTok) >>~ pushContext "gdl_shell_command_1") <|> ((pRegExpr regex_x'5c'7b >>= withAttribute OtherTok) >>~ pushContext "gdl_shell_command_2") <|> ((pRegExpr regex_x'5c'5b >>= withAttribute OtherTok) >>~ pushContext "gdl_shell_command_3") <|> ((pRegExpr regex_x'3c >>= withAttribute OtherTok) >>~ pushContext "gdl_shell_command_4") <|> ((pRegExpr regex_x'28'5b'5e'5cs'5cw'5d'29 >>= withAttribute OtherTok) >>~ pushContext "gdl_shell_command_5") <|> ((pRegExpr regex_r'5c'28 >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_1") <|> ((pRegExpr regex_r'5c'7b >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_2") <|> ((pRegExpr regex_r'5c'5b >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_3") <|> ((pRegExpr regex_r'3c >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_4") <|> ((pRegExpr regex_r'28'5b'5e'5cs'5cw'5d'29 >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_5") <|> ((pRegExpr regex_Q'3f'5c'28 >>= withAttribute OtherTok) >>~ pushContext "gdl_dq_string_1") <|> ((pRegExpr regex_Q'3f'5c'7b >>= withAttribute OtherTok) >>~ pushContext "gdl_dq_string_2") <|> ((pRegExpr regex_Q'3f'5c'5b >>= withAttribute OtherTok) >>~ pushContext "gdl_dq_string_3") <|> ((pRegExpr regex_Q'3f'3c >>= withAttribute OtherTok) >>~ pushContext "gdl_dq_string_4") <|> ((pRegExpr regex_Q'3f'28'5b'5e'5cs'5cw'5d'29 >>= withAttribute OtherTok) >>~ pushContext "gdl_dq_string_5")) parseRules "gdl_dq_string_1" = (((parseRules "dq_string_rules")) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute StringTok)) <|> ((pDetectChar False '(' >>= withAttribute StringTok) >>~ pushContext "gdl_dq_string_1_nested") <|> ((pDetectChar False ')' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_dq_string_1_nested" = (((parseRules "dq_string_rules")) <|> ((pDetectChar False '(' >>= withAttribute StringTok) >>~ pushContext "gdl_dq_string_1_nested") <|> ((pDetectChar False ')' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_dq_string_2" = (((parseRules "dq_string_rules")) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute StringTok)) <|> ((pDetectChar False '}' >>= withAttribute OtherTok) >>~ (popContext >> popContext)) <|> ((pDetectChar False '{' >>= withAttribute StringTok) >>~ pushContext "gdl_dq_string_2_nested")) parseRules "gdl_dq_string_2_nested" = (((pDetectChar False '{' >>= withAttribute StringTok) >>~ pushContext "gdl_dq_string_2_nested") <|> ((pDetectChar False '}' >>= withAttribute StringTok) >>~ (popContext)) <|> ((parseRules "dq_string_rules"))) parseRules "gdl_dq_string_3" = (((parseRules "dq_string_rules")) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute StringTok)) <|> ((pDetectChar False '[' >>= withAttribute StringTok) >>~ pushContext "gdl_dq_string_3_nested") <|> ((pDetectChar False ']' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_dq_string_3_nested" = (((pDetectChar False '[' >>= withAttribute StringTok) >>~ pushContext "gdl_dq_string_3_nested") <|> ((pDetectChar False ']' >>= withAttribute StringTok) >>~ (popContext)) <|> ((parseRules "dq_string_rules"))) parseRules "gdl_dq_string_4" = (((parseRules "dq_string_rules")) <|> ((pDetect2Chars False '\\' '>' >>= withAttribute StringTok)) <|> ((pDetectChar False '<' >>= withAttribute StringTok) >>~ pushContext "gdl_dq_string_4_nested") <|> ((pDetectChar False '>' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_dq_string_4_nested" = (((pDetectChar False '<' >>= withAttribute StringTok) >>~ pushContext "gdl_dq_string_4_nested") <|> ((pDetectChar False '>' >>= withAttribute StringTok) >>~ (popContext)) <|> ((parseRules "dq_string_rules"))) parseRules "gdl_dq_string_5" = (((parseRules "dq_string_rules")) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\s*%1" >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "dq_string_rules" = (((pDetect2Chars False '\\' '\\' >>= withAttribute StringTok)) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute OtherTok) >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute OtherTok) >>~ pushContext "Subst")) parseRules "gdl_token_array_1" = (((parseRules "token_array_rules")) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute StringTok)) <|> ((pDetectChar False '(' >>= withAttribute StringTok) >>~ pushContext "gdl_token_array_1_nested") <|> ((pDetectChar False ')' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_token_array_1_nested" = (((parseRules "token_array_rules")) <|> ((pDetectChar False '(' >>= withAttribute StringTok) >>~ pushContext "gdl_token_array_1_nested") <|> ((pDetectChar False ')' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_token_array_2" = (((parseRules "token_array_rules")) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute StringTok)) <|> ((pDetectChar False '}' >>= withAttribute OtherTok) >>~ (popContext >> popContext)) <|> ((pDetectChar False '{' >>= withAttribute StringTok) >>~ pushContext "gdl_token_array_2_nested")) parseRules "gdl_token_array_2_nested" = (((parseRules "token_array_rules")) <|> ((pDetectChar False '{' >>= withAttribute StringTok) >>~ pushContext "gdl_token_array_2_nested") <|> ((pDetectChar False '}' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_token_array_3" = (((parseRules "token_array_rules")) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute StringTok)) <|> ((pDetectChar False '[' >>= withAttribute StringTok) >>~ pushContext "gdl_token_array_3_nested") <|> ((pDetectChar False ']' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_token_array_3_nested" = (((parseRules "token_array_rules")) <|> ((pDetectChar False '[' >>= withAttribute StringTok) >>~ pushContext "gdl_token_array_3_nested") <|> ((pDetectChar False ']' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_token_array_4" = (((parseRules "token_array_rules")) <|> ((pDetect2Chars False '\\' '>' >>= withAttribute StringTok)) <|> ((pDetectChar False '<' >>= withAttribute StringTok) >>~ pushContext "gdl_token_array_4_nested") <|> ((pDetectChar False '>' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_token_array_4_nested" = (((parseRules "token_array_rules")) <|> ((pDetectChar False '<' >>= withAttribute StringTok) >>~ pushContext "gdl_token_array_4_nested") <|> ((pDetectChar False '>' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_token_array_5" = (((parseRules "token_array_rules")) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\s*%1" >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "token_array_rules" = ((pString False "\\\\" >>= withAttribute StringTok)) parseRules "gdl_apostrophed_1" = (((parseRules "apostrophed_rules")) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute StringTok)) <|> ((pDetectChar False '(' >>= withAttribute StringTok) >>~ pushContext "gdl_apostrophed_1_nested") <|> ((pDetectChar False ')' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_apostrophed_1_nested" = (((parseRules "apostrophed_rules")) <|> ((pDetectChar False '(' >>= withAttribute StringTok) >>~ pushContext "gdl_apostrophed_1_nested") <|> ((pDetectChar False ')' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_apostrophed_2" = (((parseRules "apostrophed_rules")) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute StringTok)) <|> ((pDetectChar False '}' >>= withAttribute OtherTok) >>~ (popContext >> popContext)) <|> ((pDetectChar False '{' >>= withAttribute StringTok) >>~ pushContext "gdl_apostrophed_2_nested")) parseRules "gdl_apostrophed_2_nested" = (((parseRules "apostrophed_rules")) <|> ((pDetectChar False '{' >>= withAttribute StringTok) >>~ pushContext "gdl_apostrophed_2_nested") <|> ((pDetectChar False '}' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_apostrophed_3" = (((parseRules "apostrophed_rules")) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute StringTok)) <|> ((pDetectChar False '[' >>= withAttribute StringTok) >>~ pushContext "gdl_apostrophed_3_nested") <|> ((pDetectChar False ']' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_apostrophed_3_nested" = (((parseRules "apostrophed_rules")) <|> ((pDetectChar False '[' >>= withAttribute StringTok) >>~ pushContext "gdl_apostrophed_3_nested") <|> ((pDetectChar False ']' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_apostrophed_4" = (((parseRules "apostrophed_rules")) <|> ((pDetect2Chars False '\\' '>' >>= withAttribute StringTok)) <|> ((pDetectChar False '<' >>= withAttribute StringTok) >>~ pushContext "gdl_apostrophed_4_nested") <|> ((pDetectChar False '>' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_apostrophed_4_nested" = (((parseRules "apostrophed_rules")) <|> ((pDetectChar False '<' >>= withAttribute StringTok) >>~ pushContext "gdl_apostrophed_4_nested") <|> ((pDetectChar False '>' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_apostrophed_5" = (((parseRules "apostrophed_rules")) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\s*%1" >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "apostrophed_rules" = ((pDetect2Chars False '\\' '\\' >>= withAttribute StringTok)) parseRules "gdl_shell_command_1" = (((parseRules "shell_command_rules")) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute StringTok)) <|> ((pDetectChar False '(' >>= withAttribute StringTok) >>~ pushContext "gdl_shell_command_1_nested") <|> ((pDetectChar False ')' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_shell_command_1_nested" = (((parseRules "shell_command_rules")) <|> ((pDetectChar False '(' >>= withAttribute StringTok) >>~ pushContext "gdl_shell_command_1_nested") <|> ((pDetectChar False ')' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_shell_command_2" = (((parseRules "shell_command_rules")) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute StringTok)) <|> ((pDetectChar False '}' >>= withAttribute OtherTok) >>~ (popContext >> popContext)) <|> ((pDetectChar False '{' >>= withAttribute StringTok) >>~ pushContext "gdl_shell_command_2_nested")) parseRules "gdl_shell_command_2_nested" = (((parseRules "shell_command_rules")) <|> ((pDetectChar False '{' >>= withAttribute StringTok) >>~ pushContext "gdl_shell_command_2_nested") <|> ((pDetectChar False '}' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_shell_command_3" = (((parseRules "shell_command_rules")) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute StringTok)) <|> ((pDetectChar False '[' >>= withAttribute StringTok) >>~ pushContext "gdl_shell_command_3_nested") <|> ((pDetectChar False ']' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_shell_command_3_nested" = (((parseRules "shell_command_rules")) <|> ((pDetectChar False '[' >>= withAttribute StringTok) >>~ pushContext "gdl_shell_command_3_nested") <|> ((pDetectChar False ']' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_shell_command_4" = (((parseRules "shell_command_rules")) <|> ((pDetect2Chars False '\\' '>' >>= withAttribute StringTok)) <|> ((pDetectChar False '<' >>= withAttribute StringTok) >>~ pushContext "gdl_shell_command_4_nested") <|> ((pDetectChar False '>' >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_shell_command_4_nested" = (((parseRules "shell_command_rules")) <|> ((pDetectChar False '<' >>= withAttribute StringTok) >>~ pushContext "gdl_shell_command_4_nested") <|> ((pDetectChar False '>' >>= withAttribute StringTok) >>~ (popContext))) parseRules "gdl_shell_command_5" = (((parseRules "shell_command_rules")) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\s*%1" >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "shell_command_rules" = (((pDetect2Chars False '\\' '\\' >>= withAttribute StringTok)) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute OtherTok) >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute OtherTok) >>~ pushContext "Subst")) parseRules "gdl_regexpr_1" = (((parseRules "regexpr_rules")) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute OtherTok)) <|> ((pDetectChar False '(' >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_1_nested") <|> ((pRegExpr regex_'5c'29'5buiomxn'5d'2a >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_regexpr_1_nested" = (((parseRules "regexpr_rules")) <|> ((pDetectChar False '(' >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_1_nested") <|> ((pDetectChar False ')' >>= withAttribute OtherTok) >>~ (popContext))) parseRules "gdl_regexpr_2" = (((parseRules "regexpr_rules")) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'5c'7d'5buiomxn'5d'2a >>= withAttribute OtherTok) >>~ (popContext >> popContext)) <|> ((pDetectChar False '{' >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_2_nested")) parseRules "gdl_regexpr_2_nested" = (((parseRules "regexpr_rules")) <|> ((pDetectChar False '{' >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_2_nested") <|> ((pDetectChar False '}' >>= withAttribute OtherTok) >>~ (popContext))) parseRules "gdl_regexpr_3" = (((parseRules "regexpr_rules")) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute OtherTok)) <|> ((pDetectChar False '[' >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_3_nested") <|> ((pRegExpr regex_'5c'5d'5buiomxn'5d'2a >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_regexpr_3_nested" = (((parseRules "regexpr_rules")) <|> ((pDetectChar False '[' >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_3_nested") <|> ((pDetectChar False ']' >>= withAttribute OtherTok) >>~ (popContext))) parseRules "gdl_regexpr_4" = (((parseRules "regexpr_rules")) <|> ((pDetect2Chars False '\\' '>' >>= withAttribute OtherTok)) <|> ((pDetectChar False '<' >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_4_nested") <|> ((pRegExpr regex_'3e'5buiomxn'5d'2a >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "gdl_regexpr_4_nested" = (((parseRules "regexpr_rules")) <|> ((pDetectChar False '<' >>= withAttribute OtherTok) >>~ pushContext "gdl_regexpr_4_nested") <|> ((pDetectChar False '>' >>= withAttribute OtherTok) >>~ (popContext))) parseRules "gdl_regexpr_5" = (((parseRules "regexpr_rules")) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute OtherTok)) <|> ((pRegExprDynamic "\\s*%1[uiomxn]*" >>= withAttribute OtherTok) >>~ (popContext >> popContext))) parseRules "regexpr_rules" = (((pDetect2Chars False '\\' '\\' >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute OtherTok) >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute OtherTok) >>~ pushContext "Subst")) parseRules "DATA" = pzero parseRules "" = parseRules "Normal" parseRules x = fail $ "Unknown context" ++ x