{- This module was generated from data in the Kate syntax highlighting file makefile.xml, version 1.12, by Per Wigren (wigren@home.se) -} module Text.Highlighting.Kate.Syntax.Makefile (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 qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "Makefile" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "GNUmakefile;Makefile;makefile;GNUmakefile.*;Makefile.*;makefile.*" -- | 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 result <- parseRules (lang,cont) optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("Makefile","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 ("Makefile","Normal") -> return () ("Makefile","String") -> (popContext) >> pEndLine ("Makefile","Value") -> (popContext) >> pEndLine ("Makefile","VarFromValue(") -> return () ("Makefile","VarFromValue{") -> return () ("Makefile","VarFromNormal(") -> return () ("Makefile","VarFromNormal{") -> return () ("Makefile","FunctionCall(") -> return () ("Makefile","FunctionCall{") -> return () ("Makefile","Commands") -> (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_keywords = Set.fromList $ words $ "include define else endef endif ifdef ifeq ifndef ifneq" list_functions = Set.fromList $ words $ "call subst patsubst strip findstring filter filter-out sort word wordlist words firstword lastword dir notdir suffix basename addsuffix addprefix join wildcard realpath abspath if or and foreach value eval origin flavor shell error warning info" regex_'5b'5f'5cw'5cd'5d'2a'5cs'2a'28'3f'3d'3a'3d'7c'3d'7c'5c'2b'3d'7c'5c'3f'3d'29 = compileRegex "[_\\w\\d]*\\s*(?=:=|=|\\+=|\\?=)" regex_'5b'5f'5cw'5cd'2d'5d'2a'5cs'2a'3a = compileRegex "[_\\w\\d-]*\\s*:" regex_'5b'2e'5d'2e'2a'3a = compileRegex "[.].*:" regex_'23'2e'2a'24 = compileRegex "#.*$" regex_'40'5b'2d'5f'5cd'5cw'5d'2a'40 = compileRegex "@[-_\\d\\w]*@" regex_'5b'5f'5cw'2d'5d'2a'5cb = compileRegex "[_\\w-]*\\b" parseRules ("Makefile","Normal") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5b'5f'5cw'5cd'5d'2a'5cs'2a'28'3f'3d'3a'3d'7c'3d'7c'5c'2b'3d'7c'5c'3f'3d'29 >>= withAttribute DataTypeTok) >>~ pushContext ("Makefile","Value")) <|> ((pFirstNonSpace >> pRegExpr regex_'5b'5f'5cw'5cd'2d'5d'2a'5cs'2a'3a >>= withAttribute DecValTok)) <|> ((pColumn 0 >> pRegExpr regex_'5b'2e'5d'2e'2a'3a >>= withAttribute OtherTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Makefile","String")) <|> ((pDetect2Chars False '$' '{' >>= withAttribute CharTok) >>~ pushContext ("Makefile","VarFromNormal{")) <|> ((pDetect2Chars False '$' '(' >>= withAttribute CharTok) >>~ pushContext ("Makefile","VarFromNormal(")) <|> ((pDetect2Chars False '\\' '#' >>= withAttribute FloatTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute FloatTok)) <|> ((pAnyChar "+*=%$():\\;" >>= withAttribute CharTok)) <|> ((pFirstNonSpace >> pAnyChar "@-" >>= withAttribute CharTok) >>~ pushContext ("Makefile","Commands")) <|> ((pRegExpr regex_'23'2e'2a'24 >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("Makefile","Normal")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Makefile","String") = (((pLineContinue >>= withAttribute StringTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Makefile","String")) >> pDefault >>= withAttribute StringTok)) parseRules ("Makefile","Value") = (((pLineContinue >>= withAttribute CharTok)) <|> ((pDetect2Chars False '$' '{' >>= withAttribute CharTok) >>~ pushContext ("Makefile","VarFromValue{")) <|> ((pDetect2Chars False '$' '(' >>= withAttribute CharTok) >>~ pushContext ("Makefile","VarFromValue(")) <|> ((pRegExpr regex_'40'5b'2d'5f'5cd'5cw'5d'2a'40 >>= withAttribute FloatTok) >>~ (popContext)) <|> ((pDetectChar False ';' >>= withAttribute CharTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Makefile","Value")) >> pDefault >>= withAttribute StringTok)) parseRules ("Makefile","VarFromValue(") = (((pDetectChar False ')' >>= withAttribute CharTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Makefile","VarFromValue(")) >> pDefault >>= withAttribute DataTypeTok)) parseRules ("Makefile","VarFromValue{") = (((pDetectChar False '}' >>= withAttribute CharTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Makefile","VarFromValue{")) >> pDefault >>= withAttribute DataTypeTok)) parseRules ("Makefile","VarFromNormal(") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_functions >>= withAttribute KeywordTok) >>~ pushContext ("Makefile","FunctionCall(")) <|> ((pDetectChar False ')' >>= withAttribute CharTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Makefile","VarFromNormal(")) >> pDefault >>= withAttribute DataTypeTok)) parseRules ("Makefile","VarFromNormal{") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_functions >>= withAttribute KeywordTok) >>~ pushContext ("Makefile","FunctionCall{")) <|> ((pDetectChar False '}' >>= withAttribute CommentTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Makefile","VarFromNormal{")) >> pDefault >>= withAttribute DataTypeTok)) parseRules ("Makefile","FunctionCall(") = (((pDetect2Chars False '$' '{' >>= withAttribute CharTok) >>~ pushContext ("Makefile","VarFromNormal{")) <|> ((pDetect2Chars False '$' '(' >>= withAttribute CharTok) >>~ pushContext ("Makefile","VarFromNormal(")) <|> ((pDetectChar False ')' >>= withAttribute CharTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("Makefile","FunctionCall(")) >> pDefault >>= withAttribute StringTok)) parseRules ("Makefile","FunctionCall{") = (((pDetect2Chars False '$' '{' >>= withAttribute CharTok) >>~ pushContext ("Makefile","VarFromNormal{")) <|> ((pDetect2Chars False '$' '(' >>= withAttribute CharTok) >>~ pushContext ("Makefile","VarFromNormal(")) <|> ((pDetectChar False '}' >>= withAttribute CharTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("Makefile","FunctionCall{")) >> pDefault >>= withAttribute StringTok)) parseRules ("Makefile","Commands") = (((pDetect2Chars False '$' '{' >>= withAttribute CharTok) >>~ pushContext ("Makefile","VarFromNormal{")) <|> ((pDetect2Chars False '$' '(' >>= withAttribute CharTok) >>~ pushContext ("Makefile","VarFromNormal(")) <|> ((pRegExpr regex_'5b'5f'5cw'2d'5d'2a'5cb >>= withAttribute BaseNTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Makefile","Commands")) >> pDefault >>= withAttribute NormalTok)) parseRules x = parseRules ("Makefile","Normal") <|> fail ("Unknown context" ++ show x)