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