{-# INLINE flip16 #-}
 flip16 :: Word16 -> Word16
-flip16 xx = 
+flip16 xx =
   shift xx 8 .|. (shift xx (-8) .&. 0x00ff)
 
 
+swap_bytes :: (Shape sh) => (RawData sh) -> (RawData sh)
+swap_bytes arr =
+    R.force $ R.map flip16 arr
+
 bracket_array :: (Shape sh) => (RawData 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 mri_lower_threshold mri_upper_threshold) . fromIntegral
+
 
 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