]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/MRI.hs
Use cmdargs to parse command-line arguments.
[spline3.git] / src / MRI.hs
index 094991c2dac537b38e18bd992b7dfe90737ea726..1c244c1c81c8b738b95bcf5385d52290e536082a 100644 (file)
@@ -7,8 +7,6 @@
 module MRI (
   flip_x,
   flip_y,
-  mri_shape,
-  mri_slice3d,
   read_word16s,
   round_array,
   swap_bytes,
@@ -30,27 +28,12 @@ import Data.Array.Repa.IO.BMP                   as R (writeImageToBMP)
 
 import Values
 
-mri_depth :: Int
-mri_depth = 109
-
-mri_width :: Int
-mri_width = 256
-
-mri_height :: Int
-mri_height = 256
-
-mri_shape :: DIM3
-mri_shape = (Z :. mri_depth :. mri_height :. mri_width)
-
 mri_lower_threshold :: Double
 mri_lower_threshold = 1400
 
 mri_upper_threshold :: Double
 mri_upper_threshold = 2500
 
-mri_slice3d :: DIM3
-mri_slice3d = (Z :. 1 :. mri_height  :. mri_width)
-
 -- | RawData is an array of words (16 bits), as contained in the MRI
 --   data files.
 type RawData sh = Array U sh Word16
@@ -63,10 +46,11 @@ type ColorData sh = Array U sh RGB
 
 
 {-# INLINE read_word16s #-}
-read_word16s :: FilePath -> IO RawData3D
-read_word16s path = do
+read_word16s :: FilePath -> DIM3 -> IO RawData3D
+read_word16s path mri_shape = do
   arr <- R.readArrayFromStorableFile path mri_shape
-  now $ R.copyS arr
+  c   <- R.copyP arr
+  now $ c
 
 
 
@@ -87,7 +71,7 @@ flip16 xx =
 
 
 {-# INLINE swap_bytes #-}
-swap_bytes :: (Shape sh, Repr r Word16) => Array r sh Word16
+swap_bytes :: (Shape sh, Source r Word16) => Array r sh Word16
              -> Array D sh Word16
 swap_bytes =
   R.map flip16
@@ -104,17 +88,17 @@ round_array =
   R.map round
 
 
-flip_y :: Repr r Word16 => Array r DIM3 Word16 -> Array D DIM3 Word16
-flip_y arr =
+flip_y :: Source r Word16 => Int -> Array r DIM3 Word16 -> Array D DIM3 Word16
+flip_y height arr =
   R.unsafeTraverse arr id
               (\get (Z :. z :. y :. x) ->
-                   get (Z :. z :. (mri_height - 1) - y :. x))
+                   get (Z :. z :. (height - 1) - y :. x))
 
-flip_x :: Repr r Word16 => Array r DIM3 Word16 -> Array D DIM3 Word16
-flip_x arr =
+flip_x :: Source r Word16 => Int -> Array r DIM3 Word16 -> Array D DIM3 Word16
+flip_x width arr =
   R.unsafeTraverse arr id
               (\get (Z :. z :. y :. x) ->
-                   get (Z :. z :. y :. (mri_width - 1) - x))
+                   get (Z :. z :. y :. (width - 1) - x))
 
 
 {-# INLINE write_word16s #-}
@@ -123,9 +107,13 @@ write_word16s = R.writeArrayToStorableFile
 
 
 
-values_to_colors :: (Shape sh) => (Values sh) -> (ColorData sh)
+--
+-- Instead of IO, we could get away with a generic monad 'm'
+-- here. However, /we/ only call this function from within IO.
+--
+values_to_colors :: (Shape sh) => (Values sh) -> IO (ColorData sh)
 values_to_colors arr =
-  R.computeS $ R.map (truncate_rgb . ramp_it) arr
+  R.computeUnboxedP $ R.map (truncate_rgb . ramp_it) arr
   where
     ramp_it :: Double -> (Double, Double, Double)
     ramp_it x =
@@ -143,14 +131,15 @@ values_to_colors arr =
         b' = truncate (b * 255)
 
 
-z_slice :: (R.Unbox a, Repr r a) => Int -> Array r DIM3 a -> Array D DIM2 a
+z_slice :: (R.Unbox a, Source r a) => Int -> Array r DIM3 a -> Array D DIM2 a
 z_slice n arr =
   slice arr (Any :. n :. All :. All)
 
 
 write_values_slice_to_bitmap :: Values2D -> FilePath -> IO ()
-write_values_slice_to_bitmap v3d path =
+write_values_slice_to_bitmap v3d path = do
+  values <- R.computeUnboxedP $ R.map fromIntegral arr_bracketed
+  colors <- values_to_colors $ values
   R.writeImageToBMP path colors
   where
     arr_bracketed = bracket_array v3d
-    colors = values_to_colors $ R.computeS $ R.map fromIntegral arr_bracketed