]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Tests/Tetrahedron.hs
Move the FunctionValues tests into the FunctionValues module.
[spline3.git] / src / Tests / Tetrahedron.hs
index 5e176719b7f22f27490f3e5a09c25b18943f18d2..ec71e3b826ad9fea0008d541f5c1becec549fdd7 100644 (file)
 module Tests.Tetrahedron
 where
 
+import Test.Framework (Test, testGroup)
+import Test.Framework.Providers.HUnit (testCase)
 import Test.HUnit
-import Test.QuickCheck
+import Test.QuickCheck (Property, (==>))
 
 import Cardinal
 import Comparisons
-import Point
 import FunctionValues
-import Tests.FunctionValues()
 import Tetrahedron
 import ThreeDimensional
 
-instance Arbitrary Tetrahedron where
-    arbitrary = do
-      rnd_v0 <- arbitrary :: Gen Point
-      rnd_v1 <- arbitrary :: Gen Point
-      rnd_v2 <- arbitrary :: Gen Point
-      rnd_v3 <- arbitrary :: Gen Point
-      rnd_fv <- arbitrary :: Gen FunctionValues
-      return (Tetrahedron rnd_fv rnd_v0 rnd_v1 rnd_v2 rnd_v3)
-
 -- HUnit Tests
 
 
--- | Check the volume of a particular tetrahedron against the value
---   computed by hand. Its vertices are in clockwise order, so the
---   volume should be negative.
-test_volume1 :: Assertion
-test_volume1 =
-    assertEqual "volume is correct" True (vol ~= (-1/3))
-    where
-      p0 = (0, -0.5, 0)
-      p1 = (0, 0.5, 0)
-      p2 = (2, 0, 0)
-      p3 = (1, 0, 1)
-      t = Tetrahedron { v0 = p0,
-                        v1 = p1,
-                        v2 = p2,
-                        v3 = p3,
-                        fv = empty_values }
-      vol = volume t
-
-
--- | Check the volume of a particular tetrahedron against the value
---   computed by hand. Its vertices are in counter-clockwise order, so
---   the volume should be positive.
-test_volume2 :: Assertion
-test_volume2 =
-    assertEqual "volume is correct" True (vol ~= (1/3))
-    where
-      p0 = (0, -0.5, 0)
-      p1 = (2, 0, 0)
-      p2 = (0, 0.5, 0)
-      p3 = (1, 0, 1)
-      t = Tetrahedron { v0 = p0,
-                        v1 = p1,
-                        v2 = p2,
-                        v3 = p3,
-                        fv = empty_values }
-      vol = volume t
-
-
--- | Ensure that a tetrahedron contains a particular point chosen to
---   be inside of it.
-test_contains_point1 :: Assertion
-test_contains_point1 =
-    assertEqual "contains an inner point" True (contains_point t inner_point)
-    where
-      p0 = (0, -0.5, 0)
-      p1 = (0, 0.5, 0)
-      p2 = (2, 0, 0)
-      p3 = (1, 0, 1)
-      inner_point = (1, 0, 0.5)
-      t = Tetrahedron { v0 = p0,
-                        v1 = p1,
-                        v2 = p2,
-                        v3 = p3,
-                        fv = empty_values }
-
-
--- | Ensure that a tetrahedron does not contain a particular point chosen to
---   be outside of it (first test).
-test_doesnt_contain_point1 :: Assertion
-test_doesnt_contain_point1 =
-    assertEqual "doesn't contain an exterior point" False (contains_point t exterior_point)
-    where
-      p0 = (0, -0.5, 0)
-      p1 = (0, 0.5, 0)
-      p2 = (2, 0, 0)
-      p3 = (1, 0, 1)
-      exterior_point = (5, 2, -9.0212)
-      t = Tetrahedron { v0 = p0,
-                        v1 = p1,
-                        v2 = p2,
-                        v3 = p3,
-                        fv = empty_values }
-
-
--- | Ensure that a tetrahedron does not contain a particular point chosen to
---   be outside of it (second test).
-test_doesnt_contain_point2 :: Assertion
-test_doesnt_contain_point2 =
-    assertEqual "doesn't contain an exterior point" False (contains_point t exterior_point)
-    where
-      p0 = (0, 1, 1)
-      p1 = (1, 1, 1)
-      p2 = (0.5, 0.5, 1)
-      p3 = (0.5, 0.5, 0.5)
-      exterior_point = (0, 0, 0)
-      t = Tetrahedron { v0 = p0,
-                        v1 = p1,
-                        v2 = p2,
-                        v3 = p3,
-                        fv = empty_values }
-
-
--- | Ensure that a tetrahedron does not contain a particular point chosen to
---   be outside of it (third test).
-test_doesnt_contain_point3 :: Assertion
-test_doesnt_contain_point3 =
-    assertEqual "doesn't contain an exterior point" False (contains_point t exterior_point)
-    where
-      p0 = (1, 1, 1)
-      p1 = (1, 0, 1)
-      p2 = (0.5, 0.5, 1)
-      p3 = (0.5, 0.5, 0.5)
-      exterior_point = (0, 0, 0)
-      t = Tetrahedron { v0 = p0,
-                        v1 = p1,
-                        v2 = p2,
-                        v3 = p3,
-                        fv = empty_values }
-
-
--- | Ensure that a tetrahedron does not contain a particular point chosen to
---   be outside of it (fourth test).
-test_doesnt_contain_point4 :: Assertion
-test_doesnt_contain_point4 =
-    assertEqual "doesn't contain an exterior point" False (contains_point t exterior_point)
-    where
-      p0 = (1, 0, 1)
-      p1 = (0, 0, 1)
-      p2 = (0.5, 0.5, 1)
-      p3 = (0.5, 0.5, 0.5)
-      exterior_point = (0, 0, 0)
-      t = Tetrahedron { v0 = p0,
-                        v1 = p1,
-                        v2 = p2,
-                        v3 = p3,
-                        fv = empty_values }
-
-
--- | Ensure that a tetrahedron does not contain a particular point chosen to
---   be outside of it (fifth test).
-test_doesnt_contain_point5 :: Assertion
-test_doesnt_contain_point5 =
-    assertEqual "doesn't contain an exterior point" False (contains_point t exterior_point)
-    where
-      p0 = (0, 0, 1)
-      p1 = (0, 1, 1)
-      p2 = (0.5, 0.5, 1)
-      p3 = (0.5, 0.5, 0.5)
-      exterior_point = (0, 0, 0)
-      t = Tetrahedron { v0 = p0,
-                        v1 = p1,
-                        v2 = p2,
-                        v3 = p3,
-                        fv = empty_values }
+-- | Check the volume of a particular tetrahedron (computed by hand)
+--   and whether or not it contains a specific point chosen to be
+--   outside of it. Its vertices are in clockwise order, so the volume
+--   should be negative.
+tetrahedron1_geometry_tests :: Test.Framework.Test
+tetrahedron1_geometry_tests =
+  testGroup "tetrahedron1 geometry"
+              [ testCase "volume1" volume1,
+                testCase "doesn't contain point1" doesnt_contain_point1]
+  where
+    p0 = (0, -0.5, 0)
+    p1 = (0, 0.5, 0)
+    p2 = (2, 0, 0)
+    p3 = (1, 0, 1)
+    t = Tetrahedron { v0 = p0,
+                      v1 = p1,
+                      v2 = p2,
+                      v3 = p3,
+                      fv = empty_values,
+                      precomputed_volume = 0 }
+
+    volume1 :: Assertion
+    volume1 =
+      assertEqual "volume is correct" True (vol ~= (-1/3))
+      where
+        vol = volume t
+
+    doesnt_contain_point1 :: Assertion
+    doesnt_contain_point1 =
+      assertEqual "doesn't contain an exterior point" False contained
+      where
+        exterior_point = (5, 2, -9.0212)
+        contained = contains_point t exterior_point
+
+
+-- | Check the volume of a particular tetrahedron (computed by hand)
+--   and whether or not it contains a specific point chosen to be
+--   inside of it. Its vertices are in counter-clockwise order, so the
+--   volume should be positive.
+tetrahedron2_geometry_tests :: Test.Framework.Test
+tetrahedron2_geometry_tests =
+  testGroup "tetrahedron2 geometry"
+              [ testCase "volume1" volume1,
+                testCase "contains point1" contains_point1]
+  where
+    p0 = (0, -0.5, 0)
+    p1 = (2, 0, 0)
+    p2 = (0, 0.5, 0)
+    p3 = (1, 0, 1)
+    t = Tetrahedron { v0 = p0,
+                      v1 = p1,
+                      v2 = p2,
+                      v3 = p3,
+                      fv = empty_values,
+                      precomputed_volume = 0 }
+
+    volume1 :: Assertion
+    volume1 = assertEqual "volume1 is correct" True (vol ~= (1/3))
+      where
+        vol = volume t
+
+    contains_point1 :: Assertion
+    contains_point1 = assertEqual "contains an inner point" True contained
+        where
+          inner_point = (1, 0, 0.5)
+          contained = contains_point t inner_point
+
+
+-- | Ensure that tetrahedra do not contain a particular point chosen to
+--   be outside of them.
+containment_tests :: Test.Framework.Test
+containment_tests =
+  testGroup "containment tests"
+              [ testCase "doesn't contain point2" doesnt_contain_point2,
+                testCase "doesn't contain point3" doesnt_contain_point3,
+                testCase "doesn't contain point4" doesnt_contain_point4,
+                testCase "doesn't contain point5" doesnt_contain_point5]
+  where
+    p2 = (0.5, 0.5, 1)
+    p3 = (0.5, 0.5, 0.5)
+    exterior_point = (0, 0, 0)
+
+    doesnt_contain_point2 :: Assertion
+    doesnt_contain_point2 =
+      assertEqual "doesn't contain an exterior point" False contained
+      where
+        p0 = (0, 1, 1)
+        p1 = (1, 1, 1)
+        t = Tetrahedron { v0 = p0,
+                          v1 = p1,
+                          v2 = p2,
+                          v3 = p3,
+                          fv = empty_values,
+                          precomputed_volume = 0 }
+        contained = contains_point t exterior_point
+
+
+    doesnt_contain_point3 :: Assertion
+    doesnt_contain_point3 =
+      assertEqual "doesn't contain an exterior point" False contained
+      where
+        p0 = (1, 1, 1)
+        p1 = (1, 0, 1)
+        t = Tetrahedron { v0 = p0,
+                          v1 = p1,
+                          v2 = p2,
+                          v3 = p3,
+                          fv = empty_values,
+                          precomputed_volume = 0 }
+        contained = contains_point t exterior_point
+
+
+    doesnt_contain_point4 :: Assertion
+    doesnt_contain_point4 =
+      assertEqual "doesn't contain an exterior point" False contained
+      where
+        p0 = (1, 0, 1)
+        p1 = (0, 0, 1)
+        t = Tetrahedron { v0 = p0,
+                          v1 = p1,
+                          v2 = p2,
+                          v3 = p3,
+                          fv = empty_values,
+                          precomputed_volume = 0 }
+        contained = contains_point t exterior_point
+
+
+    doesnt_contain_point5 :: Assertion
+    doesnt_contain_point5 =
+      assertEqual "doesn't contain an exterior point" False contained
+      where
+        p0 = (0, 0, 1)
+        p1 = (0, 1, 1)
+        t = Tetrahedron { v0 = p0,
+                          v1 = p1,
+                          v2 = p2,
+                          v3 = p3,
+                          fv = empty_values,
+                          precomputed_volume = 0 }
+        contained = contains_point t exterior_point
 
 
 -- | The barycentric coordinate of v0 with respect to itself should
@@ -304,7 +291,7 @@ prop_x_rotation_doesnt_affect_front t =
     expr1 == expr2
     where
       fv0 = Tetrahedron.fv t
-      fv1 = rotate (Tetrahedron.fv t) cwx
+      fv1 = rotate cwx (Tetrahedron.fv t)
       expr1 = front fv0
       expr2 = front fv1
 
@@ -313,7 +300,7 @@ prop_x_rotation_doesnt_affect_back t =
     expr1 == expr2
     where
       fv0 = Tetrahedron.fv t
-      fv1 = rotate (Tetrahedron.fv t) cwx
+      fv1 = rotate cwx (Tetrahedron.fv t)
       expr1 = back fv0
       expr2 = back fv1
 
@@ -323,7 +310,7 @@ prop_y_rotation_doesnt_affect_left t =
     expr1 == expr2
     where
       fv0 = Tetrahedron.fv t
-      fv1 = rotate (Tetrahedron.fv t) cwy
+      fv1 = rotate cwy (Tetrahedron.fv t)
       expr1 = left fv0
       expr2 = left fv1
 
@@ -332,7 +319,7 @@ prop_y_rotation_doesnt_affect_right t =
     expr1 == expr2
     where
       fv0 = Tetrahedron.fv t
-      fv1 = rotate (Tetrahedron.fv t) cwy
+      fv1 = rotate cwy (Tetrahedron.fv t)
       expr1 = right fv0
       expr2 = right fv1
 
@@ -342,7 +329,7 @@ prop_z_rotation_doesnt_affect_down t =
     expr1 == expr2
     where
       fv0 = Tetrahedron.fv t
-      fv1 = rotate (Tetrahedron.fv t) cwz
+      fv1 = rotate cwz (Tetrahedron.fv t)
       expr1 = down fv0
       expr2 = down fv1
 
@@ -352,7 +339,7 @@ prop_z_rotation_doesnt_affect_top t =
     expr1 == expr2
     where
       fv0 = Tetrahedron.fv t
-      fv1 = rotate (Tetrahedron.fv t) cwz
+      fv1 = rotate cwz (Tetrahedron.fv t)
       expr1 = top fv0
       expr2 = top fv1