print params
This commit is contained in:
parent
9f5882719b
commit
0c6032d166
47
app/Main.hs
47
app/Main.hs
@ -2,6 +2,7 @@ module Main where
|
|||||||
|
|
||||||
import GEval.Core
|
import GEval.Core
|
||||||
import GEval.OptionsParser
|
import GEval.OptionsParser
|
||||||
|
import GEval.ParseParams
|
||||||
|
|
||||||
import System.Environment
|
import System.Environment
|
||||||
import Options.Applicative
|
import Options.Applicative
|
||||||
@ -15,7 +16,12 @@ import Data.Conduit.SmartSource
|
|||||||
|
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
|
||||||
import Data.List (intercalate)
|
import Data.List (intercalate, sort)
|
||||||
|
|
||||||
|
import qualified Data.Text as T
|
||||||
|
|
||||||
|
import Data.Map.Strict as M
|
||||||
|
import Data.Set as S
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
@ -33,16 +39,37 @@ showTheResult opts multipleResults = showTable opts multipleResults
|
|||||||
|
|
||||||
showTable :: GEvalOptions -> [(SourceSpec, [MetricValue])] -> IO ()
|
showTable :: GEvalOptions -> [(SourceSpec, [MetricValue])] -> IO ()
|
||||||
showTable opts multipleResults = do
|
showTable opts multipleResults = do
|
||||||
case metrics of
|
let params = Prelude.map (\(ss, _) -> parseParamsFromSourceSpec ss) multipleResults
|
||||||
[singleMetric] -> return ()
|
|
||||||
[] -> error "no metric given"
|
let paramNames =
|
||||||
metrics -> putStrLn $ intercalate "\t" ("File name" : map show metrics)
|
sort
|
||||||
mapM_ (\entry -> putStrLn $ formatTableEntry opts entry) multipleResults
|
$ S.toList
|
||||||
|
$ S.unions
|
||||||
|
$ Prelude.map (\(OutputFileParsed _ m) -> M.keysSet m)
|
||||||
|
$ params
|
||||||
|
|
||||||
|
case getHeader paramNames metrics of
|
||||||
|
Just header -> putStrLn header
|
||||||
|
Nothing -> return ()
|
||||||
|
|
||||||
|
mapM_ (\entry -> putStrLn $ formatTableEntry opts paramNames entry) $ zip multipleResults params
|
||||||
where metrics = gesMetrics $ geoSpec opts
|
where metrics = gesMetrics $ geoSpec opts
|
||||||
|
|
||||||
formatTableEntry :: GEvalOptions -> (SourceSpec, [MetricValue]) -> String
|
getHeader :: [T.Text] -> [Metric] -> Maybe String
|
||||||
formatTableEntry opts (sourceSpec, metrics) = intercalate "\t" (formatSourceSpec sourceSpec : vals)
|
getHeader [] [singleMetric] = Nothing
|
||||||
where vals = map (formatTheResult (gesPrecision $ geoSpec opts)) metrics
|
getHeader [] [] = error "no metric given"
|
||||||
|
getHeader [] metrics = Just $ intercalate "\t" ("File name" : Prelude.map show metrics)
|
||||||
|
getHeader params metrics = Just $ intercalate "\t" (Prelude.map T.unpack params
|
||||||
|
++ Prelude.map show metrics)
|
||||||
|
|
||||||
|
formatTableEntry :: GEvalOptions -> [T.Text] -> ((SourceSpec, [MetricValue]), OutputFileParsed) -> String
|
||||||
|
formatTableEntry opts paramNames ((sourceSpec, metrics), ofParsed) = intercalate "\t" ((initialColumns paramNames sourceSpec ofParsed) ++ vals)
|
||||||
|
where vals = Prelude.map (formatTheResult (gesPrecision $ geoSpec opts)) metrics
|
||||||
|
|
||||||
|
initialColumns :: [T.Text] -> SourceSpec -> OutputFileParsed -> [String]
|
||||||
|
initialColumns [] sourceSpec ofParsed = [formatSourceSpec sourceSpec]
|
||||||
|
initialColumns params sourceSpec (OutputFileParsed _ paramMap) =
|
||||||
|
Prelude.map (\p -> T.unpack $ M.findWithDefault (T.pack "") p paramMap) params
|
||||||
|
|
||||||
showTheResult' :: GEvalOptions -> [MetricValue] -> IO ()
|
showTheResult' :: GEvalOptions -> [MetricValue] -> IO ()
|
||||||
-- do not show the metric if just one was given
|
-- do not show the metric if just one was given
|
||||||
@ -50,7 +77,7 @@ showTheResult' opts [val] = putStrLn $ formatTheResult (gesPrecision $ geoSpec o
|
|||||||
showTheResult' opts [] = do
|
showTheResult' opts [] = do
|
||||||
hPutStrLn stderr "no metric given, use --metric option"
|
hPutStrLn stderr "no metric given, use --metric option"
|
||||||
exitFailure
|
exitFailure
|
||||||
showTheResult' opts vals = mapM_ putStrLn $ map (formatTheMetricAndResult (gesPrecision $ geoSpec opts)) $ zip (gesMetrics $ geoSpec opts) vals
|
showTheResult' opts vals = mapM_ putStrLn $ Prelude.map (formatTheMetricAndResult (gesPrecision $ geoSpec opts)) $ zip (gesMetrics $ geoSpec opts) vals
|
||||||
|
|
||||||
formatSourceSpec :: SourceSpec -> String
|
formatSourceSpec :: SourceSpec -> String
|
||||||
formatSourceSpec (FilePathSpec fp) = dropExtensions $ takeFileName fp
|
formatSourceSpec (FilePathSpec fp) = dropExtensions $ takeFileName fp
|
||||||
|
@ -75,6 +75,9 @@ executable geval
|
|||||||
, optparse-applicative
|
, optparse-applicative
|
||||||
, fgl
|
, fgl
|
||||||
, filepath
|
, filepath
|
||||||
|
, containers
|
||||||
|
, unordered-containers
|
||||||
|
, text
|
||||||
default-language: Haskell2010
|
default-language: Haskell2010
|
||||||
|
|
||||||
test-suite geval-test
|
test-suite geval-test
|
||||||
|
@ -1,6 +1,8 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
module GEval.ParseParams(parseParamsFromFilePath,OutputFileParsed(..))
|
module GEval.ParseParams(parseParamsFromFilePath,
|
||||||
|
parseParamsFromSourceSpec,
|
||||||
|
OutputFileParsed(..))
|
||||||
where
|
where
|
||||||
|
|
||||||
import Data.Map.Strict as M
|
import Data.Map.Strict as M
|
||||||
@ -9,9 +11,15 @@ import Data.Attoparsec.Text
|
|||||||
|
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
|
||||||
|
import Data.Conduit.SmartSource (SourceSpec(..), recoverPath)
|
||||||
|
|
||||||
data OutputFileParsed = OutputFileParsed String (M.Map Text Text)
|
data OutputFileParsed = OutputFileParsed String (M.Map Text Text)
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
|
||||||
|
parseParamsFromSourceSpec :: SourceSpec -> OutputFileParsed
|
||||||
|
parseParamsFromSourceSpec (FilePathSpec filePath) = parseParamsFromFilePath filePath
|
||||||
|
parseParamsFromSourceSpec spec = OutputFileParsed (recoverPath spec) M.empty
|
||||||
|
|
||||||
parseParamsFromFilePath :: FilePath -> OutputFileParsed
|
parseParamsFromFilePath :: FilePath -> OutputFileParsed
|
||||||
parseParamsFromFilePath filePath = parseParamsFromBaseName fileBaseName
|
parseParamsFromFilePath filePath = parseParamsFromBaseName fileBaseName
|
||||||
where fileBaseName = dropExtensions $ takeBaseName filePath
|
where fileBaseName = dropExtensions $ takeBaseName filePath
|
||||||
|
Loading…
Reference in New Issue
Block a user