{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Xul (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"XUL\", sFilename = \"xul.xml\", sShortname = \"Xul\", sContexts = fromList [(\"(Internal regex catch)\",Context {cName = \"(Internal regex catch)\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\s*\", reCaseSensitive = True}), rAttribute = NormalTok, 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 = [Pop]},Rule {rMatcher = Detect2Chars '/' '/', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"JSComment\")]},Rule {rMatcher = Detect2Chars '/' '*', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"Multi/inline Comment\")]},Rule {rMatcher = DetectChar '/', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"(regex caret first check)\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"(charclass caret first check)\",Context {cName = \"(charclass caret first check)\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = DetectChar '^', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"Regular Expression Character Class\")]}], cAttribute = FloatTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Push (\"XUL\",\"Regular Expression Character Class\")], cDynamic = False}),(\"(regex caret first check)\",Context {cName = \"(regex caret first check)\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = DetectChar '^', rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"Regular Expression\")]}], cAttribute = FloatTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Push (\"XUL\",\"Regular Expression\")], cDynamic = False}),(\"Attribute\",Context {cName = \"Attribute\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = DetectChar '=', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"Value\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\S\", reCaseSensitive = True}), rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"CDATA\",Context {cName = \"CDATA\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = StringDetect \"]]>\", rAttribute = BaseNTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = StringDetect \"]]>\", rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"//BEGIN\", rAttribute = RegionMarkerTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"region_marker\")]},Rule {rMatcher = StringDetect \"//END\", rAttribute = RegionMarkerTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"region_marker\")]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-./:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"break\",\"case\",\"catch\",\"const\",\"continue\",\"default\",\"delete\",\"do\",\"else\",\"false\",\"finally\",\"for\",\"function\",\"if\",\"in\",\"new\",\"return\",\"switch\",\"throw\",\"true\",\"try\",\"typeof\",\"var\",\"void\",\"while\",\"with\"])), 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 [\"Number\",\"escape\",\"isFinite\",\"isNaN\",\"parseFloat\",\"parseInt\",\"reload\",\"taint\",\"unescape\",\"untaint\",\"write\"])), rAttribute = FunctionTok, 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 [\"Anchor\",\"Applet\",\"Area\",\"Array\",\"Boolean\",\"Button\",\"Checkbox\",\"Date\",\"FileUpload\",\"Form\",\"Frame\",\"Function\",\"Hidden\",\"Image\",\"Layer\",\"Link\",\"Math\",\"Max\",\"MimeType\",\"Min\",\"Object\",\"Password\",\"Plugin\",\"Radio\",\"RegExp\",\"Reset\",\"Screen\",\"Select\",\"String\",\"Text\",\"Textarea\",\"Window\",\"document\",\"navigator\",\"this\",\"window\"])), 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 [\"E\",\"LN10\",\"LN2\",\"LOG10E\",\"LOG2E\",\"PI\",\"SQRT1_2\",\"SQRT2\",\"abs\",\"acos\",\"asin\",\"atan\",\"atan2\",\"ceil\",\"cos\",\"ctg\",\"exp\",\"floor\",\"log\",\"pow\",\"round\",\"sin\",\"sqrt\",\"tan\"])), 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 [\"onAbort\",\"onBlur\",\"onChange\",\"onClick\",\"onError\",\"onFocus\",\"onLoad\",\"onMouseOut\",\"onMouseOver\",\"onReset\",\"onSelect\",\"onSubmit\",\"onUnload\"])), 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 [\"MAX_VALUE\",\"MIN_VALUE\",\"NEGATIVE_INFINITY\",\"NaN\",\"POSITIVE_INFINITY\",\"URL\",\"UTC\",\"above\",\"action\",\"alert\",\"alinkColor\",\"anchor\",\"anchors\",\"appCodeName\",\"appName\",\"appVersion\",\"applets\",\"apply\",\"argument\",\"arguments\",\"arity\",\"availHeight\",\"availWidth\",\"back\",\"background\",\"below\",\"bgColor\",\"big\",\"blink\",\"blur\",\"bold\",\"border\",\"call\",\"caller\",\"charAt\",\"charCodeAt\",\"checked\",\"clearInterval\",\"clearTimeout\",\"click\",\"clip\",\"close\",\"closed\",\"colorDepth\",\"compile\",\"complete\",\"confirm\",\"constructor\",\"cookie\",\"current\",\"cursor\",\"data\",\"defaultChecked\",\"defaultSelected\",\"defaultStatus\",\"defaultValue\",\"description\",\"disableExternalCapture\",\"domain\",\"elements\",\"embeds\",\"enableExternalCapture\",\"enabledPlugin\",\"encoding\",\"eval\",\"exec\",\"fgColor\",\"filename\",\"find\",\"fixed\",\"focus\",\"fontcolor\",\"fontsize\",\"form\",\"formName\",\"forms\",\"forward\",\"frames\",\"fromCharCode\",\"getDate\",\"getDay\",\"getHours\",\"getMiliseconds\",\"getMinutes\",\"getMonth\",\"getSeconds\",\"getSelection\",\"getTime\",\"getTimezoneOffset\",\"getUTCDate\",\"getUTCDay\",\"getUTCFullYear\",\"getUTCHours\",\"getUTCMilliseconds\",\"getUTCMinutes\",\"getUTCMonth\",\"getUTCSeconds\",\"getYear\",\"global\",\"go\",\"hash\",\"height\",\"history\",\"home\",\"host\",\"hostname\",\"href\",\"hspace\",\"ignoreCase\",\"images\",\"index\",\"indexOf\",\"innerHeight\",\"innerWidth\",\"input\",\"italics\",\"javaEnabled\",\"join\",\"language\",\"lastIndex\",\"lastIndexOf\",\"lastModified\",\"lastParen\",\"layerX\",\"layerY\",\"layers\",\"left\",\"leftContext\",\"length\",\"link\",\"linkColor\",\"links\",\"load\",\"location\",\"locationbar\",\"lowsrc\",\"match\",\"menubar\",\"method\",\"mimeTypes\",\"modifiers\",\"moveAbove\",\"moveBelow\",\"moveBy\",\"moveTo\",\"moveToAbsolute\",\"multiline\",\"name\",\"negative_infinity\",\"next\",\"open\",\"opener\",\"options\",\"outerHeight\",\"outerWidth\",\"pageX\",\"pageXoffset\",\"pageY\",\"pageYoffset\",\"parent\",\"parse\",\"pathname\",\"personalbar\",\"pixelDepth\",\"platform\",\"plugins\",\"pop\",\"port\",\"positive_infinity\",\"preference\",\"previous\",\"print\",\"prompt\",\"protocol\",\"prototype\",\"push\",\"referrer\",\"refresh\",\"releaseEvents\",\"reload\",\"replace\",\"reset\",\"resizeBy\",\"resizeTo\",\"reverse\",\"rightContext\",\"screenX\",\"screenY\",\"scroll\",\"scrollBy\",\"scrollTo\",\"scrollbar\",\"search\",\"select\",\"selected\",\"selectedIndex\",\"self\",\"setDate\",\"setHours\",\"setMinutes\",\"setMonth\",\"setSeconds\",\"setTime\",\"setTimeout\",\"setUTCDate\",\"setUTCDay\",\"setUTCFullYear\",\"setUTCHours\",\"setUTCMilliseconds\",\"setUTCMinutes\",\"setUTCMonth\",\"setUTCSeconds\",\"setYear\",\"shift\",\"siblingAbove\",\"siblingBelow\",\"small\",\"sort\",\"source\",\"splice\",\"split\",\"src\",\"status\",\"statusbar\",\"strike\",\"sub\",\"submit\",\"substr\",\"substring\",\"suffixes\",\"sup\",\"taintEnabled\",\"target\",\"test\",\"text\",\"title\",\"toGMTString\",\"toLocaleString\",\"toLowerCase\",\"toSource\",\"toString\",\"toUTCString\",\"toUpperCase\",\"toolbar\",\"top\",\"type\",\"unshift\",\"unwatch\",\"userAgent\",\"value\",\"valueOf\",\"visibility\",\"vlinkColor\",\"vspace\",\"watch\",\"which\",\"width\",\"write\",\"writeln\",\"x\",\"y\",\"zIndex\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectIdentifier, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Float, rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Int, rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '\"', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"String\")]},Rule {rMatcher = DetectChar '\\'', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"String 1\")]},Rule {rMatcher = Detect2Chars '/' '/', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"JSComment\")]},Rule {rMatcher = Detect2Chars '/' '*', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"Multi/inline Comment\")]},Rule {rMatcher = RegExpr (RE {reString = \"[=?:]\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"(Internal regex catch)\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\(\", reCaseSensitive = True}), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"(Internal regex catch)\")]},Rule {rMatcher = DetectChar '{', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar '}', rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = AnyChar \":!%&+,-/.*<=>?[]|~^;\", 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}),(\"Comment\",Context {cName = \"Comment\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"-->\", rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"-(-(?!->))+\", reCaseSensitive = True}), rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"Alerts\",\"\"), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectIdentifier, rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = CommentTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"Doctype\",Context {cName = \"Doctype\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = DetectChar '>', rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar '[', rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"Doctype Internal Subset\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"Doctype Internal Subset\",Context {cName = \"Doctype Internal Subset\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = DetectChar ']', rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"', rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar '\"', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"Doctype Markupdecl DQ\")]},Rule {rMatcher = DetectChar '\\'', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"Doctype Markupdecl SQ\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"Doctype Markupdecl DQ\",Context {cName = \"Doctype Markupdecl DQ\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = DetectChar '\"', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"XUL\",\"FindPEntityRefs\"), 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}),(\"Doctype Markupdecl SQ\",Context {cName = \"Doctype Markupdecl SQ\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = DetectChar '\\'', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"XUL\",\"FindPEntityRefs\"), 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}),(\"El Content\",Context {cName = \"El Content\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop,Pop]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\S\", reCaseSensitive = True}), rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"Element\",Context {cName = \"Element\", cSyntax = \"XUL\", 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 = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"El Content\")]},Rule {rMatcher = RegExpr (RE {reString = \"[A-Za-z_:][\\\\w.:_-]*\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Push (\"XUL\",\"Attribute\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\s+[A-Za-z_:][\\\\w.:_-]*\", reCaseSensitive = True}), rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"XUL\",\"Attribute\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\S\", reCaseSensitive = True}), rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"FindEntityRefs\",Context {cName = \"FindEntityRefs\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"&(#[0-9]+|#[xX][0-9A-Fa-f]+|[A-Za-z_:][\\\\w.:_-]*);\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = AnyChar \"&<\", rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"FindPEntityRefs\",Context {cName = \"FindPEntityRefs\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"&(#[0-9]+|#[xX][0-9A-Fa-f]+|[A-Za-z_:][\\\\w.:_-]*);\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"%[A-Za-z_:][\\\\w.:_-]*;\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = AnyChar \"&%\", rAttribute = ErrorTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"FindXML\",Context {cName = \"FindXML\", cSyntax = \"XUL\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = StringDetect \"