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