statistics-0.14.0.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

Contents

Description

Resampling statistics.

Synopsis

Data types

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.14.0.0-9xPMo3QbnR7BEP0FkvUcUB" True) (C1 (MetaCons "Resample" PrefixI True) (S1 (MetaSel (Just Symbol "fromResample") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Double))))

data Bootstrap v a Source #

Constructors

Bootstrap 

Fields

Instances

Functor v => Functor (Bootstrap v) Source # 

Methods

fmap :: (a -> b) -> Bootstrap v a -> Bootstrap v b #

(<$) :: a -> Bootstrap v b -> Bootstrap v a #

Foldable v => Foldable (Bootstrap v) Source # 

Methods

fold :: Monoid m => Bootstrap v m -> m #

foldMap :: Monoid m => (a -> m) -> Bootstrap v a -> m #

foldr :: (a -> b -> b) -> b -> Bootstrap v a -> b #

foldr' :: (a -> b -> b) -> b -> Bootstrap v a -> b #

foldl :: (b -> a -> b) -> b -> Bootstrap v a -> b #

foldl' :: (b -> a -> b) -> b -> Bootstrap v a -> b #

foldr1 :: (a -> a -> a) -> Bootstrap v a -> a #

foldl1 :: (a -> a -> a) -> Bootstrap v a -> a #

toList :: Bootstrap v a -> [a] #

null :: Bootstrap v a -> Bool #

length :: Bootstrap v a -> Int #

elem :: Eq a => a -> Bootstrap v a -> Bool #

maximum :: Ord a => Bootstrap v a -> a #

minimum :: Ord a => Bootstrap v a -> a #

sum :: Num a => Bootstrap v a -> a #

product :: Num a => Bootstrap v a -> a #

Traversable v => Traversable (Bootstrap v) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Bootstrap v a -> f (Bootstrap v b) #

sequenceA :: Applicative f => Bootstrap v (f a) -> f (Bootstrap v a) #

mapM :: Monad m => (a -> m b) -> Bootstrap v a -> m (Bootstrap v b) #

sequence :: Monad m => Bootstrap v (m a) -> m (Bootstrap v a) #

(Eq (v a), Eq a) => Eq (Bootstrap v a) Source # 

Methods

(==) :: Bootstrap v a -> Bootstrap v a -> Bool #

(/=) :: Bootstrap v a -> Bootstrap v a -> Bool #

(Data (v a), Data a, Typeable (* -> *) v) => Data (Bootstrap v a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bootstrap v a -> c (Bootstrap v a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Bootstrap v a) #

toConstr :: Bootstrap v a -> Constr #

dataTypeOf :: Bootstrap v a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Bootstrap v a -> Bootstrap v a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Bootstrap v a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bootstrap v a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bootstrap v a -> m (Bootstrap v a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bootstrap v a -> m (Bootstrap v a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bootstrap v a -> m (Bootstrap v a) #

(Read (v a), Read a) => Read (Bootstrap v a) Source # 
(Show (v a), Show a) => Show (Bootstrap v a) Source # 

Methods

showsPrec :: Int -> Bootstrap v a -> ShowS #

show :: Bootstrap v a -> String #

showList :: [Bootstrap v a] -> ShowS #

Generic (Bootstrap v a) Source # 

Associated Types

type Rep (Bootstrap v a) :: * -> * #

Methods

from :: Bootstrap v a -> Rep (Bootstrap v a) x #

to :: Rep (Bootstrap v a) x -> Bootstrap v a #

(ToJSON a, ToJSON (v a)) => ToJSON (Bootstrap v a) Source # 
(FromJSON a, FromJSON (v a)) => FromJSON (Bootstrap v a) Source # 
(Binary a, Binary (v a)) => Binary (Bootstrap v a) Source # 

Methods

put :: Bootstrap v a -> Put #

get :: Get (Bootstrap v a) #

putList :: [Bootstrap v a] -> Put #

type Rep (Bootstrap v a) Source # 
type Rep (Bootstrap v a) = D1 (MetaData "Bootstrap" "Statistics.Resampling" "statistics-0.14.0.0-9xPMo3QbnR7BEP0FkvUcUB" False) (C1 (MetaCons "Bootstrap" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "fullSample") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) (S1 (MetaSel (Just Symbol "resamples") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (v a)))))

data Estimator Source #

An estimator of a property of a sample, such as its mean.

The use of an algebraic data type here allows functions such as jackknife and bootstrapBCA to use more efficient algorithms when possible.

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

Run an Estimator over a sample.

Resampling

resampleST Source #

Arguments

:: PrimMonad m 
=> Gen (PrimState m) 
-> [Estimator]

Estimation functions.

-> Int

Number of resamples to compute.

-> Vector Double

Original sample.

-> m [Bootstrap Vector Double] 

Single threaded and deterministic version of resample.

resample Source #

Arguments

:: GenIO 
-> [Estimator]

Estimation functions.

-> Int

Number of resamples to compute.

-> Vector Double

Original sample.

-> IO [(Estimator, Bootstrap Vector Double)] 

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

resampleVector :: (PrimMonad m, Vector v a) => Gen (PrimState m) -> v a -> m (v a) Source #

Create vector using resamples

Jackknife

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.

Helper functions

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

Split a generator into several that can run independently.