{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Tcsh (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"Tcsh\", sFilename = \"tcsh.xml\", sShortname = \"Tcsh\", sContexts = fromList [(\"Assign\",Context {cName = \"Assign\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar '(', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"AssignArray\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindSubstitutions\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindOthers\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[\\\\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 = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar ')', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar '[', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Subscript\")]},Rule {rMatcher = DetectChar '=', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Assign\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar '[', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Subscript\")]},Rule {rMatcher = DetectChar '=', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Assign\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindSubstitutions\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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}),(\"CmdSetEnv\",Context {cName = \"CmdSetEnv\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\b[A-Za-z_][A-Za-z0-9_]*\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar ' ', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Assign\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindMost\"), 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}),(\"Comment\",Context {cName = \"Comment\", cSyntax = \"Tcsh\", cRules = [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}),(\"CommentBackq\",Context {cName = \"CommentBackq\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"[^`](?=`)\", 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 = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"[^)](?=\\\\))\", 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 = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\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;|&]))\", 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 (\"Tcsh\",\"ExprSubParen\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindTests\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\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;|&]))\", 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 (\"Tcsh\",\"ExprSubParen\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindTests\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", 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 (\"Tcsh\",\"ExprSubParen\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = Detect2Chars ')' ')', rAttribute = OtherTok, 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 (\"Tcsh\",\"ExprSubParen\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", 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 (\"Tcsh\",\"ExprSubParen\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindComments\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindCommands\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindSubstitutions\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = Detect2Chars '(' '(', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"ExprDblParen\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\[\\\\[(?=($|\\\\s))\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Push (\"Tcsh\",\"ExprDblBracket\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s\\\\[\\\\[(?=($|\\\\s))\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"ExprDblBracket\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\[(?=($|\\\\s))\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Push (\"Tcsh\",\"ExprBracket\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s\\\\[(?=($|\\\\s))\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"ExprBracket\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\{(?=($|\\\\s))\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Group\")]},Rule {rMatcher = DetectChar '(', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"SubShell\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\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$+-])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\belse\\\\s+if(?![\\\\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(?![\\\\w$+-])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\bendif(?![\\\\w$+-])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\bswitch(?![\\\\w$+-])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Switch\")]},Rule {rMatcher = RegExpr (RE {reString = \"-[A-Za-z0-9][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_-]*\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b@\\\\s\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\bset\\\\s\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\bsetenv\\\\s\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"CmdSetEnv\")]},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\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"FunctionDef\")]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !&()*+,/;<=>?\\\\`|~\"}) (CaseSensitiveWords (fromList [\".\",\"else\",\"for\",\"function\",\"in\",\"select\",\"then\",\"until\",\"while\"])), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !&()*+,/;<=>?\\\\`|~\"}) (CaseSensitiveWords (fromList [\":\",\"alias\",\"alloc\",\"bg\",\"bindkey\",\"break\",\"builtins\",\"bye\",\"cd\",\"chdir\",\"complete\",\"continue\",\"dirs\",\"echo\",\"echotc\",\"eval\",\"exec\",\"exit\",\"fg\",\"filetest\",\"glob\",\"hashstat\",\"history\",\"hup\",\"inlib\",\"jobs\",\"kill\",\"limit\",\"log\",\"login\",\"logout\",\"ls-F\",\"migrate\",\"newgrp\",\"nice\",\"nohup\",\"notify\",\"onintr\",\"popd\",\"printenv\",\"pushd\",\"rehash\",\"repeat\",\"sched\",\"settc\",\"setty\",\"shift\",\"source\",\"stop\",\"suspend\",\"telltc\",\"time\",\"umask\",\"unalias\",\"uncomplete\",\"unhash\",\"unlimit\",\"ver\",\"wait\",\"watchlog\",\"where\",\"which\"])), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !&()*+,/;<=>?\\\\`|~\"}) (CaseSensitiveWords (fromList [\"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\",\"clear\",\"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\",\"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\",\"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\",\"rbash\",\"rcs\",\"readlink\",\"red\",\"resizecons\",\"rev\",\"rm\",\"rmdir\",\"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\",\"sync\",\"tac\",\"tail\",\"tar\",\"tee\",\"tempfile\",\"test\",\"touch\",\"tr\",\"troff\",\"true\",\"umount\",\"uname\",\"unicode_start\",\"unicode_stop\",\"uniq\",\"unlink\",\"unzip\",\"updatedb\",\"updmap\",\"uptime\",\"users\",\"utmpdump\",\"uuidgen\",\"vdir\",\"vmstat\",\"w\",\"wall\",\"wc\",\"wget\",\"whatis\",\"whereis\",\"which\",\"who\",\"whoami\",\"write\",\"xargs\",\"xhost\",\"xmodmap\",\"xset\",\"yacc\",\"yes\",\"ypdomainname\",\"zcat\",\"zcmp\",\"zdiff\",\"zegrep\",\"zfgrep\",\"zforce\",\"zgrep\",\"zip\",\"zless\",\"zmore\",\"znew\",\"zsh\",\"zsoelim\"])), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !&()*+,/;<=>?\\\\`|~\"}) (CaseSensitiveWords (fromList [\"unset\",\"unsetenv\"])), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"VarName\")]},Rule {rMatcher = RegExpr (RE {reString = \"(<>?&?!?)\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"([|&])\\\\1?\", reCaseSensitive = True}), rAttribute = KeywordTok, 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_:#%@-]*\\\\s*\\\\(\\\\)\", reCaseSensitive = True}), rAttribute = FunctionTok, 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 = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar '#', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = True, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Comment\")]},Rule {rMatcher = RegExpr (RE {reString = \"[\\\\s;](?=#)\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Comment\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"FindCommentsBackq\",Context {cName = \"FindCommentsBackq\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar '#', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = True, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"CommentBackq\")]},Rule {rMatcher = RegExpr (RE {reString = \"[\\\\s;](?=#)\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"CommentBackq\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"FindCommentsParen\",Context {cName = \"FindCommentsParen\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar '#', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = True, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"CommentParen\")]},Rule {rMatcher = RegExpr (RE {reString = \"[\\\\s;](?=#)\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"CommentParen\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"FindMost\",Context {cName = \"FindMost\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindComments\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindSubstitutions\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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}),(\"FindOthers\",Context {cName = \"FindOthers\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[;\\\"\\\\\\\\'$`{}()|&<>* ]\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"([\\\\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*\", 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/):;$`'\\\"]|$))\", 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}),(\"FindStrings\",Context {cName = \"FindStrings\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar '\\'', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"StringSQ\")]},Rule {rMatcher = DetectChar '\"', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"StringDQ\")]},Rule {rMatcher = Detect2Chars '$' '\\'', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"StringEsc\")]},Rule {rMatcher = Detect2Chars '$' '\"', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"StringDQ\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"FindSubstitutions\",Context {cName = \"FindSubstitutions\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\$[A-Za-z_][A-Za-z0-9_]*\\\\[\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Subscript\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$[A-Za-z_][A-Za-z0-9_]*\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$[*@#?$!_0-9-]\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$\\\\{[*@#?$!_0-9-]\\\\}\", reCaseSensitive = True}), rAttribute = OtherTok, 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_]*\\\\}\", reCaseSensitive = True}), rAttribute = OtherTok, 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_]*\\\\*?\\\\}\", reCaseSensitive = True}), rAttribute = OtherTok, 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_]*\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"VarBrace\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\$\\\\{[*@#?$!_0-9-](?=[:#%/])\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"VarBrace\")]},Rule {rMatcher = StringDetect \"$((\", rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"ExprDblParenSubst\")]},Rule {rMatcher = DetectChar '`', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"SubstBackq\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[`$\\\\\\\\]\", 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 = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"-[rwxXeozsfdlbcpSugktRLDIFNZ](?=\\\\s)\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"-[AMCUG]:?(?=\\\\s)\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"-P[0-7]{,3}:?(?=\\\\s)\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"([|&=><])\\\\1\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[|^&><+\\\\-*/%!~]\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"([!=]~|[!><]=)\", 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 = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\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 = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"(<<-\\\\s*\\\"([|&;()<>\\\\s]+)\\\")\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocIQ\")]},Rule {rMatcher = RegExpr (RE {reString = \"(<<-\\\\s*'([|&;()<>\\\\s]+)')\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocIQ\")]},Rule {rMatcher = RegExpr (RE {reString = \"(<<-\\\\s*\\\\\\\\([|&;()<>\\\\s]+))\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocIQ\")]},Rule {rMatcher = RegExpr (RE {reString = \"(<<-\\\\s*([|&;()<>\\\\s]+))\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocINQ\")]},Rule {rMatcher = RegExpr (RE {reString = \"(<<\\\\s*\\\"([|&;()<>\\\\s]+)\\\")\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocQ\")]},Rule {rMatcher = RegExpr (RE {reString = \"(<<\\\\s*'([|&;()<>\\\\s]+)')\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocQ\")]},Rule {rMatcher = RegExpr (RE {reString = \"(<<\\\\s*\\\\\\\\([|&;()<>\\\\s]+))\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocQ\")]},Rule {rMatcher = RegExpr (RE {reString = \"(<<\\\\s*([|&;()<>\\\\s]+))\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocNQ\")]},Rule {rMatcher = StringDetect \"<<\", rAttribute = KeywordTok, 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 = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"%1\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocRemainder\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*%2[\\\\s;]*$\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"%1\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocRemainder\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*%2[\\\\s;]*$\", reCaseSensitive = True}), rAttribute = KeywordTok, 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 = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"%1\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocRemainder\")]},Rule {rMatcher = RegExpr (RE {reString = \"%2[\\\\s;]*$\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"%1\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = True, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"HereDocRemainder\")]},Rule {rMatcher = RegExpr (RE {reString = \"%2[\\\\s;]*$\", reCaseSensitive = True}), rAttribute = KeywordTok, 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 = \"Tcsh\", cRules = [Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar ')', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindCommentsParen\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindCommands\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindSubstitutions\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", 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]\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", 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\\\\\\\\']\", 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.)\", 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 = \"Tcsh\", 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 = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar ')', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar ']', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindStrings\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindSubstitutions\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindOthers\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"SubstBackq\",Context {cName = \"SubstBackq\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar '`', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindCommentsBackq\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindCommands\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindSubstitutions\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar ')', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindCommentsParen\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindCommands\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindSubstitutions\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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 = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar ')', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindCommentsParen\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindSubstitutions\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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}),(\"Switch\",Context {cName = \"Switch\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\scase\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"SwitchCase\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\sdefault\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"SwitchDefault\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\bendsw(?=$|[\\\\s;)])\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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}),(\"SwitchCase\",Context {cName = \"SwitchCase\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar ':', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"SwitchExpr\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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}),(\"SwitchDefault\",Context {cName = \"SwitchDefault\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar ':', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"SwitchExpr\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"SwitchExpr\",Context {cName = \"SwitchExpr\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\sbreaksw\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\scase\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"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}),(\"VarBrace\",Context {cName = \"VarBrace\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar '[', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Subscript\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindStrings\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindSubstitutions\"), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = OtherTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"VarName\",Context {cName = \"VarName\", cSyntax = \"Tcsh\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"-[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_-]*\", 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_]*\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '[', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Subscript\")]},Rule {rMatcher = DetectChar '=', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Tcsh\",\"Assign\")]},Rule {rMatcher = IncludeRules (\"Tcsh\",\"FindMost\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[^]})|;`&><]\", 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})], sAuthor = \"Matthew Woehlke (mw_triad@users.sourceforge.net)\", sVersion = \"1\", sLicense = \"LGPL\", sExtensions = [\"*.csh\",\"*.tcsh\",\"csh.cshrc\",\"csh.login\",\".tcshrc\",\".cshrc\",\".login\"], sStartingContext = \"Start\"}"