module Tests.Cube where import Test.QuickCheck import Comparisons import Cube import FunctionValues 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. -- | Since the grid size is necessarily positive, all tetrahedrons -- (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 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 -- | All tetrahedron should have their v0 located at the center of the cube. 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. 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 \ 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. Repeats -- prop_c0120_identity2 with tetrahedrons 3 and 2. prop_c0120_identity2 :: Cube -> Bool prop_c0120_identity2 cube = c t3 0 1 2 0 ~= (c t3 0 0 2 1 + c t2 0 0 1 2) / 2 where t3 = tetrahedron3 cube t2 = tetrahedron2 cube -- | Given in Sorokina and Zeilfelder, p. 79. Repeats -- prop_c0120_identity1 with tetrahedrons 2 and 1. 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 t2 = tetrahedron2 cube t1 = tetrahedron1 cube -- | Given in Sorokina and Zeilfelder, p. 79. Repeats -- prop_c0120_identity1 with tetrahedrons 4 and 7. prop_c0120_identity4 :: Cube -> Bool prop_c0120_identity4 cube = c t4 0 1 2 0 ~= (c t4 0 0 2 1 + c t7 0 0 1 2) / 2 where t4 = tetrahedron4 cube t7 = tetrahedron7 cube -- | Given in Sorokina and Zeilfelder, p. 79. Repeats -- prop_c0120_identity1 with tetrahedrons 7 and 6. prop_c0120_identity5 :: Cube -> Bool prop_c0120_identity5 cube = c t7 0 1 2 0 ~= (c t7 0 0 2 1 + c t6 0 0 1 2) / 2 where t7 = tetrahedron7 cube t6 = tetrahedron6 cube -- | Given in Sorokina and Zeilfelder, p. 79. Repeats -- prop_c0120_identity1 with tetrahedrons 6 and 5. 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 t6 = tetrahedron6 cube t5 = tetrahedron5 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 \ 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 \ 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 \ 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 \ 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 \ 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 \ 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 \ 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 \ 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 \ 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 \ 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 \ 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 -- | Given in Sorokina and Zeilfelder, p. 79. 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) { v2 = (v3 t6), v3 = (v2 t6) } -- | 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. -- prop_cijk1_identity :: Cube -> Bool -- prop_cijk1_identity cube = -- and [ c t0 i j k 1 ~= -- (c t1 (i+1) j k 0) * ((b0 t0) (v3 t1)) + -- (c t1 i (j+1) k 0) * ((b1 t0) (v3 t1)) + -- (c t1 i j (k+1) 0) * ((b2 t0) (v3 t1)) + -- (c t1 i j k 1) * ((b3 t0) (v3 t1)) | i <- [0..2], -- j <- [0..2], -- k <- [0..2], -- i + j + k == 2] -- where -- t0 = tetrahedron0 cube -- t1 = tetrahedron1 cube -- | We know what (c t6 2 1 0 0) should be from Sorokina and Zeilfelder, p. 87. -- This test checks the actual value based on the FunctionValues of the cube. prop_c_tilde_2100_correct :: Cube -> Bool prop_c_tilde_2100_correct cube = c t6 2 1 0 0 == (3/8)*int + (1/12)*(f + r + l + b) + (1/64)*(ft + rt + lt + bt) + (7/48)*t + (1/48)*d + (1/96)*(fr + fl + br + bl) + (1/192)*(fd + rd + ld + bd) where t6 = tetrahedron6 cube fvs = Tetrahedron.fv t6 int = interior fvs f = front fvs r = right fvs l = left fvs b = back fvs ft = front_top fvs rt = right_top fvs lt = left_top fvs bt = back_top fvs t = top fvs d = down fvs fr = front_right fvs fl = front_left fvs br = back_right fvs bl = back_left fvs fd = front_down fvs rd = right_down fvs ld = left_down fvs bd = back_down fvs -- Tests to check that the correct edges are incidental. prop_t0_shares_edge_with_t1 :: Cube -> Bool prop_t0_shares_edge_with_t1 cube = (v1 t0) == (v1 t1) && (v3 t0) == (v2 t1) where t0 = tetrahedron0 cube t1 = tetrahedron1 cube prop_t0_shares_edge_with_t3 :: Cube -> Bool prop_t0_shares_edge_with_t3 cube = (v1 t0) == (v1 t3) && (v2 t0) == (v3 t3) where t0 = tetrahedron0 cube t3 = tetrahedron3 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 prop_t1_shares_edge_with_t2 :: Cube -> Bool prop_t1_shares_edge_with_t2 cube = (v1 t1) == (v1 t2) && (v3 t1) == (v2 t2) where t1 = tetrahedron1 cube t2 = tetrahedron2 cube prop_t1_shares_edge_with_t19 :: Cube -> Bool prop_t1_shares_edge_with_t19 cube = (v2 t1) == (v3 t19) && (v3 t1) == (v2 t19) where t1 = tetrahedron1 cube t19 = tetrahedron19 cube prop_t2_shares_edge_with_t3 :: Cube -> Bool prop_t2_shares_edge_with_t3 cube = (v1 t1) == (v1 t2) && (v3 t1) == (v2 t2) where t1 = tetrahedron1 cube t2 = tetrahedron2 cube prop_t2_shares_edge_with_t12 :: Cube -> Bool prop_t2_shares_edge_with_t12 cube = (v2 t2) == (v3 t12) && (v3 t2) == (v2 t12) where t2 = tetrahedron2 cube t12 = tetrahedron12 cube prop_t3_shares_edge_with_t21 :: Cube -> Bool prop_t3_shares_edge_with_t21 cube = (v2 t3) == (v3 t21) && (v3 t3) == (v2 t21) where t3 = tetrahedron3 cube t21 = tetrahedron21 cube prop_t4_shares_edge_with_t5 :: Cube -> Bool prop_t4_shares_edge_with_t5 cube = (v1 t4) == (v1 t5) && (v3 t4) == (v2 t5) where t4 = tetrahedron4 cube t5 = tetrahedron5 cube prop_t4_shares_edge_with_t7 :: Cube -> Bool prop_t4_shares_edge_with_t7 cube = (v1 t4) == (v1 t7) && (v2 t4) == (v3 t7) where t4 = tetrahedron4 cube t7 = tetrahedron7 cube prop_t4_shares_edge_with_t10 :: Cube -> Bool prop_t4_shares_edge_with_t10 cube = (v2 t4) == (v3 t10) && (v3 t4) == (v2 t10) where t4 = tetrahedron4 cube t10 = tetrahedron10 cube prop_t5_shares_edge_with_t6 :: Cube -> Bool prop_t5_shares_edge_with_t6 cube = (v1 t5) == (v1 t6) && (v3 t5) == (v2 t6) where t5 = tetrahedron5 cube t6 = tetrahedron6 cube prop_t5_shares_edge_with_t16 :: Cube -> Bool prop_t5_shares_edge_with_t16 cube = (v2 t5) == (v3 t16) && (v3 t5) == (v2 t16) where t5 = tetrahedron5 cube t16 = tetrahedron16 cube prop_t6_shares_edge_with_t7 :: Cube -> Bool prop_t6_shares_edge_with_t7 cube = (v1 t6) == (v1 t7) && (v3 t6) == (v2 t7) where t6 = tetrahedron6 cube t7 = tetrahedron7 cube prop_t7_shares_edge_with_t20 :: Cube -> Bool prop_t7_shares_edge_with_t20 cube = (v2 t7) == (v3 t20) && (v2 t7) == (v3 t20) where t7 = tetrahedron7 cube t20 = tetrahedron20 cube