criterion-1.6.2.0: Robust, reliable performance measurement and analysis
Copyright(c) 2009-2014 Bryan O'Sullivan
LicenseBSD-style
Maintainerbos@serpentine.com
Stabilityexperimental
PortabilityGHC
Safe HaskellTrustworthy
LanguageHaskell2010

Criterion.Types

Description

Types for benchmarking.

The core type is Benchmarkable, which admits both pure functions and IO actions.

For a pure function of type a -> b, the benchmarking harness calls this function repeatedly, each time with a different Int64 argument (the number of times to run the function in a loop), and reduces the result the function returns to weak head normal form.

For an action of type IO a, the benchmarking harness calls the action repeatedly, but does not reduce the result.

Synopsis

Configuration

data Config Source #

Top-level benchmarking configuration.

Constructors

Config 

Fields

Instances

Instances details
Data Config Source # 
Instance details

Defined in Criterion.Types

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 :: forall r r'. (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 #

Generic Config Source # 
Instance details

Defined in Criterion.Types

Associated Types

type Rep Config :: Type -> Type #

Methods

from :: Config -> Rep Config x #

to :: Rep Config x -> Config #

Read Config Source # 
Instance details

Defined in Criterion.Types

Show Config Source # 
Instance details

Defined in Criterion.Types

Eq Config Source # 
Instance details

Defined in Criterion.Types

Methods

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

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

MonadReader Config Criterion Source # 
Instance details

Defined in Criterion.Monad.Internal

Methods

ask :: Criterion Config #

local :: (Config -> Config) -> Criterion a -> Criterion a #

reader :: (Config -> a) -> Criterion a #

type Rep Config Source # 
Instance details

Defined in Criterion.Types

data Verbosity Source #

Control the amount of information displayed.

Constructors

Quiet 
Normal 
Verbose 

Instances

Instances details
Data Verbosity Source # 
Instance details

Defined in Criterion.Types

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 :: forall r r'. (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 #

Bounded Verbosity Source # 
Instance details

Defined in Criterion.Types

Enum Verbosity Source # 
Instance details

Defined in Criterion.Types

Generic Verbosity Source # 
Instance details

Defined in Criterion.Types

Associated Types

type Rep Verbosity :: Type -> Type #

Read Verbosity Source # 
Instance details

Defined in Criterion.Types

Show Verbosity Source # 
Instance details

Defined in Criterion.Types

Eq Verbosity Source # 
Instance details

Defined in Criterion.Types

Ord Verbosity Source # 
Instance details

Defined in Criterion.Types

type Rep Verbosity Source # 
Instance details

Defined in Criterion.Types

type Rep Verbosity = D1 ('MetaData "Verbosity" "Criterion.Types" "criterion-1.6.2.0-By21f2YjhCxFohaNLiJyOk" 'False) (C1 ('MetaCons "Quiet" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Normal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Verbose" 'PrefixI 'False) (U1 :: Type -> Type)))

Benchmark descriptions

data Benchmarkable #

A pure function or impure action that can be benchmarked. The Int64 parameter indicates the number of times to run the given function or action.

Constructors

NFData a => Benchmarkable 

Fields

data Benchmark where #

Specification of a collection of benchmarks and environments. A benchmark may consist of:

  • An environment that creates input data for benchmarks, created with env.
  • A single Benchmarkable item with a name, created with bench.
  • A (possibly nested) group of Benchmarks, created with bgroup.

Constructors

Environment :: forall env a. NFData env => IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark 
Benchmark :: String -> Benchmarkable -> Benchmark 
BenchGroup :: String -> [Benchmark] -> Benchmark 

Instances

Instances details
Show Benchmark 
Instance details

Defined in Criterion.Measurement.Types

Measurements

data Measured #

A collection of measurements made while benchmarking.

Measurements related to garbage collection are tagged with GC. They will only be available if a benchmark is run with "+RTS -T".

Packed storage. When GC statistics cannot be collected, GC values will be set to huge negative values. If a field is labeled with "GC" below, use fromInt and fromDouble to safely convert to "real" values.

Constructors

Measured 

Fields

Instances

Instances details
FromJSON Measured 
Instance details

Defined in Criterion.Measurement.Types

ToJSON Measured 
Instance details

Defined in Criterion.Measurement.Types

Data Measured 
Instance details

Defined in Criterion.Measurement.Types

Methods

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

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

toConstr :: Measured -> Constr #

dataTypeOf :: Measured -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Measured 
Instance details

Defined in Criterion.Measurement.Types

Associated Types

type Rep Measured :: Type -> Type #

Methods

from :: Measured -> Rep Measured x #

to :: Rep Measured x -> Measured #

Read Measured 
Instance details

Defined in Criterion.Measurement.Types

Show Measured 
Instance details

Defined in Criterion.Measurement.Types

Binary Measured 
Instance details

Defined in Criterion.Measurement.Types

Methods

put :: Measured -> Put #

get :: Get Measured #

putList :: [Measured] -> Put #

NFData Measured 
Instance details

Defined in Criterion.Measurement.Types

Methods

rnf :: Measured -> () #

Eq Measured 
Instance details

Defined in Criterion.Measurement.Types

type Rep Measured 
Instance details

Defined in Criterion.Measurement.Types

type Rep Measured = D1 ('MetaData "Measured" "Criterion.Measurement.Types" "criterion-measurement-0.2.1.0-2z8DZlQbJhB2Q0X6EauBdJ" 'False) (C1 ('MetaCons "Measured" 'PrefixI 'True) (((S1 ('MetaSel ('Just "measTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: (S1 ('MetaSel ('Just "measCpuTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "measCycles") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64))) :*: (S1 ('MetaSel ('Just "measIters") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: (S1 ('MetaSel ('Just "measAllocated") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: S1 ('MetaSel ('Just "measPeakMbAllocated") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64)))) :*: ((S1 ('MetaSel ('Just "measNumGcs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: (S1 ('MetaSel ('Just "measBytesCopied") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: S1 ('MetaSel ('Just "measMutatorWallSeconds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double))) :*: (S1 ('MetaSel ('Just "measMutatorCpuSeconds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: (S1 ('MetaSel ('Just "measGcWallSeconds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "measGcCpuSeconds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double))))))

fromInt :: Int64 -> Maybe Int64 #

Convert a (possibly unavailable) GC measurement to a true value. If the measurement is a huge negative number that corresponds to "no data", this will return Nothing.

toInt :: Maybe Int64 -> Int64 #

Convert from a true value back to the packed representation used for GC measurements.

fromDouble :: Double -> Maybe Double #

Convert a (possibly unavailable) GC measurement to a true value. If the measurement is a huge negative number that corresponds to "no data", this will return Nothing.

toDouble :: Maybe Double -> Double #

Convert from a true value back to the packed representation used for GC measurements.

measureAccessors :: Map String (Measured -> Maybe Double, String) #

Field names and accessors for a Measured record.

measureKeys :: [String] #

Field names in a Measured record, in the order in which they appear.

measure :: Unbox a => (Measured -> a) -> Vector Measured -> Vector a #

rescale :: Measured -> Measured #

Normalise every measurement as if measIters was 1.

(measIters itself is left unaffected.)

Benchmark construction

env #

Arguments

:: NFData env 
=> IO env

Create the environment. The environment will be evaluated to normal form before being passed to the benchmark.

-> (env -> Benchmark)

Take the newly created environment and make it available to the given benchmarks.

-> Benchmark 

Run a benchmark (or collection of benchmarks) in the given environment. The purpose of an environment is to lazily create input data to pass to the functions that will be benchmarked.

A common example of environment data is input that is read from a file. Another is a large data structure constructed in-place.

Motivation. In earlier versions of criterion, all benchmark inputs were always created when a program started running. By deferring the creation of an environment when its associated benchmarks need the its, we avoid two problems that this strategy caused:

  • Memory pressure distorted the results of unrelated benchmarks. If one benchmark needed e.g. a gigabyte-sized input, it would force the garbage collector to do extra work when running some other benchmark that had no use for that input. Since the data created by an environment is only available when it is in scope, it should be garbage collected before other benchmarks are run.
  • The time cost of generating all needed inputs could be significant in cases where no inputs (or just a few) were really needed. This occurred often, for instance when just one out of a large suite of benchmarks was run, or when a user would list the collection of benchmarks without running any.

Creation. An environment is created right before its related benchmarks are run. The IO action that creates the environment is run, then the newly created environment is evaluated to normal form (hence the NFData constraint) before being passed to the function that receives the environment.

Complex environments. If you need to create an environment that contains multiple values, simply pack the values into a tuple.

Lazy pattern matching. In situations where a "real" environment is not needed, e.g. if a list of benchmark names is being generated, a value which throws an exception will be passed to the function that receives the environment. This avoids the overhead of generating an environment that will not actually be used.

The function that receives the environment must use lazy pattern matching to deconstruct the tuple (e.g., ~(x, y), not (x, y)), as use of strict pattern matching will cause a crash if an exception-throwing value is passed in.

Example. This program runs benchmarks in an environment that contains two values. The first value is the contents of a text file; the second is a string. Pay attention to the use of a lazy pattern to deconstruct the tuple in the function that returns the benchmarks to be run.

setupEnv = do
  let small = replicate 1000 (1 :: Int)
  big <- map length . words <$> readFile "/usr/dict/words"
  return (small, big)

main = defaultMain [
   -- notice the lazy pattern match here!
   env setupEnv $ \ ~(small,big) -> bgroup "main" [
   bgroup "small" [
     bench "length" $ whnf length small
   , bench "length . filter" $ whnf (length . filter (==1)) small
   ]
 ,  bgroup "big" [
     bench "length" $ whnf length big
   , bench "length . filter" $ whnf (length . filter (==1)) big
   ]
 ] ]

Discussion. The environment created in the example above is intentionally not ideal. As Haskell's scoping rules suggest, the variable big is in scope for the benchmarks that use only small. It would be better to create a separate environment for big, so that it will not be kept alive while the unrelated benchmarks are being run.

envWithCleanup #

Arguments

:: NFData env 
=> IO env

Create the environment. The environment will be evaluated to normal form before being passed to the benchmark.

-> (env -> IO a)

Clean up the created environment.

-> (env -> Benchmark)

Take the newly created environment and make it available to the given benchmarks.

-> Benchmark 

Same as env, but but allows for an additional callback to clean up the environment. Resource clean up is exception safe, that is, it runs even if the Benchmark throws an exception.

perBatchEnv #

Arguments

:: (NFData env, NFData b) 
=> (Int64 -> IO env)

Create an environment for a batch of N runs. The environment will be evaluated to normal form before running.

-> (env -> IO b)

Function returning the IO action that should be benchmarked with the newly generated environment.

-> Benchmarkable 

Create a Benchmarkable where a fresh environment is allocated for every batch of runs of the benchmarkable.

The environment is evaluated to normal form before the benchmark is run.

When using whnf, whnfIO, etc. Criterion creates a Benchmarkable whichs runs a batch of N repeat runs of that expressions. Criterion may run any number of these batches to get accurate measurements. Environments created by env and envWithCleanup, are shared across all these batches of runs.

This is fine for simple benchmarks on static input, but when benchmarking IO operations where these operations can modify (and especially grow) the environment this means that later batches might have their accuracy effected due to longer, for example, longer garbage collection pauses.

An example: Suppose we want to benchmark writing to a Chan, if we allocate the Chan using environment and our benchmark consists of writeChan env (), the contents and thus size of the Chan will grow with every repeat. If Criterion runs a 1,000 batches of 1,000 repeats, the result is that the channel will have 999,000 items in it by the time the last batch is run. Since GHC GC has to copy the live set for every major GC this means our last set of writes will suffer a lot of noise of the previous repeats.

By allocating a fresh environment for every batch of runs this function should eliminate this effect.

perBatchEnvWithCleanup #

Arguments

:: (NFData env, NFData b) 
=> (Int64 -> IO env)

Create an environment for a batch of N runs. The environment will be evaluated to normal form before running.

-> (Int64 -> env -> IO ())

Clean up the created environment.

-> (env -> IO b)

Function returning the IO action that should be benchmarked with the newly generated environment.

-> Benchmarkable 

Same as perBatchEnv, but but allows for an additional callback to clean up the environment. Resource clean up is exception safe, that is, it runs even if the Benchmark throws an exception.

perRunEnv #

Arguments

:: (NFData env, NFData b) 
=> IO env

Action that creates the environment for a single run.

-> (env -> IO b)

Function returning the IO action that should be benchmarked with the newly generated environment.

-> Benchmarkable 

Create a Benchmarkable where a fresh environment is allocated for every run of the operation to benchmark. This is useful for benchmarking mutable operations that need a fresh environment, such as sorting a mutable Vector.

As with env and perBatchEnv the environment is evaluated to normal form before the benchmark is run.

This introduces extra noise and result in reduce accuracy compared to other Criterion benchmarks. But allows easier benchmarking for mutable operations than was previously possible.

perRunEnvWithCleanup #

Arguments

:: (NFData env, NFData b) 
=> IO env

Action that creates the environment for a single run.

-> (env -> IO ())

Clean up the created environment.

-> (env -> IO b)

Function returning the IO action that should be benchmarked with the newly generated environment.

-> Benchmarkable 

Same as perRunEnv, but but allows for an additional callback to clean up the environment. Resource clean up is exception safe, that is, it runs even if the Benchmark throws an exception.

toBenchmarkable :: (Int64 -> IO ()) -> Benchmarkable #

Construct a Benchmarkable value from an impure action, where the Int64 parameter indicates the number of times to run the action.

bench #

Arguments

:: String

A name to identify the benchmark.

-> Benchmarkable

An activity to be benchmarked.

-> Benchmark 

Create a single benchmark.

bgroup #

Arguments

:: String

A name to identify the group of benchmarks.

-> [Benchmark]

Benchmarks to group under this name.

-> Benchmark 

Group several benchmarks together under a common name.

addPrefix #

Arguments

:: String

Prefix.

-> String

Name.

-> String 

Add the given prefix to a name. If the prefix is empty, the name is returned unmodified. Otherwise, the prefix and name are separated by a '/' character.

benchNames :: Benchmark -> [String] #

Retrieve the names of all benchmarks. Grouped benchmarks are prefixed with the name of the group they're in.

Evaluation control

nf :: NFData b => (a -> b) -> a -> Benchmarkable #

Apply an argument to a function, and evaluate the result to normal form (NF).

whnf :: (a -> b) -> a -> Benchmarkable #

Apply an argument to a function, and evaluate the result to weak head normal form (WHNF).

nfIO :: NFData a => IO a -> Benchmarkable #

Perform an action, then evaluate its result to normal form (NF). This is particularly useful for forcing a lazy IO action to be completely performed.

If the construction of the 'IO a' value is an important factor in the benchmark, it is best to use nfAppIO instead.

whnfIO :: IO a -> Benchmarkable #

Perform an action, then evaluate its result to weak head normal form (WHNF). This is useful for forcing an IO action whose result is an expression to be evaluated down to a more useful value.

If the construction of the 'IO a' value is an important factor in the benchmark, it is best to use whnfAppIO instead.

nfAppIO :: NFData b => (a -> IO b) -> a -> Benchmarkable #

Apply an argument to a function which performs an action, then evaluate its result to normal form (NF). This function constructs the 'IO b' value on each iteration, similar to nf. This is particularly useful for IO actions where the bulk of the work is not bound by IO, but by pure computations that may optimize away if the argument is known statically, as in nfIO.

whnfAppIO :: (a -> IO b) -> a -> Benchmarkable #

Perform an action, then evaluate its result to weak head normal form (WHNF). This function constructs the 'IO b' value on each iteration, similar to whnf. This is particularly useful for IO actions where the bulk of the work is not bound by IO, but by pure computations that may optimize away if the argument is known statically, as in nfIO.

Result types

data Outliers Source #

Outliers from sample data, calculated using the boxplot technique.

Constructors

Outliers 

Fields

Instances

Instances details
FromJSON Outliers Source # 
Instance details

Defined in Criterion.Types

ToJSON Outliers Source # 
Instance details

Defined in Criterion.Types

Data Outliers Source # 
Instance details

Defined in Criterion.Types

Methods

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

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

toConstr :: Outliers -> Constr #

dataTypeOf :: Outliers -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid Outliers Source # 
Instance details

Defined in Criterion.Types

Semigroup Outliers Source # 
Instance details

Defined in Criterion.Types

Generic Outliers Source # 
Instance details

Defined in Criterion.Types

Associated Types

type Rep Outliers :: Type -> Type #

Methods

from :: Outliers -> Rep Outliers x #

to :: Rep Outliers x -> Outliers #

Read Outliers Source # 
Instance details

Defined in Criterion.Types

Show Outliers Source # 
Instance details

Defined in Criterion.Types

Binary Outliers Source # 
Instance details

Defined in Criterion.Types

Methods

put :: Outliers -> Put #

get :: Get Outliers #

putList :: [Outliers] -> Put #

NFData Outliers Source # 
Instance details

Defined in Criterion.Types

Methods

rnf :: Outliers -> () #

Eq Outliers Source # 
Instance details

Defined in Criterion.Types

type Rep Outliers Source # 
Instance details

Defined in Criterion.Types

type Rep Outliers = D1 ('MetaData "Outliers" "Criterion.Types" "criterion-1.6.2.0-By21f2YjhCxFohaNLiJyOk" 'False) (C1 ('MetaCons "Outliers" 'PrefixI 'True) ((S1 ('MetaSel ('Just "samplesSeen") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: S1 ('MetaSel ('Just "lowSevere") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64)) :*: (S1 ('MetaSel ('Just "lowMild") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: (S1 ('MetaSel ('Just "highMild") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: S1 ('MetaSel ('Just "highSevere") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64)))))

data OutlierEffect Source #

A description of the extent to which outliers in the sample data affect the sample mean and standard deviation.

Constructors

Unaffected

Less than 1% effect.

Slight

Between 1% and 10%.

Moderate

Between 10% and 50%.

Severe

Above 50% (i.e. measurements are useless).

Instances

Instances details
FromJSON OutlierEffect Source # 
Instance details

Defined in Criterion.Types

ToJSON OutlierEffect Source # 
Instance details

Defined in Criterion.Types

Data OutlierEffect Source # 
Instance details

Defined in Criterion.Types

Methods

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

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

toConstr :: OutlierEffect -> Constr #

dataTypeOf :: OutlierEffect -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic OutlierEffect Source # 
Instance details

Defined in Criterion.Types

Associated Types

type Rep OutlierEffect :: Type -> Type #

Read OutlierEffect Source # 
Instance details

Defined in Criterion.Types

Show OutlierEffect Source # 
Instance details

Defined in Criterion.Types

Binary OutlierEffect Source # 
Instance details

Defined in Criterion.Types

NFData OutlierEffect Source # 
Instance details

Defined in Criterion.Types

Methods

rnf :: OutlierEffect -> () #

Eq OutlierEffect Source # 
Instance details

Defined in Criterion.Types

Ord OutlierEffect Source # 
Instance details

Defined in Criterion.Types

type Rep OutlierEffect Source # 
Instance details

Defined in Criterion.Types

type Rep OutlierEffect = D1 ('MetaData "OutlierEffect" "Criterion.Types" "criterion-1.6.2.0-By21f2YjhCxFohaNLiJyOk" 'False) ((C1 ('MetaCons "Unaffected" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Slight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Moderate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Severe" 'PrefixI 'False) (U1 :: Type -> Type)))

data OutlierVariance Source #

Analysis of the extent to which outliers in a sample affect its standard deviation (and to some extent, its mean).

Constructors

OutlierVariance 

Fields

Instances

Instances details
FromJSON OutlierVariance Source # 
Instance details

Defined in Criterion.Types

ToJSON OutlierVariance Source # 
Instance details

Defined in Criterion.Types

Data OutlierVariance Source # 
Instance details

Defined in Criterion.Types

Methods

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

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

toConstr :: OutlierVariance -> Constr #

dataTypeOf :: OutlierVariance -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic OutlierVariance Source # 
Instance details

Defined in Criterion.Types

Associated Types

type Rep OutlierVariance :: Type -> Type #

Read OutlierVariance Source # 
Instance details

Defined in Criterion.Types

Show OutlierVariance Source # 
Instance details

Defined in Criterion.Types

Binary OutlierVariance Source # 
Instance details

Defined in Criterion.Types

NFData OutlierVariance Source # 
Instance details

Defined in Criterion.Types

Methods

rnf :: OutlierVariance -> () #

Eq OutlierVariance Source # 
Instance details

Defined in Criterion.Types

type Rep OutlierVariance Source # 
Instance details

Defined in Criterion.Types

type Rep OutlierVariance = D1 ('MetaData "OutlierVariance" "Criterion.Types" "criterion-1.6.2.0-By21f2YjhCxFohaNLiJyOk" 'False) (C1 ('MetaCons "OutlierVariance" 'PrefixI 'True) (S1 ('MetaSel ('Just "ovEffect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OutlierEffect) :*: (S1 ('MetaSel ('Just "ovDesc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "ovFraction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))))

data Regression Source #

Results of a linear regression.

Constructors

Regression 

Fields

Instances

Instances details
FromJSON Regression Source # 
Instance details

Defined in Criterion.Types

ToJSON Regression Source # 
Instance details

Defined in Criterion.Types

Generic Regression Source # 
Instance details

Defined in Criterion.Types

Associated Types

type Rep Regression :: Type -> Type #

Read Regression Source # 
Instance details

Defined in Criterion.Types

Show Regression Source # 
Instance details

Defined in Criterion.Types

Binary Regression Source # 
Instance details

Defined in Criterion.Types

NFData Regression Source # 
Instance details

Defined in Criterion.Types

Methods

rnf :: Regression -> () #

Eq Regression Source # 
Instance details

Defined in Criterion.Types

type Rep Regression Source # 
Instance details

Defined in Criterion.Types

type Rep Regression = D1 ('MetaData "Regression" "Criterion.Types" "criterion-1.6.2.0-By21f2YjhCxFohaNLiJyOk" 'False) (C1 ('MetaCons "Regression" 'PrefixI 'True) (S1 ('MetaSel ('Just "regResponder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "regCoeffs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String (Estimate ConfInt Double))) :*: S1 ('MetaSel ('Just "regRSquare") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Estimate ConfInt Double)))))

data KDE Source #

Data for a KDE chart of performance.

Constructors

KDE 

Instances

Instances details
FromJSON KDE Source # 
Instance details

Defined in Criterion.Types

ToJSON KDE Source # 
Instance details

Defined in Criterion.Types

Data KDE Source # 
Instance details

Defined in Criterion.Types

Methods

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

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

toConstr :: KDE -> Constr #

dataTypeOf :: KDE -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic KDE Source # 
Instance details

Defined in Criterion.Types

Associated Types

type Rep KDE :: Type -> Type #

Methods

from :: KDE -> Rep KDE x #

to :: Rep KDE x -> KDE #

Read KDE Source # 
Instance details

Defined in Criterion.Types

Show KDE Source # 
Instance details

Defined in Criterion.Types

Methods

showsPrec :: Int -> KDE -> ShowS #

show :: KDE -> String #

showList :: [KDE] -> ShowS #

Binary KDE Source # 
Instance details

Defined in Criterion.Types

Methods

put :: KDE -> Put #

get :: Get KDE #

putList :: [KDE] -> Put #

NFData KDE Source # 
Instance details

Defined in Criterion.Types

Methods

rnf :: KDE -> () #

Eq KDE Source # 
Instance details

Defined in Criterion.Types

Methods

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

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

type Rep KDE Source # 
Instance details

Defined in Criterion.Types

type Rep KDE = D1 ('MetaData "KDE" "Criterion.Types" "criterion-1.6.2.0-By21f2YjhCxFohaNLiJyOk" 'False) (C1 ('MetaCons "KDE" 'PrefixI 'True) (S1 ('MetaSel ('Just "kdeType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "kdeValues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Double)) :*: S1 ('MetaSel ('Just "kdePDF") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Double)))))

data Report Source #

Report of a sample analysis.

Constructors

Report 

Fields

Instances

Instances details
FromJSON Report Source # 
Instance details

Defined in Criterion.Types

ToJSON Report Source # 
Instance details

Defined in Criterion.Types

Generic Report Source # 
Instance details

Defined in Criterion.Types

Associated Types

type Rep Report :: Type -> Type #

Methods

from :: Report -> Rep Report x #

to :: Rep Report x -> Report #

Read Report Source # 
Instance details

Defined in Criterion.Types

Show Report Source # 
Instance details

Defined in Criterion.Types

Binary Report Source # 
Instance details

Defined in Criterion.Types

Methods

put :: Report -> Put #

get :: Get Report #

putList :: [Report] -> Put #

NFData Report Source # 
Instance details

Defined in Criterion.Types

Methods

rnf :: Report -> () #

Eq Report Source # 
Instance details

Defined in Criterion.Types

Methods

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

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

type Rep Report Source # 
Instance details

Defined in Criterion.Types

data SampleAnalysis Source #

Result of a bootstrap analysis of a non-parametric sample.

Constructors

SampleAnalysis 

Fields

Instances

Instances details
FromJSON SampleAnalysis Source # 
Instance details

Defined in Criterion.Types

ToJSON SampleAnalysis Source # 
Instance details

Defined in Criterion.Types

Generic SampleAnalysis Source # 
Instance details

Defined in Criterion.Types

Associated Types

type Rep SampleAnalysis :: Type -> Type #

Read SampleAnalysis Source # 
Instance details

Defined in Criterion.Types

Show SampleAnalysis Source # 
Instance details

Defined in Criterion.Types

Binary SampleAnalysis Source # 
Instance details

Defined in Criterion.Types

NFData SampleAnalysis Source # 
Instance details

Defined in Criterion.Types

Methods

rnf :: SampleAnalysis -> () #

Eq SampleAnalysis Source # 
Instance details

Defined in Criterion.Types

type Rep SampleAnalysis Source # 
Instance details

Defined in Criterion.Types

type Rep SampleAnalysis = D1 ('MetaData "SampleAnalysis" "Criterion.Types" "criterion-1.6.2.0-By21f2YjhCxFohaNLiJyOk" 'False) (C1 ('MetaCons "SampleAnalysis" 'PrefixI 'True) ((S1 ('MetaSel ('Just "anRegress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Regression]) :*: S1 ('MetaSel ('Just "anMean") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Estimate ConfInt Double))) :*: (S1 ('MetaSel ('Just "anStdDev") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Estimate ConfInt Double)) :*: S1 ('MetaSel ('Just "anOutlierVar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OutlierVariance))))

data DataRecord Source #

Instances

Instances details
FromJSON DataRecord Source # 
Instance details

Defined in Criterion.Types

ToJSON DataRecord Source # 
Instance details

Defined in Criterion.Types

Generic DataRecord Source # 
Instance details

Defined in Criterion.Types

Associated Types

type Rep DataRecord :: Type -> Type #

Read DataRecord Source # 
Instance details

Defined in Criterion.Types

Show DataRecord Source # 
Instance details

Defined in Criterion.Types

Binary DataRecord Source # 
Instance details

Defined in Criterion.Types

NFData DataRecord Source # 
Instance details

Defined in Criterion.Types

Methods

rnf :: DataRecord -> () #

Eq DataRecord Source # 
Instance details

Defined in Criterion.Types

type Rep DataRecord Source # 
Instance details

Defined in Criterion.Types