{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Sed (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex syntax :: Syntax syntax = Syntax { sName = "sed" , sFilename = "sed.xml" , sShortname = "Sed" , sContexts = fromList [ ( "AICCommand" , Context { cName = "AICCommand" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = LineContinue , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "LiteralText" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Error" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "AfterCommand" , Context { cName = "AfterCommand" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar ';' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "BeginningOfLine" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterCommand" ) ] } , Rule { rMatcher = DetectChar '#' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Error" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "BeginningOfLine" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "AfterFirstAddress" , Context { cName = "AfterFirstAddress" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '!' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Command" ) ] } , Rule { rMatcher = IncludeRules ( "sed" , "AfterFirstAddress2" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Error" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "BeginningOfLine" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "AfterFirstAddress2" , Context { cName = "AfterFirstAddress2" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar ',' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "SecondAddress" ) ] } , Rule { rMatcher = DetectChar '~' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Step" ) ] } , Rule { rMatcher = IncludeRules ( "sed" , "Command" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Error" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "BeginningOfLine" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "AfterSecondAddress" , Context { cName = "AfterSecondAddress" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '!' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Command" ) ] } , Rule { rMatcher = IncludeRules ( "sed" , "Command" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Error" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "BTCommand" , Context { cName = "BTCommand" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\w+" , reCompiled = Just (compileRegex True "\\w+") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterCommand" ) ] } , Rule { rMatcher = IncludeRules ( "sed" , "AfterCommand" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "BeginningOfLine" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "BeginningOfLine" , Context { cName = "BeginningOfLine" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '#' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(/)" , reCompiled = Just (compileRegex True "(/)") , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "FirstAddressRegex" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(\\S)" , reCompiled = Just (compileRegex True "\\\\(\\S)") , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "FirstAddressRegex" ) ] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterFirstAddress" ) ] } , Rule { rMatcher = DetectChar '$' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterFirstAddress" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterCommand" ) ] } , Rule { rMatcher = DetectChar ':' , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Label" ) ] } , Rule { rMatcher = DetectChar '!' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Command" ) ] } , Rule { rMatcher = IncludeRules ( "sed" , "Command" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Error" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Command" , Context { cName = "Command" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar 's' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "SCommand" ) ] } , Rule { rMatcher = DetectChar 'y' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "YCommand" ) ] } , Rule { rMatcher = AnyChar "dpnDNPhHgGxFvz=" , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterCommand" ) ] } , Rule { rMatcher = AnyChar "aic" , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AICCommand" ) ] } , Rule { rMatcher = AnyChar "bTt" , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "BTCommand" ) ] } , Rule { rMatcher = AnyChar "WwrR" , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "WRCommand" ) ] } , Rule { rMatcher = AnyChar "lL" , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "LCommand" ) ] } , Rule { rMatcher = AnyChar "qQ" , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "QCommand" ) ] } , Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "BeginningOfLine" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Error" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Comment" , Context { cName = "Comment" , cSyntax = "sed" , cRules = [] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "BeginningOfLine" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Error" , Context { cName = "Error" , cSyntax = "sed" , cRules = [] , cAttribute = ErrorTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "BeginningOfLine" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FirstAddressRegex" , Context { cName = "FirstAddressRegex" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterFirstAddress" ) ] } , Rule { rMatcher = IncludeRules ( "sed" , "Regex" ) , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "LCommand" , Context { cName = "LCommand" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterCommand" ) ] } , Rule { rMatcher = IncludeRules ( "sed" , "AfterCommand" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "BeginningOfLine" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Label" , Context { cName = "Label" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\w+" , reCompiled = Just (compileRegex True "\\w+") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterCommand" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Error" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "LiteralText" , Context { cName = "LiteralText" , cSyntax = "sed" , cRules = [ Rule { rMatcher = Detect2Chars '\\' '\\' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "LiteralText" ) ] } , Rule { rMatcher = LineContinue , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "LiteralText" ) ] } , Rule { rMatcher = DetectChar '\\' , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Error" ) ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "BeginningOfLine" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "QCommand" , Context { cName = "QCommand" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterCommand" ) ] } , Rule { rMatcher = IncludeRules ( "sed" , "AfterCommand" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "BeginningOfLine" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Regex" , Context { cName = "Regex" , cSyntax = "sed" , cRules = [ Rule { rMatcher = Detect2Chars '\\' '(' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' ')' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '+' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '?' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '|' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '{' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '}' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '[' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' ']' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '.' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '*' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '\\' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '^' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '$' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' 'n' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' 't' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '0' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '1' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '2' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '3' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '4' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '5' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '6' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '7' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '8' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '9' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '*' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '.' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '^' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '$' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '[' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar ']' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SCommand" , Context { cName = "SCommand" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(\\S)" , reCompiled = Just (compileRegex True "(\\S)") , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "SRegex" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SFlags" , Context { cName = "SFlags" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = AnyChar "gpeIiMm" , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar 'w' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "WFlag" ) ] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "sed" , "AfterCommand" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "BeginningOfLine" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SRegex" , Context { cName = "SRegex" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(%1)" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "SReplacement" ) ] } , Rule { rMatcher = IncludeRules ( "sed" , "Regex" ) , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "SReplacement" , Context { cName = "SReplacement" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "SFlags" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\[0-9LlUuE\\\\&]" , reCompiled = Just (compileRegex True "\\\\[0-9LlUuE\\\\&]") , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '&' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "SecondAddress" , Context { cName = "SecondAddress" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(/)" , reCompiled = Just (compileRegex True "(/)") , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "SecondAddressRegex" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\(\\S)" , reCompiled = Just (compileRegex True "\\\\(\\S)") , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "SecondAddressRegex" ) ] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterSecondAddress" ) ] } , Rule { rMatcher = DetectChar '$' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterSecondAddress" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Error" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SecondAddressRegex" , Context { cName = "SecondAddressRegex" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterSecondAddress" ) ] } , Rule { rMatcher = IncludeRules ( "sed" , "Regex" ) , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "Step" , Context { cName = "Step" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Command" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\S" , reCompiled = Just (compileRegex True "\\S") , reCaseSensitive = True } , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "Error" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "WFlag" , Context { cName = "WFlag" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\S+" , reCompiled = Just (compileRegex True "\\S+") , reCaseSensitive = True } , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "SFlags" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "BeginningOfLine" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "WRCommand" , Context { cName = "WRCommand" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\S+" , reCompiled = Just (compileRegex True "\\S+") , reCaseSensitive = True } , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterCommand" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "YCommand" , Context { cName = "YCommand" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(\\S)" , reCompiled = Just (compileRegex True "(\\S)") , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "YSourceList" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "YDestList" , Context { cName = "YDestList" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "AfterCommand" ) ] } , Rule { rMatcher = Detect2Chars '\\' 'n' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '\\' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "YSourceList" , Context { cName = "YSourceList" , cSyntax = "sed" , cRules = [ Rule { rMatcher = DetectSpaces , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "(%1)" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "sed" , "YDestList" ) ] } , Rule { rMatcher = Detect2Chars '\\' 'n' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '\\' , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "sed" , "Error" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) ] , sAuthor = "Bart Sas (bart.sas@gmail.com)" , sVersion = "2" , sLicense = "GPL" , sExtensions = [ "*.sed" ] , sStartingContext = "BeginningOfLine" }