X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FGrid.hs;h=d98bda1d0ce0e602bee9796c245dd10666d74176;hb=0696fc4f3e428d2156f0be4ca40728abf2e35abe;hp=b40f6558453e619ebae33f505eb4d5737bbb5b62;hpb=999576c62823479bd840e11e4802913d88c22cc5;p=spline3.git diff --git a/src/Grid.hs b/src/Grid.hs index b40f655..d98bda1 100644 --- a/src/Grid.hs +++ b/src/Grid.hs @@ -3,6 +3,7 @@ -- function used to build the interpolation. module Grid ( cube_at, + grid_properties, grid_tests, slow_tests, zoom ) @@ -15,17 +16,17 @@ import Data.Array.Repa ( computeUnboxedP, fromListUnboxed ) import Data.Array.Repa.Operators.Traversal ( 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(..), +import Test.Tasty ( TestTree, testGroup ) +import Test.Tasty.HUnit ( Assertion, assertEqual, testCase ) +import Test.Tasty.QuickCheck ( + Arbitrary( arbitrary ), Gen, Property, + (==>), choose, - vectorOf ) + vectorOf, + testProperty ) + import Assertions ( assertAlmostEqual, assertTrue ) import Comparisons ( (~=) ) import Cube ( @@ -35,10 +36,10 @@ import Cube ( tetrahedron ) import Examples ( trilinear, trilinear9x9x9, zeros ) import FunctionValues ( make_values, value_at ) -import Point ( Point(..) ) +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 ) @@ -50,8 +51,8 @@ import Values ( Values3D, dims, empty3d, zoom_shape ) -- 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 @@ -76,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 @@ -95,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'. @@ -120,7 +121,7 @@ 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 @@ -142,7 +143,7 @@ zoom v3d scale_factor where (xsize, ysize, zsize) = dims v3d transExtent = zoom_shape scale_factor - f = zoom_lookup v3d scale_factor + f = zoom_lookup v3d scale_factor :: (DIM3 -> Double) -> DIM3 -> Double -- | Check all coefficients of tetrahedron0 belonging to the cube @@ -152,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" @@ -190,63 +191,63 @@ trilinear_c0_t0_tests = test_trilinear_c0030 :: Assertion test_trilinear_c0030 = - assertAlmostEqual "c0030 is correct" (c t 0 0 3 0) (17/8) + assertAlmostEqual "c0030 is correct" (c t 0 0 3 0) (17 / 8) test_trilinear_c0003 :: Assertion test_trilinear_c0003 = - assertAlmostEqual "c0003 is correct" (c t 0 0 0 3) (27/8) + assertAlmostEqual "c0003 is correct" (c t 0 0 0 3) (27 / 8) test_trilinear_c0021 :: Assertion test_trilinear_c0021 = - assertAlmostEqual "c0021 is correct" (c t 0 0 2 1) (61/24) + assertAlmostEqual "c0021 is correct" (c t 0 0 2 1) (61 / 24) test_trilinear_c0012 :: Assertion test_trilinear_c0012 = - assertAlmostEqual "c0012 is correct" (c t 0 0 1 2) (71/24) + assertAlmostEqual "c0012 is correct" (c t 0 0 1 2) (71 / 24) test_trilinear_c0120 :: Assertion test_trilinear_c0120 = - assertAlmostEqual "c0120 is correct" (c t 0 1 2 0) (55/24) + assertAlmostEqual "c0120 is correct" (c t 0 1 2 0) (55 / 24) test_trilinear_c0102 :: Assertion test_trilinear_c0102 = - assertAlmostEqual "c0102 is correct" (c t 0 1 0 2) (73/24) + assertAlmostEqual "c0102 is correct" (c t 0 1 0 2) (73 / 24) test_trilinear_c0111 :: Assertion test_trilinear_c0111 = - assertAlmostEqual "c0111 is correct" (c t 0 1 1 1) (8/3) + assertAlmostEqual "c0111 is correct" (c t 0 1 1 1) (8 / 3) test_trilinear_c0210 :: Assertion test_trilinear_c0210 = - assertAlmostEqual "c0210 is correct" (c t 0 2 1 0) (29/12) + assertAlmostEqual "c0210 is correct" (c t 0 2 1 0) (29 / 12) test_trilinear_c0201 :: Assertion test_trilinear_c0201 = - assertAlmostEqual "c0201 is correct" (c t 0 2 0 1) (11/4) + assertAlmostEqual "c0201 is correct" (c t 0 2 0 1) (11 / 4) test_trilinear_c0300 :: Assertion test_trilinear_c0300 = - assertAlmostEqual "c0300 is correct" (c t 0 3 0 0) (5/2) + assertAlmostEqual "c0300 is correct" (c t 0 3 0 0) (5 / 2) test_trilinear_c1020 :: Assertion test_trilinear_c1020 = - assertAlmostEqual "c1020 is correct" (c t 1 0 2 0) (8/3) + assertAlmostEqual "c1020 is correct" (c t 1 0 2 0) (8 / 3) test_trilinear_c1002 :: Assertion test_trilinear_c1002 = - assertAlmostEqual "c1002 is correct" (c t 1 0 0 2) (23/6) + assertAlmostEqual "c1002 is correct" (c t 1 0 0 2) (23 / 6) test_trilinear_c1011 :: Assertion test_trilinear_c1011 = - assertAlmostEqual "c1011 is correct" (c t 1 0 1 1) (13/4) + assertAlmostEqual "c1011 is correct" (c t 1 0 1 1) (13 / 4) test_trilinear_c1110 :: Assertion test_trilinear_c1110 = - assertAlmostEqual "c1110 is correct" (c t 1 1 1 0) (23/8) + assertAlmostEqual "c1110 is correct" (c t 1 1 1 0) (23 / 8) test_trilinear_c1101 :: Assertion test_trilinear_c1101 = - assertAlmostEqual "c1101 is correct" (c t 1 1 0 1) (27/8) + assertAlmostEqual "c1101 is correct" (c t 1 1 0 1) (27 / 8) test_trilinear_c1200 :: Assertion test_trilinear_c1200 = @@ -254,7 +255,7 @@ trilinear_c0_t0_tests = test_trilinear_c2010 :: Assertion test_trilinear_c2010 = - assertAlmostEqual "c2010 is correct" (c t 2 0 1 0) (10/3) + assertAlmostEqual "c2010 is correct" (c t 2 0 1 0) (10 / 3) test_trilinear_c2001 :: Assertion test_trilinear_c2001 = @@ -262,7 +263,7 @@ trilinear_c0_t0_tests = test_trilinear_c2100 :: Assertion test_trilinear_c2100 = - assertAlmostEqual "c2100 is correct" (c t 2 1 0 0) (7/2) + assertAlmostEqual "c2100 is correct" (c t 2 1 0 0) (7 / 2) test_trilinear_c3000 :: Assertion test_trilinear_c3000 = @@ -295,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] ] @@ -310,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 ] @@ -331,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 @@ -343,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) @@ -462,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, @@ -473,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 ]