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