{- This module was generated from data in the Kate syntax highlighting file css.xml, version 3, by Wilbert Berendsen (wilbert@kde.nl) -} module Text.Highlighting.Kate.Syntax.Css (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Alert import Text.ParserCombinators.Parsec hiding (State) import Control.Monad.State import Data.Char (isSpace) import qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "CSS" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.css" -- | Highlight source code using this syntax definition. highlight :: String -> [SourceLine] highlight input = evalState (mapM parseSourceLine $ lines input) startingState parseSourceLine :: String -> State SyntaxState SourceLine parseSourceLine = mkParseSourceLine (parseExpression Nothing) -- | Parse an expression using appropriate local context. parseExpression :: Maybe (String,String) -> KateParser Token parseExpression mbcontext = do (lang,cont) <- maybe currentContext return mbcontext result <- parseRules (lang,cont) optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("CSS","Base")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStContinuation = False, synStCaseSensitive = True, synStKeywordCaseSensitive = False, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext contexts <- synStContexts `fmap` getState st <- getState if length contexts >= 2 then case context of _ | synStContinuation st -> updateState $ \st -> st{ synStContinuation = False } ("CSS","Base") -> return () ("CSS","FindRuleSets") -> return () ("CSS","FindValues") -> return () ("CSS","FindStrings") -> return () ("CSS","FindComments") -> return () ("CSS","Media") -> return () ("CSS","MediaTypes") -> return () ("CSS","MediaQueries") -> return () ("CSS","MediaQueryExpression") -> return () ("CSS","MQEE") -> return () ("CSS","MQEV") -> return () ("CSS","Media2") -> return () ("CSS","SelAttr") -> return () ("CSS","SelPseudo") -> (popContext) >> pEndLine ("CSS","Import") -> return () ("CSS","Comment") -> return () ("CSS","RuleSet") -> return () ("CSS","Rule") -> return () ("CSS","Rule2") -> return () ("CSS","PropParen") -> return () ("CSS","PropParen2") -> return () ("CSS","StringDQ") -> return () ("CSS","StringSQ") -> return () ("CSS","InsideString") -> return () _ -> return () else return () withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" updateState $ \st -> st { synStPrevChar = last txt , synStPrevNonspace = synStPrevNonspace st || not (all isSpace txt) } return (attr, txt) list_properties = Set.fromList $ words $ "azimuth align-content align-items align-self alignment-baseline all animation-name animation-duration animation-iteration-count animation-direction animation-delay animation-play-state animation-fill-mode animation-timing-function 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-shift bookmark-label bookmark-level bookmark-level border border-bottom border-bottom-color border-bottom-image border-bottom-style border-bottom-width border-bottom-left-image border-bottom-left-radius border-bottom-right-image border-bottom-right-radius 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-style border-top-width border-top-left-image border-top-left-radius border-top-right-image border-top-right-radius 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 caret-color caption-side 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 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-size font-size-adjust font-stretch font-style font-variant font-weight font-stretch font-feature-settings font-kerning font-language-override font-synthesis font-variant-alternates font-variant-caps font-variant-east-asian font-variant-ligatures font-variant-numeric font-variant-position 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 left letter-spacing lighting-color linear-gradient line-grid line-height line-snap 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 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 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 speak speak-as speak-header speak-numeral speak-punctuation speech-rate 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 transform transform-origin transform-style transition transition-delay transition-property transition-duration transition-timing-function unicode-bidi vertical-align visibility voice-balance voice-duration voice-family voice-pitch voice-range voice-rate voice-stress voice-volume volume white-space widows width will-change word-break word-spacing word-wrap wrap-flow wrap-through writing-mode z-index -moz-animation-name -moz-animation-duration -moz-animation-iteration -moz-animation-direction -moz-animation-delay -moz-animation-play-state -moz-animation-fill-mode -moz-background-size -moz-border-image -moz-border-bottom-colors -moz-border-left-colors -moz-border-radius -moz-border-radius-topleft -moz-border-radius-topright -moz-border-radius-bottomleft -moz-border-radius-bottomright -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-property -moz-transition-duration -o-background-size -o-linear-gradient -o-text-overflow -o-transition -o-transform-origin konq_bgpos_x konq_bgpos_y -khtml-background-size -khtml-border-top-left-radius -khtml-border-top-right-radius -khtml-border-bottom-left-radius -khtml-border-bottom-right-radius -khtml-border-radius -khtml-box-shadow -khtml-opacity -webkit-appearance -webkit-animation-name -webkit-animation-duration -webkit-animation-iteration -webkit-animation-direction -webkit-animation-delay -webkit-animation-play-state -webkit-animation-fill-mode -webkit-background-size -webkit-border-image -webkit-border-bottom-colors -webkit-border-left-colors -webkit-border-radius -webkit-border-right-colors -webkit-border-top-colors -webkit-border-top-left-radius -webkit-border-top-right-radius -webkit-border-bottom-left-radius -webkit-border-bottom-right-radius -webkit-border-radius-bottomleft -webkit-border-radius-bottomright -webkit-box-flex -webkit-box-reflect -webkit-box-shadow -webkit-box-sizing -webkit-column-count -webkit-column-gap -webkit-hyphens -webkit-linear-gradient -webkit-gradient -webkit-perspective -webkit-text-fill-color -webkit-text-stroke-color -webkit-text-stroke-width -webkit-text-size-adjust -webkit-transform -webkit-transform-origin -webkit-transform-style -webkit-transition -webkit-transition-property -webkit-transition-duration zoom -ms-animation-name -ms-animation-duration -ms-animation-iteration -ms-animation-direction -ms-animation-delay -ms-animation-play-state -ms-animation-fill-mode -ms-box-sizing -ms-filter -ms-interpolation-mode -ms-linear-gradient -ms-text-size-adjust -ms-transform -ms-transition font-family font-size font-stretch font-style font-variant font-weight unicode-range units-per-em src panose-1 stemv stemh slope cap-height x-height ascent descent widths bbox definition-src baseline centerline mathline topline" list_types = Set.fromList $ words $ "inherit none hidden dotted dashed solid double groove ridge inset outset xx-small x-small small medium large x-large xx-large smaller larger italic oblique small-caps normal bold bolder lighter light 100 200 300 400 500 600 700 800 900 transparent repeat repeat-x repeat-y no-repeat baseline sub super top text-top middle bottom text-bottom left right center justify konq-center disc circle square box decimal decimal-leading-zero lower-roman upper-roman lower-greek lower-alpha lower-latin upper-alpha upper-latin hebrew armenian georgian cjk-ideographic hiragana katakana hiragana-iroha katakana-iroha inline inline-block block list-item run-in compact marker table inline-table table-row-group table-header-group table-footer-group table-row table-column-group table-column table-cell table-caption auto crosshair default pointer move e-resize ne-resize nw-resize n-resize se-resize sw-resize s-resize w-resize text wait help above absolute always avoid below bidi-override blink both capitalize caption clip close-quote collapse condensed crop cross ellipsis ellipsis-word embed expanded extra-condensed extra-expanded fixed hand hide higher icon inside invert landscape level line-through loud lower lowercase ltr menu message-box mix narrower no-close-quote no-open-quote nowrap open-quote outside overline portrait pre pre-line pre-wrap relative rtl scroll semi-condensed semi-expanded separate show small-caption static static-position status-bar thick thin ultra-condensed ultra-expanded underline uppercase visible wider break serif sans-serif cursive fantasy monospace border-box content-box -epub-hyphens" list_colors = Set.fromList $ words $ "aqua black blue cyan fuchsia gray green lime maroon navy olive purple red silver teal white yellow activeborder activecaption appworkspace background buttonface buttonhighlight buttonshadow buttontext captiontext graytext highlight highlighttext inactiveborder inactivecaption inactivecaptiontext infobackground infotext menu menutext scrollbar threeddarkshadow threedface threedhighlight threedlightshadow threedshadow window windowframe windowtext" list_paren = Set.fromList $ words $ "url attr rect rgb rgba hsl hsla counter counters local format expression" list_mediatypes = Set.fromList $ words $ "all aural braille embossed handheld print projection screen speech tty tv" list_mediatypes'5fop = Set.fromList $ words $ "not only" list_media'5ffeatures = Set.fromList $ words $ "width min-width max-width height min-height max-height device-width min-device-width max-device-width device-height min-device-height max-device-height orientation aspect-ratio min-aspect-ratio max-aspect-ratio device-aspect-ratio min-device-aspect-ratio max-device-aspect-ratio color min-color max-color color-index min-color-index max-color-index monochrome min-monochrome max-monochrome resolution min-resolution max-resolution scan grid" list_pseudoclasses = Set.fromList $ words $ "hover link visited active focus first-child last-child only-child first-of-type last-of-type only-of-type first-letter first-line before after selection root empty target enabled disabled checked indeterminate nth-child nth-last-child nth-of-type nth-last-of-type not" regex_'40media'5cb = compileRegex True "@media\\b" regex_'40import'5cb = compileRegex True "@import\\b" regex_'40'28font'2dface'7ccharset'29'5cb = compileRegex True "@(font-face|charset)\\b" regex_'23'28'2d'29'3f'28'5b'5fa'2dzA'2dZ'5d'7c'28'5c'5c'5b0'2d9a'2dfA'2dF'5d'7b1'2c6'7d'29'7c'28'5c'5c'5b'5e'5cn'5cr'5cf0'2d9a'2dfA'2dF'5d'29'29'28'5b'5fa'2dzA'2dZ0'2d9'2d'5d'7c'28'5c'5c'5b0'2d9a'2dfA'2dF'5d'7b1'2c6'7d'29'7c'28'5c'5c'5b'5e'5cn'5cr'5cf0'2d9a'2dfA'2dF'5d'29'29'2a = compileRegex True "#(-)?([_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]))*" regex_'5c'2e'28'5ba'2dzA'2dZ0'2d9'5c'2d'5f'5d'7c'5b'5cx80'2d'5cxFF'5d'7c'5c'5c'5b0'2d9A'2dFa'2df'5d'7b1'2c6'7d'29'2a = compileRegex True "\\.([a-zA-Z0-9\\-_]|[\\x80-\\xFF]|\\\\[0-9A-Fa-f]{1,6})*" regex_'3alang'5c'28'5b'5cw'5f'2d'5d'2b'5c'29 = compileRegex True ":lang\\([\\w_-]+\\)" regex_'5b'2d'2b'5d'3f'5b0'2d9'2e'5d'2b'28em'7cex'7cch'7crem'7cvw'7cvh'7cvm'7cpx'7cin'7ccm'7cmm'7cpt'7cpc'7cdeg'7crad'7cgrad'7cturn'7cms'7cs'7cHz'7ckHz'29'5cb = compileRegex True "[-+]?[0-9.]+(em|ex|ch|rem|vw|vh|vm|px|in|cm|mm|pt|pc|deg|rad|grad|turn|ms|s|Hz|kHz)\\b" regex_'5b'2d'2b'5d'3f'5b0'2d9'2e'5d'2b'5b'25'5d'3f = compileRegex True "[-+]?[0-9.]+[%]?" regex_'5b'5cw'5c'2d'5d'2b = compileRegex True "[\\w\\-]+" regex_'2f'5c'2aBEGIN'2e'2a'5c'2a'2f = compileRegex True "/\\*BEGIN.*\\*/" regex_'2f'5c'2aEND'2e'2a'5c'2a'2f = compileRegex True "/\\*END.*\\*/" regex_'5cS'2b = compileRegex True "\\S+" regex_'5cs'2band'5cs'2b'5c'28 = compileRegex True "\\s+and\\s+\\(" regex_'5c'29'5cs'2band'5cs'2b'5c'28 = compileRegex True "\\)\\s+and\\s+\\(" regex_'5b1'2d9'5d'5b0'2d9'2e'5d'2a'5cs'2a'2f'5cs'2a'5b1'2d9'5d'5b0'2d9'2e'5d'2a = compileRegex True "[1-9][0-9.]*\\s*/\\s*[1-9][0-9.]*" regex_'5b0'2d9'2e'5d'2b'28em'7cex'7cch'7crem'7cvw'7cvh'7cvm'7cpx'7cin'7ccm'7cmm'7cpt'7cpc'7cdeg'7crad'7cgrad'7cturn'7cms'7cs'7cHz'7ckHz'7cdpi'7cdpcm'29'5cb = compileRegex True "[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" regex_'5b0'2d9'2e'5d'2b'5b'25'5d'3f = compileRegex True "[0-9.]+[%]?" regex_'28portrait'7clandscape'29 = compileRegex True "(portrait|landscape)" regex_'2e'2a = compileRegex True ".*" regex_'2d'3f'5bA'2dZa'2dz'5f'2d'5d'2b'28'3f'3d'5cs'2a'3a'29 = compileRegex True "-?[A-Za-z_-]+(?=\\s*:)" regex_'5cS = compileRegex True "\\S" regex_'23'28'5b0'2d9A'2dFa'2df'5d'7b3'7d'29'7b1'2c4'7d'5cb = compileRegex True "#([0-9A-Fa-f]{3}){1,4}\\b" regex_'21important'5cb = compileRegex True "!important\\b" regex_'5c'5c'5b'22'27'5d = compileRegex True "\\\\[\"']" parseRules ("CSS","Base") = (((pLineContinue >>= withAttribute NormalTok)) <|> ((pDetectSpaces >>= withAttribute NormalTok)) <|> ((parseRules ("CSS","FindRuleSets"))) <|> (currentContext >>= \x -> guard (x == ("CSS","Base")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","FindRuleSets") = (((pRegExpr regex_'40media'5cb >>= withAttribute DecValTok) >>~ pushContext ("CSS","Media")) <|> ((pRegExpr regex_'40import'5cb >>= withAttribute DecValTok) >>~ pushContext ("CSS","Import")) <|> ((pRegExpr regex_'40'28font'2dface'7ccharset'29'5cb >>= withAttribute DecValTok)) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext ("CSS","RuleSet")) <|> ((pDetectChar False '[' >>= withAttribute AttributeTok) >>~ pushContext ("CSS","SelAttr")) <|> ((pRegExpr regex_'23'28'2d'29'3f'28'5b'5fa'2dzA'2dZ'5d'7c'28'5c'5c'5b0'2d9a'2dfA'2dF'5d'7b1'2c6'7d'29'7c'28'5c'5c'5b'5e'5cn'5cr'5cf0'2d9a'2dfA'2dF'5d'29'29'28'5b'5fa'2dzA'2dZ0'2d9'2d'5d'7c'28'5c'5c'5b0'2d9a'2dfA'2dF'5d'7b1'2c6'7d'29'7c'28'5c'5c'5b'5e'5cn'5cr'5cf0'2d9a'2dfA'2dF'5d'29'29'2a >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'5c'2e'28'5ba'2dzA'2dZ0'2d9'5c'2d'5f'5d'7c'5b'5cx80'2d'5cxFF'5d'7c'5c'5c'5b0'2d9A'2dFa'2df'5d'7b1'2c6'7d'29'2a >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'3alang'5c'28'5b'5cw'5f'2d'5d'2b'5c'29 >>= withAttribute DecValTok)) <|> ((pDetectChar False ':' >>= withAttribute DecValTok) >>~ pushContext ("CSS","SelPseudo")) <|> ((parseRules ("CSS","FindStrings"))) <|> ((parseRules ("CSS","FindComments"))) <|> (currentContext >>= \x -> guard (x == ("CSS","FindRuleSets")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","FindValues") = (((pRegExpr regex_'5b'2d'2b'5d'3f'5b0'2d9'2e'5d'2b'28em'7cex'7cch'7crem'7cvw'7cvh'7cvm'7cpx'7cin'7ccm'7cmm'7cpt'7cpc'7cdeg'7crad'7cgrad'7cturn'7cms'7cs'7cHz'7ckHz'29'5cb >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5b'2d'2b'5d'3f'5b0'2d9'2e'5d'2b'5b'25'5d'3f >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5b'5cw'5c'2d'5d'2b >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("CSS","FindValues")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","FindStrings") = (((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("CSS","StringDQ")) <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext ("CSS","StringSQ")) <|> (currentContext >>= \x -> guard (x == ("CSS","FindStrings")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","FindComments") = (((pRegExpr regex_'2f'5c'2aBEGIN'2e'2a'5c'2a'2f >>= withAttribute RegionMarkerTok)) <|> ((pRegExpr regex_'2f'5c'2aEND'2e'2a'5c'2a'2f >>= withAttribute RegionMarkerTok)) <|> ((pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("CSS","Comment")) <|> (currentContext >>= \x -> guard (x == ("CSS","FindComments")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","Media") = (((pDetectChar False '{' >>= withAttribute DecValTok) >>~ pushContext ("CSS","Media2")) <|> ((pDetectChar False '(' >>= withAttribute DecValTok) >>~ pushContext ("CSS","MediaQueryExpression")) <|> ((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_mediatypes >>= withAttribute DecValTok) >>~ pushContext ("CSS","MediaQueries")) <|> ((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_mediatypes'5fop >>= withAttribute DecValTok) >>~ pushContext ("CSS","MediaTypes")) <|> ((pDetectChar False ',' >>= withAttribute DecValTok)) <|> ((parseRules ("CSS","FindComments"))) <|> ((pRegExpr regex_'5cS'2b >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("CSS","Media")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","MediaTypes") = (((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_mediatypes >>= withAttribute DecValTok) >>~ pushContext ("CSS","MediaQueries")) <|> ((lookAhead (pDetectChar False '{') >> (popContext) >> currentContext >>= parseRules)) <|> ((lookAhead (pDetectChar False ',') >> (popContext) >> currentContext >>= parseRules)) <|> ((pDetectSpaces >>= withAttribute DecValTok)) <|> ((parseRules ("CSS","FindComments"))) <|> ((pRegExpr regex_'5cS'2b >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("CSS","MediaTypes")) >> pDefault >>= withAttribute DecValTok)) parseRules ("CSS","MediaQueries") = (((pRegExpr regex_'5cs'2band'5cs'2b'5c'28 >>= withAttribute DecValTok) >>~ pushContext ("CSS","MediaQueryExpression")) <|> ((lookAhead (pDetectChar False '{') >> (popContext) >> currentContext >>= parseRules)) <|> ((lookAhead (pDetectChar False ',') >> (popContext) >> currentContext >>= parseRules)) <|> ((pDetectSpaces >>= withAttribute DecValTok)) <|> ((parseRules ("CSS","FindComments"))) <|> ((pRegExpr regex_'5cS'2b >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("CSS","MediaQueries")) >> pDefault >>= withAttribute DecValTok)) parseRules ("CSS","MediaQueryExpression") = (((pDetectSpaces >>= withAttribute DecValTok)) <|> ((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_media'5ffeatures >>= withAttribute DecValTok) >>~ pushContext ("CSS","MQEE")) <|> ((parseRules ("CSS","FindComments"))) <|> ((pRegExpr regex_'5cS'2b >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("CSS","MediaQueryExpression")) >> pDefault >>= withAttribute DecValTok)) parseRules ("CSS","MQEE") = (((pDetectSpaces >>= withAttribute DecValTok)) <|> ((parseRules ("CSS","FindComments"))) <|> ((pDetectChar False ':' >>= withAttribute DecValTok) >>~ pushContext ("CSS","MQEV")) <|> ((pRegExpr regex_'5c'29'5cs'2band'5cs'2b'5c'28 >>= withAttribute DecValTok) >>~ (popContext)) <|> ((pDetectChar False ')' >>= withAttribute DecValTok) >>~ (popContext >> popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("CSS","MQEV") = (((pDetectSpaces >>= withAttribute DecValTok)) <|> ((pRegExpr regex_'5b1'2d9'5d'5b0'2d9'2e'5d'2a'5cs'2a'2f'5cs'2a'5b1'2d9'5d'5b0'2d9'2e'5d'2a >>= withAttribute DataTypeTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b0'2d9'2e'5d'2b'28em'7cex'7cch'7crem'7cvw'7cvh'7cvm'7cpx'7cin'7ccm'7cmm'7cpt'7cpc'7cdeg'7crad'7cgrad'7cturn'7cms'7cs'7cHz'7ckHz'7cdpi'7cdpcm'29'5cb >>= withAttribute DataTypeTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b0'2d9'2e'5d'2b'5b'25'5d'3f >>= withAttribute DataTypeTok) >>~ (popContext)) <|> ((pRegExpr regex_'28portrait'7clandscape'29 >>= withAttribute DataTypeTok) >>~ (popContext)) <|> ((pRegExpr regex_'2e'2a >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("CSS","MQEV")) >> pDefault >>= withAttribute DecValTok)) parseRules ("CSS","Media2") = (((pDetectChar False '}' >>= withAttribute DecValTok) >>~ (popContext >> popContext)) <|> ((parseRules ("CSS","FindRuleSets"))) <|> (currentContext >>= \x -> guard (x == ("CSS","Media2")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","SelAttr") = (((pDetectChar False ']' >>= withAttribute AttributeTok) >>~ (popContext)) <|> ((parseRules ("CSS","FindStrings"))) <|> (currentContext >>= \x -> guard (x == ("CSS","SelAttr")) >> pDefault >>= withAttribute AttributeTok)) parseRules ("CSS","SelPseudo") = (((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_pseudoclasses >>= withAttribute DecValTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("CSS","Import") = (((pDetectChar False ';' >>= withAttribute DecValTok) >>~ (popContext)) <|> ((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_mediatypes >>= withAttribute DecValTok)) <|> ((parseRules ("CSS","FindValues"))) <|> ((parseRules ("CSS","FindStrings"))) <|> ((parseRules ("CSS","FindComments"))) <|> (currentContext >>= \x -> guard (x == ("CSS","Import")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","Comment") = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((pDetect2Chars False '*' '/' >>= withAttribute CommentTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> ((pDetectIdentifier >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("CSS","Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("CSS","RuleSet") = (((pDetectChar False '}' >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_properties >>= withAttribute KeywordTok) >>~ pushContext ("CSS","Rule")) <|> ((pRegExpr regex_'2d'3f'5bA'2dZa'2dz'5f'2d'5d'2b'28'3f'3d'5cs'2a'3a'29 >>= withAttribute KeywordTok) >>~ pushContext ("CSS","Rule")) <|> ((parseRules ("CSS","FindComments"))) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("CSS","RuleSet")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","Rule") = (((pDetectChar False ':' >>= withAttribute KeywordTok) >>~ pushContext ("CSS","Rule2")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("CSS","Rule")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","Rule2") = (((pDetectChar False ';' >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> ((pDetectChar False '}' >>= withAttribute KeywordTok) >>~ (popContext >> popContext >> popContext)) <|> ((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_types >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_colors >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'23'28'5b0'2d9A'2dFa'2df'5d'7b3'7d'29'7b1'2c4'7d'5cb >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_paren >>= withAttribute DataTypeTok) >>~ pushContext ("CSS","PropParen")) <|> ((pRegExpr regex_'21important'5cb >>= withAttribute KeywordTok)) <|> ((parseRules ("CSS","FindValues"))) <|> ((parseRules ("CSS","FindStrings"))) <|> ((parseRules ("CSS","FindComments"))) <|> (currentContext >>= \x -> guard (x == ("CSS","Rule2")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","PropParen") = (((pDetectChar False '(' >>= withAttribute DataTypeTok) >>~ pushContext ("CSS","PropParen2")) <|> ((parseRules ("CSS","FindComments"))) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok)) <|> (currentContext >>= \x -> guard (x == ("CSS","PropParen")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","PropParen2") = (((pDetectChar False ')' >>= withAttribute DataTypeTok) >>~ (popContext >> popContext)) <|> ((parseRules ("CSS","FindValues"))) <|> ((parseRules ("CSS","FindStrings"))) <|> ((parseRules ("CSS","FindComments"))) <|> (currentContext >>= \x -> guard (x == ("CSS","PropParen2")) >> pDefault >>= withAttribute NormalTok)) parseRules ("CSS","StringDQ") = (((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> ((parseRules ("CSS","InsideString"))) <|> (currentContext >>= \x -> guard (x == ("CSS","StringDQ")) >> pDefault >>= withAttribute StringTok)) parseRules ("CSS","StringSQ") = (((pDetectChar False '\'' >>= withAttribute StringTok) >>~ (popContext)) <|> ((parseRules ("CSS","InsideString"))) <|> (currentContext >>= \x -> guard (x == ("CSS","StringSQ")) >> pDefault >>= withAttribute StringTok)) parseRules ("CSS","InsideString") = (((pRegExpr regex_'5c'5c'5b'22'27'5d >>= withAttribute StringTok)) <|> ((pDetectIdentifier >>= withAttribute StringTok)) <|> (currentContext >>= \x -> guard (x == ("CSS","InsideString")) >> pDefault >>= withAttribute StringTok)) parseRules ("Alerts", _) = Text.Highlighting.Kate.Syntax.Alert.parseExpression Nothing parseRules x = parseRules ("CSS","Base") <|> fail ("Unknown context" ++ show x)