{- This module was generated from data in the Kate syntax highlighting file dtd.xml, version 1.02, by Andriy Lesyuk (s-andy@in.if.ua) -} module Text.Highlighting.Kate.Syntax.Dtd (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 Control.Monad.State import Data.Char (isSpace) import qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "DTD" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.dtd" -- | 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 = [("DTD","Normal")], 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 ("DTD","Normal") -> return () ("DTD","Comment") -> return () ("DTD","PI") -> return () ("DTD","Declaration") -> return () ("DTD","String") -> return () ("DTD","InlineComment") -> (popContext) >> pEndLine _ -> 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) list_Category = Set.fromList $ words $ "EMPTY ANY CDATA ID IDREF IDREFS NMTOKEN NMTOKENS ENTITY ENTITIES NOTATION PUBLIC SYSTEM NDATA" list_Keywords = Set.fromList $ words $ "#PCDATA #REQUIRED #IMPLIED #FIXED" regex_'28'2d'7cO'29'5cs'28'2d'7cO'29 = compileRegex True "(-|O)\\s(-|O)" regex_'28'25'7c'26'29'28'23'5b0'2d9'5d'2b'7c'23'5bxX'5d'5b0'2d9A'2dFa'2df'5d'2b'7c'5b'5c'2d'5cw'5cd'5c'2e'3a'5f'5d'2b'29'3b = compileRegex True "(%|&)(#[0-9]+|#[xX][0-9A-Fa-f]+|[\\-\\w\\d\\.:_]+);" regex_'25'5cs = compileRegex True "%\\s" regex_'5cb'5b'5c'2d'5cw'5cd'5c'2e'3a'5f'5d'2b'5cb = compileRegex True "\\b[\\-\\w\\d\\.:_]+\\b" regex_'25'5b'5c'2d'5cw'5cd'5c'2e'3a'5f'5d'2b'3b = compileRegex True "%[\\-\\w\\d\\.:_]+;" parseRules ("DTD","Normal") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pString False "" >>= withAttribute CommentTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> ((pDetectIdentifier >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("DTD","Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("DTD","PI") = (((pDetect2Chars False '?' '>' >>= withAttribute KeywordTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("DTD","PI")) >> pDefault >>= withAttribute NormalTok)) parseRules ("DTD","Declaration") = (((pString False "