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

Description

Analysis code for benchmarks.

Synopsis

Documentation

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.3.0-GHH5yeofef278Ue7pPlzMy" '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.3.0-GHH5yeofef278Ue7pPlzMy" '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.3.0-GHH5yeofef278Ue7pPlzMy" '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 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.3.0-GHH5yeofef278Ue7pPlzMy" '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))))

analyseSample Source #

Arguments

:: Int

Experiment number.

-> String

Experiment name.

-> Vector Measured

Sample data.

-> ExceptT String Criterion Report 

Perform an analysis of a measurement.

scale Source #

Arguments

:: Double

Value to multiply by.

-> SampleAnalysis 
-> SampleAnalysis 

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

analyseMean Source #

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 Source #

Count the total number of outliers in a sample.

classifyOutliers :: Sample -> Outliers Source #

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

noteOutliers :: Outliers -> Criterion () Source #

Display a report of the Outliers present in a Sample.

outlierVariance Source #

Arguments

:: Estimate ConfInt Double

Bootstrap estimate of sample mean.

-> Estimate ConfInt Double

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)] Source #

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 Source #

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 Source #

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.