]> gitweb.michael.orlitzky.com - spline3.git/blob - src/Grid.hs
94b9e1de7715bd4107a52904dff3ab803a0cd1a7
[spline3.git] / src / Grid.hs
1 {-# LANGUAGE BangPatterns #-}
2 -- | The Grid module just contains the Grid type and two constructors
3 -- for it. We hide the main Grid constructor because we don't want
4 -- to allow instantiation of a grid with h <= 0.
5 module Grid (
6 cube_at,
7 grid_tests,
8 make_grid,
9 slow_tests,
10 zoom
11 )
12 where
13
14 import qualified Data.Array.Repa as R
15 import Test.HUnit (Assertion, assertEqual)
16 import Test.Framework (Test, testGroup)
17 import Test.Framework.Providers.HUnit (testCase)
18 import Test.Framework.Providers.QuickCheck2 (testProperty)
19 import Test.QuickCheck ((==>),
20 Arbitrary(..),
21 Gen,
22 Positive(..),
23 Property,
24 choose)
25 import Assertions (assertAlmostEqual, assertTrue)
26 import Comparisons ((~=))
27 import Cube (Cube(Cube),
28 find_containing_tetrahedron,
29 tetrahedra,
30 tetrahedron)
31 import Examples (trilinear, trilinear9x9x9, zeros, naturals_1d)
32 import FunctionValues (make_values, value_at)
33 import Point (Point(..))
34 import ScaleFactor (ScaleFactor)
35 import Tetrahedron (
36 Tetrahedron(v0,v1,v2,v3),
37 c,
38 contains_point,
39 polynomial,
40 )
41 import Values (Values3D, dims, empty3d, zoom_shape)
42
43
44 -- | Our problem is defined on a Grid. The grid size is given by the
45 -- positive number h. The function values are the values of the
46 -- function at the grid points, which are distance h from one
47 -- another in each direction (x,y,z).
48 data Grid = Grid { h :: Double, -- MUST BE GREATER THAN ZERO!
49 function_values :: Values3D }
50 deriving (Show)
51
52
53 instance Arbitrary Grid where
54 arbitrary = do
55 (Positive h') <- arbitrary :: Gen (Positive Double)
56 fvs <- arbitrary :: Gen Values3D
57 return (make_grid h' fvs)
58
59
60 -- | The constructor that we want people to use.
61 -- Ignore non-positive grid sizes for performance.
62 make_grid :: Double -> Values3D -> Grid
63 make_grid grid_size values =
64 Grid grid_size values
65
66
67
68 -- | Takes a grid and a position as an argument and returns the cube
69 -- centered on that position. If there is no cube there, well, you
70 -- shouldn't have done that. The omitted "otherwise" case actually
71 -- does improve performance.
72 cube_at :: Grid -> Int -> Int -> Int -> Cube
73 cube_at !g !i !j !k =
74 Cube delta i j k fvs' tet_vol
75 where
76 fvs = function_values g
77 fvs' = make_values fvs i j k
78 delta = h g
79 tet_vol = (1/24)*(delta^(3::Int))
80
81
82 -- The first cube along any axis covers (-h/2, h/2). The second
83 -- covers (h/2, 3h/2). The third, (3h/2, 5h/2), and so on.
84 --
85 -- We translate the (x,y,z) coordinates forward by 'h/2' so that the
86 -- first covers (0, h), the second covers (h, 2h), etc. This makes
87 -- it easy to figure out which cube contains the given point.
88 calculate_containing_cube_coordinate :: Grid -> Double -> Int
89 calculate_containing_cube_coordinate g coord
90 -- Don't use a cube on the boundary if we can help it. This
91 -- returns cube #1 if we would have returned cube #0 and cube #1
92 -- exists.
93 | coord < offset = 0
94 | coord == offset && (xsize > 1 && ysize > 1 && zsize > 1) = 1
95 | otherwise = (ceiling ( (coord + offset) / cube_width )) - 1
96 where
97 (xsize, ysize, zsize) = dims (function_values g)
98 cube_width = (h g)
99 offset = cube_width / 2
100
101
102 -- | Takes a 'Grid', and returns a 'Cube' containing the given 'Point'.
103 -- Since our grid is rectangular, we can figure this out without having
104 -- to check every cube.
105 find_containing_cube :: Grid -> Point -> Cube
106 find_containing_cube g (Point x y z) =
107 cube_at g i j k
108 where
109 i = calculate_containing_cube_coordinate g x
110 j = calculate_containing_cube_coordinate g y
111 k = calculate_containing_cube_coordinate g z
112
113
114 zoom_lookup :: Values3D -> ScaleFactor -> a -> (R.DIM3 -> Double)
115 zoom_lookup v3d scale_factor _ =
116 zoom_result v3d scale_factor
117
118
119 zoom_result :: Values3D -> ScaleFactor -> R.DIM3 -> Double
120 zoom_result v3d (sfx, sfy, sfz) (R.Z R.:. m R.:. n R.:. o) =
121 f p
122 where
123 g = make_grid 1 v3d
124 offset = (h g)/2
125 m' = (fromIntegral m) / (fromIntegral sfx) - offset
126 n' = (fromIntegral n) / (fromIntegral sfy) - offset
127 o' = (fromIntegral o) / (fromIntegral sfz) - offset
128 p = Point m' n' o'
129 cube = find_containing_cube g p
130 t = find_containing_tetrahedron cube p
131 f = polynomial t
132
133
134 zoom :: Values3D -> ScaleFactor -> Values3D
135 zoom v3d scale_factor
136 | xsize == 0 || ysize == 0 || zsize == 0 = empty3d
137 | otherwise =
138 R.compute $ R.unsafeTraverse v3d transExtent f
139 where
140 (xsize, ysize, zsize) = dims v3d
141 transExtent = zoom_shape scale_factor
142 f = zoom_lookup v3d scale_factor
143
144
145 -- | Check all coefficients of tetrahedron0 belonging to the cube
146 -- centered on (1,1,1) with a grid constructed from the trilinear
147 -- values. See example one in the paper.
148 --
149 -- We also verify that the four vertices on face0 of the cube are
150 -- in the correct location.
151 --
152 trilinear_c0_t0_tests :: Test.Framework.Test
153 trilinear_c0_t0_tests =
154 testGroup "trilinear c0 t0"
155 [testGroup "coefficients"
156 [testCase "c0030 is correct" test_trilinear_c0030,
157 testCase "c0003 is correct" test_trilinear_c0003,
158 testCase "c0021 is correct" test_trilinear_c0021,
159 testCase "c0012 is correct" test_trilinear_c0012,
160 testCase "c0120 is correct" test_trilinear_c0120,
161 testCase "c0102 is correct" test_trilinear_c0102,
162 testCase "c0111 is correct" test_trilinear_c0111,
163 testCase "c0210 is correct" test_trilinear_c0210,
164 testCase "c0201 is correct" test_trilinear_c0201,
165 testCase "c0300 is correct" test_trilinear_c0300,
166 testCase "c1020 is correct" test_trilinear_c1020,
167 testCase "c1002 is correct" test_trilinear_c1002,
168 testCase "c1011 is correct" test_trilinear_c1011,
169 testCase "c1110 is correct" test_trilinear_c1110,
170 testCase "c1101 is correct" test_trilinear_c1101,
171 testCase "c1200 is correct" test_trilinear_c1200,
172 testCase "c2010 is correct" test_trilinear_c2010,
173 testCase "c2001 is correct" test_trilinear_c2001,
174 testCase "c2100 is correct" test_trilinear_c2100,
175 testCase "c3000 is correct" test_trilinear_c3000],
176
177 testGroup "face0 vertices"
178 [testCase "v0 is correct" test_trilinear_f0_t0_v0,
179 testCase "v1 is correct" test_trilinear_f0_t0_v1,
180 testCase "v2 is correct" test_trilinear_f0_t0_v2,
181 testCase "v3 is correct" test_trilinear_f0_t0_v3]
182 ]
183 where
184 g = make_grid 1 trilinear
185 cube = cube_at g 1 1 1
186 t = tetrahedron cube 0
187
188 test_trilinear_c0030 :: Assertion
189 test_trilinear_c0030 =
190 assertAlmostEqual "c0030 is correct" (c t 0 0 3 0) (17/8)
191
192 test_trilinear_c0003 :: Assertion
193 test_trilinear_c0003 =
194 assertAlmostEqual "c0003 is correct" (c t 0 0 0 3) (27/8)
195
196 test_trilinear_c0021 :: Assertion
197 test_trilinear_c0021 =
198 assertAlmostEqual "c0021 is correct" (c t 0 0 2 1) (61/24)
199
200 test_trilinear_c0012 :: Assertion
201 test_trilinear_c0012 =
202 assertAlmostEqual "c0012 is correct" (c t 0 0 1 2) (71/24)
203
204 test_trilinear_c0120 :: Assertion
205 test_trilinear_c0120 =
206 assertAlmostEqual "c0120 is correct" (c t 0 1 2 0) (55/24)
207
208 test_trilinear_c0102 :: Assertion
209 test_trilinear_c0102 =
210 assertAlmostEqual "c0102 is correct" (c t 0 1 0 2) (73/24)
211
212 test_trilinear_c0111 :: Assertion
213 test_trilinear_c0111 =
214 assertAlmostEqual "c0111 is correct" (c t 0 1 1 1) (8/3)
215
216 test_trilinear_c0210 :: Assertion
217 test_trilinear_c0210 =
218 assertAlmostEqual "c0210 is correct" (c t 0 2 1 0) (29/12)
219
220 test_trilinear_c0201 :: Assertion
221 test_trilinear_c0201 =
222 assertAlmostEqual "c0201 is correct" (c t 0 2 0 1) (11/4)
223
224 test_trilinear_c0300 :: Assertion
225 test_trilinear_c0300 =
226 assertAlmostEqual "c0300 is correct" (c t 0 3 0 0) (5/2)
227
228 test_trilinear_c1020 :: Assertion
229 test_trilinear_c1020 =
230 assertAlmostEqual "c1020 is correct" (c t 1 0 2 0) (8/3)
231
232 test_trilinear_c1002 :: Assertion
233 test_trilinear_c1002 =
234 assertAlmostEqual "c1002 is correct" (c t 1 0 0 2) (23/6)
235
236 test_trilinear_c1011 :: Assertion
237 test_trilinear_c1011 =
238 assertAlmostEqual "c1011 is correct" (c t 1 0 1 1) (13/4)
239
240 test_trilinear_c1110 :: Assertion
241 test_trilinear_c1110 =
242 assertAlmostEqual "c1110 is correct" (c t 1 1 1 0) (23/8)
243
244 test_trilinear_c1101 :: Assertion
245 test_trilinear_c1101 =
246 assertAlmostEqual "c1101 is correct" (c t 1 1 0 1) (27/8)
247
248 test_trilinear_c1200 :: Assertion
249 test_trilinear_c1200 =
250 assertAlmostEqual "c1200 is correct" (c t 1 2 0 0) 3
251
252 test_trilinear_c2010 :: Assertion
253 test_trilinear_c2010 =
254 assertAlmostEqual "c2010 is correct" (c t 2 0 1 0) (10/3)
255
256 test_trilinear_c2001 :: Assertion
257 test_trilinear_c2001 =
258 assertAlmostEqual "c2001 is correct" (c t 2 0 0 1) 4
259
260 test_trilinear_c2100 :: Assertion
261 test_trilinear_c2100 =
262 assertAlmostEqual "c2100 is correct" (c t 2 1 0 0) (7/2)
263
264 test_trilinear_c3000 :: Assertion
265 test_trilinear_c3000 =
266 assertAlmostEqual "c3000 is correct" (c t 3 0 0 0) 4
267
268 test_trilinear_f0_t0_v0 :: Assertion
269 test_trilinear_f0_t0_v0 =
270 assertEqual "v0 is correct" (v0 t) (Point 1 1 1)
271
272 test_trilinear_f0_t0_v1 :: Assertion
273 test_trilinear_f0_t0_v1 =
274 assertEqual "v1 is correct" (v1 t) (Point 0.5 1 1)
275
276 test_trilinear_f0_t0_v2 :: Assertion
277 test_trilinear_f0_t0_v2 =
278 assertEqual "v2 is correct" (v2 t) (Point 0.5 0.5 1.5)
279
280 test_trilinear_f0_t0_v3 :: Assertion
281 test_trilinear_f0_t0_v3 =
282 assertEqual "v3 is correct" (v3 t) (Point 0.5 1.5 1.5)
283
284
285 test_trilinear_reproduced :: Assertion
286 test_trilinear_reproduced =
287 assertTrue "trilinears are reproduced correctly" $
288 and [p (Point i' j' k') ~= value_at trilinear i j k
289 | i <- [0..2],
290 j <- [0..2],
291 k <- [0..2],
292 c0 <- cs,
293 t <- tetrahedra c0,
294 let p = polynomial t,
295 let i' = fromIntegral i,
296 let j' = fromIntegral j,
297 let k' = fromIntegral k]
298 where
299 g = make_grid 1 trilinear
300 cs = [ cube_at g ci cj ck | ci <- [0..2], cj <- [0..2], ck <- [0..2] ]
301
302
303 test_zeros_reproduced :: Assertion
304 test_zeros_reproduced =
305 assertTrue "the zero function is reproduced correctly" $
306 and [p (Point i' j' k') ~= value_at zeros i j k
307 | i <- [0..2],
308 j <- [0..2],
309 k <- [0..2],
310 let i' = fromIntegral i,
311 let j' = fromIntegral j,
312 let k' = fromIntegral k,
313 c0 <- cs,
314 t0 <- tetrahedra c0,
315 let p = polynomial t0 ]
316 where
317 g = make_grid 1 zeros
318 cs = [ cube_at g ci cj ck | ci <- [0..2], cj <- [0..2], ck <- [0..2] ]
319
320
321 -- | Make sure we can reproduce a 9x9x9 trilinear from the 3x3x3 one.
322 test_trilinear9x9x9_reproduced :: Assertion
323 test_trilinear9x9x9_reproduced =
324 assertTrue "trilinear 9x9x9 is reproduced correctly" $
325 and [p (Point i' j' k') ~= value_at trilinear9x9x9 i j k
326 | i <- [0..8],
327 j <- [0..8],
328 k <- [0..8],
329 t <- tetrahedra c0,
330 let p = polynomial t,
331 let i' = (fromIntegral i) * 0.5,
332 let j' = (fromIntegral j) * 0.5,
333 let k' = (fromIntegral k) * 0.5]
334 where
335 g = make_grid 1 trilinear
336 c0 = cube_at g 1 1 1
337
338
339 -- | The point 'p' in this test lies on the boundary of tetrahedra 12 and 15.
340 -- However, the 'contains_point' test fails due to some numerical innacuracy.
341 -- This bug should have been fixed by setting a positive tolerance level.
342 --
343 -- Example from before the fix:
344 --
345 -- b1 (tetrahedron c 20) (0, 17.5, 0.5)
346 -- -0.0
347 --
348 test_tetrahedra_collision_sensitivity :: Assertion
349 test_tetrahedra_collision_sensitivity =
350 assertTrue "tetrahedron collision tests isn't too sensitive" $
351 contains_point t20 p
352 where
353 g = make_grid 1 naturals_1d
354 cube = cube_at g 0 18 0
355 p = Point 0 17.5 0.5
356 t20 = tetrahedron cube 20
357
358
359 prop_cube_indices_never_go_out_of_bounds :: Grid -> Gen Bool
360 prop_cube_indices_never_go_out_of_bounds g =
361 do
362 let delta = Grid.h g
363 let coordmin = negate (delta/2)
364
365 let (xsize, ysize, zsize) = dims $ function_values g
366 let xmax = delta*(fromIntegral xsize) - (delta/2)
367 let ymax = delta*(fromIntegral ysize) - (delta/2)
368 let zmax = delta*(fromIntegral zsize) - (delta/2)
369
370 x <- choose (coordmin, xmax)
371 y <- choose (coordmin, ymax)
372 z <- choose (coordmin, zmax)
373
374 let idx_x = calculate_containing_cube_coordinate g x
375 let idx_y = calculate_containing_cube_coordinate g y
376 let idx_z = calculate_containing_cube_coordinate g z
377
378 return $
379 idx_x >= 0 &&
380 idx_x <= xsize - 1 &&
381 idx_y >= 0 &&
382 idx_y <= ysize - 1 &&
383 idx_z >= 0 &&
384 idx_z <= zsize - 1
385
386
387 -- | Given in Sorokina and Zeilfelder, p. 80, (2.9). Note that the
388 -- third and fourth indices of c-t10 have been switched. This is
389 -- because we store the triangles oriented such that their volume is
390 -- positive. If T and T-tilde share \<v1,v2,v3\> and v0,v0-tilde point
391 -- in opposite directions, one of them has to have negative volume!
392 prop_c0120_identity :: Grid -> Property
393 prop_c0120_identity g =
394 and [xsize >= 3, ysize >= 3, zsize >= 3] ==>
395 c t0 0 1 2 0 ~= (c t0 1 0 2 0 + c t10 1 0 0 2) / 2
396 where
397 fvs = function_values g
398 (xsize, ysize, zsize) = dims fvs
399 cube0 = cube_at g 1 1 1
400 cube1 = cube_at g 0 1 1
401 t0 = tetrahedron cube0 0 -- These two tetrahedra share a face.
402 t10 = tetrahedron cube1 10
403
404
405 -- | Given in Sorokina and Zeilfelder, p. 80, (2.9). See
406 -- 'prop_c0120_identity'.
407 prop_c0111_identity :: Grid -> Property
408 prop_c0111_identity g =
409 and [xsize >= 3, ysize >= 3, zsize >= 3] ==>
410 c t0 0 1 1 1 ~= (c t0 1 0 1 1 + c t10 1 0 1 1) / 2
411 where
412 fvs = function_values g
413 (xsize, ysize, zsize) = dims fvs
414 cube0 = cube_at g 1 1 1
415 cube1 = cube_at g 0 1 1
416 t0 = tetrahedron cube0 0 -- These two tetrahedra share a face.
417 t10 = tetrahedron cube1 10
418
419
420 -- | Given in Sorokina and Zeilfelder, p. 80, (2.9). See
421 -- 'prop_c0120_identity'.
422 prop_c0201_identity :: Grid -> Property
423 prop_c0201_identity g =
424 and [xsize >= 3, ysize >= 3, zsize >= 3] ==>
425 c t0 0 2 0 1 ~= (c t0 1 1 0 1 + c t10 1 1 1 0) / 2
426 where
427 fvs = function_values g
428 (xsize, ysize, zsize) = dims fvs
429 cube0 = cube_at g 1 1 1
430 cube1 = cube_at g 0 1 1
431 t0 = tetrahedron cube0 0 -- These two tetrahedra share a face.
432 t10 = tetrahedron cube1 10
433
434
435 -- | Given in Sorokina and Zeilfelder, p. 80, (2.9). See
436 -- 'prop_c0120_identity'.
437 prop_c0102_identity :: Grid -> Property
438 prop_c0102_identity g =
439 and [xsize >= 3, ysize >= 3, zsize >= 3] ==>
440 c t0 0 1 0 2 ~= (c t0 1 0 0 2 + c t10 1 0 2 0) / 2
441 where
442 fvs = function_values g
443 (xsize, ysize, zsize) = dims fvs
444 cube0 = cube_at g 1 1 1
445 cube1 = cube_at g 0 1 1
446 t0 = tetrahedron cube0 0 -- These two tetrahedra share a face.
447 t10 = tetrahedron cube1 10
448
449
450 -- | Given in Sorokina and Zeilfelder, p. 80, (2.9). See
451 -- 'prop_c0120_identity'.
452 prop_c0210_identity :: Grid -> Property
453 prop_c0210_identity g =
454 and [xsize >= 3, ysize >= 3, zsize >= 3] ==>
455 c t0 0 2 1 0 ~= (c t0 1 1 1 0 + c t10 1 1 0 1) / 2
456 where
457 fvs = function_values g
458 (xsize, ysize, zsize) = dims fvs
459 cube0 = cube_at g 1 1 1
460 cube1 = cube_at g 0 1 1
461 t0 = tetrahedron cube0 0 -- These two tetrahedra share a face.
462 t10 = tetrahedron cube1 10
463
464
465 -- | Given in Sorokina and Zeilfelder, p. 80, (2.9). See
466 -- 'prop_c0120_identity'.
467 prop_c0300_identity :: Grid -> Property
468 prop_c0300_identity g =
469 and [xsize >= 3, ysize >= 3, zsize >= 3] ==>
470 c t0 0 3 0 0 ~= (c t0 1 2 0 0 + c t10 1 2 0 0) / 2
471 where
472 fvs = function_values g
473 (xsize, ysize, zsize) = dims fvs
474 cube0 = cube_at g 1 1 1
475 cube1 = cube_at g 0 1 1
476 t0 = tetrahedron cube0 0 -- These two tetrahedra share a face.
477 t10 = tetrahedron cube1 10
478
479
480 -- | All of the properties from Section (2.9), p. 80. These require a
481 -- grid since they refer to two adjacent cubes.
482 p80_29_properties :: Test.Framework.Test
483 p80_29_properties =
484 testGroup "p. 80, Section (2.9) Properties" [
485 testProperty "c0120 identity" prop_c0120_identity,
486 testProperty "c0111 identity" prop_c0111_identity,
487 testProperty "c0201 identity" prop_c0201_identity,
488 testProperty "c0102 identity" prop_c0102_identity,
489 testProperty "c0210 identity" prop_c0210_identity,
490 testProperty "c0300 identity" prop_c0300_identity ]
491
492
493 grid_tests :: Test.Framework.Test
494 grid_tests =
495 testGroup "Grid Tests" [
496 trilinear_c0_t0_tests,
497 p80_29_properties,
498 testCase "tetrahedra collision test isn't too sensitive"
499 test_tetrahedra_collision_sensitivity,
500 testProperty "cube indices within bounds"
501 prop_cube_indices_never_go_out_of_bounds ]
502
503
504 -- Do the slow tests last so we can stop paying attention.
505 slow_tests :: Test.Framework.Test
506 slow_tests =
507 testGroup "Slow Tests" [
508 testCase "trilinear reproduced" test_trilinear_reproduced,
509 testCase "trilinear9x9x9 reproduced" test_trilinear9x9x9_reproduced,
510 testCase "zeros reproduced" test_zeros_reproduced ]