{- This module was generated from data in the Kate syntax highlighting file ruby.xml, version 1.18, by Stefan Lang (langstefan@gmx.at), Sebastian Vuorinen (sebastian.vuorinen@helsinki.fi), Robin Pedersen (robinpeder@gmail.com) -} module Text.Highlighting.Kate.Syntax.Ruby ( highlight, parseExpression, syntaxName, syntaxExtensions ) where import Text.Highlighting.Kate.Definitions import Text.Highlighting.Kate.Common import Text.ParserCombinators.Parsec import Control.Monad (when) import Data.Map (fromList) import Data.Maybe (fromMaybe, maybeToList) 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" -- | Highlight source code using this syntax definition. highlight :: String -> Either String [SourceLine] highlight input = case runParser parseSource startingState "source" input of Left err -> Left $ show err Right result -> Right result -- | Parse an expression using appropriate local context. parseExpression :: GenParser Char SyntaxState LabeledSource parseExpression = do st <- getState let oldLang = synStLanguage st setState $ st { synStLanguage = "Ruby" } context <- currentContext <|> (pushContext "Normal" >> currentContext) result <- parseRules context updateState $ \st -> st { synStLanguage = oldLang } return result parseSource = do lineContents <- lookAhead wholeLine updateState $ \st -> st { synStCurrentLine = lineContents } result <- manyTill parseSourceLine eof return $ map normalizeHighlighting result startingState = SyntaxState {synStContexts = fromList [("Ruby",["Normal"])], synStLanguage = "Ruby", synStCurrentLine = "", synStCharsParsedInLine = 0, synStPrevChar = '\n', synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} parseSourceLine = manyTill parseExpressionInternal pEndLine pEndLine = do lookAhead $ newline <|> (eof >> return '\n') context <- currentContext case context of "Normal" -> return () >> pHandleEndLine "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 () >> pHandleEndLine "Quoted String" -> return () >> pHandleEndLine "Apostrophed String" -> return () >> pHandleEndLine "Command String" -> return () >> pHandleEndLine "Embedded documentation" -> return () >> pHandleEndLine "RegEx 1" -> return () >> pHandleEndLine "Subst" -> return () >> pHandleEndLine "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 () >> pHandleEndLine "apostrophed_indented_heredoc" -> return () >> pHandleEndLine "normal_heredoc" -> return () >> pHandleEndLine "apostrophed_normal_heredoc" -> return () >> pHandleEndLine "heredoc_rules" -> return () >> pHandleEndLine "find_gdl_input" -> (popContext) >> pEndLine "gdl_dq_string_1" -> return () >> pHandleEndLine "gdl_dq_string_1_nested" -> return () >> pHandleEndLine "gdl_dq_string_2" -> return () >> pHandleEndLine "gdl_dq_string_2_nested" -> return () >> pHandleEndLine "gdl_dq_string_3" -> return () >> pHandleEndLine "gdl_dq_string_3_nested" -> return () >> pHandleEndLine "gdl_dq_string_4" -> return () >> pHandleEndLine "gdl_dq_string_4_nested" -> return () >> pHandleEndLine "gdl_dq_string_5" -> return () >> pHandleEndLine "dq_string_rules" -> return () >> pHandleEndLine "gdl_token_array_1" -> return () >> pHandleEndLine "gdl_token_array_1_nested" -> return () >> pHandleEndLine "gdl_token_array_2" -> return () >> pHandleEndLine "gdl_token_array_2_nested" -> return () >> pHandleEndLine "gdl_token_array_3" -> return () >> pHandleEndLine "gdl_token_array_3_nested" -> return () >> pHandleEndLine "gdl_token_array_4" -> return () >> pHandleEndLine "gdl_token_array_4_nested" -> return () >> pHandleEndLine "gdl_token_array_5" -> return () >> pHandleEndLine "token_array_rules" -> return () >> pHandleEndLine "gdl_apostrophed_1" -> return () >> pHandleEndLine "gdl_apostrophed_1_nested" -> return () >> pHandleEndLine "gdl_apostrophed_2" -> return () >> pHandleEndLine "gdl_apostrophed_2_nested" -> return () >> pHandleEndLine "gdl_apostrophed_3" -> return () >> pHandleEndLine "gdl_apostrophed_3_nested" -> return () >> pHandleEndLine "gdl_apostrophed_4" -> return () >> pHandleEndLine "gdl_apostrophed_4_nested" -> return () >> pHandleEndLine "gdl_apostrophed_5" -> return () >> pHandleEndLine "apostrophed_rules" -> return () >> pHandleEndLine "gdl_shell_command_1" -> return () >> pHandleEndLine "gdl_shell_command_1_nested" -> return () >> pHandleEndLine "gdl_shell_command_2" -> return () >> pHandleEndLine "gdl_shell_command_2_nested" -> return () >> pHandleEndLine "gdl_shell_command_3" -> return () >> pHandleEndLine "gdl_shell_command_3_nested" -> return () >> pHandleEndLine "gdl_shell_command_4" -> return () >> pHandleEndLine "gdl_shell_command_4_nested" -> return () >> pHandleEndLine "gdl_shell_command_5" -> return () >> pHandleEndLine "shell_command_rules" -> return () >> pHandleEndLine "gdl_regexpr_1" -> return () >> pHandleEndLine "gdl_regexpr_1_nested" -> return () >> pHandleEndLine "gdl_regexpr_2" -> return () >> pHandleEndLine "gdl_regexpr_2_nested" -> return () >> pHandleEndLine "gdl_regexpr_3" -> return () >> pHandleEndLine "gdl_regexpr_3_nested" -> return () >> pHandleEndLine "gdl_regexpr_4" -> return () >> pHandleEndLine "gdl_regexpr_4_nested" -> return () >> pHandleEndLine "gdl_regexpr_5" -> return () >> pHandleEndLine "regexpr_rules" -> return () >> pHandleEndLine "DATA" -> return () >> pHandleEndLine _ -> pHandleEndLine withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" let labs = attr : maybeToList (lookup attr styles) st <- getState let oldCharsParsed = synStCharsParsedInLine st let prevchar = if null txt then '\n' else last txt updateState $ \st -> st { synStCharsParsedInLine = oldCharsParsed + length txt, synStPrevChar = prevchar } return (labs, txt) styles = [("Keyword","kw"),("Attribute Definition","ot"),("Access Control","kw"),("Definition","kw"),("Pseudo variable","dv"),("Dec","dv"),("Float","fl"),("Char","ch"),("Octal","bn"),("Hex","bn"),("Bin","bn"),("Symbol","st"),("String","st"),("Raw String","st"),("Command","st"),("Regular Expression","ot"),("Substitution","ot"),("GDL input","ot"),("Default globals","dt"),("Global Variable","dt"),("Global Constant","dt"),("Constant","dt"),("Constant Value","dt"),("Instance Variable","ot"),("Class Variable","ot"),("Comment","co"),("Blockcomment","co"),("RDoc Value","ot"),("Here Document","ot"),("Error","er"),("Alert","al"),("Expression","ot")] parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ 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 while 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 scan select set_trace_func sleep split sprintf srand sub sub! syscall system test throw trace_var trap untrace_var warn" list_attention = Set.fromList $ words $ "TODO FIXME NOTE" 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'5bQqxw'5d'3f'5b'5e'5cs'5d'29 = compileRegex "\\s*[%](?=[Qqxw]?[^\\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_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","Normal Text"),("check_div_1","Normal Text"),("check_div_1_pop","Normal Text"),("check_div_2","Normal Text"),("check_div_2_internal","Normal Text"),("check_div_2_pop","Normal Text"),("check_div_2_pop_internal","Normal Text"),("Line Continue","Normal Text"),("Find closing block brace","Normal Text"),("Quoted String","String"),("Apostrophed String","Raw String"),("Command String","Command"),("Embedded documentation","Blockcomment"),("RegEx 1","Regular Expression"),("Subst","Normal Text"),("Short Subst","Substitution"),("Member Access","Member"),("Comment Line","Comment"),("General Comment","Comment"),("RDoc Label","RDoc Value"),("find_heredoc","Normal Text"),("find_indented_heredoc","Normal Text"),("indented_heredoc","Here Document"),("apostrophed_indented_heredoc","Here Document"),("normal_heredoc","Here Document"),("apostrophed_normal_heredoc","Here Document"),("heredoc_rules","Normal Text"),("find_gdl_input","Normal Text"),("gdl_dq_string_1","String"),("gdl_dq_string_1_nested","String"),("gdl_dq_string_2","String"),("gdl_dq_string_2_nested","String"),("gdl_dq_string_3","String"),("gdl_dq_string_3_nested","String"),("gdl_dq_string_4","String"),("gdl_dq_string_4_nested","String"),("gdl_dq_string_5","String"),("dq_string_rules","String"),("gdl_token_array_1","String"),("gdl_token_array_1_nested","String"),("gdl_token_array_2","String"),("gdl_token_array_2_nested","String"),("gdl_token_array_3","String"),("gdl_token_array_3_nested","String"),("gdl_token_array_4","String"),("gdl_token_array_4_nested","String"),("gdl_token_array_5","String"),("token_array_rules","String"),("gdl_apostrophed_1","Raw String"),("gdl_apostrophed_1_nested","Raw String"),("gdl_apostrophed_2","Raw String"),("gdl_apostrophed_2_nested","Raw String"),("gdl_apostrophed_3","Raw String"),("gdl_apostrophed_3_nested","Raw String"),("gdl_apostrophed_4","Raw String"),("gdl_apostrophed_4_nested","Raw String"),("gdl_apostrophed_5","Raw String"),("apostrophed_rules","Raw String"),("gdl_shell_command_1","Command"),("gdl_shell_command_1_nested","Command"),("gdl_shell_command_2","Command"),("gdl_shell_command_2_nested","Command"),("gdl_shell_command_3","Command"),("gdl_shell_command_3_nested","Command"),("gdl_shell_command_4","Command"),("gdl_shell_command_4_nested","Command"),("gdl_shell_command_5","Command"),("shell_command_rules","Command"),("gdl_regexpr_1","Regular Expression"),("gdl_regexpr_1_nested","Regular Expression"),("gdl_regexpr_2","Regular Expression"),("gdl_regexpr_2_nested","Regular Expression"),("gdl_regexpr_3","Regular Expression"),("gdl_regexpr_3_nested","Regular Expression"),("gdl_regexpr_4","Regular Expression"),("gdl_regexpr_4_nested","Regular Expression"),("gdl_regexpr_5","Regular Expression"),("regexpr_rules","Regular Expression"),("DATA","Data")] parseRules "Normal" = do (attr, result) <- (((pLineContinue >>= withAttribute "Normal Text") >>~ pushContext "Line Continue") <|> ((pColumn 0 >> pRegExpr regex_'5f'5fEND'5f'5f'24 >>= withAttribute "Keyword") >>~ pushContext "DATA") <|> ((pColumn 0 >> pRegExpr regex_'23'21'5c'2f'2e'2a >>= withAttribute "Keyword")) <|> ((pDetectChar False '{' >>= withAttribute "Operator") >>~ 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 "Keyword")) <|> ((pFirstNonSpace >> pRegExpr regex_'28while'7cuntil'29'5cb'28'3f'21'2e'2a'5cbdo'5cb'29 >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5c'3b'5cs'2a'28while'7cuntil'29'5cb'28'3f'21'2e'2a'5cbdo'5cb'29 >>= withAttribute "Keyword")) <|> ((pFirstNonSpace >> pRegExpr regex_'28if'7cunless'29'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5c'3b'5cs'2a'28if'7cunless'29'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cbclass'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cbmodule'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cbbegin'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cbfor'5cb'28'3f'21'2e'2a'5cbdo'5cb'29 >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cbcase'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cbdo'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cbdef'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cbend'5cb >>= withAttribute "Keyword")) <|> ((pRegExpr regex_'5cb'28else'7celsif'7crescue'7censure'29'5cb >>= withAttribute "Keyword")) <|> ((pString False "..." >>= withAttribute "Operator")) <|> ((pDetect2Chars False '.' '.' >>= withAttribute "Operator")) <|> ((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 "Message") >>~ 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 "Dec") >>~ pushContext "check_div_1") <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_keywords >>= withAttribute "Keyword")) <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_attribute'2ddefinitions >>= withAttribute "Attribute Definition") >>~ pushContext "check_div_2") <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_access'2dcontrol >>= withAttribute "Access Control") >>~ pushContext "check_div_2") <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_definitions >>= withAttribute "Definition")) <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_pseudo'2dvariables >>= withAttribute "Pseudo variable") >>~ pushContext "check_div_1") <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_default'2dglobals >>= withAttribute "Default globals") >>~ pushContext "check_div_2") <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_kernel'2dmethods >>= withAttribute "Kernel methods") >>~ pushContext "check_div_2") <|> ((pRegExpr regex_'5c'24'5ba'2dzA'2dZ'5f0'2d9'5d'2b >>= withAttribute "Global Variable") >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5c'24'5c'2d'5ba'2dzA'2dz'5f'5d'5cb >>= withAttribute "Global Variable") >>~ 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 "Default globals") >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5cb'5b'5fA'2dZ'5d'2b'5bA'2dZ'5f0'2d9'5d'2b'5cb >>= withAttribute "Global Constant") >>~ 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 "Constant") >>~ pushContext "check_div_2") <|> ((pRegExpr regex_'5cb'5c'2d'3f0'5bxX'5d'5b'5f0'2d9a'2dfA'2dF'5d'2b >>= withAttribute "Hex") >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5cb'5c'2d'3f0'5bbB'5d'5b'5f01'5d'2b >>= withAttribute "Bin") >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5cb'5c'2d'3f0'5b1'2d7'5d'5b'5f0'2d7'5d'2a >>= withAttribute "Octal") >>~ 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 "Float") >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'5cb'5c'2d'3f'5b1'2d9'5d'5b0'2d9'5f'5d'2a'5cb >>= withAttribute "Dec") >>~ pushContext "check_div_1") <|> ((pInt >>= withAttribute "Dec") >>~ pushContext "check_div_1") <|> ((pHlCChar >>= withAttribute "Char") >>~ pushContext "check_div_1") <|> ((pColumn 0 >> pRegExpr regex_'3dbegin'28'3f'3a'5cs'7c'24'29 >>= withAttribute "Blockcomment") >>~ pushContext "Embedded documentation") <|> ((pRegExpr regex_'5cs'2a'3c'3c'2d'28'3f'3d'5cw'2b'7c'5b'22'27'5d'29 >>= withAttribute "Operator") >>~ pushContext "find_indented_heredoc") <|> ((pRegExpr regex_'5cs'2a'3c'3c'28'3f'3d'5cw'2b'7c'5b'22'27'5d'29 >>= withAttribute "Operator") >>~ pushContext "find_heredoc") <|> ((pDetectChar False '.' >>= withAttribute "Operator")) <|> ((pDetect2Chars False '&' '&' >>= withAttribute "Operator")) <|> ((pDetect2Chars False '|' '|' >>= withAttribute "Operator")) <|> ((pRegExpr regex_'5cs'5b'5c'3f'5c'3a'5c'25'5d'5cs >>= withAttribute "Operator")) <|> ((pRegExpr regex_'5b'7c'26'3c'3e'5c'5e'5c'2b'2a'7e'5c'2d'3d'5d'2b >>= withAttribute "Operator")) <|> ((pRegExpr regex_'5cs'21 >>= withAttribute "Operator")) <|> ((pRegExpr regex_'2f'3d'5cs >>= withAttribute "Operator")) <|> ((pString False "%=" >>= withAttribute "Operator")) <|> ((pDetect2Chars False ':' ':' >>= withAttribute "Operator") >>~ 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 "Symbol") >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'3a'5c'5b'5c'5d'3d'3f >>= withAttribute "Symbol")) <|> ((pDetectChar False '"' >>= withAttribute "String") >>~ pushContext "Quoted String") <|> ((pDetectChar False '\'' >>= withAttribute "Raw String") >>~ pushContext "Apostrophed String") <|> ((pDetectChar False '`' >>= withAttribute "Command") >>~ pushContext "Command String") <|> ((pString False "?#" >>= withAttribute "Normal Text")) <|> ((pColumn 0 >> pRegExpr regex_'23'5cs'2aBEGIN'2e'2a'24 >>= withAttribute "Comment")) <|> ((pColumn 0 >> pRegExpr regex_'23'5cs'2aEND'2e'2a'24 >>= withAttribute "Comment")) <|> ((pDetectChar False '#' >>= withAttribute "Comment") >>~ pushContext "General Comment") <|> ((pDetectChar False '[' >>= withAttribute "Delimiter")) <|> ((pDetectChar False ']' >>= withAttribute "Delimiter") >>~ pushContext "check_div_1") <|> ((pDetectChar False '{' >>= withAttribute "Delimiter")) <|> ((pDetectChar False '}' >>= withAttribute "Delimiter") >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'40'5ba'2dzA'2dZ'5f0'2d9'5d'2b >>= withAttribute "Instance Variable") >>~ pushContext "check_div_1") <|> ((pRegExpr regex_'40'40'5ba'2dzA'2dZ'5f0'2d9'5d'2b >>= withAttribute "Class Variable") >>~ pushContext "check_div_1") <|> ((pDetectChar False '/' >>= withAttribute "Regular Expression") >>~ pushContext "RegEx 1") <|> ((pRegExpr regex_'5cs'2a'5b'25'5d'28'3f'3d'5bQqxw'5d'3f'5b'5e'5cs'5d'29 >>= withAttribute "GDL input") >>~ pushContext "find_gdl_input") <|> ((pDetectChar False ')' >>= withAttribute "Normal Text") >>~ pushContext "check_div_1") <|> ((pDetectIdentifier >>= withAttribute "Normal Text") >>~ pushContext "check_div_2")) return (attr, result) parseRules "check_div_1" = do (attr, result) <- (((pRegExpr regex_'5cs'2a >>= withAttribute "Normal Text")) <|> ((pAnyChar "/%" >>= withAttribute "Operator") >>~ (popContext)) <|> ((popContext) >> return ([], ""))) return (attr, result) parseRules "check_div_1_pop" = do (attr, result) <- (((pRegExpr regex_'5cs'2a >>= withAttribute "Normal Text")) <|> ((pAnyChar "/%" >>= withAttribute "Operator") >>~ (popContext >> popContext)) <|> ((popContext >> popContext) >> return ([], ""))) return (attr, result) parseRules "check_div_2" = do (attr, result) <- (((pAnyChar "/%" >>= withAttribute "Operator") >>~ (popContext)) <|> ((pRegExpr regex_'5cs'2b >>= withAttribute "Normal Text") >>~ pushContext "check_div_2_internal") <|> ((popContext) >> return ([], ""))) return (attr, result) parseRules "check_div_2_internal" = do (attr, result) <- (((pRegExpr regex_'5b'2f'25'5d'28'3f'3d'5cs'29 >>= withAttribute "Operator") >>~ (popContext >> popContext)) <|> ((popContext >> popContext) >> return ([], ""))) return (attr, result) parseRules "check_div_2_pop" = do (attr, result) <- (((pAnyChar "/%" >>= withAttribute "Operator") >>~ (popContext >> popContext)) <|> ((pRegExpr regex_'5cs'2b >>= withAttribute "Normal Text") >>~ pushContext "check_div_2_pop_internal") <|> ((popContext >> popContext) >> return ([], ""))) return (attr, result) parseRules "check_div_2_pop_internal" = do (attr, result) <- (((pDetectChar False '%' >>= withAttribute "Operator") >>~ (popContext >> popContext >> popContext)) <|> ((pRegExpr regex_'2f'28'3f'3d'5cs'29 >>= withAttribute "Operator") >>~ (popContext >> popContext >> popContext)) <|> ((popContext >> popContext >> popContext) >> return ([], ""))) return (attr, result) parseRules "Line Continue" = do (attr, result) <- (((pFirstNonSpace >> pRegExpr regex_'28while'7cuntil'29'5cb'28'3f'21'2e'2a'5cbdo'5cb'29 >>= withAttribute "Keyword")) <|> ((pFirstNonSpace >> pRegExpr regex_'28if'7cunless'29'5cb >>= withAttribute "Keyword")) <|> ((parseRules "Normal"))) return (attr, result) parseRules "Find closing block brace" = do (attr, result) <- (((pDetectChar False '}' >>= withAttribute "Operator") >>~ pushContext "check_div_1_pop") <|> ((parseRules "Normal"))) return (attr, result) parseRules "Quoted String" = do (attr, result) <- (((pString False "\\\\" >>= withAttribute "String")) <|> ((pRegExpr regex_'5c'5c'5c'22 >>= withAttribute "String")) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute "Substitution") >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute "Substitution") >>~ pushContext "Subst") <|> ((pDetectChar False '"' >>= withAttribute "String") >>~ pushContext "check_div_1_pop")) return (attr, result) parseRules "Apostrophed String" = do (attr, result) <- (((pString False "\\\\" >>= withAttribute "String")) <|> ((pRegExpr regex_'5c'5c'5c'27 >>= withAttribute "String")) <|> ((pDetectChar False '\'' >>= withAttribute "Raw String") >>~ pushContext "check_div_1_pop")) return (attr, result) parseRules "Command String" = do (attr, result) <- (((pString False "\\\\" >>= withAttribute "String")) <|> ((pRegExpr regex_'5c'5c'5c'60 >>= withAttribute "String")) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute "Substitution") >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute "Substitution") >>~ pushContext "Subst") <|> ((pDetectChar False '`' >>= withAttribute "Command") >>~ pushContext "check_div_1_pop")) return (attr, result) parseRules "Embedded documentation" = do (attr, result) <- ((pColumn 0 >> pRegExpr regex_'3dend'28'3f'3a'5cs'2e'2a'7c'24'29 >>= withAttribute "Comment") >>~ (popContext)) return (attr, result) parseRules "RegEx 1" = do (attr, result) <- (((pRegExpr regex_'5c'5c'5c'2f >>= withAttribute "Regular Expression")) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute "Substitution") >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute "Substitution") >>~ pushContext "Subst") <|> ((pRegExpr regex_'2f'5buiomxn'5d'2a >>= withAttribute "Regular Expression") >>~ pushContext "check_div_1_pop")) return (attr, result) parseRules "Subst" = do (attr, result) <- (((pDetectChar False '}' >>= withAttribute "Substitution") >>~ (popContext)) <|> ((parseRules "Normal"))) return (attr, result) parseRules "Short Subst" = do (attr, result) <- (((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute "Substitution")) <|> ((pRegExpr regex_'5cw'28'3f'21'5cw'29 >>= withAttribute "Substitution") >>~ (popContext))) return (attr, result) parseRules "Member Access" = do (attr, result) <- (((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 "Message") >>~ 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 "Message")) <|> ((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 "Constant") >>~ 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 "Constant")) <|> ((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 "Constant Value") >>~ pushContext "check_div_2_pop") <|> ((pRegExpr regex_'5b'5fA'2dZ'5d'5b'5fA'2dZ0'2d9'5d'2a >>= withAttribute "Constant Value")) <|> ((pDetect2Chars False ':' ':' >>= withAttribute "Operator")) <|> ((pDetectChar False '.' >>= withAttribute "Member")) <|> ((pAnyChar "=+-*/%|&[]{}~" >>= withAttribute "Operator") >>~ (popContext)) <|> ((pDetectChar False '#' >>= withAttribute "Comment") >>~ (popContext)) <|> ((pAnyChar "()\\" >>= withAttribute "Normal Text") >>~ (popContext)) <|> ((pRegExpr regex_'5cW >>= withAttribute "Member") >>~ (popContext))) return (attr, result) parseRules "Comment Line" = do (attr, result) <- (((pRegExpr regex_'5cw'5c'3a'5c'3a'5cs >>= withAttribute "Comment") >>~ pushContext "RDoc Label") <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_attention >>= withAttribute "Alert"))) return (attr, result) parseRules "General Comment" = do (attr, result) <- ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_attention >>= withAttribute "Dec")) return (attr, result) parseRules "RDoc Label" = pzero parseRules "find_heredoc" = do (attr, result) <- (((pRegExpr regex_'27'28'5cw'2b'29'27 >>= withAttribute "Keyword") >>~ pushContext "apostrophed_normal_heredoc") <|> ((pRegExpr regex_'22'3f'28'5cw'2b'29'22'3f >>= withAttribute "Keyword") >>~ pushContext "normal_heredoc")) return (attr, result) parseRules "find_indented_heredoc" = do (attr, result) <- (((pRegExpr regex_'27'28'5cw'2b'29'27 >>= withAttribute "Keyword") >>~ pushContext "apostrophed_indented_heredoc") <|> ((pRegExpr regex_'22'3f'28'5cw'2b'29'22'3f >>= withAttribute "Keyword") >>~ pushContext "indented_heredoc")) return (attr, result) parseRules "indented_heredoc" = do (attr, result) <- (((pFirstNonSpace >> pRegExprDynamic "%1$" >>= withAttribute "Keyword") >>~ (popContext >> popContext)) <|> ((parseRules "heredoc_rules"))) return (attr, result) parseRules "apostrophed_indented_heredoc" = do (attr, result) <- ((pFirstNonSpace >> pRegExprDynamic "%1$" >>= withAttribute "Keyword") >>~ (popContext >> popContext)) return (attr, result) parseRules "normal_heredoc" = do (attr, result) <- (((pColumn 0 >> pRegExprDynamic "%1$" >>= withAttribute "Keyword") >>~ (popContext >> popContext)) <|> ((parseRules "heredoc_rules"))) return (attr, result) parseRules "apostrophed_normal_heredoc" = do (attr, result) <- ((pColumn 0 >> pRegExprDynamic "%1$" >>= withAttribute "Keyword") >>~ (popContext >> popContext)) return (attr, result) parseRules "heredoc_rules" = do (attr, result) <- (((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute "Substitution") >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute "Substitution") >>~ pushContext "Subst")) return (attr, result) parseRules "find_gdl_input" = do (attr, result) <- (((pRegExpr regex_w'5c'28 >>= withAttribute "GDL input") >>~ pushContext "gdl_token_array_1") <|> ((pRegExpr regex_w'5c'7b >>= withAttribute "GDL input") >>~ pushContext "gdl_token_array_2") <|> ((pRegExpr regex_w'5c'5b >>= withAttribute "GDL input") >>~ pushContext "gdl_token_array_3") <|> ((pRegExpr regex_w'3c >>= withAttribute "GDL input") >>~ pushContext "gdl_token_array_4") <|> ((pRegExpr regex_w'28'5b'5e'5cs'5cw'5d'29 >>= withAttribute "GDL input") >>~ pushContext "gdl_token_array_5") <|> ((pRegExpr regex_q'5c'28 >>= withAttribute "GDL input") >>~ pushContext "gdl_apostrophed_1") <|> ((pRegExpr regex_q'5c'7b >>= withAttribute "GDL input") >>~ pushContext "gdl_apostrophed_2") <|> ((pRegExpr regex_q'5c'5b >>= withAttribute "GDL input") >>~ pushContext "gdl_apostrophed_3") <|> ((pRegExpr regex_q'3c >>= withAttribute "GDL input") >>~ pushContext "gdl_apostrophed_4") <|> ((pRegExpr regex_q'28'5b'5e'5cs'5cw'5d'29 >>= withAttribute "GDL input") >>~ pushContext "gdl_apostrophed_5") <|> ((pRegExpr regex_x'5c'28 >>= withAttribute "GDL input") >>~ pushContext "gdl_shell_command_1") <|> ((pRegExpr regex_x'5c'7b >>= withAttribute "GDL input") >>~ pushContext "gdl_shell_command_2") <|> ((pRegExpr regex_x'5c'5b >>= withAttribute "GDL input") >>~ pushContext "gdl_shell_command_3") <|> ((pRegExpr regex_x'3c >>= withAttribute "GDL input") >>~ pushContext "gdl_shell_command_4") <|> ((pRegExpr regex_x'28'5b'5e'5cs'5cw'5d'29 >>= withAttribute "GDL input") >>~ pushContext "gdl_shell_command_5") <|> ((pRegExpr regex_r'5c'28 >>= withAttribute "GDL input") >>~ pushContext "gdl_regexpr_1") <|> ((pRegExpr regex_r'5c'7b >>= withAttribute "GDL input") >>~ pushContext "gdl_regexpr_2") <|> ((pRegExpr regex_r'5c'5b >>= withAttribute "GDL input") >>~ pushContext "gdl_regexpr_3") <|> ((pRegExpr regex_r'3c >>= withAttribute "GDL input") >>~ pushContext "gdl_regexpr_4") <|> ((pRegExpr regex_r'28'5b'5e'5cs'5cw'5d'29 >>= withAttribute "GDL input") >>~ pushContext "gdl_regexpr_5") <|> ((pRegExpr regex_Q'3f'5c'28 >>= withAttribute "GDL input") >>~ pushContext "gdl_dq_string_1") <|> ((pRegExpr regex_Q'3f'5c'7b >>= withAttribute "GDL input") >>~ pushContext "gdl_dq_string_2") <|> ((pRegExpr regex_Q'3f'5c'5b >>= withAttribute "GDL input") >>~ pushContext "gdl_dq_string_3") <|> ((pRegExpr regex_Q'3f'3c >>= withAttribute "GDL input") >>~ pushContext "gdl_dq_string_4") <|> ((pRegExpr regex_Q'3f'28'5b'5e'5cs'5cw'5d'29 >>= withAttribute "GDL input") >>~ pushContext "gdl_dq_string_5")) return (attr, result) parseRules "gdl_dq_string_1" = do (attr, result) <- (((parseRules "dq_string_rules")) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute "String")) <|> ((pDetectChar False '(' >>= withAttribute "String") >>~ pushContext "gdl_dq_string_1_nested") <|> ((pDetectChar False ')' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_dq_string_1_nested" = do (attr, result) <- (((parseRules "dq_string_rules")) <|> ((pDetectChar False '(' >>= withAttribute "String") >>~ pushContext "gdl_dq_string_1_nested") <|> ((pDetectChar False ')' >>= withAttribute "String") >>~ (popContext))) return (attr, result) parseRules "gdl_dq_string_2" = do (attr, result) <- (((parseRules "dq_string_rules")) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute "String")) <|> ((pDetectChar False '}' >>= withAttribute "GDL input") >>~ (popContext >> popContext)) <|> ((pDetectChar False '{' >>= withAttribute "String") >>~ pushContext "gdl_dq_string_2_nested")) return (attr, result) parseRules "gdl_dq_string_2_nested" = do (attr, result) <- (((pDetectChar False '{' >>= withAttribute "String") >>~ pushContext "gdl_dq_string_2_nested") <|> ((pDetectChar False '}' >>= withAttribute "String") >>~ (popContext)) <|> ((parseRules "dq_string_rules"))) return (attr, result) parseRules "gdl_dq_string_3" = do (attr, result) <- (((parseRules "dq_string_rules")) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute "String")) <|> ((pDetectChar False '[' >>= withAttribute "String") >>~ pushContext "gdl_dq_string_3_nested") <|> ((pDetectChar False ']' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_dq_string_3_nested" = do (attr, result) <- (((pDetectChar False '[' >>= withAttribute "String") >>~ pushContext "gdl_dq_string_3_nested") <|> ((pDetectChar False ']' >>= withAttribute "String") >>~ (popContext)) <|> ((parseRules "dq_string_rules"))) return (attr, result) parseRules "gdl_dq_string_4" = do (attr, result) <- (((parseRules "dq_string_rules")) <|> ((pDetect2Chars False '\\' '>' >>= withAttribute "String")) <|> ((pDetectChar False '<' >>= withAttribute "String") >>~ pushContext "gdl_dq_string_4_nested") <|> ((pDetectChar False '>' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_dq_string_4_nested" = do (attr, result) <- (((pDetectChar False '<' >>= withAttribute "String") >>~ pushContext "gdl_dq_string_4_nested") <|> ((pDetectChar False '>' >>= withAttribute "String") >>~ (popContext)) <|> ((parseRules "dq_string_rules"))) return (attr, result) parseRules "gdl_dq_string_5" = do (attr, result) <- (((parseRules "dq_string_rules")) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute "String")) <|> ((pRegExprDynamic "\\s*%1" >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "dq_string_rules" = do (attr, result) <- (((pDetect2Chars False '\\' '\\' >>= withAttribute "String")) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute "Substitution") >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute "Substitution") >>~ pushContext "Subst")) return (attr, result) parseRules "gdl_token_array_1" = do (attr, result) <- (((parseRules "token_array_rules")) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute "String")) <|> ((pDetectChar False '(' >>= withAttribute "String") >>~ pushContext "gdl_token_array_1_nested") <|> ((pDetectChar False ')' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_token_array_1_nested" = do (attr, result) <- (((parseRules "token_array_rules")) <|> ((pDetectChar False '(' >>= withAttribute "String") >>~ pushContext "gdl_token_array_1_nested") <|> ((pDetectChar False ')' >>= withAttribute "String") >>~ (popContext))) return (attr, result) parseRules "gdl_token_array_2" = do (attr, result) <- (((parseRules "token_array_rules")) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute "String")) <|> ((pDetectChar False '}' >>= withAttribute "GDL input") >>~ (popContext >> popContext)) <|> ((pDetectChar False '{' >>= withAttribute "String") >>~ pushContext "gdl_token_array_2_nested")) return (attr, result) parseRules "gdl_token_array_2_nested" = do (attr, result) <- (((parseRules "token_array_rules")) <|> ((pDetectChar False '{' >>= withAttribute "String") >>~ pushContext "gdl_token_array_2_nested") <|> ((pDetectChar False '}' >>= withAttribute "String") >>~ (popContext))) return (attr, result) parseRules "gdl_token_array_3" = do (attr, result) <- (((parseRules "token_array_rules")) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute "String")) <|> ((pDetectChar False '[' >>= withAttribute "String") >>~ pushContext "gdl_token_array_3_nested") <|> ((pDetectChar False ']' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_token_array_3_nested" = do (attr, result) <- (((parseRules "token_array_rules")) <|> ((pDetectChar False '[' >>= withAttribute "String") >>~ pushContext "gdl_token_array_3_nested") <|> ((pDetectChar False ']' >>= withAttribute "String") >>~ (popContext))) return (attr, result) parseRules "gdl_token_array_4" = do (attr, result) <- (((parseRules "token_array_rules")) <|> ((pDetect2Chars False '\\' '>' >>= withAttribute "String")) <|> ((pDetectChar False '<' >>= withAttribute "String") >>~ pushContext "gdl_token_array_4_nested") <|> ((pDetectChar False '>' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_token_array_4_nested" = do (attr, result) <- (((parseRules "token_array_rules")) <|> ((pDetectChar False '<' >>= withAttribute "String") >>~ pushContext "gdl_token_array_4_nested") <|> ((pDetectChar False '>' >>= withAttribute "String") >>~ (popContext))) return (attr, result) parseRules "gdl_token_array_5" = do (attr, result) <- (((parseRules "token_array_rules")) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute "String")) <|> ((pRegExprDynamic "\\s*%1" >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "token_array_rules" = do (attr, result) <- ((pString False "\\\\" >>= withAttribute "String")) return (attr, result) parseRules "gdl_apostrophed_1" = do (attr, result) <- (((parseRules "apostrophed_rules")) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute "Raw String")) <|> ((pDetectChar False '(' >>= withAttribute "Raw String") >>~ pushContext "gdl_apostrophed_1_nested") <|> ((pDetectChar False ')' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_apostrophed_1_nested" = do (attr, result) <- (((parseRules "apostrophed_rules")) <|> ((pDetectChar False '(' >>= withAttribute "Raw String") >>~ pushContext "gdl_apostrophed_1_nested") <|> ((pDetectChar False ')' >>= withAttribute "Raw String") >>~ (popContext))) return (attr, result) parseRules "gdl_apostrophed_2" = do (attr, result) <- (((parseRules "apostrophed_rules")) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute "Raw String")) <|> ((pDetectChar False '}' >>= withAttribute "GDL input") >>~ (popContext >> popContext)) <|> ((pDetectChar False '{' >>= withAttribute "Raw String") >>~ pushContext "gdl_apostrophed_2_nested")) return (attr, result) parseRules "gdl_apostrophed_2_nested" = do (attr, result) <- (((parseRules "apostrophed_rules")) <|> ((pDetectChar False '{' >>= withAttribute "Raw String") >>~ pushContext "gdl_apostrophed_2_nested") <|> ((pDetectChar False '}' >>= withAttribute "Raw String") >>~ (popContext))) return (attr, result) parseRules "gdl_apostrophed_3" = do (attr, result) <- (((parseRules "apostrophed_rules")) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute "Raw String")) <|> ((pDetectChar False '[' >>= withAttribute "Raw String") >>~ pushContext "gdl_apostrophed_3_nested") <|> ((pDetectChar False ']' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_apostrophed_3_nested" = do (attr, result) <- (((parseRules "apostrophed_rules")) <|> ((pDetectChar False '[' >>= withAttribute "Raw String") >>~ pushContext "gdl_apostrophed_3_nested") <|> ((pDetectChar False ']' >>= withAttribute "Raw String") >>~ (popContext))) return (attr, result) parseRules "gdl_apostrophed_4" = do (attr, result) <- (((parseRules "apostrophed_rules")) <|> ((pDetect2Chars False '\\' '>' >>= withAttribute "Raw String")) <|> ((pDetectChar False '<' >>= withAttribute "Raw String") >>~ pushContext "gdl_apostrophed_4_nested") <|> ((pDetectChar False '>' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_apostrophed_4_nested" = do (attr, result) <- (((parseRules "apostrophed_rules")) <|> ((pDetectChar False '<' >>= withAttribute "Raw String") >>~ pushContext "gdl_apostrophed_4_nested") <|> ((pDetectChar False '>' >>= withAttribute "Raw String") >>~ (popContext))) return (attr, result) parseRules "gdl_apostrophed_5" = do (attr, result) <- (((parseRules "apostrophed_rules")) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute "Raw String")) <|> ((pRegExprDynamic "\\s*%1" >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "apostrophed_rules" = do (attr, result) <- ((pDetect2Chars False '\\' '\\' >>= withAttribute "Raw String")) return (attr, result) parseRules "gdl_shell_command_1" = do (attr, result) <- (((parseRules "shell_command_rules")) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute "Command")) <|> ((pDetectChar False '(' >>= withAttribute "Command") >>~ pushContext "gdl_shell_command_1_nested") <|> ((pDetectChar False ')' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_shell_command_1_nested" = do (attr, result) <- (((parseRules "shell_command_rules")) <|> ((pDetectChar False '(' >>= withAttribute "Command") >>~ pushContext "gdl_shell_command_1_nested") <|> ((pDetectChar False ')' >>= withAttribute "Command") >>~ (popContext))) return (attr, result) parseRules "gdl_shell_command_2" = do (attr, result) <- (((parseRules "shell_command_rules")) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute "Command")) <|> ((pDetectChar False '}' >>= withAttribute "GDL input") >>~ (popContext >> popContext)) <|> ((pDetectChar False '{' >>= withAttribute "Command") >>~ pushContext "gdl_shell_command_2_nested")) return (attr, result) parseRules "gdl_shell_command_2_nested" = do (attr, result) <- (((parseRules "shell_command_rules")) <|> ((pDetectChar False '{' >>= withAttribute "Command") >>~ pushContext "gdl_shell_command_2_nested") <|> ((pDetectChar False '}' >>= withAttribute "Command") >>~ (popContext))) return (attr, result) parseRules "gdl_shell_command_3" = do (attr, result) <- (((parseRules "shell_command_rules")) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute "Command")) <|> ((pDetectChar False '[' >>= withAttribute "Command") >>~ pushContext "gdl_shell_command_3_nested") <|> ((pDetectChar False ']' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_shell_command_3_nested" = do (attr, result) <- (((parseRules "shell_command_rules")) <|> ((pDetectChar False '[' >>= withAttribute "Command") >>~ pushContext "gdl_shell_command_3_nested") <|> ((pDetectChar False ']' >>= withAttribute "Command") >>~ (popContext))) return (attr, result) parseRules "gdl_shell_command_4" = do (attr, result) <- (((parseRules "shell_command_rules")) <|> ((pDetect2Chars False '\\' '>' >>= withAttribute "Command")) <|> ((pDetectChar False '<' >>= withAttribute "Command") >>~ pushContext "gdl_shell_command_4_nested") <|> ((pDetectChar False '>' >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_shell_command_4_nested" = do (attr, result) <- (((parseRules "shell_command_rules")) <|> ((pDetectChar False '<' >>= withAttribute "Command") >>~ pushContext "gdl_shell_command_4_nested") <|> ((pDetectChar False '>' >>= withAttribute "Command") >>~ (popContext))) return (attr, result) parseRules "gdl_shell_command_5" = do (attr, result) <- (((parseRules "shell_command_rules")) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute "Command")) <|> ((pRegExprDynamic "\\s*%1" >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "shell_command_rules" = do (attr, result) <- (((pDetect2Chars False '\\' '\\' >>= withAttribute "Command")) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute "Substitution") >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute "Substitution") >>~ pushContext "Subst")) return (attr, result) parseRules "gdl_regexpr_1" = do (attr, result) <- (((parseRules "regexpr_rules")) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute "Regular Expression")) <|> ((pDetectChar False '(' >>= withAttribute "Regular Expression") >>~ pushContext "gdl_regexpr_1_nested") <|> ((pRegExpr regex_'5c'29'5buiomxn'5d'2a >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_regexpr_1_nested" = do (attr, result) <- (((parseRules "regexpr_rules")) <|> ((pDetectChar False '(' >>= withAttribute "Regular Expression") >>~ pushContext "gdl_regexpr_1_nested") <|> ((pDetectChar False ')' >>= withAttribute "Regular Expression") >>~ (popContext))) return (attr, result) parseRules "gdl_regexpr_2" = do (attr, result) <- (((parseRules "regexpr_rules")) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute "Regular Expression")) <|> ((pRegExpr regex_'5c'7d'5buiomxn'5d'2a >>= withAttribute "GDL input") >>~ (popContext >> popContext)) <|> ((pDetectChar False '{' >>= withAttribute "Regular Expression") >>~ pushContext "gdl_regexpr_2_nested")) return (attr, result) parseRules "gdl_regexpr_2_nested" = do (attr, result) <- (((parseRules "regexpr_rules")) <|> ((pDetectChar False '{' >>= withAttribute "Regular Expression") >>~ pushContext "gdl_regexpr_2_nested") <|> ((pDetectChar False '}' >>= withAttribute "Regular Expression") >>~ (popContext))) return (attr, result) parseRules "gdl_regexpr_3" = do (attr, result) <- (((parseRules "regexpr_rules")) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute "Regular Expression")) <|> ((pDetectChar False '[' >>= withAttribute "Regular Expression") >>~ pushContext "gdl_regexpr_3_nested") <|> ((pRegExpr regex_'5c'5d'5buiomxn'5d'2a >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_regexpr_3_nested" = do (attr, result) <- (((parseRules "regexpr_rules")) <|> ((pDetectChar False '[' >>= withAttribute "Regular Expression") >>~ pushContext "gdl_regexpr_3_nested") <|> ((pDetectChar False ']' >>= withAttribute "Regular Expression") >>~ (popContext))) return (attr, result) parseRules "gdl_regexpr_4" = do (attr, result) <- (((parseRules "regexpr_rules")) <|> ((pDetect2Chars False '\\' '>' >>= withAttribute "Regular Expression")) <|> ((pDetectChar False '<' >>= withAttribute "Regular Expression") >>~ pushContext "gdl_regexpr_4_nested") <|> ((pRegExpr regex_'3e'5buiomxn'5d'2a >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "gdl_regexpr_4_nested" = do (attr, result) <- (((parseRules "regexpr_rules")) <|> ((pDetectChar False '<' >>= withAttribute "Regular Expression") >>~ pushContext "gdl_regexpr_4_nested") <|> ((pDetectChar False '>' >>= withAttribute "Regular Expression") >>~ (popContext))) return (attr, result) parseRules "gdl_regexpr_5" = do (attr, result) <- (((parseRules "regexpr_rules")) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute "Regular Expression")) <|> ((pRegExprDynamic "\\s*%1[uiomxn]*" >>= withAttribute "GDL input") >>~ (popContext >> popContext))) return (attr, result) parseRules "regexpr_rules" = do (attr, result) <- (((pDetect2Chars False '\\' '\\' >>= withAttribute "Regular Expression")) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute "Substitution") >>~ pushContext "Short Subst") <|> ((pDetect2Chars False '#' '{' >>= withAttribute "Substitution") >>~ pushContext "Subst")) return (attr, result) parseRules "DATA" = pzero parseRules x = fail $ "Unknown context" ++ x