]> 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 c4204c821f4f534f1df7c72784b155dbd7072f83..9742a1f096d5bc6e1ec6946e7b968eeb846a641e 100644 (file)
@@ -1,27 +1,78 @@
 module Main
 where
 
---import Cube
---import Face
---import Grid
---import Misc (flatten)
---import Point
---import RealFunction
---import Tetrahedron
---import ThreeDimensional
+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 MRI
+import Values (drop_z, zoom_shape)
 
+main :: IO ()
+main = 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_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
 
---find_point_value :: RealFunction Point
---find_point_value p = poly p
---    where
---      g0 = make_grid 1 trilinear
---      the_cubes = flatten (cubes g0)
---      good_cubes = filter ((flip contains_point) p) the_cubes
---       target_cube = head good_cubes
---       good_tets = filter ((flip contains_point) p) (tetrahedrons target_cube)
---       target_tetrahedron = head good_tets
---       poly = polynomial target_tetrahedron
 
-main :: IO ()
-main = putStrLn "Hello, World."
+in_file :: FilePath
+in_file = "./data/mri.bin"
+
+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
+
+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