From aed1b3cc557b67aca7d8b3259f44715078db94ae Mon Sep 17 00:00:00 2001 From: Michael Orlitzky Date: Sun, 4 Sep 2011 09:03:47 -0400 Subject: [PATCH] Memoize the zoom function via PolynomialArray. --- src/Grid.hs | 45 ++++++++++++++++++++++++--------------------- src/Main.hs | 19 +++++++++++++++++-- 2 files changed, 41 insertions(+), 23 deletions(-) diff --git a/src/Grid.hs b/src/Grid.hs index 2cf56ba..d31ffab 100644 --- a/src/Grid.hs +++ b/src/Grid.hs @@ -2,6 +2,7 @@ -- for it. We hide the main Grid constructor because we don't want -- to allow instantiation of a grid with h <= 0. module Grid ( + cube_at, grid_tests, make_grid, slow_tests, @@ -22,13 +23,13 @@ import Comparisons import Cube (Cube(Cube), find_containing_tetrahedron, tetrahedra, - tetrahedron0, - tetrahedron15) + tetrahedron) import Examples import FunctionValues import Point (Point) +import PolynomialArray (PolynomialArray) import ScaleFactor -import Tetrahedron (c, polynomial, v0, v1, v2, v3) +import Tetrahedron (Tetrahedron, c, number, polynomial, v0, v1, v2, v3) import ThreeDimensional import Values (Values3D, dims, empty3d, zoom_shape) @@ -132,30 +133,32 @@ find_containing_cube g p = {-# INLINE zoom_lookup #-} -zoom_lookup :: Grid -> ScaleFactor -> a -> (R.DIM3 -> Double) -zoom_lookup g scale_factor _ = zoom_result g scale_factor +zoom_lookup :: Grid -> PolynomialArray -> ScaleFactor -> a -> (R.DIM3 -> Double) +zoom_lookup g polynomials scale_factor _ = + zoom_result g polynomials scale_factor {-# INLINE zoom_result #-} -zoom_result :: Grid -> ScaleFactor -> R.DIM3 -> Double -zoom_result g (sfx, sfy, sfz) (R.Z R.:. i R.:. j R.:. k) = - f p +zoom_result :: Grid -> PolynomialArray -> ScaleFactor -> R.DIM3 -> Double +zoom_result g polynomials (sfx, sfy, sfz) (R.Z R.:. m R.:. n R.:. o) = + (polynomials ! (i, j, k, (number t))) p where offset = (h g)/2 - i' = (fromIntegral i) / (fromIntegral sfx) - offset - j' = (fromIntegral j) / (fromIntegral sfy) - offset - k' = (fromIntegral k) / (fromIntegral sfz) - offset - p = (i', j', k') :: Point + m' = (fromIntegral m) / (fromIntegral sfx) - offset + n' = (fromIntegral n) / (fromIntegral sfy) - offset + o' = (fromIntegral o) / (fromIntegral sfz) - offset + p = (m', n', o') :: Point cube = find_containing_cube g p + -- Figure out i,j,k without importing those functions. + Cube _ i j k _ _ = cube t = find_containing_tetrahedron cube p - f = polynomial t - -zoom :: Grid -> ScaleFactor -> Values3D -zoom g scale_factor + +zoom :: Grid -> PolynomialArray -> ScaleFactor -> Values3D +zoom g polynomials scale_factor | xsize == 0 || ysize == 0 || zsize == 0 = empty3d | otherwise = - R.force $ R.traverse arr transExtent (zoom_lookup g scale_factor) + R.force $ R.traverse arr transExtent (zoom_lookup g polynomials scale_factor) where arr = function_values g (xsize, ysize, zsize) = dims arr @@ -205,7 +208,7 @@ trilinear_c0_t0_tests = where g = make_grid 1 trilinear cube = cube_at g 1 1 1 - t = tetrahedron0 cube + t = tetrahedron cube 0 test_trilinear_c0030 :: Assertion test_trilinear_c0030 = @@ -334,7 +337,7 @@ test_zeros_reproduced = where g = make_grid 1 zeros c0 = cube_at g 1 1 1 - t0 = tetrahedron0 c0 + t0 = tetrahedron c0 0 p = polynomial t0 @@ -362,7 +365,7 @@ test_trilinear9x9x9_reproduced = -- -- Example from before the fix: -- --- > b0 (tetrahedron15 c) p +-- > b0 (tetrahedron c 15) p -- -3.4694469519536365e-18 -- test_tetrahedra_collision_sensitivity :: Assertion @@ -373,7 +376,7 @@ test_tetrahedra_collision_sensitivity = g = make_grid 1 naturals_1d cube = cube_at g 0 17 1 p = (0, 16.75, 0.5) :: Point - t15 = tetrahedron15 cube + t15 = tetrahedron cube 15 prop_cube_indices_never_go_out_of_bounds :: Grid -> Gen Bool diff --git a/src/Main.hs b/src/Main.hs index c8ba345..4040276 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -9,12 +9,18 @@ import Data.Array.Repa ( import System.Environment (getArgs) +import Cube (tetrahedron) +import Grid (cube_at, make_grid, zoom) +import PolynomialArray (make_polynomial_array) +import Tetrahedron (polynomial) import Values (read_values_3d, write_values_1d) -import Grid (make_grid, zoom) mri_shape :: DIM3 mri_shape = (Z :. 256 :. 256 :. 1) + + + main :: IO () main = do args <- getArgs @@ -22,6 +28,15 @@ main = do let in_file = "./data/MRbrain.40." ++ color let out_file = "MRbrain.40." ++ color ++ ".out" mridata <- read_values_3d mri_shape in_file + let g = make_grid 1 mridata - let output = zoom g (8,8,1) + let polynomials = make_polynomial_array (255,255,0,23) + [ ((i,j,k,tet), polynomial t) | i <- [0..255], + j <- [0..255], + k <- [0], + tet <- [0..23], + let c = cube_at g i j k, + let t = tetrahedron c tet ] + + let output = zoom g polynomials (8,8,1) write_values_1d output out_file -- 2.43.2