{- This module was generated from data in the Kate syntax highlighting file m4.xml, version 1.1, by Jaak Ristioja -} module Text.Highlighting.Kate.Syntax.M4 (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 = "GNU M4" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.m4;" -- | 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 = [("GNU M4","Normal Text")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStContinuation = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext contexts <- synStContexts `fmap` getState st <- getState if length contexts >= 2 then case context of _ | synStContinuation st -> updateState $ \st -> st{ synStContinuation = False } ("GNU M4","Normal Text") -> return () ("GNU M4","inparenthesis") -> 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_optbuiltins = Set.fromList $ words $ "__gnu__ __os2__ os2 __unix__ unix __windows__ windows" list_m4'5foptbuiltins = Set.fromList $ words $ "m4___gnu__ m4___os2__ m4_os2 m4___unix__ m4_unix m4___windows__ m4_windows" list_builtins = Set.fromList $ words $ "__file__ __line__ __program__ builtin changecom changequote changeword debugfile debugmode decr define defn divert divnum dnl dumpdef errprint esyscmd eval format ifdef ifelse include incr index indir len m4exit m4wrap maketemp mkstemp patsubst popdef pushdef regexp shift sinclude substr syscmd sysval traceon traceoff translit undefine undivert" list_m4'5fbuiltins = Set.fromList $ words $ "m4___file__ m4___line__ m4___program__ m4_builtin m4_changecom m4_changequote m4_changeword m4_debugfile m4_debugmode m4_decr m4_define m4_defn m4_divert m4_divnum m4_dnl m4_dumpdef m4_errprint m4_esyscmd m4_eval m4_format m4_ifdef m4_ifelse m4_include m4_incr m4_index m4_indir m4_len m4_m4exit m4_m4wrap m4_maketemp m4_mkstemp m4_patsubst m4_popdef m4_pushdef m4_regexp m4_shift m4_sinclude m4_substr m4_syscmd m4_sysval m4_traceon m4_traceoff m4_translit m4_undefine m4_undivert" regex_'5ba'2dzA'2dZ'5f'5d'5cw'2b = compileRegex True "[a-zA-Z_]\\w+" regex_'5c'24'28'5b1'2d9'5d'5cd'2a'7c0'7c'5c'23'7c'5c'2a'7c'5c'40'7c'5c'7b'28'5b1'2d9'5d'5cd'2a'7c0'29'5c'7d'29 = compileRegex True "\\$([1-9]\\d*|0|\\#|\\*|\\@|\\{([1-9]\\d*|0)\\})" regex_'28'5b1'2d9'5d'5cd'2a'7c0'7c0x'5b0'2d9abcdefABCDEF'5d'2b'29 = compileRegex True "([1-9]\\d*|0|0x[0-9abcdefABCDEF]+)" regex_'23'2e'2a'24 = compileRegex True "#.*$" regex_'5b'2b'2a'2f'25'5c'7c'3d'5c'21'3c'3e'21'5e'26'7e'2d'5d = compileRegex True "[+*/%\\|=\\!<>!^&~-]" parseRules ("GNU M4","Normal Text") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_builtins >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_m4'5fbuiltins >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_optbuiltins >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_m4'5foptbuiltins >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5f'5d'5cw'2b >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5c'24'28'5b1'2d9'5d'5cd'2a'7c0'7c'5c'23'7c'5c'2a'7c'5c'40'7c'5c'7b'28'5b1'2d9'5d'5cd'2a'7c0'29'5c'7d'29 >>= withAttribute CharTok)) <|> ((pRegExpr regex_'28'5b1'2d9'5d'5cd'2a'7c0'7c0x'5b0'2d9abcdefABCDEF'5d'2b'29 >>= withAttribute DecValTok)) <|> ((pRegExpr regex_'23'2e'2a'24 >>= withAttribute CommentTok)) <|> ((pDetectChar False ',' >>= withAttribute CharTok)) <|> ((pDetectChar False '(' >>= withAttribute CharTok) >>~ pushContext ("GNU M4","inparenthesis")) <|> ((pDetectChar False ')' >>= withAttribute CharTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b'2b'2a'2f'25'5c'7c'3d'5c'21'3c'3e'21'5e'26'7e'2d'5d >>= withAttribute CharTok)) <|> (currentContext >>= \x -> guard (x == ("GNU M4","Normal Text")) >> pDefault >>= withAttribute NormalTok)) parseRules ("GNU M4","inparenthesis") = (((parseRules ("GNU M4","Normal Text"))) <|> (currentContext >>= \x -> guard (x == ("GNU M4","inparenthesis")) >> pDefault >>= withAttribute NormalTok)) parseRules x = parseRules ("GNU M4","Normal Text") <|> fail ("Unknown context" ++ show x)