{- This module was generated from data in the Kate syntax highlighting file rhtml.xml, version 1.01, by Richard Dale rdale@foton.es -} module Text.Highlighting.Kate.Syntax.Rhtml ( highlight, parseExpression, syntaxName, syntaxExtensions ) where import Text.Highlighting.Kate.Definitions import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Alert import qualified Text.Highlighting.Kate.Syntax.Css import qualified Text.Highlighting.Kate.Syntax.Javascript 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/Rails/RHTML" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.rhtml;*.html.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/Rails/RHTML" } context <- currentContext <|> (pushContext "Start" >> 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/Rails/RHTML",["Start"])], synStLanguage = "Ruby/Rails/RHTML", 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 "Start" -> return () >> pHandleEndLine "FindHTML" -> return () >> pHandleEndLine "FindEntityRefs" -> return () >> pHandleEndLine "FindPEntityRefs" -> return () >> pHandleEndLine "FindAttributes" -> return () >> pHandleEndLine "FindDTDRules" -> return () >> pHandleEndLine "Comment" -> return () >> pHandleEndLine "CDATA" -> return () >> pHandleEndLine "PI" -> return () >> pHandleEndLine "Doctype" -> return () >> pHandleEndLine "Doctype Internal Subset" -> return () >> pHandleEndLine "Doctype Markupdecl" -> return () >> pHandleEndLine "Doctype Markupdecl DQ" -> return () >> pHandleEndLine "Doctype Markupdecl SQ" -> return () >> pHandleEndLine "El Open" -> return () >> pHandleEndLine "El Close" -> return () >> pHandleEndLine "El Close 2" -> return () >> pHandleEndLine "El Close 3" -> return () >> pHandleEndLine "CSS" -> return () >> pHandleEndLine "CSS content" -> return () >> pHandleEndLine "JS" -> return () >> pHandleEndLine "JS content" -> return () >> pHandleEndLine "JS comment close" -> (popContext) >> pEndLine "Value" -> return () >> pHandleEndLine "Value NQ" -> (popContext >> popContext) >> pEndLine "Value DQ" -> return () >> pHandleEndLine "Value SQ" -> return () >> pHandleEndLine "rubysourceline" -> (popContext) >> pEndLine "rubysource" -> return () >> pHandleEndLine "Line Continue" -> (popContext) >> pEndLine "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"),("Ruby Comment","co"),("Blockcomment","co"),("RDoc Value","ot"),("Error","er"),("Alert","al"),("Delimiter","ch"),("Expression","ot"),("Operator","ch"),("Comment","co"),("CDATA","bn"),("Processing Instruction","kw"),("Doctype","dt"),("Element","kw"),("Attribute","ot"),("Value","st"),("EntityRef","dv"),("PEntityRef","dv"),("Error","er")] 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 auto_complete_field auto_complete_result auto_discovery_link_tag auto_link benchmark button_to cache capture check_box check_box_tag collection_select concat content_for content_tag country_options_for_select country_select current_page? date_select datetime_select debug define_javascript_functions distance_of_time_in_words distance_of_time_in_words_to_now draggable_element drop_receiving_element end_form_tag error_message_on error_messages_for escape_javascript evaluate_remote_response excerpt file_field file_field_tag finish_upload_status form form_remote_tag form_tag form_tag_with_upload_progress h hidden_field hidden_field_tag highlight human_size image_path image_submit_tag image_tag input javascript_include_tag javascript_path javascript_tag link_image_to link_to link_to_function link_to_if link_to_image link_to_remote link_to_unless link_to_unless_current mail_to markdown number_to_currency number_to_human_size number_to_percentage number_to_phone number_with_delimiter number_with_precision observe_field observe_form option_groups_from_collection_for_select options_for_select options_from_collection_for_select pagination_links password_field password_field_tag periodically_call_remote pluralize radio_button radio_button_tag register_template_handler render render_file render_template sanitize select select_date select_datetime select_day select_hour select_minute select_month select_second select_tag select_time select_year simple_format sortable_element start_form_tag strip_links stylesheet_link_tag stylesheet_path submit_tag submit_to_remote tag text_area text_area_tag text_field text_field_tag text_field_with_auto_complete textilize textilize_without_paragraph time_ago_in_words time_zone_options_for_select time_zone_select truncate update_element_function upload_progress_status upload_progress_text upload_progress_update_bar_js upload_status_progress_bar_tag upload_status_tag upload_status_text_tag url_for visual_effect word_wrap" list_attention = Set.fromList $ words $ "TODO FIXME NOTE" regex_'3c'25'3d'3f = compileRegex "<%=?" regex_'3c'21DOCTYPE'5cs'2b = compileRegex "))+" regex_'5cS = compileRegex "\\S" regex_'3c'2fstyle'5cb = compileRegex ")" regex_'5b'5e'2f'3e'3c'22'27'5cs'5d = compileRegex "[^/><\"'\\s]" regex_'2d'3f'25'3e = compileRegex "-?%>" 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_'28'5cb'7c'5e'5cs'2a'29'28else'7celsif'7crescue'7censure'29'28'5cs'2b'7c'24'29 = compileRegex "(\\b|^\\s*)(else|elsif|rescue|ensure)(\\s+|$)" 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'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_'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'2f'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'5ba'2dzA'2dZ'5f'5d'5ba'2dzA'2dZ0'2d9'5f'5d'2a = compileRegex ":[a-zA-Z_][a-zA-Z0-9_]*" regex_'23'5cs'2aBEGIN'2e'2a'24 = compileRegex "#\\s*BEGIN.*$" regex_'23'5cs'2aEND'2e'2a'24 = compileRegex "#\\s*END.*$" regex_'23 = compileRegex "#" regex_'5cs'23 = compileRegex "\\s#" regex_'5b'5c'5b'5c'5d'5d'2b = compileRegex "[\\[\\]]+" 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'3e'5d'29 = compileRegex "\\s*[%](?=[Qqxw]?[^\\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_'5c'5c'5c'2f = compileRegex "\\\\\\/" regex_'5b'5e'5c'5c'5d'24 = 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 = [("Start","Normal Text"),("FindHTML","Normal Text"),("FindEntityRefs","Normal Text"),("FindPEntityRefs","Normal Text"),("FindAttributes","Normal Text"),("FindDTDRules","Normal Text"),("Comment","Comment"),("CDATA","Normal Text"),("PI","Normal Text"),("Doctype","Normal Text"),("Doctype Internal Subset","Normal Text"),("Doctype Markupdecl","Normal Text"),("Doctype Markupdecl DQ","Value"),("Doctype Markupdecl SQ","Value"),("El Open","Normal Text"),("El Close","Normal Text"),("El Close 2","Normal Text"),("El Close 3","Normal Text"),("CSS","Normal Text"),("CSS content","Normal Text"),("JS","Normal Text"),("JS content","Normal Text"),("JS comment close","Comment"),("Value","Normal Text"),("Value NQ","Normal Text"),("Value DQ","Value"),("Value SQ","Value"),("rubysourceline","RUBY RAILS ERB Text"),("rubysource","RUBY RAILS ERB Text"),("Line Continue","Ruby Normal Text"),("Quoted String","String"),("Apostrophed String","Raw String"),("Command String","Command"),("Embedded documentation","Ruby Comment"),("RegEx 1","Regular Expression"),("Subst","Ruby Normal Text"),("Short Subst","Substitution"),("Member Access","Member"),("Comment Line","Ruby Comment"),("General Comment","Ruby Comment"),("RDoc Label","RDoc Value"),("find_heredoc","Ruby Normal Text"),("find_indented_heredoc","Ruby Normal Text"),("indented_heredoc","Ruby Normal Text"),("apostrophed_indented_heredoc","Ruby Normal Text"),("normal_heredoc","Ruby Normal Text"),("apostrophed_normal_heredoc","Ruby Normal Text"),("heredoc_rules","Ruby Normal Text"),("find_gdl_input","Ruby 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 "Start" = do (attr, result) <- ((parseRules "FindHTML")) return (attr, result) parseRules "FindHTML" = do (attr, result) <- (((pDetectSpaces >>= withAttribute "Normal Text")) <|> ((pDetectIdentifier >>= withAttribute "Normal Text")) <|> ((pRegExpr regex_'3c'25'3d'3f >>= withAttribute "Keyword") >>~ pushContext "rubysource") <|> ((pString False "%" >>= withAttribute "Keyword") >>~ pushContext "rubysourceline") <|> ((pString False "" >>= withAttribute "Comment") >>~ (popContext)) <|> ((pRegExpr regex_'2d'28'2d'28'3f'21'2d'3e'29'29'2b >>= withAttribute "Error"))) return (attr, result) parseRules "CDATA" = do (attr, result) <- (((pDetectSpaces >>= withAttribute "Normal Text")) <|> ((pDetectIdentifier >>= withAttribute "Normal Text")) <|> ((pString False "]]>" >>= withAttribute "CDATA") >>~ (popContext)) <|> ((pString False "]]>" >>= withAttribute "EntityRef"))) return (attr, result) parseRules "PI" = do (attr, result) <- ((pDetect2Chars False '?' '>' >>= withAttribute "Processing Instruction") >>~ (popContext)) return (attr, result) parseRules "Doctype" = do (attr, result) <- (((pDetectChar False '>' >>= withAttribute "Doctype") >>~ (popContext)) <|> ((pDetectChar False '[' >>= withAttribute "Doctype") >>~ pushContext "Doctype Internal Subset")) return (attr, result) parseRules "Doctype Internal Subset" = do (attr, result) <- (((pDetectChar False ']' >>= withAttribute "Doctype") >>~ (popContext)) <|> ((parseRules "FindDTDRules")) <|> ((pString False "