]> gitweb.michael.orlitzky.com - spline3.git/blob - src/FunctionValues.hs
632a7f4bd7370d2867fd2af61bf528233661a985
[spline3.git] / src / FunctionValues.hs
1 -- The "value_at" function pattern matches on some integers, but
2 -- doesn't handle the "otherwise" case, for performance reasons.
3 {-# OPTIONS_GHC -Wno-incomplete-patterns #-}
4 {-# LANGUAGE BangPatterns #-}
5
6 -- | The FunctionValues module contains the 'FunctionValues' type and
7 -- the functions used to manipulate it.
8 --
9 module FunctionValues (
10 FunctionValues(..),
11 empty_values,
12 eval,
13 make_values,
14 rotate,
15 function_values_tests,
16 function_values_properties,
17 value_at )
18 where
19
20 import Prelude hiding ( LT )
21 import Test.Tasty ( TestTree, testGroup )
22 import Test.Tasty.HUnit ( Assertion, testCase )
23 import Test.Tasty.QuickCheck ( Arbitrary( arbitrary ), choose, testProperty )
24
25 import Assertions ( assertTrue )
26 import Cardinal (
27 Cardinal(F, B, L, R, D, T, FL, FR, FD, FT, BL, BR, BD, BT, LD, LT, RD,
28 RT, FLD, FLT, FRD, FRT, BLD, BLT, BRD, BRT, I, Scalar, Sum,
29 Difference, Product, Quotient ),
30 cwx,
31 cwy,
32 cwz )
33 import Examples ( trilinear )
34 import Values ( Values3D, dims, idx )
35
36 -- | The FunctionValues type represents the value of our function f at
37 -- the 27 points surrounding (and including) the center of a
38 -- cube. Each value of f can be accessed by the name of its
39 -- direction.
40 --
41 data FunctionValues =
42 FunctionValues { front :: !Double,
43 back :: !Double,
44 left :: !Double,
45 right :: !Double,
46 top :: !Double,
47 down :: !Double,
48 front_left :: !Double,
49 front_right :: !Double,
50 front_down :: !Double,
51 front_top :: !Double,
52 back_left :: !Double,
53 back_right :: !Double,
54 back_down :: !Double,
55 back_top :: !Double,
56 left_down :: !Double,
57 left_top :: !Double,
58 right_down :: !Double,
59 right_top :: !Double,
60 front_left_down :: !Double,
61 front_left_top :: !Double,
62 front_right_down :: !Double,
63 front_right_top :: !Double,
64 back_left_down :: !Double,
65 back_left_top :: !Double,
66 back_right_down :: !Double,
67 back_right_top :: !Double,
68 interior :: !Double }
69 deriving (Eq, Show)
70
71
72 instance Arbitrary FunctionValues where
73 arbitrary = do
74 front' <- choose (min_double, max_double)
75 back' <- choose (min_double, max_double)
76 left' <- choose (min_double, max_double)
77 right' <- choose (min_double, max_double)
78 top' <- choose (min_double, max_double)
79 down' <- choose (min_double, max_double)
80 front_left' <- choose (min_double, max_double)
81 front_right' <- choose (min_double, max_double)
82 front_top' <- choose (min_double, max_double)
83 front_down' <- choose (min_double, max_double)
84 back_left' <- choose (min_double, max_double)
85 back_right' <- choose (min_double, max_double)
86 back_top' <- choose (min_double, max_double)
87 back_down' <- choose (min_double, max_double)
88 left_top' <- choose (min_double, max_double)
89 left_down' <- choose (min_double, max_double)
90 right_top' <- choose (min_double, max_double)
91 right_down' <- choose (min_double, max_double)
92 front_left_top' <- choose (min_double, max_double)
93 front_left_down' <- choose (min_double, max_double)
94 front_right_top' <- choose (min_double, max_double)
95 front_right_down' <- choose (min_double, max_double)
96 back_left_top' <- choose (min_double, max_double)
97 back_left_down' <- choose (min_double, max_double)
98 back_right_top' <- choose (min_double, max_double)
99 back_right_down' <- choose (min_double, max_double)
100 interior' <- choose (min_double, max_double)
101
102 return empty_values { front = front',
103 back = back',
104 left = left',
105 right = right',
106 top = top',
107 down = down',
108 front_left = front_left',
109 front_right = front_right',
110 front_top = front_top',
111 front_down = front_down',
112 back_left = back_left',
113 back_right = back_right',
114 back_top = back_top',
115 back_down = back_down',
116 left_top = left_top',
117 left_down = left_down',
118 right_top = right_top',
119 right_down = right_down',
120 front_left_top = front_left_top',
121 front_left_down = front_left_down',
122 front_right_top = front_right_top',
123 front_right_down = front_right_down',
124 back_left_top = back_left_top',
125 back_left_down = back_left_down',
126 back_right_top = back_right_top',
127 back_right_down = back_right_down',
128 interior = interior' }
129 where
130 -- | We perform addition with the function values contained in a
131 -- FunctionValues object. If we choose random doubles near the machine
132 -- min/max, we risk overflowing or underflowing the 'Double'. This
133 -- places a reasonably safe limit on the maximum size of our generated
134 -- 'Double' members.
135 max_double :: Double
136 max_double = 10000.0
137
138 -- | See 'max_double'.
139 min_double :: Double
140 min_double = (-1) * max_double
141
142
143 -- | Return a 'FunctionValues' with a bunch of zeros for data points.
144 empty_values :: FunctionValues
145 empty_values =
146 FunctionValues 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
147
148
149 -- | The eval function is where the magic happens for the
150 -- FunctionValues type. Given a 'Cardinal' direction and a
151 -- 'FunctionValues' object, eval will return the value of the
152 -- function f in that 'Cardinal' direction. Note that 'Cardinal' can
153 -- be a composite type; eval is what performs the \"arithmetic\" on
154 -- 'Cardinal' directions.
155 eval :: FunctionValues -> Cardinal -> Double
156 eval f F = front f
157 eval f B = back f
158 eval f L = left f
159 eval f R = right f
160 eval f T = top f
161 eval f D = down f
162 eval f FL = front_left f
163 eval f FR = front_right f
164 eval f FD = front_down f
165 eval f FT = front_top f
166 eval f BL = back_left f
167 eval f BR = back_right f
168 eval f BD = back_down f
169 eval f BT = back_top f
170 eval f LD = left_down f
171 eval f LT = left_top f
172 eval f RD = right_down f
173 eval f RT = right_top f
174 eval f FLD = front_left_down f
175 eval f FLT = front_left_top f
176 eval f FRD = front_right_down f
177 eval f FRT = front_right_top f
178 eval f BLD = back_left_down f
179 eval f BLT = back_left_top f
180 eval f BRD = back_right_down f
181 eval f BRT = back_right_top f
182 eval f I = interior f
183 eval _ (Scalar x) = x
184 eval f (Sum x y) = (eval f x) + (eval f y)
185 eval f (Difference x y) = (eval f x) - (eval f y)
186 eval f (Product x y) = (eval f x) * (eval f y)
187 eval f (Quotient x y) = (eval f x) / (eval f y)
188
189
190 -- | Takes a three-dimensional list of 'Double' and a set of 3D
191 -- coordinates (i,j,k), and returns the value at (i,j,k) in the
192 -- supplied list. If there is no such value, we calculate one
193 -- according to Sorokina and Zeilfelder, remark 7.3, p. 99.
194 --
195 -- We specifically do not consider values more than one unit away
196 -- from our grid.
197 --
198 -- Examples:
199 --
200 -- >>> value_at Examples.trilinear 0 0 0
201 -- 1.0
202 --
203 -- >>> value_at Examples.trilinear (-1) 0 0
204 -- 0.0
205 --
206 -- >>> value_at Examples.trilinear 0 0 4
207 -- 1.0
208 --
209 -- >>> value_at Examples.trilinear 1 3 0
210 -- 5.0
211 --
212 value_at :: Values3D -> Int -> Int -> Int -> Double
213 value_at v3d !i !j !k
214 -- Put the most common case first!
215 | (valid_i i) && (valid_j j) && (valid_k k) =
216 idx v3d i j k
217
218 -- The next three are from the first line in (7.3). Analogous cases
219 -- have been added where the indices are one-too-big. These are the
220 -- "one index is bad" cases.
221 | not (valid_i i) =
222 if (dim_i == 1)
223 then
224 -- We're one-dimensional in our first coordinate, so just
225 -- return the data point that we do have. If we try to use
226 -- the formula from remark 7.3, we go into an infinite loop.
227 value_at v3d 0 j k
228 else
229 if (i == -1)
230 then
231 2*(value_at v3d 0 j k) - (value_at v3d 1 j k)
232 else
233 2*(value_at v3d (i-1) j k) - (value_at v3d (i-2) j k)
234
235 | not (valid_j j) =
236 if (dim_j == 1)
237 then
238 -- We're one-dimensional in our second coordinate, so just
239 -- return the data point that we do have. If we try to use
240 -- the formula from remark 7.3, we go into an infinite loop.
241 value_at v3d i 0 k
242 else
243 if (j == -1)
244 then
245 2*(value_at v3d i 0 k) - (value_at v3d i 1 k)
246 else
247 2*(value_at v3d i (j-1) k) - (value_at v3d i (j-2) k)
248
249 | not (valid_k k) =
250 if (dim_k == 1)
251 then
252 -- We're one-dimensional in our third coordinate, so just
253 -- return the data point that we do have. If we try to use
254 -- the formula from remark 7.3, we go into an infinite loop.
255 value_at v3d i j 0
256 else
257 if (k == -1)
258 then
259 2*(value_at v3d i j 0) - (value_at v3d i j 1)
260 else
261 2*(value_at v3d i j (k-1)) - (value_at v3d i j (k-2))
262 where
263 (dim_i, dim_j, dim_k) = dims v3d
264
265 valid_i :: Int -> Bool
266 valid_i i' = (i' >= 0) && (i' < dim_i)
267
268 valid_j :: Int -> Bool
269 valid_j j' = (j' >= 0) && (j' < dim_j)
270
271 valid_k :: Int -> Bool
272 valid_k k' = (k' >= 0) && (k' < dim_k)
273
274
275
276 -- | Given a three-dimensional list of 'Double' and a set of 3D
277 -- coordinates (i,j,k), constructs and returns the 'FunctionValues'
278 -- object centered at (i,j,k)
279 make_values :: Values3D -> Int -> Int -> Int -> FunctionValues
280 make_values values !i !j !k =
281 empty_values { front = value_at values (i-1) j k,
282 back = value_at values (i+1) j k,
283 left = value_at values i (j-1) k,
284 right = value_at values i (j+1) k,
285 down = value_at values i j (k-1),
286 top = value_at values i j (k+1),
287 front_left = value_at values (i-1) (j-1) k,
288 front_right = value_at values (i-1) (j+1) k,
289 front_down =value_at values (i-1) j (k-1),
290 front_top = value_at values (i-1) j (k+1),
291 back_left = value_at values (i+1) (j-1) k,
292 back_right = value_at values (i+1) (j+1) k,
293 back_down = value_at values (i+1) j (k-1),
294 back_top = value_at values (i+1) j (k+1),
295 left_down = value_at values i (j-1) (k-1),
296 left_top = value_at values i (j-1) (k+1),
297 right_down = value_at values i (j+1) (k-1),
298 right_top = value_at values i (j+1) (k+1),
299 front_left_down = value_at values (i-1) (j-1) (k-1),
300 front_left_top = value_at values (i-1) (j-1) (k+1),
301 front_right_down = value_at values (i-1) (j+1) (k-1),
302 front_right_top = value_at values (i-1) (j+1) (k+1),
303 back_left_down = value_at values (i+1) (j-1) (k-1),
304 back_left_top = value_at values (i+1) (j-1) (k+1),
305 back_right_down = value_at values (i+1) (j+1) (k-1),
306 back_right_top = value_at values (i+1) (j+1) (k+1),
307 interior = value_at values i j k }
308
309 -- | Takes a 'FunctionValues' and a function that transforms one
310 -- 'Cardinal' to another (called a rotation). Then it applies the
311 -- rotation to each element of the 'FunctionValues' object, and
312 -- returns the result.
313 rotate :: (Cardinal -> Cardinal) -> FunctionValues -> FunctionValues
314 rotate rotation fv =
315 FunctionValues { front = eval fv (rotation F),
316 back = eval fv (rotation B),
317 left = eval fv (rotation L),
318 right = eval fv (rotation R),
319 down = eval fv (rotation D),
320 top = eval fv (rotation T),
321 front_left = eval fv (rotation FL),
322 front_right = eval fv (rotation FR),
323 front_down = eval fv (rotation FD),
324 front_top = eval fv (rotation FT),
325 back_left = eval fv (rotation BL),
326 back_right = eval fv (rotation BR),
327 back_down = eval fv (rotation BD),
328 back_top = eval fv (rotation BT),
329 left_down = eval fv (rotation LD),
330 left_top = eval fv (rotation LT),
331 right_down = eval fv (rotation RD),
332 right_top = eval fv (rotation RT),
333 front_left_down = eval fv (rotation FLD),
334 front_left_top = eval fv (rotation FLT),
335 front_right_down = eval fv (rotation FRD),
336 front_right_top = eval fv (rotation FRT),
337 back_left_down = eval fv (rotation BLD),
338 back_left_top = eval fv (rotation BLT),
339 back_right_down = eval fv (rotation BRD),
340 back_right_top = eval fv (rotation BRT),
341 interior = interior fv }
342
343
344
345 -- | Ensure that the trilinear values wind up where we think they
346 -- should.
347 test_directions :: Assertion
348 test_directions =
349 assertTrue "all direction functions work" (and equalities)
350 where
351 fvs = make_values trilinear 1 1 1
352 equalities = [ interior fvs == 4,
353 front fvs == 1,
354 back fvs == 7,
355 left fvs == 2,
356 right fvs == 6,
357 down fvs == 3,
358 top fvs == 5,
359 front_left fvs == 1,
360 front_right fvs == 1,
361 front_down fvs == 1,
362 front_top fvs == 1,
363 back_left fvs == 3,
364 back_right fvs == 11,
365 back_down fvs == 5,
366 back_top fvs == 9,
367 left_down fvs == 2,
368 left_top fvs == 2,
369 right_down fvs == 4,
370 right_top fvs == 8,
371 front_left_down fvs == 1,
372 front_left_top fvs == 1,
373 front_right_down fvs == 1,
374 front_right_top fvs == 1,
375 back_left_down fvs == 3,
376 back_left_top fvs == 3,
377 back_right_down fvs == 7,
378 back_right_top fvs == 15]
379
380
381 function_values_tests :: TestTree
382 function_values_tests =
383 testGroup "FunctionValues tests"
384 [ testCase "test directions" test_directions ]
385
386
387 prop_x_rotation_doesnt_affect_front :: FunctionValues -> Bool
388 prop_x_rotation_doesnt_affect_front fv0 =
389 expr1 == expr2
390 where
391 fv1 = rotate cwx fv0
392 expr1 = front fv0
393 expr2 = front fv1
394
395 prop_x_rotation_doesnt_affect_back :: FunctionValues -> Bool
396 prop_x_rotation_doesnt_affect_back fv0 =
397 expr1 == expr2
398 where
399 fv1 = rotate cwx fv0
400 expr1 = back fv0
401 expr2 = back fv1
402
403
404 prop_y_rotation_doesnt_affect_left :: FunctionValues -> Bool
405 prop_y_rotation_doesnt_affect_left fv0 =
406 expr1 == expr2
407 where
408 fv1 = rotate cwy fv0
409 expr1 = left fv0
410 expr2 = left fv1
411
412 prop_y_rotation_doesnt_affect_right :: FunctionValues -> Bool
413 prop_y_rotation_doesnt_affect_right fv0 =
414 expr1 == expr2
415 where
416 fv1 = rotate cwy fv0
417 expr1 = right fv0
418 expr2 = right fv1
419
420
421 prop_z_rotation_doesnt_affect_down :: FunctionValues -> Bool
422 prop_z_rotation_doesnt_affect_down fv0 =
423 expr1 == expr2
424 where
425 fv1 = rotate cwz fv0
426 expr1 = down fv0
427 expr2 = down fv1
428
429
430 prop_z_rotation_doesnt_affect_top :: FunctionValues -> Bool
431 prop_z_rotation_doesnt_affect_top fv0 =
432 expr1 == expr2
433 where
434 fv1 = rotate cwz fv0
435 expr1 = top fv0
436 expr2 = top fv1
437
438
439 function_values_properties :: TestTree
440 function_values_properties =
441 testGroup "FunctionValues properties" [
442 testProperty
443 "x rotation doesn't affect front"
444 prop_x_rotation_doesnt_affect_front,
445 testProperty
446 "x rotation doesn't affect back"
447 prop_x_rotation_doesnt_affect_back,
448 testProperty
449 "y rotation doesn't affect left"
450 prop_y_rotation_doesnt_affect_left,
451 testProperty
452 "y rotation doesn't affect right"
453 prop_y_rotation_doesnt_affect_right,
454 testProperty
455 "z rotation doesn't affect top"
456 prop_z_rotation_doesnt_affect_top,
457 testProperty
458 "z rotation doesn't affect down"
459 prop_z_rotation_doesnt_affect_down ]