{- This module was generated from data in the Kate syntax highlighting file sed.xml, version 1.0, by Bart Sas (bart.sas@gmail.com) -} module Text.Highlighting.Kate.Syntax.Sed (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) -- | Full name of language. syntaxName :: String syntaxName = "sed" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.sed" -- | 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 = [("sed","BeginningOfLine")], 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 ("sed","BeginningOfLine") -> return () ("sed","FirstAddressRegex") -> pushContext ("sed","Error") >> return () ("sed","AfterFirstAddress") -> pushContext ("sed","BeginningOfLine") >> return () ("sed","AfterFirstAddress2") -> pushContext ("sed","BeginningOfLine") >> return () ("sed","SecondAddress") -> pushContext ("sed","Error") >> return () ("sed","SecondAddressRegex") -> pushContext ("sed","Error") >> return () ("sed","AfterSecondAddress") -> pushContext ("sed","Error") >> return () ("sed","Step") -> pushContext ("sed","Error") >> return () ("sed","Command") -> pushContext ("sed","Error") >> return () ("sed","SCommand") -> pushContext ("sed","Error") >> return () ("sed","SRegex") -> pushContext ("sed","Error") >> return () ("sed","SReplacement") -> pushContext ("sed","Error") >> return () ("sed","SFlags") -> pushContext ("sed","BeginningOfLine") >> return () ("sed","WFlag") -> pushContext ("sed","BeginningOfLine") >> return () ("sed","YCommand") -> pushContext ("sed","Error") >> return () ("sed","YSourceList") -> pushContext ("sed","Error") >> return () ("sed","YDestList") -> pushContext ("sed","Error") >> return () ("sed","AICCommand") -> pushContext ("sed","Error") >> return () ("sed","LiteralText") -> pushContext ("sed","BeginningOfLine") >> return () ("sed","BTCommand") -> pushContext ("sed","BeginningOfLine") >> return () ("sed","WRCommand") -> pushContext ("sed","Error") >> return () ("sed","LCommand") -> pushContext ("sed","BeginningOfLine") >> return () ("sed","QCommand") -> pushContext ("sed","BeginningOfLine") >> return () ("sed","Label") -> pushContext ("sed","Error") >> return () ("sed","AfterCommand") -> pushContext ("sed","BeginningOfLine") >> return () ("sed","Regex") -> pushContext ("sed","Error") >> return () ("sed","Comment") -> pushContext ("sed","BeginningOfLine") >> return () ("sed","Error") -> pushContext ("sed","BeginningOfLine") >> 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) regex_'28'2f'29 = compileRegex "(/)" regex_'5c'5c'28'5cS'29 = compileRegex "\\\\(\\S)" regex_'5cS = compileRegex "\\S" regex_'28'5cS'29 = compileRegex "(\\S)" regex_'5c'5c'5b0'2d9LlUuE'5c'5c'26'5d = compileRegex "\\\\[0-9LlUuE\\\\&]" regex_'5cS'2b = compileRegex "\\S+" regex_'5cw'2b = compileRegex "\\w+" parseRules ("sed","BeginningOfLine") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("sed","Comment")) <|> ((pRegExpr regex_'28'2f'29 >>= withAttribute StringTok) >>~ pushContext ("sed","FirstAddressRegex")) <|> ((pRegExpr regex_'5c'5c'28'5cS'29 >>= withAttribute StringTok) >>~ pushContext ("sed","FirstAddressRegex")) <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext ("sed","AfterFirstAddress")) <|> ((pDetectChar False '$' >>= withAttribute OtherTok) >>~ pushContext ("sed","AfterFirstAddress")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext ("sed","AfterCommand")) <|> ((pDetectChar False ':' >>= withAttribute FunctionTok) >>~ pushContext ("sed","Label")) <|> ((pDetectChar False '!' >>= withAttribute OtherTok) >>~ pushContext ("sed","Command")) <|> ((parseRules ("sed","Command"))) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext ("sed","Error")) <|> (currentContext >>= \x -> guard (x == ("sed","BeginningOfLine")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","FirstAddressRegex") = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "%1" >>= withAttribute StringTok) >>~ pushContext ("sed","AfterFirstAddress")) <|> ((parseRules ("sed","Regex"))) <|> (currentContext >>= \x -> guard (x == ("sed","FirstAddressRegex")) >> pDefault >>= withAttribute StringTok)) parseRules ("sed","AfterFirstAddress") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '!' >>= withAttribute OtherTok) >>~ pushContext ("sed","Command")) <|> ((parseRules ("sed","AfterFirstAddress2"))) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext ("sed","Error")) <|> (currentContext >>= \x -> guard (x == ("sed","AfterFirstAddress")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","AfterFirstAddress2") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False ',' >>= withAttribute NormalTok) >>~ pushContext ("sed","SecondAddress")) <|> ((pDetectChar False '~' >>= withAttribute NormalTok) >>~ pushContext ("sed","Step")) <|> ((parseRules ("sed","Command"))) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext ("sed","Error")) <|> (currentContext >>= \x -> guard (x == ("sed","AfterFirstAddress2")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","SecondAddress") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28'2f'29 >>= withAttribute StringTok) >>~ pushContext ("sed","SecondAddressRegex")) <|> ((pRegExpr regex_'5c'5c'28'5cS'29 >>= withAttribute StringTok) >>~ pushContext ("sed","SecondAddressRegex")) <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext ("sed","AfterSecondAddress")) <|> ((pDetectChar False '$' >>= withAttribute OtherTok) >>~ pushContext ("sed","AfterSecondAddress")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext ("sed","Error")) <|> (currentContext >>= \x -> guard (x == ("sed","SecondAddress")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","SecondAddressRegex") = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "%1" >>= withAttribute StringTok) >>~ pushContext ("sed","AfterSecondAddress")) <|> ((parseRules ("sed","Regex"))) <|> (currentContext >>= \x -> guard (x == ("sed","SecondAddressRegex")) >> pDefault >>= withAttribute StringTok)) parseRules ("sed","AfterSecondAddress") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '!' >>= withAttribute OtherTok) >>~ pushContext ("sed","Command")) <|> ((parseRules ("sed","Command"))) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext ("sed","Error")) <|> (currentContext >>= \x -> guard (x == ("sed","AfterSecondAddress")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","Step") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext ("sed","Command")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext ("sed","Error")) <|> (currentContext >>= \x -> guard (x == ("sed","Step")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","Command") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False 's' >>= withAttribute KeywordTok) >>~ pushContext ("sed","SCommand")) <|> ((pDetectChar False 'y' >>= withAttribute KeywordTok) >>~ pushContext ("sed","YCommand")) <|> ((pAnyChar "dpnDNPhHgGxFvz=" >>= withAttribute KeywordTok) >>~ pushContext ("sed","AfterCommand")) <|> ((pAnyChar "aic" >>= withAttribute KeywordTok) >>~ pushContext ("sed","AICCommand")) <|> ((pAnyChar "bTt" >>= withAttribute KeywordTok) >>~ pushContext ("sed","BTCommand")) <|> ((pAnyChar "WwrR" >>= withAttribute KeywordTok) >>~ pushContext ("sed","WRCommand")) <|> ((pAnyChar "lL" >>= withAttribute KeywordTok) >>~ pushContext ("sed","LCommand")) <|> ((pAnyChar "qQ" >>= withAttribute KeywordTok) >>~ pushContext ("sed","QCommand")) <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext ("sed","BeginningOfLine")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext ("sed","Error")) <|> (currentContext >>= \x -> guard (x == ("sed","Command")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","SCommand") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28'5cS'29 >>= withAttribute StringTok) >>~ pushContext ("sed","SRegex")) <|> (currentContext >>= \x -> guard (x == ("sed","SCommand")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","SRegex") = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "(%1)" >>= withAttribute StringTok) >>~ pushContext ("sed","SReplacement")) <|> ((parseRules ("sed","Regex"))) <|> (currentContext >>= \x -> guard (x == ("sed","SRegex")) >> pDefault >>= withAttribute StringTok)) parseRules ("sed","SReplacement") = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "%1" >>= withAttribute StringTok) >>~ pushContext ("sed","SFlags")) <|> ((pRegExpr regex_'5c'5c'5b0'2d9LlUuE'5c'5c'26'5d >>= withAttribute CharTok)) <|> ((pDetectChar False '&' >>= withAttribute CharTok)) <|> (currentContext >>= \x -> guard (x == ("sed","SReplacement")) >> pDefault >>= withAttribute StringTok)) parseRules ("sed","SFlags") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pAnyChar "gpeIiMm" >>= withAttribute DataTypeTok)) <|> ((pDetectChar False 'w' >>= withAttribute DataTypeTok) >>~ pushContext ("sed","WFlag")) <|> ((pInt >>= withAttribute DecValTok)) <|> ((parseRules ("sed","AfterCommand"))) <|> (currentContext >>= \x -> guard (x == ("sed","SFlags")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","WFlag") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cS'2b >>= withAttribute BaseNTok) >>~ pushContext ("sed","SFlags")) <|> (currentContext >>= \x -> guard (x == ("sed","WFlag")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","YCommand") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28'5cS'29 >>= withAttribute StringTok) >>~ pushContext ("sed","YSourceList")) <|> (currentContext >>= \x -> guard (x == ("sed","YCommand")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","YSourceList") = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "(%1)" >>= withAttribute StringTok) >>~ pushContext ("sed","YDestList")) <|> ((pDetect2Chars False '\\' 'n' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok)) <|> (currentContext >>= \x -> guard (x == ("sed","YSourceList")) >> pDefault >>= withAttribute StringTok)) parseRules ("sed","YDestList") = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "%1" >>= withAttribute StringTok) >>~ pushContext ("sed","AfterCommand")) <|> ((pDetect2Chars False '\\' 'n' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok)) <|> (currentContext >>= \x -> guard (x == ("sed","YDestList")) >> pDefault >>= withAttribute StringTok)) parseRules ("sed","AICCommand") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pLineContinue >>= withAttribute OtherTok) >>~ pushContext ("sed","LiteralText")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext ("sed","Error")) <|> (currentContext >>= \x -> guard (x == ("sed","AICCommand")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","LiteralText") = (((pDetect2Chars False '\\' '\\' >>= withAttribute OtherTok) >>~ pushContext ("sed","LiteralText")) <|> ((pLineContinue >>= withAttribute OtherTok) >>~ pushContext ("sed","LiteralText")) <|> ((pDetectChar False '\\' >>= withAttribute ErrorTok) >>~ pushContext ("sed","Error")) <|> (currentContext >>= \x -> guard (x == ("sed","LiteralText")) >> pDefault >>= withAttribute OtherTok)) parseRules ("sed","BTCommand") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cw'2b >>= withAttribute FunctionTok) >>~ pushContext ("sed","AfterCommand")) <|> ((parseRules ("sed","AfterCommand"))) <|> (currentContext >>= \x -> guard (x == ("sed","BTCommand")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","WRCommand") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cS'2b >>= withAttribute BaseNTok) >>~ pushContext ("sed","AfterCommand")) <|> (currentContext >>= \x -> guard (x == ("sed","WRCommand")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","LCommand") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext ("sed","AfterCommand")) <|> ((parseRules ("sed","AfterCommand"))) <|> (currentContext >>= \x -> guard (x == ("sed","LCommand")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","QCommand") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext ("sed","AfterCommand")) <|> ((parseRules ("sed","AfterCommand"))) <|> (currentContext >>= \x -> guard (x == ("sed","QCommand")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","Label") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cw'2b >>= withAttribute FunctionTok) >>~ pushContext ("sed","AfterCommand")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext ("sed","Error")) <|> (currentContext >>= \x -> guard (x == ("sed","Label")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","AfterCommand") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False ';' >>= withAttribute NormalTok) >>~ pushContext ("sed","BeginningOfLine")) <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext ("sed","AfterCommand")) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("sed","Comment")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext ("sed","Error")) <|> (currentContext >>= \x -> guard (x == ("sed","AfterCommand")) >> pDefault >>= withAttribute NormalTok)) parseRules ("sed","Regex") = (((pDetect2Chars False '\\' '(' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '+' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '?' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '|' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '{' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '}' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '[' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '.' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '*' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '^' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '$' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' 'n' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' 't' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '0' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '1' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '2' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '3' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '4' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '5' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '6' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '7' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '8' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '9' >>= withAttribute CharTok)) <|> ((pDetectChar False '*' >>= withAttribute CharTok)) <|> ((pDetectChar False '.' >>= withAttribute CharTok)) <|> ((pDetectChar False '^' >>= withAttribute CharTok)) <|> ((pDetectChar False '$' >>= withAttribute CharTok)) <|> ((pDetectChar False '[' >>= withAttribute CharTok)) <|> ((pDetectChar False ']' >>= withAttribute CharTok)) <|> (currentContext >>= \x -> guard (x == ("sed","Regex")) >> pDefault >>= withAttribute StringTok)) parseRules ("sed","Comment") = (currentContext >>= \x -> guard (x == ("sed","Comment")) >> pDefault >>= withAttribute CommentTok) parseRules ("sed","Error") = (currentContext >>= \x -> guard (x == ("sed","Error")) >> pDefault >>= withAttribute ErrorTok) parseRules x = parseRules ("sed","BeginningOfLine") <|> fail ("Unknown context" ++ show x)