]> 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 c9165d3e3dc71287cdcee00590a5e35142a6e40b..c1456f4a94c968ac47d3c764b7bdbc3da9b26245 100644 (file)
@@ -1,73 +1,59 @@
 module Main
 where
 
-import Data.Array.Repa (
-  DIM2,
-  DIM3,
-  Z(..),
-  (:.)(..),
-  slice,
-  reshape,
-  Any(..),
-  All(..)
-  )
-import qualified Data.Array.Repa as R (map)
-
-import Data.Array.Repa.IO.BMP (writeComponentsToBMP)
-import Data.Word
+import qualified Data.Array.Repa as R
 import System.Environment (getArgs)
 
-import Grid (make_grid, zoom)
-import MRI
-import Values (read_values_3d, write_values_1d)
+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
+  )
 
-mri_shape2d :: DIM2
-mri_shape2d = (Z :. 256*2 :. 256*2)
+in_file :: FilePath
+in_file = "./data/mri.bin"
 
-mri_shape3d :: DIM3
-mri_shape3d = (Z :. 256 :. 256 :. 1)
 
 main :: IO ()
-main = do
---  args <- getArgs
---  let color = head args
---  let in_file  = "./data/MRbrain.40." ++ color
-  let out_file = "MRbrain.50.red.out"
-  arr <- read_word16s
-  let arrBrack = bracket_array arr
-  let arrInv   = flip_x $ flip_y arrBrack
-  let arrSlice = slice arrInv (Any :. (50 :: Int) :. All :. All)
-  let arrColor = raw_data_to_color arrSlice
-
-  let arrColor' = reshape mri_shape3d arrColor
-  let rdata = red_dbl_data arrColor'
-  let gdata = green_dbl_data arrColor'
-  let bdata = blue_dbl_data arrColor'
-
---  mridata <- read_values_3d mri_shape in_file
-
-  let gr = make_grid 1 rdata
-  let routput = zoom gr (2,2,1)
-
-  let gg = make_grid 1 gdata
-  let goutput = zoom gg (2,2,1)
-
-  let gb = make_grid 1 bdata
-  let boutput = zoom gb (2,2,1)
-
-  let routput' = R.map double_to_word8 (reshape mri_shape2d routput)
-  let goutput' = R.map double_to_word8 (reshape mri_shape2d goutput)
-  let boutput' = R.map double_to_word8 (reshape mri_shape2d boutput)
-
---  write_values_1d output out_file
-  writeComponentsToBMP out_file routput' goutput' boutput'
-  where
-    double_to_word8 :: Double -> Word8
-    double_to_word8 x =
-      if x > 255 then
-        255 :: Word8
-      else
-        if x < 0 then
-          0 :: Word8
-        else
-          fromIntegral $ truncate x
+main = main3d
+
+main3d :: IO ()
+main3d = do
+  (s:_) <- getArgs
+  let scale = read s :: Int
+  let zoom_factor = (scale, scale, scale)
+  let out_file = "output.bin"
+  arr <- read_word16s in_file
+  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 arrSlice  = R.computeUnboxedS $ z_slice 50 $ flip_x $ flip_y $ swap_bytes arr
+  let arrSlice' = R.reshape mri_slice3d arrSlice
+
+  -- 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