1 -- The local "coefficient" function defined within the "c" function
2 -- pattern matches on a bunch of integers, but doesn't handle the
3 -- "otherwise" case for performance reasons.
4 {-# OPTIONS_GHC -Wno-incomplete-patterns #-}
5 {-# LANGUAGE BangPatterns #-}
16 tetrahedron_properties,
21 import Data.Vector ( singleton, snoc )
22 import qualified Data.Vector as V ( sum )
23 import Test.Tasty ( TestTree, testGroup )
24 import Test.Tasty.HUnit ( Assertion, assertEqual, testCase )
25 import Test.Tasty.QuickCheck (
26 Arbitrary( arbitrary ),
32 import Comparisons ( (~=) )
33 import FunctionValues (
34 FunctionValues( front, back, left, right, top, down, front_left,
35 front_right, front_down, front_top, back_left, back_right,
36 back_down, back_top, left_down, left_top, right_down,
37 right_top, front_left_down, front_left_top,
38 front_right_down, front_right_top, interior ),
40 import Misc ( factorial )
41 import Point ( Point(Point), scale )
42 import RealFunction ( RealFunction, cmult, fexp )
45 Tetrahedron { function_values :: FunctionValues,
50 precomputed_volume :: !Double
55 instance Arbitrary Tetrahedron where
57 rnd_v0 <- arbitrary :: Gen Point
58 rnd_v1 <- arbitrary :: Gen Point
59 rnd_v2 <- arbitrary :: Gen Point
60 rnd_v3 <- arbitrary :: Gen Point
61 rnd_fv <- arbitrary :: Gen FunctionValues
63 -- We can't assign an incorrect precomputed volume,
64 -- so we have to calculate the correct one here.
65 let t' = Tetrahedron rnd_fv rnd_v0 rnd_v1 rnd_v2 rnd_v3 0
67 return (Tetrahedron rnd_fv rnd_v0 rnd_v1 rnd_v2 rnd_v3 vol)
70 instance Show Tetrahedron where
71 show t = "Tetrahedron:\n" ++
72 " function_values: " ++ (show (function_values t)) ++ "\n" ++
73 " v0: " ++ (show (v0 t)) ++ "\n" ++
74 " v1: " ++ (show (v1 t)) ++ "\n" ++
75 " v2: " ++ (show (v2 t)) ++ "\n" ++
76 " v3: " ++ (show (v3 t)) ++ "\n"
79 -- | Find the barycenter of the given tetrahedron.
80 -- We just average the four vertices.
81 barycenter :: Tetrahedron -> Point
82 barycenter (Tetrahedron _ v0' v1' v2' v3' _) =
83 (v0' + v1' + v2' + v3') `scale` (1/4)
87 {-# INLINE polynomial #-}
88 polynomial :: Tetrahedron -> (RealFunction Point)
90 V.sum $ singleton ((c t 0 0 0 3) `cmult` (beta t 0 0 0 3)) `snoc`
91 ((c t 0 0 1 2) `cmult` (beta t 0 0 1 2)) `snoc`
92 ((c t 0 0 2 1) `cmult` (beta t 0 0 2 1)) `snoc`
93 ((c t 0 0 3 0) `cmult` (beta t 0 0 3 0)) `snoc`
94 ((c t 0 1 0 2) `cmult` (beta t 0 1 0 2)) `snoc`
95 ((c t 0 1 1 1) `cmult` (beta t 0 1 1 1)) `snoc`
96 ((c t 0 1 2 0) `cmult` (beta t 0 1 2 0)) `snoc`
97 ((c t 0 2 0 1) `cmult` (beta t 0 2 0 1)) `snoc`
98 ((c t 0 2 1 0) `cmult` (beta t 0 2 1 0)) `snoc`
99 ((c t 0 3 0 0) `cmult` (beta t 0 3 0 0)) `snoc`
100 ((c t 1 0 0 2) `cmult` (beta t 1 0 0 2)) `snoc`
101 ((c t 1 0 1 1) `cmult` (beta t 1 0 1 1)) `snoc`
102 ((c t 1 0 2 0) `cmult` (beta t 1 0 2 0)) `snoc`
103 ((c t 1 1 0 1) `cmult` (beta t 1 1 0 1)) `snoc`
104 ((c t 1 1 1 0) `cmult` (beta t 1 1 1 0)) `snoc`
105 ((c t 1 2 0 0) `cmult` (beta t 1 2 0 0)) `snoc`
106 ((c t 2 0 0 1) `cmult` (beta t 2 0 0 1)) `snoc`
107 ((c t 2 0 1 0) `cmult` (beta t 2 0 1 0)) `snoc`
108 ((c t 2 1 0 0) `cmult` (beta t 2 1 0 0)) `snoc`
109 ((c t 3 0 0 0) `cmult` (beta t 3 0 0 0))
113 -- | The Bernstein polynomial on t with indices i,j,k,l. Denoted by a
114 -- capital 'B' in the Sorokina/Zeilfelder paper.
115 beta :: Tetrahedron -> Int -> Int -> Int -> Int -> (RealFunction Point)
117 coefficient `cmult` (b0_term * b1_term * b2_term * b3_term)
119 denominator = (factorial i)*(factorial j)*(factorial k)*(factorial l)
120 coefficient = (6 / (fromIntegral denominator)) :: Double
121 b0_term = (b0 t) `fexp` i
122 b1_term = (b1 t) `fexp` j
123 b2_term = (b2 t) `fexp` k
124 b3_term = (b3 t) `fexp` l
127 -- | The coefficient function. c t i j k l returns the coefficient
128 -- c_ijkl with respect to the tetrahedron t. The definition uses
129 -- pattern matching to mimic the definitions given in Sorokina and
130 -- Zeilfelder, pp. 84-86. If incorrect indices are supplied, the world
131 -- will end. This is for performance reasons.
132 c :: Tetrahedron -> Int -> Int -> Int -> Int -> Double
136 fvs = function_values t
155 fld = front_left_down fvs
156 flt = front_left_top fvs
157 frd = front_right_down fvs
158 frt = front_right_top fvs
161 coefficient :: Int -> Int -> Int -> Int -> Double
162 coefficient 0 0 3 0 =
163 (1/8) * (i' + f + l' + t' + lt + fl + ft + flt)
165 coefficient 0 0 0 3 =
166 (1/8) * (i' + f + r + t' + rt + fr + ft + frt)
168 coefficient 0 0 2 1 =
169 (5/24)*(i' + f + t' + ft) + (1/24)*(l' + fl + lt + flt)
171 coefficient 0 0 1 2 =
172 (5/24)*(i' + f + t' + ft) + (1/24)*(r + fr + rt + frt)
174 coefficient 0 1 2 0 =
175 (5/24)*(i' + f) + (1/8)*(l' + t' + fl + ft)
178 coefficient 0 1 0 2 =
179 (5/24)*(i' + f) + (1/8)*(r + t' + fr + ft)
182 coefficient 0 1 1 1 =
183 (13/48)*(i' + f) + (7/48)*(t' + ft)
184 + (1/32)*(l' + r + fl + fr)
185 + (1/96)*(lt + rt + flt + frt)
187 coefficient 0 2 1 0 =
188 (13/48)*(i' + f) + (17/192)*(l' + t' + fl + ft)
190 + (1/64)*(r + d + fr + fd)
191 + (1/192)*(rt + ld + frt + fld)
193 coefficient 0 2 0 1 =
194 (13/48)*(i' + f) + (17/192)*(r + t' + fr + ft)
196 + (1/64)*(l' + d + fl + fd)
197 + (1/192)*(rd + lt + flt + frd)
199 coefficient 0 3 0 0 =
200 (13/48)*(i' + f) + (5/96)*(l' + r + t' + d + fl + fr + ft + fd)
201 + (1/192)*(rt + rd + lt + ld + frt + frd + flt + fld)
203 coefficient 1 0 2 0 =
204 (1/4)*i' + (1/6)*(f + l' + t')
205 + (1/12)*(lt + fl + ft)
207 coefficient 1 0 0 2 =
208 (1/4)*i' + (1/6)*(f + r + t')
209 + (1/12)*(rt + fr + ft)
211 coefficient 1 0 1 1 =
212 (1/3)*i' + (5/24)*(f + t')
215 + (1/48)*(lt + rt + fl + fr)
217 coefficient 1 1 1 0 =
221 + (1/48)*(d + r + lt)
222 + (1/96)*(fd + ld + rt + fr)
224 coefficient 1 1 0 1 =
228 + (1/48)*(d + l' + rt)
229 + (1/96)*(fd + lt + rd + fl)
231 coefficient 1 2 0 0 =
233 + (7/96)*(l' + r + t' + d)
234 + (1/32)*(fl + fr + ft + fd)
235 + (1/96)*(rt + rd + lt + ld)
237 coefficient 2 0 1 0 =
238 (3/8)*i' + (7/48)*(f + t' + l')
239 + (1/48)*(r + d + b + lt + fl + ft)
240 + (1/96)*(rt + bt + fr + fd + ld + bl)
242 coefficient 2 0 0 1 =
243 (3/8)*i' + (7/48)*(f + t' + r)
244 + (1/48)*(l' + d + b + rt + fr + ft)
245 + (1/96)*(lt + bt + fl + fd + rd + br)
247 coefficient 2 1 0 0 =
248 (3/8)*i' + (1/12)*(t' + r + l' + d)
249 + (1/64)*(ft + fr + fl + fd)
252 + (1/96)*(rt + ld + lt + rd)
253 + (1/192)*(bt + br + bl + bd)
255 coefficient 3 0 0 0 =
256 (3/8)*i' + (1/12)*(t' + f + l' + r + d + b)
257 + (1/96)*(lt + fl + ft + rt + bt + fr)
258 + (1/96)*(fd + ld + bd + br + rd + bl)
262 -- | Compute the determinant of the 4x4 matrix,
269 -- where [1] = [1, 1, 1, 1],
270 -- [x] = [x1,x2,x3,x4],
274 -- The termX nonsense is an attempt to prevent Double overflow.
275 -- which has been observed to happen with large coordinates.
277 det :: Point -> Point -> Point -> Point -> Double
285 term1 = ((x2 - x4)*y1 - (x1 - x4)*y2 + (x1 - x2)*y4)*z3
286 term2 = ((x2 - x3)*y1 - (x1 - x3)*y2 + (x1 - x2)*y3)*z4
287 term3 = ((x3 - x4)*y2 - (x2 - x4)*y3 + (x2 - x3)*y4)*z1
288 term4 = ((x3 - x4)*y1 - (x1 - x4)*y3 + (x1 - x3)*y4)*z2
289 term5 = term1 - term2
290 term6 = term3 - term4
293 -- | Computed using the formula from Lai & Schumaker, Definition 15.4,
295 {-# INLINE volume #-}
296 volume :: Tetrahedron -> Double
297 volume (Tetrahedron _ v0' v1' v2' v3' _) =
298 (1/6)*(det v0' v1' v2' v3')
300 -- | The barycentric coordinates of a point with respect to v0.
302 b0 :: Tetrahedron -> (RealFunction Point)
303 b0 t point = (volume inner_tetrahedron) / (precomputed_volume t)
305 inner_tetrahedron = t { v0 = point }
308 -- | The barycentric coordinates of a point with respect to v1.
310 b1 :: Tetrahedron -> (RealFunction Point)
311 b1 t point = (volume inner_tetrahedron) / (precomputed_volume t)
313 inner_tetrahedron = t { v1 = point }
316 -- | The barycentric coordinates of a point with respect to v2.
318 b2 :: Tetrahedron -> (RealFunction Point)
319 b2 t point = (volume inner_tetrahedron) / (precomputed_volume t)
321 inner_tetrahedron = t { v2 = point }
324 -- | The barycentric coordinates of a point with respect to v3.
326 b3 :: Tetrahedron -> (RealFunction Point)
327 b3 t point = (volume inner_tetrahedron) / (precomputed_volume t)
329 inner_tetrahedron = t { v3 = point }
334 -- | Check the volume of a particular tetrahedron (computed by hand)
335 -- Its vertices are in clockwise order, so the volume should be
337 tetrahedron1_geometry_tests :: TestTree
338 tetrahedron1_geometry_tests =
339 testGroup "tetrahedron1 geometry"
340 [ testCase "volume1" volume1 ]
342 p0 = Point 0 (-0.5) 0
346 t = Tetrahedron { v0 = p0,
350 function_values = empty_values,
351 precomputed_volume = 0 }
355 assertEqual "volume is correct" True (vol ~= (-1/3))
360 -- | Check the volume of a particular tetrahedron (computed by hand)
361 -- Its vertices are in counter-clockwise order, so the volume should
363 tetrahedron2_geometry_tests :: TestTree
364 tetrahedron2_geometry_tests =
365 testGroup "tetrahedron2 geometry"
366 [ testCase "volume1" volume1 ]
368 p0 = Point 0 (-0.5) 0
372 t = Tetrahedron { v0 = p0,
376 function_values = empty_values,
377 precomputed_volume = 0 }
380 volume1 = assertEqual "volume1 is correct" True (vol ~= (1/3))
386 -- | The barycentric coordinate of v0 with respect to itself should
388 prop_b0_v0_always_unity :: Tetrahedron -> Property
389 prop_b0_v0_always_unity t =
390 (volume t) > 0 ==> (b0 t) (v0 t) ~= 1.0
392 -- | The barycentric coordinate of v1 with respect to v0 should
394 prop_b0_v1_always_zero :: Tetrahedron -> Property
395 prop_b0_v1_always_zero t =
396 (volume t) > 0 ==> (b0 t) (v1 t) ~= 0
398 -- | The barycentric coordinate of v2 with respect to v0 should
400 prop_b0_v2_always_zero :: Tetrahedron -> Property
401 prop_b0_v2_always_zero t =
402 (volume t) > 0 ==> (b0 t) (v2 t) ~= 0
404 -- | The barycentric coordinate of v3 with respect to v0 should
406 prop_b0_v3_always_zero :: Tetrahedron -> Property
407 prop_b0_v3_always_zero t =
408 (volume t) > 0 ==> (b0 t) (v3 t) ~= 0
410 -- | The barycentric coordinate of v1 with respect to itself should
412 prop_b1_v1_always_unity :: Tetrahedron -> Property
413 prop_b1_v1_always_unity t =
414 (volume t) > 0 ==> (b1 t) (v1 t) ~= 1.0
416 -- | The barycentric coordinate of v0 with respect to v1 should
418 prop_b1_v0_always_zero :: Tetrahedron -> Property
419 prop_b1_v0_always_zero t =
420 (volume t) > 0 ==> (b1 t) (v0 t) ~= 0
422 -- | The barycentric coordinate of v2 with respect to v1 should
424 prop_b1_v2_always_zero :: Tetrahedron -> Property
425 prop_b1_v2_always_zero t =
426 (volume t) > 0 ==> (b1 t) (v2 t) ~= 0
428 -- | The barycentric coordinate of v3 with respect to v1 should
430 prop_b1_v3_always_zero :: Tetrahedron -> Property
431 prop_b1_v3_always_zero t =
432 (volume t) > 0 ==> (b1 t) (v3 t) ~= 0
434 -- | The barycentric coordinate of v2 with respect to itself should
436 prop_b2_v2_always_unity :: Tetrahedron -> Property
437 prop_b2_v2_always_unity t =
438 (volume t) > 0 ==> (b2 t) (v2 t) ~= 1.0
440 -- | The barycentric coordinate of v0 with respect to v2 should
442 prop_b2_v0_always_zero :: Tetrahedron -> Property
443 prop_b2_v0_always_zero t =
444 (volume t) > 0 ==> (b2 t) (v0 t) ~= 0
446 -- | The barycentric coordinate of v1 with respect to v2 should
448 prop_b2_v1_always_zero :: Tetrahedron -> Property
449 prop_b2_v1_always_zero t =
450 (volume t) > 0 ==> (b2 t) (v1 t) ~= 0
452 -- | The barycentric coordinate of v3 with respect to v2 should
454 prop_b2_v3_always_zero :: Tetrahedron -> Property
455 prop_b2_v3_always_zero t =
456 (volume t) > 0 ==> (b2 t) (v3 t) ~= 0
458 -- | The barycentric coordinate of v3 with respect to itself should
460 prop_b3_v3_always_unity :: Tetrahedron -> Property
461 prop_b3_v3_always_unity t =
462 (volume t) > 0 ==> (b3 t) (v3 t) ~= 1.0
464 -- | The barycentric coordinate of v0 with respect to v3 should
466 prop_b3_v0_always_zero :: Tetrahedron -> Property
467 prop_b3_v0_always_zero t =
468 (volume t) > 0 ==> (b3 t) (v0 t) ~= 0
470 -- | The barycentric coordinate of v1 with respect to v3 should
472 prop_b3_v1_always_zero :: Tetrahedron -> Property
473 prop_b3_v1_always_zero t =
474 (volume t) > 0 ==> (b3 t) (v1 t) ~= 0
476 -- | The barycentric coordinate of v2 with respect to v3 should
478 prop_b3_v2_always_zero :: Tetrahedron -> Property
479 prop_b3_v2_always_zero t =
480 (volume t) > 0 ==> (b3 t) (v2 t) ~= 0
483 prop_swapping_vertices_doesnt_affect_coefficients1 :: Tetrahedron -> Bool
484 prop_swapping_vertices_doesnt_affect_coefficients1 t =
485 c t 0 0 1 2 == c t' 0 0 1 2
487 t' = t { v0 = (v1 t), v1 = (v0 t) }
489 prop_swapping_vertices_doesnt_affect_coefficients2 :: Tetrahedron -> Bool
490 prop_swapping_vertices_doesnt_affect_coefficients2 t =
491 c t 0 1 1 1 == c t' 0 1 1 1
493 t' = t { v2 = (v3 t), v3 = (v2 t) }
495 prop_swapping_vertices_doesnt_affect_coefficients3 :: Tetrahedron -> Bool
496 prop_swapping_vertices_doesnt_affect_coefficients3 t =
497 c t 2 1 0 0 == c t' 2 1 0 0
499 t' = t { v2 = (v3 t), v3 = (v2 t) }
501 prop_swapping_vertices_doesnt_affect_coefficients4 :: Tetrahedron -> Bool
502 prop_swapping_vertices_doesnt_affect_coefficients4 t =
503 c t 2 0 0 1 == c t' 2 0 0 1
505 t' = t { v0 = (v3 t), v3 = (v0 t) }
510 tetrahedron_tests :: TestTree
512 testGroup "Tetrahedron tests" [
513 tetrahedron1_geometry_tests,
514 tetrahedron2_geometry_tests ]
518 p78_24_properties :: TestTree
520 testGroup "p. 78, Section (2.4) properties" [
521 testProperty "c3000 identity" prop_c3000_identity,
522 testProperty "c2100 identity" prop_c2100_identity,
523 testProperty "c1110 identity" prop_c1110_identity]
525 -- | Returns the domain point of t with indices i,j,k,l.
526 domain_point :: Tetrahedron -> Int -> Int -> Int -> Int -> Point
527 domain_point t i j k l =
528 weighted_sum `scale` (1/3)
530 v0' = (v0 t) `scale` (fromIntegral i)
531 v1' = (v1 t) `scale` (fromIntegral j)
532 v2' = (v2 t) `scale` (fromIntegral k)
533 v3' = (v3 t) `scale` (fromIntegral l)
534 weighted_sum = v0' + v1' + v2' + v3'
537 -- | Used for convenience in the next few tests.
538 p :: Tetrahedron -> Int -> Int -> Int -> Int -> Double
539 p t i j k l = (polynomial t) (domain_point t i j k l)
542 -- | Given in Sorokina and Zeilfelder, p. 78.
543 prop_c3000_identity :: Tetrahedron -> Property
544 prop_c3000_identity t =
546 c t 3 0 0 0 ~= p t 3 0 0 0
548 -- | Given in Sorokina and Zeilfelder, p. 78.
549 prop_c2100_identity :: Tetrahedron -> Property
550 prop_c2100_identity t =
552 c t 2 1 0 0 ~= (term1 - term2 + term3 - term4)
554 term1 = (1/3)*(p t 0 3 0 0)
555 term2 = (5/6)*(p t 3 0 0 0)
556 term3 = 3*(p t 2 1 0 0)
557 term4 = (3/2)*(p t 1 2 0 0)
559 -- | Given in Sorokina and Zeilfelder, p. 78.
560 prop_c1110_identity :: Tetrahedron -> Property
561 prop_c1110_identity t =
563 c t 1 1 1 0 ~= (term1 + term2 - term3 - term4)
565 term1 = (1/3)*((p t 3 0 0 0) + (p t 0 3 0 0) + (p t 0 0 3 0))
566 term2 = (9/2)*(p t 1 1 1 0)
567 term3 = (3/4)*((p t 2 1 0 0) + (p t 1 2 0 0) + (p t 2 0 1 0))
568 term4 = (3/4)*((p t 1 0 2 0) + (p t 0 2 1 0) + (p t 0 1 2 0))
572 tetrahedron_properties :: TestTree
573 tetrahedron_properties =
574 testGroup "Tetrahedron properties" [
576 testProperty "b0_v0_always_unity" prop_b0_v0_always_unity,
577 testProperty "b0_v1_always_zero" prop_b0_v1_always_zero,
578 testProperty "b0_v2_always_zero" prop_b0_v2_always_zero,
579 testProperty "b0_v3_always_zero" prop_b0_v3_always_zero,
580 testProperty "b1_v1_always_unity" prop_b1_v1_always_unity,
581 testProperty "b1_v0_always_zero" prop_b1_v0_always_zero,
582 testProperty "b1_v2_always_zero" prop_b1_v2_always_zero,
583 testProperty "b1_v3_always_zero" prop_b1_v3_always_zero,
584 testProperty "b2_v2_always_unity" prop_b2_v2_always_unity,
585 testProperty "b2_v0_always_zero" prop_b2_v0_always_zero,
586 testProperty "b2_v1_always_zero" prop_b2_v1_always_zero,
587 testProperty "b2_v3_always_zero" prop_b2_v3_always_zero,
588 testProperty "b3_v3_always_unity" prop_b3_v3_always_unity,
589 testProperty "b3_v0_always_zero" prop_b3_v0_always_zero,
590 testProperty "b3_v1_always_zero" prop_b3_v1_always_zero,
591 testProperty "b3_v2_always_zero" prop_b3_v2_always_zero,
592 testProperty "swapping_vertices_doesnt_affect_coefficients1"
593 prop_swapping_vertices_doesnt_affect_coefficients1,
594 testProperty "swapping_vertices_doesnt_affect_coefficients2"
595 prop_swapping_vertices_doesnt_affect_coefficients2,
596 testProperty "swapping_vertices_doesnt_affect_coefficients3"
597 prop_swapping_vertices_doesnt_affect_coefficients3,
598 testProperty "swapping_vertices_doesnt_affect_coefficients4"
599 prop_swapping_vertices_doesnt_affect_coefficients4 ]