grid_tests,
   make_grid,
   slow_tests,
-  zoom
+  zoom,
+  zoom_chunk
   )
 where
 
     cube = find_containing_cube g p
     t = find_containing_tetrahedron cube p
     f = polynomial t
-    
+
+
 zoom :: Grid -> ScaleFactor -> Values3D
 zoom g scale_factor
     | xsize == 0 || ysize == 0 || zsize == 0 = empty3d
 
 
 
+{-# INLINE zoom_chunk_lookup #-}
+zoom_chunk_lookup :: Grid -> ScaleFactor -> a -> (R.DIM3 -> Double)
+zoom_chunk_lookup g scale_factor _ =
+    zoom_chunk_result g scale_factor
+
+
+{-# INLINE zoom_chunk_result #-}
+zoom_chunk_result :: Grid -> ScaleFactor -> R.DIM3 -> Double
+zoom_chunk_result g (sfx, sfy, sfz) (R.Z R.:. m R.:. n R.:. o)
+  | m /= 1 = 0 -- We're going to drop these anyway.
+  | otherwise = f p
+    where
+      offset = (h g)/2
+      sfx' = fromIntegral sfx
+      sfy' = fromIntegral sfy
+      sfz' = fromIntegral sfz
+      m' = (fromIntegral m) / sfx' - offset
+      n' = (fromIntegral n) / sfy' - offset
+      o' = (fromIntegral o) / sfz' - offset
+      p  = (m', n', o') :: Point
+      cube = find_containing_cube g p
+      t = find_containing_tetrahedron cube p
+      f = polynomial t
+
+
+zoom_chunk :: Grid -> ScaleFactor -> Values3D
+zoom_chunk g scale_factor
+    | xsize == 0 || ysize == 0 || zsize == 0 = empty3d
+    | otherwise =
+        R.force $ R.unsafeTraverse arr transExtent (zoom_chunk_lookup g scale_factor)
+          where
+            arr = function_values g
+            (xsize, ysize, zsize) = dims arr
+            transExtent = zoom_shape scale_factor
+
+
+
 -- | Check all coefficients of tetrahedron0 belonging to the cube
 --   centered on (1,1,1) with a grid constructed from the trilinear
 --   values. See example one in the paper.
 
 where
 
 import qualified Data.Array.Repa as R
-import qualified Data.Array.Repa.IO.BMP as R (writeComponentsToBMP)
 import System.Environment (getArgs)
 
-import Grid (make_grid, zoom)
+import Grid (make_grid, zoom, zoom_chunk)
 import MRI
-import Values (drop_z, zoom_shape)
+
+
+in_file :: FilePath
+in_file = "./data/mri.bin"
+
 
 main :: IO ()
-main = do
+main = main2d_chunk
+
+
+main2d_chunk :: IO ()
+main2d_chunk = do
   (s:_) <- getArgs
   let scale = read s :: Int
   let zoom_factor = (1, scale, scale)
   let arrSlice = z_slice3 50 arrInv
   let dbl_data = R.map fromIntegral arrSlice
   let g = make_grid 1 dbl_data
-  let output = zoom g zoom_factor
-  let arrBrack = bracket_array output
-  print $ "arrBrack extent:" ++ (show $ R.extent arrBrack)
-  let arrBrack' = z_slice 1 arrBrack
-  print $ "arrBrack' extent:" ++ (show $ R.extent arrBrack')
-  let mri_slice2d = drop_z $ zoom_shape zoom_factor mri_slice3d
-  let colors = values_to_colors $ R.reshape mri_slice2d
-                                $ R.map fromIntegral arrBrack'
-  let routput = R.map (\(red, _,     _)    -> red)   colors
-  let goutput = R.map (\(_,   green, _)    -> green) colors
-  let boutput = R.map (\(_,   _,     blue) -> blue)  colors
-  R.writeComponentsToBMP out_file routput goutput boutput
+  let output = zoom_chunk g zoom_factor
+  write_values_chunk_to_bitmap output out_file
 
 
-in_file :: FilePath
-in_file = "./data/mri.bin"
 
 main3d :: IO ()
 main3d = do
   let word16_output = bracket_array output
   write_word16s out_file word16_output
 
+
 main2d :: IO ()
 main2d = do
   (s:_) <- getArgs
   let dbl_data = R.map fromIntegral arrSlice'
   let g = make_grid 1 dbl_data
   let output = zoom g zoom_factor
-  let arrBrack = bracket_array output
-  let mri_slice2d = drop_z $ zoom_shape zoom_factor mri_slice3d
-  let colors = values_to_colors $ R.reshape mri_slice2d
-                                $ R.map fromIntegral arrBrack
-  let routput = R.map (\(red, _,     _)    -> red)   colors
-  let goutput = R.map (\(_,   green, _)    -> green) colors
-  let boutput = R.map (\(_,   _,     blue) -> blue)  colors
-  R.writeComponentsToBMP out_file routput goutput boutput
+  write_values_slice_to_bitmap (z_slice 0 output) out_file