module Tests.Face
where
+import Control.Monad (unless)
+import Test.HUnit
import Test.QuickCheck
import Comparisons
-import Cube (Cube(grid), top)
+import Cube (Cube(grid), cube_at, top)
import Face (face0,
face2,
face5,
tetrahedron2,
tetrahedron3,
tetrahedrons)
-import Grid (Grid(h))
+import Grid (Grid(h), make_grid)
import Tetrahedron
+
+-- HUnit tests.
+
+-- | An HUnit assertion that wraps the almost_equals function. Stolen
+-- from the definition of assertEqual in Test/HUnit/Base.hs.
+assertAlmostEqual :: String -> Double -> Double -> Assertion
+assertAlmostEqual preface expected actual =
+ unless (actual ~= expected) (assertFailure msg)
+ where msg = (if null preface then "" else preface ++ "\n") ++
+ "expected: " ++ show expected ++ "\n but got: " ++ show actual
+
+
+-- | Values of the function f(x,y,z) = 1 + x + xy + xyz taken at nine
+-- points (hi, hj, jk) with h = 1. From example one in the paper.
+-- Used in the next bunch of tests.
+trilinear :: [[[Double]]]
+trilinear = [ [ [ 1, 2, 3 ],
+ [ 1, 3, 5 ],
+ [ 1, 4, 7 ] ],
+ [ [ 1, 2, 3 ],
+ [ 1, 4, 7 ],
+ [ 1, 6, 11 ] ],
+ [ [ 1, 2, 3 ],
+ [ 1, 5, 9 ],
+ [ 1, 8, 15 ]]]
+
+-- | Check the value of c0030 for any tetrahedron belonging to the
+-- cube centered on (1,1,1) with a grid constructed from the
+-- trilinear values. See example one in the paper.
+test_trilinear_c0030 :: Test
+test_trilinear_c0030 =
+ TestCase $ assertAlmostEqual "c0030 is correct" (c t 0 0 3 0) (17/8)
+ where
+ g = make_grid 1 trilinear
+ cube = cube_at g 1 1 1
+ t = head (tetrahedrons cube) -- Any one will do.
+
+
+-- | Check the value of c0003 for any tetrahedron belonging to the
+-- cube centered on (1,1,1) with a grid constructed from the
+-- trilinear values. See example one in the paper.
+test_trilinear_c0003 :: Test
+test_trilinear_c0003 =
+ TestCase $ assertAlmostEqual "c0003 is correct" (c t 0 0 0 3) (27/8)
+ where
+ g = make_grid 1 trilinear
+ cube = cube_at g 1 1 1
+ t = head (tetrahedrons cube) -- Any one will do.
+
+
+-- | Check the value of c0021 for any tetrahedron belonging to the
+-- cube centered on (1,1,1) with a grid constructed from the
+-- trilinear values. See example one in the paper.
+test_trilinear_c0021 :: Test
+test_trilinear_c0021 =
+ TestCase $ assertAlmostEqual "c0021 is correct" (c t 0 0 2 1) (61/24)
+ where
+ g = make_grid 1 trilinear
+ cube = cube_at g 1 1 1
+ t = head (tetrahedrons cube) -- Any one will do.
+
+
+-- | Check the value of c0012 for any tetrahedron belonging to the
+-- cube centered on (1,1,1) with a grid constructed from the
+-- trilinear values. See example one in the paper.
+test_trilinear_c0012 :: Test
+test_trilinear_c0012 =
+ TestCase $ assertAlmostEqual "c0012 is correct" (c t 0 0 1 2) (71/24)
+ where
+ g = make_grid 1 trilinear
+ cube = cube_at g 1 1 1
+ t = head (tetrahedrons cube) -- Any one will do.
+
+
+-- | Check the value of c0120 for any tetrahedron belonging to the
+-- cube centered on (1,1,1) with a grid constructed from the
+-- trilinear values. See example one in the paper.
+test_trilinear_c0120 :: Test
+test_trilinear_c0120 =
+ TestCase $ assertAlmostEqual "c0120 is correct" (c t 0 1 2 0) (55/24)
+ where
+ g = make_grid 1 trilinear
+ cube = cube_at g 1 1 1
+ t = head (tetrahedrons cube) -- Any one will do.
+
+
+face_tests :: [Test]
+face_tests = [test_trilinear_c0030,
+ test_trilinear_c0003,
+ test_trilinear_c0021,
+ test_trilinear_c0012,
+ test_trilinear_c0120]
+
+
-- QuickCheck Tests.
-- | Since the grid size is necessarily positive, all tetrahedrons