Copyright | (c) 2009-2014 Bryan O'Sullivan |
---|---|
License | BSD-style |
Maintainer | bos@serpentine.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Analysis code for benchmarks.
Synopsis
- data Outliers = Outliers {
- samplesSeen :: !Int64
- lowSevere :: !Int64
- lowMild :: !Int64
- highMild :: !Int64
- highSevere :: !Int64
- data OutlierEffect
- = Unaffected
- | Slight
- | Moderate
- | Severe
- data OutlierVariance = OutlierVariance {}
- data Report
- data SampleAnalysis = SampleAnalysis {
- anRegress :: [Regression]
- anMean :: Estimate ConfInt Double
- anStdDev :: Estimate ConfInt Double
- anOutlierVar :: OutlierVariance
- analyseSample :: String -> Vector Measured -> Gauge (Either String Report)
- scale :: Double -> SampleAnalysis -> SampleAnalysis
- analyseBenchmark :: String -> Vector Measured -> Gauge Report
- analyseMean :: Sample -> Int -> Gauge Double
- countOutliers :: Outliers -> Int64
- classifyOutliers :: Sample -> Outliers
- noteOutliers :: Outliers -> Gauge ()
- outlierVariance :: Estimate ConfInt Double -> Estimate ConfInt Double -> Double -> OutlierVariance
- regress :: GenIO -> [String] -> String -> Vector Measured -> Gauge (Either String Regression)
- benchmark' :: Benchmarkable -> IO ()
- benchmarkWith' :: Config -> Benchmarkable -> IO ()
Documentation
Outliers from sample data, calculated using the boxplot technique.
Outliers | |
|
Instances
Eq Outliers Source # | |
Data Outliers Source # | |
Defined in Gauge.Analysis 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 # | |
Generic Outliers Source # | |
NFData Outliers Source # | |
Defined in Gauge.Analysis | |
type Rep Outliers Source # | |
Defined in Gauge.Analysis type Rep Outliers = D1 (MetaData "Outliers" "Gauge.Analysis" "gauge-0.2.3-Imkc1Njmn4gAlDTJZlAwSy" 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.
Unaffected | Less than 1% effect. |
Slight | Between 1% and 10%. |
Moderate | Between 10% and 50%. |
Severe | Above 50% (i.e. measurements are useless). |
Instances
data OutlierVariance Source #
Analysis of the extent to which outliers in a sample affect its standard deviation (and to some extent, its mean).
OutlierVariance | |
|
Instances
Report of a sample analysis.
data SampleAnalysis Source #
Result of a bootstrap analysis of a non-parametric sample.
SampleAnalysis | |
|
Instances
Eq SampleAnalysis Source # | |
Defined in Gauge.Analysis (==) :: SampleAnalysis -> SampleAnalysis -> Bool # (/=) :: SampleAnalysis -> SampleAnalysis -> Bool # | |
Show SampleAnalysis Source # | |
Defined in Gauge.Analysis showsPrec :: Int -> SampleAnalysis -> ShowS # show :: SampleAnalysis -> String # showList :: [SampleAnalysis] -> ShowS # | |
Generic SampleAnalysis Source # | |
Defined in Gauge.Analysis type Rep SampleAnalysis :: * -> * # from :: SampleAnalysis -> Rep SampleAnalysis x # to :: Rep SampleAnalysis x -> SampleAnalysis # | |
NFData SampleAnalysis Source # | |
Defined in Gauge.Analysis rnf :: SampleAnalysis -> () # | |
type Rep SampleAnalysis Source # | |
Defined in Gauge.Analysis |
Perform an analysis of a measurement.
:: Double | Value to multiply by. |
-> SampleAnalysis | |
-> SampleAnalysis |
Multiply the Estimate
s in an analysis by the given value, using
scale
.
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
.
:: 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.
:: 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.