{- This module was generated from data in the Kate syntax highlighting file yacc.xml, version 1.03, by Jan Villat (jan.villat@net2000.ch) -} module Text.Highlighting.Kate.Syntax.Yacc (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Cpp 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 = "Yacc/Bison" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.y;*.yy" -- | 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 == "Yacc/Bison" then parseRules (lang,cont) <|> (pDefault >>= withAttribute defAttr) else parseRules ("Yacc/Bison","Pre Start") optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("Yacc/Bison","Pre Start")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext case context of ("Yacc/Bison","Pre Start") -> return () ("Yacc/Bison","C Declarations") -> return () ("Yacc/Bison","Declarations") -> return () ("Yacc/Bison","Union Start") -> return () ("Yacc/Bison","Union In") -> return () ("Yacc/Bison","Union InIn") -> return () ("Yacc/Bison","Rules") -> return () ("Yacc/Bison","Rule In") -> return () ("Yacc/Bison","User Code") -> return () ("Yacc/Bison","Percent Command") -> (popContext) >> pEndLine ("Yacc/Bison","Percent Command In") -> (popContext >> popContext) >> pEndLine ("Yacc/Bison","PC type") -> (popContext >> popContext >> popContext) >> pEndLine ("Yacc/Bison","Comment") -> return () ("Yacc/Bison","CommentStar") -> return () ("Yacc/Bison","CommentSlash") -> return () ("Yacc/Bison","StringOrChar") -> return () ("Yacc/Bison","String") -> (popContext) >> pEndLine ("Yacc/Bison","Char") -> (popContext) >> pEndLine ("Yacc/Bison","Normal C Bloc") -> return () ("Yacc/Bison","Dol") -> return () ("Yacc/Bison","DolEnd") -> 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) regex_'2e = compileRegex "." regex_'5cW = compileRegex "\\W" regex_'5b'5e'5c'5c'5d'24 = compileRegex "[^\\\\]$" regex_'5c'5c'2e = compileRegex "\\\\." regex_'3c'5b'5e'3e'5d'2b'3e = compileRegex "<[^>]+>" regex_'5cd'2b = compileRegex "\\d+" defaultAttributes = [(("Yacc/Bison","Pre Start"),NormalTok),(("Yacc/Bison","C Declarations"),NormalTok),(("Yacc/Bison","Declarations"),NormalTok),(("Yacc/Bison","Union Start"),NormalTok),(("Yacc/Bison","Union In"),NormalTok),(("Yacc/Bison","Union InIn"),NormalTok),(("Yacc/Bison","Rules"),StringTok),(("Yacc/Bison","Rule In"),NormalTok),(("Yacc/Bison","User Code"),NormalTok),(("Yacc/Bison","Percent Command"),KeywordTok),(("Yacc/Bison","Percent Command In"),NormalTok),(("Yacc/Bison","PC type"),DataTypeTok),(("Yacc/Bison","Comment"),CommentTok),(("Yacc/Bison","CommentStar"),CommentTok),(("Yacc/Bison","CommentSlash"),CommentTok),(("Yacc/Bison","StringOrChar"),NormalTok),(("Yacc/Bison","String"),StringTok),(("Yacc/Bison","Char"),CharTok),(("Yacc/Bison","Normal C Bloc"),NormalTok),(("Yacc/Bison","Dol"),NormalTok),(("Yacc/Bison","DolEnd"),NormalTok)] parseRules ("Yacc/Bison","Pre Start") = (((parseRules ("Yacc/Bison","Comment"))) <|> ((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pColumn 0 >> pDetect2Chars False '%' '{' >>= withAttribute BaseNTok) >>~ pushContext ("Yacc/Bison","C Declarations")) <|> ((lookAhead (pRegExpr regex_'2e) >> pushContext ("Yacc/Bison","Declarations") >> currentContext >>= parseRules))) parseRules ("Yacc/Bison","C Declarations") = (((parseRules ("Yacc/Bison","Comment"))) <|> ((pColumn 0 >> pDetect2Chars False '%' '}' >>= withAttribute BaseNTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Cpp.parseExpression))) parseRules ("Yacc/Bison","Declarations") = (((parseRules ("Yacc/Bison","Comment"))) <|> ((pString False "%union" >>= withAttribute KeywordTok) >>~ pushContext ("Yacc/Bison","Union Start")) <|> ((pDetect2Chars False '%' '%' >>= withAttribute BaseNTok) >>~ pushContext ("Yacc/Bison","Rules")) <|> ((pColumn 0 >> pDetect2Chars False '%' '{' >>= withAttribute BaseNTok) >>~ pushContext ("Yacc/Bison","C Declarations")) <|> ((pDetectChar False '%' >>= withAttribute KeywordTok) >>~ pushContext ("Yacc/Bison","Percent Command"))) parseRules ("Yacc/Bison","Union Start") = (((parseRules ("Yacc/Bison","Comment"))) <|> ((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("Yacc/Bison","Union In")) <|> ((pRegExpr regex_'2e >>= withAttribute AlertTok) >>~ (popContext))) parseRules ("Yacc/Bison","Union In") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("Yacc/Bison","Union InIn")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext >> popContext)) <|> ((Text.Highlighting.Kate.Syntax.Cpp.parseExpression))) parseRules ("Yacc/Bison","Union InIn") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("Yacc/Bison","Union InIn")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Cpp.parseExpression))) parseRules ("Yacc/Bison","Rules") = (((parseRules ("Yacc/Bison","Comment"))) <|> ((pDetect2Chars False '%' '%' >>= withAttribute BaseNTok) >>~ pushContext ("Yacc/Bison","User Code")) <|> ((pDetectChar False ':' >>= withAttribute NormalTok) >>~ pushContext ("Yacc/Bison","Rule In"))) parseRules ("Yacc/Bison","Rule In") = (((parseRules ("Yacc/Bison","Comment"))) <|> ((pDetectChar False ';' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("Yacc/Bison","Normal C Bloc")) <|> ((pDetectChar False '|' >>= withAttribute NormalTok)) <|> ((parseRules ("Yacc/Bison","StringOrChar")))) parseRules ("Yacc/Bison","User Code") = ((Text.Highlighting.Kate.Syntax.Cpp.parseExpression)) parseRules ("Yacc/Bison","Percent Command") = (((parseRules ("Yacc/Bison","Comment"))) <|> ((lookAhead (pRegExpr regex_'5cW) >> pushContext ("Yacc/Bison","Percent Command In") >> currentContext >>= parseRules))) parseRules ("Yacc/Bison","Percent Command In") = (((parseRules ("Yacc/Bison","StringOrChar"))) <|> ((pDetectChar False '<' >>= withAttribute DataTypeTok) >>~ pushContext ("Yacc/Bison","PC type"))) parseRules ("Yacc/Bison","PC type") = ((pDetectChar False '>' >>= withAttribute DataTypeTok) >>~ (popContext)) parseRules ("Yacc/Bison","Comment") = (((pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("Yacc/Bison","CommentStar")) <|> ((pDetect2Chars False '/' '/' >>= withAttribute CommentTok) >>~ pushContext ("Yacc/Bison","CommentSlash"))) parseRules ("Yacc/Bison","CommentStar") = ((pDetect2Chars False '*' '/' >>= withAttribute CommentTok) >>~ (popContext)) parseRules ("Yacc/Bison","CommentSlash") = ((pRegExpr regex_'5b'5e'5c'5c'5d'24 >>= withAttribute CommentTok) >>~ (popContext)) parseRules ("Yacc/Bison","StringOrChar") = (((pDetectChar False '\'' >>= withAttribute CharTok) >>~ pushContext ("Yacc/Bison","Char")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Yacc/Bison","String"))) parseRules ("Yacc/Bison","String") = (((pRegExpr regex_'5c'5c'2e >>= withAttribute StringTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext))) parseRules ("Yacc/Bison","Char") = (((pRegExpr regex_'5c'5c'2e >>= withAttribute StringTok)) <|> ((pDetectChar False '\'' >>= withAttribute CharTok) >>~ (popContext))) parseRules ("Yacc/Bison","Normal C Bloc") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("Yacc/Bison","Normal C Bloc")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Cpp.parseExpression)) <|> ((pDetectChar False '$' >>= withAttribute KeywordTok) >>~ pushContext ("Yacc/Bison","Dol"))) parseRules ("Yacc/Bison","Dol") = (((pRegExpr regex_'3c'5b'5e'3e'5d'2b'3e >>= withAttribute DataTypeTok) >>~ pushContext ("Yacc/Bison","DolEnd")) <|> (pushContext ("Yacc/Bison","DolEnd") >> currentContext >>= parseRules)) parseRules ("Yacc/Bison","DolEnd") = (((pRegExpr regex_'5cd'2b >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((pDetectChar False '$' >>= withAttribute KeywordTok) >>~ (popContext >> popContext))) parseRules ("C++", _) = Text.Highlighting.Kate.Syntax.Cpp.parseExpression parseRules x = fail $ "Unknown context" ++ show x