criterion-1.5.4.0: Robust, reliable performance measurement and analysis

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

Criterion.Main.Options

Description

Benchmarking command-line configuration.

Synopsis

Documentation

data Mode Source #

Execution mode for a benchmark program.

Constructors

List

List all benchmarks.

Version

Print the version.

RunIters Config Int64 MatchType [String]

Run the given benchmarks, without collecting or analysing performance numbers.

Run Config MatchType [String]

Run and analyse the given benchmarks.

Instances
Eq Mode Source # 
Instance details

Defined in Criterion.Main.Options

Methods

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

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

Data Mode Source # 
Instance details

Defined in Criterion.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 Criterion.Main.Options

Show Mode Source # 
Instance details

Defined in Criterion.Main.Options

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Generic Mode Source # 
Instance details

Defined in Criterion.Main.Options

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

type Rep Mode Source # 
Instance details

Defined in Criterion.Main.Options

data MatchType Source #

How to match a benchmark name.

Constructors

Prefix

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

Glob

Match by Unix-style glob pattern. When using this match type, benchmark names are treated as if they were file-paths. For example, the glob patterns "*/ba*" and "*/*" will match "foo/bar", but "*" or "*bar" will not.

Pattern

Match by searching given substring in benchmark paths.

IPattern

Same as Pattern, but case insensitive.

Instances
Bounded MatchType Source # 
Instance details

Defined in Criterion.Main.Options

Enum MatchType Source # 
Instance details

Defined in Criterion.Main.Options

Eq MatchType Source # 
Instance details

Defined in Criterion.Main.Options

Data MatchType Source # 
Instance details

Defined in Criterion.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 Criterion.Main.Options

Read MatchType Source # 
Instance details

Defined in Criterion.Main.Options

Show MatchType Source # 
Instance details

Defined in Criterion.Main.Options

Generic MatchType Source # 
Instance details

Defined in Criterion.Main.Options

Associated Types

type Rep MatchType :: Type -> Type #

type Rep MatchType Source # 
Instance details

Defined in Criterion.Main.Options

type Rep MatchType = D1 (MetaData "MatchType" "Criterion.Main.Options" "criterion-1.5.4.0-H3A6wYVHkko5H6PPmDdtJm" False) ((C1 (MetaCons "Prefix" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Glob" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Pattern" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IPattern" PrefixI False) (U1 :: Type -> Type)))

defaultConfig :: Config Source #

Default benchmarking configuration.

parseWith Source #

Arguments

:: Config

Default configuration to use if options are not explicitly specified.

-> Parser Mode 

Parse a command line.

config :: Config -> Parser Config Source #

Parse a configuration.

describe :: Config -> ParserInfo Mode Source #

Flesh out a command-line parser.

describeWith :: Parser a -> ParserInfo a Source #

Flesh out command-line information using a custom Parser.

versionInfo :: String Source #

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