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