{- This module was generated from data in the Kate syntax highlighting file html.xml, version 1.99, by Wilbert Berendsen (wilbert@kde.nl) -} module Text.Highlighting.Kate.Syntax.Html (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types 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 hiding (State) import Control.Monad.State import Data.Char (isSpace) -- | Full name of language. syntaxName :: String syntaxName = "HTML" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.htm;*.html;*.shtml;*.shtm" -- | 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 (parseExpression Nothing) -- | Parse an expression using appropriate local context. parseExpression :: Maybe (String,String) -> KateParser Token parseExpression mbcontext = do (lang,cont) <- maybe currentContext return mbcontext result <- parseRules (lang,cont) optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("HTML","Start")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext contexts <- synStContexts `fmap` getState if length contexts >= 2 then case context of ("HTML","Start") -> return () ("HTML","FindHTML") -> return () ("HTML","FindEntityRefs") -> return () ("HTML","FindPEntityRefs") -> return () ("HTML","FindAttributes") -> return () ("HTML","FindDTDRules") -> return () ("HTML","Comment") -> return () ("HTML","CDATA") -> return () ("HTML","PI") -> return () ("HTML","Doctype") -> return () ("HTML","Doctype Internal Subset") -> return () ("HTML","Doctype Markupdecl") -> return () ("HTML","Doctype Markupdecl DQ") -> return () ("HTML","Doctype Markupdecl SQ") -> return () ("HTML","El Open") -> return () ("HTML","El Close") -> return () ("HTML","El Close 2") -> return () ("HTML","El Close 3") -> return () ("HTML","CSS") -> return () ("HTML","CSS content") -> return () ("HTML","JS") -> return () ("HTML","JS content") -> return () ("HTML","JS comment close") -> (popContext) >> pEndLine ("HTML","Value") -> return () ("HTML","Value NQ") -> (popContext >> popContext) >> pEndLine ("HTML","Value DQ") -> return () ("HTML","Value SQ") -> return () _ -> return () else 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) 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]" parseRules ("HTML","Start") = (((parseRules ("HTML","FindHTML"))) <|> (currentContext >>= \x -> guard (x == ("HTML","Start")) >> pDefault >>= withAttribute NormalTok)) parseRules ("HTML","FindHTML") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pString False "" >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pRegExpr regex_'2d'28'2d'28'3f'21'2d'3e'29'29'2b >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("HTML","Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("HTML","CDATA") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pString False "]]>" >>= withAttribute BaseNTok) >>~ (popContext)) <|> ((pString False "]]>" >>= withAttribute DecValTok)) <|> (currentContext >>= \x -> guard (x == ("HTML","CDATA")) >> pDefault >>= withAttribute NormalTok)) parseRules ("HTML","PI") = (((pDetect2Chars False '?' '>' >>= withAttribute KeywordTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("HTML","PI")) >> pDefault >>= withAttribute NormalTok)) parseRules ("HTML","Doctype") = (((pDetectChar False '>' >>= withAttribute DataTypeTok) >>~ (popContext)) <|> ((pDetectChar False '[' >>= withAttribute DataTypeTok) >>~ pushContext ("HTML","Doctype Internal Subset")) <|> (currentContext >>= \x -> guard (x == ("HTML","Doctype")) >> pDefault >>= withAttribute NormalTok)) parseRules ("HTML","Doctype Internal Subset") = (((pDetectChar False ']' >>= withAttribute DataTypeTok) >>~ (popContext)) <|> ((parseRules ("HTML","FindDTDRules"))) <|> ((pString False "