{- This module was generated from data in the Kate syntax highlighting file lex.xml, version 2, by Jan Villat (jan.villat@net2000.ch) -} module Text.Highlighting.Kate.Syntax.Lex (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Cpp import Text.ParserCombinators.Parsec hiding (State) import Control.Monad.State import Data.Char (isSpace) -- | Full name of language. syntaxName :: String syntaxName = "Lex/Flex" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.l;*.lex;*.flex" -- | 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 = [("Lex/Flex","Pre Start")], 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 } ("Lex/Flex","Pre Start") -> return () ("Lex/Flex","Definitions") -> return () ("Lex/Flex","Rules") -> return () ("Lex/Flex","User Code") -> return () ("Lex/Flex","Percent Command") -> (popContext) >> pEndLine ("Lex/Flex","Comment") -> return () ("Lex/Flex","Definition RegExpr") -> (popContext) >> pEndLine ("Lex/Flex","Rule RegExpr") -> (popContext) >> pEndLine ("Lex/Flex","RegExpr (") -> return () ("Lex/Flex","RegExpr [") -> return () ("Lex/Flex","RegExpr {") -> return () ("Lex/Flex","RegExpr Q") -> return () ("Lex/Flex","RegExpr Base") -> return () ("Lex/Flex","Start Conditions Scope") -> return () ("Lex/Flex","Action") -> (popContext) >> pEndLine ("Lex/Flex","Detect C") -> return () ("Lex/Flex","Indented C") -> (popContext) >> pEndLine ("Lex/Flex","Lex C Bloc") -> return () ("Lex/Flex","Lex Rule C Bloc") -> return () ("Lex/Flex","Normal C Bloc") -> return () ("Lex/Flex","Action C") -> (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) regex_'2e = compileRegex True "." regex_'5bA'2dZa'2dz'5f'5d'5cw'2a'5cs'2b = compileRegex True "[A-Za-z_]\\w*\\s+" regex_'5cS = compileRegex True "\\S" regex_'2e'2a = compileRegex True ".*" regex_'5c'7b'24 = compileRegex True "\\{$" regex_'5cs'2b = compileRegex True "\\s+" regex_'5c'5c'2e = compileRegex True "\\\\." regex_'5cs'2a'5c'7d = compileRegex True "\\s*\\}" regex_'5cs'2a = compileRegex True "\\s*" regex_'5c'7c'5cs'2a'24 = compileRegex True "\\|\\s*$" regex_'5cs = compileRegex True "\\s" parseRules ("Lex/Flex","Pre Start") = (((lookAhead (pRegExpr regex_'2e) >> pushContext ("Lex/Flex","Definitions") >> currentContext >>= parseRules)) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","Pre Start")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Lex/Flex","Definitions") = (((parseRules ("Lex/Flex","Detect C"))) <|> ((pDetect2Chars False '%' '%' >>= withAttribute BaseNTok) >>~ pushContext ("Lex/Flex","Rules")) <|> ((pDetectChar False '%' >>= withAttribute KeywordTok) >>~ pushContext ("Lex/Flex","Percent Command")) <|> ((pColumn 0 >> pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("Lex/Flex","Comment")) <|> ((pColumn 0 >> pRegExpr regex_'5bA'2dZa'2dz'5f'5d'5cw'2a'5cs'2b >>= withAttribute DataTypeTok) >>~ pushContext ("Lex/Flex","Definition RegExpr")) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","Definitions")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Lex/Flex","Rules") = (((parseRules ("Lex/Flex","Detect C"))) <|> ((pDetect2Chars False '%' '%' >>= withAttribute BaseNTok) >>~ pushContext ("Lex/Flex","User Code")) <|> (pushContext ("Lex/Flex","Rule RegExpr") >> currentContext >>= parseRules)) parseRules ("Lex/Flex","User Code") = (((Text.Highlighting.Kate.Syntax.Cpp.parseExpression (Just ("C++","")))) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","User Code")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Lex/Flex","Percent Command") = (currentContext >>= \x -> guard (x == ("Lex/Flex","Percent Command")) >> pDefault >>= withAttribute KeywordTok) parseRules ("Lex/Flex","Comment") = (((pDetect2Chars False '*' '/' >>= withAttribute CommentTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Lex/Flex","Definition RegExpr") = (((parseRules ("Lex/Flex","RegExpr Base"))) <|> ((pRegExpr regex_'5cS >>= withAttribute StringTok)) <|> ((pRegExpr regex_'2e'2a >>= withAttribute AlertTok)) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","Definition RegExpr")) >> pDefault >>= withAttribute StringTok)) parseRules ("Lex/Flex","Rule RegExpr") = (((pRegExpr regex_'5c'7b'24 >>= withAttribute BaseNTok) >>~ pushContext ("Lex/Flex","Start Conditions Scope")) <|> ((parseRules ("Lex/Flex","RegExpr Base"))) <|> ((pRegExpr regex_'5cS >>= withAttribute StringTok)) <|> ((pRegExpr regex_'5cs'2b >>= withAttribute NormalTok) >>~ pushContext ("Lex/Flex","Action")) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","Rule RegExpr")) >> pDefault >>= withAttribute StringTok)) parseRules ("Lex/Flex","RegExpr (") = (((parseRules ("Lex/Flex","RegExpr Base"))) <|> ((pDetectChar False ')' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pRegExpr regex_'2e >>= withAttribute StringTok)) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","RegExpr (")) >> pDefault >>= withAttribute StringTok)) parseRules ("Lex/Flex","RegExpr [") = (((pRegExpr regex_'5c'5c'2e >>= withAttribute StringTok)) <|> ((pDetectChar False ']' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pRegExpr regex_'2e >>= withAttribute StringTok)) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","RegExpr [")) >> pDefault >>= withAttribute StringTok)) parseRules ("Lex/Flex","RegExpr {") = (((pRegExpr regex_'5c'5c'2e >>= withAttribute StringTok)) <|> ((pDetectChar False '}' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pRegExpr regex_'2e >>= withAttribute StringTok)) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","RegExpr {")) >> pDefault >>= withAttribute StringTok)) parseRules ("Lex/Flex","RegExpr Q") = (((pRegExpr regex_'5c'5c'2e >>= withAttribute StringTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pRegExpr regex_'2e >>= withAttribute StringTok)) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","RegExpr Q")) >> pDefault >>= withAttribute StringTok)) parseRules ("Lex/Flex","RegExpr Base") = (((pRegExpr regex_'5c'5c'2e >>= withAttribute StringTok)) <|> ((pDetectChar False '(' >>= withAttribute StringTok) >>~ pushContext ("Lex/Flex","RegExpr (")) <|> ((pDetectChar False '[' >>= withAttribute StringTok) >>~ pushContext ("Lex/Flex","RegExpr [")) <|> ((pDetectChar False '{' >>= withAttribute StringTok) >>~ pushContext ("Lex/Flex","RegExpr {")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Lex/Flex","RegExpr Q")) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","RegExpr Base")) >> pDefault >>= withAttribute StringTok)) parseRules ("Lex/Flex","Start Conditions Scope") = (((pRegExpr regex_'5cs'2a'5c'7d >>= withAttribute BaseNTok) >>~ (popContext)) <|> ((pRegExpr regex_'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("Lex/Flex","Rule RegExpr")) <|> (pushContext ("Lex/Flex","Rule RegExpr") >> currentContext >>= parseRules)) parseRules ("Lex/Flex","Action") = (((pRegExpr regex_'5c'7c'5cs'2a'24 >>= withAttribute KeywordTok)) <|> ((pDetect2Chars False '%' '{' >>= withAttribute BaseNTok) >>~ pushContext ("Lex/Flex","Lex Rule C Bloc")) <|> (pushContext ("Lex/Flex","Action C") >> currentContext >>= parseRules)) parseRules ("Lex/Flex","Detect C") = (((pColumn 0 >> pRegExpr regex_'5cs >>= withAttribute NormalTok) >>~ pushContext ("Lex/Flex","Indented C")) <|> ((pColumn 0 >> pDetect2Chars False '%' '{' >>= withAttribute BaseNTok) >>~ pushContext ("Lex/Flex","Lex C Bloc")) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","Detect C")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Lex/Flex","Indented C") = (((Text.Highlighting.Kate.Syntax.Cpp.parseExpression (Just ("C++","")))) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","Indented C")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Lex/Flex","Lex C Bloc") = (((pColumn 0 >> pDetect2Chars False '%' '}' >>= withAttribute BaseNTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Cpp.parseExpression (Just ("C++","")))) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","Lex C Bloc")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Lex/Flex","Lex Rule C Bloc") = (((pDetect2Chars False '%' '}' >>= withAttribute BaseNTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Cpp.parseExpression (Just ("C++","")))) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","Lex Rule C Bloc")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Lex/Flex","Normal C Bloc") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("Lex/Flex","Normal C Bloc")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Cpp.parseExpression (Just ("C++","")))) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","Normal C Bloc")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Lex/Flex","Action C") = (((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("Lex/Flex","Normal C Bloc")) <|> ((pDetectChar False '}' >>= withAttribute AlertTok)) <|> ((Text.Highlighting.Kate.Syntax.Cpp.parseExpression (Just ("C++","")))) <|> (currentContext >>= \x -> guard (x == ("Lex/Flex","Action C")) >> pDefault >>= withAttribute NormalTok)) parseRules ("C++", _) = Text.Highlighting.Kate.Syntax.Cpp.parseExpression Nothing parseRules x = parseRules ("Lex/Flex","Pre Start") <|> fail ("Unknown context" ++ show x)