]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/MRI.hs
Un-inline two functions.
[spline3.git] / src / MRI.hs
index 5f2ceea483437bc7a9216f066e86e1d32867288d..157b89972aa8dfe817951805cdede467714e4918 100644 (file)
@@ -48,7 +48,6 @@ read_word16s path = do
   return arr
 
 
-{-# INLINE bracket #-}
 bracket :: Double -> Word16
 bracket x
         | x < mri_lower_threshold      = 0
@@ -60,7 +59,6 @@ bracket x
               r = numerator/denominator
 
 
-{-# INLINE flip16 #-}
 flip16 :: Word16 -> Word16
 flip16 xx =
   shift xx 8 .|. (shift xx (-8) .&. 0x00ff)
@@ -70,11 +68,15 @@ 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.force $ R.map f arr
-  where
-    f = bracket
+  R.force $ R.map bracket arr
+
+
+round_array :: (Shape sh) => (Values sh) -> (RawData sh)
+round_array arr =
+  R.force $ R.map round arr
 
 
 flip_y :: RawData3D -> RawData3D
@@ -170,13 +172,3 @@ write_values_slice_to_bitmap v3d path =
     routput = R.map (\(red, _,     _)    -> red)   colors
     goutput = R.map (\(_,   green, _)    -> green) colors
     boutput = R.map (\(_,   _,     blue) -> blue)  colors
-
-
-write_values_chunk_to_bitmap :: Values3D -> FilePath -> IO ()
-write_values_chunk_to_bitmap v3d path
-  | zdim /= 3 = error "not a 3xMxN chunk"
-  | otherwise = write_values_slice_to_bitmap target_slice path
-  where
-    (Z :. zdim :. _ :. _) = extent v3d
-    target_slice = z_slice 1 v3d
-