{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, RecordWildCards #-}
module Gauge.Main.Options
( defaultConfig
, makeSelector
, parseWith
, describe
, versionInfo
, Config (..)
, Verbosity (..)
, DisplayMode (..)
, MatchType (..)
, Mode (..)
) where
import Data.Monoid
import Gauge.Measurement
(validateAccessors, defaultMinSamplesNormal,
defaultMinSamplesQuick, defaultTimeLimitNormal,
defaultTimeLimitQuick)
import Gauge.Time (MilliSeconds(..))
import Data.Char (isSpace, toLower)
import Data.List (foldl')
import Data.Version (showVersion)
import System.Console.GetOpt
import Paths_gauge (version)
import Data.Data (Data, Typeable)
import Data.Int (Int64)
import Data.List (isInfixOf, isPrefixOf)
import GHC.Generics (Generic)
data Verbosity = Quiet
| Normal
| Verbose
deriving (Eq, Ord, Bounded, Enum, Read, Show, Typeable, Data,
Generic)
data MatchType = Exact
| Prefix
| Pattern
| IPattern
deriving (Eq, Ord, Bounded, Enum, Read, Show, Typeable, Data,
Generic)
data Mode = List
| Version
| Help
| DefaultMode
deriving (Eq, Read, Show, Typeable, Data, Generic)
data DisplayMode =
Condensed
| StatsTable
deriving (Eq, Read, Show, Typeable, Data, Generic)
data Config = Config {
confInterval :: Maybe Double
, forceGC :: Bool
, timeLimit :: Maybe Double
, minSamples :: Maybe Int
, minDuration :: MilliSeconds
, includeFirstIter :: Bool
, quickMode :: Bool
, measureOnly :: Maybe FilePath
, measureWith :: Maybe FilePath
, resamples :: Int
, regressions :: [([String], String)]
, rawDataFile :: Maybe FilePath
, reportFile :: Maybe FilePath
, csvFile :: Maybe FilePath
, csvRawFile :: Maybe FilePath
, jsonFile :: Maybe FilePath
, junitFile :: Maybe FilePath
, verbosity :: Verbosity
, template :: FilePath
, iters :: Maybe Int64
, match :: MatchType
, mode :: Mode
, displayMode :: DisplayMode
} deriving (Eq, Read, Show, Typeable, Data, Generic)
defaultMinDuration :: MilliSeconds
defaultMinDuration = MilliSeconds 30
defaultConfig :: Config
defaultConfig = Config
{ confInterval = Nothing
, forceGC = True
, timeLimit = Nothing
, minSamples = Nothing
, minDuration = defaultMinDuration
, includeFirstIter = False
, quickMode = False
, measureOnly = Nothing
, measureWith = Nothing
, resamples = 1000
, regressions = []
, rawDataFile = Nothing
, reportFile = Nothing
, csvFile = Nothing
, csvRawFile = Nothing
, jsonFile = Nothing
, junitFile = Nothing
, verbosity = Normal
, template = "default"
, iters = Nothing
, match = Prefix
, mode = DefaultMode
, displayMode = StatsTable
}
makeSelector :: MatchType
-> [String]
-> (String -> Bool)
makeSelector matchKind args =
case matchKind of
Exact -> \b -> null args || any (== b) args
Prefix -> \b -> null args || any (`isPrefixOf` b) args
Pattern -> \b -> null args || any (`isInfixOf` b) args
IPattern -> \b -> null args || any (`isInfixOf` map toLower b) (map (map toLower) args)
parseWith :: Config
-> [String]
-> (Config, [String])
parseWith start argv =
case getOpt Permute opts argv of
(o,n,[] ) -> (foldl' (flip id) start o, n)
(_,_,errs) -> optionError (concat errs ++ usageInfo header opts)
opts :: [OptDescr (Config -> Config)]
opts =
[ Option "I" ["ci"] (ReqArg setCI "CI") "Confidence interval"
, Option "G" ["no-gc"] (NoArg setNoGC) "Do not collect garbage between iterations"
, Option "L" ["time-limit"] (ReqArg setTimeLimit "SECS") $
"Min seconds for each benchmark run, default is "
++ show defaultTimeLimitNormal ++ " in normal mode, "
++ show defaultTimeLimitQuick ++ " in quick mode"
, Option "" ["min-samples"] (ReqArg setMinSamples "COUNT") $
"Min no. of samples for each benchmark, default is "
++ show defaultMinSamplesNormal ++ " in normal mode, "
++ show defaultMinSamplesQuick ++ " in quick mode"
, Option "" ["min-duration"] (ReqArg setMinDuration "MILLISECS") $
"Min duration for each sample, default is "
++ show defaultMinDuration ++ ", when 0 stops after first iteration"
, Option "" ["include-first-iter"] (NoArg setIncludeFirst) "Do not discard the measurement of the first iteration"
, Option "q" ["quick"] (NoArg setQuickMode) "Perform a quick measurement and report results without statistical analysis"
, Option "" ["measure-only"] (fileArg setMeasureOnly) "Just measure the benchmark and place the raw data in the given file"
, Option "" ["measure-with"] (fileArg setMeasureProg) "Perform measurements in a separate process using this program."
, Option "" ["resamples"] (ReqArg setResamples "COUNT") "Number of boostrap resamples to perform"
, Option "" ["regress"] (ReqArg setRegressions "RESP:PRED..") "Regressions to perform"
, Option "" ["raw"] (fileArg setRaw) "File to write raw data to"
, Option "o" ["output"] (fileArg setOutput) "File to write report to"
, Option "" ["csvraw"] (fileArg setCSVRaw) "File to write CSV measurements to"
, Option "" ["csv"] (fileArg setCSV) "File to write CSV summary to"
, Option "" ["json"] (fileArg setJSON) "File to write JSON summary to"
, Option "" ["junit"] (fileArg setJUnit) "File to write JUnit summary to"
, Option "v" ["verbosity"] (ReqArg setVerbosity "LEVEL") "Verbosity level"
, Option "t" ["template"] (fileArg setTemplate) "Template to use for report"
, Option "n" ["iters"] (ReqArg setIters "ITERS") "Run benchmarks, don't analyse"
, Option "m" ["match"] (ReqArg setMatch "MATCH") $
"Benchmark match style: prefix (default), exact, pattern (substring), "
++ "or ipattern (case insensitive)"
, Option "l" ["list"] (NoArg $ setMode List) "List benchmarks"
, Option "" ["version"] (NoArg $ setMode Version) "Show version info"
, Option "s" ["small"] (NoArg $ setDisplayMode Condensed) "Set benchmark display to the minimum useful information"
, Option "h" ["help"] (NoArg $ setMode Help) "Show help"
]
where
fileArg f = ReqArg f "FILE"
setCI s v = v { confInterval = Just $ range 0.001 0.999 s }
setNoGC v = v { forceGC = False }
setTimeLimit s v = v { timeLimit = Just $ range 0.0 86400 s }
setMinSamples n v = v { minSamples = Just $ read n }
setMinDuration ms v = v { minDuration = MilliSeconds $ read ms }
setIncludeFirst v = v { includeFirstIter = True }
setQuickMode v = v { quickMode = True }
setMeasureOnly f v = v { measureOnly = Just f }
setMeasureProg f v = v { measureWith = Just f }
setResamples s v = v { resamples = range 1 1000000 s }
setRegressions s v = v { regressions = regressParams s : regressions v }
setRaw f v = v { rawDataFile = Just f }
setOutput f v = v { reportFile = Just f }
setCSV f v = v { csvFile = Just f }
setCSVRaw f v = v { csvRawFile = Just f }
setJSON f v = v { jsonFile = Just f }
setJUnit f v = v { junitFile = Just f }
setVerbosity s v = v { verbosity = toEnum (range 0 2 s) }
setTemplate f v = v { template = f }
setIters s v = v { iters = Just $ read s }
setMatch s v =
let m = case map toLower s of
"pfx" -> Prefix
"prefix" -> Prefix
"exact" -> Exact
"pattern" -> Pattern
"ipattern" -> IPattern
_ -> optionError ("unknown match type: " <> s)
in v { match = m }
setMode m v = v { mode = m }
setDisplayMode m v = v { displayMode = m }
optionError :: String -> a
optionError s = error s
range :: (Show a, Read a, Ord a) => a -> a -> String -> a
range lo hi s = do
case reads s of
[(i, "")]
| i >= lo && i <= hi -> i
| otherwise -> optionError $ show i ++ " is outside range " ++ show (lo,hi)
_ -> optionError $ show s ++ " is not a number"
describe :: String
describe = usageInfo header opts
header :: String
header = "Microbenchmark suite - " <> versionInfo
versionInfo :: String
versionInfo = "built with gauge " <> showVersion version
regressParams :: String -> ([String], String)
regressParams m
| null r = optionError "no responder specified"
| null ps = optionError "no predictors specified"
| otherwise =
let ret = (words . map repl . drop 1 $ ps, tidy r)
in either optionError (const ret) $ uncurry validateAccessors ret
where
repl ',' = ' '
repl c = c
tidy = reverse . dropWhile isSpace . reverse . dropWhile isSpace
(r,ps) = break (==':') m