module Tests.Cube where import Debug.Trace (trace) import Test.QuickCheck import Comparisons 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 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 c = null nonpositive_volumes where ts = tetrahedrons c 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 c = volume (tetrahedron0 c) ~= (1/24)*(delta^(3::Int)) where delta = h c -- | 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)) where delta = h c -- | 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)) where delta = h c -- | 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)) where delta = h c -- | 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)) where delta = h c -- | 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)) where delta = h c -- | 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)) where delta = h c -- | 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)) where delta = h c -- | 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) where t0 = head (tetrahedrons c) -- Doesn't matter which two we choose. t1 = head $ tail (tetrahedrons c) -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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 -- | 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. 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