{- This module was generated from data in the Kate syntax highlighting file awk.xml, version 0.92, by -} module Text.Highlighting.Kate.Syntax.Awk (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 = "AWK" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.awk" -- | 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 = [("AWK","Pattern")], 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 ("AWK","Pattern") -> return () ("AWK","Block") -> return () ("AWK","base") -> return () ("AWK","String") -> return () ("AWK","Comment") -> (popContext) >> pEndLine ("AWK","Escape") -> (popContext) >> pEndLine ("AWK","Match") -> (popContext) >> pEndLine ("AWK","Regex") -> return () ("AWK","regex") -> return () ("AWK","Regex Escape") -> (popContext) >> pEndLine ("AWK","RegexChar") -> (popContext) >> pEndLine ("AWK","InChar") -> return () ("AWK","CharClass") -> (popContext) >> pEndLine ("AWK","MatchPattern") -> (popContext) >> pEndLine ("AWK","RegexPattern") -> return () ("AWK","CheckRange") -> (popContext >> popContext >> popContext) >> pEndLine ("AWK","RangePattern") -> (popContext >> popContext >> popContext >> popContext) >> pEndLine ("AWK","Pattern2") -> 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 $ "if else while do for in continue break print printf getline function return next exit" list_builtins = Set.fromList $ words $ "ARGC ARGV CONVFMT ENVIRON FILENAME FNR FS NF NR OFMT OFS ORS RS RSTART RLENGTH SUBSEP" list_functions = Set.fromList $ words $ "gsub gensub index length match split sprintf sub substr tolower toupper atan2 cos exp int log rand sin sqrt srand close fflush system" list_special = Set.fromList $ words $ "BEGIN END" regex_'5c'24'5bA'2dZa'2dz0'2d9'5f'5d'2b = compileRegex True "\\$[A-Za-z0-9_]+" regex_'2e = compileRegex True "." regex_'5c'5b'3a'28'3f'3d'5b'5f'5cw'5d'5b'5f'5cd'5cw'5d'2a'3a'5c'5d'29 = compileRegex True "\\[:(?=[_\\w][_\\d\\w]*:\\])" regex_'28alpha'7calnum'7cblank'7ccntrl'7cdigit'7cgraph'7clower'7cpunct'7cspace'7cupper'7cxdigit'29'28'3f'3d'3a'5c'5d'29 = compileRegex True "(alpha|alnum|blank|cntrl|digit|graph|lower|punct|space|upper|xdigit)(?=:\\])" regex_'5cs'2a'2c'5cs'2a'28'3f'3d'2f'29 = compileRegex True "\\s*,\\s*(?=/)" parseRules ("AWK","Pattern") = (((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext ("AWK","Block")) <|> ((pDetectChar False '}' >>= withAttribute ErrorTok)) <|> ((pFirstNonSpace >> lookAhead (pDetectChar False '/') >> pushContext ("AWK","MatchPattern") >> currentContext >>= parseRules)) <|> ((parseRules ("AWK","base"))) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_special >>= withAttribute KeywordTok)) <|> (currentContext >>= \x -> guard (x == ("AWK","Pattern")) >> pDefault >>= withAttribute NormalTok)) parseRules ("AWK","Block") = (((pDetectChar False '}' >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext ("AWK","Block")) <|> ((parseRules ("AWK","base"))) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_special >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("AWK","Block")) >> pDefault >>= withAttribute NormalTok)) parseRules ("AWK","base") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("AWK","Comment")) <|> ((pDetectChar False '~' >>= withAttribute NormalTok) >>~ pushContext ("AWK","Match")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("AWK","String")) <|> ((pAnyChar "!%&*+,-./:;<=>?^|" >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_builtins >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_functions >>= withAttribute FunctionTok)) <|> ((pFloat >>= withAttribute FloatTok)) <|> ((pInt >>= withAttribute DecValTok)) <|> ((pRegExpr regex_'5c'24'5bA'2dZa'2dz0'2d9'5f'5d'2b >>= withAttribute DataTypeTok)) <|> (currentContext >>= \x -> guard (x == ("AWK","base")) >> pDefault >>= withAttribute NormalTok)) parseRules ("AWK","String") = (((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pHlCStringChar >>= withAttribute StringTok)) <|> ((pDetectChar False '\\' >>= withAttribute NormalTok) >>~ pushContext ("AWK","Escape")) <|> (currentContext >>= \x -> guard (x == ("AWK","String")) >> pDefault >>= withAttribute StringTok)) parseRules ("AWK","Comment") = (((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> (currentContext >>= \x -> guard (x == ("AWK","Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("AWK","Escape") = (((pRegExpr regex_'2e >>= withAttribute StringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("AWK","Escape")) >> pDefault >>= withAttribute NormalTok)) parseRules ("AWK","Match") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetect2Chars False '/' '^' >>= withAttribute OtherTok) >>~ pushContext ("AWK","Regex")) <|> ((pDetectChar False '/' >>= withAttribute OtherTok) >>~ pushContext ("AWK","Regex")) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("AWK","Regex") = (((parseRules ("AWK","regex"))) <|> ((pDetectChar False '/' >>= withAttribute OtherTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("AWK","Regex")) >> pDefault >>= withAttribute StringTok)) parseRules ("AWK","regex") = (((pHlCStringChar >>= withAttribute StringTok)) <|> ((pDetectChar False '\\' >>= withAttribute OtherTok) >>~ pushContext ("AWK","Regex Escape")) <|> ((pDetect2Chars False '[' '^' >>= withAttribute OtherTok) >>~ pushContext ("AWK","RegexChar")) <|> ((pDetectChar False '[' >>= withAttribute OtherTok) >>~ pushContext ("AWK","RegexChar")) <|> ((pAnyChar "$.+?*()|" >>= withAttribute OtherTok)) <|> (currentContext >>= \x -> guard (x == ("AWK","regex")) >> pDefault >>= withAttribute NormalTok)) parseRules ("AWK","Regex Escape") = (((pRegExpr regex_'2e >>= withAttribute StringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("AWK","Regex Escape")) >> pDefault >>= withAttribute NormalTok)) parseRules ("AWK","RegexChar") = (((pDetect2Chars False '-' ']' >>= withAttribute StringTok) >>~ pushContext ("AWK","InChar")) <|> ((pAnyChar "-]" >>= withAttribute StringTok) >>~ pushContext ("AWK","InChar")) <|> (pushContext ("AWK","InChar") >> currentContext >>= parseRules)) parseRules ("AWK","InChar") = (((pHlCStringChar >>= withAttribute StringTok)) <|> ((pDetectChar False '\\' >>= withAttribute OtherTok) >>~ pushContext ("AWK","Regex Escape")) <|> ((lookAhead (pDetect2Chars False '-' ']') >> pushContext ("AWK","Regex Escape") >> currentContext >>= parseRules)) <|> ((pDetectChar False ']' >>= withAttribute OtherTok) >>~ (popContext >> popContext)) <|> ((pDetectChar False '-' >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'5c'5b'3a'28'3f'3d'5b'5f'5cw'5d'5b'5f'5cd'5cw'5d'2a'3a'5c'5d'29 >>= withAttribute OtherTok) >>~ pushContext ("AWK","CharClass")) <|> (currentContext >>= \x -> guard (x == ("AWK","InChar")) >> pDefault >>= withAttribute StringTok)) parseRules ("AWK","CharClass") = (((pRegExpr regex_'28alpha'7calnum'7cblank'7ccntrl'7cdigit'7cgraph'7clower'7cpunct'7cspace'7cupper'7cxdigit'29'28'3f'3d'3a'5c'5d'29 >>= withAttribute StringTok)) <|> ((pDetect2Chars False ':' ']' >>= withAttribute OtherTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("AWK","CharClass")) >> pDefault >>= withAttribute StringTok)) parseRules ("AWK","MatchPattern") = (((pDetect2Chars False '/' '^' >>= withAttribute OtherTok) >>~ pushContext ("AWK","RegexPattern")) <|> ((pDetectChar False '/' >>= withAttribute OtherTok) >>~ pushContext ("AWK","RegexPattern")) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("AWK","RegexPattern") = (((parseRules ("AWK","regex"))) <|> ((pDetectChar False '/' >>= withAttribute OtherTok) >>~ pushContext ("AWK","CheckRange")) <|> (currentContext >>= \x -> guard (x == ("AWK","RegexPattern")) >> pDefault >>= withAttribute StringTok)) parseRules ("AWK","CheckRange") = (((pRegExpr regex_'5cs'2a'2c'5cs'2a'28'3f'3d'2f'29 >>= withAttribute NormalTok) >>~ pushContext ("AWK","RangePattern")) <|> ((popContext >> popContext >> popContext) >> currentContext >>= parseRules)) parseRules ("AWK","RangePattern") = (((pDetect2Chars False '/' '^' >>= withAttribute OtherTok) >>~ pushContext ("AWK","Pattern2")) <|> ((pDetectChar False '/' >>= withAttribute OtherTok) >>~ pushContext ("AWK","Pattern2")) <|> ((popContext >> popContext >> popContext >> popContext) >> currentContext >>= parseRules)) parseRules ("AWK","Pattern2") = (((parseRules ("AWK","regex"))) <|> ((pDetectChar False '/' >>= withAttribute OtherTok) >>~ (popContext >> popContext >> popContext >> popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("AWK","Pattern2")) >> pDefault >>= withAttribute StringTok)) parseRules ("Alerts", _) = Text.Highlighting.Kate.Syntax.Alert.parseExpression Nothing parseRules x = parseRules ("AWK","Pattern") <|> fail ("Unknown context" ++ show x)