]> gitweb.michael.orlitzky.com - spline3.git/blob - src/Tetrahedron.hs
Inline Tetrahedron functions volume, b0, b1, b2, and b3 (Ben Lippmeier).
[spline3.git] / src / Tetrahedron.hs
1 {-# LANGUAGE BangPatterns #-}
2 module Tetrahedron (
3 Tetrahedron(..),
4 b0, -- Cube test
5 b1, -- Cube test
6 b2, -- Cube test
7 b3, -- Cube test
8 c,
9 polynomial,
10 tetrahedron_properties,
11 tetrahedron_tests,
12 volume -- Cube test
13 )
14 where
15
16 import qualified Data.Vector as V (
17 singleton,
18 snoc,
19 sum
20 )
21
22 import Test.Framework (Test, testGroup)
23 import Test.Framework.Providers.HUnit (testCase)
24 import Test.Framework.Providers.QuickCheck2 (testProperty)
25 import Test.HUnit (Assertion, assertEqual)
26 import Test.QuickCheck (Arbitrary(..), Gen, Property, (==>))
27
28 import Comparisons ((~=), nearly_ge)
29 import FunctionValues (FunctionValues(..), empty_values)
30 import Misc (factorial)
31 import Point (Point(..), scale)
32 import RealFunction (RealFunction, cmult, fexp)
33 import ThreeDimensional (ThreeDimensional(..))
34
35 data Tetrahedron =
36 Tetrahedron { function_values :: FunctionValues,
37 v0 :: !Point,
38 v1 :: !Point,
39 v2 :: !Point,
40 v3 :: !Point,
41 precomputed_volume :: !Double
42 }
43 deriving (Eq)
44
45
46 instance Arbitrary Tetrahedron where
47 arbitrary = do
48 rnd_v0 <- arbitrary :: Gen Point
49 rnd_v1 <- arbitrary :: Gen Point
50 rnd_v2 <- arbitrary :: Gen Point
51 rnd_v3 <- arbitrary :: Gen Point
52 rnd_fv <- arbitrary :: Gen FunctionValues
53
54 -- We can't assign an incorrect precomputed volume,
55 -- so we have to calculate the correct one here.
56 let t' = Tetrahedron rnd_fv rnd_v0 rnd_v1 rnd_v2 rnd_v3 0
57 let vol = volume t'
58 return (Tetrahedron rnd_fv rnd_v0 rnd_v1 rnd_v2 rnd_v3 vol)
59
60
61 instance Show Tetrahedron where
62 show t = "Tetrahedron:\n" ++
63 " function_values: " ++ (show (function_values t)) ++ "\n" ++
64 " v0: " ++ (show (v0 t)) ++ "\n" ++
65 " v1: " ++ (show (v1 t)) ++ "\n" ++
66 " v2: " ++ (show (v2 t)) ++ "\n" ++
67 " v3: " ++ (show (v3 t)) ++ "\n"
68
69
70 instance ThreeDimensional Tetrahedron where
71 center (Tetrahedron _ v0' v1' v2' v3' _) =
72 (v0' + v1' + v2' + v3') `scale` (1/4)
73
74 -- contains_point is only used in tests.
75 contains_point t p0 =
76 b0_unscaled `nearly_ge` 0 &&
77 b1_unscaled `nearly_ge` 0 &&
78 b2_unscaled `nearly_ge` 0 &&
79 b3_unscaled `nearly_ge` 0
80 where
81 -- Drop the useless division and volume calculation that we
82 -- would do if we used the regular b0,..b3 functions.
83 b0_unscaled :: Double
84 b0_unscaled = volume inner_tetrahedron
85 where inner_tetrahedron = t { v0 = p0 }
86
87 b1_unscaled :: Double
88 b1_unscaled = volume inner_tetrahedron
89 where inner_tetrahedron = t { v1 = p0 }
90
91 b2_unscaled :: Double
92 b2_unscaled = volume inner_tetrahedron
93 where inner_tetrahedron = t { v2 = p0 }
94
95 b3_unscaled :: Double
96 b3_unscaled = volume inner_tetrahedron
97 where inner_tetrahedron = t { v3 = p0 }
98
99
100 polynomial :: Tetrahedron -> (RealFunction Point)
101 polynomial t =
102 V.sum $ V.singleton ((c t 0 0 0 3) `cmult` (beta t 0 0 0 3)) `V.snoc`
103 ((c t 0 0 1 2) `cmult` (beta t 0 0 1 2)) `V.snoc`
104 ((c t 0 0 2 1) `cmult` (beta t 0 0 2 1)) `V.snoc`
105 ((c t 0 0 3 0) `cmult` (beta t 0 0 3 0)) `V.snoc`
106 ((c t 0 1 0 2) `cmult` (beta t 0 1 0 2)) `V.snoc`
107 ((c t 0 1 1 1) `cmult` (beta t 0 1 1 1)) `V.snoc`
108 ((c t 0 1 2 0) `cmult` (beta t 0 1 2 0)) `V.snoc`
109 ((c t 0 2 0 1) `cmult` (beta t 0 2 0 1)) `V.snoc`
110 ((c t 0 2 1 0) `cmult` (beta t 0 2 1 0)) `V.snoc`
111 ((c t 0 3 0 0) `cmult` (beta t 0 3 0 0)) `V.snoc`
112 ((c t 1 0 0 2) `cmult` (beta t 1 0 0 2)) `V.snoc`
113 ((c t 1 0 1 1) `cmult` (beta t 1 0 1 1)) `V.snoc`
114 ((c t 1 0 2 0) `cmult` (beta t 1 0 2 0)) `V.snoc`
115 ((c t 1 1 0 1) `cmult` (beta t 1 1 0 1)) `V.snoc`
116 ((c t 1 1 1 0) `cmult` (beta t 1 1 1 0)) `V.snoc`
117 ((c t 1 2 0 0) `cmult` (beta t 1 2 0 0)) `V.snoc`
118 ((c t 2 0 0 1) `cmult` (beta t 2 0 0 1)) `V.snoc`
119 ((c t 2 0 1 0) `cmult` (beta t 2 0 1 0)) `V.snoc`
120 ((c t 2 1 0 0) `cmult` (beta t 2 1 0 0)) `V.snoc`
121 ((c t 3 0 0 0) `cmult` (beta t 3 0 0 0))
122
123
124
125 -- | The Bernstein polynomial on t with indices i,j,k,l. Denoted by a
126 -- capital 'B' in the Sorokina/Zeilfelder paper.
127 beta :: Tetrahedron -> Int -> Int -> Int -> Int -> (RealFunction Point)
128 beta t i j k l
129 | (i + j + k + l == 3) =
130 coefficient `cmult` (b0_term * b1_term * b2_term * b3_term)
131 | otherwise = error "basis function index out of bounds"
132 where
133 denominator = (factorial i)*(factorial j)*(factorial k)*(factorial l)
134 coefficient = 6 / (fromIntegral denominator)
135 b0_term = (b0 t) `fexp` i
136 b1_term = (b1 t) `fexp` j
137 b2_term = (b2 t) `fexp` k
138 b3_term = (b3 t) `fexp` l
139
140
141 -- | The coefficient function. c t i j k l returns the coefficient
142 -- c_ijkl with respect to the tetrahedron t. The definition uses
143 -- pattern matching to mimic the definitions given in Sorokina and
144 -- Zeilfelder, pp. 84-86. If incorrect indices are supplied, the
145 -- function will simply error.
146 c :: Tetrahedron -> Int -> Int -> Int -> Int -> Double
147 c !t !i !j !k !l =
148 coefficient i j k l
149 where
150 fvs = function_values t
151 f = front fvs
152 b = back fvs
153 r = right fvs
154 l' = left fvs
155 t' = top fvs
156 d = down fvs
157 fl = front_left fvs
158 fr = front_right fvs
159 fd = front_down fvs
160 ft = front_top fvs
161 bl = back_left fvs
162 br = back_right fvs
163 bd = back_down fvs
164 bt = back_top fvs
165 ld = left_down fvs
166 lt = left_top fvs
167 rd = right_down fvs
168 rt = right_top fvs
169 fld = front_left_down fvs
170 flt = front_left_top fvs
171 frd = front_right_down fvs
172 frt = front_right_top fvs
173 i' = interior fvs
174
175 coefficient :: Int -> Int -> Int -> Int -> Double
176 coefficient 0 0 3 0 =
177 (1/8) * (i' + f + l' + t' + lt + fl + ft + flt)
178
179 coefficient 0 0 0 3 =
180 (1/8) * (i' + f + r + t' + rt + fr + ft + frt)
181
182 coefficient 0 0 2 1 =
183 (5/24)*(i' + f + t' + ft) + (1/24)*(l' + fl + lt + flt)
184
185 coefficient 0 0 1 2 =
186 (5/24)*(i' + f + t' + ft) + (1/24)*(r + fr + rt + frt)
187
188 coefficient 0 1 2 0 =
189 (5/24)*(i' + f) + (1/8)*(l' + t' + fl + ft)
190 + (1/24)*(lt + flt)
191
192 coefficient 0 1 0 2 =
193 (5/24)*(i' + f) + (1/8)*(r + t' + fr + ft)
194 + (1/24)*(rt + frt)
195
196 coefficient 0 1 1 1 =
197 (13/48)*(i' + f) + (7/48)*(t' + ft)
198 + (1/32)*(l' + r + fl + fr)
199 + (1/96)*(lt + rt + flt + frt)
200
201 coefficient 0 2 1 0 =
202 (13/48)*(i' + f) + (17/192)*(l' + t' + fl + ft)
203 + (1/96)*(lt + flt)
204 + (1/64)*(r + d + fr + fd)
205 + (1/192)*(rt + ld + frt + fld)
206
207 coefficient 0 2 0 1 =
208 (13/48)*(i' + f) + (17/192)*(r + t' + fr + ft)
209 + (1/96)*(rt + frt)
210 + (1/64)*(l' + d + fl + fd)
211 + (1/192)*(rd + lt + flt + frd)
212
213 coefficient 0 3 0 0 =
214 (13/48)*(i' + f) + (5/96)*(l' + r + t' + d + fl + fr + ft + fd)
215 + (1/192)*(rt + rd + lt + ld + frt + frd + flt + fld)
216
217 coefficient 1 0 2 0 =
218 (1/4)*i' + (1/6)*(f + l' + t')
219 + (1/12)*(lt + fl + ft)
220
221 coefficient 1 0 0 2 =
222 (1/4)*i' + (1/6)*(f + r + t')
223 + (1/12)*(rt + fr + ft)
224
225 coefficient 1 0 1 1 =
226 (1/3)*i' + (5/24)*(f + t')
227 + (1/12)*ft
228 + (1/24)*(l' + r)
229 + (1/48)*(lt + rt + fl + fr)
230
231 coefficient 1 1 1 0 =
232 (1/3)*i' + (5/24)*f
233 + (1/8)*(l' + t')
234 + (5/96)*(fl + ft)
235 + (1/48)*(d + r + lt)
236 + (1/96)*(fd + ld + rt + fr)
237
238 coefficient 1 1 0 1 =
239 (1/3)*i' + (5/24)*f
240 + (1/8)*(r + t')
241 + (5/96)*(fr + ft)
242 + (1/48)*(d + l' + rt)
243 + (1/96)*(fd + lt + rd + fl)
244
245 coefficient 1 2 0 0 =
246 (1/3)*i' + (5/24)*f
247 + (7/96)*(l' + r + t' + d)
248 + (1/32)*(fl + fr + ft + fd)
249 + (1/96)*(rt + rd + lt + ld)
250
251 coefficient 2 0 1 0 =
252 (3/8)*i' + (7/48)*(f + t' + l')
253 + (1/48)*(r + d + b + lt + fl + ft)
254 + (1/96)*(rt + bt + fr + fd + ld + bl)
255
256 coefficient 2 0 0 1 =
257 (3/8)*i' + (7/48)*(f + t' + r)
258 + (1/48)*(l' + d + b + rt + fr + ft)
259 + (1/96)*(lt + bt + fl + fd + rd + br)
260
261 coefficient 2 1 0 0 =
262 (3/8)*i' + (1/12)*(t' + r + l' + d)
263 + (1/64)*(ft + fr + fl + fd)
264 + (7/48)*f
265 + (1/48)*b
266 + (1/96)*(rt + ld + lt + rd)
267 + (1/192)*(bt + br + bl + bd)
268
269 coefficient 3 0 0 0 =
270 (3/8)*i' + (1/12)*(t' + f + l' + r + d + b)
271 + (1/96)*(lt + fl + ft + rt + bt + fr)
272 + (1/96)*(fd + ld + bd + br + rd + bl)
273
274 coefficient _ _ _ _ = error "coefficient index out of bounds"
275
276
277
278 -- | Compute the determinant of the 4x4 matrix,
279 --
280 -- [1]
281 -- [x]
282 -- [y]
283 -- [z]
284 --
285 -- where [1] = [1, 1, 1, 1],
286 -- [x] = [x1,x2,x3,x4],
287 --
288 -- et cetera.
289 --
290 -- The termX nonsense is an attempt to prevent Double overflow.
291 -- which has been observed to happen with large coordinates.
292 --
293 det :: Point -> Point -> Point -> Point -> Double
294 det p0 p1 p2 p3 =
295 term5 + term6
296 where
297 Point x1 y1 z1 = p0
298 Point x2 y2 z2 = p1
299 Point x3 y3 z3 = p2
300 Point x4 y4 z4 = p3
301 term1 = ((x2 - x4)*y1 - (x1 - x4)*y2 + (x1 - x2)*y4)*z3
302 term2 = ((x2 - x3)*y1 - (x1 - x3)*y2 + (x1 - x2)*y3)*z4
303 term3 = ((x3 - x4)*y2 - (x2 - x4)*y3 + (x2 - x3)*y4)*z1
304 term4 = ((x3 - x4)*y1 - (x1 - x4)*y3 + (x1 - x3)*y4)*z2
305 term5 = term1 - term2
306 term6 = term3 - term4
307
308
309 -- | Computed using the formula from Lai & Schumaker, Definition 15.4,
310 -- page 436.
311 {-# INLINE volume #-}
312 volume :: Tetrahedron -> Double
313 volume t
314 | v0' == v1' = 0
315 | v0' == v2' = 0
316 | v0' == v3' = 0
317 | v1' == v2' = 0
318 | v1' == v3' = 0
319 | v2' == v3' = 0
320 | otherwise = (1/6)*(det v0' v1' v2' v3')
321 where
322 v0' = v0 t
323 v1' = v1 t
324 v2' = v2 t
325 v3' = v3 t
326
327
328 -- | The barycentric coordinates of a point with respect to v0.
329 {-# INLINE b0 #-}
330 b0 :: Tetrahedron -> (RealFunction Point)
331 b0 t point = (volume inner_tetrahedron) / (precomputed_volume t)
332 where
333 inner_tetrahedron = t { v0 = point }
334
335
336 -- | The barycentric coordinates of a point with respect to v1.
337 {-# INLINE b1 #-}
338 b1 :: Tetrahedron -> (RealFunction Point)
339 b1 t point = (volume inner_tetrahedron) / (precomputed_volume t)
340 where
341 inner_tetrahedron = t { v1 = point }
342
343
344 -- | The barycentric coordinates of a point with respect to v2.
345 {-# INLINE b2 #-}
346 b2 :: Tetrahedron -> (RealFunction Point)
347 b2 t point = (volume inner_tetrahedron) / (precomputed_volume t)
348 where
349 inner_tetrahedron = t { v2 = point }
350
351
352 -- | The barycentric coordinates of a point with respect to v3.
353 {-# INLINE b3 #-}
354 b3 :: Tetrahedron -> (RealFunction Point)
355 b3 t point = (volume inner_tetrahedron) / (precomputed_volume t)
356 where
357 inner_tetrahedron = t { v3 = point }
358
359
360
361
362 -- Tests
363
364
365 -- | Check the volume of a particular tetrahedron (computed by hand)
366 -- and whether or not it contains a specific point chosen to be
367 -- outside of it. Its vertices are in clockwise order, so the volume
368 -- should be negative.
369 tetrahedron1_geometry_tests :: Test.Framework.Test
370 tetrahedron1_geometry_tests =
371 testGroup "tetrahedron1 geometry"
372 [ testCase "volume1" volume1,
373 testCase "doesn't contain point1" doesnt_contain_point1]
374 where
375 p0 = Point 0 (-0.5) 0
376 p1 = Point 0 0.5 0
377 p2 = Point 2 0 0
378 p3 = Point 1 0 1
379 t = Tetrahedron { v0 = p0,
380 v1 = p1,
381 v2 = p2,
382 v3 = p3,
383 function_values = empty_values,
384 precomputed_volume = 0 }
385
386 volume1 :: Assertion
387 volume1 =
388 assertEqual "volume is correct" True (vol ~= (-1/3))
389 where
390 vol = volume t
391
392 doesnt_contain_point1 :: Assertion
393 doesnt_contain_point1 =
394 assertEqual "doesn't contain an exterior point" False contained
395 where
396 exterior_point = Point 5 2 (-9.0212)
397 contained = contains_point t exterior_point
398
399
400 -- | Check the volume of a particular tetrahedron (computed by hand)
401 -- and whether or not it contains a specific point chosen to be
402 -- inside of it. Its vertices are in counter-clockwise order, so the
403 -- volume should be positive.
404 tetrahedron2_geometry_tests :: Test.Framework.Test
405 tetrahedron2_geometry_tests =
406 testGroup "tetrahedron2 geometry"
407 [ testCase "volume1" volume1,
408 testCase "contains point1" contains_point1]
409 where
410 p0 = Point 0 (-0.5) 0
411 p1 = Point 2 0 0
412 p2 = Point 0 0.5 0
413 p3 = Point 1 0 1
414 t = Tetrahedron { v0 = p0,
415 v1 = p1,
416 v2 = p2,
417 v3 = p3,
418 function_values = empty_values,
419 precomputed_volume = 0 }
420
421 volume1 :: Assertion
422 volume1 = assertEqual "volume1 is correct" True (vol ~= (1/3))
423 where
424 vol = volume t
425
426 contains_point1 :: Assertion
427 contains_point1 = assertEqual "contains an inner point" True contained
428 where
429 inner_point = Point 1 0 0.5
430 contained = contains_point t inner_point
431
432
433 -- | Ensure that tetrahedra do not contain a particular point chosen to
434 -- be outside of them.
435 containment_tests :: Test.Framework.Test
436 containment_tests =
437 testGroup "containment tests"
438 [ testCase "doesn't contain point2" doesnt_contain_point2,
439 testCase "doesn't contain point3" doesnt_contain_point3,
440 testCase "doesn't contain point4" doesnt_contain_point4,
441 testCase "doesn't contain point5" doesnt_contain_point5]
442 where
443 p2 = Point 0.5 0.5 1
444 p3 = Point 0.5 0.5 0.5
445 exterior_point = Point 0 0 0
446
447 doesnt_contain_point2 :: Assertion
448 doesnt_contain_point2 =
449 assertEqual "doesn't contain an exterior point" False contained
450 where
451 p0 = Point 0 1 1
452 p1 = Point 1 1 1
453 t = Tetrahedron { v0 = p0,
454 v1 = p1,
455 v2 = p2,
456 v3 = p3,
457 function_values = empty_values,
458 precomputed_volume = 0 }
459 contained = contains_point t exterior_point
460
461
462 doesnt_contain_point3 :: Assertion
463 doesnt_contain_point3 =
464 assertEqual "doesn't contain an exterior point" False contained
465 where
466 p0 = Point 1 1 1
467 p1 = Point 1 0 1
468 t = Tetrahedron { v0 = p0,
469 v1 = p1,
470 v2 = p2,
471 v3 = p3,
472 function_values = empty_values,
473 precomputed_volume = 0 }
474 contained = contains_point t exterior_point
475
476
477 doesnt_contain_point4 :: Assertion
478 doesnt_contain_point4 =
479 assertEqual "doesn't contain an exterior point" False contained
480 where
481 p0 = Point 1 0 1
482 p1 = Point 0 0 1
483 t = Tetrahedron { v0 = p0,
484 v1 = p1,
485 v2 = p2,
486 v3 = p3,
487 function_values = empty_values,
488 precomputed_volume = 0 }
489 contained = contains_point t exterior_point
490
491
492 doesnt_contain_point5 :: Assertion
493 doesnt_contain_point5 =
494 assertEqual "doesn't contain an exterior point" False contained
495 where
496 p0 = Point 0 0 1
497 p1 = Point 0 1 1
498 t = Tetrahedron { v0 = p0,
499 v1 = p1,
500 v2 = p2,
501 v3 = p3,
502 function_values = empty_values,
503 precomputed_volume = 0 }
504 contained = contains_point t exterior_point
505
506
507 -- | The barycentric coordinate of v0 with respect to itself should
508 -- be one.
509 prop_b0_v0_always_unity :: Tetrahedron -> Property
510 prop_b0_v0_always_unity t =
511 (volume t) > 0 ==> (b0 t) (v0 t) ~= 1.0
512
513 -- | The barycentric coordinate of v1 with respect to v0 should
514 -- be zero.
515 prop_b0_v1_always_zero :: Tetrahedron -> Property
516 prop_b0_v1_always_zero t =
517 (volume t) > 0 ==> (b0 t) (v1 t) ~= 0
518
519 -- | The barycentric coordinate of v2 with respect to v0 should
520 -- be zero.
521 prop_b0_v2_always_zero :: Tetrahedron -> Property
522 prop_b0_v2_always_zero t =
523 (volume t) > 0 ==> (b0 t) (v2 t) ~= 0
524
525 -- | The barycentric coordinate of v3 with respect to v0 should
526 -- be zero.
527 prop_b0_v3_always_zero :: Tetrahedron -> Property
528 prop_b0_v3_always_zero t =
529 (volume t) > 0 ==> (b0 t) (v3 t) ~= 0
530
531 -- | The barycentric coordinate of v1 with respect to itself should
532 -- be one.
533 prop_b1_v1_always_unity :: Tetrahedron -> Property
534 prop_b1_v1_always_unity t =
535 (volume t) > 0 ==> (b1 t) (v1 t) ~= 1.0
536
537 -- | The barycentric coordinate of v0 with respect to v1 should
538 -- be zero.
539 prop_b1_v0_always_zero :: Tetrahedron -> Property
540 prop_b1_v0_always_zero t =
541 (volume t) > 0 ==> (b1 t) (v0 t) ~= 0
542
543 -- | The barycentric coordinate of v2 with respect to v1 should
544 -- be zero.
545 prop_b1_v2_always_zero :: Tetrahedron -> Property
546 prop_b1_v2_always_zero t =
547 (volume t) > 0 ==> (b1 t) (v2 t) ~= 0
548
549 -- | The barycentric coordinate of v3 with respect to v1 should
550 -- be zero.
551 prop_b1_v3_always_zero :: Tetrahedron -> Property
552 prop_b1_v3_always_zero t =
553 (volume t) > 0 ==> (b1 t) (v3 t) ~= 0
554
555 -- | The barycentric coordinate of v2 with respect to itself should
556 -- be one.
557 prop_b2_v2_always_unity :: Tetrahedron -> Property
558 prop_b2_v2_always_unity t =
559 (volume t) > 0 ==> (b2 t) (v2 t) ~= 1.0
560
561 -- | The barycentric coordinate of v0 with respect to v2 should
562 -- be zero.
563 prop_b2_v0_always_zero :: Tetrahedron -> Property
564 prop_b2_v0_always_zero t =
565 (volume t) > 0 ==> (b2 t) (v0 t) ~= 0
566
567 -- | The barycentric coordinate of v1 with respect to v2 should
568 -- be zero.
569 prop_b2_v1_always_zero :: Tetrahedron -> Property
570 prop_b2_v1_always_zero t =
571 (volume t) > 0 ==> (b2 t) (v1 t) ~= 0
572
573 -- | The barycentric coordinate of v3 with respect to v2 should
574 -- be zero.
575 prop_b2_v3_always_zero :: Tetrahedron -> Property
576 prop_b2_v3_always_zero t =
577 (volume t) > 0 ==> (b2 t) (v3 t) ~= 0
578
579 -- | The barycentric coordinate of v3 with respect to itself should
580 -- be one.
581 prop_b3_v3_always_unity :: Tetrahedron -> Property
582 prop_b3_v3_always_unity t =
583 (volume t) > 0 ==> (b3 t) (v3 t) ~= 1.0
584
585 -- | The barycentric coordinate of v0 with respect to v3 should
586 -- be zero.
587 prop_b3_v0_always_zero :: Tetrahedron -> Property
588 prop_b3_v0_always_zero t =
589 (volume t) > 0 ==> (b3 t) (v0 t) ~= 0
590
591 -- | The barycentric coordinate of v1 with respect to v3 should
592 -- be zero.
593 prop_b3_v1_always_zero :: Tetrahedron -> Property
594 prop_b3_v1_always_zero t =
595 (volume t) > 0 ==> (b3 t) (v1 t) ~= 0
596
597 -- | The barycentric coordinate of v2 with respect to v3 should
598 -- be zero.
599 prop_b3_v2_always_zero :: Tetrahedron -> Property
600 prop_b3_v2_always_zero t =
601 (volume t) > 0 ==> (b3 t) (v2 t) ~= 0
602
603
604 prop_swapping_vertices_doesnt_affect_coefficients1 :: Tetrahedron -> Bool
605 prop_swapping_vertices_doesnt_affect_coefficients1 t =
606 c t 0 0 1 2 == c t' 0 0 1 2
607 where
608 t' = t { v0 = (v1 t), v1 = (v0 t) }
609
610 prop_swapping_vertices_doesnt_affect_coefficients2 :: Tetrahedron -> Bool
611 prop_swapping_vertices_doesnt_affect_coefficients2 t =
612 c t 0 1 1 1 == c t' 0 1 1 1
613 where
614 t' = t { v2 = (v3 t), v3 = (v2 t) }
615
616 prop_swapping_vertices_doesnt_affect_coefficients3 :: Tetrahedron -> Bool
617 prop_swapping_vertices_doesnt_affect_coefficients3 t =
618 c t 2 1 0 0 == c t' 2 1 0 0
619 where
620 t' = t { v2 = (v3 t), v3 = (v2 t) }
621
622 prop_swapping_vertices_doesnt_affect_coefficients4 :: Tetrahedron -> Bool
623 prop_swapping_vertices_doesnt_affect_coefficients4 t =
624 c t 2 0 0 1 == c t' 2 0 0 1
625 where
626 t' = t { v0 = (v3 t), v3 = (v0 t) }
627
628
629
630
631 tetrahedron_tests :: Test.Framework.Test
632 tetrahedron_tests =
633 testGroup "Tetrahedron Tests" [
634 tetrahedron1_geometry_tests,
635 tetrahedron2_geometry_tests,
636 containment_tests ]
637
638
639
640 p78_24_properties :: Test.Framework.Test
641 p78_24_properties =
642 testGroup "p. 78, Section (2.4) Properties" [
643 testProperty "c3000 identity" prop_c3000_identity,
644 testProperty "c2100 identity" prop_c2100_identity,
645 testProperty "c1110 identity" prop_c1110_identity]
646 where
647 -- | Returns the domain point of t with indices i,j,k,l.
648 domain_point :: Tetrahedron -> Int -> Int -> Int -> Int -> Point
649 domain_point t i j k l
650 | i + j + k + l == 3 = weighted_sum `scale` (1/3)
651 | otherwise = error "domain point index out of bounds"
652 where
653 v0' = (v0 t) `scale` (fromIntegral i)
654 v1' = (v1 t) `scale` (fromIntegral j)
655 v2' = (v2 t) `scale` (fromIntegral k)
656 v3' = (v3 t) `scale` (fromIntegral l)
657 weighted_sum = v0' + v1' + v2' + v3'
658
659
660 -- | Used for convenience in the next few tests.
661 p :: Tetrahedron -> Int -> Int -> Int -> Int -> Double
662 p t i j k l = (polynomial t) (domain_point t i j k l)
663
664
665 -- | Given in Sorokina and Zeilfelder, p. 78.
666 prop_c3000_identity :: Tetrahedron -> Property
667 prop_c3000_identity t =
668 (volume t) > 0 ==>
669 c t 3 0 0 0 ~= p t 3 0 0 0
670
671 -- | Given in Sorokina and Zeilfelder, p. 78.
672 prop_c2100_identity :: Tetrahedron -> Property
673 prop_c2100_identity t =
674 (volume t) > 0 ==>
675 c t 2 1 0 0 ~= (term1 - term2 + term3 - term4)
676 where
677 term1 = (1/3)*(p t 0 3 0 0)
678 term2 = (5/6)*(p t 3 0 0 0)
679 term3 = 3*(p t 2 1 0 0)
680 term4 = (3/2)*(p t 1 2 0 0)
681
682 -- | Given in Sorokina and Zeilfelder, p. 78.
683 prop_c1110_identity :: Tetrahedron -> Property
684 prop_c1110_identity t =
685 (volume t) > 0 ==>
686 c t 1 1 1 0 ~= (term1 + term2 - term3 - term4)
687 where
688 term1 = (1/3)*((p t 3 0 0 0) + (p t 0 3 0 0) + (p t 0 0 3 0))
689 term2 = (9/2)*(p t 1 1 1 0)
690 term3 = (3/4)*((p t 2 1 0 0) + (p t 1 2 0 0) + (p t 2 0 1 0))
691 term4 = (3/4)*((p t 1 0 2 0) + (p t 0 2 1 0) + (p t 0 1 2 0))
692
693
694
695 tetrahedron_properties :: Test.Framework.Test
696 tetrahedron_properties =
697 testGroup "Tetrahedron Properties" [
698 p78_24_properties,
699 testProperty "b0_v0_always_unity" prop_b0_v0_always_unity,
700 testProperty "b0_v1_always_zero" prop_b0_v1_always_zero,
701 testProperty "b0_v2_always_zero" prop_b0_v2_always_zero,
702 testProperty "b0_v3_always_zero" prop_b0_v3_always_zero,
703 testProperty "b1_v1_always_unity" prop_b1_v1_always_unity,
704 testProperty "b1_v0_always_zero" prop_b1_v0_always_zero,
705 testProperty "b1_v2_always_zero" prop_b1_v2_always_zero,
706 testProperty "b1_v3_always_zero" prop_b1_v3_always_zero,
707 testProperty "b2_v2_always_unity" prop_b2_v2_always_unity,
708 testProperty "b2_v0_always_zero" prop_b2_v0_always_zero,
709 testProperty "b2_v1_always_zero" prop_b2_v1_always_zero,
710 testProperty "b2_v3_always_zero" prop_b2_v3_always_zero,
711 testProperty "b3_v3_always_unity" prop_b3_v3_always_unity,
712 testProperty "b3_v0_always_zero" prop_b3_v0_always_zero,
713 testProperty "b3_v1_always_zero" prop_b3_v1_always_zero,
714 testProperty "b3_v2_always_zero" prop_b3_v2_always_zero,
715 testProperty "swapping_vertices_doesnt_affect_coefficients1" $
716 prop_swapping_vertices_doesnt_affect_coefficients1,
717 testProperty "swapping_vertices_doesnt_affect_coefficients2" $
718 prop_swapping_vertices_doesnt_affect_coefficients2,
719 testProperty "swapping_vertices_doesnt_affect_coefficients3" $
720 prop_swapping_vertices_doesnt_affect_coefficients3,
721 testProperty "swapping_vertices_doesnt_affect_coefficients4" $
722 prop_swapping_vertices_doesnt_affect_coefficients4 ]