{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TupleSections #-} ----------------------------------------------------------------------------- -- | -- Module : Hasmin.Parser.Value -- Copyright : (c) 2017 Cristian Adrián Ontivero -- License : BSD3 -- Stability : experimental -- Portability : unknown -- -- Parsers for CSS values. -- ----------------------------------------------------------------------------- module Hasmin.Parser.Value ( valuesFor , valuesFallback , value , valuesInParens , stringOrUrl , percentage , url , stringtype , textualvalue , stringvalue -- used in StringSpec , shadowList -- used in ShadowSpec , timingFunction , repeatStyle , position , color , number , fontStyle ) where import Control.Applicative ((<|>), many, liftA3) import Control.Arrow (first, (&&&)) import Control.Monad (mzero) import Data.Functor (($>)) import Data.Attoparsec.Text (asciiCI, char, count, option, Parser, satisfy, skipSpace, string) import Data.Map.Strict (Map) import Data.Monoid ((<>)) import Data.Maybe (fromMaybe, isNothing) import Data.Text (Text) import Data.Word (Word8) import Data.Char (isAscii) import Text.Parser.Permutation ((<|?>), (<$$>), (<$?>), (<||>), permute) import Numeric (readSigned, readFloat) import qualified Data.Set as Set import qualified Data.Attoparsec.Text as A import qualified Data.Char as C import qualified Data.Map.Strict as Map import qualified Data.List as L import qualified Data.Text as T import Hasmin.Parser.Utils import Hasmin.Types.BgSize import Hasmin.Class import Hasmin.Types.Color import Hasmin.Types.Dimension import Hasmin.Types.FilterFunction import Hasmin.Types.Gradient import Hasmin.Types.Numeric import Hasmin.Types.PercentageLength import Hasmin.Types.Position import Hasmin.Types.RepeatStyle import Hasmin.Types.Shadow import Hasmin.Types.String import Hasmin.Types.TimingFunction import Hasmin.Types.TransformFunction import Hasmin.Types.Value -- | Given a propery name, it returns a specific parser of values for that -- property. Fails if no specific parser is found. valuesFor :: Text -> Parser Values valuesFor propName = case Map.lookup (T.toLower propName) propertyValueParsersMap of Just x -> x <* skipComments Nothing -> mzero -- | Parser for >. number :: Parser Number number = Number <$> rational -- --------------------------------------------------------------------------- -- Color Parsers -- --------------------------------------------------------------------------- -- Assumes "rgb(" has already been read rgb :: Parser Color rgb = functionParser (rgbInt <|> rgbPer) where rgbInt = mkRGBInt <$> word8 <* comma <*> word8 <* comma <*> word8 rgbPer = mkRGBPer <$> percentage <* comma <*> percentage <* comma <*> percentage -- Assumes "rgba(" has already been read rgba :: Parser Color rgba = functionParser (rgbaInt <|> rgbaPer) where rgbaInt = mkRGBAInt <$> word8 <* comma <*> word8 <* comma <*> word8 <* comma <*> alphavalue rgbaPer = mkRGBAPer <$> percentage <* comma <*> percentage <* comma <*> percentage <* comma <*> alphavalue -- Assumes "hsl(" has already been read hsl :: Parser Color hsl = functionParser p where p = mkHSL <$> int <* comma <*> percentage <* comma <*> percentage -- Assumes "hsla(" has already been read hsla :: Parser Color hsla = functionParser p where p = mkHSLA <$> int <* comma <*> percentage <* comma <*> percentage <* comma <*> alphavalue alphavalue :: Parser Alphavalue alphavalue = mkAlphavalue <$> rational hexvalue :: Parser Value hexvalue = ColorV <$> hex hex :: Parser Color hex = do _ <- char '#' a <- hexadecimal b <- hexadecimal c <- hexadecimal x <- optional hexadecimal case x of Nothing -> pure $ mkHex3 a b c Just d -> do y <- optional hexadecimal case y of Nothing -> pure $ mkHex4 a b c d Just e -> do f <- hexadecimal z <- optional hexadecimal case z of Nothing -> pure $ mkHex6 [a,b] [c,d] [e,f] Just g -> do h <- hexadecimal pure $ mkHex8 [a,b] [c,d] [e,f] [g,h] where optional w = option Nothing (Just <$> w) hexadecimal = satisfy C.isHexDigit -- --------------------------------------------------------------------------- -- Dimensions Parsers -- --------------------------------------------------------------------------- -- A map relating dimension units and the percentage symbol, -- to functions that construct that value. Meant to unify all the numerical -- parsing in a single parse for generality without losing much efficiency. -- See numericalvalue. numericalConstructorsMap :: Map Text (Number -> Value) numericalConstructorsMap = Map.fromList $ fmap (first T.toCaseFold) l where durationFunc u v = DurationV (Duration v u) frequencyFunc u v = FrequencyV (Frequency v u) resolutionFunc u v = ResolutionV (Resolution v u) l = [("s", durationFunc S) ,("ms", durationFunc Ms) ,("hz", frequencyFunc Hz) ,("khz", frequencyFunc Khz) ,("dpi", resolutionFunc Dpi) ,("dpcm", resolutionFunc Dpcm) ,("dppx", resolutionFunc Dppx) ,("%", \x -> PercentageV (Percentage $ toRational x)) ] ++ (fmap . fmap) (LengthV .) distanceConstructorsList ++ (fmap . fmap) (AngleV .) angleConstructorsList -- Unified numerical parser. -- Parses , dimensions (i.e. , , ...), and numericalvalue :: Parser Value numericalvalue = do n <- number rest <- opt (string "%" <|> A.takeWhile1 C.isAlpha) if T.null rest -- if true, then it was just a value then pure $ NumberV n else case Map.lookup (T.toCaseFold rest) numericalConstructorsMap of Just f -> pure $ f n Nothing -> mzero -- TODO see if we should return an "Other" value -- Create a numerical parser based on a Map. -- See for instance, the "angle" parser dimensionParser :: Map Text (Number -> a) -> a -> Parser a dimensionParser m unitlessValue = do n <- number u <- opt (A.takeWhile1 C.isAlpha) if T.null u then if n == 0 then pure unitlessValue -- 0, without units else mzero -- Non-zero , fail else case Map.lookup (T.toCaseFold u) m of Just f -> pure $ f n Nothing -> mzero -- parsed units aren't angle units, fail distance :: Parser Length distance = dimensionParser distanceConstructorsMap NullLength where distanceConstructorsMap = Map.fromList distanceConstructorsList angle :: Parser Angle angle = dimensionParser angleConstructorsMap NullAngle where angleConstructorsMap = Map.fromList angleConstructorsList duration :: Parser Duration duration = do n <- number u <- opt (A.takeWhile1 C.isAlpha) if T.null u then mzero else case Map.lookup (T.toCaseFold u) durationConstructorsMap of Just f -> pure $ f n Nothing -> mzero -- parsed units aren't angle units, fail where durationConstructorsMap = Map.fromList $ fmap (toText &&& flip Duration) [S, Ms] angleConstructorsList :: [(Text, Number -> Angle)] angleConstructorsList = fmap (toText &&& flip Angle) [Deg, Grad, Rad, Turn] distanceConstructorsList :: [(Text, Number -> Length)] distanceConstructorsList = fmap (toText &&& flip Length) [EM, EX, CH, VH, VW, VMIN, VMAX, REM, Q, CM, MM, IN, PC, PT, PX] -- | Parser for >. percentage :: Parser Percentage percentage = Percentage <$> rational <* char '%' -- --------------------------------------------------------------------------- -- Primitives -- --------------------------------------------------------------------------- -- | \ data type parser, but into a String instead of an Int, for other -- parsers to use (e.g.: see the parsers int, or rational) int' :: Parser String int' = do sign <- option '+' (char '-' <|> char '+') d <- digits case sign of '+' -> pure d '-' -> pure (sign:d) _ -> error "int': parsed a number starting with other than [+|-]" -- | Parser for \: [+|-][0-9]+ int :: Parser Int int = read <$> int' word8 :: Parser Word8 word8 = read <$> digits -- Note that many properties that allow an integer or real number as a value -- actually restrict the value to some range, often to a non-negative value. -- -- | Real number parser. \: <'int' integer> | [0-9]*.[0-9]+ rational :: Parser Rational rational = do sign <- option [] (wrapMinus <$> (char '-' <|> char '+')) dgts <- ((++) <$> digits <*> option "" fractionalPart) <|> ("0"++) <$> fractionalPart -- append a zero for read not to fail e <- option [] expo pure . fst . head $ readSigned readFloat (sign ++ dgts ++ e) where fractionalPart = (:) <$> char '.' <*> digits expo = (:) <$> satisfy (\c -> c == 'e' || c == 'E') <*> int' wrapMinus x = [x | x == '-'] -- we use this since read fails with leading '+' -- | Parser for >, -- used in the @font-style@ and @font@ properties. fontStyle :: Parser Value fontStyle = do k <- ident if Set.member k keywords then pure $ mkOther k else mzero where keywords = Set.fromList ["normal", "italic", "oblique"] {- fontWeight :: Parser Value fontWeight = do k <- ident if Set.member k keywords then pure $ mkOther k else mzero where keywords = Set.fromList ["normal", "bold", "lighter", "bolder"] validNumbers = Set.fromList [100, 200, 300, 400, 500, 600, 700, 800, 900] -} fontSize :: Parser Value fontSize = fontSizeKeyword <|> (LengthV <$> distance) <|> (PercentageV <$> percentage) where fontSizeKeyword = do v1 <- ident if Set.member v1 keywords then pure $ mkOther v1 else mzero keywords = Set.fromList ["medium", "xx-small", "x-small", "small" ,"large", "x-large", "xx-large", "smaller" ,"larger"] {- [ [ <‘font-style’> || || <‘font-weight’> || - <‘font-stretch’> ]? <‘font-size’> [ / <‘line-height’> ]? <‘font-family’> ] | - caption | icon | menu | message-box | small-caption | status-bar where = [normal | small-caps] -} -- TODO clean parsers pos1, pos2, and pos4 positionvalue :: Parser Value positionvalue = PositionV <$> position -- | Parser for >. position :: Parser Position position = pos4 <|> pos2 <|> pos1 pos1 :: Parser Position pos1 = (asciiCI "left" $> f (Just PosLeft)) <|> (asciiCI "center" $> f (Just PosCenter)) <|> (asciiCI "right" $> f (Just PosRight)) <|> (asciiCI "top" $> f (Just PosTop)) <|> (asciiCI "bottom" $> f (Just PosBottom)) <|> ((\a -> Position Nothing a Nothing Nothing) <$> (Just <$> percentageLength)) where f x = Position x Nothing Nothing Nothing pos2 :: Parser Position pos2 = firstx <|> firsty where firstx = do a <- (asciiCI "left" $> Position (Just PosLeft) Nothing) <|> (asciiCI "center" $> Position (Just PosCenter) Nothing) <|> (asciiCI "right" $> Position (Just PosRight) Nothing) <|> ((Position Nothing . Just) <$> percentageLength) skipComments *> ((asciiCI "top" $> a (Just PosTop) Nothing) <|> (asciiCI "center" $> a (Just PosCenter) Nothing) <|> (asciiCI "bottom" $> a (Just PosBottom) Nothing) <|> ((a Nothing . Just) <$> percentageLength)) firsty = do a <- (asciiCI "top" $> Position (Just PosTop) Nothing) <|> (asciiCI "center" $> Position (Just PosCenter) Nothing) <|> (asciiCI "bottom" $> Position (Just PosBottom) Nothing) <|> ((Position Nothing . Just) <$> percentageLength) skipComments *> ((asciiCI "left" $> a (Just PosLeft) Nothing) <|> (asciiCI "center" $> a (Just PosCenter) Nothing) <|> (asciiCI "right" $> a (Just PosRight) Nothing) <|> ((a Nothing . Just) <$> percentageLength)) pos4 :: Parser Position pos4 = firstx <|> firsty where posTop = asciiCI "top" $> Position (Just PosTop) posRight = asciiCI "right" $> Position (Just PosRight) posBottom = asciiCI "bottom" $> Position (Just PosBottom) posLeft = asciiCI "left" $> Position (Just PosLeft) firstx = do x <- (asciiCI "center" $> Position (Just PosCenter) Nothing) <|> ((posLeft <|> posRight) <*> (skipComments *> option Nothing (Just <$> percentageLength))) _ <- skipComments (asciiCI "center" $> x (Just PosCenter) Nothing) <|> (((asciiCI "top" $> x (Just PosTop)) <|> (asciiCI "bottom" $> x (Just PosBottom))) <*> (skipComments *> option Nothing (Just <$> percentageLength))) firsty = do x <- (asciiCI "center" $> Position (Just PosCenter) Nothing) <|> ((posTop <|> posBottom) <*> (skipComments *> option Nothing (Just <$> percentageLength))) _ <- skipComments (asciiCI "center" $> x (Just PosCenter) Nothing) <|> (((asciiCI "left" $> x (Just PosLeft)) <|> (asciiCI "right" $> x (Just PosRight))) <*> (skipComments *> option Nothing (Just <$> percentageLength))) {- transformOrigin :: Parser Values transformOrigin = twoVal <|> oneVal where oneVal = (singleValue numericalvalue) <|> offsetKeyword offsetKeyword = do v1 <- ident if v1 == "top" || v1 == "right" || v1 == "bottom" || v1 == "left" || v1 == "center" then pure $ mkValues [mkOther v1] else mzero twoVal = do (v1, v2) <- ((,) <$> yAxis <*> (skipComments *> (xAxis <|> numericalvalue))) <|> ((,) <$> xAxis <*> (skipComments *> (yAxis <|> numericalvalue))) <|> ((,) <$> numericalvalue <*> (skipComments *> (yAxis <|> xAxis))) option (mkValues [v1,v2]) ((\x -> mkValues [v1,v2, LengthV x]) <$> distance) yAxis = do v1 <- ident if v1 == "top" || v1 == "bottom" || v1 == "center" then pure $ mkOther v1 else mzero xAxis = do v1 <- ident if v1 == "right" || v1 == "left" || v1 == "center" then pure $ mkOther v1 else mzero -} bgSize :: Parser BgSize bgSize = twovaluesyntax <|> contain <|> cover where cover = asciiCI "cover" $> Cover contain = asciiCI "contain" $> Contain twovaluesyntax = do x <- bgsizeValue <* skipComments (BgSize2 x <$> bgsizeValue) <|> pure (BgSize1 x) bgsizeValue = (Left <$> percentageLength) <|> (Right <$> auto) bgAttachment :: Parser TextV bgAttachment = matchKeywords ["scroll", "fixed", "local"] box :: Parser TextV box = matchKeywords ["border-box", "padding-box", "content-box"] -- [ , ]* background :: Parser Values background = do xs <- many (bgLayer <* char ',' <* skipComments) x <- finalBgLayer pure $ if null xs then Values x [] else Values (head xs) (fmap (Comma,) $ tail xs ++ [x]) -- = || [ / ]? || || || || || <'background-color'> finalBgLayer :: Parser Value finalBgLayer = do layer <- permute (mkFinalBgLayer <$?> (Nothing, Just <$> image <* skipComments) <|?> (Nothing, Just <$> positionAndBgSize <* skipComments) <|?> (Nothing, Just <$> repeatStyle <* skipComments) <|?> (Nothing, Just <$> bgAttachment <* skipComments) <|?> (Nothing, Just <$> box <* skipComments) <|?> (Nothing, Just <$> box <* skipComments) <|?> (Nothing, Just <$> color <* skipComments)) if finalBgLayerIsEmpty layer then mzero else pure layer where finalBgLayerIsEmpty (FinalBgLayer Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing) = True finalBgLayerIsEmpty _ = False -- parameters e and f are being swapped to deal with the permutation -- changing the original order of the parsed values. mkFinalBgLayer a Nothing c d e f g = FinalBgLayer a Nothing Nothing c d f e g mkFinalBgLayer a (Just (p,s)) c d e f g = FinalBgLayer a (Just p) s c d f e g -- = || [ / ]? || || || {1,2} bgLayer :: Parser Value bgLayer = do layer <- permute (mkBgLayer <$?> (Nothing, Just <$> image <* skipComments) <|?> (Nothing, Just <$> positionAndBgSize <* skipComments) <|?> (Nothing, Just <$> repeatStyle <* skipComments) <|?> (Nothing, Just <$> bgAttachment <* skipComments) <|?> (Nothing, Just <$> box2 <* skipComments)) if bgLayerIsEmpty layer then mzero else pure layer where bgLayerIsEmpty (BgLayer Nothing Nothing Nothing Nothing Nothing Nothing Nothing) = True bgLayerIsEmpty _ = False mkBgLayer a Nothing c d Nothing = BgLayer a Nothing Nothing c d Nothing Nothing mkBgLayer a (Just (p,s)) c d Nothing = BgLayer a (Just p) s c d Nothing Nothing mkBgLayer a Nothing c d (Just (i,j)) = BgLayer a Nothing Nothing c d (Just i) j mkBgLayer a (Just (p,s)) c d (Just (i,j)) = BgLayer a (Just p) s c d (Just i) j box2 :: Parser (TextV, Maybe TextV) box2 = do x <- box <* skipComments y <- option Nothing (Just <$> box) pure (x,y) -- used for the background property, which takes among other things: -- [ / ]? positionAndBgSize :: Parser (Position, Maybe BgSize) positionAndBgSize = do x <- position <* skipComments y <- option Nothing (Just <$> (char '/' *> skipComments *> bgSize)) pure (x,y) matchKeywords :: [Text] -> Parser TextV matchKeywords listOfKeywords = do i <- ident if T.toCaseFold i `elem` Set.fromList listOfKeywords then pure $ TextV i else mzero -- = | | | | | image :: Parser Value image = do i <- ident let lowercased = T.toLower i if lowercased == "none" then pure $ mkOther "none" else do _ <- char '(' if Set.member lowercased possibilities then fromMaybe mzero (Map.lookup lowercased functionsMap) else mzero where possibilities = Set.fromList $ map T.toCaseFold ["url", "element", "linear-gradient", "radial-gradient"] transition :: Parser Values transition = parseCommaSeparated singleTransition -- [ none | ] ||