]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Tetrahedron.hs
Inline Tetrahedron functions volume, b0, b1, b2, and b3 (Ben Lippmeier).
[spline3.git] / src / Tetrahedron.hs
index 670a6e0f26f5024be159b8f870bcfd61e1dafe92..a9e6c2c6c299a9ec8df42af3a3b137b5c97728b1 100644 (file)
@@ -28,7 +28,7 @@ import Test.QuickCheck (Arbitrary(..), Gen, Property, (==>))
 import Comparisons ((~=), nearly_ge)
 import FunctionValues (FunctionValues(..), empty_values)
 import Misc (factorial)
-import Point (Point, scale)
+import Point (Point(..), scale)
 import RealFunction (RealFunction, cmult, fexp)
 import ThreeDimensional (ThreeDimensional(..))
 
@@ -71,6 +71,7 @@ instance ThreeDimensional Tetrahedron where
     center (Tetrahedron _ v0' v1' v2' v3' _) =
         (v0' + v1' + v2' + v3') `scale` (1/4)
 
+    -- contains_point is only used in tests.
     contains_point t p0 =
       b0_unscaled `nearly_ge` 0 &&
       b1_unscaled `nearly_ge` 0 &&
@@ -293,10 +294,10 @@ det :: Point -> Point -> Point -> Point -> Double
 det p0 p1 p2 p3 =
   term5 + term6
   where
-    (x1, y1, z1) = p0
-    (x2, y2, z2) = p1
-    (x3, y3, z3) = p2
-    (x4, y4, z4) = p3
+    Point x1 y1 z1 = p0
+    Point x2 y2 z2 = p1
+    Point x3 y3 z3 = p2
+    Point x4 y4 z4 = p3
     term1 = ((x2 - x4)*y1 - (x1 - x4)*y2 + (x1 - x2)*y4)*z3
     term2 = ((x2 - x3)*y1 - (x1 - x3)*y2 + (x1 - x2)*y3)*z4
     term3 = ((x3 - x4)*y2 - (x2 - x4)*y3 + (x2 - x3)*y4)*z1
@@ -307,6 +308,7 @@ det p0 p1 p2 p3 =
 
 -- | Computed using the formula from Lai & Schumaker, Definition 15.4,
 --   page 436.
+{-# INLINE volume #-}
 volume :: Tetrahedron -> Double
 volume t
        | v0' == v1' = 0
@@ -324,6 +326,7 @@ volume t
 
 
 -- | The barycentric coordinates of a point with respect to v0.
+{-# INLINE b0 #-}
 b0 :: Tetrahedron -> (RealFunction Point)
 b0 t point = (volume inner_tetrahedron) / (precomputed_volume t)
              where
@@ -331,6 +334,7 @@ b0 t point = (volume inner_tetrahedron) / (precomputed_volume t)
 
 
 -- | The barycentric coordinates of a point with respect to v1.
+{-# INLINE b1 #-}
 b1 :: Tetrahedron -> (RealFunction Point)
 b1 t point = (volume inner_tetrahedron) / (precomputed_volume t)
              where
@@ -338,6 +342,7 @@ b1 t point = (volume inner_tetrahedron) / (precomputed_volume t)
 
 
 -- | The barycentric coordinates of a point with respect to v2.
+{-# INLINE b2 #-}
 b2 :: Tetrahedron -> (RealFunction Point)
 b2 t point = (volume inner_tetrahedron) / (precomputed_volume t)
              where
@@ -345,6 +350,7 @@ b2 t point = (volume inner_tetrahedron) / (precomputed_volume t)
 
 
 -- | The barycentric coordinates of a point with respect to v3.
+{-# INLINE b3 #-}
 b3 :: Tetrahedron -> (RealFunction Point)
 b3 t point = (volume inner_tetrahedron) / (precomputed_volume t)
              where
@@ -366,10 +372,10 @@ tetrahedron1_geometry_tests =
               [ 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)
+    p0 = Point 0 (-0.5) 0
+    p1 = Point 0 0.5 0
+    p2 = Point 2 0 0
+    p3 = Point 1 0 1
     t = Tetrahedron { v0 = p0,
                       v1 = p1,
                       v2 = p2,
@@ -387,7 +393,7 @@ tetrahedron1_geometry_tests =
     doesnt_contain_point1 =
       assertEqual "doesn't contain an exterior point" False contained
       where
-        exterior_point = (5, 2, -9.0212)
+        exterior_point = Point 5 2 (-9.0212)
         contained = contains_point t exterior_point
 
 
@@ -401,10 +407,10 @@ tetrahedron2_geometry_tests =
               [ 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)
+    p0 = Point 0 (-0.5) 0
+    p1 = Point 2 0 0
+    p2 = Point 0 0.5 0
+    p3 = Point 1 0 1
     t = Tetrahedron { v0 = p0,
                       v1 = p1,
                       v2 = p2,
@@ -420,7 +426,7 @@ tetrahedron2_geometry_tests =
     contains_point1 :: Assertion
     contains_point1 = assertEqual "contains an inner point" True contained
         where
-          inner_point = (1, 0, 0.5)
+          inner_point = Point 1 0 0.5
           contained = contains_point t inner_point
 
 
@@ -434,16 +440,16 @@ containment_tests =
                 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)
+    p2 = Point 0.5 0.5 1
+    p3 = Point 0.5 0.5 0.5
+    exterior_point = 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)
+        p0 = Point 0 1 1
+        p1 = Point 1 1 1
         t = Tetrahedron { v0 = p0,
                           v1 = p1,
                           v2 = p2,
@@ -457,8 +463,8 @@ containment_tests =
     doesnt_contain_point3 =
       assertEqual "doesn't contain an exterior point" False contained
       where
-        p0 = (1, 1, 1)
-        p1 = (1, 0, 1)
+        p0 = Point 1 1 1
+        p1 = Point 1 0 1
         t = Tetrahedron { v0 = p0,
                           v1 = p1,
                           v2 = p2,
@@ -472,8 +478,8 @@ containment_tests =
     doesnt_contain_point4 =
       assertEqual "doesn't contain an exterior point" False contained
       where
-        p0 = (1, 0, 1)
-        p1 = (0, 0, 1)
+        p0 = Point 1 0 1
+        p1 = Point 0 0 1
         t = Tetrahedron { v0 = p0,
                           v1 = p1,
                           v2 = p2,
@@ -487,8 +493,8 @@ containment_tests =
     doesnt_contain_point5 =
       assertEqual "doesn't contain an exterior point" False contained
       where
-        p0 = (0, 0, 1)
-        p1 = (0, 1, 1)
+        p0 = Point 0 0 1
+        p1 = Point 0 1 1
         t = Tetrahedron { v0 = p0,
                           v1 = p1,
                           v2 = p2,