~alcinnz/Mondrian

ref: 4fb39760e2559c8622c33aac8f27aba8b6887edd Mondrian/lib/Graphics/Rendering/Rect/CSS/Backgrounds.hs -rw-r--r-- 6.1 KiB
4fb39760 — Adrian Cochrane Implement background-size! 1 year, 4 months ago
                                                                                
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
{-# LANGUAGE OverloadedStrings, FlexibleInstances #-}
module Graphics.Rendering.Rect.CSS.Backgrounds (Backgrounds(..),
    Resize(..), Length(..), resolveSize) where

import Stylist (PropertyParser(..), parseUnorderedShorthand)
import Data.CSS.Syntax.Tokens (Token(..), NumericValue(..))
import Data.Maybe (isJust, catMaybes)
import Data.Text (Text)
import Data.Scientific (scientific, toRealFloat)

import Graphics.Rendering.Rect.CSS.Colour (ColourPallet, parseColour)
import Data.Colour (AlphaColour, transparent)
import Graphics.Rendering.Rect.Types (Rects(..), Rect(..))

data Backgrounds img = Backgrounds {
    pallet :: ColourPallet,
    background :: AlphaColour Float,
    clip :: [Rects -> Rect],
    image :: [img],
    bgSize :: [Resize]
} deriving (Eq, Show, Read)

-- We need to resolve images before we can compute the actual lengths!
data Resize = Cover | Contain | Size Length Length deriving (Eq, Show, Read)
data Length = Absolute Float | Scale Float | Auto deriving (Eq, Show, Read)

instance PropertyParser (Backgrounds Text) where
    temp = Backgrounds {
        pallet = temp, background = transparent, clip = [borderBox],
        image = [""], bgSize = [Size Auto Auto]
      }
    inherit _ = temp
    priority _ = []

    longhand _ self@Backgrounds{ pallet = c } "background-color" toks
        | Just ([], val) <- parseColour c toks = Just self { background = val }
    longhand _ self "background-clip" t | val@(_:_) <- parseCSSList inner t =
        Just self { clip = reverse val }
      where
        inner [Ident "content-box"] = Just contentBox
        inner [Ident "padding-box"] = Just paddingBox
        inner [Ident "border-box"] = Just borderBox
        inner [Ident "initial"] = Just borderBox -- To aid shorthand implementation.
        inner _ = Nothing
    longhand _ self "background-image" t | val@(_:_) <- parseCSSList inner t =
        Just self { image = reverse val }
      where
        inner [Ident "none"] = Just ""
        inner [Ident "initial"] = Just ""
        inner [Url ret] = Just ret
        inner [Function "url", String ret, RightParen] = Just ret
        inner _ = Nothing
    longhand _ self "background-size" t | val@(_:_) <- parseCSSList inner t =
        Just self { bgSize = reverse val }
      where -- TODO: Add shorthand support, after background-position.
        inner [x, y] | Just a <- length x, Just b <- length y = Just $ Size a b
        inner [Ident "contain"] = Just Contain
        inner [Ident "cover"] = Just Cover
        inner [Ident "auto"] = Just $ Size Auto Auto
        inner [Ident "initial"] = Just $ Size Auto Auto
        inner _ = Nothing
        -- NOTE: Leave lowering other units to CatTrap.
        length (Ident "auto") = Just Auto
        length (Dimension _ x "px") = Just $ Absolute $ f x
        length (Percentage _ x) = Just $ Scale $ p x
        length _ = Nothing
    longhand _ _ _ _ = Nothing

    -- The multi-layered shorthand is one source of parsing complexity.
    shorthand self "background" t = catProps $ reverse $ parseCSSList inner t
      where
        catProps [] = []
        catProps (props:pss)
            | Just [Ident "initial"] <- "background-color" `lookup` catProps pss =
                map (catProp $ catProps pss) props
            | otherwise = [] -- Only allow background-color in bottommost layer.
        catProp _ ret@("background-color", _) = ret
        catProp bases (key, val)
            | Just base <- key `lookup` bases = (key, base ++ Comma:val)
            -- Shouldn't happen, `inner` expands all props at least to "initial"!
            | otherwise = (key, val)
        inner toks | ret@(_:_) <- parseUnorderedShorthand self [
                "background-color", "background-clip", "background-image"
              ] toks = Just ret
          | otherwise = Nothing
    shorthand self key val | Just _ <- longhand self self key val = [(key, val)]
        | otherwise = []

parseCSSList cb toks | all isJust ret = catMaybes ret
    | otherwise = []
  where ret = map cb $ splitList Comma toks

f :: NumericValue -> Float
f (NVInteger x) = fromInteger x
f (NVNumber x) = toRealFloat x
p :: NumericValue -> Float
p (NVInteger x) = fromInteger x / 100
-- Do the division while we're in base-10!
p (NVNumber x) = toRealFloat (x/scientific 1 2)

------
--- Utils taken from HappStack
------

-- | Repeadly splits a list by the provided separator and collects the results
splitList :: Eq a => a -> [a] -> [[a]]
splitList _   [] = []
splitList sep list = h:splitList sep t
        where (h,t)=split (==sep) list

-- | Split is like break, but the matching element is dropped.
split :: (a -> Bool) -> [a] -> ([a], [a])
split f s = (left,right)
        where
        (left,right')=break f s
        right = if null right' then [] else tail right'

------
--- Dynamically-computed properties
------

resolveSize :: (Float, Float) -> (Float, Float) -> Resize -> (Float, Float)
resolveSize (owidth, oheight) (width, height) Contain
    | width > owidth, height*sw > oheight, height > width = (width*sh, height*sh)
    | width > owidth = (width*sw, height*sw)
    | height > oheight = (width*sh, height*sh)
    | height > width = (width*sw, height*sw)
    | width > height = (width*sh, height*sh)
  where
    sh = oheight/height
    sw = owidth/width
resolveSize (owidth, oheight) (width, height) Cover
    | owidth > width, oheight > height*sw = (width*sh, height*sh)
    | oheight > height, owidth > width*sh = (width*sw, height*sw)
    | owidth > width = (width*sw, height*sw)
    | oheight > height = (width*sh, height*sh)
    | oheight > height*sw = (width*sh, height*sh)
    | owidth > width*sh = (width*sw, height*sw)
    | height > width = (width*sw, height*sw)
    | width > height = (width*sh, height*sh)
  where
    sh = oheight/height
    sw = owidth/width
resolveSize _ ret (Size Auto Auto) = ret
resolveSize _ (width, height) (Size x y) = (x', y')
  where
    x' | Absolute ret <- x = ret
        | Scale s <- x = width*s
        | Auto <- x = y' * width/height
    y' | Absolute ret <- y = ret
        | Scale s <- y = height*s
    -- NOTE: If Auto,Auto case wasn't handled above this'd be an infinite loop.
        | Auto <- y = x' * height/width