module Tests.Cube
where
-import Debug.Trace (trace)
import Test.QuickCheck
import Comparisons
volume (tetrahedron23 c) > 0
--- | 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
+-- | 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. 78.
module Tests.Face
where
--- -- | Given in Sorokina and Zeilfelder, p. 79.
--- 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
--- where
--- t0 = tetrahedron0 (face0 cube)
--- t1 = tetrahedron1 (face0 cube)
--- t0' = Tetrahedron cube (v3 t0) (v2 t0) (v1 t0) (v0 t0)
--- t1' = Tetrahedron cube (v3 t1) (v2 t1) (v0 t1) (v1 t1)
-
-
--- -- | Given in Sorokina and Zeilfelder, p. 79.
--- 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 0 1) / 2
--- where
--- t0 = tetrahedron0 (face0 cube)
--- t1 = tetrahedron1 (face0 cube)
--- t0' = Tetrahedron cube (v3 t0) (v2 t0) (v1 t0) (v0 t0)
--- t1' = Tetrahedron cube (v3 t1) (v2 t1) (v0 t1) (v1 t1)
-
--- -- | Given in Sorokina and Zeilfelder, p. 79.
--- 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
--- where
--- t0 = tetrahedron0 (face0 cube)
--- t1 = tetrahedron1 (face0 cube)
--- t0' = Tetrahedron cube (v3 t0) (v2 t0) (v1 t0) (v0 t0)
--- t1' = Tetrahedron cube (v3 t1) (v2 t1) (v0 t1) (v1 t1)
--- -- | Given in Sorokina and Zeilfelder, p. 79.
--- 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 0 1) / 2
--- where
--- t0 = tetrahedron0 (face0 cube)
--- t1 = tetrahedron1 (face0 cube)
--- t0' = Tetrahedron cube (v3 t0) (v2 t0) (v1 t0) (v0 t0)
--- t1' = Tetrahedron cube (v3 t1) (v2 t1) (v0 t1) (v1 t1)
-
-
--- -- | Given in Sorokina and Zeilfelder, p. 79.
--- 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 0 1) / 2
--- where
--- t0 = tetrahedron0 (face0 cube)
--- t1 = tetrahedron1 (face0 cube)
--- t0' = Tetrahedron cube (v3 t0) (v2 t0) (v1 t0) (v0 t0)
--- t1' = Tetrahedron cube (v3 t1) (v2 t1) (v0 t1) (v1 t1)
-- -- | Given in Sorokina and Zeilfelder, p. 79.
import Test.QuickCheck
import Tests.Cardinal
-import Tests.Cube
+import Tests.Cube as TC
import Tests.Grid
import Tests.Misc
import Tests.Tetrahedron as TT
putStrLn "\nCube Tests\n"
- -- putStr "prop_c0120_identity1... "
- -- quickCheckWith qc_args prop_c0120_identity1
-
putStr "prop_all_volumes_positive... "
quickCheckWith qc_args prop_all_volumes_positive
putStr "prop_v0_all_equal... "
quickCheckWith qc_args prop_v0_all_equal
--- putStrLn "\np. 78, (2.5)\n"
-
--- putStr "prop_cijk1_identity... "
--- quickCheckWith qc_args prop_cijk1_identity
-
-
- putStrLn "\nMisc Tests\n"
-
- putStr "prop_factorial_greater... "
- quickCheckWith qc_args prop_factorial_greater
-
- putStrLn "\nTetrahedron Tests\n"
-
- putStr "prop_b0_v0_always_unity... "
- quickCheckWith qc_args prop_b0_v0_always_unity
-
- putStr "prop_b0_v1_always_zero... "
- quickCheckWith qc_args prop_b0_v1_always_zero
-
- putStr "prop_b0_v2_always_zero... "
- quickCheckWith qc_args prop_b0_v2_always_zero
-
- putStr "prop_b0_v3_always_zero... "
- quickCheckWith qc_args prop_b0_v3_always_zero
-
- putStr "prop_b1_v1_always_unity... "
- quickCheckWith qc_args prop_b1_v1_always_unity
-
- putStr "prop_b1_v0_always_zero... "
- quickCheckWith qc_args prop_b1_v0_always_zero
-
- putStr "prop_b1_v2_always_zero... "
- quickCheckWith qc_args prop_b1_v2_always_zero
-
- putStr "prop_b1_v3_always_zero... "
- quickCheckWith qc_args prop_b1_v3_always_zero
-
- putStr "prop_b2_v2_always_unity... "
- quickCheckWith qc_args prop_b2_v2_always_unity
-
- putStr "prop_b2_v0_always_zero... "
- quickCheckWith qc_args prop_b2_v0_always_zero
-
- putStr "prop_b2_v1_always_zero... "
- quickCheckWith qc_args prop_b2_v1_always_zero
+ -- putStrLn "\np. 78, (2.5)\n"
- putStr "prop_b2_v3_always_zero... "
- quickCheckWith qc_args prop_b2_v3_always_zero
-
- putStr "prop_b3_v3_always_unity... "
- quickCheckWith qc_args prop_b3_v3_always_unity
-
- putStr "prop_b3_v0_always_zero... "
- quickCheckWith qc_args prop_b3_v0_always_zero
+ -- putStr "prop_cijk1_identity... "
+ -- quickCheckWith qc_args prop_cijk1_identity
- putStr "prop_b3_v1_always_zero... "
- quickCheckWith qc_args prop_b3_v1_always_zero
- putStr "prop_b3_v2_always_zero... "
- quickCheckWith qc_args prop_b3_v2_always_zero
+ -- putStrLn "\np. 79, (2.6)\n"
- putStrLn "\np. 78, (2.4)\n"
+ putStr "prop_c0120_identity1... "
+ quickCheckWith qc_args TC.prop_c0120_identity1
- putStr "prop_c3000_identity... "
- quickCheckWith qc_args TT.prop_c3000_identity
+ putStr "prop_c0210_identity1... "
+ quickCheckWith qc_args TC.prop_c0210_identity1
- putStr "prop_c2100_identity... "
- quickCheckWith qc_args TT.prop_c2100_identity
+ putStr "prop_c0300_identity1... "
+ quickCheckWith qc_args TC.prop_c0300_identity1
putStr "prop_c1110_identity... "
- quickCheckWith qc_args TT.prop_c1110_identity
-
- -- putStrLn "\np. 79, (2.6)\n"
+ quickCheckWith qc_args TC.prop_c1110_identity
- -- putStr "prop_c0210_identity1... "
- -- quickCheckWith qc_args TF.prop_c0210_identity1
+ putStr "prop_c1200_identity1... "
+ quickCheckWith qc_args TC.prop_c1200_identity1
- -- putStr "prop_c0300_identity1... "
- -- quickCheckWith qc_args TF.prop_c0300_identity1
-
- -- putStr "prop_c1110_identity... "
- -- quickCheckWith qc_args TF.prop_c1110_identity
-
- -- putStr "prop_c1200_identity1... "
- -- quickCheckWith qc_args prop_c1200_identity1
-
- -- putStr "prop_c2100_identity1... "
- -- quickCheckWith qc_args TF.prop_c2100_identity1
+ putStr "prop_c2100_identity1... "
+ quickCheckWith qc_args TC.prop_c2100_identity1
-- putStrLn "\np. 79, (2.7)\n"
-- putStr "prop_c0300_identity3... "
-- quickCheckWith qc_args TF.prop_c0300_identity3
+
+ putStrLn "\nMisc Tests\n"
+
+ putStr "prop_factorial_greater... "
+ quickCheckWith qc_args prop_factorial_greater
+
+ putStrLn "\nTetrahedron Tests\n"
+
+ putStr "prop_b0_v0_always_unity... "
+ quickCheckWith qc_args prop_b0_v0_always_unity
+
+ putStr "prop_b0_v1_always_zero... "
+ quickCheckWith qc_args prop_b0_v1_always_zero
+
+ putStr "prop_b0_v2_always_zero... "
+ quickCheckWith qc_args prop_b0_v2_always_zero
+
+ putStr "prop_b0_v3_always_zero... "
+ quickCheckWith qc_args prop_b0_v3_always_zero
+
+ putStr "prop_b1_v1_always_unity... "
+ quickCheckWith qc_args prop_b1_v1_always_unity
+
+ putStr "prop_b1_v0_always_zero... "
+ quickCheckWith qc_args prop_b1_v0_always_zero
+
+ putStr "prop_b1_v2_always_zero... "
+ quickCheckWith qc_args prop_b1_v2_always_zero
+
+ putStr "prop_b1_v3_always_zero... "
+ quickCheckWith qc_args prop_b1_v3_always_zero
+
+ putStr "prop_b2_v2_always_unity... "
+ quickCheckWith qc_args prop_b2_v2_always_unity
+
+ putStr "prop_b2_v0_always_zero... "
+ quickCheckWith qc_args prop_b2_v0_always_zero
+
+ putStr "prop_b2_v1_always_zero... "
+ quickCheckWith qc_args prop_b2_v1_always_zero
+
+ putStr "prop_b2_v3_always_zero... "
+ quickCheckWith qc_args prop_b2_v3_always_zero
+
+ putStr "prop_b3_v3_always_unity... "
+ quickCheckWith qc_args prop_b3_v3_always_unity
+
+ putStr "prop_b3_v0_always_zero... "
+ quickCheckWith qc_args prop_b3_v0_always_zero
+
+ putStr "prop_b3_v1_always_zero... "
+ quickCheckWith qc_args prop_b3_v1_always_zero
+
+ putStr "prop_b3_v2_always_zero... "
+ quickCheckWith qc_args prop_b3_v2_always_zero
+
+ putStrLn "\np. 78, (2.4)\n"
+
+ putStr "prop_c3000_identity... "
+ quickCheckWith qc_args TT.prop_c3000_identity
+
+ putStr "prop_c2100_identity... "
+ quickCheckWith qc_args TT.prop_c2100_identity
+
+ putStr "prop_c1110_identity... "
+ quickCheckWith qc_args TT.prop_c1110_identity
+
+
putStrLn "\nCardinal Tests\n"
putStr "prop_ccwx_rotation_changes_direction... "