{- This module was generated from data in the Kate syntax highlighting file xml.xml, version 2.03, by Wilbert Berendsen (wilbert@kde.nl) -} module Text.Highlighting.Kate.Syntax.Xml (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) -- | Full name of language. syntaxName :: String syntaxName = "XML" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.docbook;*.xml;*.rc;*.daml;*.rdf;*.rss;*.xspf;*.xsd;*.svg;*.ui;*.kcfg;*.qrc;*.wsdl" -- | 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 = "XML" } context <- currentContext <|> (pushContext "Start" >> currentContext) result <- parseRules context optional $ eof >> pEndLine updateState $ \st -> st { synStLanguage = oldLang } return result startingState = SyntaxState {synStContexts = fromList [("XML",["Start"])], synStLanguage = "XML", synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do context <- currentContext case context of "Start" -> return () "FindXML" -> return () "FindEntityRefs" -> return () "FindPEntityRefs" -> return () "Comment" -> return () "CDATA" -> return () "PI" -> return () "Doctype" -> return () "Doctype Internal Subset" -> return () "Doctype Markupdecl" -> return () "Doctype Markupdecl DQ" -> return () "Doctype Markupdecl SQ" -> return () "Element" -> return () "El Content" -> return () "El End" -> return () "Attribute" -> return () "Value" -> return () "Value DQ" -> return () "Value SQ" -> 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)) regex_'3c'21DOCTYPE'5cs'2b = compileRegex "))+" regex_'3c'21'28ELEMENT'7cENTITY'7cATTLIST'7cNOTATION'29'5cb = compileRegex ">= withAttribute NormalTok)) <|> ((pString False "" >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pRegExpr regex_'2d'28'2d'28'3f'21'2d'3e'29'29'2b >>= withAttribute ErrorTok)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression >>= ((withAttribute CommentTok) . snd))) <|> ((pDetectIdentifier >>= withAttribute CommentTok))) parseRules "CDATA" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pString False "]]>" >>= withAttribute BaseNTok) >>~ (popContext)) <|> ((pString False "]]>" >>= withAttribute DecValTok))) parseRules "PI" = ((pDetect2Chars False '?' '>' >>= withAttribute KeywordTok) >>~ (popContext)) parseRules "Doctype" = (((pDetectChar False '>' >>= withAttribute DataTypeTok) >>~ (popContext)) <|> ((pDetectChar False '[' >>= withAttribute DataTypeTok) >>~ pushContext "Doctype Internal Subset")) parseRules "Doctype Internal Subset" = (((pDetectChar False ']' >>= withAttribute DataTypeTok) >>~ (popContext)) <|> ((pRegExpr regex_'3c'21'28ELEMENT'7cENTITY'7cATTLIST'7cNOTATION'29'5cb >>= withAttribute DataTypeTok) >>~ pushContext "Doctype Markupdecl") <|> ((pString False "