module Gauge.Main
(
defaultMain
, defaultMainWith
, runMode
, benchmark
, benchmarkWith
, module Gauge.Benchmark
) where
import Control.Applicative
import Control.Monad (unless, when)
#ifdef HAVE_ANALYSIS
import Gauge.Analysis (analyseBenchmark)
import qualified Gauge.CSV as CSV
#endif
import Gauge.IO.Printf (note, printError, rewindClearLine)
import Gauge.Benchmark
import Gauge.Main.Options
import Gauge.Measurement (Measured, measureAccessors_, rescale)
import Gauge.Monad (Gauge, askConfig, withConfig, gaugeIO)
import Data.List (sort)
import Data.Traversable
import System.Environment (getProgName, getArgs)
import System.Exit (ExitCode(..), exitWith)
import System.IO (BufferMode(..), hSetBuffering, stdout)
import Basement.Terminal (initialize)
import qualified Data.Vector as V
import Prelude
defaultMain :: [Benchmark] -> IO ()
defaultMain = defaultMainWith defaultConfig
parseError :: String -> IO a
parseError msg = do
_ <- printError "Error: %s\n" msg
_ <- printError "Run \"%s --help\" for usage information\n" =<< getProgName
exitWith (ExitFailure 64)
selectBenches :: MatchType -> [String] -> Benchmark -> IO (String -> Bool)
selectBenches matchType benches bsgroup = do
let toRun = makeSelector matchType benches
unless (null benches || any toRun (benchNames bsgroup)) $
parseError "none of the specified names matches a benchmark"
return toRun
quickAnalyse :: String -> V.Vector Measured -> Gauge ()
quickAnalyse desc meas = do
Config{..} <- askConfig
let accessors =
if verbosity == Verbose
then measureAccessors_
else filter (("time" ==) . fst) measureAccessors_
_ <- note "%s%-40s " rewindClearLine desc
if verbosity == Verbose then gaugeIO (putStrLn "") else return ()
_ <- traverse
(\(k, (a, s, _)) -> reportStat a s k)
accessors
_ <- note "\n"
pure ()
where
reportStat accessor sh msg =
when (not $ V.null meas) $
let val = (accessor . rescale) $ V.last meas
in maybe (return ()) (\x -> note "%-20s %-10s\n" msg (sh x)) val
benchmarkWith :: Config -> Benchmarkable -> IO ()
benchmarkWith cfg bm =
withConfig cfg $
runBenchmark (const True) (Benchmark "function" bm) (BenchmarkNormal quickAnalyse)
benchmark :: Benchmarkable -> IO ()
benchmark = benchmarkWith defaultConfig
defaultMainWith :: Config
-> [Benchmark]
-> IO ()
defaultMainWith defCfg bs = do
initialize
args <- getArgs
let (cfg, extra) = parseWith defCfg args
#ifdef HAVE_ANALYSIS
let cfg' = cfg
#else
let cfg' = cfg {quickMode = True}
#endif
runMode (mode cfg') cfg' extra bs
runMode :: Mode -> Config -> [String] -> [Benchmark] -> IO ()
runMode wat cfg benches bs =
case wat of
List -> mapM_ putStrLn . sort . concatMap benchNames $ bs
Version -> putStrLn versionInfo
Help -> putStrLn describe
DefaultMode -> runDefault
where
runDefault = do
CSV.write (csvRawFile cfg) $ CSV.Row $ map (CSV.string . fst) measureAccessors_
CSV.write (csvFile cfg) $ CSV.Row $ map CSV.string
["Name", "Mean","MeanLB","MeanUB","Stddev","StddevLB","StddevUB"]
hSetBuffering stdout NoBuffering
selector <- selectBenches (match cfg) benches bsgroup
#ifdef HAVE_ANALYSIS
let compiledAnalyseStep = analyseBenchmark
#else
let compiledAnalyseStep = quickAnalyse
#endif
let mode = case (measureOnly cfg, iters cfg, quickMode cfg) of
(Just outfile, _ , _ ) -> BenchmarkNormal $ \_ r -> gaugeIO (writeFile outfile (show r))
(Nothing , Just nbIters, _ ) -> BenchmarkIters nbIters
(Nothing , Nothing , True) -> BenchmarkNormal quickAnalyse
(Nothing , Nothing , False) -> BenchmarkNormal compiledAnalyseStep
withConfig cfg $ runBenchmark selector bsgroup mode
bsgroup = BenchGroup "" bs