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