add a function for running with args, reading config file

This commit is contained in:
Filip Gralinski 2015-08-23 07:40:37 +02:00 committed by Filip Gralinski
parent 1ca75163b0
commit bbf6b1ec43
7 changed files with 61 additions and 8 deletions

View File

@ -46,6 +46,7 @@ test-suite geval-test
, geval
, hspec
, HUnit
, optparse-applicative
ghc-options: -threaded -rtsopts -with-rtsopts=-N
default-language: Haskell2010

View File

@ -10,7 +10,8 @@ module GEval
defaultTestName,
defaultOutFile,
defaultExpectedFile,
defaultMetric
defaultMetric,
getExpectedDirectory
) where
import Data.Conduit
@ -51,6 +52,10 @@ data GEvalSpecification = GEvalSpecification
gesExpectedFile :: String,
gesMetric :: Metric }
getExpectedDirectory :: GEvalSpecification -> FilePath
getExpectedDirectory spec = fromMaybe outDirectory $ gesExpectedDirectory spec
where outDirectory = gesOutDirectory spec
data GEvalOptions = GEvalOptions
{ geoInit :: Bool,
geoSpec :: GEvalSpecification }
@ -98,7 +103,7 @@ geval gevalSpec = do
outFilePath = outTestDirectory </> (gesOutFile gevalSpec)
expectedTestDirectory = expectedDirectory </> testName
outTestDirectory = outDirectory </> testName
expectedDirectory = fromMaybe outDirectory $ gesExpectedDirectory gevalSpec
expectedDirectory = getExpectedDirectory gevalSpec
outDirectory = gesOutDirectory gevalSpec
testName = gesTestName gevalSpec
metric = gesMetric gevalSpec

View File

@ -3,6 +3,11 @@ module OptionsParser
runGEval) where
import Options.Applicative
import qualified System.Directory as D
import System.FilePath
import Data.Maybe
import System.IO
import GEval
fullOptionsParser = info (helper <*> optionsParser)
@ -57,11 +62,35 @@ metricReader = option auto
<> metavar "METRIC"
<> help "Metric to be used" )
configFileName :: FilePath
configFileName = "config.txt"
runGEval :: [String] -> IO (Either (ParserResult GEvalOptions) (Maybe MetricValue))
runGEval args =
runGEval = runGEval' True
runGEval' :: Bool -> [String] -> IO (Either (ParserResult GEvalOptions) (Maybe MetricValue))
runGEval' readOptsFromConfigFile args =
case parserResult of
Success opts -> do
val <- geval $ geoSpec opts
return $ Right $ Just val
Success opts -> if readOptsFromConfigFile then
attemptToReadOptsFromConfigFile args opts else
Right <$> runGEval'' opts
otherwise -> return $ Left parserResult
where parserResult = execParserPure (prefs idm) fullOptionsParser args
attemptToReadOptsFromConfigFile :: [String] -> GEvalOptions -> IO (Either (ParserResult GEvalOptions) (Maybe MetricValue))
attemptToReadOptsFromConfigFile args opts = do
configExists <- D.doesFileExist configFilePath
if configExists then do
configH <- openFile configFilePath ReadMode
contents <- hGetContents configH
runGEval' False ((words contents) ++ args)
else
runGEval' False args
where configFilePath = (getExpectedDirectory $ geoSpec opts) </> configFileName
runGEval'' :: GEvalOptions -> IO (Maybe MetricValue)
runGEval'' opts = do
val <- geval $ geoSpec opts
return $ Just val

View File

@ -1,13 +1,24 @@
import Test.Hspec
import GEval
import OptionsParser
import Options.Applicative
import qualified Test.HUnit as HU
main :: IO ()
main = hspec $ do
describe "mean square error" $ do
describe "root mean square error" $ do
it "simple test" $ do
geval (defaultGEvalSpecification {gesExpectedDirectory=Just "test/mse-simple/mse-simple", gesOutDirectory="test/mse-simple/mse-simple-solution"}) `shouldReturnAlmost` 0.64549722436790
geval (defaultGEvalSpecification {gesExpectedDirectory=Just "test/rmse-simple/rmse-simple", gesOutDirectory="test/rmse-simple/rmse-simple-solution"}) `shouldReturnAlmost` 0.64549722436790
describe "mean square error" $ do
it "simple test with arguments" $ do
((runGEval ["--expected-directory",
"test/mse-simple/mse-simple",
"--out-directory",
"test/mse-simple/mse-simple-solution"]) >>= extractVal) `shouldReturnAlmost` 0.4166666666666667
extractVal :: (Either (ParserResult GEvalOptions) (Maybe MetricValue)) -> IO MetricValue
extractVal (Right (Just val)) = return val
class AEq a where
(=~) :: a -> a -> Bool

View File

@ -0,0 +1 @@
--metric MSE

View File

@ -0,0 +1,3 @@
3.0
3.0
2.0
1 3.0
2 3.0
3 2.0

View File

@ -0,0 +1,3 @@
2.0
3.0
1.5
1 2.0
2 3.0
3 1.5