{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Bash (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "Bash" , sFilename = "bash.xml" , sShortname = "Bash" , sContexts = fromList [ ( "Assign" , Context { cName = "Assign" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '(' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "AssignArray" ) ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindOthers" ) , 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 = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "AssignArray" , Context { cName = "AssignArray" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar ')' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '[' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Subscript" ) ] } , Rule { rMatcher = DetectChar '=' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Assign" ) ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindMost" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "AssignSubscr" , Context { cName = "AssignSubscr" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '[' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Subscript" ) ] } , Rule { rMatcher = Detect2Chars '+' '=' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Assign" ) ] } , Rule { rMatcher = DetectChar '=' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Assign" ) ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindOthers" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "Case" , Context { cName = "Case" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\sin\\b" , reCompiled = Just (compileRegex True "\\sin\\b") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CaseIn" ) ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindMost" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "CaseExpr" , Context { cName = "CaseExpr" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = Detect2Chars ';' ';' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "esac(?=$|[\\s;)])" , reCompiled = Just (compileRegex True "esac(?=$|[\\s;)])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindAll" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "CaseIn" , Context { cName = "CaseIn" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\besac(?=$|[\\s;)])" , reCompiled = Just (compileRegex True "\\besac(?=$|[\\s;)])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = DetectChar ')' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CaseExpr" ) ] } , Rule { rMatcher = AnyChar "(|" , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindMost" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "CommandArgs" , Context { cName = "CommandArgs" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = LineContinue , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindMost" ) , 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 = KeywordTok , 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 = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\d*<<<" , reCompiled = Just (compileRegex True "\\d*<<<") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "<<" , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDoc" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[<>]\\(" , reCompiled = Just (compileRegex True "[<>]\\(") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "ProcessSubst" ) ] } , Rule { rMatcher = RegExpr RE { reString = "([0-9]*(>{1,2}|<)(&[0-9]+-?)?|&>|>&|[0-9]*<>)" , reCompiled = Just (compileRegex True "([0-9]*(>{1,2}|<)(&[0-9]+-?)?|&>|>&|[0-9]*<>)") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "([|&;])\\1?" , reCompiled = Just (compileRegex True "([|&;])\\1?") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "-?-[a-z][A-Za-z0-9_-]*" , reCompiled = Just (compileRegex True "-?-[a-z][A-Za-z0-9_-]*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !&()*+,;<=>?\\`|~" } (makeWordSet True [ "elif" , "else" , "for" , "function" , "in" , "select" , "set" , "then" , "until" , "while" ]) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = AnyChar ")}" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "CommandArgsBackq" , Context { cName = "CommandArgsBackq" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = LineContinue , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '`' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "CommandArgs" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Comment" , Context { cName = "Comment" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = IncludeRules ( "Alerts" , "" ) , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Modelines" , "" ) , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "CommentBackq" , Context { cName = "CommentBackq" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "[^`](?=`)" , reCompiled = Just (compileRegex True "[^`](?=`)") , reCaseSensitive = True } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Alerts" , "" ) , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "CommentParen" , Context { cName = "CommentParen" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "[^)](?=\\))" , reCompiled = Just (compileRegex True "[^)](?=\\))") , reCaseSensitive = True } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Alerts" , "" ) , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ExprBracket" , Context { cName = "ExprBracket" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s\\](?=($|[\\s;|&]))" , reCompiled = Just (compileRegex True "\\s\\](?=($|[\\s;|&]))") , reCaseSensitive = True } , rAttribute = BuiltInTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\](?=($|[\\s;|&]))" , reCompiled = Just (compileRegex True "\\](?=($|[\\s;|&]))") , reCaseSensitive = True } , rAttribute = BuiltInTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '(' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "ExprSubParen" ) ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindTests" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindMost" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ExprDblBracket" , Context { cName = "ExprDblBracket" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s\\]\\](?=($|[\\s;|&]))" , reCompiled = Just (compileRegex True "\\s\\]\\](?=($|[\\s;|&]))") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\]\\](?=($|[\\s;|&]))" , reCompiled = Just (compileRegex True "\\]\\](?=($|[\\s;|&]))") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '(' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "ExprSubParen" ) ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindTests" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindMost" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ExprDblParen" , Context { cName = "ExprDblParen" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = Detect2Chars ')' ')' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '(' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "ExprSubParen" ) ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindMost" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ExprDblParenSubst" , Context { cName = "ExprDblParenSubst" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = Detect2Chars ')' ')' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '(' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "ExprSubParen" ) ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindMost" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ExprSubParen" , Context { cName = "ExprSubParen" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar ')' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '(' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "ExprSubParen" ) ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindMost" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindAll" , Context { cName = "FindAll" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = IncludeRules ( "Bash" , "FindComments" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindCommands" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindOthers" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindCommands" , Context { cName = "FindCommands" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = IncludeRules ( "Bash" , "FindSpecialCommands" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindNormalCommands" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindCommandsBackq" , Context { cName = "FindCommandsBackq" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = IncludeRules ( "Bash" , "FindSpecialCommands" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindNormalCommandsBackq" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindComments" , Context { cName = "FindComments" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '#' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[\\s;](?=#)" , reCompiled = Just (compileRegex True "[\\s;](?=#)") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Comment" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindCommentsBackq" , Context { cName = "FindCommentsBackq" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '#' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommentBackq" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[\\s;](?=#)" , reCompiled = Just (compileRegex True "[\\s;](?=#)") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommentBackq" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindCommentsParen" , Context { cName = "FindCommentsParen" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '#' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommentParen" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[\\s;](?=#)" , reCompiled = Just (compileRegex True "[\\s;](?=#)") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommentParen" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindMost" , Context { cName = "FindMost" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = IncludeRules ( "Bash" , "FindComments" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindOthers" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindNormalCommands" , Context { cName = "FindNormalCommands" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !&()*+,;<=>?\\`|~" } (makeWordSet True [ ":" , "alias" , "bg" , "bind" , "break" , "builtin" , "caller" , "cd" , "command" , "compgen" , "complete" , "continue" , "dirs" , "disown" , "echo" , "enable" , "eval" , "exec" , "exit" , "fc" , "fg" , "getopts" , "hash" , "help" , "history" , "jobs" , "kill" , "let" , "logout" , "popd" , "printf" , "pushd" , "pwd" , "return" , "set" , "shift" , "shopt" , "source" , "suspend" , "test" , "time" , "times" , "trap" , "type" , "ulimit" , "umask" , "unalias" , "wait" ]) , rAttribute = BuiltInTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommandArgs" ) ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !&()*+,;<=>?\\`|~" } (makeWordSet True [ "aclocal" , "aconnect" , "aplay" , "apm" , "apmsleep" , "apropos" , "ar" , "arch" , "arecord" , "as" , "as86" , "autoconf" , "autoheader" , "automake" , "awk" , "basename" , "bash" , "bc" , "bison" , "bunzip2" , "bzcat" , "bzcmp" , "bzdiff" , "bzegrep" , "bzfgrep" , "bzgrep" , "bzip2" , "bzip2recover" , "bzless" , "bzmore" , "c++" , "cal" , "cat" , "cc" , "cd-read" , "cdda2wav" , "cdparanoia" , "cdrdao" , "cdrecord" , "chattr" , "chfn" , "chgrp" , "chmod" , "chown" , "chroot" , "chsh" , "chvt" , "clang" , "clear" , "cmake" , "cmp" , "co" , "col" , "comm" , "cp" , "cpio" , "cpp" , "cut" , "date" , "dc" , "dcop" , "dd" , "deallocvt" , "df" , "diff" , "diff3" , "dir" , "dircolors" , "directomatic" , "dirname" , "dmesg" , "dnsdomainname" , "domainname" , "du" , "dumpkeys" , "echo" , "ed" , "egrep" , "env" , "expr" , "false" , "fbset" , "fgconsole" , "fgrep" , "file" , "find" , "flex" , "flex++" , "fmt" , "free" , "ftp" , "funzip" , "fuser" , "g++" , "gawk" , "gc" , "gcc" , "gdb" , "getent" , "getkeycodes" , "getopt" , "gettext" , "gettextize" , "gimp" , "gimp-remote" , "gimptool" , "git" , "gmake" , "gocr" , "grep" , "groff" , "groups" , "gs" , "gunzip" , "gzexe" , "gzip" , "head" , "hexdump" , "hostname" , "id" , "igawk" , "install" , "join" , "kbd_mode" , "kbdrate" , "kdialog" , "kfile" , "kill" , "killall" , "last" , "lastb" , "ld" , "ld86" , "ldd" , "less" , "lex" , "link" , "ln" , "loadkeys" , "loadunimap" , "locate" , "lockfile" , "login" , "logname" , "lp" , "lpr" , "ls" , "lsattr" , "lsmod" , "lsmod.old" , "lynx" , "lzcat" , "lzcmp" , "lzdiff" , "lzegrep" , "lzfgrep" , "lzgrep" , "lzless" , "lzma" , "lzmainfo" , "lzmore" , "m4" , "make" , "man" , "mapscrn" , "mesg" , "mkdir" , "mkfifo" , "mknod" , "mktemp" , "more" , "mount" , "msgfmt" , "mv" , "namei" , "nano" , "nasm" , "nawk" , "netstat" , "nice" , "nisdomainname" , "nl" , "nm" , "nm86" , "nmap" , "nohup" , "nop" , "nroff" , "od" , "openvt" , "passwd" , "patch" , "pcregrep" , "pcretest" , "perl" , "perror" , "pgawk" , "pidof" , "ping" , "pr" , "printf" , "procmail" , "prune" , "ps" , "ps2ascii" , "ps2epsi" , "ps2frag" , "ps2pdf" , "ps2ps" , "psbook" , "psmerge" , "psnup" , "psresize" , "psselect" , "pstops" , "pstree" , "pwd" , "qmake" , "rbash" , "rcs" , "readlink" , "red" , "resizecons" , "rev" , "rm" , "rmdir" , "rsync" , "run-parts" , "sash" , "scp" , "sed" , "seq" , "setfont" , "setkeycodes" , "setleds" , "setmetamode" , "setserial" , "setterm" , "sh" , "showkey" , "shred" , "size" , "size86" , "skill" , "sleep" , "slogin" , "snice" , "sort" , "sox" , "split" , "ssed" , "ssh" , "ssh-add" , "ssh-agent" , "ssh-keygen" , "ssh-keyscan" , "stat" , "strings" , "strip" , "stty" , "su" , "sudo" , "suidperl" , "sum" , "svn" , "sync" , "tac" , "tail" , "tar" , "tee" , "tempfile" , "test" , "touch" , "tr" , "troff" , "true" , "umount" , "uname" , "unicode_start" , "unicode_stop" , "uniq" , "unlink" , "unlzma" , "unxz" , "unzip" , "updatedb" , "updmap" , "uptime" , "users" , "utmpdump" , "uuidgen" , "valgrind" , "vdir" , "vmstat" , "w" , "wall" , "wc" , "wget" , "whatis" , "whereis" , "which" , "who" , "whoami" , "write" , "xargs" , "xdg-open" , "xhost" , "xmodmap" , "xset" , "xz" , "xzcat" , "yacc" , "yes" , "ypdomainname" , "zcat" , "zcmp" , "zdiff" , "zegrep" , "zfgrep" , "zforce" , "zgrep" , "zip" , "zless" , "zmore" , "znew" , "zsh" , "zsoelim" ]) , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommandArgs" ) ] } , Rule { rMatcher = RegExpr RE { reString = "([\\w_@.%*?+-]|\\\\ )*(?=/)" , reCompiled = Just (compileRegex True "([\\w_@.%*?+-]|\\\\ )*(?=/)") , reCaseSensitive = True } , rAttribute = ExtensionTok , 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 = ExtensionTok , 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 = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "/([\\w_@.%*?+-]|\\\\ )*(?=([\\s);$`'\"]|$))" , reCompiled = Just (compileRegex True "/([\\w_@.%*?+-]|\\\\ )*(?=([\\s);$`'\"]|$))") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommandArgs" ) ] } , Rule { rMatcher = RegExpr RE { reString = "([\\w_@.%*?+-]|\\\\ )*" , reCompiled = Just (compileRegex True "([\\w_@.%*?+-]|\\\\ )*") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommandArgs" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindNormalCommandsBackq" , Context { cName = "FindNormalCommandsBackq" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !&()*+,;<=>?\\`|~" } (makeWordSet True [ ":" , "alias" , "bg" , "bind" , "break" , "builtin" , "caller" , "cd" , "command" , "compgen" , "complete" , "continue" , "dirs" , "disown" , "echo" , "enable" , "eval" , "exec" , "exit" , "fc" , "fg" , "getopts" , "hash" , "help" , "history" , "jobs" , "kill" , "let" , "logout" , "popd" , "printf" , "pushd" , "pwd" , "return" , "set" , "shift" , "shopt" , "source" , "suspend" , "test" , "time" , "times" , "trap" , "type" , "ulimit" , "umask" , "unalias" , "wait" ]) , rAttribute = BuiltInTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommandArgsBackq" ) ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !&()*+,;<=>?\\`|~" } (makeWordSet True [ "aclocal" , "aconnect" , "aplay" , "apm" , "apmsleep" , "apropos" , "ar" , "arch" , "arecord" , "as" , "as86" , "autoconf" , "autoheader" , "automake" , "awk" , "basename" , "bash" , "bc" , "bison" , "bunzip2" , "bzcat" , "bzcmp" , "bzdiff" , "bzegrep" , "bzfgrep" , "bzgrep" , "bzip2" , "bzip2recover" , "bzless" , "bzmore" , "c++" , "cal" , "cat" , "cc" , "cd-read" , "cdda2wav" , "cdparanoia" , "cdrdao" , "cdrecord" , "chattr" , "chfn" , "chgrp" , "chmod" , "chown" , "chroot" , "chsh" , "chvt" , "clang" , "clear" , "cmake" , "cmp" , "co" , "col" , "comm" , "cp" , "cpio" , "cpp" , "cut" , "date" , "dc" , "dcop" , "dd" , "deallocvt" , "df" , "diff" , "diff3" , "dir" , "dircolors" , "directomatic" , "dirname" , "dmesg" , "dnsdomainname" , "domainname" , "du" , "dumpkeys" , "echo" , "ed" , "egrep" , "env" , "expr" , "false" , "fbset" , "fgconsole" , "fgrep" , "file" , "find" , "flex" , "flex++" , "fmt" , "free" , "ftp" , "funzip" , "fuser" , "g++" , "gawk" , "gc" , "gcc" , "gdb" , "getent" , "getkeycodes" , "getopt" , "gettext" , "gettextize" , "gimp" , "gimp-remote" , "gimptool" , "git" , "gmake" , "gocr" , "grep" , "groff" , "groups" , "gs" , "gunzip" , "gzexe" , "gzip" , "head" , "hexdump" , "hostname" , "id" , "igawk" , "install" , "join" , "kbd_mode" , "kbdrate" , "kdialog" , "kfile" , "kill" , "killall" , "last" , "lastb" , "ld" , "ld86" , "ldd" , "less" , "lex" , "link" , "ln" , "loadkeys" , "loadunimap" , "locate" , "lockfile" , "login" , "logname" , "lp" , "lpr" , "ls" , "lsattr" , "lsmod" , "lsmod.old" , "lynx" , "lzcat" , "lzcmp" , "lzdiff" , "lzegrep" , "lzfgrep" , "lzgrep" , "lzless" , "lzma" , "lzmainfo" , "lzmore" , "m4" , "make" , "man" , "mapscrn" , "mesg" , "mkdir" , "mkfifo" , "mknod" , "mktemp" , "more" , "mount" , "msgfmt" , "mv" , "namei" , "nano" , "nasm" , "nawk" , "netstat" , "nice" , "nisdomainname" , "nl" , "nm" , "nm86" , "nmap" , "nohup" , "nop" , "nroff" , "od" , "openvt" , "passwd" , "patch" , "pcregrep" , "pcretest" , "perl" , "perror" , "pgawk" , "pidof" , "ping" , "pr" , "printf" , "procmail" , "prune" , "ps" , "ps2ascii" , "ps2epsi" , "ps2frag" , "ps2pdf" , "ps2ps" , "psbook" , "psmerge" , "psnup" , "psresize" , "psselect" , "pstops" , "pstree" , "pwd" , "qmake" , "rbash" , "rcs" , "readlink" , "red" , "resizecons" , "rev" , "rm" , "rmdir" , "rsync" , "run-parts" , "sash" , "scp" , "sed" , "seq" , "setfont" , "setkeycodes" , "setleds" , "setmetamode" , "setserial" , "setterm" , "sh" , "showkey" , "shred" , "size" , "size86" , "skill" , "sleep" , "slogin" , "snice" , "sort" , "sox" , "split" , "ssed" , "ssh" , "ssh-add" , "ssh-agent" , "ssh-keygen" , "ssh-keyscan" , "stat" , "strings" , "strip" , "stty" , "su" , "sudo" , "suidperl" , "sum" , "svn" , "sync" , "tac" , "tail" , "tar" , "tee" , "tempfile" , "test" , "touch" , "tr" , "troff" , "true" , "umount" , "uname" , "unicode_start" , "unicode_stop" , "uniq" , "unlink" , "unlzma" , "unxz" , "unzip" , "updatedb" , "updmap" , "uptime" , "users" , "utmpdump" , "uuidgen" , "valgrind" , "vdir" , "vmstat" , "w" , "wall" , "wc" , "wget" , "whatis" , "whereis" , "which" , "who" , "whoami" , "write" , "xargs" , "xdg-open" , "xhost" , "xmodmap" , "xset" , "xz" , "xzcat" , "yacc" , "yes" , "ypdomainname" , "zcat" , "zcmp" , "zdiff" , "zegrep" , "zfgrep" , "zforce" , "zgrep" , "zip" , "zless" , "zmore" , "znew" , "zsh" , "zsoelim" ]) , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommandArgsBackq" ) ] } , Rule { rMatcher = RegExpr RE { reString = "([\\w_@.%*?+-]|\\\\ )*(?=/)" , reCompiled = Just (compileRegex True "([\\w_@.%*?+-]|\\\\ )*(?=/)") , reCaseSensitive = True } , rAttribute = ExtensionTok , 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 = ExtensionTok , 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 = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "/([\\w_@.%*?+-]|\\\\ )*(?=([\\s);$`'\"]|$))" , reCompiled = Just (compileRegex True "/([\\w_@.%*?+-]|\\\\ )*(?=([\\s);$`'\"]|$))") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommandArgsBackq" ) ] } , Rule { rMatcher = RegExpr RE { reString = "([\\w_@.%*?+-]|\\\\ )*" , reCompiled = Just (compileRegex True "([\\w_@.%*?+-]|\\\\ )*") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "CommandArgsBackq" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindOthers" , Context { cName = "FindOthers" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\\\[][;\\\\$`{}()|&<>* ]" , reCompiled = Just (compileRegex True "\\\\[][;\\\\$`{}()|&<>* ]") , reCaseSensitive = True } , rAttribute = DataTypeTok , 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 = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\{(?!(\\s|$))\\S*\\}" , reCompiled = Just (compileRegex True "\\{(?!(\\s|$))\\S*\\}") , reCaseSensitive = True } , rAttribute = DataTypeTok , 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 = 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 = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "/([\\w_@.%*?+-]|\\\\ )*(?=([\\s/):;$`'\"]|$))" , reCompiled = Just (compileRegex True "/([\\w_@.%*?+-]|\\\\ )*(?=([\\s/):;$`'\"]|$))") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindSpecialCommands" , Context { cName = "FindSpecialCommands" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = Detect2Chars '(' '(' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "ExprDblParen" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\[\\[(?=($|\\s))" , reCompiled = Just (compileRegex True "\\[\\[(?=($|\\s))") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Bash" , "ExprDblBracket" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s\\[\\[(?=($|\\s))" , reCompiled = Just (compileRegex True "\\s\\[\\[(?=($|\\s))") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "ExprDblBracket" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\[(?=($|\\s))" , reCompiled = Just (compileRegex True "\\[(?=($|\\s))") , reCaseSensitive = True } , rAttribute = BuiltInTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Bash" , "ExprBracket" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s\\[(?=($|\\s))" , reCompiled = Just (compileRegex True "\\s\\[(?=($|\\s))") , reCaseSensitive = True } , rAttribute = BuiltInTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "ExprBracket" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\{(?=($|\\s))" , reCompiled = Just (compileRegex True "\\{(?=($|\\s))") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Group" ) ] } , Rule { rMatcher = DetectChar '(' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "SubShell" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\bdo(?![\\w$+-])" , reCompiled = Just (compileRegex True "\\bdo(?![\\w$+-])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\bdone(?![\\w$+-])" , reCompiled = Just (compileRegex True "\\bdone(?![\\w$+-])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\bif(?=($|\\s))" , reCompiled = Just (compileRegex True "\\bif(?=($|\\s))") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\bfi(?![\\w$+-])" , reCompiled = Just (compileRegex True "\\bfi(?![\\w$+-])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\bcase(?![\\w$+-])" , reCompiled = Just (compileRegex True "\\bcase(?![\\w$+-])") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Case" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\b[A-Za-z_][A-Za-z0-9_]*\\+?=" , reCompiled = Just (compileRegex True "\\b[A-Za-z_][A-Za-z0-9_]*\\+?=") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Assign" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\b[A-Za-z_][A-Za-z0-9_]*(?=\\[.+\\]\\+?=)" , reCompiled = Just (compileRegex True "\\b[A-Za-z_][A-Za-z0-9_]*(?=\\[.+\\]\\+?=)") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "AssignSubscr" ) ] } , Rule { rMatcher = StringDetect ":()" , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\bfunction\\b" , reCompiled = Just (compileRegex True "\\bfunction\\b") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "FunctionDef" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[A-Za-z_:][A-Za-z0-9_:#%@-]*\\s*\\(\\)" , reCompiled = Just (compileRegex True "[A-Za-z_:][A-Za-z0-9_:#%@-]*\\s*\\(\\)") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !&()*+,;<=>?\\`|~" } (makeWordSet True [ "elif" , "else" , "for" , "function" , "in" , "select" , "set" , "then" , "until" , "while" ]) , rAttribute = KeywordTok , 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 = BuiltInTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !&()*+,;<=>?\\`|~" } (makeWordSet True [ "declare" , "export" , "local" , "read" , "readonly" , "typeset" , "unset" ]) , rAttribute = BuiltInTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "VarName" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\d*<<<" , reCompiled = Just (compileRegex True "\\d*<<<") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "<<" , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDoc" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[<>]\\(" , reCompiled = Just (compileRegex True "[<>]\\(") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "ProcessSubst" ) ] } , Rule { rMatcher = RegExpr RE { reString = "([0-9]*(>{1,2}|<)(&[0-9]+-?)?|&>|>&|[0-9]*<>)" , reCompiled = Just (compileRegex True "([0-9]*(>{1,2}|<)(&[0-9]+-?)?|&>|>&|[0-9]*<>)") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "([|&])\\1?" , reCompiled = Just (compileRegex True "([|&])\\1?") , reCaseSensitive = True } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindStrings" , Context { cName = "FindStrings" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = Detect2Chars '\\' '\'' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '\\' '"' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '\'' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "StringSQ" ) ] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "StringDQ" ) ] } , Rule { rMatcher = Detect2Chars '$' '\'' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "StringEsc" ) ] } , Rule { rMatcher = Detect2Chars '$' '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "StringDQ" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindSubstitutions" , Context { cName = "FindSubstitutions" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\$[A-Za-z_][A-Za-z0-9_]*\\[" , reCompiled = Just (compileRegex True "\\$[A-Za-z_][A-Za-z0-9_]*\\[") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Subscript" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\$[A-Za-z_][A-Za-z0-9_]*" , reCompiled = Just (compileRegex True "\\$[A-Za-z_][A-Za-z0-9_]*") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\$[*@#?$!_0-9-]" , reCompiled = Just (compileRegex True "\\$[*@#?$!_0-9-]") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\$\\{[*@#?$!_0-9-]\\}" , reCompiled = Just (compileRegex True "\\$\\{[*@#?$!_0-9-]\\}") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\$\\{#[A-Za-z_][A-Za-z0-9_]*(\\[[*@]\\])?\\}" , reCompiled = Just (compileRegex True "\\$\\{#[A-Za-z_][A-Za-z0-9_]*(\\[[*@]\\])?\\}") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\$\\{![A-Za-z_][A-Za-z0-9_]*(\\[[*@]\\]|[*@])?\\}" , reCompiled = Just (compileRegex True "\\$\\{![A-Za-z_][A-Za-z0-9_]*(\\[[*@]\\]|[*@])?\\}") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\$\\{#[0-9]+\\}" , reCompiled = Just (compileRegex True "\\$\\{#[0-9]+\\}") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\$\\{[A-Za-z_][A-Za-z0-9_]*" , reCompiled = Just (compileRegex True "\\$\\{[A-Za-z_][A-Za-z0-9_]*") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "VarBrace" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\$\\{[*@#?$!_0-9-](?=[:#%/=?+-])" , reCompiled = Just (compileRegex True "\\$\\{[*@#?$!_0-9-](?=[:#%/=?+-])") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "VarBrace" ) ] } , Rule { rMatcher = StringDetect "$((" , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "ExprDblParenSubst" ) ] } , Rule { rMatcher = StringDetect "$(<" , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "SubstFile" ) ] } , Rule { rMatcher = StringDetect "$(" , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "SubstCommand" ) ] } , Rule { rMatcher = DetectChar '`' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "SubstBackq" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\[`$\\\\]" , reCompiled = Just (compileRegex True "\\\\[`$\\\\]") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FindTests" , Context { cName = "FindTests" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "-[abcdefghkprstuwxOGLSNozn](?=\\s)" , reCompiled = Just (compileRegex True "-[abcdefghkprstuwxOGLSNozn](?=\\s)") , reCaseSensitive = True } , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "-([no]t|ef)(?=\\s)" , reCompiled = Just (compileRegex True "-([no]t|ef)(?=\\s)") , reCaseSensitive = True } , rAttribute = OtherTok , 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 = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "-(eq|ne|[gl][te])(?=\\s)" , reCompiled = Just (compileRegex True "-(eq|ne|[gl][te])(?=\\s)") , reCaseSensitive = True } , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "FunctionDef" , Context { cName = "FunctionDef" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s+[A-Za-z_:][A-Za-z0-9_:#%@-]*(\\s*\\(\\))?" , reCompiled = Just (compileRegex True "\\s+[A-Za-z_:][A-Za-z0-9_:#%@-]*(\\s*\\(\\))?") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = FunctionTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "Group" , Context { cName = "Group" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindAll" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "HereDoc" , Context { cName = "HereDoc" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "(<<-\\s*\"([^|&;()<>\\s]+)\")" , reCompiled = Just (compileRegex True "(<<-\\s*\"([^|&;()<>\\s]+)\")") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocIQ" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(<<-\\s*'([^|&;()<>\\s]+)')" , reCompiled = Just (compileRegex True "(<<-\\s*'([^|&;()<>\\s]+)')") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocIQ" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(<<-\\s*\\\\([^|&;()<>\\s]+))" , reCompiled = Just (compileRegex True "(<<-\\s*\\\\([^|&;()<>\\s]+))") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocIQ" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(<<-\\s*([^|&;()<>\\s]+))" , reCompiled = Just (compileRegex True "(<<-\\s*([^|&;()<>\\s]+))") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocINQ" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(<<\\s*\"([^|&;()<>\\s]+)\")" , reCompiled = Just (compileRegex True "(<<\\s*\"([^|&;()<>\\s]+)\")") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocQ" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(<<\\s*'([^|&;()<>\\s]+)')" , reCompiled = Just (compileRegex True "(<<\\s*'([^|&;()<>\\s]+)')") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocQ" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(<<\\s*\\\\([^|&;()<>\\s]+))" , reCompiled = Just (compileRegex True "(<<\\s*\\\\([^|&;()<>\\s]+))") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocQ" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(<<\\s*([^|&;()<>\\s]+))" , reCompiled = Just (compileRegex True "(<<\\s*([^|&;()<>\\s]+))") , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocNQ" ) ] } , Rule { rMatcher = StringDetect "<<" , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "HereDocINQ" , Context { cName = "HereDocINQ" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocRemainder" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\t*%2\\b" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "HereDocIQ" , Context { cName = "HereDocIQ" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocRemainder" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\t*%2\\b" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "HereDocNQ" , Context { cName = "HereDocNQ" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocRemainder" ) ] } , Rule { rMatcher = RegExpr RE { reString = "%2\\b" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "HereDocQ" , Context { cName = "HereDocQ" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "%1" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "HereDocRemainder" ) ] } , Rule { rMatcher = RegExpr RE { reString = "%2\\b" , reCompiled = Nothing , reCaseSensitive = True } , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = True , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = True } ) , ( "HereDocRemainder" , Context { cName = "HereDocRemainder" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = IncludeRules ( "Bash" , "FindAll" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "ProcessSubst" , Context { cName = "ProcessSubst" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar ')' , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindCommentsParen" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindCommands" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindOthers" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Start" , Context { cName = "Start" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = IncludeRules ( "Bash" , "FindAll" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "StringDQ" , Context { cName = "StringDQ" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\[`\"\\\\$\\n]" , reCompiled = Just (compileRegex True "\\\\[`\"\\\\$\\n]") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "StringEsc" , Context { cName = "StringEsc" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '\'' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\\\[abefnrtv\\\\']" , reCompiled = Just (compileRegex True "\\\\[abefnrtv\\\\']") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\\\([0-7]{1,3}|x[A-Fa-f0-9]{1,2}|c.)" , reCompiled = Just (compileRegex True "\\\\([0-7]{1,3}|x[A-Fa-f0-9]{1,2}|c.)") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "StringSQ" , Context { cName = "StringSQ" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '\'' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SubShell" , Context { cName = "SubShell" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar ')' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindAll" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Subscript" , Context { cName = "Subscript" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar ']' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindOthers" ) , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = VariableTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SubstBackq" , Context { cName = "SubstBackq" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '`' , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindCommentsBackq" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindCommandsBackq" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindOthers" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SubstCommand" , Context { cName = "SubstCommand" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar ')' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindCommentsParen" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindCommands" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindOthers" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SubstFile" , Context { cName = "SubstFile" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar ')' , rAttribute = OperatorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindCommentsParen" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindOthers" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "VarAlt" , Context { cName = "VarAlt" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "VarBrace" , Context { cName = "VarBrace" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '[' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Subscript" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(:?[-=?+]|##?|%%?)" , reCompiled = Just (compileRegex True "(:?[-=?+]|##?|%%?)") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "VarAlt" ) ] } , Rule { rMatcher = RegExpr RE { reString = "//?" , reCompiled = Just (compileRegex True "//?") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "VarSubst" ) ] } , Rule { rMatcher = DetectChar ':' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "VarSub" ) ] } ] , cAttribute = ErrorTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "VarName" , Context { cName = "VarName" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "-[A-Za-z0-9]+" , reCompiled = Just (compileRegex True "-[A-Za-z0-9]+") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "--[a-z][A-Za-z0-9_-]*" , reCompiled = Just (compileRegex True "--[a-z][A-Za-z0-9_-]*") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b[A-Za-z_][A-Za-z0-9_]*" , reCompiled = Just (compileRegex True "\\b[A-Za-z_][A-Za-z0-9_]*") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '[' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Subscript" ) ] } , Rule { rMatcher = DetectChar '=' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "Assign" ) ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindMost" ) , 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 = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "VarSub" , Context { cName = "VarSub" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar ':' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "VarSub2" ) ] } , Rule { rMatcher = DetectChar '}' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[A-Za-z_][A-Za-z0-9_]*" , reCompiled = Just (compileRegex True "[A-Za-z_][A-Za-z0-9_]*") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[0-9]+(?=[:}])" , reCompiled = Just (compileRegex True "[0-9]+(?=[:}])") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = ErrorTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "VarSub2" , Context { cName = "VarSub2" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } , Rule { rMatcher = RegExpr RE { reString = "[A-Za-z_][A-Za-z0-9_]*" , reCompiled = Just (compileRegex True "[A-Za-z_][A-Za-z0-9_]*") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[0-9](?=[:}])" , reCompiled = Just (compileRegex True "[0-9](?=[:}])") , reCaseSensitive = True } , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = ErrorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = ErrorTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "VarSubst" , Context { cName = "VarSubst" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = DetectChar '/' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Bash" , "VarSubst2" ) ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "VarSubst2" , Context { cName = "VarSubst2" , cSyntax = "Bash" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindStrings" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "Bash" , "FindSubstitutions" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Wilbert Berendsen (wilbert@kde.nl)" , sVersion = "3" , sLicense = "LGPL" , sExtensions = [ "*.sh" , "*.bash" , "*.ebuild" , "*.eclass" , "*.nix" , ".bashrc" , ".bash_profile" , ".bash_login" , ".profile" ] , sStartingContext = "Start" }