]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Volumetric.hs
Move the last two MRI-specific variables out of MRI.hs and into the command-line...
[spline3.git] / src / Volumetric.hs
similarity index 73%
rename from src/MRI.hs
rename to src/Volumetric.hs
index 1c244c1c81c8b738b95bcf5385d52290e536082a..24bc13bb464ca524c0cfc280332c1b7e3ce87a5d 100644 (file)
@@ -1,16 +1,17 @@
 {-# LANGUAGE FlexibleContexts #-}
--- | The MRI module contains functionsd and definitions relevant (and
---   specific) to the MRI data files found at,
+-- | The Volumetric module contains functions for manipulating the
+--   volumetric data files found at,
 --
---   <http://graphics.stanford.edu/data/voldata/>
+--     <http://graphics.stanford.edu/data/voldata/>
 --
-module MRI (
+module Volumetric (
+  bracket_array,
   flip_x,
   flip_y,
   read_word16s,
   round_array,
   swap_bytes,
-  write_values_slice_to_bitmap,
+  write_values_to_bmp,
   write_word16s,
   z_slice
   )
@@ -28,14 +29,8 @@ import Data.Array.Repa.IO.BMP                   as R (writeImageToBMP)
 
 import Values
 
-mri_lower_threshold :: Double
-mri_lower_threshold = 1400
-
-mri_upper_threshold :: Double
-mri_upper_threshold = 2500
-
--- | RawData is an array of words (16 bits), as contained in the MRI
---   data files.
+-- | RawData is an array of words (16 bits), as contained in the
+--   volumetric data files.
 type RawData sh = Array U sh Word16
 
 -- | A specialization of the 'RawData' type, to three dimensions.
@@ -47,21 +42,21 @@ type ColorData sh = Array U sh RGB
 
 {-# INLINE read_word16s #-}
 read_word16s :: FilePath -> DIM3 -> IO RawData3D
-read_word16s path mri_shape = do
-  arr <- R.readArrayFromStorableFile path mri_shape
+read_word16s path shape = do
+  arr <- R.readArrayFromStorableFile path shape
   c   <- R.copyP arr
   now $ c
 
 
 
-bracket :: Double -> Word16
-bracket x
-        | x < mri_lower_threshold      = 0
-        | x > mri_upper_threshold      = 255
+bracket :: Double -> Double -> Double -> Word16
+bracket lower_threshold upper_threshold x
+        | x < lower_threshold      = 0
+        | x > upper_threshold      = 255
         | otherwise                    = truncate (r * 255)
             where
-              numerator = x - mri_lower_threshold
-              denominator = mri_upper_threshold - mri_lower_threshold
+              numerator = x - lower_threshold
+              denominator = upper_threshold - lower_threshold
               r = numerator/denominator
 
 
@@ -77,9 +72,9 @@ swap_bytes =
   R.map flip16
 
 
-bracket_array :: Shape sh => Values sh -> Array D sh Word16
-bracket_array =
-  R.map bracket
+bracket_array :: Shape sh => Double -> Double -> Values sh -> Array D sh Word16
+bracket_array lt ut =
+  R.map (bracket lt ut)
 
 
 {-# INLINE round_array #-}
@@ -131,15 +126,12 @@ values_to_colors arr =
         b' = truncate (b * 255)
 
 
+write_values_to_bmp :: FilePath -> Values2D -> IO ()
+write_values_to_bmp path values = do
+  colors <- values_to_colors values
+  R.writeImageToBMP path colors
+
+
 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 = do
-  values <- R.computeUnboxedP $ R.map fromIntegral arr_bracketed
-  colors <- values_to_colors $ values
-  R.writeImageToBMP path colors
-  where
-    arr_bracketed = bracket_array v3d