criterion-1.1.4.0: Robust, reliable performance measurement and analysis

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

Criterion.Types

Contents

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 #

Top-level benchmarking configuration.

Constructors

Config 

Fields

  • confInterval :: 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 :: Double

    Number of seconds to run a single benchmark. (In practice, execution time will very slightly exceed this limit.)

  • 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.

  • 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.

Instances

Eq Config # 

Methods

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

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

Data Config # 

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 # 
Show Config # 
Generic Config # 

Associated Types

type Rep Config :: * -> * #

Methods

from :: Config -> Rep Config x #

to :: Rep Config x -> Config #

MonadReader Config Criterion # 

Methods

ask :: Criterion Config #

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

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

type Rep Config # 
type Rep Config = D1 (MetaData "Config" "Criterion.Types" "criterion-1.1.4.0-6laSJqkqOBG3pKwyq5FUfX" False) (C1 (MetaCons "Config" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "confInterval") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) ((:*:) (S1 (MetaSel (Just Symbol "forceGC") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "timeLimit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))) ((:*:) (S1 (MetaSel (Just Symbol "resamples") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "regressions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [([String], String)])) (S1 (MetaSel (Just Symbol "rawDataFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "reportFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath))) ((:*:) (S1 (MetaSel (Just Symbol "csvFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath))) (S1 (MetaSel (Just Symbol "jsonFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath))))) ((:*:) (S1 (MetaSel (Just Symbol "junitFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath))) ((:*:) (S1 (MetaSel (Just Symbol "verbosity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Verbosity)) (S1 (MetaSel (Just Symbol "template") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)))))))

data Verbosity #

Control the amount of information displayed.

Constructors

Quiet 
Normal 
Verbose 

Instances

Bounded Verbosity # 
Enum Verbosity # 
Eq Verbosity # 
Data Verbosity # 

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 # 
Read Verbosity # 
Show Verbosity # 
Generic Verbosity # 

Associated Types

type Rep Verbosity :: * -> * #

type Rep Verbosity # 
type Rep Verbosity = D1 (MetaData "Verbosity" "Criterion.Types" "criterion-1.1.4.0-6laSJqkqOBG3pKwyq5FUfX" False) ((:+:) (C1 (MetaCons "Quiet" PrefixI False) U1) ((:+:) (C1 (MetaCons "Normal" PrefixI False) U1) (C1 (MetaCons "Verbose" PrefixI False) U1)))

Benchmark descriptions

newtype 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

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 :: NFData env => IO env -> (env -> Benchmark) -> Benchmark 
Benchmark :: String -> Benchmarkable -> Benchmark 
BenchGroup :: String -> [Benchmark] -> Benchmark 

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

Eq Measured # 
Data Measured # 

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 :: (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 #

Read Measured # 
Show Measured # 
Generic Measured # 

Associated Types

type Rep Measured :: * -> * #

Methods

from :: Measured -> Rep Measured x #

to :: Rep Measured x -> Measured #

NFData Measured # 

Methods

rnf :: Measured -> () #

ToJSON Measured # 
FromJSON Measured # 
Binary Measured # 

Methods

put :: Measured -> Put #

get :: Get Measured #

putList :: [Measured] -> Put #

type Rep Measured # 

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, undefined 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, as use of strict pattern matching will cause a crash if undefined 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.

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

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

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

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

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

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

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

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.

Result types

data Outliers #

Outliers from sample data, calculated using the boxplot technique.

Constructors

Outliers 

Fields

Instances

Eq Outliers # 
Data Outliers # 

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 :: (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 #

Read Outliers # 
Show Outliers # 
Generic Outliers # 

Associated Types

type Rep Outliers :: * -> * #

Methods

from :: Outliers -> Rep Outliers x #

to :: Rep Outliers x -> Outliers #

Monoid Outliers # 
NFData Outliers # 

Methods

rnf :: Outliers -> () #

ToJSON Outliers # 
FromJSON Outliers # 
Binary Outliers # 

Methods

put :: Outliers -> Put #

get :: Get Outliers #

putList :: [Outliers] -> Put #

type Rep Outliers # 

data OutlierEffect #

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

Eq OutlierEffect # 
Data OutlierEffect # 

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 :: (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 #

Ord OutlierEffect # 
Read OutlierEffect # 
Show OutlierEffect # 
Generic OutlierEffect # 

Associated Types

type Rep OutlierEffect :: * -> * #

NFData OutlierEffect # 

Methods

rnf :: OutlierEffect -> () #

ToJSON OutlierEffect # 
FromJSON OutlierEffect # 
Binary OutlierEffect # 
type Rep OutlierEffect # 
type Rep OutlierEffect = D1 (MetaData "OutlierEffect" "Criterion.Types" "criterion-1.1.4.0-6laSJqkqOBG3pKwyq5FUfX" False) ((:+:) ((:+:) (C1 (MetaCons "Unaffected" PrefixI False) U1) (C1 (MetaCons "Slight" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Moderate" PrefixI False) U1) (C1 (MetaCons "Severe" PrefixI False) U1)))

data OutlierVariance #

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

Constructors

OutlierVariance 

Fields

Instances

Eq OutlierVariance # 
Data OutlierVariance # 

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 :: (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 #

Read OutlierVariance # 
Show OutlierVariance # 
Generic OutlierVariance # 
NFData OutlierVariance # 

Methods

rnf :: OutlierVariance -> () #

ToJSON OutlierVariance # 
FromJSON OutlierVariance # 
Binary OutlierVariance # 
type Rep OutlierVariance # 
type Rep OutlierVariance = D1 (MetaData "OutlierVariance" "Criterion.Types" "criterion-1.1.4.0-6laSJqkqOBG3pKwyq5FUfX" False) (C1 (MetaCons "OutlierVariance" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "ovEffect") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OutlierEffect)) ((:*:) (S1 (MetaSel (Just Symbol "ovDesc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "ovFraction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))))

data Regression #

Results of a linear regression.

Constructors

Regression 

Fields

Instances

Eq Regression # 
Data Regression # 

Methods

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

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

toConstr :: Regression -> Constr #

dataTypeOf :: Regression -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Regression # 
Show Regression # 
Generic Regression # 

Associated Types

type Rep Regression :: * -> * #

NFData Regression # 

Methods

rnf :: Regression -> () #

ToJSON Regression # 
FromJSON Regression # 
Binary Regression # 
type Rep Regression # 
type Rep Regression = D1 (MetaData "Regression" "Criterion.Types" "criterion-1.1.4.0-6laSJqkqOBG3pKwyq5FUfX" False) (C1 (MetaCons "Regression" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "regResponder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "regCoeffs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map String Estimate))) (S1 (MetaSel (Just Symbol "regRSquare") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Estimate)))))

data KDE #

Data for a KDE chart of performance.

Constructors

KDE 

Instances

Eq KDE # 

Methods

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

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

Data KDE # 

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 :: (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 #

Read KDE # 
Show KDE # 

Methods

showsPrec :: Int -> KDE -> ShowS #

show :: KDE -> String #

showList :: [KDE] -> ShowS #

Generic KDE # 

Associated Types

type Rep KDE :: * -> * #

Methods

from :: KDE -> Rep KDE x #

to :: Rep KDE x -> KDE #

NFData KDE # 

Methods

rnf :: KDE -> () #

ToJSON KDE # 
FromJSON KDE # 
Binary KDE # 

Methods

put :: KDE -> Put #

get :: Get KDE #

putList :: [KDE] -> Put #

type Rep KDE # 

data Report #

Report of a sample analysis.

Constructors

Report 

Fields

Instances

Eq Report # 

Methods

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

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

Data Report # 

Methods

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

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

toConstr :: Report -> Constr #

dataTypeOf :: Report -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Report # 
Show Report # 
Generic Report # 

Associated Types

type Rep Report :: * -> * #

Methods

from :: Report -> Rep Report x #

to :: Rep Report x -> Report #

NFData Report # 

Methods

rnf :: Report -> () #

ToJSON Report # 
FromJSON Report # 
Binary Report # 

Methods

put :: Report -> Put #

get :: Get Report #

putList :: [Report] -> Put #

type Rep Report # 

data SampleAnalysis #

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

Constructors

SampleAnalysis 

Fields

Instances

Eq SampleAnalysis # 
Data SampleAnalysis # 

Methods

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

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

toConstr :: SampleAnalysis -> Constr #

dataTypeOf :: SampleAnalysis -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SampleAnalysis # 
Show SampleAnalysis # 
Generic SampleAnalysis # 

Associated Types

type Rep SampleAnalysis :: * -> * #

NFData SampleAnalysis # 

Methods

rnf :: SampleAnalysis -> () #

ToJSON SampleAnalysis # 
FromJSON SampleAnalysis # 
Binary SampleAnalysis # 
type Rep SampleAnalysis # 

data DataRecord #

Instances

Eq DataRecord # 
Data DataRecord # 

Methods

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

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

toConstr :: DataRecord -> Constr #

dataTypeOf :: DataRecord -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DataRecord # 
Show DataRecord # 
Generic DataRecord # 

Associated Types

type Rep DataRecord :: * -> * #

NFData DataRecord # 

Methods

rnf :: DataRecord -> () #

ToJSON DataRecord # 
FromJSON DataRecord # 
Binary DataRecord # 
type Rep DataRecord #