start parsing options

This commit is contained in:
Filip Gralinski 2015-08-22 00:00:46 +02:00 committed by Filip Gralinski
parent 6290250125
commit 759c258ecb
3 changed files with 70 additions and 3 deletions

View File

@ -3,8 +3,62 @@ module Main where
import GEval import GEval
import System.Environment import System.Environment
import Options.Applicative
fullOptionsParser = info (helper <*> optionsParser)
(fullDesc
<> progDesc "Run evaluation for tests in Gonito platform"
<> header "geval - stand-alone evaluation tool for tests in Gonito platform")
optionsParser :: Parser GEvalOptions
optionsParser = GEvalOptions
<$> switch
( long "init"
<> help "Init a sample Gonito challange rather than run an evaluation" )
<*> specParser
specParser :: Parser GEvalSpecification
specParser = GEvalSpecification
<$> strOption
( long "out-directory"
<> value defaultOutDirectory
<> showDefault
<> metavar "OUT-DIRECTORY"
<> help "Directory with test results to be evaluated" )
<*> optional (strOption
( long "expected-directory"
<> metavar "EXPECTED-DIRECTORY"
<> help "Directory with expected test results (if not specified the same as OUT-DIRECTORY)" ))
<*> strOption
( long "test-name"
<> value defaultTestName
<> showDefault
<> metavar "NAME"
<> help "Test name (i.e. subdirectory with results or expected results)" )
<*> strOption
( long "out-file"
<> value defaultOutFile
<> showDefault
<> metavar "OUT"
<> help "The name of the file to be evaluated" )
<*> strOption
( long "expected-file"
<> value defaultExpectedFile
<> showDefault
<> metavar "EXPECTED"
<> help "The name of the file with expected results" )
<*> metricReader
metricReader :: Parser Metric
metricReader = option auto
( long "metric"
<> value defaultMetric
<> showDefault
<> metavar "METRIC"
<> help "Metric to be used" )
main :: IO () main :: IO ()
main = do main = do
[expectedFilePath, outFilePath] <- getArgs opts <- execParser fullOptionsParser
result <- gevalCore MSE expectedFilePath outFilePath result <- geval $ geoSpec opts
print $ result print $ result

View File

@ -31,6 +31,7 @@ executable geval-exe
ghc-options: -threaded -rtsopts -with-rtsopts=-N ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends: base build-depends: base
, geval , geval
, optparse-applicative
default-language: Haskell2010 default-language: Haskell2010
test-suite geval-test test-suite geval-test

View File

@ -3,7 +3,13 @@ module GEval
gevalCore, gevalCore,
Metric(..), Metric(..),
GEvalSpecification(..), GEvalSpecification(..),
defaultGEvalSpecification GEvalOptions(..),
defaultGEvalSpecification,
defaultOutDirectory,
defaultTestName,
defaultOutFile,
defaultExpectedFile,
defaultMetric
) where ) where
import Data.Conduit import Data.Conduit
@ -20,6 +26,7 @@ import System.FilePath
import Data.Maybe import Data.Maybe
data Metric = MSE | BLEU data Metric = MSE | BLEU
deriving (Show, Read)
defaultOutDirectory = "." defaultOutDirectory = "."
defaultTestName = "test-A" defaultTestName = "test-A"
@ -29,6 +36,7 @@ defaultExpectedFile = "expected.tsv"
defaultMetric :: Metric defaultMetric :: Metric
defaultMetric = MSE defaultMetric = MSE
data GEvalSpecification = GEvalSpecification data GEvalSpecification = GEvalSpecification
{ gesOutDirectory :: String, { gesOutDirectory :: String,
gesExpectedDirectory :: Maybe String, gesExpectedDirectory :: Maybe String,
@ -37,6 +45,10 @@ data GEvalSpecification = GEvalSpecification
gesExpectedFile :: String, gesExpectedFile :: String,
gesMetric :: Metric } gesMetric :: Metric }
data GEvalOptions = GEvalOptions
{ geoInit :: Bool,
geoSpec :: GEvalSpecification }
defaultGEvalSpecification = GEvalSpecification { defaultGEvalSpecification = GEvalSpecification {
gesOutDirectory = defaultOutDirectory, gesOutDirectory = defaultOutDirectory,