{-# LANGUAGE Trustworthy #-}
module Criterion.Main
(
Benchmarkable
, Benchmark
, env
, envWithCleanup
, perBatchEnv
, perBatchEnvWithCleanup
, perRunEnv
, perRunEnvWithCleanup
, toBenchmarkable
, bench
, bgroup
, nf
, whnf
, nfIO
, whnfIO
, nfAppIO
, whnfAppIO
, defaultMain
, defaultMainWith
, defaultConfig
, makeMatcher
, runMode
) where
import Control.Monad (unless)
import Control.Monad.Trans (liftIO)
import Criterion.IO.Printf (printError, writeCsv)
import Criterion.Internal (runAndAnalyse, runFixedIters)
import Criterion.Main.Options (MatchType(..), Mode(..), defaultConfig, describe,
versionInfo)
import Criterion.Measurement (initializeTime)
import Criterion.Monad (withConfig)
import Criterion.Types
import Data.Char (toLower)
import Data.List (isInfixOf, isPrefixOf, sort, stripPrefix)
import Data.Maybe (fromMaybe)
import Options.Applicative (execParser)
import System.Environment (getProgName)
import System.Exit (ExitCode(..), exitWith)
import System.FilePath.Glob
defaultMain :: [Benchmark] -> IO ()
defaultMain :: [Benchmark] -> IO ()
defaultMain = Config -> [Benchmark] -> IO ()
defaultMainWith Config
defaultConfig
makeMatcher :: MatchType
-> [String]
-> Either String (String -> Bool)
makeMatcher :: MatchType -> [String] -> Either String (String -> Bool)
makeMatcher MatchType
matchKind [String]
args =
case MatchType
matchKind of
MatchType
Prefix -> (String -> Bool) -> Either String (String -> Bool)
forall a b. b -> Either a b
Right ((String -> Bool) -> Either String (String -> Bool))
-> (String -> Bool) -> Either String (String -> Bool)
forall a b. (a -> b) -> a -> b
$ \String
b -> [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
args Bool -> Bool -> Bool
|| (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
b) [String]
args
MatchType
Glob ->
let compOptions :: CompOptions
compOptions = CompOptions
compDefault { errorRecovery = False }
in case (String -> Either String Pattern)
-> [String] -> Either String [Pattern]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (CompOptions -> String -> Either String Pattern
tryCompileWith CompOptions
compOptions) [String]
args of
Left String
errMsg -> String -> Either String (String -> Bool)
forall a b. a -> Either a b
Left (String -> Either String (String -> Bool))
-> (String -> String) -> String -> Either String (String -> Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
errMsg (Maybe String -> String)
-> (String -> Maybe String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> Maybe String
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix String
"compile :: " (String -> Either String (String -> Bool))
-> String -> Either String (String -> Bool)
forall a b. (a -> b) -> a -> b
$
String
errMsg
Right [Pattern]
ps -> (String -> Bool) -> Either String (String -> Bool)
forall a b. b -> Either a b
Right ((String -> Bool) -> Either String (String -> Bool))
-> (String -> Bool) -> Either String (String -> Bool)
forall a b. (a -> b) -> a -> b
$ \String
b -> [Pattern] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Pattern]
ps Bool -> Bool -> Bool
|| (Pattern -> Bool) -> [Pattern] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Pattern -> String -> Bool
`match` String
b) [Pattern]
ps
MatchType
Pattern -> (String -> Bool) -> Either String (String -> Bool)
forall a b. b -> Either a b
Right ((String -> Bool) -> Either String (String -> Bool))
-> (String -> Bool) -> Either String (String -> Bool)
forall a b. (a -> b) -> a -> b
$ \String
b -> [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
args Bool -> Bool -> Bool
|| (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` String
b) [String]
args
MatchType
IPattern -> (String -> Bool) -> Either String (String -> Bool)
forall a b. b -> Either a b
Right ((String -> Bool) -> Either String (String -> Bool))
-> (String -> Bool) -> Either String (String -> Bool)
forall a b. (a -> b) -> a -> b
$ \String
b -> [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
args Bool -> Bool -> Bool
|| (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower String
b) ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ((Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower) [String]
args)
selectBenches :: MatchType -> [String] -> Benchmark -> IO (String -> Bool)
selectBenches :: MatchType -> [String] -> Benchmark -> IO (String -> Bool)
selectBenches MatchType
matchType [String]
benches Benchmark
bsgroup = do
toRun <- (String -> IO (String -> Bool))
-> ((String -> Bool) -> IO (String -> Bool))
-> Either String (String -> Bool)
-> IO (String -> Bool)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> IO (String -> Bool)
forall a. String -> IO a
parseError (String -> Bool) -> IO (String -> Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String (String -> Bool) -> IO (String -> Bool))
-> ([String] -> Either String (String -> Bool))
-> [String]
-> IO (String -> Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MatchType -> [String] -> Either String (String -> Bool)
makeMatcher MatchType
matchType ([String] -> IO (String -> Bool))
-> [String] -> IO (String -> Bool)
forall a b. (a -> b) -> a -> b
$ [String]
benches
unless (null benches || any toRun (benchNames bsgroup)) $
parseError "none of the specified names matches a benchmark"
return toRun
defaultMainWith :: Config
-> [Benchmark]
-> IO ()
defaultMainWith :: Config -> [Benchmark] -> IO ()
defaultMainWith Config
defCfg [Benchmark]
bs = do
wat <- ParserInfo Mode -> IO Mode
forall a. ParserInfo a -> IO a
execParser (Config -> ParserInfo Mode
describe Config
defCfg)
runMode wat bs
runMode :: Mode -> [Benchmark] -> IO ()
runMode :: Mode -> [Benchmark] -> IO ()
runMode Mode
wat [Benchmark]
bs =
case Mode
wat of
Mode
List -> (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> IO ()
putStrLn ([String] -> IO ())
-> ([Benchmark] -> [String]) -> [Benchmark] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. Ord a => [a] -> [a]
sort ([String] -> [String])
-> ([Benchmark] -> [String]) -> [Benchmark] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Benchmark -> [String]) -> [Benchmark] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Benchmark -> [String]
benchNames ([Benchmark] -> IO ()) -> [Benchmark] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Benchmark]
bs
Mode
Version -> String -> IO ()
putStrLn String
versionInfo
RunIters Config
cfg Int64
iters MatchType
matchType [String]
benches -> do
shouldRun <- MatchType -> [String] -> Benchmark -> IO (String -> Bool)
selectBenches MatchType
matchType [String]
benches Benchmark
bsgroup
withConfig cfg $
runFixedIters iters shouldRun bsgroup
Run Config
cfg MatchType
matchType [String]
benches -> do
shouldRun <- MatchType -> [String] -> Benchmark -> IO (String -> Bool)
selectBenches MatchType
matchType [String]
benches Benchmark
bsgroup
withConfig cfg $ do
writeCsv ("Name","Mean","MeanLB","MeanUB","Stddev","StddevLB",
"StddevUB")
liftIO initializeTime
runAndAnalyse shouldRun bsgroup
where bsgroup :: Benchmark
bsgroup = String -> [Benchmark] -> Benchmark
BenchGroup String
"" [Benchmark]
bs
parseError :: String -> IO a
parseError :: forall a. String -> IO a
parseError String
msg = do
_ <- String -> String -> IO (ZonkAny 1)
forall r. CritHPrintfType r => String -> r
printError String
"Error: %s\n" String
msg
_ <- printError "Run \"%s --help\" for usage information\n" =<< getProgName
exitWith (ExitFailure 64)