gauge-0.2.3: small framework for performance measurement and analysis

Copyright(c) 2014 Bryan O'Sullivan
LicenseBSD-style
Maintainerbos@serpentine.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Gauge.Main.Options

Description

Benchmarking command-line configuration.

Synopsis

Documentation

defaultConfig :: Config Source #

Default benchmarking configuration.

makeSelector Source #

Arguments

:: MatchType 
-> [String]

Command line arguments.

-> String -> Bool 

Create a benchmark selector function that can tell if a name given on the command line matches a defined benchmark.

parseWith Source #

Arguments

:: Config

Default configuration to use

-> [String]

Program Argument

-> (Config, [String]) 

versionInfo :: String Source #

A string describing the version of this benchmark (really, the version of gauge that was used to build it).

data Config Source #

Top-level benchmarking configuration.

Constructors

Config 

Fields

  • confInterval :: Maybe Double

    Confidence interval for bootstrap estimation (greater than 0, less than 1).

  • forceGC :: Bool

    Obsolete, unused. This option used to force garbage collection between every benchmark run, but it no longer has an effect (we now unconditionally force garbage collection). This option remains solely for backwards API compatibility.

  • timeLimit :: Maybe Double

    Number of seconds to run a single benchmark. In practice, execution time may exceed this limit to honor minimum number of samples or minimum duration of each sample. Increased time limit allows us to take more samples. Use 0 for a single sample benchmark.

  • minSamples :: Maybe Int

    Minimum number of samples to be taken.

  • minDuration :: MilliSeconds

    Minimum duration of each sample, increased duration allows us to perform more iterations in each sample. To enforce a single iteration in a sample use duration 0.

  • includeFirstIter :: Bool

    Discard the very first iteration of a benchmark. The first iteration includes the potentially extra cost of one time evaluations introducing large variance.

  • quickMode :: Bool

    Quickly measure and report raw measurements.

  • measureOnly :: Maybe FilePath

    Just measure the given benchmark and place the raw output in this file, do not analyse and generate a report.

  • measureWith :: Maybe FilePath

    Specify the path of the benchmarking program to use (this program itself) for measuring the benchmarks in a separate process.

  • resamples :: Int

    Number of resamples to perform when bootstrapping.

  • regressions :: [([String], String)]

    Regressions to perform.

  • rawDataFile :: Maybe FilePath

    File to write binary measurement and analysis data to. If not specified, this will be a temporary file.

  • reportFile :: Maybe FilePath

    File to write report output to, with template expanded.

  • csvFile :: Maybe FilePath

    File to write CSV summary to.

  • csvRawFile :: Maybe FilePath

    File to write CSV measurements to.

  • jsonFile :: Maybe FilePath

    File to write JSON-formatted results to.

  • junitFile :: Maybe FilePath

    File to write JUnit-compatible XML results to.

  • verbosity :: Verbosity

    Verbosity level to use when running and analysing benchmarks.

  • template :: FilePath

    Template file to use if writing a report.

  • iters :: Maybe Int64

    Number of iterations

  • match :: MatchType

    Type of matching to use, if any

  • mode :: Mode

    Mode of operation

  • displayMode :: DisplayMode
     
Instances
Eq Config Source # 
Instance details

Defined in Gauge.Main.Options

Methods

(==) :: Config -> Config -> Bool #

(/=) :: Config -> Config -> Bool #

Data Config Source # 
Instance details

Defined in Gauge.Main.Options

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Config -> c Config #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Config #

toConstr :: Config -> Constr #

dataTypeOf :: Config -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Config) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config) #

gmapT :: (forall b. Data b => b -> b) -> Config -> Config #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r #

gmapQ :: (forall d. Data d => d -> u) -> Config -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Config -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Config -> m Config #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Config -> m Config #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Config -> m Config #

Read Config Source # 
Instance details

Defined in Gauge.Main.Options

Show Config Source # 
Instance details

Defined in Gauge.Main.Options

Generic Config Source # 
Instance details

Defined in Gauge.Main.Options

Associated Types

type Rep Config :: * -> * #

Methods

from :: Config -> Rep Config x #

to :: Rep Config x -> Config #

type Rep Config Source # 
Instance details

Defined in Gauge.Main.Options

type Rep Config

data Verbosity Source #

Control the amount of information displayed.

Constructors

Quiet 
Normal 
Verbose 
Instances
Bounded Verbosity Source # 
Instance details

Defined in Gauge.Main.Options

Enum Verbosity Source # 
Instance details

Defined in Gauge.Main.Options

Eq Verbosity Source # 
Instance details

Defined in Gauge.Main.Options

Data Verbosity Source # 
Instance details

Defined in Gauge.Main.Options

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Verbosity -> c Verbosity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Verbosity #

toConstr :: Verbosity -> Constr #

dataTypeOf :: Verbosity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Verbosity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity) #

gmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Verbosity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Verbosity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Verbosity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Verbosity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Verbosity -> m Verbosity #

Ord Verbosity Source # 
Instance details

Defined in Gauge.Main.Options

Read Verbosity Source # 
Instance details

Defined in Gauge.Main.Options

Show Verbosity Source # 
Instance details

Defined in Gauge.Main.Options

Generic Verbosity Source # 
Instance details

Defined in Gauge.Main.Options

Associated Types

type Rep Verbosity :: * -> * #

type Rep Verbosity Source # 
Instance details

Defined in Gauge.Main.Options

type Rep Verbosity = D1 (MetaData "Verbosity" "Gauge.Main.Options" "gauge-0.2.3-Imkc1Njmn4gAlDTJZlAwSy" False) (C1 (MetaCons "Quiet" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Normal" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Verbose" PrefixI False) (U1 :: * -> *)))

data DisplayMode Source #

Constructors

Condensed 
StatsTable 
Instances
Eq DisplayMode Source # 
Instance details

Defined in Gauge.Main.Options

Data DisplayMode Source # 
Instance details

Defined in Gauge.Main.Options

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DisplayMode -> c DisplayMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DisplayMode #

toConstr :: DisplayMode -> Constr #

dataTypeOf :: DisplayMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DisplayMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DisplayMode) #

gmapT :: (forall b. Data b => b -> b) -> DisplayMode -> DisplayMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DisplayMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DisplayMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> DisplayMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DisplayMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DisplayMode -> m DisplayMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DisplayMode -> m DisplayMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DisplayMode -> m DisplayMode #

Read DisplayMode Source # 
Instance details

Defined in Gauge.Main.Options

Show DisplayMode Source # 
Instance details

Defined in Gauge.Main.Options

Generic DisplayMode Source # 
Instance details

Defined in Gauge.Main.Options

Associated Types

type Rep DisplayMode :: * -> * #

type Rep DisplayMode Source # 
Instance details

Defined in Gauge.Main.Options

type Rep DisplayMode = D1 (MetaData "DisplayMode" "Gauge.Main.Options" "gauge-0.2.3-Imkc1Njmn4gAlDTJZlAwSy" False) (C1 (MetaCons "Condensed" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "StatsTable" PrefixI False) (U1 :: * -> *))

data MatchType Source #

How to match a benchmark name.

Constructors

Exact

Match the exact benchmark name

Prefix

Match by prefix. For example, a prefix of "foo" will match "foobar".

Pattern

Match by searching given substring in benchmark paths.

IPattern

Same as Pattern, but case insensitive.

Instances
Bounded MatchType Source # 
Instance details

Defined in Gauge.Main.Options

Enum MatchType Source # 
Instance details

Defined in Gauge.Main.Options

Eq MatchType Source # 
Instance details

Defined in Gauge.Main.Options

Data MatchType Source # 
Instance details

Defined in Gauge.Main.Options

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchType -> c MatchType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MatchType #

toConstr :: MatchType -> Constr #

dataTypeOf :: MatchType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MatchType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MatchType) #

gmapT :: (forall b. Data b => b -> b) -> MatchType -> MatchType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchType -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchType -> m MatchType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchType -> m MatchType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchType -> m MatchType #

Ord MatchType Source # 
Instance details

Defined in Gauge.Main.Options

Read MatchType Source # 
Instance details

Defined in Gauge.Main.Options

Show MatchType Source # 
Instance details

Defined in Gauge.Main.Options

Generic MatchType Source # 
Instance details

Defined in Gauge.Main.Options

Associated Types

type Rep MatchType :: * -> * #

type Rep MatchType Source # 
Instance details

Defined in Gauge.Main.Options

type Rep MatchType = D1 (MetaData "MatchType" "Gauge.Main.Options" "gauge-0.2.3-Imkc1Njmn4gAlDTJZlAwSy" False) ((C1 (MetaCons "Exact" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Prefix" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Pattern" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "IPattern" PrefixI False) (U1 :: * -> *)))

data Mode Source #

Execution mode for a benchmark program.

Constructors

List

List all benchmarks.

Version

Print the version.

Help

Print help

DefaultMode

Default Benchmark mode

Instances
Eq Mode Source # 
Instance details

Defined in Gauge.Main.Options

Methods

(==) :: Mode -> Mode -> Bool #

(/=) :: Mode -> Mode -> Bool #

Data Mode Source # 
Instance details

Defined in Gauge.Main.Options

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Mode -> c Mode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Mode #

toConstr :: Mode -> Constr #

dataTypeOf :: Mode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Mode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mode) #

gmapT :: (forall b. Data b => b -> b) -> Mode -> Mode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r #

gmapQ :: (forall d. Data d => d -> u) -> Mode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Mode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Mode -> m Mode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Mode -> m Mode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Mode -> m Mode #

Read Mode Source # 
Instance details

Defined in Gauge.Main.Options

Show Mode Source # 
Instance details

Defined in Gauge.Main.Options

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Generic Mode Source # 
Instance details

Defined in Gauge.Main.Options

Associated Types

type Rep Mode :: * -> * #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

type Rep Mode Source # 
Instance details

Defined in Gauge.Main.Options

type Rep Mode = D1 (MetaData "Mode" "Gauge.Main.Options" "gauge-0.2.3-Imkc1Njmn4gAlDTJZlAwSy" False) ((C1 (MetaCons "List" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Version" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Help" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DefaultMode" PrefixI False) (U1 :: * -> *)))