~alcinnz/Mondrian

Mondrian/lib/Graphics/Rendering/Rect/Backgrounds.hs -rw-r--r-- 11.1 KiB
a22a7f05 — Adrian Cochrane Implement groove, ridge, inset, & outset border styles! Fix border-left-color 1 year, 5 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
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
module Graphics.Rendering.Rect.Backgrounds(Backgrounds(..), Pattern(..),
    RadialShape(..), Resize(..), Length(..), Extent(..),
    resolveSize, renderBackgrounds) where

import Graphics.Rendering.Rect.CSS.Backgrounds
import Graphics.Rendering.Rect.Types
import Graphics.Rendering.Rect.Image (Texture(texSize), textureSetRepeat)
import qualified Data.ByteString.Char8 as B8
import Linear (M44, V2(..))

import Control.Monad.IO.Class (MonadIO(..))
import Data.Maybe (fromMaybe, listToMaybe)
import Control.Monad (forM)

baseFragmentShader :: B8.ByteString
baseFragmentShader = B8.pack $ unlines [
    "#version 330 core",
    "out vec4 fcolour;",
    "uniform vec4 colour;",
    "void main() { fcolour = colour; }"
  ]

imageFragmentShader :: B8.ByteString
imageFragmentShader = B8.pack $ unlines [
    "#version 330 core",
    "in vec2 coord;",
    "out vec4 fcolour;",
    "uniform vec2 pos;",
    "uniform sampler2D image;",
    "uniform vec2 size;",
    "void main() { fcolour = texture(image, coord/size - pos/size); }"
  ]

linearFragmentShader :: B8.ByteString
linearFragmentShader = B8.pack $ unlines [
    "#version 330 core",
    "in vec2 coord;",
    "out vec4 fcolour;",
    "uniform vec2 size;",
    "uniform vec4 stops[10];",
    "uniform float stopPoints[10];",
    "uniform int nStops;",
    "uniform float angle;",
    "",
    "void main() {",
    "   vec2 pos = coord/size;", -- Range 0..1
    "   pos -= 0.5; pos *= 2;", -- Range -1..1
    "   float a = pos.x*sin(angle) + pos.y*-cos(angle);", -- Range -1..1
    "   a /= 2; a += 0.5;", -- Range 0..1
    "",
    "   int i = 0;",
    -- Workaround for buggy GPU drivers on test machine.
    "   if (1 < nStops - 1 && a > stopPoints[1]) i = 1;",
    "   if (2 < nStops - 1 && a > stopPoints[2]) i = 2;",
    "   if (3 < nStops - 1 && a > stopPoints[3]) i = 3;",
    "   if (4 < nStops - 1 && a > stopPoints[4]) i = 4;",
    "   if (5 < nStops - 1 && a > stopPoints[5]) i = 5;",
    "   if (6 < nStops - 1 && a > stopPoints[6]) i = 6;",
    "   if (7 < nStops - 1 && a > stopPoints[7]) i = 7;",
    "   if (8 < nStops - 1 && a > stopPoints[8]) i = 8;",
    "",
    "   a = smoothstep(stopPoints[i], stopPoints[i+1], a);",
    "   fcolour = mix(stops[i], stops[i+1], a);",
    "}"
  ]

radialFragmentShader :: B8.ByteString
radialFragmentShader = B8.pack $ unlines [
    "#version 330 core",
    "in vec2 coord;",
    "out vec4 fcolour;",
    "uniform vec2 size;",
    "uniform vec2 extent;",
    "uniform vec2 center;",
    "uniform vec4 stops[10];",
    "uniform float stopPoints[10];",
    "uniform int nStops;",
    "",
    "void main() {",
    "   float a = distance(coord/extent, center/size) * 2;",
    "",
    "   int i = 0;",
    -- Workaround for buggy GPU drivers on test machine.
    "   if (1 < nStops - 1 && a > stopPoints[1]) i = 1;",
    "   if (2 < nStops - 1 && a > stopPoints[2]) i = 2;",
    "   if (3 < nStops - 1 && a > stopPoints[3]) i = 3;",
    "   if (4 < nStops - 1 && a > stopPoints[4]) i = 4;",
    "   if (5 < nStops - 1 && a > stopPoints[5]) i = 5;",
    "   if (6 < nStops - 1 && a > stopPoints[6]) i = 6;",
    "   if (7 < nStops - 1 && a > stopPoints[7]) i = 7;",
    "   if (8 < nStops - 1 && a > stopPoints[8]) i = 8;",
    "",
    "   a = smoothstep(stopPoints[i], stopPoints[i+1], a);",
    "   fcolour = mix(stops[i], stops[i+1], a);",
    "}"
  ]
circleFragmentShader :: B8.ByteString
circleFragmentShader = B8.pack $ unlines [
    "#version 330 core",
    "in vec2 coord;",
    "out vec4 fcolour;",
    "uniform vec2 center;",
    "uniform float radius;",
    "uniform vec4 stops[10];",
    "uniform float stopPoints[10];",
    "uniform int nStops;",
    "",
    "void main() {",
    "   float a = distance(coord, center)/radius;",
    "",
    "   int i = 0;",
    -- Workaround for buggy GPU drivers on test machine.
    "   if (1 < nStops - 1 && a > stopPoints[1]) i = 1;",
    "   if (2 < nStops - 1 && a > stopPoints[2]) i = 2;",
    "   if (3 < nStops - 1 && a > stopPoints[3]) i = 3;",
    "   if (4 < nStops - 1 && a > stopPoints[4]) i = 4;",
    "   if (5 < nStops - 1 && a > stopPoints[5]) i = 5;",
    "   if (6 < nStops - 1 && a > stopPoints[6]) i = 6;",
    "   if (7 < nStops - 1 && a > stopPoints[7]) i = 7;",
    "   if (8 < nStops - 1 && a > stopPoints[8]) i = 8;",
    "",
    "   a = smoothstep(stopPoints[i], stopPoints[i+1], a);",
    "   fcolour = mix(stops[i], stops[i+1], a);",
    "}"
  ]

conicFragmentShader :: B8.ByteString
conicFragmentShader = B8.pack $ unlines [
    "#version 330 core",
    "in vec2 coord;",
    "out vec4 fcolour;",
    "uniform vec2 center;",
    "uniform float angle;",
    "uniform vec4 stops[10];",
    "uniform float stopPoints[10];",
    "uniform int nStops;",
    "",
    "void main() {",
    "   vec2 v = coord - center;",
    "   float a = atan(v.x, -v.y) - angle;",
    "   float turn = 2*radians(180);",
    "   a = fract(a/turn);",
    "",
    "   int i = 0;",
    -- Workaround for buggy GPU drivers on test machine.
    "   if (1 < nStops - 1 && a > stopPoints[1]) i = 1;",
    "   if (2 < nStops - 1 && a > stopPoints[2]) i = 2;",
    "   if (3 < nStops - 1 && a > stopPoints[3]) i = 3;",
    "   if (4 < nStops - 1 && a > stopPoints[4]) i = 4;",
    "   if (5 < nStops - 1 && a > stopPoints[5]) i = 5;",
    "   if (6 < nStops - 1 && a > stopPoints[6]) i = 6;",
    "   if (7 < nStops - 1 && a > stopPoints[7]) i = 7;",
    "   if (8 < nStops - 1 && a > stopPoints[8]) i = 8;",
    "",
    "   a = smoothstep(stopPoints[i], stopPoints[i+1], a);",
    "   fcolour = mix(stops[i], stops[i+1], a);",
    "}"
  ]

renderBackgrounds :: (MonadIO m, MonadIO n) =>
    n (Backgrounds Texture -> Rects -> M44 Float -> m ())
renderBackgrounds = do
    base <- renderRectWith baseFragmentShader ["colour"]
    layer <- renderRectWith imageFragmentShader ["size", "pos"]
    linear <- renderRectWith linearFragmentShader ["size", "angle",
            "stops", "stopPoints", "nStops"]
    ellipse <- renderRectWith radialFragmentShader ["size", "extent", "center",
            "stops", "stopPoints", "nStops"]
    circle <- renderRectWith circleFragmentShader ["center", "radius",
            "stops", "stopPoints", "nStops"]
    conic <- renderRectWith conicFragmentShader ["center", "angle",
            "stops", "stopPoints", "nStops"]
    return $ \self a b -> do
        base [] [c $ background self] (headDef borderBox $ clip self)
                (headDef paddingBox $ origin self) a b
        let layers = image self `zip` (clip self ++ repeat borderBox)
                `zip` (bgSize self ++ repeat (Size Auto Auto))
                `zip` (origin self ++ repeat paddingBox)
                `zip` (bgPos self ++ repeat (Absolute 0, Absolute 0))
                `zip` (bgRepeat self ++ repeat (True, True))
        _<-forM layers $ \(((((pat0, clip0), size0), origin0), pos0), repeat0) ->
          case pat0 of
            None -> return ()
            Img img0 -> do
                let sz = resolveSize (size $ clip0 a) (texSize img0) size0
                let pos' = (v2$l2f' pos0$size$clip0 a) - (v2$l2f' pos0 sz)
                textureSetRepeat img0 repeat0
                layer [img0] [u $ v2 sz, u pos'] clip0 origin0 a b
            Linear angle stops -> let size' = size $ clip0 a in linear [] [
                    u $ v2 $ size', u angle, cs 10 $ map fst stops,
                    us $ ls2fs size' $ map snd $ take 10 stops, u $ length stops
                ] clip0 origin0 a b
            -- FIXME: Incorporate resolveEllipseExtent without messing up center
            Radial Ellipse ext org stops -> let sz@(_,h) = size $ clip0 a in
                let (org', ext') = resolveEllipseExtent sz org ext in ellipse [] [
                    u $ v2 sz, u $ v2 ext', u $ v2 org', cs 10 $ map fst stops,
                    us $ ls2fs (0,h/2) $ map snd $ take 10 stops, u $ length stops
                ] clip0 origin0 a b
            Radial Circle ext org stops -> let sz@(w,h) = size $ clip0 a
                in let (org', r) = resolveCircleExtent sz org ext in circle [] [
                    u $ v2 org', u r, cs 10 $ map fst stops,
                    us $ ls2fs (0,min w h/2) $ map snd $ take 10 stops,
                    u $ length stops
                ] clip0 origin0 a b
            Conical angle org stops -> let sz = size $ clip0 a in conic [] [
                    u $ v2 $ l2f' org sz, u angle, cs 10 $ map fst stops,
                    us $ ls2fs (0,2*pi) $ map snd $ take 10 stops, u $ length stops
                ] clip0 origin0 a b
        return ()

headDef :: c -> [c] -> c
headDef def = fromMaybe def . listToMaybe
v2 :: (a, a) -> V2 a
v2 = uncurry V2
-- Easier to express this algorithm on CPU-side...
ls2fs :: (Float, Float) -> [Length] -> [Float]
ls2fs (_,h) ls = resolveAutos 0 $ inner True 0 ls
  where
    -- https://drafts.csswg.org/css-images/#color-stop-fixup Step 1.
    inner True _ (Auto:ls') = Scale 0:inner False 0 ls'
    inner _ _ [Auto] = [Scale 1]
    -- Step 2
    inner _ prev (Scale x:ls') | x < prev = Scale prev:inner False prev ls'
    inner _ prev (Absolute x:ls') | x/h < prev = Scale prev:inner False prev ls'
    inner _ _ (Scale x:ls') = Scale x:inner False x ls'
    inner _ _ (Absolute x:ls') = Absolute x:inner False (x/h) ls'
    inner _ prev (Auto:ls') = Auto:inner False prev ls'
    inner _ _ [] = []
    -- Step 3
    resolveAutos :: Float -> [Length] -> [Float]
    resolveAutos _ (Scale x:ls') = x:resolveAutos x ls'
    resolveAutos _ (Absolute x:ls') = (x/h):resolveAutos (x/h) ls'
    resolveAutos _ [] = []
    resolveAutos prev ls0 = [prev + succ i*grad | i <- [0..n - 1]] ++ fs
      where
        (autos, ls') = span (==Auto) ls0
        n = toEnum $ length autos
        fs = resolveAutos 0 ls' -- Doesn't matter if prev's in another branch...
        next | (x:_) <- fs = x
            | otherwise = 1 -- Step 1 should've taken care of this...
        grad = (next - prev)/(n + 1)

l2f :: Length -> Float -> Float
l2f Auto x = x/2
l2f (Scale x) y = x*y
l2f (Absolute x) _ = x
l2f' :: (Length, Length) -> (Float, Float) -> (Float, Float)
l2f' (x,y) (w,h) = (l2f x w, l2f y h)

resolveEllipseExtent :: (Float, Float) -> (Length, Length) -> Extent ->
    ((Float, Float), (Float, Float))
resolveEllipseExtent sz@(x',y') pos ext = ((x, y), inner ext)
  where
    (x,y) = l2f' pos sz
    horiz = [x, x' - x]
    vert = [y, y' - y]
    inner (Extent s t) = (l2f s x, l2f t y)
    -- FIXME: How to calculate closest/farthest-corner?
    -- Spec just says keep this aspect ratio.
    inner ClosestCorner = (minimum horiz * 2, minimum vert * 2)
    inner ClosestSide = (minimum horiz * 2, minimum vert * 2)
    inner FarthestCorner = (maximum horiz * 2, maximum vert * 2)
    inner FarthestSide = (maximum horiz * 2, maximum vert * 2)
resolveCircleExtent :: (Float, Float) -> (Length, Length) -> Extent ->
    ((Float, Float), Float)
resolveCircleExtent sz@(x',y') pos ext = ((x, y), inner ext)
  where
    (x,y) = l2f' pos sz
    sides = [x, x' - x, y, y' - y]
    corners = [hypot x y, hypot x $ y'-y, hypot y $ x'-x, hypot (x'-x) (y'-y)]
    hypot a b = sqrt $ a*a + b*b
    inner (Extent a _) = l2f a y -- Should be absolute...
    inner ClosestCorner = minimum corners
    inner ClosestSide = minimum sides
    inner FarthestCorner = maximum corners
    inner FarthestSide = maximum sides