Copyright | (c) 2009-2014 Bryan O'Sullivan |
---|---|
License | BSD-style |
Maintainer | bos@serpentine.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
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
- data Config = Config {
- confInterval :: CL Double
- timeLimit :: Double
- resamples :: Int
- regressions :: [([String], String)]
- rawDataFile :: Maybe FilePath
- reportFile :: Maybe FilePath
- csvFile :: Maybe FilePath
- jsonFile :: Maybe FilePath
- junitFile :: Maybe FilePath
- verbosity :: Verbosity
- template :: FilePath
- data Verbosity
- data Benchmarkable = NFData a => Benchmarkable {
- allocEnv :: Int64 -> IO a
- cleanEnv :: Int64 -> a -> IO ()
- runRepeatedly :: a -> Int64 -> IO ()
- perRun :: Bool
- data Benchmark where
- Environment :: forall env a. NFData env => IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
- Benchmark :: String -> Benchmarkable -> Benchmark
- BenchGroup :: String -> [Benchmark] -> Benchmark
- data Measured = Measured {
- measTime :: !Double
- measCpuTime :: !Double
- measCycles :: !Int64
- measIters :: !Int64
- measAllocated :: !Int64
- measPeakMbAllocated :: !Int64
- measNumGcs :: !Int64
- measBytesCopied :: !Int64
- measMutatorWallSeconds :: !Double
- measMutatorCpuSeconds :: !Double
- measGcWallSeconds :: !Double
- measGcCpuSeconds :: !Double
- fromInt :: Int64 -> Maybe Int64
- toInt :: Maybe Int64 -> Int64
- fromDouble :: Double -> Maybe Double
- toDouble :: Maybe Double -> Double
- measureAccessors :: Map String (Measured -> Maybe Double, String)
- measureKeys :: [String]
- measure :: Unbox a => (Measured -> a) -> Vector Measured -> Vector a
- rescale :: Measured -> Measured
- env :: NFData env => IO env -> (env -> Benchmark) -> Benchmark
- envWithCleanup :: NFData env => IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
- perBatchEnv :: (NFData env, NFData b) => (Int64 -> IO env) -> (env -> IO b) -> Benchmarkable
- perBatchEnvWithCleanup :: (NFData env, NFData b) => (Int64 -> IO env) -> (Int64 -> env -> IO ()) -> (env -> IO b) -> Benchmarkable
- perRunEnv :: (NFData env, NFData b) => IO env -> (env -> IO b) -> Benchmarkable
- perRunEnvWithCleanup :: (NFData env, NFData b) => IO env -> (env -> IO ()) -> (env -> IO b) -> Benchmarkable
- toBenchmarkable :: (Int64 -> IO ()) -> Benchmarkable
- bench :: String -> Benchmarkable -> Benchmark
- bgroup :: String -> [Benchmark] -> Benchmark
- addPrefix :: String -> String -> String
- benchNames :: Benchmark -> [String]
- nf :: NFData b => (a -> b) -> a -> Benchmarkable
- whnf :: (a -> b) -> a -> Benchmarkable
- nfIO :: NFData a => IO a -> Benchmarkable
- whnfIO :: IO a -> Benchmarkable
- nfAppIO :: NFData b => (a -> IO b) -> a -> Benchmarkable
- whnfAppIO :: (a -> IO b) -> a -> Benchmarkable
- data Outliers = Outliers {
- samplesSeen :: !Int64
- lowSevere :: !Int64
- lowMild :: !Int64
- highMild :: !Int64
- highSevere :: !Int64
- data OutlierEffect
- = Unaffected
- | Slight
- | Moderate
- | Severe
- data OutlierVariance = OutlierVariance {
- ovEffect :: OutlierEffect
- ovDesc :: String
- ovFraction :: Double
- data Regression = Regression {
- regResponder :: String
- regCoeffs :: Map String (Estimate ConfInt Double)
- regRSquare :: Estimate ConfInt Double
- data KDE = KDE {}
- data Report = Report {
- reportNumber :: Int
- reportName :: String
- reportKeys :: [String]
- reportMeasured :: Vector Measured
- reportAnalysis :: SampleAnalysis
- reportOutliers :: Outliers
- reportKDEs :: [KDE]
- data SampleAnalysis = SampleAnalysis {
- anRegress :: [Regression]
- anMean :: Estimate ConfInt Double
- anStdDev :: Estimate ConfInt Double
- anOutlierVar :: OutlierVariance
- data DataRecord
- = Measurement Int String (Vector Measured)
- | Analysed Report
Configuration
Top-level benchmarking configuration.
Constructors
Config | |
Fields
|
Instances
Data Config Source # | |
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 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 # | |
Read Config Source # | |
Defined in Criterion.Types | |
Show Config Source # | |
Eq Config Source # | |
MonadReader Config Criterion | |
type Rep Config Source # | |
Defined in Criterion.Types type Rep Config = D1 ('MetaData "Config" "Criterion.Types" "criterion-1.6.1.0-2h8jJxyb3zL8Vx5Ow7sziS" 'False) (C1 ('MetaCons "Config" 'PrefixI 'True) (((S1 ('MetaSel ('Just "confInterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CL Double)) :*: S1 ('MetaSel ('Just "timeLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "resamples") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "regressions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [([String], String)]) :*: S1 ('MetaSel ('Just "rawDataFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath))))) :*: ((S1 ('MetaSel ('Just "reportFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "csvFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: S1 ('MetaSel ('Just "jsonFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)))) :*: (S1 ('MetaSel ('Just "junitFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "verbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Verbosity) :*: S1 ('MetaSel ('Just "template") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))))) |
Control the amount of information displayed.
Instances
Data Verbosity Source # | |
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 # | |
Defined in Criterion.Types | |
Enum Verbosity Source # | |
Defined in Criterion.Types | |
Generic Verbosity Source # | |
Read Verbosity Source # | |
Defined in Criterion.Types | |
Show Verbosity Source # | |
Eq Verbosity Source # | |
Ord Verbosity Source # | |
Defined in Criterion.Types | |
type Rep Verbosity Source # | |
Defined in Criterion.Types type Rep Verbosity = D1 ('MetaData "Verbosity" "Criterion.Types" "criterion-1.6.1.0-2h8jJxyb3zL8Vx5Ow7sziS" '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 Source #
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
|
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 withbench
. - A (possibly nested) group of
Benchmark
s, created withbgroup
.
Constructors
Environment :: forall env a. NFData env => IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark | |
Benchmark :: String -> Benchmarkable -> Benchmark | |
BenchGroup :: String -> [Benchmark] -> Benchmark |
Measurements
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
FromJSON Measured | |
Defined in Criterion.Measurement.Types | |
ToJSON Measured | |
Defined in Criterion.Measurement.Types Methods toEncoding :: Measured -> Encoding toJSONList :: [Measured] -> Value toEncodingList :: [Measured] -> Encoding | |
Data Measured | |
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 | |
Read Measured | |
Defined in Criterion.Measurement.Types | |
Show Measured | |
Binary Measured | |
NFData Measured | |
Defined in Criterion.Measurement.Types | |
Eq Measured | |
type Rep Measured | |
Defined in Criterion.Measurement.Types type Rep Measured = D1 ('MetaData "Measured" "Criterion.Measurement.Types" "criterion-measurement-0.2.1.0-JwUoAjmXFInDmt11x04qVy" 'False) (C1 ('MetaCons "Measured" 'PrefixI 'True) (((S1 ('MetaSel ('Just "measTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Double) :*: (S1 ('MetaSel ('Just "measCpuTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Double) :*: S1 ('MetaSel ('Just "measCycles") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int64))) :*: (S1 ('MetaSel ('Just "measIters") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int64) :*: (S1 ('MetaSel ('Just "measAllocated") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int64) :*: S1 ('MetaSel ('Just "measPeakMbAllocated") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int64)))) :*: ((S1 ('MetaSel ('Just "measNumGcs") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int64) :*: (S1 ('MetaSel ('Just "measBytesCopied") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int64) :*: S1 ('MetaSel ('Just "measMutatorWallSeconds") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Double))) :*: (S1 ('MetaSel ('Just "measMutatorCpuSeconds") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Double) :*: (S1 ('MetaSel ('Just "measGcWallSeconds") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Double) :*: S1 ('MetaSel ('Just "measGcCpuSeconds") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Double)))))) |
fromInt :: Int64 -> Maybe Int64 Source #
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 Source #
Convert from a true value back to the packed representation used for GC measurements.
fromDouble :: Double -> Maybe Double Source #
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 Source #
Convert from a true value back to the packed representation used for GC measurements.
measureAccessors :: Map String (Measured -> Maybe Double, String) Source #
Field names and accessors for a Measured
record.
measureKeys :: [String] Source #
Field names in a Measured
record, in the order in which they
appear.
Benchmark construction
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.
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 |
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 Source #
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.
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.
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 |
toBenchmarkable :: (Int64 -> IO ()) -> Benchmarkable Source #
Construct a Benchmarkable
value from an impure action, where the Int64
parameter indicates the number of times to run the action.
Arguments
:: String | A name to identify the benchmark. |
-> Benchmarkable | An activity to be benchmarked. |
-> Benchmark |
Create a single benchmark.
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.
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] Source #
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 Source #
Apply an argument to a function, and evaluate the result to normal form (NF).
whnf :: (a -> b) -> a -> Benchmarkable Source #
Apply an argument to a function, and evaluate the result to weak head normal form (WHNF).
nfIO :: NFData a => IO a -> Benchmarkable Source #
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 Source #
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 Source #
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 Source #
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
Outliers from sample data, calculated using the boxplot technique.
Constructors
Outliers | |
Fields
|
Instances
FromJSON Outliers Source # | |
Defined in Criterion.Types | |
ToJSON Outliers Source # | |
Defined in Criterion.Types Methods toEncoding :: Outliers -> Encoding toJSONList :: [Outliers] -> Value toEncodingList :: [Outliers] -> Encoding | |
Data Outliers Source # | |
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 # | |
Semigroup Outliers Source # | |
Generic Outliers Source # | |
Read Outliers Source # | |
Defined in Criterion.Types | |
Show Outliers Source # | |
Binary Outliers Source # | |
NFData Outliers Source # | |
Defined in Criterion.Types | |
Eq Outliers Source # | |
type Rep Outliers Source # | |
Defined in Criterion.Types type Rep Outliers = D1 ('MetaData "Outliers" "Criterion.Types" "criterion-1.6.1.0-2h8jJxyb3zL8Vx5Ow7sziS" '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
FromJSON OutlierEffect Source # | |
Defined in Criterion.Types | |
ToJSON OutlierEffect Source # | |
Defined in Criterion.Types Methods toJSON :: OutlierEffect -> Value toEncoding :: OutlierEffect -> Encoding toJSONList :: [OutlierEffect] -> Value toEncodingList :: [OutlierEffect] -> Encoding | |
Data OutlierEffect Source # | |
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 # | |
Defined in Criterion.Types Associated Types type Rep OutlierEffect :: Type -> Type | |
Read OutlierEffect Source # | |
Defined in Criterion.Types Methods readsPrec :: Int -> ReadS OutlierEffect readList :: ReadS [OutlierEffect] readPrec :: ReadPrec OutlierEffect readListPrec :: ReadPrec [OutlierEffect] | |
Show OutlierEffect Source # | |
Defined in Criterion.Types Methods showsPrec :: Int -> OutlierEffect -> ShowS show :: OutlierEffect -> String showList :: [OutlierEffect] -> ShowS | |
Binary OutlierEffect Source # | |
Defined in Criterion.Types | |
NFData OutlierEffect Source # | |
Defined in Criterion.Types Methods rnf :: OutlierEffect -> () | |
Eq OutlierEffect Source # | |
Defined in Criterion.Types | |
Ord OutlierEffect Source # | |
Defined in Criterion.Types Methods compare :: OutlierEffect -> OutlierEffect -> Ordering (<) :: OutlierEffect -> OutlierEffect -> Bool (<=) :: OutlierEffect -> OutlierEffect -> Bool (>) :: OutlierEffect -> OutlierEffect -> Bool (>=) :: OutlierEffect -> OutlierEffect -> Bool max :: OutlierEffect -> OutlierEffect -> OutlierEffect min :: OutlierEffect -> OutlierEffect -> OutlierEffect | |
type Rep OutlierEffect Source # | |
Defined in Criterion.Types type Rep OutlierEffect = D1 ('MetaData "OutlierEffect" "Criterion.Types" "criterion-1.6.1.0-2h8jJxyb3zL8Vx5Ow7sziS" '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
FromJSON OutlierVariance Source # | |
Defined in Criterion.Types Methods parseJSON :: Value -> Parser OutlierVariance parseJSONList :: Value -> Parser [OutlierVariance] | |
ToJSON OutlierVariance Source # | |
Defined in Criterion.Types Methods toJSON :: OutlierVariance -> Value toEncoding :: OutlierVariance -> Encoding toJSONList :: [OutlierVariance] -> Value toEncodingList :: [OutlierVariance] -> Encoding | |
Data OutlierVariance Source # | |
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 # | |
Defined in Criterion.Types Associated Types type Rep OutlierVariance :: Type -> Type Methods from :: OutlierVariance -> Rep OutlierVariance x to :: Rep OutlierVariance x -> OutlierVariance | |
Read OutlierVariance Source # | |
Defined in Criterion.Types Methods readsPrec :: Int -> ReadS OutlierVariance readList :: ReadS [OutlierVariance] readPrec :: ReadPrec OutlierVariance readListPrec :: ReadPrec [OutlierVariance] | |
Show OutlierVariance Source # | |
Defined in Criterion.Types Methods showsPrec :: Int -> OutlierVariance -> ShowS show :: OutlierVariance -> String showList :: [OutlierVariance] -> ShowS | |
Binary OutlierVariance Source # | |
Defined in Criterion.Types | |
NFData OutlierVariance Source # | |
Defined in Criterion.Types Methods rnf :: OutlierVariance -> () | |
Eq OutlierVariance Source # | |
Defined in Criterion.Types Methods (==) :: OutlierVariance -> OutlierVariance -> Bool (/=) :: OutlierVariance -> OutlierVariance -> Bool | |
type Rep OutlierVariance Source # | |
Defined in Criterion.Types type Rep OutlierVariance = D1 ('MetaData "OutlierVariance" "Criterion.Types" "criterion-1.6.1.0-2h8jJxyb3zL8Vx5Ow7sziS" '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
FromJSON Regression Source # | |
Defined in Criterion.Types | |
ToJSON Regression Source # | |
Defined in Criterion.Types Methods toJSON :: Regression -> Value toEncoding :: Regression -> Encoding toJSONList :: [Regression] -> Value toEncodingList :: [Regression] -> Encoding | |
Generic Regression Source # | |
Defined in Criterion.Types Associated Types type Rep Regression :: Type -> Type | |
Read Regression Source # | |
Defined in Criterion.Types Methods readsPrec :: Int -> ReadS Regression readList :: ReadS [Regression] readPrec :: ReadPrec Regression readListPrec :: ReadPrec [Regression] | |
Show Regression Source # | |
Defined in Criterion.Types Methods showsPrec :: Int -> Regression -> ShowS show :: Regression -> String showList :: [Regression] -> ShowS | |
Binary Regression Source # | |
Defined in Criterion.Types | |
NFData Regression Source # | |
Defined in Criterion.Types Methods rnf :: Regression -> () | |
Eq Regression Source # | |
Defined in Criterion.Types | |
type Rep Regression Source # | |
Defined in Criterion.Types type Rep Regression = D1 ('MetaData "Regression" "Criterion.Types" "criterion-1.6.1.0-2h8jJxyb3zL8Vx5Ow7sziS" '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 for a KDE chart of performance.
Instances
FromJSON KDE Source # | |
Defined in Criterion.Types | |
ToJSON KDE Source # | |
Defined in Criterion.Types | |
Data KDE Source # | |
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 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 # | |
Read KDE Source # | |
Defined in Criterion.Types | |
Show KDE Source # | |
Binary KDE Source # | |
NFData KDE Source # | |
Defined in Criterion.Types | |
Eq KDE Source # | |
type Rep KDE Source # | |
Defined in Criterion.Types type Rep KDE = D1 ('MetaData "KDE" "Criterion.Types" "criterion-1.6.1.0-2h8jJxyb3zL8Vx5Ow7sziS" '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))))) |
Report of a sample analysis.
Constructors
Report | |
Fields
|
Instances
FromJSON Report Source # | |
Defined in Criterion.Types | |
ToJSON Report Source # | |
Defined in Criterion.Types Methods toEncoding :: Report -> Encoding toJSONList :: [Report] -> Value toEncodingList :: [Report] -> Encoding | |
Generic Report Source # | |
Read Report Source # | |
Defined in Criterion.Types | |
Show Report Source # | |
Binary Report Source # | |
NFData Report Source # | |
Defined in Criterion.Types | |
Eq Report Source # | |
type Rep Report Source # | |
Defined in Criterion.Types type Rep Report = D1 ('MetaData "Report" "Criterion.Types" "criterion-1.6.1.0-2h8jJxyb3zL8Vx5Ow7sziS" 'False) (C1 ('MetaCons "Report" 'PrefixI 'True) ((S1 ('MetaSel ('Just "reportNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "reportName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "reportKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: ((S1 ('MetaSel ('Just "reportMeasured") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Measured)) :*: S1 ('MetaSel ('Just "reportAnalysis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SampleAnalysis)) :*: (S1 ('MetaSel ('Just "reportOutliers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Outliers) :*: S1 ('MetaSel ('Just "reportKDEs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [KDE]))))) |
data SampleAnalysis Source #
Result of a bootstrap analysis of a non-parametric sample.
Constructors
SampleAnalysis | |
Fields
|
Instances
FromJSON SampleAnalysis Source # | |
Defined in Criterion.Types | |
ToJSON SampleAnalysis Source # | |
Defined in Criterion.Types Methods toJSON :: SampleAnalysis -> Value toEncoding :: SampleAnalysis -> Encoding toJSONList :: [SampleAnalysis] -> Value toEncodingList :: [SampleAnalysis] -> Encoding | |
Generic SampleAnalysis Source # | |
Defined in Criterion.Types Associated Types type Rep SampleAnalysis :: Type -> Type | |
Read SampleAnalysis Source # | |
Defined in Criterion.Types Methods readsPrec :: Int -> ReadS SampleAnalysis readList :: ReadS [SampleAnalysis] readPrec :: ReadPrec SampleAnalysis readListPrec :: ReadPrec [SampleAnalysis] | |
Show SampleAnalysis Source # | |
Defined in Criterion.Types Methods showsPrec :: Int -> SampleAnalysis -> ShowS show :: SampleAnalysis -> String showList :: [SampleAnalysis] -> ShowS | |
Binary SampleAnalysis Source # | |
Defined in Criterion.Types | |
NFData SampleAnalysis Source # | |
Defined in Criterion.Types Methods rnf :: SampleAnalysis -> () | |
Eq SampleAnalysis Source # | |
Defined in Criterion.Types Methods (==) :: SampleAnalysis -> SampleAnalysis -> Bool (/=) :: SampleAnalysis -> SampleAnalysis -> Bool | |
type Rep SampleAnalysis Source # | |
Defined in Criterion.Types type Rep SampleAnalysis = D1 ('MetaData "SampleAnalysis" "Criterion.Types" "criterion-1.6.1.0-2h8jJxyb3zL8Vx5Ow7sziS" '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 #
Constructors
Measurement Int String (Vector Measured) | |
Analysed Report |
Instances
FromJSON DataRecord Source # | |
Defined in Criterion.Types | |
ToJSON DataRecord Source # | |
Defined in Criterion.Types Methods toJSON :: DataRecord -> Value toEncoding :: DataRecord -> Encoding toJSONList :: [DataRecord] -> Value toEncodingList :: [DataRecord] -> Encoding | |
Generic DataRecord Source # | |
Defined in Criterion.Types Associated Types type Rep DataRecord :: Type -> Type | |
Read DataRecord Source # | |
Defined in Criterion.Types Methods readsPrec :: Int -> ReadS DataRecord readList :: ReadS [DataRecord] readPrec :: ReadPrec DataRecord readListPrec :: ReadPrec [DataRecord] | |
Show DataRecord Source # | |
Defined in Criterion.Types Methods showsPrec :: Int -> DataRecord -> ShowS show :: DataRecord -> String showList :: [DataRecord] -> ShowS | |
Binary DataRecord Source # | |
Defined in Criterion.Types | |
NFData DataRecord Source # | |
Defined in Criterion.Types Methods rnf :: DataRecord -> () | |
Eq DataRecord Source # | |
Defined in Criterion.Types | |
type Rep DataRecord Source # | |
Defined in Criterion.Types type Rep DataRecord = D1 ('MetaData "DataRecord" "Criterion.Types" "criterion-1.6.1.0-2h8jJxyb3zL8Vx5Ow7sziS" 'False) (C1 ('MetaCons "Measurement" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Measured)))) :+: C1 ('MetaCons "Analysed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Report))) |