]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/MRI.hs
Bracket doubles instead of ints. This gives us /slightly/ more precision when bracket...
[spline3.git] / src / MRI.hs
index 040dcc2a521ed9553974bca43e8fe23df9a63541..2dd6f6592e6e3bb7ac8d1eefbe73a4764e3cf787 100644 (file)
@@ -21,10 +21,10 @@ mri_height = 256
 mri_shape :: DIM3
 mri_shape = (Z :. mri_depth :. mri_height :. mri_width)
 
-mri_lower_threshold :: Int
+mri_lower_threshold :: Double
 mri_lower_threshold = 1400
 
-mri_upper_threshold :: Int
+mri_upper_threshold :: Double
 mri_upper_threshold = 2500
 
 mri_slice3d :: DIM3
@@ -48,34 +48,45 @@ read_word16s path = do
 
 
 {-# INLINE bracket #-}
-bracket :: Int -> Int -> Int -> Word16
-bracket low high x
-        | x < low      = 0
-        | x > high     = 255
-        | otherwise    = truncate (r * 255)
+bracket :: Double -> Word16
+bracket x
+        | x < mri_lower_threshold      = 0
+        | x > mri_upper_threshold      = 255
+        | otherwise                    = truncate (r * 255)
             where
-              numerator = fromIntegral (x - low) :: Double
-              denominator = fromIntegral (high - low) :: Double
+              numerator = x - mri_lower_threshold
+              denominator = mri_upper_threshold - mri_lower_threshold
               r = numerator/denominator
 
 
 {-# INLINE flip16 #-}
 flip16 :: Word16 -> Word16
-flip16 xx = 
+flip16 xx =
   shift xx 8 .|. (shift xx (-8) .&. 0x00ff)
 
 
-bracket_array :: (Shape sh) => (RawData sh) -> (RawData sh)
+swap_bytes :: (Shape sh) => (RawData sh) -> (RawData sh)
+swap_bytes arr =
+    R.force $ R.map flip16 arr
+
+bracket_array :: (Shape sh) => (Values sh) -> (RawData sh)
 bracket_array arr =
-  R.map (bracket mri_lower_threshold mri_upper_threshold . fromIntegral . flip16) arr
+  R.force $ R.map f arr
+  where
+    f = bracket
+
 
 flip_y :: RawData3D -> RawData3D
 flip_y arr =
-  R.traverse arr id (\get (Z :. z :. y :. x) -> get (Z :. z :. (mri_height - 1) - y :. x))
+  R.force $ R.traverse arr id
+              (\get (Z :. z :. y :. x) ->
+                   get (Z :. z :. (mri_height - 1) - y :. x))
 
 flip_x :: RawData3D -> RawData3D
 flip_x arr =
-  R.traverse arr id (\get (Z :. z :. y :. x) -> get (Z :. z :. y :. (mri_width - 1) - x))
+  R.force $ R.traverse arr id
+              (\get (Z :. z :. y :. x) ->
+                   get (Z :. z :. y :. (mri_width - 1) - x))
 
 write_word16s :: (Shape sh) => FilePath -> (RawData sh) -> IO ()
 write_word16s = R.writeArrayToStorableFile