]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Main.hs
src/Main.hs: make two import lists explicit.
[spline3.git] / src / Main.hs
index 6848ff86264c3fc461e554cc2067cd6f312db2d4..ab37ca558f009bd30d5ac610e117f9282836442f 100644 (file)
@@ -1,19 +1,21 @@
 {-# 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 CommandLine (Args(..), apply_args)
-import ExitCodes
-import Grid (zoom)
+import Data.Maybe ( fromJust )
+import GHC.Conc ( getNumProcessors, setNumCapabilities )
+import System.IO ( hPutStrLn, stderr )
+import System.Exit (
+  ExitCode( ExitFailure ),
+  exitSuccess,
+  exitWith )
+
+import CommandLine ( Args(..), apply_args )
+import ExitCodes ( exit_arg_not_positive, exit_arg_out_of_bounds )
+import Grid ( zoom )
 import Volumetric (
   bracket_array,
   flip_x,
@@ -23,8 +25,7 @@ import Volumetric (
   swap_bytes,
   write_values_to_bmp,
   write_word16s,
-  z_slice
-  )
+  z_slice )
 
 
 validate_args :: Args -> IO ()
@@ -66,20 +67,17 @@ main = do
   num_procs <- getNumProcessors
   setNumCapabilities num_procs
 
-  -- Determine whether we're doing 2d or 3d. If we're given a slice,
-  -- assume 2d.
   let shape = (R.Z R.:. depth R.:. height R.:. width) :: R.DIM3
 
-  if (isJust slice) then
-    main2d args shape
-  else
-    main3d args shape
+  -- Determine whether we're doing 2d or 3d. If we're given a slice,
+  -- assume 2d.
+  let main_function = case slice of
+                        Nothing -> main3d
+                        Just _  -> main2d
 
+  main_function args shape
   exitSuccess
 
-  where
-
-
 
 main3d :: Args -> R.DIM3 -> IO ()
 main3d Args{..} shape = do
@@ -98,7 +96,7 @@ main3d Args{..} shape = do
 
 main2d :: Args -> R.DIM3 -> IO ()
 main2d Args{..} shape = do
-  let zoom_factor = (1, scale, scale)
+  let zoom_factor = (1 :: Int, scale, scale)
   arr <- read_word16s input shape
   arrSlice <- R.computeUnboxedP
                $ z_slice (fromJust slice)
@@ -114,8 +112,8 @@ main2d Args{..} shape = do
   arrSlice0  <- R.computeUnboxedP $ z_slice 0 raw_output
 
   -- Make doubles from the thresholds which are given as Ints.
-  let lt = fromIntegral lower_threshold
-  let ut = fromIntegral upper_threshold
+  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