]> gitweb.michael.orlitzky.com - spline3.git/blobdiff - src/Main.hs
src/Main.hs: make two import lists explicit.
[spline3.git] / src / Main.hs
index 89ac4463d096b9138dad365a52e8a33b39028896..ab37ca558f009bd30d5ac610e117f9282836442f 100644 (file)
@@ -1,6 +1,6 @@
 {-# LANGUAGE RecordWildCards, DoAndIfThenElse #-}
 
-module Main
+module Main (main)
 where
 
 import Control.Monad ( when )
@@ -8,10 +8,13 @@ import qualified Data.Array.Repa as R
 import Data.Maybe ( fromJust )
 import GHC.Conc ( getNumProcessors, setNumCapabilities )
 import System.IO ( hPutStrLn, stderr )
-import System.Exit ( exitSuccess, exitWith, ExitCode(..) )
+import System.Exit (
+  ExitCode( ExitFailure ),
+  exitSuccess,
+  exitWith )
 
 import CommandLine ( Args(..), apply_args )
-import ExitCodes
+import ExitCodes ( exit_arg_not_positive, exit_arg_out_of_bounds )
 import Grid ( zoom )
 import Volumetric (
   bracket_array,
@@ -93,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)
@@ -109,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