]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Tests/Cube.hs
Add tests for some functions used in the new 'find_containing_tetrahedron'.
[spline3.git] / src / Tests / Cube.hs
index e867e5d478364fb9073b9a6ec67bab82ff1940f7..0a1cc504179e9e0c7a79dae01c8ced961ac8b434 100644 (file)
@@ -2,257 +2,57 @@ module Tests.Cube
 where
 
 import Prelude hiding (LT)
 where
 
 import Prelude hiding (LT)
-import Test.QuickCheck
 
 import Cardinal
 import Comparisons
 
 import Cardinal
 import Comparisons
-import Cube
+import Cube hiding (i, j, k)
 import FunctionValues
 import FunctionValues
-import Misc (all_equal)
+import Misc (all_equal, disjoint)
 import Tests.FunctionValues ()
 import Tetrahedron (b0, b1, b2, b3, c, fv,
                     v0, v1, v2, v3, volume)
 
 import Tests.FunctionValues ()
 import Tetrahedron (b0, b1, b2, b3, c, fv,
                     v0, v1, v2, v3, volume)
 
-instance Arbitrary Cube where
-    arbitrary = do
-      (Positive h') <- arbitrary :: Gen (Positive Double)
-      i' <- choose (coordmin, coordmax)
-      j' <- choose (coordmin, coordmax)
-      k' <- choose (coordmin, coordmax)
-      fv' <- arbitrary :: Gen FunctionValues
-      return (Cube h' i' j' k' fv')
-        where
-          coordmin = -268435456 -- -(2^29 / 2)
-          coordmax = 268435456  -- +(2^29 / 2)
-
 
 -- Quickcheck tests.
 
 
 -- Quickcheck tests.
 
--- | Since the grid size is necessarily positive, all tetrahedrons
+-- | The 'front_half_tetrahedra' and 'back_half_tetrahedra' should
+--   have no tetrahedra in common.
+prop_front_back_tetrahedra_disjoint :: Cube -> Bool
+prop_front_back_tetrahedra_disjoint c =
+    disjoint (front_half_tetrahedra c) (back_half_tetrahedra c)
+
+
+-- | The 'top_half_tetrahedra' and 'down_half_tetrahedra' should
+--   have no tetrahedra in common.
+prop_top_down_tetrahedra_disjoint :: Cube -> Bool
+prop_top_down_tetrahedra_disjoint c =
+    disjoint (top_half_tetrahedra c) (down_half_tetrahedra c)
+
+
+-- | The 'left_half_tetrahedra' and 'right_half_tetrahedra' should
+--   have no tetrahedra in common.
+prop_left_right_tetrahedra_disjoint :: Cube -> Bool
+prop_left_right_tetrahedra_disjoint c =
+    disjoint (left_half_tetrahedra c) (right_half_tetrahedra c)
+
+
+-- | Since the grid size is necessarily positive, all tetrahedra
 --   (which comprise cubes of positive volume) must have positive volume
 --   as well.
 prop_all_volumes_positive :: Cube -> Bool
 prop_all_volumes_positive cube =
     null nonpositive_volumes
     where
 --   (which comprise cubes of positive volume) must have positive volume
 --   as well.
 prop_all_volumes_positive :: Cube -> Bool
 prop_all_volumes_positive cube =
     null nonpositive_volumes
     where
-      ts = tetrahedrons cube
+      ts = tetrahedra cube
       volumes = map volume ts
       nonpositive_volumes = filter (<= 0) volumes
 
 -- | In fact, since all of the tetrahedra are identical, we should
 --   already know their volumes. There's 24 tetrahedra to a cube, so
 --   we'd expect the volume of each one to be (1/24)*h^3.
       volumes = map volume ts
       nonpositive_volumes = filter (<= 0) volumes
 
 -- | In fact, since all of the tetrahedra are identical, we should
 --   already know their volumes. There's 24 tetrahedra to a cube, so
 --   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron0_volumes_exact :: Cube -> Bool
-prop_tetrahedron0_volumes_exact cube =
-    volume (tetrahedron0 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron1_volumes_exact :: Cube -> Bool
-prop_tetrahedron1_volumes_exact cube =
-    volume (tetrahedron1 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron2_volumes_exact :: Cube -> Bool
-prop_tetrahedron2_volumes_exact cube =
-    volume (tetrahedron2 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron3_volumes_exact :: Cube -> Bool
-prop_tetrahedron3_volumes_exact cube =
-    volume (tetrahedron3 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron4_volumes_exact :: Cube -> Bool
-prop_tetrahedron4_volumes_exact cube =
-    volume (tetrahedron4 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron5_volumes_exact :: Cube -> Bool
-prop_tetrahedron5_volumes_exact cube =
-    volume (tetrahedron5 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron6_volumes_exact :: Cube -> Bool
-prop_tetrahedron6_volumes_exact cube =
-    volume (tetrahedron6 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron7_volumes_exact :: Cube -> Bool
-prop_tetrahedron7_volumes_exact cube =
-    volume (tetrahedron7 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron8_volumes_exact :: Cube -> Bool
-prop_tetrahedron8_volumes_exact cube =
-    volume (tetrahedron8 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron9_volumes_exact :: Cube -> Bool
-prop_tetrahedron9_volumes_exact cube =
-    volume (tetrahedron9 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron10_volumes_exact :: Cube -> Bool
-prop_tetrahedron10_volumes_exact cube =
-    volume (tetrahedron10 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron11_volumes_exact :: Cube -> Bool
-prop_tetrahedron11_volumes_exact cube =
-    volume (tetrahedron11 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron12_volumes_exact :: Cube -> Bool
-prop_tetrahedron12_volumes_exact cube =
-    volume (tetrahedron12 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron13_volumes_exact :: Cube -> Bool
-prop_tetrahedron13_volumes_exact cube =
-    volume (tetrahedron13 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron14_volumes_exact :: Cube -> Bool
-prop_tetrahedron14_volumes_exact cube =
-    volume (tetrahedron14 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron15_volumes_exact :: Cube -> Bool
-prop_tetrahedron15_volumes_exact cube =
-    volume (tetrahedron15 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron16_volumes_exact :: Cube -> Bool
-prop_tetrahedron16_volumes_exact cube =
-    volume (tetrahedron16 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron17_volumes_exact :: Cube -> Bool
-prop_tetrahedron17_volumes_exact cube =
-    volume (tetrahedron17 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron18_volumes_exact :: Cube -> Bool
-prop_tetrahedron18_volumes_exact cube =
-    volume (tetrahedron18 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron19_volumes_exact :: Cube -> Bool
-prop_tetrahedron19_volumes_exact cube =
-    volume (tetrahedron19 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron20_volumes_exact :: Cube -> Bool
-prop_tetrahedron20_volumes_exact cube =
-    volume (tetrahedron20 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron21_volumes_exact :: Cube -> Bool
-prop_tetrahedron21_volumes_exact cube =
-    volume (tetrahedron21 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron22_volumes_exact :: Cube -> Bool
-prop_tetrahedron22_volumes_exact cube =
-    volume (tetrahedron22 cube) ~~= (1/24)*(delta^(3::Int))
-    where
-      delta = h cube
-
--- | In fact, since all of the tetrahedra are identical, we should
---   already know their volumes. There's 24 tetrahedra to a cube, so
---   we'd expect the volume of each one to be (1/24)*h^3.
-prop_tetrahedron23_volumes_exact :: Cube -> Bool
-prop_tetrahedron23_volumes_exact cube =
-    volume (tetrahedron23 cube) ~~= (1/24)*(delta^(3::Int))
+prop_all_volumes_exact :: Cube -> Bool
+prop_all_volumes_exact cube =
+    and [volume t ~~= (1/24)*(delta^(3::Int)) | t <- tetrahedra cube]
     where
       delta = h cube
 
     where
       delta = h cube
 
@@ -260,187 +60,46 @@ prop_tetrahedron23_volumes_exact cube =
 prop_v0_all_equal :: Cube -> Bool
 prop_v0_all_equal cube = (v0 t0) == (v0 t1)
     where
 prop_v0_all_equal :: Cube -> Bool
 prop_v0_all_equal cube = (v0 t0) == (v0 t1)
     where
-      t0 = head (tetrahedrons cube) -- Doesn't matter which two we choose.
-      t1 = head $ tail (tetrahedrons cube)
-
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron0_volumes_positive :: Cube -> Bool
-prop_tetrahedron0_volumes_positive cube =
-    volume (tetrahedron0 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron1_volumes_positive :: Cube -> Bool
-prop_tetrahedron1_volumes_positive cube =
-    volume (tetrahedron1 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron2_volumes_positive :: Cube -> Bool
-prop_tetrahedron2_volumes_positive cube =
-    volume (tetrahedron2 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron3_volumes_positive :: Cube -> Bool
-prop_tetrahedron3_volumes_positive cube =
-    volume (tetrahedron3 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron4_volumes_positive :: Cube -> Bool
-prop_tetrahedron4_volumes_positive cube =
-    volume (tetrahedron4 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron5_volumes_positive :: Cube -> Bool
-prop_tetrahedron5_volumes_positive cube =
-    volume (tetrahedron5 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron6_volumes_positive :: Cube -> Bool
-prop_tetrahedron6_volumes_positive cube =
-    volume (tetrahedron6 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron7_volumes_positive :: Cube -> Bool
-prop_tetrahedron7_volumes_positive cube =
-    volume (tetrahedron7 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron8_volumes_positive :: Cube -> Bool
-prop_tetrahedron8_volumes_positive cube =
-    volume (tetrahedron8 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron9_volumes_positive :: Cube -> Bool
-prop_tetrahedron9_volumes_positive cube =
-    volume (tetrahedron9 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron10_volumes_positive :: Cube -> Bool
-prop_tetrahedron10_volumes_positive cube =
-    volume (tetrahedron10 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron11_volumes_positive :: Cube -> Bool
-prop_tetrahedron11_volumes_positive cube =
-    volume (tetrahedron11 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron12_volumes_positive :: Cube -> Bool
-prop_tetrahedron12_volumes_positive cube =
-    volume (tetrahedron12 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron13_volumes_positive :: Cube -> Bool
-prop_tetrahedron13_volumes_positive cube =
-    volume (tetrahedron13 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron14_volumes_positive :: Cube -> Bool
-prop_tetrahedron14_volumes_positive cube =
-    volume (tetrahedron14 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron15_volumes_positive :: Cube -> Bool
-prop_tetrahedron15_volumes_positive cube =
-    volume (tetrahedron15 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron16_volumes_positive :: Cube -> Bool
-prop_tetrahedron16_volumes_positive cube =
-    volume (tetrahedron16 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron17_volumes_positive :: Cube -> Bool
-prop_tetrahedron17_volumes_positive cube =
-    volume (tetrahedron17 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron18_volumes_positive :: Cube -> Bool
-prop_tetrahedron18_volumes_positive cube =
-    volume (tetrahedron18 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron19_volumes_positive :: Cube -> Bool
-prop_tetrahedron19_volumes_positive cube =
-    volume (tetrahedron19 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron20_volumes_positive :: Cube -> Bool
-prop_tetrahedron20_volumes_positive cube =
-    volume (tetrahedron20 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron21_volumes_positive :: Cube -> Bool
-prop_tetrahedron21_volumes_positive cube =
-    volume (tetrahedron21 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron22_volumes_positive :: Cube -> Bool
-prop_tetrahedron22_volumes_positive cube =
-    volume (tetrahedron22 cube) > 0
-
--- | This pretty much repeats the prop_all_volumes_positive property,
---   but will let me know which tetrahedrons's vertices are disoriented.
-prop_tetrahedron23_volumes_positive :: Cube -> Bool
-prop_tetrahedron23_volumes_positive cube =
-    volume (tetrahedron23 cube) > 0
-
-
--- | Given in Sorokina and Zeilfelder, p. 79, (2.6). It appears that
---   the assumptions in sections (2.6) and (2.7) have been
---   switched. From the description, one would expect 'tetrahedron0'
---   and 'tetrahedron3' to share face \<v0,v1,v2\>; however, we have
---   to use 'tetrahedron0' and 'tetahedron1' for all of the tests in
---   section (2.6). Also note that the third and fourth indices of
---   c-t1 have been switched. This is because we store the triangles
---   oriented such that their volume is positive. If T and T-tilde
---   share \<v0,v1,v2\> and v3,v3-tilde point in opposite directions,
---   one of them has to have negative volume!
+      t0 = head (tetrahedra cube) -- Doesn't matter which two we choose.
+      t1 = head $ tail (tetrahedra cube)
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Note that the
+--   third and fourth indices of c-t1 have been switched. This is
+--   because we store the triangles oriented such that their volume is
+--   positive. If T and T-tilde share \<v0,v1,v2\> and v3,v3-tilde point
+--   in opposite directions, one of them has to have negative volume!
 prop_c0120_identity1 :: Cube -> Bool
 prop_c0120_identity1 cube =
 prop_c0120_identity1 :: Cube -> Bool
 prop_c0120_identity1 cube =
-   c t0 0 1 2 0 ~= (c t0 0 0 2 1 + c t1 0 0 1 2) / 2
+   c t0 0 1 2 0 ~= (c t0 0 0 2 1 + c t3 0 0 1 2) / 2
      where
        t0 = tetrahedron0 cube
      where
        t0 = tetrahedron0 cube
-       t1 = tetrahedron1 cube
+       t3 = tetrahedron3 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Repeats
 --   'prop_c0120_identity1' with tetrahedrons 1 and 2.
 prop_c0120_identity2 :: Cube -> Bool
 prop_c0120_identity2 cube =
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Repeats
 --   'prop_c0120_identity1' with tetrahedrons 1 and 2.
 prop_c0120_identity2 :: Cube -> Bool
 prop_c0120_identity2 cube =
-   c t1 0 1 2 0 ~= (c t1 0 0 2 1 + c t2 0 0 1 2) / 2
+   c t1 0 1 2 0 ~= (c t1 0 0 2 1 + c t0 0 0 1 2) / 2
+     where
+       t0 = tetrahedron0 cube
+       t1 = tetrahedron1 cube
+            
+-- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Repeats
+--   'prop_c0120_identity1' with tetrahedrons 1 and 2.
+prop_c0120_identity3 :: Cube -> Bool
+prop_c0120_identity3 cube =
+   c t2 0 1 2 0 ~= (c t2 0 0 2 1 + c t1 0 0 1 2) / 2
      where
        t1 = tetrahedron1 cube
        t2 = tetrahedron2 cube
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Repeats
 --   'prop_c0120_identity1' with tetrahedrons 2 and 3.
      where
        t1 = tetrahedron1 cube
        t2 = tetrahedron2 cube
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Repeats
 --   'prop_c0120_identity1' with tetrahedrons 2 and 3.
-prop_c0120_identity3 :: Cube -> Bool
-prop_c0120_identity3 cube =
-   c t2 0 1 2 0 ~= (c t2 0 0 2 1 + c t3 0 0 1 2) / 2
+prop_c0120_identity4 :: Cube -> Bool
+prop_c0120_identity4 cube =
+   c t3 0 1 2 0 ~= (c t3 0 0 2 1 + c t2 0 0 1 2) / 2
      where
        t2 = tetrahedron2 cube
        t3 = tetrahedron3 cube
      where
        t2 = tetrahedron2 cube
        t3 = tetrahedron3 cube
@@ -448,176 +107,146 @@ prop_c0120_identity3 cube =
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Repeats
 --   'prop_c0120_identity1' with tetrahedrons 4 and 5.
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Repeats
 --   'prop_c0120_identity1' with tetrahedrons 4 and 5.
--- prop_c0120_identity4 :: Cube -> Bool
--- prop_c0120_identity4 cube =
---     sum [trace ("c_t4_0120: " ++ (show tmp1)) tmp1,
---          trace ("c_t5_0012: " ++ (show tmp2)) tmp2,
---          trace ("c_t5_0102: " ++ (show tmp3)) tmp3,
---          trace ("c_t5_1002: " ++ (show tmp4)) tmp4,
---          trace ("c_t5_0120: " ++ (show tmp5)) tmp5,
---          trace ("c_t5_1020: " ++ (show tmp6)) tmp6,
---          trace ("c_t5_1200: " ++ (show tmp7)) tmp7,
---          trace ("c_t5_0021: " ++ (show tmp8)) tmp8,
---          trace ("c_t5_0201: " ++ (show tmp9)) tmp9,
---          trace ("c_t5_2001: " ++ (show tmp10)) tmp10,
---          trace ("c_t5_0210: " ++ (show tmp11)) tmp11,
---          trace ("c_t5_2010: " ++ (show tmp12)) tmp12,
---          trace ("c_t5_2100: " ++ (show tmp13)) tmp13] == 10
--- --   c t4 0 1 2 0 ~= (c t4 0 0 2 1 + c t5 0 0 1 2) / 2
---      where
---        t4 = tetrahedron4 cube
---        t5 = tetrahedron5 cube
---        tmp1 = c t4 0 1 2 0
---        tmp2 = (c t4 0 0 2 1 + c t5 0 0 1 2) / 2
---        tmp3 = (c t4 0 0 2 1 + c t5 0 1 0 2) / 2
---        tmp4 = (c t4 0 0 2 1 + c t5 1 0 0 2) / 2
---        tmp5 = (c t4 0 0 2 1 + c t5 0 1 2 0) / 2
---        tmp6 = (c t4 0 0 2 1 + c t5 1 0 2 0) / 2
---        tmp7 = (c t4 0 0 2 1 + c t5 1 2 0 0) / 2
---        tmp8 = (c t4 0 0 2 1 + c t5 0 0 2 1) / 2
---        tmp9 = (c t4 0 0 2 1 + c t5 0 2 0 1) / 2
---        tmp10 = (c t4 0 0 2 1 + c t5 2 0 0 1) / 2
---        tmp11 = (c t4 0 0 2 1 + c t5 0 2 1 0) / 2
---        tmp12 = (c t4 0 0 2 1 + c t5 2 0 1 0) / 2
---        tmp13 = (c t4 0 0 2 1 + c t5 2 1 0 0) / 2
+prop_c0120_identity5 :: Cube -> Bool
+prop_c0120_identity5 cube =
+    c t5 0 1 2 0 ~= (c t5 0 0 2 1 + c t4 0 0 1 2) / 2
+    where
+      t4 = tetrahedron4 cube
+      t5 = tetrahedron5 cube
 
 -- -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Repeats
 -- --   'prop_c0120_identity1' with tetrahedrons 5 and 6.
 
 -- -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Repeats
 -- --   'prop_c0120_identity1' with tetrahedrons 5 and 6.
--- prop_c0120_identity5 :: Cube -> Bool
--- prop_c0120_identity5 cube =
---    c t5 0 1 2 0 ~= (c t5 0 0 2 1 + c t6 0 0 1 2) / 2
---      where
---        t5 = tetrahedron5 cube
---        t6 = tetrahedron6 cube
+prop_c0120_identity6 :: Cube -> Bool
+prop_c0120_identity6 cube =
+   c t6 0 1 2 0 ~= (c t6 0 0 2 1 + c t5 0 0 1 2) / 2
+     where
+       t5 = tetrahedron5 cube
+       t6 = tetrahedron6 cube
 
 
 -- -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Repeats
 -- --   'prop_c0120_identity1' with tetrahedrons 6 and 7.
 
 
 -- -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). Repeats
 -- --   'prop_c0120_identity1' with tetrahedrons 6 and 7.
--- prop_c0120_identity6 :: Cube -> Bool
--- prop_c0120_identity6 cube =
---    c t6 0 1 2 0 ~= (c t6 0 0 2 1 + c t7 0 0 1 2) / 2
---      where
---        t6 = tetrahedron6 cube
---        t7 = tetrahedron7 cube
+prop_c0120_identity7 :: Cube -> Bool
+prop_c0120_identity7 cube =
+   c t7 0 1 2 0 ~= (c t7 0 0 2 1 + c t6 0 0 1 2) / 2
+     where
+       t6 = tetrahedron6 cube
+       t7 = tetrahedron7 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). See
 --   'prop_c0120_identity1'.
 prop_c0210_identity1 :: Cube -> Bool
 prop_c0210_identity1 cube =
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). See
 --   'prop_c0120_identity1'.
 prop_c0210_identity1 :: Cube -> Bool
 prop_c0210_identity1 cube =
-    c t0 0 2 1 0 ~= (c t0 0 1 1 1 + c t1 0 1 1 1) / 2
+    c t0 0 2 1 0 ~= (c t0 0 1 1 1 + c t3 0 1 1 1) / 2
       where
         t0 = tetrahedron0 cube
       where
         t0 = tetrahedron0 cube
-        t1 = tetrahedron1 cube
+        t3 = tetrahedron3 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). See
 --   'prop_c0120_identity1'.
 prop_c0300_identity1 :: Cube -> Bool
 prop_c0300_identity1 cube =
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). See
 --   'prop_c0120_identity1'.
 prop_c0300_identity1 :: Cube -> Bool
 prop_c0300_identity1 cube =
-    c t0 0 3 0 0 ~= (c t0 0 2 0 1 + c t1 0 2 1 0) / 2
+    c t0 0 3 0 0 ~= (c t0 0 2 0 1 + c t3 0 2 1 0) / 2
       where
         t0 = tetrahedron0 cube
       where
         t0 = tetrahedron0 cube
-        t1 = tetrahedron1 cube
+        t3 = tetrahedron3 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). See
 --   'prop_c0120_identity1'.
 prop_c1110_identity :: Cube -> Bool
 prop_c1110_identity cube =
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). See
 --   'prop_c0120_identity1'.
 prop_c1110_identity :: Cube -> Bool
 prop_c1110_identity cube =
-    c t0 1 1 1 0 ~= (c t0 1 0 1 1 + c t1 1 0 1 1) / 2
+    c t0 1 1 1 0 ~= (c t0 1 0 1 1 + c t3 1 0 1 1) / 2
       where
         t0 = tetrahedron0 cube
       where
         t0 = tetrahedron0 cube
-        t1 = tetrahedron1 cube
+        t3 = tetrahedron3 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). See
 --   'prop_c0120_identity1'.
 prop_c1200_identity1 :: Cube -> Bool
 prop_c1200_identity1 cube =
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). See
 --   'prop_c0120_identity1'.
 prop_c1200_identity1 :: Cube -> Bool
 prop_c1200_identity1 cube =
-    c t0 1 2 0 0 ~= (c t0 1 1 0 1 + c t1 1 1 1 0) / 2
+    c t0 1 2 0 0 ~= (c t0 1 1 0 1 + c t3 1 1 1 0) / 2
       where
         t0 = tetrahedron0 cube
       where
         t0 = tetrahedron0 cube
-        t1 = tetrahedron1 cube
+        t3 = tetrahedron3 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). See
 --   'prop_c0120_identity1'.
 prop_c2100_identity1 :: Cube -> Bool
 prop_c2100_identity1 cube =
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.6). See
 --   'prop_c0120_identity1'.
 prop_c2100_identity1 :: Cube -> Bool
 prop_c2100_identity1 cube =
-    c t0 2 1 0 0 ~= (c t0 2 0 0 1 + c t1 2 0 1 0) / 2
+    c t0 2 1 0 0 ~= (c t0 2 0 0 1 + c t3 2 0 1 0) / 2
       where
         t0 = tetrahedron0 cube
       where
         t0 = tetrahedron0 cube
-        t1 = tetrahedron1 cube
+        t3 = tetrahedron3 cube
 
 
 
 
 
 
--- | Given in Sorokina and Zeilfelder, p. 79, (2.7). It appears that
---   the assumptions in sections (2.6) and (2.7) have been
---   switched. From the description, one would expect 'tetrahedron0'
---   and 'tetrahedron1' to share face \<v0,v1,v3\>; however, we have
---   to use 'tetrahedron0' and 'tetahedron3' for all of the tests in
---   section (2.7). Also note that the third and fourth indices of
---   c-t3 have been switched. This is because we store the triangles
---   oriented such that their volume is positive. If T and T-tilde
---   share \<v0,v1,v2\> and v3,v3-tilde point in opposite directions,
---   one of them has to have negative volume!
+-- | Given in Sorokina and Zeilfelder, p. 79, (2.7). Note that the
+--   third and fourth indices of c-t3 have been switched. This is
+--   because we store the triangles oriented such that their volume is
+--   positive. If T and T-tilde share \<v0,v1,v2\> and v3,v3-tilde
+--   point in opposite directions, one of them has to have negative
+--   volume!
 prop_c0102_identity1 :: Cube -> Bool
 prop_c0102_identity1 cube =
 prop_c0102_identity1 :: Cube -> Bool
 prop_c0102_identity1 cube =
-    c t0 0 1 0 2 ~= (c t0 0 0 1 2 + c t3 0 0 2 1) / 2
+    c t0 0 1 0 2 ~= (c t0 0 0 1 2 + c t1 0 0 2 1) / 2
       where
         t0 = tetrahedron0 cube
       where
         t0 = tetrahedron0 cube
-        t3 = tetrahedron3 cube
+        t1 = tetrahedron1 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.7). See
 --   'prop_c0102_identity1'.
 prop_c0201_identity1 :: Cube -> Bool
 prop_c0201_identity1 cube =
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.7). See
 --   'prop_c0102_identity1'.
 prop_c0201_identity1 :: Cube -> Bool
 prop_c0201_identity1 cube =
-    c t0 0 2 0 1 ~= (c t0 0 1 1 1 + c t3 0 1 1 1) / 2
+    c t0 0 2 0 1 ~= (c t0 0 1 1 1 + c t1 0 1 1 1) / 2
       where
         t0 = tetrahedron0 cube
       where
         t0 = tetrahedron0 cube
-        t3 = tetrahedron3 cube
+        t1 = tetrahedron1 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.7). See
 --   'prop_c0102_identity1'.
 prop_c0300_identity2 :: Cube -> Bool
 prop_c0300_identity2 cube =
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.7). See
 --   'prop_c0102_identity1'.
 prop_c0300_identity2 :: Cube -> Bool
 prop_c0300_identity2 cube =
-    c t0 0 3 0 0 ~= (c t0 0 2 1 0 + c t3 0 2 0 1) / 2
+    c t0 0 3 0 0 ~= (c t0 0 2 1 0 + c t1 0 2 0 1) / 2
       where
         t0 = tetrahedron0 cube
       where
         t0 = tetrahedron0 cube
-        t3 = tetrahedron3 cube
+        t1 = tetrahedron1 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.7). See
 --   'prop_c0102_identity1'.
 prop_c1101_identity :: Cube -> Bool
 prop_c1101_identity cube =
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.7). See
 --   'prop_c0102_identity1'.
 prop_c1101_identity :: Cube -> Bool
 prop_c1101_identity cube =
-    c t0 1 1 0 1 ~= (c t0 1 0 1 1 + c t3 1 0 1 1) / 2
+    c t0 1 1 0 1 ~= (c t0 1 0 1 1 + c t1 1 0 1 1) / 2
       where
         t0 = tetrahedron0 cube
       where
         t0 = tetrahedron0 cube
-        t3 = tetrahedron3 cube
+        t1 = tetrahedron1 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.7). See
 --   'prop_c0102_identity1'.
 prop_c1200_identity2 :: Cube -> Bool
 prop_c1200_identity2 cube =
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.7). See
 --   'prop_c0102_identity1'.
 prop_c1200_identity2 :: Cube -> Bool
 prop_c1200_identity2 cube =
-    c t0 1 2 0 0 ~= (c t0 1 1 1 0 + c t3 1 1 0 1) / 2
+    c t0 1 2 0 0 ~= (c t0 1 1 1 0 + c t1 1 1 0 1) / 2
       where
         t0 = tetrahedron0 cube
       where
         t0 = tetrahedron0 cube
-        t3 = tetrahedron3 cube
+        t1 = tetrahedron1 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.7). See
 --   'prop_c0102_identity1'.
 prop_c2100_identity2 :: Cube -> Bool
 prop_c2100_identity2 cube =
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.7). See
 --   'prop_c0102_identity1'.
 prop_c2100_identity2 :: Cube -> Bool
 prop_c2100_identity2 cube =
-    c t0 2 1 0 0 ~= (c t0 2 0 1 0 + c t3 2 0 0 1) / 2
+    c t0 2 1 0 0 ~= (c t0 2 0 1 0 + c t1 2 0 0 1) / 2
       where
         t0 = tetrahedron0 cube
       where
         t0 = tetrahedron0 cube
-        t3 = tetrahedron3 cube
+        t1 = tetrahedron1 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.8). The third and
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79, (2.8). The third and