{- 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 Data.Map (fromList) import Control.Monad.State import Data.Char (isSpace) import Data.Maybe (fromMaybe) -- | 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 parseExpressionInternal pEndLine -- | Parse an expression using appropriate local context. parseExpression :: KateParser Token parseExpression = do st <- getState let oldLang = synStLanguage st setState $ st { synStLanguage = "sed" } context <- currentContext <|> (pushContext "BeginningOfLine" >> currentContext) result <- parseRules context optional $ eof >> pEndLine updateState $ \st -> st { synStLanguage = oldLang } return result startingState = SyntaxState {synStContexts = fromList [("sed",["BeginningOfLine"])], synStLanguage = "sed", synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext case context of "BeginningOfLine" -> return () "FirstAddressRegex" -> pushContext "Error" >> return () "AfterFirstAddress" -> pushContext "BeginningOfLine" >> return () "AfterFirstAddress2" -> pushContext "BeginningOfLine" >> return () "SecondAddress" -> pushContext "Error" >> return () "SecondAddressRegex" -> pushContext "Error" >> return () "AfterSecondAddress" -> pushContext "Error" >> return () "Step" -> pushContext "Error" >> return () "Command" -> pushContext "Error" >> return () "SCommand" -> pushContext "Error" >> return () "SRegex" -> pushContext "Error" >> return () "SReplacement" -> pushContext "Error" >> return () "SFlags" -> pushContext "BeginningOfLine" >> return () "WFlag" -> pushContext "BeginningOfLine" >> return () "YCommand" -> pushContext "Error" >> return () "YSourceList" -> pushContext "Error" >> return () "YDestList" -> pushContext "Error" >> return () "AICCommand" -> pushContext "Error" >> return () "LiteralText" -> pushContext "BeginningOfLine" >> return () "BTCommand" -> pushContext "BeginningOfLine" >> return () "WRCommand" -> pushContext "Error" >> return () "LCommand" -> pushContext "BeginningOfLine" >> return () "QCommand" -> pushContext "BeginningOfLine" >> return () "Label" -> pushContext "Error" >> return () "AfterCommand" -> pushContext "BeginningOfLine" >> return () "Regex" -> pushContext "Error" >> return () "Comment" -> pushContext "BeginningOfLine" >> return () "Error" -> pushContext "BeginningOfLine" >> return () _ -> 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) parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe NormalTok $ lookup context defaultAttributes)) 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+" defaultAttributes = [("BeginningOfLine",NormalTok),("FirstAddressRegex",StringTok),("AfterFirstAddress",NormalTok),("AfterFirstAddress2",NormalTok),("SecondAddress",NormalTok),("SecondAddressRegex",StringTok),("AfterSecondAddress",NormalTok),("Step",NormalTok),("Command",NormalTok),("SCommand",NormalTok),("SRegex",StringTok),("SReplacement",StringTok),("SFlags",NormalTok),("WFlag",NormalTok),("YCommand",NormalTok),("YSourceList",StringTok),("YDestList",StringTok),("AICCommand",NormalTok),("LiteralText",OtherTok),("BTCommand",NormalTok),("WRCommand",NormalTok),("LCommand",NormalTok),("QCommand",NormalTok),("Label",NormalTok),("AfterCommand",NormalTok),("Regex",StringTok),("Comment",CommentTok),("Error",ErrorTok)] parseRules "BeginningOfLine" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext "Comment") <|> ((pRegExpr regex_'28'2f'29 >>= withAttribute StringTok) >>~ pushContext "FirstAddressRegex") <|> ((pRegExpr regex_'5c'5c'28'5cS'29 >>= withAttribute StringTok) >>~ pushContext "FirstAddressRegex") <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext "AfterFirstAddress") <|> ((pDetectChar False '$' >>= withAttribute OtherTok) >>~ pushContext "AfterFirstAddress") <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext "AfterCommand") <|> ((pDetectChar False ':' >>= withAttribute FunctionTok) >>~ pushContext "Label") <|> ((pDetectChar False '!' >>= withAttribute OtherTok) >>~ pushContext "Command") <|> ((parseRules "Command")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext "Error")) parseRules "FirstAddressRegex" = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "%1" >>= withAttribute StringTok) >>~ pushContext "AfterFirstAddress") <|> ((parseRules "Regex"))) parseRules "AfterFirstAddress" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '!' >>= withAttribute OtherTok) >>~ pushContext "Command") <|> ((parseRules "AfterFirstAddress2")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext "Error")) parseRules "AfterFirstAddress2" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False ',' >>= withAttribute NormalTok) >>~ pushContext "SecondAddress") <|> ((pDetectChar False '~' >>= withAttribute NormalTok) >>~ pushContext "Step") <|> ((parseRules "Command")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext "Error")) parseRules "SecondAddress" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28'2f'29 >>= withAttribute StringTok) >>~ pushContext "SecondAddressRegex") <|> ((pRegExpr regex_'5c'5c'28'5cS'29 >>= withAttribute StringTok) >>~ pushContext "SecondAddressRegex") <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext "AfterSecondAddress") <|> ((pDetectChar False '$' >>= withAttribute OtherTok) >>~ pushContext "AfterSecondAddress") <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext "Error")) parseRules "SecondAddressRegex" = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "%1" >>= withAttribute StringTok) >>~ pushContext "AfterSecondAddress") <|> ((parseRules "Regex"))) parseRules "AfterSecondAddress" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False '!' >>= withAttribute OtherTok) >>~ pushContext "Command") <|> ((parseRules "Command")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext "Error")) parseRules "Step" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext "Command") <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext "Error")) parseRules "Command" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False 's' >>= withAttribute KeywordTok) >>~ pushContext "SCommand") <|> ((pDetectChar False 'y' >>= withAttribute KeywordTok) >>~ pushContext "YCommand") <|> ((pAnyChar "dpnDNPhHgGxFvz=" >>= withAttribute KeywordTok) >>~ pushContext "AfterCommand") <|> ((pAnyChar "aic" >>= withAttribute KeywordTok) >>~ pushContext "AICCommand") <|> ((pAnyChar "bTt" >>= withAttribute KeywordTok) >>~ pushContext "BTCommand") <|> ((pAnyChar "WwrR" >>= withAttribute KeywordTok) >>~ pushContext "WRCommand") <|> ((pAnyChar "lL" >>= withAttribute KeywordTok) >>~ pushContext "LCommand") <|> ((pAnyChar "qQ" >>= withAttribute KeywordTok) >>~ pushContext "QCommand") <|> ((pDetectChar False '{' >>= withAttribute NormalTok) >>~ pushContext "BeginningOfLine") <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext "Error")) parseRules "SCommand" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28'5cS'29 >>= withAttribute StringTok) >>~ pushContext "SRegex")) parseRules "SRegex" = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "(%1)" >>= withAttribute StringTok) >>~ pushContext "SReplacement") <|> ((parseRules "Regex"))) parseRules "SReplacement" = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "%1" >>= withAttribute StringTok) >>~ pushContext "SFlags") <|> ((pRegExpr regex_'5c'5c'5b0'2d9LlUuE'5c'5c'26'5d >>= withAttribute CharTok)) <|> ((pDetectChar False '&' >>= withAttribute CharTok))) parseRules "SFlags" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pAnyChar "gpeIiMm" >>= withAttribute DataTypeTok)) <|> ((pDetectChar False 'w' >>= withAttribute DataTypeTok) >>~ pushContext "WFlag") <|> ((pInt >>= withAttribute DecValTok)) <|> ((parseRules "AfterCommand"))) parseRules "WFlag" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cS'2b >>= withAttribute BaseNTok) >>~ pushContext "SFlags")) parseRules "YCommand" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28'5cS'29 >>= withAttribute StringTok) >>~ pushContext "YSourceList")) parseRules "YSourceList" = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "(%1)" >>= withAttribute StringTok) >>~ pushContext "YDestList") <|> ((pDetect2Chars False '\\' 'n' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok))) parseRules "YDestList" = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pRegExprDynamic "\\\\%1" >>= withAttribute CharTok)) <|> ((pRegExprDynamic "%1" >>= withAttribute StringTok) >>~ pushContext "AfterCommand") <|> ((pDetect2Chars False '\\' 'n' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok))) parseRules "AICCommand" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pLineContinue >>= withAttribute OtherTok) >>~ pushContext "LiteralText") <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext "Error")) parseRules "LiteralText" = (((pDetect2Chars False '\\' '\\' >>= withAttribute OtherTok) >>~ pushContext "LiteralText") <|> ((pLineContinue >>= withAttribute OtherTok) >>~ pushContext "LiteralText") <|> ((pDetectChar False '\\' >>= withAttribute ErrorTok) >>~ pushContext "Error")) parseRules "BTCommand" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cw'2b >>= withAttribute FunctionTok) >>~ pushContext "AfterCommand") <|> ((parseRules "AfterCommand"))) parseRules "WRCommand" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cS'2b >>= withAttribute BaseNTok) >>~ pushContext "AfterCommand")) parseRules "LCommand" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext "AfterCommand") <|> ((parseRules "AfterCommand"))) parseRules "QCommand" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pInt >>= withAttribute DecValTok) >>~ pushContext "AfterCommand") <|> ((parseRules "AfterCommand"))) parseRules "Label" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5cw'2b >>= withAttribute FunctionTok) >>~ pushContext "AfterCommand") <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext "Error")) parseRules "AfterCommand" = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pDetectChar False ';' >>= withAttribute NormalTok) >>~ pushContext "BeginningOfLine") <|> ((pDetectChar False '}' >>= withAttribute NormalTok) >>~ pushContext "AfterCommand") <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext "Comment") <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok) >>~ pushContext "Error")) parseRules "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))) parseRules "Comment" = pzero parseRules "Error" = pzero parseRules "" = parseRules "BeginningOfLine" parseRules x = fail $ "Unknown context" ++ x