]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Main.hs
Add some junk to Main where I am experimenting.
[spline3.git] / src / Main.hs
index 963b31ed70448c8c88860ab039b9c1d85fbd401d..9742a1f096d5bc6e1ec6946e7b968eeb846a641e 100644 (file)
@@ -1,42 +1,78 @@
 module Main
 where
 
-import Data.Array.Repa (
-  DIM3,
-  Z(..),
-  (:.)(..),
-  )
-
+import qualified Data.Array.Repa as R
+import qualified Data.Array.Repa.IO.BMP as R (writeComponentsToBMP)
 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)
-
-mri_shape :: DIM3
-mri_shape = (Z :. 256 :. 256 :. 1)
-
-
-
+import Grid (make_grid, zoom)
+import MRI
+import Values (drop_z, zoom_shape)
 
 main :: IO ()
 main = do
-  args <- getArgs
-  let color = head args
-  let in_file  = "./data/MRbrain.40." ++ color
-  let out_file = "MRbrain.40." ++ color ++ ".out"
-  mridata <- read_values_3d mri_shape in_file
+  (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_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
+
+
+in_file :: FilePath
+in_file = "./data/mri.bin"
 
-  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 ]
+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 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
+  write_word16s out_file word16_output
 
-  let output = zoom g polynomials (4,4,1)
-  write_values_1d output out_file
+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
+  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