statistics-0.13.3.0: A library of statistical types, data, and functions

Copyright(c) 2009, 2010 Bryan O'Sullivan
LicenseBSD3
Maintainerbos@serpentine.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Statistics.Resampling

Description

Resampling statistics.

Synopsis

Documentation

newtype Resample Source #

A resample drawn randomly, with replacement, from a set of data points. Distinct from a normal array to make it harder for your humble author's brain to go wrong.

Constructors

Resample 

Instances

Eq Resample Source # 
Data Resample Source # 

Methods

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

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

toConstr :: Resample -> Constr #

dataTypeOf :: Resample -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Resample Source # 
Show Resample Source # 
Generic Resample Source # 

Associated Types

type Rep Resample :: * -> * #

Methods

from :: Resample -> Rep Resample x #

to :: Rep Resample x -> Resample #

ToJSON Resample Source # 
FromJSON Resample Source # 
Binary Resample Source # 

Methods

put :: Resample -> Put #

get :: Get Resample #

putList :: [Resample] -> Put #

type Rep Resample Source # 
type Rep Resample = D1 (MetaData "Resample" "Statistics.Resampling" "statistics-0.13.3.0-4cjYwUsSjEQGDMfnb5oeqe" True) (C1 (MetaCons "Resample" PrefixI True) (S1 (MetaSel (Just Symbol "fromResample") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Double))))

jackknife :: Estimator -> Sample -> Vector Double Source #

O(n) or O(n^2) Compute a statistical estimate repeatedly over a sample, each time omitting a successive element.

jackknifeMean :: Sample -> Vector Double Source #

O(n) Compute the jackknife mean of a sample.

jackknifeVariance :: Sample -> Vector Double Source #

O(n) Compute the jackknife variance of a sample.

jackknifeVarianceUnb :: Sample -> Vector Double Source #

O(n) Compute the unbiased jackknife variance of a sample.

jackknifeStdDev :: Sample -> Vector Double Source #

O(n) Compute the jackknife standard deviation of a sample.

resample Source #

Arguments

:: GenIO 
-> [Estimator]

Estimation functions.

-> Int

Number of resamples to compute.

-> Sample

Original sample.

-> IO [Resample] 

O(e*r*s) Resample a data set repeatedly, with replacement, computing each estimate over the resampled data.

This function is expensive; it has to do work proportional to e*r*s, where e is the number of estimation functions, r is the number of resamples to compute, and s is the number of original samples.

To improve performance, this function will make use of all available CPUs. At least with GHC 7.0, parallel performance seems best if the parallel garbage collector is disabled (RTS option -qg).

estimate :: Estimator -> Sample -> Double Source #

Run an Estimator over a sample.

splitGen :: Int -> GenIO -> IO [GenIO] Source #

Split a generator into several that can run independently.