]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Main.hs
Make the minimum number of changes necessary to work with repa-3.1.1.1. Unfortunately...
[spline3.git] / src / Main.hs
index 5d2a09083dd56867f3bc42715ebe17c95238986a..c1456f4a94c968ac47d3c764b7bdbc3da9b26245 100644 (file)
@@ -1,20 +1,30 @@
 module Main
 where
 
-import qualified Data.Array.Repa as R (map, force, reshape)
-import qualified Data.Array.Repa.IO.BMP as R (writeComponentsToBMP)
+import qualified Data.Array.Repa as R
 import System.Environment (getArgs)
 
-import Grid (make_grid, zoom)
-import MRI
-import Values (drop_z, zoom_shape)
-
-main :: IO ()
-main =  main2d
+import Grid (zoom)
+import MRI (
+  flip_x,
+  flip_y,
+  mri_shape,
+  mri_slice3d,
+  read_word16s,
+  round_array,
+  swap_bytes,
+  write_values_slice_to_bitmap,
+  write_word16s,
+  z_slice
+  )
 
 in_file :: FilePath
 in_file = "./data/mri.bin"
 
+
+main :: IO ()
+main = main3d
+
 main3d :: IO ()
 main3d = do
   (s:_) <- getArgs
@@ -22,34 +32,28 @@ main3d = do
   let zoom_factor = (scale, scale, scale)
   let out_file = "output.bin"
   arr <- read_word16s in_file
-  let arr' = swap_bytes arr
---  let arrInv   = flip_x $ flip_y arr'
-  let arrMRI = R.reshape mri_shape arr'
-  let dbl_data = R.force $ R.map fromIntegral arrMRI
-  let g = make_grid 1 dbl_data
-  let output = zoom g zoom_factor
-  let word16_output = bracket_array output
+  let arr'          = swap_bytes arr
+  let arrMRI        = R.reshape mri_shape arr'
+  let dbl_data      = R.computeS $ R.map fromIntegral arrMRI
+  let output        = zoom dbl_data zoom_factor
+  let word16_output = R.computeS $ round_array output
   write_word16s out_file word16_output
 
+
 main2d :: IO ()
 main2d = do
   (s:_) <- getArgs
   let scale = read s :: Int
   let zoom_factor = (1, scale, scale)
   let out_file = "output.bmp"
-  arr <- read_word16s in_file
-  let arr' = swap_bytes arr
-  let arrInv   = flip_x $ flip_y arr'
-  let arrSlice = z_slice 50 arrInv
+  arr           <- read_word16s in_file
+  let arrSlice  = R.computeUnboxedS $ z_slice 50 $ flip_x $ flip_y $ swap_bytes arr
   let arrSlice' = R.reshape mri_slice3d arrSlice
-  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
+
+  -- If zoom isn't being inlined we need to extract the slice before hand,
+  -- and convert it to the require formed.
+  let dbl_data  = R.computeS $ R.map fromIntegral arrSlice'
+  let output    = zoom dbl_data zoom_factor
+  let arrSlice0 = R.computeUnboxedS $ z_slice 0 output
+  
+  write_values_slice_to_bitmap arrSlice0 out_file