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

Description

Analysis code for benchmarks.

Synopsis

Documentation

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-LaD0ajjusGsLEYrbAsTlGZ" 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-LaD0ajjusGsLEYrbAsTlGZ" 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 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 # 

analyseSample #

Arguments

:: Int

Experiment number.

-> String

Experiment name.

-> Vector Measured

Sample data.

-> ExceptT String Criterion Report 

Perform an analysis of a measurement.

scale #

Arguments

:: Double

Value to multiply by.

-> SampleAnalysis 
-> SampleAnalysis 

Multiply the Estimates in an analysis by the given value, using scale.

analyseMean #

Arguments

:: Sample 
-> Int

Number of iterations used to compute the sample.

-> Criterion Double 

Display the mean of a Sample, and characterise the outliers present in the sample.

countOutliers :: Outliers -> Int64 #

Count the total number of outliers in a sample.

classifyOutliers :: Sample -> Outliers #

Classify outliers in a data set, using the boxplot technique.

noteOutliers :: Outliers -> Criterion () #

Display a report of the Outliers present in a Sample.

outlierVariance #

Arguments

:: Estimate

Bootstrap estimate of sample mean.

-> Estimate

Bootstrap estimate of sample standard deviation.

-> Double

Number of original iterations.

-> OutlierVariance 

Compute the extent to which outliers in the sample data affect the sample mean and standard deviation.

resolveAccessors :: [String] -> Either String [(String, Measured -> Maybe Double)] #

Given a list of accessor names (see measureKeys), return either a mapping from accessor name to function or an error message if any names are wrong.

validateAccessors #

Arguments

:: [String]

Predictor names.

-> String

Responder name.

-> Either String [(String, Measured -> Maybe Double)] 

Given predictor and responder names, do some basic validation, then hand back the relevant accessors.

regress #

Arguments

:: GenIO 
-> [String]

Predictor names.

-> String

Responder name.

-> Vector Measured 
-> ExceptT String Criterion Regression 

Regress the given predictors against the responder.

Errors may be returned under various circumstances, such as invalid names or lack of needed data.

See olsRegress for details of the regression performed.