]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Main.hs
src/Main.hs: add an explicit export list.
[spline3.git] / src / Main.hs
index 951c9c36bf7a819b51f758de42a158484e00d90b..ae8c5e39c703491449d01bc95058f2cb67b61c80 100644 (file)
@@ -1,29 +1,28 @@
 {-# LANGUAGE RecordWildCards, DoAndIfThenElse #-}
 
-module Main
+module Main (main)
 where
 
-import Data.Maybe (fromJust)
-import Control.Monad (when)
+import Control.Monad ( when )
 import qualified Data.Array.Repa as R
-import Data.Maybe (isJust)
-import GHC.Conc (getNumProcessors, setNumCapabilities)
-import System.IO (hPutStrLn, stderr)
-import System.Exit (exitSuccess, exitWith, ExitCode(..))
+import Data.Maybe ( fromJust )
+import GHC.Conc ( getNumProcessors, setNumCapabilities )
+import System.IO ( hPutStrLn, stderr )
+import System.Exit ( exitSuccess, exitWith, ExitCode(..) )
 
-import CommandLine (Args(..), apply_args)
+import CommandLine ( Args(..), apply_args )
 import ExitCodes
-import Grid (zoom)
-import MRI (
+import Grid ( zoom )
+import 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
-  )
+  z_slice )
 
 
 validate_args :: Args -> IO ()
@@ -65,51 +64,58 @@ main = do
   num_procs <- getNumProcessors
   setNumCapabilities num_procs
 
+  let shape = (R.Z R.:. depth R.:. height R.:. width) :: R.DIM3
+
   -- Determine whether we're doing 2d or 3d. If we're given a slice,
   -- assume 2d.
-  let mri_shape = (R.Z R.:. depth R.:. height R.:. width) :: R.DIM3
-
-  if (isJust slice) then
-    main2d args mri_shape
-  else
-    main3d args mri_shape
+  let main_function = case slice of
+                        Nothing -> main3d
+                        Just _  -> main2d
 
+  main_function args shape
   exitSuccess
 
-  where
-
-
 
 main3d :: Args -> R.DIM3 -> IO ()
-main3d Args{..} mri_shape = do
+main3d Args{..} shape = do
   let zoom_factor = (scale, scale, scale)
-  arr <- read_word16s input mri_shape
-  let arr'          = swap_bytes arr
-  let arrMRI        = R.reshape mri_shape arr'
-  dbl_data <- R.computeUnboxedP $ R.map fromIntegral arrMRI
+  arr <- read_word16s input shape
+  let arr_swapped = swap_bytes arr
+  let arr_shaped  = R.reshape shape arr_swapped
+  dbl_data <- R.computeUnboxedP $ R.map fromIntegral arr_shaped
   raw_output <- zoom dbl_data zoom_factor
-  word16_output <- R.computeUnboxedP $ round_array raw_output
-  write_word16s output word16_output
+  let word16_output = round_array raw_output
+  -- Switch the bytes order back to what it was. This lets us use the
+  -- same program to view the input/output data.
+  swapped_output <- R.computeUnboxedP $ swap_bytes word16_output
+  write_word16s output swapped_output
 
 
 main2d :: Args -> R.DIM3 -> IO ()
-main2d Args{..} mri_shape = do
-  let zoom_factor = (1, scale, scale)
-  arr <- read_word16s input mri_shape
+main2d Args{..} shape = do
+  let zoom_factor = (1 :: Int, scale, scale)
+  arr <- read_word16s input shape
   arrSlice <- R.computeUnboxedP
                $ z_slice (fromJust slice)
                $ flip_x width
                $ flip_y height
                $ swap_bytes arr
-  let arrSlice' = R.reshape mri_slice3d arrSlice
+  let arrSlice' = R.reshape slice3d arrSlice
 
   -- If zoom isn't being inlined we need to extract the slice before hand,
   -- and convert it to the require formed.
-  dbl_data      <- R.computeUnboxedP $ R.map fromIntegral arrSlice'
-  raw_output    <- zoom dbl_data zoom_factor
-  arrSlice0     <- R.computeUnboxedP $ z_slice 0 raw_output
+  dbl_data   <- R.computeUnboxedP $ R.map fromIntegral arrSlice'
+  raw_output <- zoom dbl_data zoom_factor
+  arrSlice0  <- R.computeUnboxedP $ z_slice 0 raw_output
+
+  -- Make doubles from the thresholds which are given as Ints.
+  let lt = fromIntegral lower_threshold :: Double
+  let ut = fromIntegral upper_threshold :: Double
+
+  let arr_bracketed = bracket_array lt ut arrSlice0
+  values <- R.computeUnboxedP $ R.map fromIntegral arr_bracketed
+  write_values_to_bmp output values
 
-  write_values_slice_to_bitmap arrSlice0 output
   where
-    mri_slice3d :: R.DIM3
-    mri_slice3d = (R.Z R.:. 1 R.:. height  R.:. width)
+    slice3d :: R.DIM3
+    slice3d = (R.Z R.:. 1 R.:. height  R.:. width)