gauge-0.2.3: small framework for performance measurement and analysis

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

Gauge.Analysis

Description

Analysis code for benchmarks.

Synopsis

Documentation

data Outliers Source #

Outliers from sample data, calculated using the boxplot technique.

Constructors

Outliers 

Fields

Instances
Eq Outliers Source # 
Instance details

Defined in Gauge.Analysis

Data Outliers Source # 
Instance details

Defined in Gauge.Analysis

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 #

Show Outliers Source # 
Instance details

Defined in Gauge.Analysis

Generic Outliers Source # 
Instance details

Defined in Gauge.Analysis

Associated Types

type Rep Outliers :: * -> * #

Methods

from :: Outliers -> Rep Outliers x #

to :: Rep Outliers x -> Outliers #

NFData Outliers Source # 
Instance details

Defined in Gauge.Analysis

Methods

rnf :: Outliers -> () #

type Rep Outliers Source # 
Instance details

Defined in Gauge.Analysis

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
Eq OutlierEffect Source # 
Instance details

Defined in Gauge.Analysis

Data OutlierEffect Source # 
Instance details

Defined in Gauge.Analysis

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

Defined in Gauge.Analysis

Show OutlierEffect Source # 
Instance details

Defined in Gauge.Analysis

Generic OutlierEffect Source # 
Instance details

Defined in Gauge.Analysis

Associated Types

type Rep OutlierEffect :: * -> * #

NFData OutlierEffect Source # 
Instance details

Defined in Gauge.Analysis

Methods

rnf :: OutlierEffect -> () #

type Rep OutlierEffect Source # 
Instance details

Defined in Gauge.Analysis

type Rep OutlierEffect = D1 (MetaData "OutlierEffect" "Gauge.Analysis" "gauge-0.2.3-Imkc1Njmn4gAlDTJZlAwSy" 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 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
Eq OutlierVariance Source # 
Instance details

Defined in Gauge.Analysis

Data OutlierVariance Source # 
Instance details

Defined in Gauge.Analysis

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 #

Show OutlierVariance Source # 
Instance details

Defined in Gauge.Analysis

Generic OutlierVariance Source # 
Instance details

Defined in Gauge.Analysis

Associated Types

type Rep OutlierVariance :: * -> * #

NFData OutlierVariance Source # 
Instance details

Defined in Gauge.Analysis

Methods

rnf :: OutlierVariance -> () #

type Rep OutlierVariance Source # 
Instance details

Defined in Gauge.Analysis

type Rep OutlierVariance = D1 (MetaData "OutlierVariance" "Gauge.Analysis" "gauge-0.2.3-Imkc1Njmn4gAlDTJZlAwSy" 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 Report Source #

Report of a sample analysis.

Instances
Eq Report Source # 
Instance details

Defined in Gauge.Analysis

Methods

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

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

Show Report Source # 
Instance details

Defined in Gauge.Analysis

Generic Report Source # 
Instance details

Defined in Gauge.Analysis

Associated Types

type Rep Report :: * -> * #

Methods

from :: Report -> Rep Report x #

to :: Rep Report x -> Report #

NFData Report Source # 
Instance details

Defined in Gauge.Analysis

Methods

rnf :: Report -> () #

type Rep Report Source # 
Instance details

Defined in Gauge.Analysis

type Rep Report

data SampleAnalysis Source #

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

Constructors

SampleAnalysis 

Fields

Instances
Eq SampleAnalysis Source # 
Instance details

Defined in Gauge.Analysis

Show SampleAnalysis Source # 
Instance details

Defined in Gauge.Analysis

Generic SampleAnalysis Source # 
Instance details

Defined in Gauge.Analysis

Associated Types

type Rep SampleAnalysis :: * -> * #

NFData SampleAnalysis Source # 
Instance details

Defined in Gauge.Analysis

Methods

rnf :: SampleAnalysis -> () #

type Rep SampleAnalysis Source # 
Instance details

Defined in Gauge.Analysis

analyseSample Source #

Arguments

:: String

Experiment name.

-> Vector Measured

Sample data.

-> Gauge (Either String 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.

analyseBenchmark :: String -> Vector Measured -> Gauge Report Source #

Analyse a single benchmark.

analyseMean Source #

Arguments

:: Sample 
-> Int

Number of iterations used to compute the sample.

-> Gauge 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 -> Gauge () 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.

regress Source #

Arguments

:: GenIO 
-> [String]

Predictor names.

-> String

Responder name.

-> Vector Measured 
-> Gauge (Either String 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.

benchmark' :: Benchmarkable -> IO () Source #

Run a benchmark interactively and analyse its performanc.

benchmarkWith' :: Config -> Benchmarkable -> IO () Source #

Run a benchmark interactively and analyse its performance.