{- This module was generated from data in the Kate syntax highlighting file makefile.xml, version 2.0, 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","prereq") -> pushContext ("Makefile","rule") >> return () ("Makefile","rule") -> return () ("Makefile","silent") -> (popContext) >> pEndLine ("Makefile","string\"") -> (popContext) >> pEndLine ("Makefile","string'") -> (popContext) >> pEndLine ("Makefile","assign") -> (popContext) >> pEndLine ("Makefile","value") -> (popContext >> popContext) >> pEndLine ("Makefile","dollar") -> (popContext) >> pEndLine ("Makefile","call(") -> return () ("Makefile","call{") -> return () ("Makefile","callVar(") -> return () ("Makefile","callVar{") -> return () ("Makefile","callFunc(") -> return () ("Makefile","callFunc{") -> return () _ -> 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 override" 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'5e'5cs'3a'2b'3f'5d'2a'5cs'2a'28'3f'3d'3a'3d'7c'3d'7c'5c'2b'3d'7c'5c'3f'3d'29 = compileRegex "[^\\s:+?]*\\s*(?=:=|=|\\+=|\\?=)" regex_'5b'2e'5d'2e'2a'3a = compileRegex "[.].*:" regex_'2e'2a'3a = compileRegex ".*:" regex_'23'2e'2a'24 = compileRegex "#.*$" regex__'2b = compileRegex " +" regex_'5b'5e'5ct'5d = compileRegex "[^\\t]" regex_'40'5b'2d'5f'5cd'5cw'5d'2a'40 = compileRegex "@[-_\\d\\w]*@" regex_'2e = compileRegex "." parseRules ("Makefile","normal") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5b'5e'5cs'3a'2b'3f'5d'2a'5cs'2a'28'3f'3d'3a'3d'7c'3d'7c'5c'2b'3d'7c'5c'3f'3d'29 >>= withAttribute DataTypeTok) >>~ pushContext ("Makefile","assign")) <|> ((pColumn 0 >> pRegExpr regex_'5b'2e'5d'2e'2a'3a >>= withAttribute OtherTok) >>~ pushContext ("Makefile","prereq")) <|> ((pColumn 0 >> pRegExpr regex_'2e'2a'3a >>= withAttribute DecValTok) >>~ pushContext ("Makefile","prereq")) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Makefile","string\"")) <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext ("Makefile","string'")) <|> ((pDetectChar False '$' >>= withAttribute CharTok) >>~ pushContext ("Makefile","dollar")) <|> ((pDetect2Chars False '\\' '#' >>= withAttribute FloatTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute FloatTok)) <|> ((pFirstNonSpace >> pAnyChar "@-" >>= withAttribute CharTok) >>~ pushContext ("Makefile","silent")) <|> ((pRegExpr regex_'23'2e'2a'24 >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("Makefile","normal")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Makefile","prereq") = (((pDetectSpaces >>= withAttribute DataTypeTok)) <|> ((pDetectIdentifier >>= withAttribute DataTypeTok)) <|> ((pDetectChar False '$' >>= withAttribute CharTok) >>~ pushContext ("Makefile","dollar")) <|> ((pDetect2Chars False '\\' '#' >>= withAttribute FloatTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'23'2e'2a'24 >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("Makefile","prereq")) >> pDefault >>= withAttribute DataTypeTok)) parseRules ("Makefile","rule") = (((pLineContinue >>= withAttribute CharTok)) <|> ((pColumn 0 >> pFirstNonSpace >> pRegExpr regex__'2b >>= withAttribute ErrorTok) >>~ (popContext >> popContext >> popContext)) <|> ((pColumn 0 >> pFirstNonSpace >> lookAhead (pRegExpr regex_'5b'5e'5ct'5d) >> (popContext >> popContext >> popContext) >> currentContext >>= parseRules)) <|> ((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Makefile","string\"")) <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext ("Makefile","string'")) <|> ((pDetectChar False '$' >>= withAttribute CharTok) >>~ pushContext ("Makefile","dollar")) <|> ((pDetect2Chars False '\\' '#' >>= withAttribute FloatTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute FloatTok)) <|> ((pFirstNonSpace >> pAnyChar "@-" >>= withAttribute CharTok) >>~ pushContext ("Makefile","silent")) <|> ((pRegExpr regex_'23'2e'2a'24 >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("Makefile","rule")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Makefile","silent") = (((pLineContinue >>= withAttribute CharTok)) <|> ((pDetectSpaces >>= withAttribute FunctionTok)) <|> ((pDetectIdentifier >>= withAttribute FunctionTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Makefile","string\"")) <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext ("Makefile","string'")) <|> ((pDetectChar False '$' >>= withAttribute CharTok) >>~ pushContext ("Makefile","dollar")) <|> ((pDetect2Chars False '\\' '#' >>= withAttribute FloatTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'23'2e'2a'24 >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("Makefile","silent")) >> pDefault >>= withAttribute FunctionTok)) parseRules ("Makefile","string\"") = (((pLineContinue >>= withAttribute CharTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pDetectChar False '$' >>= withAttribute CharTok) >>~ pushContext ("Makefile","dollar")) <|> (currentContext >>= \x -> guard (x == ("Makefile","string\"")) >> pDefault >>= withAttribute StringTok)) parseRules ("Makefile","string'") = (((pLineContinue >>= withAttribute StringTok)) <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pDetectChar False '$' >>= withAttribute CharTok) >>~ pushContext ("Makefile","dollar")) <|> (currentContext >>= \x -> guard (x == ("Makefile","string'")) >> pDefault >>= withAttribute StringTok)) parseRules ("Makefile","assign") = (((pDetectChar False '=' >>= withAttribute CharTok) >>~ pushContext ("Makefile","value")) <|> (currentContext >>= \x -> guard (x == ("Makefile","assign")) >> pDefault >>= withAttribute CharTok)) parseRules ("Makefile","value") = (((pLineContinue >>= withAttribute CharTok)) <|> ((pDetectChar False '$' >>= withAttribute CharTok) >>~ pushContext ("Makefile","dollar")) <|> ((pRegExpr regex_'40'5b'2d'5f'5cd'5cw'5d'2a'40 >>= withAttribute FloatTok) >>~ (popContext >> popContext)) <|> ((pDetectChar False ';' >>= withAttribute CharTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("Makefile","value")) >> pDefault >>= withAttribute StringTok)) parseRules ("Makefile","dollar") = (((pDetectChar False '(' >>= withAttribute CharTok) >>~ pushContext ("Makefile","call(")) <|> ((pDetectChar False '{' >>= withAttribute CharTok) >>~ pushContext ("Makefile","call{")) <|> ((pRegExpr regex_'2e >>= withAttribute CharTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Makefile","dollar")) >> pDefault >>= withAttribute CharTok)) parseRules ("Makefile","call(") = (((pKeyword " \n\t.():!+,<=>%&*/;?[]^{|}~\\" list_functions >>= withAttribute KeywordTok) >>~ pushContext ("Makefile","callFunc(")) <|> (pushContext ("Makefile","callVar(") >> currentContext >>= parseRules)) parseRules ("Makefile","call{") = (((pKeyword " \n\t.():!+,<=>%&*/;?[]^{|}~\\" list_functions >>= withAttribute KeywordTok) >>~ pushContext ("Makefile","callFunc{")) <|> (pushContext ("Makefile","callVar{") >> currentContext >>= parseRules)) parseRules ("Makefile","callVar(") = (((pDetectChar False ')' >>= withAttribute CharTok) >>~ (popContext >> popContext >> popContext)) <|> ((pDetectChar False '$' >>= withAttribute CharTok) >>~ pushContext ("Makefile","dollar")) <|> ((pDetectSpaces >>= withAttribute ErrorTok)) <|> ((pAnyChar "=#:" >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("Makefile","callVar(")) >> pDefault >>= withAttribute DataTypeTok)) parseRules ("Makefile","callVar{") = (((pDetectChar False '}' >>= withAttribute CharTok) >>~ (popContext >> popContext >> popContext)) <|> ((pDetectChar False '$' >>= withAttribute CharTok) >>~ pushContext ("Makefile","dollar")) <|> ((pDetectSpaces >>= withAttribute ErrorTok)) <|> ((pAnyChar "=#:" >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("Makefile","callVar{")) >> pDefault >>= withAttribute DataTypeTok)) parseRules ("Makefile","callFunc(") = (((pDetectChar False ')' >>= withAttribute CharTok) >>~ (popContext >> popContext >> popContext)) <|> ((pDetectChar False '$' >>= withAttribute CharTok) >>~ pushContext ("Makefile","dollar")) <|> ((pDetectChar False ',' >>= withAttribute KeywordTok)) <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext ("Makefile","string'")) <|> (currentContext >>= \x -> guard (x == ("Makefile","callFunc(")) >> pDefault >>= withAttribute StringTok)) parseRules ("Makefile","callFunc{") = (((pDetectChar False '}' >>= withAttribute CharTok) >>~ (popContext >> popContext >> popContext)) <|> ((pDetectChar False '$' >>= withAttribute CharTok) >>~ pushContext ("Makefile","dollar")) <|> ((pDetectChar False ',' >>= withAttribute KeywordTok)) <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext ("Makefile","string'")) <|> (currentContext >>= \x -> guard (x == ("Makefile","callFunc{")) >> pDefault >>= withAttribute StringTok)) parseRules x = parseRules ("Makefile","normal") <|> fail ("Unknown context" ++ show x)