]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Tests/Cube.hs
Escape some special characters in comments, and make the publish_doc target sync...
[spline3.git] / src / Tests / Cube.hs
index 26d4d33f5ab7e21f3b85fc032ae98113edd6b25d..418730ab61245b8ea028beaa3d67035b3632e77a 100644 (file)
@@ -1,7 +1,6 @@
 module Tests.Cube
 where
 
-import Debug.Trace (trace)
 import Test.QuickCheck
 
 import Comparisons
@@ -9,7 +8,6 @@ import Cube
 import FunctionValues (FunctionValues)
 import Tests.FunctionValues ()
 import Tetrahedron (b0, b1, b2, b3, c,
-                    Tetrahedron(Tetrahedron),
                     v0, v1, v2, v3, volume)
 
 instance Arbitrary Cube where
@@ -31,10 +29,10 @@ instance Arbitrary Cube where
 --   (which comprise cubes of positive volume) must have positive volume
 --   as well.
 prop_all_volumes_positive :: Cube -> Bool
-prop_all_volumes_positive c =
+prop_all_volumes_positive cube =
     null nonpositive_volumes
     where
-      ts = tetrahedrons c
+      ts = tetrahedrons cube
       volumes = map volume ts
       nonpositive_volumes = filter (<= 0) volumes
 
@@ -42,237 +40,444 @@ prop_all_volumes_positive c =
 --   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 c =
-    volume (tetrahedron0 c) ~= (1/24)*(delta^(3::Int))
+prop_tetrahedron0_volumes_exact cube =
+    volume (tetrahedron0 cube) ~= (1/24)*(delta^(3::Int))
     where
-      delta = h c
+      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 c =
-    volume (tetrahedron1 c) ~= (1/24)*(delta^(3::Int))
+prop_tetrahedron1_volumes_exact cube =
+    volume (tetrahedron1 cube) ~= (1/24)*(delta^(3::Int))
     where
-      delta = h c
+      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 c =
-    volume (tetrahedron2 c) ~= (1/24)*(delta^(3::Int))
+prop_tetrahedron2_volumes_exact cube =
+    volume (tetrahedron2 cube) ~= (1/24)*(delta^(3::Int))
     where
-      delta = h c
+      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 c =
-    volume (tetrahedron3 c) ~= (1/24)*(delta^(3::Int))
+prop_tetrahedron3_volumes_exact cube =
+    volume (tetrahedron3 cube) ~= (1/24)*(delta^(3::Int))
     where
-      delta = h c
+      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 c =
-    volume (tetrahedron4 c) ~= (1/24)*(delta^(3::Int))
+prop_tetrahedron4_volumes_exact cube =
+    volume (tetrahedron4 cube) ~= (1/24)*(delta^(3::Int))
     where
-      delta = h c
+      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 c =
-    volume (tetrahedron5 c) ~= (1/24)*(delta^(3::Int))
+prop_tetrahedron5_volumes_exact cube =
+    volume (tetrahedron5 cube) ~= (1/24)*(delta^(3::Int))
     where
-      delta = h c
+      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 c =
-    volume (tetrahedron6 c) ~= (1/24)*(delta^(3::Int))
+prop_tetrahedron6_volumes_exact cube =
+    volume (tetrahedron6 cube) ~= (1/24)*(delta^(3::Int))
     where
-      delta = h c
+      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 c =
-    volume (tetrahedron7 c) ~= (1/24)*(delta^(3::Int))
+prop_tetrahedron7_volumes_exact cube =
+    volume (tetrahedron7 cube) ~= (1/24)*(delta^(3::Int))
     where
-      delta = h c
+      delta = h cube
 
 -- | All tetrahedron should have their v0 located at the center of the cube.
 prop_v0_all_equal :: Cube -> Bool
-prop_v0_all_equal c = (v0 t0) == (v0 t1)
+prop_v0_all_equal cube = (v0 t0) == (v0 t1)
     where
-      t0 = head (tetrahedrons c) -- Doesn't matter which two we choose.
-      t1 = head $ tail (tetrahedrons c)
+      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 c =
-    volume (tetrahedron0 c) > 0
+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 c =
-    volume (tetrahedron1 c) > 0
+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 c =
-    volume (tetrahedron2 c) > 0
+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 c =
-    volume (tetrahedron3 c) > 0
+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 c =
-    volume (tetrahedron4 c) > 0
+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 c =
-    volume (tetrahedron5 c) > 0
+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 c =
-    volume (tetrahedron6 c) > 0
+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 c =
-    volume (tetrahedron7 c) > 0
+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 c =
-    volume (tetrahedron8 c) > 0
+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 c =
-    volume (tetrahedron9 c) > 0
+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 c =
-    volume (tetrahedron10 c) > 0
+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 c =
-    volume (tetrahedron11 c) > 0
+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 c =
-    volume (tetrahedron12 c) > 0
+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 c =
-    volume (tetrahedron13 c) > 0
+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 c =
-    volume (tetrahedron14 c) > 0
+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 c =
-    volume (tetrahedron15 c) > 0
+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 c =
-    volume (tetrahedron16 c) > 0
+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 c =
-    volume (tetrahedron17 c) > 0
+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 c =
-    volume (tetrahedron18 c) > 0
+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 c =
-    volume (tetrahedron19 c) > 0
+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 c =
-    volume (tetrahedron20 c) > 0
+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 c =
-    volume (tetrahedron21 c) > 0
+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 c =
-    volume (tetrahedron22 c) > 0
+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 c =
-    volume (tetrahedron23 c) > 0
+prop_tetrahedron23_volumes_positive cube =
+    volume (tetrahedron23 cube) > 0
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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_c0120_identity1 :: Cube -> Bool
+prop_c0120_identity1 cube =
+   c t0 0 1 2 0 ~= (c t0 0 0 2 1 + c t3 0 0 1 2) / 2
+     where
+       t0 = tetrahedron0 cube
+       t3 = tetrahedron3 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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_c0210_identity1 :: Cube -> Bool
+prop_c0210_identity1 cube =
+    c t0 0 2 1 0 ~= (c t0 0 1 1 1 + c t3 0 1 1 1) / 2
+      where
+        t0 = tetrahedron0 cube
+        t3 = tetrahedron3 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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_c0300_identity1 :: Cube -> Bool
+prop_c0300_identity1 cube =
+    c t0 0 3 0 0 ~= (c t0 0 2 0 1 + c t3 0 2 1 0) / 2
+      where
+        t0 = tetrahedron0 cube
+        t3 = tetrahedron3 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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_c1110_identity :: Cube -> Bool
+prop_c1110_identity cube =
+    c t0 1 1 1 0 ~= (c t0 1 0 1 1 + c t3 1 0 1 1) / 2
+      where
+        t0 = tetrahedron0 cube
+        t3 = tetrahedron3 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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_c1200_identity1 :: Cube -> Bool
+prop_c1200_identity1 cube =
+    c t0 1 2 0 0 ~= (c t0 1 1 0 1 + c t3 1 1 1 0) / 2
+      where
+        t0 = tetrahedron0 cube
+        t3 = tetrahedron3 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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_c2100_identity1 :: Cube -> Bool
+prop_c2100_identity1 cube =
+    c t0 2 1 0 0 ~= (c t0 2 0 0 1 + c t3 2 0 1 0) / 2
+      where
+        t0 = tetrahedron0 cube
+        t3 = tetrahedron3 cube
+
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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,v3\> and v2,v2-tilde point
+--   in opposite directions, one of them has to have negative volume!
+prop_c0102_identity1 :: Cube -> Bool
+prop_c0102_identity1 cube =
+    c t0 0 1 0 2 ~= (c t0 0 0 1 2 + c t1 0 0 2 1) / 2
+      where
+        t0 = tetrahedron0 cube
+        t1 = tetrahedron1 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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,v3\> and v2,v2-tilde point
+--   in opposite directions, one of them has to have negative volume!
+prop_c0201_identity1 :: Cube -> Bool
+prop_c0201_identity1 cube =
+    c t0 0 2 0 1 ~= (c t0 0 1 1 1 + c t1 0 1 1 1) / 2
+      where
+        t0 = tetrahedron0 cube
+        t1 = tetrahedron1 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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,v3\> and v2,v2-tilde point
+--   in opposite directions, one of them has to have negative volume!
+prop_c0300_identity2 :: Cube -> Bool
+prop_c0300_identity2 cube =
+    c t0 0 3 0 0 ~= (c t0 0 2 1 0 + c t1 0 2 0 1) / 2
+      where
+        t0 = tetrahedron0 cube
+        t1 = tetrahedron1 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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,v3\> and v2,v2-tilde point
+--   in opposite directions, one of them has to have negative volume!
+prop_c1101_identity :: Cube -> Bool
+prop_c1101_identity cube =
+    c t0 1 1 0 1 ~= (c t0 1 0 1 1 + c t1 1 0 1 1) / 2
+      where
+        t0 = tetrahedron0 cube
+        t1 = tetrahedron1 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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,v3\> and v2,v2-tilde point
+--   in opposite directions, one of them has to have negative volume!
+prop_c1200_identity2 :: Cube -> Bool
+prop_c1200_identity2 cube =
+    c t0 1 2 0 0 ~= (c t0 1 1 1 0 + c t1 1 1 0 1) / 2
+      where
+        t0 = tetrahedron0 cube
+        t1 = tetrahedron1 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79. 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,v3\> and v2,v2-tilde point
+--   in opposite directions, one of them has to have negative volume!
+prop_c2100_identity2 :: Cube -> Bool
+prop_c2100_identity2 cube =
+    c t0 2 1 0 0 ~= (c t0 2 0 1 0 + c t1 2 0 0 1) / 2
+      where
+        t0 = tetrahedron0 cube
+        t1 = tetrahedron1 cube
+
+
+prop_t0_shares_edge_with_t6 :: Cube -> Bool
+prop_t0_shares_edge_with_t6 cube =
+    (v2 t0) == (v3 t6) && (v3 t0) == (v2 t6)
+      where
+        t0 = tetrahedron0 cube
+        t6 = tetrahedron6 cube
 
 
 -- | Given in Sorokina and Zeilfelder, p. 79.
---prop_c0120_identity1 :: Cube -> Bool
---prop_c0120_identity1 cube =
---   c0 ~= (c1 + c2) / 2
---     where
---       c0 = trace ("c0 :" ++ (show (c t0 0 1 2 0))) (c t0 0 1 2 0)
---       c1 = trace ("c1 :" ++ (show (c t0 0 0 2 1))) (c t0 0 0 2 1)
---       c2 = trace ("c2 :" ++ (show (c t1 0 0 2 1))) (c t1 0 0 2 1)
---       t0 = tetrahedron0 cube
---       t1 = tetrahedron1 cube
+prop_c3000_identity :: Cube -> Bool
+prop_c3000_identity cube =
+    c t0 3 0 0 0 ~= c t0 2 1 0 0 + c t6 2 1 0 0 - ((c t0 2 0 1 0 + c t0 2 0 0 1)/ 2)
+      where
+        t0 = tetrahedron0 cube
+        t6 = tetrahedron6 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79.
+prop_c2010_identity :: Cube -> Bool
+prop_c2010_identity cube =
+    c t0 2 0 1 0 ~= c t0 1 1 1 0 + c t6 1 1 1 0 - ((c t0 1 0 2 0 + c t0 1 0 1 1)/ 2)
+      where
+        t0 = tetrahedron0 cube
+        t6 = tetrahedron6 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79.
+prop_c2001_identity :: Cube -> Bool
+prop_c2001_identity cube =
+    c t0 2 0 0 1 ~= c t0 1 1 0 1 + c t6 1 1 0 1 - ((c t0 1 0 0 2 + c t0 1 0 1 1)/ 2)
+      where
+        t0 = tetrahedron0 cube
+        t6 = tetrahedron6 cube
+
+-- | Given in Sorokina and Zeilfelder, p. 79.
+prop_c1020_identity :: Cube -> Bool
+prop_c1020_identity cube =
+    c t0 1 0 2 0 ~= c t0 0 1 2 0 + c t6 0 1 2 0 - ((c t0 0 0 3 0 + c t0 0 0 2 1)/ 2)
+      where
+        t0 = tetrahedron0 cube
+        t6 = tetrahedron6 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79.
+prop_c1002_identity :: Cube -> Bool
+prop_c1002_identity cube =
+    c t0 1 0 0 2 ~= c t0 0 1 0 2 + c t6 0 1 0 2 - ((c t0 0 0 0 3 + c t0 0 0 1 2)/ 2)
+      where
+        t0 = tetrahedron0 cube
+        t6 = tetrahedron6 cube
+
+
+-- | Given in Sorokina and Zeilfelder, p. 79.
+prop_c1011_identity :: Cube -> Bool
+prop_c1011_identity cube =
+    c t0 1 0 1 1 ~= c t0 0 1 1 1 + c t6 0 1 1 1 - ((c t0 0 0 1 2 + c t0 0 0 2 1)/ 2)
+      where
+        t0 = tetrahedron0 cube
+        t6 = tetrahedron6 cube
+
 
 
 -- | Given in Sorokina and Zeilfelder, p. 78.