{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Css (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"CSS\", sFilename = \"css.xml\", sShortname = \"Css\", sContexts = fromList [(\"Base\",Context {cName = \"Base\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = LineContinue, rAttribute = NormalTok, 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 = IncludeRules (\"CSS\",\"FindRuleSets\"), 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 = \"CSS\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '*' '/', 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 = []},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}),(\"FindComments\",Context {cName = \"FindComments\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"/\\\\*BEGIN.*\\\\*/\", reCaseSensitive = True}), rAttribute = RegionMarkerTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"/\\\\*END.*\\\\*/\", reCaseSensitive = True}), rAttribute = RegionMarkerTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Detect2Chars '/' '*', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"Comment\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"FindRuleSets\",Context {cName = \"FindRuleSets\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"@media\\\\b\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"Media\")]},Rule {rMatcher = RegExpr (RE {reString = \"@import\\\\b\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"Import\")]},Rule {rMatcher = RegExpr (RE {reString = \"@(font-face|charset)\\\\b\", reCaseSensitive = True}), rAttribute = DecValTok, 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 = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"RuleSet\")]},Rule {rMatcher = DetectChar '[', rAttribute = AttributeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"SelAttr\")]},Rule {rMatcher = RegExpr (RE {reString = \"#(-)?([_a-zA-Z]|(\\\\\\\\[0-9a-fA-F]{1,6})|(\\\\\\\\[^\\\\n\\\\r\\\\f0-9a-fA-F]))([_a-zA-Z0-9-]|(\\\\\\\\[0-9a-fA-F]{1,6})|(\\\\\\\\[^\\\\n\\\\r\\\\f0-9a-fA-F]))*\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\.([a-zA-Z0-9\\\\-_]|[\\\\x80-\\\\xFF]|\\\\\\\\[0-9A-Fa-f]{1,6})*\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \":lang\\\\([\\\\w_-]+\\\\)\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar ':', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"SelPseudo\")]},Rule {rMatcher = IncludeRules (\"CSS\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindComments\"), 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 = \"CSS\", cRules = [Rule {rMatcher = DetectChar '\"', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"StringDQ\")]},Rule {rMatcher = DetectChar '\\'', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"StringSQ\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"FindValues\",Context {cName = \"FindValues\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"[-+]?[0-9.]+(em|ex|ch|rem|vw|vh|vm|px|in|cm|mm|pt|pc|deg|rad|grad|turn|ms|s|Hz|kHz)\\\\b\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[-+]?[0-9.]+[%]?\", 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 = []}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"Import\",Context {cName = \"Import\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectChar ';', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !&()*+,./:;<=>?[\\\\]^{|}~\"}) (CaseInsensitiveWords (fromList [\"all\",\"aural\",\"braille\",\"embossed\",\"handheld\",\"print\",\"projection\",\"screen\",\"speech\",\"tty\",\"tv\"])), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindValues\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindComments\"), 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}),(\"InsideString\",Context {cName = \"InsideString\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\\\\\[\\\"']\", reCaseSensitive = True}), rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectIdentifier, 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}),(\"MQEE\",Context {cName = \"MQEE\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindComments\"), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = DetectChar ':', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"MQEV\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\)\\\\s+and\\\\s+\\\\(\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar ')', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]}], cAttribute = DecValTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"MQEV\",Context {cName = \"MQEV\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"[1-9][0-9.]*\\\\s*/\\\\s*[1-9][0-9.]*\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"[0-9.]+(em|ex|ch|rem|vw|vh|vm|px|in|cm|mm|pt|pc|deg|rad|grad|turn|ms|s|Hz|kHz|dpi|dpcm)\\\\b\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"[0-9.]+[%]?\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = RegExpr (RE {reString = \"(portrait|landscape)\", reCaseSensitive = True}), rAttribute = DataTypeTok, 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 = []}], cAttribute = DecValTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"Media\",Context {cName = \"Media\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectChar '{', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"Media2\")]},Rule {rMatcher = DetectChar '(', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"MediaQueryExpression\")]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !&()*+,./:;<=>?[\\\\]^{|}~\"}) (CaseInsensitiveWords (fromList [\"all\",\"aural\",\"braille\",\"embossed\",\"handheld\",\"print\",\"projection\",\"screen\",\"speech\",\"tty\",\"tv\"])), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"MediaQueries\")]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !&()*+,./:;<=>?[\\\\]^{|}~\"}) (CaseInsensitiveWords (fromList [\"not\",\"only\"])), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"MediaTypes\")]},Rule {rMatcher = DetectChar ',', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindComments\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},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}),(\"Media2\",Context {cName = \"Media2\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"CSS\",\"FindRuleSets\"), 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}),(\"MediaQueries\",Context {cName = \"MediaQueries\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\s+and\\\\s+\\\\(\", reCaseSensitive = True}), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"MediaQueryExpression\")]},Rule {rMatcher = DetectChar '{', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar ',', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectSpaces, rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindComments\"), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},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 = DecValTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"MediaQueryExpression\",Context {cName = \"MediaQueryExpression\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectSpaces, rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !&()*+,./:;<=>?[\\\\]^{|}~\"}) (CaseInsensitiveWords (fromList [\"aspect-ratio\",\"color\",\"color-index\",\"device-aspect-ratio\",\"device-height\",\"device-width\",\"grid\",\"height\",\"max-aspect-ratio\",\"max-color\",\"max-color-index\",\"max-device-aspect-ratio\",\"max-device-height\",\"max-device-width\",\"max-height\",\"max-monochrome\",\"max-resolution\",\"max-width\",\"min-aspect-ratio\",\"min-color\",\"min-color-index\",\"min-device-aspect-ratio\",\"min-device-height\",\"min-device-width\",\"min-height\",\"min-monochrome\",\"min-resolution\",\"min-width\",\"monochrome\",\"orientation\",\"resolution\",\"scan\",\"width\"])), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"MQEE\")]},Rule {rMatcher = IncludeRules (\"CSS\",\"FindComments\"), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},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 = DecValTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"MediaTypes\",Context {cName = \"MediaTypes\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !&()*+,./:;<=>?[\\\\]^{|}~\"}) (CaseInsensitiveWords (fromList [\"all\",\"aural\",\"braille\",\"embossed\",\"handheld\",\"print\",\"projection\",\"screen\",\"speech\",\"tty\",\"tv\"])), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"MediaQueries\")]},Rule {rMatcher = DetectChar '{', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectChar ',', rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = True, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = DetectSpaces, rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindComments\"), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},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 = DecValTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"PropParen\",Context {cName = \"PropParen\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectChar '(', rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"PropParen2\")]},Rule {rMatcher = IncludeRules (\"CSS\",\"FindComments\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},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}),(\"PropParen2\",Context {cName = \"PropParen2\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectChar ')', rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop,Pop]},Rule {rMatcher = IncludeRules (\"CSS\",\"FindValues\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindComments\"), 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}),(\"Rule\",Context {cName = \"Rule\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectChar ':', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"Rule2\")]},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}),(\"Rule2\",Context {cName = \"Rule2\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectChar ';', 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 = [Pop,Pop,Pop]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !&()*+,./:;<=>?[\\\\]^{|}~\"}) (CaseInsensitiveWords (fromList [\"-epub-hyphens\",\"100\",\"200\",\"300\",\"400\",\"500\",\"600\",\"700\",\"800\",\"900\",\"above\",\"absolute\",\"always\",\"armenian\",\"auto\",\"avoid\",\"baseline\",\"below\",\"bidi-override\",\"blink\",\"block\",\"bold\",\"bolder\",\"border-box\",\"both\",\"bottom\",\"box\",\"break\",\"capitalize\",\"caption\",\"center\",\"circle\",\"cjk-ideographic\",\"clip\",\"close-quote\",\"collapse\",\"compact\",\"condensed\",\"content-box\",\"crop\",\"cross\",\"crosshair\",\"cursive\",\"dashed\",\"decimal\",\"decimal-leading-zero\",\"default\",\"disc\",\"dotted\",\"double\",\"e-resize\",\"ellipsis\",\"ellipsis-word\",\"embed\",\"expanded\",\"extra-condensed\",\"extra-expanded\",\"fantasy\",\"fixed\",\"georgian\",\"groove\",\"hand\",\"hebrew\",\"help\",\"hidden\",\"hide\",\"higher\",\"hiragana\",\"hiragana-iroha\",\"icon\",\"inherit\",\"inline\",\"inline-block\",\"inline-table\",\"inset\",\"inside\",\"invert\",\"italic\",\"justify\",\"katakana\",\"katakana-iroha\",\"konq-center\",\"landscape\",\"large\",\"larger\",\"left\",\"level\",\"light\",\"lighter\",\"line-through\",\"list-item\",\"loud\",\"lower\",\"lower-alpha\",\"lower-greek\",\"lower-latin\",\"lower-roman\",\"lowercase\",\"ltr\",\"marker\",\"medium\",\"menu\",\"message-box\",\"middle\",\"mix\",\"monospace\",\"move\",\"n-resize\",\"narrower\",\"ne-resize\",\"no-close-quote\",\"no-open-quote\",\"no-repeat\",\"none\",\"normal\",\"nowrap\",\"nw-resize\",\"oblique\",\"open-quote\",\"outset\",\"outside\",\"overline\",\"pointer\",\"portrait\",\"pre\",\"pre-line\",\"pre-wrap\",\"relative\",\"repeat\",\"repeat-x\",\"repeat-y\",\"ridge\",\"right\",\"rtl\",\"run-in\",\"s-resize\",\"sans-serif\",\"scroll\",\"se-resize\",\"semi-condensed\",\"semi-expanded\",\"separate\",\"serif\",\"show\",\"small\",\"small-caps\",\"small-caption\",\"smaller\",\"solid\",\"square\",\"static\",\"static-position\",\"status-bar\",\"sub\",\"super\",\"sw-resize\",\"table\",\"table-caption\",\"table-cell\",\"table-column\",\"table-column-group\",\"table-footer-group\",\"table-header-group\",\"table-row\",\"table-row-group\",\"text\",\"text-bottom\",\"text-top\",\"thick\",\"thin\",\"top\",\"transparent\",\"ultra-condensed\",\"ultra-expanded\",\"underline\",\"upper-alpha\",\"upper-latin\",\"upper-roman\",\"uppercase\",\"visible\",\"w-resize\",\"wait\",\"wider\",\"x-large\",\"x-small\",\"xx-large\",\"xx-small\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !&()*+,./:;<=>?[\\\\]^{|}~\"}) (CaseInsensitiveWords (fromList [\"ActiveBorder\",\"ActiveCaption\",\"AppWorkspace\",\"aqua\",\"Background\",\"black\",\"blue\",\"ButtonFace\",\"ButtonHighlight\",\"ButtonShadow\",\"ButtonText\",\"CaptionText\",\"cyan\",\"fuchsia\",\"gray\",\"GrayText\",\"green\",\"Highlight\",\"HighlightText\",\"InactiveBorder\",\"InactiveCaption\",\"InactiveCaptionText\",\"InfoBackground\",\"InfoText\",\"lime\",\"maroon\",\"Menu\",\"MenuText\",\"navy\",\"olive\",\"purple\",\"red\",\"Scrollbar\",\"silver\",\"teal\",\"ThreeDDarkShadow\",\"ThreeDFace\",\"ThreeDHighlight\",\"ThreeDLightShadow\",\"ThreeDShadow\",\"white\",\"Window\",\"WindowFrame\",\"WindowText\",\"yellow\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"#([0-9A-Fa-f]{3}){1,4}\\\\b\", reCaseSensitive = True}), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !&()*+,./:;<=>?[\\\\]^{|}~\"}) (CaseInsensitiveWords (fromList [\"attr\",\"counter\",\"counters\",\"expression\",\"format\",\"hsl\",\"hsla\",\"local\",\"rect\",\"rgb\",\"rgba\",\"url\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"PropParen\")]},Rule {rMatcher = RegExpr (RE {reString = \"!important\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindValues\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindStrings\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = IncludeRules (\"CSS\",\"FindComments\"), 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}),(\"RuleSet\",Context {cName = \"RuleSet\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectChar '}', rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !&()*+,./:;<=>?[\\\\]^{|}~\"}) (CaseInsensitiveWords (fromList [\"-khtml-background-size\",\"-khtml-border-bottom-left-radius\",\"-khtml-border-bottom-right-radius\",\"-khtml-border-radius\",\"-khtml-border-top-left-radius\",\"-khtml-border-top-right-radius\",\"-khtml-box-shadow\",\"-khtml-opacity\",\"-moz-animation-delay\",\"-moz-animation-direction\",\"-moz-animation-duration\",\"-moz-animation-fill-mode\",\"-moz-animation-iteration\",\"-moz-animation-name\",\"-moz-animation-play-state\",\"-moz-background-size\",\"-moz-border-bottom-colors\",\"-moz-border-image\",\"-moz-border-left-colors\",\"-moz-border-radius\",\"-moz-border-radius-bottomleft\",\"-moz-border-radius-bottomright\",\"-moz-border-radius-topleft\",\"-moz-border-radius-topright\",\"-moz-border-right-colors\",\"-moz-border-top-colors\",\"-moz-box\",\"-moz-box-flex\",\"-moz-box-shadow\",\"-moz-box-sizing\",\"-moz-column-count\",\"-moz-column-gap\",\"-moz-hyphens\",\"-moz-linear-gradient\",\"-moz-opacity\",\"-moz-outline-style\",\"-moz-perspective\",\"-moz-radial-gradient\",\"-moz-resize\",\"-moz-transform\",\"-moz-transform-origin\",\"-moz-transform-style\",\"-moz-transition\",\"-moz-transition-duration\",\"-moz-transition-property\",\"-ms-animation-delay\",\"-ms-animation-direction\",\"-ms-animation-duration\",\"-ms-animation-fill-mode\",\"-ms-animation-iteration\",\"-ms-animation-name\",\"-ms-animation-play-state\",\"-ms-box-sizing\",\"-ms-filter\",\"-ms-interpolation-mode\",\"-ms-linear-gradient\",\"-ms-text-size-adjust\",\"-ms-transform\",\"-ms-transition\",\"-o-background-size\",\"-o-linear-gradient\",\"-o-text-overflow\",\"-o-transform-origin\",\"-o-transition\",\"-webkit-animation-delay\",\"-webkit-animation-direction\",\"-webkit-animation-duration\",\"-webkit-animation-fill-mode\",\"-webkit-animation-iteration\",\"-webkit-animation-name\",\"-webkit-animation-play-state\",\"-webkit-appearance\",\"-webkit-background-size\",\"-webkit-border-bottom-colors\",\"-webkit-border-bottom-left-radius\",\"-webkit-border-bottom-right-radius\",\"-webkit-border-image\",\"-webkit-border-left-colors\",\"-webkit-border-radius\",\"-webkit-border-radius-bottomleft\",\"-webkit-border-radius-bottomright\",\"-webkit-border-right-colors\",\"-webkit-border-top-colors\",\"-webkit-border-top-left-radius\",\"-webkit-border-top-right-radius\",\"-webkit-box-flex\",\"-webkit-box-reflect\",\"-webkit-box-shadow\",\"-webkit-box-sizing\",\"-webkit-column-count\",\"-webkit-column-gap\",\"-webkit-gradient\",\"-webkit-hyphens\",\"-webkit-linear-gradient\",\"-webkit-perspective\",\"-webkit-text-fill-color\",\"-webkit-text-size-adjust\",\"-webkit-text-stroke-color\",\"-webkit-text-stroke-width\",\"-webkit-transform\",\"-webkit-transform-origin\",\"-webkit-transform-style\",\"-webkit-transition\",\"-webkit-transition-duration\",\"-webkit-transition-property\",\"align-content\",\"align-items\",\"align-self\",\"alignment-baseline\",\"all\",\"animation-delay\",\"animation-direction\",\"animation-duration\",\"animation-fill-mode\",\"animation-iteration-count\",\"animation-name\",\"animation-play-state\",\"animation-timing-function\",\"ascent\",\"azimuth\",\"backface-visibility\",\"background\",\"background-attachment\",\"background-blend-mode\",\"background-break\",\"background-clip\",\"background-color\",\"background-image\",\"background-origin\",\"background-position\",\"background-repeat\",\"background-size\",\"baseline\",\"baseline-shift\",\"bbox\",\"bookmark-label\",\"bookmark-level\",\"border\",\"border-bottom\",\"border-bottom-color\",\"border-bottom-image\",\"border-bottom-left-image\",\"border-bottom-left-radius\",\"border-bottom-right-image\",\"border-bottom-right-radius\",\"border-bottom-style\",\"border-bottom-width\",\"border-boundary\",\"border-collapse\",\"border-color\",\"border-corner-image\",\"border-image\",\"border-image-outset\",\"border-image-repeat\",\"border-image-slice\",\"border-image-source\",\"border-image-width\",\"border-left\",\"border-left-color\",\"border-left-image\",\"border-left-style\",\"border-left-width\",\"border-radius\",\"border-right\",\"border-right-color\",\"border-right-image\",\"border-right-style\",\"border-right-width\",\"border-spacing\",\"border-style\",\"border-top\",\"border-top-color\",\"border-top-image\",\"border-top-left-image\",\"border-top-left-radius\",\"border-top-right-image\",\"border-top-right-radius\",\"border-top-style\",\"border-top-width\",\"border-width\",\"bottom\",\"box-align\",\"box-decoration-break\",\"box-direction\",\"box-flex\",\"box-shadow\",\"box-sizing\",\"box-snap\",\"box-suppress\",\"break-after\",\"break-before\",\"break-inside\",\"cap-height\",\"caption-side\",\"caret-color\",\"centerline\",\"chains\",\"clear\",\"clip\",\"clip-path\",\"clip-rule\",\"color\",\"color-interpolation-filters\",\"column-count\",\"column-fill\",\"column-gap\",\"column-rule\",\"column-rule-color\",\"column-rule-style\",\"column-rule-width\",\"column-span\",\"column-width\",\"columns\",\"content\",\"counter-increment\",\"counter-reset\",\"counter-set\",\"cue\",\"cue-after\",\"cue-before\",\"cursor\",\"definition-src\",\"descent\",\"direction\",\"display\",\"dominant-baseline\",\"elevation\",\"empty-cells\",\"filter\",\"flex\",\"flex-basis\",\"flex-direction\",\"flex-flow\",\"flex-grow\",\"flex-shrink\",\"flex-wrap\",\"float\",\"flood-color\",\"flood-opacity\",\"flow\",\"flow-from\",\"flow-into\",\"font\",\"font-family\",\"font-feature-settings\",\"font-kerning\",\"font-language-override\",\"font-size\",\"font-size-adjust\",\"font-stretch\",\"font-style\",\"font-synthesis\",\"font-variant\",\"font-variant-alternates\",\"font-variant-caps\",\"font-variant-east-asian\",\"font-variant-ligatures\",\"font-variant-numeric\",\"font-variant-position\",\"font-weight\",\"footnote-display\",\"footnote-policy\",\"glyph-orientation-vertical\",\"grid\",\"grid-area\",\"grid-auto-columns\",\"grid-auto-flow\",\"grid-auto-rows\",\"grid-column\",\"grid-column-end\",\"grid-column-gap\",\"grid-column-start\",\"grid-gap\",\"grid-row\",\"grid-row-end\",\"grid-row-gap\",\"grid-row-start\",\"grid-template\",\"grid-template-areas\",\"grid-template-columns\",\"grid-template-rows\",\"hanging-punctuation\",\"height\",\"hyphens\",\"image-orientation\",\"image-rendering\",\"image-resolution\",\"initial-letter\",\"initial-letter-align\",\"initial-letter-wrap\",\"isolation\",\"justify-content\",\"justify-items\",\"justify-self\",\"konq_bgpos_x\",\"konq_bgpos_y\",\"left\",\"letter-spacing\",\"lighting-color\",\"line-grid\",\"line-height\",\"line-snap\",\"linear-gradient\",\"list-style\",\"list-style-image\",\"list-style-keyword\",\"list-style-position\",\"list-style-type\",\"margin\",\"margin-bottom\",\"margin-left\",\"margin-right\",\"margin-top\",\"marker-offset\",\"marker-side\",\"marquee-direction\",\"marquee-loop\",\"marquee-speed\",\"marquee-style\",\"mask\",\"mask-border\",\"mask-border-mode\",\"mask-border-outset\",\"mask-border-repeat\",\"mask-border-slice\",\"mask-border-source\",\"mask-border-width\",\"mask-clip\",\"mask-composite\",\"mask-image\",\"mask-mode\",\"mask-origin\",\"mask-position\",\"mask-repeat\",\"mask-size\",\"mask-type\",\"mathline\",\"max-height\",\"max-lines\",\"max-width\",\"min-height\",\"min-width\",\"mix-blend-mode\",\"nav-down\",\"nav-left\",\"nav-right\",\"nav-up\",\"object-fit\",\"object-position\",\"offset-after\",\"offset-before\",\"offset-end\",\"offset-start\",\"opacity\",\"order\",\"orphans\",\"outline\",\"outline-color\",\"outline-offset\",\"outline-style\",\"outline-width\",\"overflow\",\"overflow-style\",\"overflow-wrap\",\"overflow-x\",\"overflow-y\",\"padding\",\"padding-bottom\",\"padding-left\",\"padding-right\",\"padding-top\",\"page\",\"page-break-after\",\"page-break-before\",\"page-break-inside\",\"panose-1\",\"pause\",\"pause-after\",\"pause-before\",\"perspective\",\"perspective-origin\",\"pitch\",\"pitch-range\",\"play-during\",\"pointer-events\",\"polar-anchor\",\"polar-angle\",\"polar-distance\",\"polar-origin\",\"position\",\"presentation-level\",\"quotes\",\"resize\",\"rest\",\"rest-after\",\"rest-before\",\"richness\",\"right\",\"rotation\",\"rotation-point\",\"ruby-align\",\"ruby-merge\",\"ruby-position\",\"running\",\"scroll-behavior\",\"scroll-snap-align\",\"scroll-snap-margin\",\"scroll-snap-margin-block\",\"scroll-snap-margin-block-end\",\"scroll-snap-margin-block-start\",\"scroll-snap-margin-bottom\",\"scroll-snap-margin-inline\",\"scroll-snap-margin-inline-end\",\"scroll-snap-margin-inline-start\",\"scroll-snap-margin-left\",\"scroll-snap-margin-right\",\"scroll-snap-margin-top\",\"scroll-snap-padding\",\"scroll-snap-padding-block\",\"scroll-snap-padding-block-end\",\"scroll-snap-padding-block-start\",\"scroll-snap-padding-bottom\",\"scroll-snap-padding-inline\",\"scroll-snap-padding-inline-end\",\"scroll-snap-padding-inline-start\",\"scroll-snap-padding-left\",\"scroll-snap-padding-right\",\"scroll-snap-padding-top\",\"scroll-snap-stop\",\"scroll-snap-type\",\"shape-image-threshold\",\"shape-inside\",\"shape-margin\",\"shape-outside\",\"size\",\"slope\",\"speak\",\"speak-as\",\"speak-header\",\"speak-numeral\",\"speak-punctuation\",\"speech-rate\",\"src\",\"stemh\",\"stemv\",\"stress\",\"string-set\",\"tab-size\",\"table-layout\",\"text-align\",\"text-align-last\",\"text-combine-upright\",\"text-decoration\",\"text-decoration-color\",\"text-decoration-line\",\"text-decoration-skip\",\"text-decoration-style\",\"text-emphasis\",\"text-emphasis-color\",\"text-emphasis-position\",\"text-emphasis-style\",\"text-indent\",\"text-justify\",\"text-orientation\",\"text-overflow\",\"text-shadow\",\"text-transform\",\"text-underline-position\",\"text-wrap\",\"top\",\"topline\",\"transform\",\"transform-origin\",\"transform-style\",\"transition\",\"transition-delay\",\"transition-duration\",\"transition-property\",\"transition-timing-function\",\"unicode-bidi\",\"unicode-range\",\"units-per-em\",\"vertical-align\",\"visibility\",\"voice-balance\",\"voice-duration\",\"voice-family\",\"voice-pitch\",\"voice-range\",\"voice-rate\",\"voice-stress\",\"voice-volume\",\"volume\",\"white-space\",\"widows\",\"width\",\"widths\",\"will-change\",\"word-break\",\"word-spacing\",\"word-wrap\",\"wrap-flow\",\"wrap-through\",\"writing-mode\",\"x-height\",\"z-index\",\"zoom\"])), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"Rule\")]},Rule {rMatcher = RegExpr (RE {reString = \"-?[A-Za-z_-]+(?=\\\\s*:)\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"CSS\",\"Rule\")]},Rule {rMatcher = IncludeRules (\"CSS\",\"FindComments\"), rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},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}),(\"SelAttr\",Context {cName = \"SelAttr\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectChar ']', rAttribute = AttributeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"CSS\",\"FindStrings\"), rAttribute = AttributeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []}], cAttribute = AttributeTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"SelPseudo\",Context {cName = \"SelPseudo\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = False, keywordDelims = fromList \"\\t\\n !&()*+,./:;<=>?[\\\\]^{|}~\"}) (CaseInsensitiveWords (fromList [\"active\",\"after\",\"before\",\"checked\",\"disabled\",\"empty\",\"enabled\",\"first-child\",\"first-letter\",\"first-line\",\"first-of-type\",\"focus\",\"hover\",\"indeterminate\",\"last-child\",\"last-of-type\",\"link\",\"not\",\"nth-child\",\"nth-last-child\",\"nth-last-of-type\",\"nth-of-type\",\"only-child\",\"only-of-type\",\"root\",\"selection\",\"target\",\"visited\"])), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]}], cAttribute = DecValTok, cLineEmptyContext = [], cLineEndContext = [Pop], cLineBeginContext = [], cFallthrough = True, cFallthroughContext = [Pop], cDynamic = False}),(\"StringDQ\",Context {cName = \"StringDQ\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectChar '\"', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"CSS\",\"InsideString\"), 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}),(\"StringSQ\",Context {cName = \"StringSQ\", cSyntax = \"CSS\", cRules = [Rule {rMatcher = DetectChar '\\'', rAttribute = StringTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Pop]},Rule {rMatcher = IncludeRules (\"CSS\",\"InsideString\"), 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})], sAuthor = \"Wilbert Berendsen (wilbert@kde.nl)\", sVersion = \"3\", sLicense = \"LGPL\", sExtensions = [\"*.css\"], sStartingContext = \"Base\"}"