{- This module was generated from data in the Kate syntax highlighting file awk.xml, version 0.91, 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 -- | 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 = [("AWK","Base")], 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","Base") -> return () ("AWK","String") -> return () ("AWK","Comment") -> (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 $ "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" regex_'5cb'28BEGIN'7cEND'29'5cb = compileRegex "\\b(BEGIN|END)\\b" regex_'5c'24'5bA'2dZa'2dz0'2d9'5f'5d'2b = compileRegex "\\$[A-Za-z0-9_]+" parseRules ("AWK","Base") = (((pRegExpr regex_'5cb'28BEGIN'7cEND'29'5cb >>= withAttribute StringTok)) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok)) <|> ((pDetectChar False '}' >>= withAttribute KeywordTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("AWK","Comment")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("AWK","String")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_builtins >>= withAttribute DataTypeTok)) <|> ((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 OtherTok)) <|> (currentContext >>= \x -> guard (x == ("AWK","Base")) >> pDefault >>= withAttribute NormalTok)) parseRules ("AWK","String") = (((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pHlCStringChar >>= withAttribute StringTok)) <|> (currentContext >>= \x -> guard (x == ("AWK","String")) >> pDefault >>= withAttribute StringTok)) parseRules ("AWK","Comment") = (((Text.Highlighting.Kate.Syntax.Alert.parseExpression >>= ((withAttribute CommentTok) . snd))) <|> (currentContext >>= \x -> guard (x == ("AWK","Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Alerts", _) = Text.Highlighting.Kate.Syntax.Alert.parseExpression parseRules x = parseRules ("AWK","Base") <|> fail ("Unknown context" ++ show x)