{- This module was generated from data in the Kate syntax highlighting file yaml.xml, version 1.1, by Dr Orlovsky MA (dr.orlovsky@gmail.com) -} module Text.Highlighting.Kate.Syntax.Yaml (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import Text.ParserCombinators.Parsec hiding (State) import Control.Monad.State import Data.Char (isSpace) import Data.Maybe (fromMaybe) -- | Full name of language. syntaxName :: String syntaxName = "YAML" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.yaml;*.yml" -- | 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 -- | Parse an expression using appropriate local context. parseExpression :: KateParser Token parseExpression = do (lang,cont) <- currentContext let defAttr = fromMaybe NormalTok $ lookup (lang,cont) defaultAttributes result <- if lang == "YAML" then parseRules (lang,cont) <|> (pDefault >>= withAttribute defAttr) else parseRules ("YAML","normal") optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("YAML","normal")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext case context of ("YAML","normal") -> return () ("YAML","dash") -> (popContext) >> pEndLine ("YAML","header") -> (popContext) >> pEndLine ("YAML","EOD") -> return () ("YAML","directive") -> (popContext) >> pEndLine ("YAML","attribute") -> (popContext >> popContext) >> pEndLine ("YAML","attribute-inline") -> return () ("YAML","attribute-pre") -> (popContext) >> pEndLine ("YAML","attribute-pre-inline") -> (popContext) >> pEndLine ("YAML","list") -> return () ("YAML","hash") -> return () ("YAML","attribute-string") -> return () ("YAML","attribute-stringx") -> return () ("YAML","attribute-string-inline") -> return () ("YAML","attribute-stringx-inline") -> return () ("YAML","attribute-end") -> (popContext >> popContext >> popContext) >> pEndLine ("YAML","attribute-end-inline") -> (popContext >> popContext >> popContext) >> pEndLine ("YAML","string") -> return () ("YAML","stringx") -> return () ("YAML","comment") -> (popContext) >> pEndLine _ -> 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_'2d'2d'2d = compileRegex "---" regex_'5c'2e'5c'2e'5c'2e'24 = compileRegex "\\.\\.\\.$" regex_'25 = compileRegex "%" regex_'21'21'5cS'2b = compileRegex "!!\\S+" regex_'26'5cS'2b = compileRegex "&\\S+" regex_'5c'2a'5cS'2b = compileRegex "\\*\\S+" regex_'5c'3f'3f'5cs'2a'5b'5e'22'27'23'2d'5d'5b'5e'3a'23'5d'2a'3a = compileRegex "\\??\\s*[^\"'#-][^:#]*:" regex_'5c'3f'3f'5cs'2a'22'5b'5e'22'23'5d'2b'22'5cs'2a'3a = compileRegex "\\??\\s*\"[^\"#]+\"\\s*:" regex_'5c'3f'3f'5cs'2a'27'5b'5e'27'23'5d'2b'27'5cs'2a'3a = compileRegex "\\??\\s*'[^'#]+'\\s*:" regex_null'24 = compileRegex "null$" regex_'2e = compileRegex "." regex_'5cs'2a = compileRegex "\\s*" regex_'2c'5cs = compileRegex ",\\s" defaultAttributes = [(("YAML","normal"),NormalTok),(("YAML","dash"),NormalTok),(("YAML","header"),OtherTok),(("YAML","EOD"),CommentTok),(("YAML","directive"),OtherTok),(("YAML","attribute"),NormalTok),(("YAML","attribute-inline"),NormalTok),(("YAML","attribute-pre"),NormalTok),(("YAML","attribute-pre-inline"),NormalTok),(("YAML","list"),NormalTok),(("YAML","hash"),NormalTok),(("YAML","attribute-string"),NormalTok),(("YAML","attribute-stringx"),NormalTok),(("YAML","attribute-string-inline"),NormalTok),(("YAML","attribute-stringx-inline"),NormalTok),(("YAML","attribute-end"),ErrorTok),(("YAML","attribute-end-inline"),ErrorTok),(("YAML","string"),NormalTok),(("YAML","stringx"),NormalTok),(("YAML","comment"),CommentTok)] parseRules ("YAML","normal") = (((pColumn 0 >> pRegExpr regex_'2d'2d'2d >>= withAttribute OtherTok) >>~ pushContext ("YAML","header")) <|> ((pColumn 0 >> pRegExpr regex_'5c'2e'5c'2e'5c'2e'24 >>= withAttribute CommentTok) >>~ pushContext ("YAML","EOD")) <|> ((pColumn 0 >> pRegExpr regex_'25 >>= withAttribute OtherTok) >>~ pushContext ("YAML","directive")) <|> ((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("YAML","comment")) <|> ((pFirstNonSpace >> pDetectChar False '-' >>= withAttribute KeywordTok) >>~ pushContext ("YAML","dash")) <|> ((pDetectChar False '[' >>= withAttribute KeywordTok) >>~ pushContext ("YAML","list")) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext ("YAML","hash")) <|> ((pFirstNonSpace >> pRegExpr regex_'21'21'5cS'2b >>= withAttribute DataTypeTok)) <|> ((pFirstNonSpace >> pRegExpr regex_'26'5cS'2b >>= withAttribute DataTypeTok)) <|> ((pFirstNonSpace >> pRegExpr regex_'5c'2a'5cS'2b >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5c'3f'3f'5cs'2a'5b'5e'22'27'23'2d'5d'5b'5e'3a'23'5d'2a'3a >>= withAttribute FunctionTok) >>~ pushContext ("YAML","attribute-pre")) <|> ((pRegExpr regex_'5c'3f'3f'5cs'2a'22'5b'5e'22'23'5d'2b'22'5cs'2a'3a >>= withAttribute FunctionTok) >>~ pushContext ("YAML","attribute-pre")) <|> ((pRegExpr regex_'5c'3f'3f'5cs'2a'27'5b'5e'27'23'5d'2b'27'5cs'2a'3a >>= withAttribute FunctionTok) >>~ pushContext ("YAML","attribute-pre")) <|> ((pDetectChar False '\'' >>= withAttribute NormalTok) >>~ pushContext ("YAML","string")) <|> ((pDetectChar False '"' >>= withAttribute NormalTok) >>~ pushContext ("YAML","stringx"))) parseRules ("YAML","dash") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("YAML","comment")) <|> ((pRegExpr regex_null'24 >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'21'21'5cS'2b >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'26'5cS'2b >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5c'2a'5cS'2b >>= withAttribute DataTypeTok)) <|> ((lookAhead (pRegExpr regex_'2e) >> (popContext) >> currentContext >>= parseRules))) parseRules ("YAML","header") = ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("YAML","comment")) parseRules ("YAML","EOD") = pzero parseRules ("YAML","directive") = pzero parseRules ("YAML","attribute") = ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("YAML","comment")) parseRules ("YAML","attribute-inline") = (((pDetectChar False ',' >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((lookAhead (pDetectChar False '}') >> (popContext >> popContext) >> currentContext >>= parseRules)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("YAML","comment"))) parseRules ("YAML","attribute-pre") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("YAML","comment")) <|> ((pRegExpr regex_null'24 >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'21'21'5cS'2b >>= withAttribute DataTypeTok)) <|> ((pDetectChar False '[' >>= withAttribute KeywordTok) >>~ pushContext ("YAML","list")) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext ("YAML","hash")) <|> ((pDetectChar False '\'' >>= withAttribute NormalTok) >>~ pushContext ("YAML","attribute-string")) <|> ((pDetectChar False '"' >>= withAttribute NormalTok) >>~ pushContext ("YAML","attribute-stringx")) <|> ((pRegExpr regex_'26'5cS'2b >>= withAttribute DataTypeTok) >>~ pushContext ("YAML","attribute")) <|> ((pRegExpr regex_'5c'2a'5cS'2b >>= withAttribute DataTypeTok) >>~ pushContext ("YAML","attribute")) <|> ((pRegExpr regex_'2e >>= withAttribute NormalTok) >>~ pushContext ("YAML","attribute"))) parseRules ("YAML","attribute-pre-inline") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("YAML","comment")) <|> ((pString False "null" >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'21'21'5cS'2b >>= withAttribute DataTypeTok)) <|> ((pDetectChar False '[' >>= withAttribute KeywordTok) >>~ pushContext ("YAML","list")) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext ("YAML","hash")) <|> ((pDetectChar False '\'' >>= withAttribute NormalTok) >>~ pushContext ("YAML","attribute-string-inline")) <|> ((pDetectChar False '"' >>= withAttribute NormalTok) >>~ pushContext ("YAML","attribute-stringx-inline")) <|> ((pRegExpr regex_'26'5cS'2b >>= withAttribute DataTypeTok) >>~ pushContext ("YAML","attribute-inline")) <|> ((pRegExpr regex_'5c'2a'5cS'2b >>= withAttribute DataTypeTok) >>~ pushContext ("YAML","attribute-inline")) <|> ((pDetectChar False ',' >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((lookAhead (pDetectChar False '}') >> (popContext) >> currentContext >>= parseRules)) <|> ((pRegExpr regex_'2e >>= withAttribute NormalTok) >>~ pushContext ("YAML","attribute-inline"))) parseRules ("YAML","list") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("YAML","comment")) <|> ((pDetectChar False ']' >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'3f'3f'5cs'2a'5b'5e'22'27'23'2d'5d'5b'5e'3a'23'5d'2a'3a >>= withAttribute FunctionTok) >>~ pushContext ("YAML","attribute-pre")) <|> ((pRegExpr regex_'5c'3f'3f'5cs'2a'22'5b'5e'22'23'5d'2b'22'5cs'2a'3a >>= withAttribute FunctionTok) >>~ pushContext ("YAML","attribute-pre")) <|> ((pRegExpr regex_'5c'3f'3f'5cs'2a'27'5b'5e'27'23'5d'2b'27'5cs'2a'3a >>= withAttribute FunctionTok) >>~ pushContext ("YAML","attribute-pre")) <|> ((pString False "null" >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'21'21'5cS'2b >>= withAttribute DataTypeTok)) <|> ((pDetectChar False '[' >>= withAttribute KeywordTok) >>~ pushContext ("YAML","list")) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext ("YAML","hash")) <|> ((pRegExpr regex_'26'5cS'2b >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5c'2a'5cS'2b >>= withAttribute DataTypeTok)) <|> ((pDetectChar False '\'' >>= withAttribute NormalTok) >>~ pushContext ("YAML","string")) <|> ((pDetectChar False '"' >>= withAttribute NormalTok) >>~ pushContext ("YAML","stringx")) <|> ((pDetectChar False ',' >>= withAttribute KeywordTok))) parseRules ("YAML","hash") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("YAML","comment")) <|> ((pRegExpr regex_'5c'3f'3f'5cs'2a'5b'5e'22'27'23'2d'5d'5b'5e'3a'23'5d'2a'3a >>= withAttribute FunctionTok) >>~ pushContext ("YAML","attribute-pre-inline")) <|> ((pRegExpr regex_'5c'3f'3f'5cs'2a'22'5b'5e'22'23'5d'2b'22'5cs'2a'3a >>= withAttribute FunctionTok) >>~ pushContext ("YAML","attribute-pre-inline")) <|> ((pRegExpr regex_'5c'3f'3f'5cs'2a'27'5b'5e'27'23'5d'2b'27'5cs'2a'3a >>= withAttribute FunctionTok) >>~ pushContext ("YAML","attribute-pre-inline")) <|> ((pDetectChar False '}' >>= withAttribute KeywordTok) >>~ (popContext))) parseRules ("YAML","attribute-string") = (((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pDetectChar False '\'' >>= withAttribute NormalTok) >>~ pushContext ("YAML","attribute-end"))) parseRules ("YAML","attribute-stringx") = (((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pDetectChar False '"' >>= withAttribute NormalTok) >>~ pushContext ("YAML","attribute-end"))) parseRules ("YAML","attribute-string-inline") = (((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pDetectChar False '\'' >>= withAttribute NormalTok) >>~ pushContext ("YAML","attribute-end-inline"))) parseRules ("YAML","attribute-stringx-inline") = (((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pDetectChar False '"' >>= withAttribute NormalTok) >>~ pushContext ("YAML","attribute-end-inline"))) parseRules ("YAML","attribute-end") = pzero parseRules ("YAML","attribute-end-inline") = (((pRegExpr regex_'5cs'2a >>= withAttribute NormalTok)) <|> ((lookAhead (pDetectChar False '}') >> (popContext >> popContext >> popContext) >> currentContext >>= parseRules)) <|> ((pRegExpr regex_'2c'5cs >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext))) parseRules ("YAML","string") = (((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pDetectChar False '\'' >>= withAttribute NormalTok) >>~ (popContext))) parseRules ("YAML","stringx") = (((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pDetectChar False '"' >>= withAttribute NormalTok) >>~ (popContext))) parseRules ("YAML","comment") = pzero parseRules x = fail $ "Unknown context" ++ show x