| Copyright | (c) 2009 2010 Bryan O'Sullivan | 
|---|---|
| License | BSD3 | 
| Maintainer | bos@serpentine.com | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Statistics.Resampling
Description
Resampling statistics.
Synopsis
- newtype Resample = Resample {}
- data Bootstrap v a = Bootstrap {- fullSample :: !a
- resamples :: v a
 
- data Estimator
- estimate :: Estimator -> Sample -> Double
- resampleST :: PrimMonad m => Gen (PrimState m) -> [Estimator] -> Int -> Vector Double -> m [Bootstrap Vector Double]
- resample :: GenIO -> [Estimator] -> Int -> Vector Double -> IO [(Estimator, Bootstrap Vector Double)]
- resampleVector :: (PrimMonad m, Vector v a) => Gen (PrimState m) -> v a -> m (v a)
- jackknife :: Estimator -> Sample -> Vector Double
- jackknifeMean :: Sample -> Vector Double
- jackknifeVariance :: Sample -> Vector Double
- jackknifeVarianceUnb :: Sample -> Vector Double
- jackknifeStdDev :: Sample -> Vector Double
- splitGen :: Int -> GenIO -> IO [GenIO]
Data types
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 | |
| Fields | |
Instances
| Eq Resample Source # | |
| Data Resample Source # | |
| Defined in Statistics.Resampling 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 # | |
| ToJSON Resample Source # | |
| Defined in Statistics.Resampling | |
| FromJSON Resample Source # | |
| Binary Resample Source # | |
| type Rep Resample Source # | |
| Defined in Statistics.Resampling | |
Constructors
| Bootstrap | |
| Fields 
 | |
Instances
| Functor v => Functor (Bootstrap v) Source # | |
| Foldable v => Foldable (Bootstrap v) Source # | |
| Defined in Statistics.Resampling 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 # | |
| Traversable v => Traversable (Bootstrap v) Source # | |
| Defined in Statistics.Resampling | |
| (Eq a, Eq (v a)) => Eq (Bootstrap v a) Source # | |
| (Typeable v, Data a, Data (v a)) => Data (Bootstrap v a) Source # | |
| Defined in Statistics.Resampling 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 a, Read (v a)) => Read (Bootstrap v a) Source # | |
| (Show a, Show (v a)) => Show (Bootstrap v a) Source # | |
| Generic (Bootstrap v a) Source # | |
| (ToJSON a, ToJSON (v a)) => ToJSON (Bootstrap v a) Source # | |
| Defined in Statistics.Resampling | |
| (FromJSON a, FromJSON (v a)) => FromJSON (Bootstrap v a) Source # | |
| (Binary a, Binary (v a)) => Binary (Bootstrap v a) Source # | |
| type Rep (Bootstrap v a) Source # | |
| Defined in Statistics.Resampling type Rep (Bootstrap v a) = D1 (MetaData "Bootstrap" "Statistics.Resampling" "statistics-0.15.0.0-AkglZgHZAgx3cdskkvnxTn" False) (C1 (MetaCons "Bootstrap" PrefixI True) (S1 (MetaSel (Just "fullSample") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "resamples") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (v a)))) | |
Resampling
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.
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.
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.