import Examples
import FunctionValues
import Point (Point)
-import PolynomialArray (PolynomialArray)
import ScaleFactor
-import Tetrahedron (Tetrahedron, c, number, polynomial, v0, v1, v2, v3)
+import Tetrahedron (Tetrahedron, c, polynomial, v0, v1, v2, v3)
import ThreeDimensional
import Values (Values3D, dims, empty3d, zoom_shape)
{-# INLINE zoom_lookup #-}
-zoom_lookup :: Grid -> PolynomialArray -> ScaleFactor -> a -> (R.DIM3 -> Double)
-zoom_lookup g polynomials scale_factor _ =
- zoom_result g polynomials scale_factor
+zoom_lookup :: Grid -> ScaleFactor -> a -> (R.DIM3 -> Double)
+zoom_lookup g scale_factor _ =
+ zoom_result g scale_factor
{-# INLINE zoom_result #-}
-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
+zoom_result :: Grid -> ScaleFactor -> R.DIM3 -> Double
+zoom_result g (sfx, sfy, sfz) (R.Z R.:. m R.:. n R.:. o) =
+ f p
where
offset = (h g)/2
m' = (fromIntegral m) / (fromIntegral sfx) - 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 -> PolynomialArray -> ScaleFactor -> Values3D
-zoom g polynomials scale_factor
+zoom :: Grid -> ScaleFactor -> Values3D
+zoom g scale_factor
| xsize == 0 || ysize == 0 || zsize == 0 = empty3d
| otherwise =
- R.force $ R.traverse arr transExtent (zoom_lookup g polynomials scale_factor)
+ R.force $ R.traverse arr transExtent (zoom_lookup g scale_factor)
where
arr = function_values g
(xsize, ysize, zsize) = dims arr
import System.Environment (getArgs)
-import Cube (tetrahedron)
-import Grid (cube_at, make_grid, zoom)
-import PolynomialArray (make_polynomial_array)
-import Tetrahedron (polynomial)
+import Grid (make_grid, zoom)
import Values (read_values_3d, write_values_1d)
mri_shape :: DIM3
mridata <- read_values_3d mri_shape in_file
let g = make_grid 1 mridata
- 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)
+ let output = zoom g (4,4,1)
write_values_1d output out_file
+++ /dev/null
--- | The PolynomialArray module contains one type, 'PolynomialArray',
--- and a smart constructor for it. The array is essentially a hash;
--- the unique keys can be thought of as a cube/tetrahedron pair, and
--- the associated value is the polynomial function over that
--- tetrahedron. Rather than define 'Ord' instances and a proper map,
--- we just use the indices i,j,k along with the tetrahedron number
--- as the keys.
-module PolynomialArray (
- PolynomialArray,
- make_polynomial_array
- )
-where
-
-import RealFunction(RealFunction)
-import Point (Point)
-
-import Data.Array (Array, array)
-
-type PolynomialArray =
- Array (Int,Int,Int,Int) (RealFunction Point)
-
-make_polynomial_array :: (Int, Int, Int, Int) ->
- [( (Int,Int,Int,Int), (RealFunction Point) )] ->
- PolynomialArray
-make_polynomial_array (max_i, max_j, max_k, max_tetrahedron_number) =
- array ( (0,0,0,0), (max_i,max_j,max_k, max_tetrahedron_number) )