]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Grid.hs
src/Grid.hs: make two import lists explicit.
[spline3.git] / src / Grid.hs
index 192bbaf8d3ac4e5dd5e48cac776726e414c4171c..43e60ef2c17948e78e334b2c49847b4c1fa19f50 100644 (file)
@@ -3,39 +3,46 @@
 --   function used to build the interpolation.
 module Grid (
   cube_at,
+  grid_properties,
   grid_tests,
   slow_tests,
-  zoom
-  )
+  zoom )
 where
 
-import qualified Data.Array.Repa as R
-import qualified Data.Array.Repa.Operators.Traversal as R (unsafeTraverse)
-import Test.HUnit (Assertion, assertEqual)
-import Test.Framework (Test, testGroup)
-import Test.Framework.Providers.HUnit (testCase)
-import Test.Framework.Providers.QuickCheck2 (testProperty)
-import Test.QuickCheck ((==>),
-                        Arbitrary(..),
-                        Gen,
-                        Property,
-                        choose)
-import Assertions (assertAlmostEqual, assertTrue)
-import Comparisons ((~=))
-import Cube (Cube(Cube),
-             find_containing_tetrahedron,
-             tetrahedra,
-             tetrahedron)
-import Examples (trilinear, trilinear9x9x9, zeros)
-import FunctionValues (make_values, value_at)
-import Point (Point(..))
-import ScaleFactor (ScaleFactor)
+import Data.Array.Repa (
+  (:.)( (:.) ),
+  DIM3,
+  Z( Z ),
+  computeUnboxedP,
+  fromListUnboxed )
+import Data.Array.Repa.Operators.Traversal ( unsafeTraverse )
+import Test.Tasty ( TestTree, testGroup )
+import Test.Tasty.HUnit ( Assertion, assertEqual, testCase )
+import Test.Tasty.QuickCheck (
+  Arbitrary( arbitrary ),
+  Gen,
+  Property,
+  (==>),
+  choose,
+  vectorOf,
+  testProperty )
+
+import Assertions ( assertAlmostEqual, assertTrue )
+import Comparisons ( (~=) )
+import Cube (
+  Cube( Cube ),
+  find_containing_tetrahedron,
+  tetrahedra,
+  tetrahedron )
+import Examples ( trilinear, trilinear9x9x9, zeros )
+import FunctionValues ( make_values, value_at )
+import Point ( Point(Point) )
+import ScaleFactor ( ScaleFactor )
 import Tetrahedron (
-  Tetrahedron(v0,v1,v2,v3),
+  Tetrahedron( v0, v1, v2, v3 ),
   c,
-  polynomial,
-  )
-import Values (Values3D, dims, empty3d, zoom_shape)
+  polynomial )
+import Values ( Values3D, dims, empty3d, zoom_shape )
 
 
 -- | Our problem is defined on a Grid. The grid size is given by the
@@ -43,13 +50,19 @@ import Values (Values3D, dims, empty3d, zoom_shape)
 --   performance reasons (and simplicity). The function values are the
 --   values of the function at the grid points, which are distance h=1
 --   from one another in each direction (x,y,z).
-data Grid = Grid { function_values :: Values3D }
-          deriving (Show)
+--
+newtype Grid = Grid { function_values :: Values3D }
+                 deriving (Show)
 
 
 instance Arbitrary Grid where
     arbitrary = do
-      fvs <- arbitrary :: Gen Values3D
+      x_dim <- choose (1, 27)
+      y_dim <- choose (1, 27)
+      z_dim <- choose (1, 27)
+      elements <- vectorOf (x_dim * y_dim * z_dim) (arbitrary :: Gen Double)
+      let new_shape = (Z :. x_dim :. y_dim :. z_dim)
+      let fvs = fromListUnboxed new_shape elements
       return $ Grid fvs
 
 
@@ -64,7 +77,7 @@ cube_at !g !i !j !k =
    where
      fvs = function_values g
      fvs' = make_values fvs i j k
-     tet_vol = 1/24
+     tet_vol = (1/24) :: Double
 
 
 --   The first cube along any axis covers (-1/2, 1/2). The second
@@ -83,7 +96,7 @@ calculate_containing_cube_coordinate g coord
     | otherwise = (ceiling (coord + offset)) - 1
     where
       (xsize, ysize, zsize) = dims (function_values g)
-      offset = 1/2
+      offset = (1/2) :: Double
 
 
 -- | Takes a 'Grid', and returns a 'Cube' containing the given 'Point'.
@@ -98,17 +111,17 @@ find_containing_cube g (Point x y z) =
       k = calculate_containing_cube_coordinate g z
 
 
-zoom_lookup :: Values3D -> ScaleFactor -> a -> (R.DIM3 -> Double)
+zoom_lookup :: Values3D -> ScaleFactor -> a -> (DIM3 -> Double)
 zoom_lookup v3d scale_factor _ =
     zoom_result v3d scale_factor
 
 
-zoom_result :: Values3D -> ScaleFactor -> R.DIM3 -> Double
-zoom_result v3d (sfx, sfy, sfz) (R.Z R.:. m R.:. n R.:. o) =
+zoom_result :: Values3D -> ScaleFactor -> DIM3 -> Double
+zoom_result v3d (sfx, sfy, sfz) (Z :. m :. n :. o) =
   f p
   where
     g = Grid v3d
-    offset = 1/2
+    offset = (1/2) :: Double
     m' = (fromIntegral m) / (fromIntegral sfx) - offset
     n' = (fromIntegral n) / (fromIntegral sfy) - offset
     o' = (fromIntegral o) / (fromIntegral sfz) - offset
@@ -118,15 +131,19 @@ zoom_result v3d (sfx, sfy, sfz) (R.Z R.:. m R.:. n R.:. o) =
     f = polynomial t
 
 
-zoom :: Values3D -> ScaleFactor -> Values3D
+--
+-- Instead of IO, we could get away with a generic monad 'm'
+-- here. However, /we/ only call this function from within IO.
+--
+zoom :: Values3D -> ScaleFactor -> IO Values3D
 zoom v3d scale_factor
-    | xsize == 0 || ysize == 0 || zsize == 0 = empty3d
+    | xsize == 0 || ysize == 0 || zsize == 0 = return empty3d
     | otherwise =
-        R.computeS $ R.unsafeTraverse v3d transExtent f
-          where
-            (xsize, ysize, zsize) = dims v3d
-            transExtent = zoom_shape scale_factor
-            f = zoom_lookup v3d scale_factor
+        computeUnboxedP $ unsafeTraverse v3d transExtent f
+        where
+          (xsize, ysize, zsize) = dims v3d
+          transExtent = zoom_shape scale_factor
+          f = zoom_lookup v3d scale_factor :: (DIM3 -> Double) -> DIM3 -> Double
 
 
 -- | Check all coefficients of tetrahedron0 belonging to the cube
@@ -136,7 +153,7 @@ zoom v3d scale_factor
 --   We also verify that the four vertices on face0 of the cube are
 --   in the correct location.
 --
-trilinear_c0_t0_tests :: Test.Framework.Test
+trilinear_c0_t0_tests :: TestTree
 trilinear_c0_t0_tests =
   testGroup "trilinear c0 t0"
     [testGroup "coefficients"
@@ -279,9 +296,9 @@ test_trilinear_reproduced =
                       c0 <- cs,
                       t <- tetrahedra c0,
                       let p = polynomial t,
-                      let i' = fromIntegral i,
-                      let j' = fromIntegral j,
-                      let k' = fromIntegral k]
+                      let i' = fromIntegral i :: Double,
+                      let j' = fromIntegral j :: Double,
+                      let k' = fromIntegral k :: Double]
     where
       g = Grid trilinear
       cs = [ cube_at g ci cj ck | ci <- [0..2], cj <- [0..2], ck <- [0..2] ]
@@ -294,9 +311,9 @@ test_zeros_reproduced =
                     | i <- [0..2],
                       j <- [0..2],
                       k <- [0..2],
-                      let i' = fromIntegral i,
-                      let j' = fromIntegral j,
-                      let k' = fromIntegral k,
+                      let i' = fromIntegral i :: Double,
+                      let j' = fromIntegral j :: Double,
+                      let k' = fromIntegral k :: Double,
                       c0 <- cs,
                       t0 <- tetrahedra c0,
                       let p = polynomial t0 ]
@@ -315,9 +332,9 @@ test_trilinear9x9x9_reproduced =
               k <- [0..8],
               t <- tetrahedra c0,
               let p = polynomial t,
-              let i' = (fromIntegral i) * 0.5,
-              let j' = (fromIntegral j) * 0.5,
-              let k' = (fromIntegral k) * 0.5]
+              let i' = (fromIntegral i) * 0.5 :: Double,
+              let j' = (fromIntegral j) * 0.5 :: Double,
+              let k' = (fromIntegral k) * 0.5 :: Double]
     where
       g = Grid trilinear
       c0 = cube_at g 1 1 1
@@ -327,12 +344,12 @@ test_trilinear9x9x9_reproduced =
 prop_cube_indices_never_go_out_of_bounds :: Grid -> Gen Bool
 prop_cube_indices_never_go_out_of_bounds g =
   do
-    let coordmin = negate (1/2)
+    let coordmin = negate (1/2) :: Double
 
     let (xsize, ysize, zsize) = dims $ function_values g
-    let xmax = (fromIntegral xsize) - (1/2)
-    let ymax = (fromIntegral ysize) - (1/2)
-    let zmax = (fromIntegral zsize) - (1/2)
+    let xmax = (fromIntegral xsize) - (1/2) :: Double
+    let ymax = (fromIntegral ysize) - (1/2) :: Double
+    let zmax = (fromIntegral zsize) - (1/2) :: Double
 
     x <- choose (coordmin, xmax)
     y <- choose (coordmin, ymax)
@@ -446,9 +463,9 @@ prop_c0300_identity g =
 
 -- | All of the properties from Section (2.9), p. 80. These require a
 --   grid since they refer to two adjacent cubes.
-p80_29_properties :: Test.Framework.Test
+p80_29_properties :: TestTree
 p80_29_properties =
-  testGroup "p. 80, Section (2.9) Properties" [
+  testGroup "p. 80, Section (2.9) properties" [
     testProperty "c0120 identity" prop_c0120_identity,
     testProperty "c0111 identity" prop_c0111_identity,
     testProperty "c0201 identity" prop_c0201_identity,
@@ -457,19 +474,22 @@ p80_29_properties =
     testProperty "c0300 identity" prop_c0300_identity ]
 
 
-grid_tests :: Test.Framework.Test
+grid_tests :: TestTree
 grid_tests =
-    testGroup "Grid Tests" [
-      trilinear_c0_t0_tests,
-      p80_29_properties,
-      testProperty "cube indices within bounds"
-        prop_cube_indices_never_go_out_of_bounds ]
+  testGroup "Grid tests" [ trilinear_c0_t0_tests ]
+
 
+grid_properties :: TestTree
+grid_properties =
+  testGroup "Grid properties"
+    [ p80_29_properties,
+      testProperty "cube indices within bounds"
+                   prop_cube_indices_never_go_out_of_bounds ]
 
 -- Do the slow tests last so we can stop paying attention.
-slow_tests :: Test.Framework.Test
+slow_tests :: TestTree
 slow_tests =
-    testGroup "Slow Tests" [
+    testGroup "Slow tests" [
       testCase "trilinear reproduced" test_trilinear_reproduced,
       testCase "trilinear9x9x9 reproduced" test_trilinear9x9x9_reproduced,
       testCase "zeros reproduced" test_zeros_reproduced ]