{- This module was generated from data in the Kate syntax highlighting file css.xml, version 2.05, 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 Data.Map (fromList) import Control.Monad.State import Data.Char (isSpace) import Data.Maybe (fromMaybe) 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 parseExpressionInternal pEndLine -- | Parse an expression using appropriate local context. parseExpression :: KateParser Token parseExpression = do st <- getState let oldLang = synStLanguage st setState $ st { synStLanguage = "CSS" } context <- currentContext <|> (pushContext "Base" >> currentContext) result <- parseRules context optional $ eof >> pEndLine updateState $ \st -> st { synStLanguage = oldLang } return result startingState = SyntaxState {synStContexts = fromList [("CSS",["Base"])], synStLanguage = "CSS", synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = False, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext case context of "Base" -> return () "FindRuleSets" -> return () "FindValues" -> return () "FindStrings" -> return () "FindComments" -> return () "Media" -> return () "Media2" -> return () "SelAttr" -> return () "SelPseudo" -> (popContext) >> pEndLine "Import" -> return () "Comment" -> return () "RuleSet" -> return () "Rule" -> return () "Rule2" -> return () "PropParen" -> return () "PropParen2" -> return () "StringDQ" -> return () "StringSQ" -> return () "InsideString" -> return () _ -> 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) parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe NormalTok $ lookup context defaultAttributes)) list_properties = Set.fromList $ words $ "azimuth background background-attachment background-color background-image background-position background-repeat border border-bottom border-bottom-color border-bottom-style border-bottom-width border-collapse border-color border-left border-left-color border-left-style border-left-width border-right border-right-color border-right-style border-right-width border-spacing border-style border-top border-top-color border-top-style border-top-width border-width bottom caption-side clear clip color content counter-increment counter-reset cue cue-after cue-before cursor direction display elevation empty-cells float font font-family font-size font-size-adjust font-stretch font-style font-variant font-weight height left letter-spacing line-height 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 max-height max-width min-height min-width orphans outline outline-color outline-style outline-width overflow padding padding-bottom padding-left padding-right padding-top page page-break-after page-break-before page-break-inside pause pause-after pause-before pitch pitch-range play-during position quotes richness right size speak speak-header speak-numeral speak-punctuation speech-rate stress table-layout text-align text-decoration text-decoration-color text-indent text-shadow text-transform top unicode-bidi vertical-align visibility voice-family volume white-space widows width word-spacing z-index border-bottom-image border-bottom-left-image border-bottom-left-radius border-bottom-right-image border-bottom-right-radius border-corner-image border-image border-left-image border-radius border-right-image border-top-image border-top-left-image border-top-left-radius border-top-right-image border-top-right-radius box-shadow box-sizing opacity outline-offset overflow-x overflow-y text-overflow text-shadow -moz-border-bottom-colors -moz-border-left-colors -moz-border-radius -moz-border-right-colors -moz-border-top-colors -moz-box-flex -o-background-size -o-text-overflow -khtml-background-size konq_bgpos_x konq_bgpos_y -webkit-background-size 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 -moz-box" 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 tty tv" 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 "@media\\b" regex_'40import'5cb = compileRegex "@import\\b" regex_'40'28font'2dface'7ccharset'29'5cb = compileRegex "@(font-face|charset)\\b" regex_'23'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 "#([a-zA-Z0-9\\-_]|[\\x80-\\xFF]|\\\\[0-9A-Fa-f]{1,6})*" 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 "\\.([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 ":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 "[-+]?[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 "[-+]?[0-9.]+[%]?" regex_'5b'5cw'5c'2d'5d'2b = compileRegex "[\\w\\-]+" regex_'2f'5c'2aBEGIN'2e'2a'5c'2a'2f = compileRegex "/\\*BEGIN.*\\*/" regex_'2f'5c'2aEND'2e'2a'5c'2a'2f = compileRegex "/\\*END.*\\*/" regex_'5cS'2b = compileRegex "\\S+" regex_'2d'3f'5bA'2dZa'2dz'5f'2d'5d'2b'28'3f'3d'5cs'2a'3a'29 = compileRegex "-?[A-Za-z_-]+(?=\\s*:)" regex_'5cS = compileRegex "\\S" regex_'23'28'5b0'2d9A'2dFa'2df'5d'7b3'7d'29'7b1'2c4'7d'5cb = compileRegex "#([0-9A-Fa-f]{3}){1,4}\\b" regex_'21important'5cb = compileRegex "!important\\b" regex_'5c'5c'5b'22'27'5d = compileRegex "\\\\[\"']" defaultAttributes = [("Base",NormalTok),("FindRuleSets",NormalTok),("FindValues",NormalTok),("FindStrings",NormalTok),("FindComments",NormalTok),("Media",NormalTok),("Media2",NormalTok),("SelAttr",CharTok),("SelPseudo",DecValTok),("Import",NormalTok),("Comment",CommentTok),("RuleSet",NormalTok),("Rule",NormalTok),("Rule2",NormalTok),("PropParen",NormalTok),("PropParen2",NormalTok),("StringDQ",StringTok),("StringSQ",StringTok),("InsideString",StringTok)] parseRules "Base" = (((pLineContinue >>= withAttribute NormalTok)) <|> ((pDetectSpaces >>= withAttribute NormalTok)) <|> ((parseRules "FindRuleSets"))) parseRules "FindRuleSets" = (((pRegExpr regex_'40media'5cb >>= withAttribute DecValTok) >>~ pushContext "Media") <|> ((pRegExpr regex_'40import'5cb >>= withAttribute DecValTok) >>~ pushContext "Import") <|> ((pRegExpr regex_'40'28font'2dface'7ccharset'29'5cb >>= withAttribute DecValTok)) <|> ((pDetectChar False '{' >>= withAttribute KeywordTok) >>~ pushContext "RuleSet") <|> ((pDetectChar False '[' >>= withAttribute CharTok) >>~ pushContext "SelAttr") <|> ((pRegExpr regex_'23'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_'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 "SelPseudo") <|> ((parseRules "FindStrings")) <|> ((parseRules "FindComments"))) parseRules "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))) parseRules "FindStrings" = (((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext "StringDQ") <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext "StringSQ")) parseRules "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 "Comment")) parseRules "Media" = (((pDetectChar False '{' >>= withAttribute DecValTok) >>~ pushContext "Media2") <|> ((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_mediatypes >>= withAttribute DecValTok)) <|> ((pDetectChar False ',' >>= withAttribute DecValTok)) <|> ((parseRules "FindComments")) <|> ((pRegExpr regex_'5cS'2b >>= withAttribute ErrorTok))) parseRules "Media2" = (((pDetectChar False '}' >>= withAttribute DecValTok) >>~ (popContext >> popContext)) <|> ((parseRules "FindRuleSets"))) parseRules "SelAttr" = (((pDetectChar False ']' >>= withAttribute CharTok) >>~ (popContext)) <|> ((parseRules "FindStrings"))) parseRules "SelPseudo" = (((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_pseudoclasses >>= withAttribute DecValTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules "Import" = (((pDetectChar False ';' >>= withAttribute DecValTok) >>~ (popContext)) <|> ((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_mediatypes >>= withAttribute DecValTok)) <|> ((parseRules "FindValues")) <|> ((parseRules "FindStrings")) <|> ((parseRules "FindComments"))) parseRules "Comment" = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((pDetect2Chars False '*' '/' >>= withAttribute CommentTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Alert.parseExpression >>= ((withAttribute CommentTok) . snd))) <|> ((pDetectIdentifier >>= withAttribute CommentTok))) parseRules "RuleSet" = (((pDetectChar False '}' >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((pKeyword " \n\t.():!+,<=>&*/;?[]^{|}~\\" list_properties >>= withAttribute KeywordTok) >>~ pushContext "Rule") <|> ((pRegExpr regex_'2d'3f'5bA'2dZa'2dz'5f'2d'5d'2b'28'3f'3d'5cs'2a'3a'29 >>= withAttribute KeywordTok) >>~ pushContext "Rule") <|> ((parseRules "FindComments")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok))) parseRules "Rule" = (((pDetectChar False ':' >>= withAttribute KeywordTok) >>~ pushContext "Rule2") <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok))) parseRules "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 "PropParen") <|> ((pRegExpr regex_'21important'5cb >>= withAttribute KeywordTok)) <|> ((parseRules "FindValues")) <|> ((parseRules "FindStrings")) <|> ((parseRules "FindComments"))) parseRules "PropParen" = (((pDetectChar False '(' >>= withAttribute DataTypeTok) >>~ pushContext "PropParen2") <|> ((parseRules "FindComments")) <|> ((pRegExpr regex_'5cS >>= withAttribute ErrorTok))) parseRules "PropParen2" = (((pDetectChar False ')' >>= withAttribute DataTypeTok) >>~ (popContext >> popContext)) <|> ((parseRules "FindValues")) <|> ((parseRules "FindStrings")) <|> ((parseRules "FindComments"))) parseRules "StringDQ" = (((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> ((parseRules "InsideString"))) parseRules "StringSQ" = (((pDetectChar False '\'' >>= withAttribute StringTok) >>~ (popContext)) <|> ((parseRules "InsideString"))) parseRules "InsideString" = (((pRegExpr regex_'5c'5c'5b'22'27'5d >>= withAttribute StringTok)) <|> ((pDetectIdentifier >>= withAttribute StringTok))) parseRules "" = parseRules "Base" parseRules x = fail $ "Unknown context" ++ x