]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/MRI.hs
Use lenient comparisons in two failing tests.
[spline3.git] / src / MRI.hs
index f63c729797cbdba81937736338506070de3c7bcc..d7410912f43ef5431376780e0123f754ac3aeb16 100644 (file)
@@ -20,11 +20,13 @@ where
 
 import Data.Word
 import Data.Bits
-import Data.Array.Repa                  as R
-import Data.Array.Repa.Repr.Unboxed     as R
-import Data.Array.Repa.IO.Binary        as R
+import Data.Array.Repa                          as R
+import Data.Array.Repa.Eval                     as R (now)
+import Data.Array.Repa.Repr.Unboxed             as R
+import Data.Array.Repa.IO.Binary                as R
 import Data.Array.Repa.Algorithms.ColorRamp     as R
-import Data.Array.Repa.IO.BMP           as R (writeImageToBMP)
+import Data.Array.Repa.Operators.Traversal      as R (unsafeTraverse)
+import Data.Array.Repa.IO.BMP                   as R (writeImageToBMP)
 
 import Values
 
@@ -64,8 +66,9 @@ type ColorData sh = Array U sh RGB
 read_word16s :: FilePath -> IO RawData3D
 read_word16s path = do
   arr <- R.readArrayFromStorableFile path mri_shape
-  arr'   <- now $ R.copy arr
-  return arr'
+  c   <- R.copyP arr
+  now $ c
+
 
 
 bracket :: Double -> Word16
@@ -87,19 +90,19 @@ flip16 xx =
 {-# INLINE swap_bytes #-}
 swap_bytes :: (Shape sh, Repr r Word16) => Array r sh Word16
              -> Array D sh Word16
-swap_bytes arr =
-  R.map flip16 arr
+swap_bytes =
+  R.map flip16
 
 
 bracket_array :: Shape sh => Values sh -> Array D sh Word16
-bracket_array arr =
-  R.map bracket arr
+bracket_array =
+  R.map bracket
 
 
 {-# INLINE round_array #-}
 round_array :: Shape sh => Values sh -> Array D sh Word16
-round_array arr =
-  R.map round arr
+round_array =
+  R.map round
 
 
 flip_y :: Repr r Word16 => Array r DIM3 Word16 -> Array D DIM3 Word16
@@ -121,9 +124,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.compute $ 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 =
@@ -147,8 +154,9 @@ z_slice n arr =
 
 
 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.compute $ R.map fromIntegral arr_bracketed