{- This module was generated from data in the Kate syntax highlighting file rhtml.xml, version 1.00, 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 Data.List (nub) import Data.Map (fromList) import Data.Maybe (fromMaybe) -- | 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, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} parseSourceLine = manyTill parseExpressionInternal pEndLine pEndLine = do newline <|> (eof >> return '\n') context <- currentContext case context of "Start" -> return () "FindHTML" -> return () "FindEntityRefs" -> return () "FindPEntityRefs" -> return () "FindAttributes" -> return () "FindDTDRules" -> return () "Comment" -> return () "CDATA" -> return () "PI" -> return () "Doctype" -> return () "Doctype Internal Subset" -> return () "Doctype Markupdecl" -> return () "Doctype Markupdecl DQ" -> return () "Doctype Markupdecl SQ" -> return () "El Open" -> return () "El Close" -> return () "El Close 2" -> return () "El Close 3" -> return () "CSS" -> return () "CSS content" -> return () "JS" -> return () "JS content" -> return () "JS comment close" -> (popContext >> return ()) "Value" -> return () "Value NQ" -> (popContext >> popContext >> return ()) "Value DQ" -> return () "Value SQ" -> return () "rubysourceline" -> (popContext >> return ()) "rubysource" -> return () "Line Continue" -> (popContext >> return ()) "Quoted String" -> return () "Apostrophed String" -> return () "Command String" -> return () "Embedded documentation" -> return () "RegEx 1" -> return () "Subst" -> return () "Short Subst" -> (popContext >> return ()) "Member Access" -> (popContext >> return ()) "Comment Line" -> (popContext >> return ()) "General Comment" -> (popContext >> return ()) "RDoc Label" -> (popContext >> return ()) "find_heredoc" -> (popContext >> return ()) "find_indented_heredoc" -> (popContext >> return ()) "indented_heredoc" -> return () "apostrophed_indented_heredoc" -> return () "normal_heredoc" -> return () "apostrophed_normal_heredoc" -> return () "heredoc_rules" -> return () "find_gdl_input" -> (popContext >> return ()) "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 () lineContents <- lookAhead wholeLine updateState $ \st -> st { synStCurrentLine = lineContents, synStCharsParsedInLine = 0 } withAttribute attr txt = do if null txt then fail "Parser matched no text" else return () let style = fromMaybe "" $ lookup attr styles st <- getState let oldCharsParsed = synStCharsParsedInLine st updateState $ \st -> st { synStCharsParsedInLine = oldCharsParsed + length txt } return (nub [style, attr], txt) styles = [("Ruby Normal Text","Normal"),("Keyword","Keyword"),("Attribute Definition","Others"),("Access Control","Keyword"),("Definition","Keyword"),("Pseudo variable","DecVal"),("Dec","DecVal"),("Float","Float"),("Char","Char"),("Octal","BaseN"),("Hex","BaseN"),("Bin","BaseN"),("Symbol","String"),("String","String"),("Raw String","String"),("Command","String"),("Message","Normal"),("Regular Expression","Others"),("Substitution","Others"),("Data","Normal"),("GDL input","Others"),("Default globals","DataType"),("Global Variable","DataType"),("Global Constant","DataType"),("Constant","DataType"),("Constant Value","DataType"),("Kernel methods","Normal"),("Member","Normal"),("Instance Variable","Others"),("Class Variable","Others"),("Ruby Comment","Comment"),("Blockcomment","Comment"),("Region Marker","Normal"),("RDoc Value","Others"),("Error","Error"),("Alert","Alert"),("Delimiter","Char"),("Expression","Others"),("Operator","Char"),("Normal Text","Normal"),("Comment","Comment"),("CDATA","BaseN"),("Processing Instruction","Keyword"),("Doctype","DataType"),("Element","Keyword"),("Attribute","Others"),("Value","String"),("EntityRef","DecVal"),("PEntityRef","DecVal"),("Error","Error")] parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes)) 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 (compileRegex "<%=?") >>= withAttribute "Keyword") >>~ pushContext "rubysource") <|> ((pString False "%" >>= withAttribute "Keyword") >>~ pushContext "rubysourceline") <|> ((pString False "" >>= withAttribute "Comment") >>~ (popContext >> return ())) <|> ((pRegExpr (compileRegex "-(-(?!->))+") >>= withAttribute "Error"))) return (attr, result) parseRules "CDATA" = do (attr, result) <- (((pDetectSpaces >>= withAttribute "Normal Text")) <|> ((pDetectIdentifier >>= withAttribute "Normal Text")) <|> ((pString False "]]>" >>= withAttribute "CDATA") >>~ (popContext >> return ())) <|> ((pString False "]]>" >>= withAttribute "EntityRef"))) return (attr, result) parseRules "PI" = do (attr, result) <- ((pDetect2Chars False '?' '>' >>= withAttribute "Processing Instruction") >>~ (popContext >> return ())) return (attr, result) parseRules "Doctype" = do (attr, result) <- (((pDetectChar False '>' >>= withAttribute "Doctype") >>~ (popContext >> return ())) <|> ((pDetectChar False '[' >>= withAttribute "Doctype") >>~ pushContext "Doctype Internal Subset")) return (attr, result) parseRules "Doctype Internal Subset" = do (attr, result) <- (((pDetectChar False ']' >>= withAttribute "Doctype") >>~ (popContext >> return ())) <|> ((parseRules "FindDTDRules")) <|> ((pString False "