{-# LANGUAGE BangPatterns #-}{-# LANGUAGE DeriveDataTypeable #-}{-# LANGUAGE DeriveFoldable #-}{-# LANGUAGE DeriveFunctor #-}{-# LANGUAGE DeriveGeneric #-}{-# LANGUAGE DeriveTraversable #-}{-# LANGUAGE FlexibleContexts #-}{-# LANGUAGE TypeFamilies #-}-- |-- Module : Statistics.Resampling-- Copyright : (c) 2009, 2010 Bryan O'Sullivan-- License : BSD3---- Maintainer : bos@serpentine.com-- Stability : experimental-- Portability : portable---- Resampling statistics.moduleStatistics.Resampling(-- * Data typesResample (..),Bootstrap (..),Estimator (..),estimate -- * Resampling,resampleST ,resample ,resampleVector -- * Jackknife,jackknife ,jackknifeMean ,jackknifeVariance ,jackknifeVarianceUnb ,jackknifeStdDev -- * Helper functions,splitGen )whereimportData.Aeson(FromJSON,ToJSON)importControl.Concurrent.Async(forConcurrently_)importControl.Monad(forM_,forM,replicateM,liftM2)importControl.Monad.Primitive(PrimMonad(..))importData.Binary(Binary(..))importData.Data(Data,Typeable)importData.Vector.Algorithms.Intro(sort)importData.Vector.Binary()importData.Vector.Generic(unsafeFreeze,unsafeThaw)importData.Word(Word32)importqualifiedData.FoldableasTimportqualifiedData.TraversableasTimportqualifiedData.Vector.GenericasGimportqualifiedData.Vector.UnboxedasUimportqualifiedData.Vector.Unboxed.MutableasMUimportGHC.Conc(numCapabilities)importGHC.Generics(Generic)importNumeric.Sum(Summation(..),kbn)importStatistics.Function (indices )importStatistics.Sample (mean ,stdDev ,variance ,varianceUnbiased )importStatistics.Types (Sample )importSystem.Random.MWC(Gen,GenIO,initialize,uniformR,uniformVector)------------------------------------------------------------------ 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.newtypeResample =Resample {Resample -> Vector Double
fromResample ::U.VectorDouble}deriving(Resample -> Resample -> Bool
(Resample -> Resample -> Bool)
-> (Resample -> Resample -> Bool) -> Eq Resample
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Resample -> Resample -> Bool
== :: Resample -> Resample -> Bool
$c/= :: Resample -> Resample -> Bool
/= :: Resample -> Resample -> Bool
Eq,ReadPrec [Resample]
ReadPrec Resample
Int -> ReadS Resample
ReadS [Resample]
(Int -> ReadS Resample)
-> ReadS [Resample]
-> ReadPrec Resample
-> ReadPrec [Resample]
-> Read Resample
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Resample
readsPrec :: Int -> ReadS Resample
$creadList :: ReadS [Resample]
readList :: ReadS [Resample]
$creadPrec :: ReadPrec Resample
readPrec :: ReadPrec Resample
$creadListPrec :: ReadPrec [Resample]
readListPrec :: ReadPrec [Resample]
Read,Int -> Resample -> ShowS
[Resample] -> ShowS
Resample -> String
(Int -> Resample -> ShowS)
-> (Resample -> String) -> ([Resample] -> ShowS) -> Show Resample
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Resample -> ShowS
showsPrec :: Int -> Resample -> ShowS
$cshow :: Resample -> String
show :: Resample -> String
$cshowList :: [Resample] -> ShowS
showList :: [Resample] -> ShowS
Show,Typeable,Typeable Resample
Typeable Resample =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Resample -> c Resample)
-> (forall (c :: * -> *).
 (forall b r. Data b => c (b -> r) -> c r)
 -> (forall r. r -> c r) -> Constr -> c Resample)
-> (Resample -> Constr)
-> (Resample -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
 Typeable t =>
 (forall d. Data d => c (t d)) -> Maybe (c Resample))
-> (forall (t :: * -> * -> *) (c :: * -> *).
 Typeable t =>
 (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Resample))
-> ((forall b. Data b => b -> b) -> Resample -> Resample)
-> (forall r r'.
 (r -> r' -> r)
 -> r -> (forall d. Data d => d -> r') -> Resample -> r)
-> (forall r r'.
 (r' -> r -> r)
 -> r -> (forall d. Data d => d -> r') -> Resample -> r)
-> (forall u. (forall d. Data d => d -> u) -> Resample -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Resample -> u)
-> (forall (m :: * -> *).
 Monad m =>
 (forall d. Data d => d -> m d) -> Resample -> m Resample)
-> (forall (m :: * -> *).
 MonadPlus m =>
 (forall d. Data d => d -> m d) -> Resample -> m Resample)
-> (forall (m :: * -> *).
 MonadPlus m =>
 (forall d. Data d => d -> m d) -> Resample -> m Resample)
-> Data Resample
Resample -> Constr
Resample -> DataType
(forall b. Data b => b -> b) -> Resample -> Resample
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
 (forall b r. Data b => c (b -> r) -> c r)
 -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
 Typeable t =>
 (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
 Typeable t =>
 (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
 (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
 (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
 Monad m =>
 (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
 MonadPlus m =>
 (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
 MonadPlus m =>
 (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Resample -> u
forall u. (forall d. Data d => d -> u) -> Resample -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Resample -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Resample -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Resample -> m Resample
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Resample -> m Resample
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Resample
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Resample -> c Resample
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Resample)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Resample)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Resample -> c Resample
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Resample -> c Resample
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Resample
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Resample
$ctoConstr :: Resample -> Constr
toConstr :: Resample -> Constr
$cdataTypeOf :: Resample -> DataType
dataTypeOf :: Resample -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Resample)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Resample)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Resample)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Resample)
$cgmapT :: (forall b. Data b => b -> b) -> Resample -> Resample
gmapT :: (forall b. Data b => b -> b) -> Resample -> Resample
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Resample -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Resample -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Resample -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Resample -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Resample -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Resample -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Resample -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Resample -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Resample -> m Resample
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Resample -> m Resample
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Resample -> m Resample
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Resample -> m Resample
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Resample -> m Resample
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Resample -> m Resample
Data,(forall x. Resample -> Rep Resample x)
-> (forall x. Rep Resample x -> Resample) -> Generic Resample
forall x. Rep Resample x -> Resample
forall x. Resample -> Rep Resample x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Resample -> Rep Resample x
from :: forall x. Resample -> Rep Resample x
$cto :: forall x. Rep Resample x -> Resample
to :: forall x. Rep Resample x -> Resample
Generic)instanceFromJSONResample instanceToJSONResample instanceBinaryResample whereput :: Resample -> Put
put =Vector Double -> Put
forall t. Binary t => t -> Put
put(Vector Double -> Put)
-> (Resample -> Vector Double) -> Resample -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Resample -> Vector Double
fromResample get :: Get Resample
get =(Vector Double -> Resample) -> Get (Vector Double) -> Get Resample
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmapVector Double -> Resample
Resample Get (Vector Double)
forall t. Binary t => Get t
getdataBootstrap v a =Bootstrap {forall (v :: * -> *) a. Bootstrap v a -> a
fullSample ::!a ,forall (v :: * -> *) a. Bootstrap v a -> v a
resamples ::v a }deriving(Bootstrap v a -> Bootstrap v a -> Bool
(Bootstrap v a -> Bootstrap v a -> Bool)
-> (Bootstrap v a -> Bootstrap v a -> Bool) -> Eq (Bootstrap v a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (v :: * -> *) a.
(Eq a, Eq (v a)) =>
Bootstrap v a -> Bootstrap v a -> Bool
$c== :: forall (v :: * -> *) a.
(Eq a, Eq (v a)) =>
Bootstrap v a -> Bootstrap v a -> Bool
== :: Bootstrap v a -> Bootstrap v a -> Bool
$c/= :: forall (v :: * -> *) a.
(Eq a, Eq (v a)) =>
Bootstrap v a -> Bootstrap v a -> Bool
/= :: Bootstrap v a -> Bootstrap v a -> Bool
Eq,ReadPrec [Bootstrap v a]
ReadPrec (Bootstrap v a)
Int -> ReadS (Bootstrap v a)
ReadS [Bootstrap v a]
(Int -> ReadS (Bootstrap v a))
-> ReadS [Bootstrap v a]
-> ReadPrec (Bootstrap v a)
-> ReadPrec [Bootstrap v a]
-> Read (Bootstrap v a)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall (v :: * -> *) a.
(Read a, Read (v a)) =>
ReadPrec [Bootstrap v a]
forall (v :: * -> *) a.
(Read a, Read (v a)) =>
ReadPrec (Bootstrap v a)
forall (v :: * -> *) a.
(Read a, Read (v a)) =>
Int -> ReadS (Bootstrap v a)
forall (v :: * -> *) a.
(Read a, Read (v a)) =>
ReadS [Bootstrap v a]
$creadsPrec :: forall (v :: * -> *) a.
(Read a, Read (v a)) =>
Int -> ReadS (Bootstrap v a)
readsPrec :: Int -> ReadS (Bootstrap v a)
$creadList :: forall (v :: * -> *) a.
(Read a, Read (v a)) =>
ReadS [Bootstrap v a]
readList :: ReadS [Bootstrap v a]
$creadPrec :: forall (v :: * -> *) a.
(Read a, Read (v a)) =>
ReadPrec (Bootstrap v a)
readPrec :: ReadPrec (Bootstrap v a)
$creadListPrec :: forall (v :: * -> *) a.
(Read a, Read (v a)) =>
ReadPrec [Bootstrap v a]
readListPrec :: ReadPrec [Bootstrap v a]
Read,Int -> Bootstrap v a -> ShowS
[Bootstrap v a] -> ShowS
Bootstrap v a -> String
(Int -> Bootstrap v a -> ShowS)
-> (Bootstrap v a -> String)
-> ([Bootstrap v a] -> ShowS)
-> Show (Bootstrap v a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (v :: * -> *) a.
(Show a, Show (v a)) =>
Int -> Bootstrap v a -> ShowS
forall (v :: * -> *) a.
(Show a, Show (v a)) =>
[Bootstrap v a] -> ShowS
forall (v :: * -> *) a.
(Show a, Show (v a)) =>
Bootstrap v a -> String
$cshowsPrec :: forall (v :: * -> *) a.
(Show a, Show (v a)) =>
Int -> Bootstrap v a -> ShowS
showsPrec :: Int -> Bootstrap v a -> ShowS
$cshow :: forall (v :: * -> *) a.
(Show a, Show (v a)) =>
Bootstrap v a -> String
show :: Bootstrap v a -> String
$cshowList :: forall (v :: * -> *) a.
(Show a, Show (v a)) =>
[Bootstrap v a] -> ShowS
showList :: [Bootstrap v a] -> ShowS
Show,(forall x. Bootstrap v a -> Rep (Bootstrap v a) x)
-> (forall x. Rep (Bootstrap v a) x -> Bootstrap v a)
-> Generic (Bootstrap v a)
forall x. Rep (Bootstrap v a) x -> Bootstrap v a
forall x. Bootstrap v a -> Rep (Bootstrap v a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (v :: * -> *) a x. Rep (Bootstrap v a) x -> Bootstrap v a
forall (v :: * -> *) a x. Bootstrap v a -> Rep (Bootstrap v a) x
$cfrom :: forall (v :: * -> *) a x. Bootstrap v a -> Rep (Bootstrap v a) x
from :: forall x. Bootstrap v a -> Rep (Bootstrap v a) x
$cto :: forall (v :: * -> *) a x. Rep (Bootstrap v a) x -> Bootstrap v a
to :: forall x. Rep (Bootstrap v a) x -> Bootstrap v a
Generic,(forall a b. (a -> b) -> Bootstrap v a -> Bootstrap v b)
-> (forall a b. a -> Bootstrap v b -> Bootstrap v a)
-> Functor (Bootstrap v)
forall a b. a -> Bootstrap v b -> Bootstrap v a
forall a b. (a -> b) -> Bootstrap v a -> Bootstrap v b
forall (v :: * -> *) a b.
Functor v =>
a -> Bootstrap v b -> Bootstrap v a
forall (v :: * -> *) a b.
Functor v =>
(a -> b) -> Bootstrap v a -> Bootstrap v b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall (v :: * -> *) a b.
Functor v =>
(a -> b) -> Bootstrap v a -> Bootstrap v b
fmap :: forall a b. (a -> b) -> Bootstrap v a -> Bootstrap v b
$c<$ :: forall (v :: * -> *) a b.
Functor v =>
a -> Bootstrap v b -> Bootstrap v a
<$ :: forall a b. a -> Bootstrap v b -> Bootstrap v a
Functor,(forall m. Monoid m => Bootstrap v m -> m)
-> (forall m a. Monoid m => (a -> m) -> Bootstrap v a -> m)
-> (forall m a. Monoid m => (a -> m) -> Bootstrap v a -> m)
-> (forall a b. (a -> b -> b) -> b -> Bootstrap v a -> b)
-> (forall a b. (a -> b -> b) -> b -> Bootstrap v a -> b)
-> (forall b a. (b -> a -> b) -> b -> Bootstrap v a -> b)
-> (forall b a. (b -> a -> b) -> b -> Bootstrap v a -> b)
-> (forall a. (a -> a -> a) -> Bootstrap v a -> a)
-> (forall a. (a -> a -> a) -> Bootstrap v a -> a)
-> (forall a. Bootstrap v a -> [a])
-> (forall a. Bootstrap v a -> Bool)
-> (forall a. Bootstrap v a -> Int)
-> (forall a. Eq a => a -> Bootstrap v a -> Bool)
-> (forall a. Ord a => Bootstrap v a -> a)
-> (forall a. Ord a => Bootstrap v a -> a)
-> (forall a. Num a => Bootstrap v a -> a)
-> (forall a. Num a => Bootstrap v a -> a)
-> Foldable (Bootstrap v)
forall a. Eq a => a -> Bootstrap v a -> Bool
forall a. Num a => Bootstrap v a -> a
forall a. Ord a => Bootstrap v a -> a
forall m. Monoid m => Bootstrap v m -> m
forall a. Bootstrap v a -> Bool
forall a. Bootstrap v a -> Int
forall a. Bootstrap v a -> [a]
forall a. (a -> a -> a) -> Bootstrap v a -> a
forall m a. Monoid m => (a -> m) -> Bootstrap v a -> m
forall b a. (b -> a -> b) -> b -> Bootstrap v a -> b
forall a b. (a -> b -> b) -> b -> Bootstrap v a -> b
forall (v :: * -> *) a.
(Foldable v, Eq a) =>
a -> Bootstrap v a -> Bool
forall (v :: * -> *) a. (Foldable v, Num a) => Bootstrap v a -> a
forall (v :: * -> *) a. (Foldable v, Ord a) => Bootstrap v a -> a
forall (v :: * -> *) m.
(Foldable v, Monoid m) =>
Bootstrap v m -> m
forall (v :: * -> *) a. Foldable v => Bootstrap v a -> Bool
forall (v :: * -> *) a. Foldable v => Bootstrap v a -> Int
forall (v :: * -> *) a. Foldable v => Bootstrap v a -> [a]
forall (v :: * -> *) a.
Foldable v =>
(a -> a -> a) -> Bootstrap v a -> a
forall (v :: * -> *) m a.
(Foldable v, Monoid m) =>
(a -> m) -> Bootstrap v a -> m
forall (v :: * -> *) b a.
Foldable v =>
(b -> a -> b) -> b -> Bootstrap v a -> b
forall (v :: * -> *) a b.
Foldable v =>
(a -> b -> b) -> b -> Bootstrap v a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall (v :: * -> *) m.
(Foldable v, Monoid m) =>
Bootstrap v m -> m
fold :: forall m. Monoid m => Bootstrap v m -> m
$cfoldMap :: forall (v :: * -> *) m a.
(Foldable v, Monoid m) =>
(a -> m) -> Bootstrap v a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Bootstrap v a -> m
$cfoldMap' :: forall (v :: * -> *) m a.
(Foldable v, Monoid m) =>
(a -> m) -> Bootstrap v a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> Bootstrap v a -> m
$cfoldr :: forall (v :: * -> *) a b.
Foldable v =>
(a -> b -> b) -> b -> Bootstrap v a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Bootstrap v a -> b
$cfoldr' :: forall (v :: * -> *) a b.
Foldable v =>
(a -> b -> b) -> b -> Bootstrap v a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Bootstrap v a -> b
$cfoldl :: forall (v :: * -> *) b a.
Foldable v =>
(b -> a -> b) -> b -> Bootstrap v a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Bootstrap v a -> b
$cfoldl' :: forall (v :: * -> *) b a.
Foldable v =>
(b -> a -> b) -> b -> Bootstrap v a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> Bootstrap v a -> b
$cfoldr1 :: forall (v :: * -> *) a.
Foldable v =>
(a -> a -> a) -> Bootstrap v a -> a
foldr1 :: forall a. (a -> a -> a) -> Bootstrap v a -> a
$cfoldl1 :: forall (v :: * -> *) a.
Foldable v =>
(a -> a -> a) -> Bootstrap v a -> a
foldl1 :: forall a. (a -> a -> a) -> Bootstrap v a -> a
$ctoList :: forall (v :: * -> *) a. Foldable v => Bootstrap v a -> [a]
toList :: forall a. Bootstrap v a -> [a]
$cnull :: forall (v :: * -> *) a. Foldable v => Bootstrap v a -> Bool
null :: forall a. Bootstrap v a -> Bool
$clength :: forall (v :: * -> *) a. Foldable v => Bootstrap v a -> Int
length :: forall a. Bootstrap v a -> Int
$celem :: forall (v :: * -> *) a.
(Foldable v, Eq a) =>
a -> Bootstrap v a -> Bool
elem :: forall a. Eq a => a -> Bootstrap v a -> Bool
$cmaximum :: forall (v :: * -> *) a. (Foldable v, Ord a) => Bootstrap v a -> a
maximum :: forall a. Ord a => Bootstrap v a -> a
$cminimum :: forall (v :: * -> *) a. (Foldable v, Ord a) => Bootstrap v a -> a
minimum :: forall a. Ord a => Bootstrap v a -> a
$csum :: forall (v :: * -> *) a. (Foldable v, Num a) => Bootstrap v a -> a
sum :: forall a. Num a => Bootstrap v a -> a
$cproduct :: forall (v :: * -> *) a. (Foldable v, Num a) => Bootstrap v a -> a
product :: forall a. Num a => Bootstrap v a -> a
T.Foldable,Functor (Bootstrap v)
Foldable (Bootstrap v)
(Functor (Bootstrap v), Foldable (Bootstrap v)) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> Bootstrap v a -> f (Bootstrap v b))
-> (forall (f :: * -> *) a.
 Applicative f =>
 Bootstrap v (f a) -> f (Bootstrap v a))
-> (forall (m :: * -> *) a b.
 Monad m =>
 (a -> m b) -> Bootstrap v a -> m (Bootstrap v b))
-> (forall (m :: * -> *) a.
 Monad m =>
 Bootstrap v (m a) -> m (Bootstrap v a))
-> Traversable (Bootstrap v)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
 Monad m =>
 (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (v :: * -> *). Traversable v => Functor (Bootstrap v)
forall (v :: * -> *). Traversable v => Foldable (Bootstrap v)
forall (v :: * -> *) (m :: * -> *) a.
(Traversable v, Monad m) =>
Bootstrap v (m a) -> m (Bootstrap v a)
forall (v :: * -> *) (f :: * -> *) a.
(Traversable v, Applicative f) =>
Bootstrap v (f a) -> f (Bootstrap v a)
forall (v :: * -> *) (m :: * -> *) a b.
(Traversable v, Monad m) =>
(a -> m b) -> Bootstrap v a -> m (Bootstrap v b)
forall (v :: * -> *) (f :: * -> *) a b.
(Traversable v, Applicative f) =>
(a -> f b) -> Bootstrap v a -> f (Bootstrap v b)
forall (m :: * -> *) a.
Monad m =>
Bootstrap v (m a) -> m (Bootstrap v a)
forall (f :: * -> *) a.
Applicative f =>
Bootstrap v (f a) -> f (Bootstrap v a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Bootstrap v a -> m (Bootstrap v b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Bootstrap v a -> f (Bootstrap v b)
$ctraverse :: forall (v :: * -> *) (f :: * -> *) a b.
(Traversable v, Applicative f) =>
(a -> f b) -> Bootstrap v a -> f (Bootstrap v b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Bootstrap v a -> f (Bootstrap v b)
$csequenceA :: forall (v :: * -> *) (f :: * -> *) a.
(Traversable v, Applicative f) =>
Bootstrap v (f a) -> f (Bootstrap v a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Bootstrap v (f a) -> f (Bootstrap v a)
$cmapM :: forall (v :: * -> *) (m :: * -> *) a b.
(Traversable v, Monad m) =>
(a -> m b) -> Bootstrap v a -> m (Bootstrap v b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Bootstrap v a -> m (Bootstrap v b)
$csequence :: forall (v :: * -> *) (m :: * -> *) a.
(Traversable v, Monad m) =>
Bootstrap v (m a) -> m (Bootstrap v a)
sequence :: forall (m :: * -> *) a.
Monad m =>
Bootstrap v (m a) -> m (Bootstrap v a)
T.Traversable,Typeable,Typeable (Bootstrap v a)
Typeable (Bootstrap v a) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Bootstrap v a -> c (Bootstrap v a))
-> (forall (c :: * -> *).
 (forall b r. Data b => c (b -> r) -> c r)
 -> (forall r. r -> c r) -> Constr -> c (Bootstrap v a))
-> (Bootstrap v a -> Constr)
-> (Bootstrap v a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
 Typeable t =>
 (forall d. Data d => c (t d)) -> Maybe (c (Bootstrap v a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
 Typeable t =>
 (forall d e. (Data d, Data e) => c (t d e))
 -> Maybe (c (Bootstrap v a)))
-> ((forall b. Data b => b -> b) -> Bootstrap v a -> Bootstrap v a)
-> (forall r r'.
 (r -> r' -> r)
 -> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r)
-> (forall r r'.
 (r' -> r -> r)
 -> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Bootstrap v a -> [u])
-> (forall u.
 Int -> (forall d. Data d => d -> u) -> Bootstrap v a -> u)
-> (forall (m :: * -> *).
 Monad m =>
 (forall d. Data d => d -> m d)
 -> Bootstrap v a -> m (Bootstrap v a))
-> (forall (m :: * -> *).
 MonadPlus m =>
 (forall d. Data d => d -> m d)
 -> Bootstrap v a -> m (Bootstrap v a))
-> (forall (m :: * -> *).
 MonadPlus m =>
 (forall d. Data d => d -> m d)
 -> Bootstrap v a -> m (Bootstrap v a))
-> Data (Bootstrap v a)
Bootstrap v a -> Constr
Bootstrap v a -> DataType
(forall b. Data b => b -> b) -> Bootstrap v a -> Bootstrap v a
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
 (forall b r. Data b => c (b -> r) -> c r)
 -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
 Typeable t =>
 (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
 Typeable t =>
 (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
 (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
 (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
 Monad m =>
 (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
 MonadPlus m =>
 (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
 MonadPlus m =>
 (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Bootstrap v a -> u
forall u. (forall d. Data d => d -> u) -> Bootstrap v a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Bootstrap v a -> m (Bootstrap v a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Bootstrap v a -> m (Bootstrap v a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Bootstrap v a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bootstrap v a -> c (Bootstrap v a)
forall (v :: * -> *) a.
(Typeable v, Data a, Data (v a)) =>
Typeable (Bootstrap v a)
forall (v :: * -> *) a.
(Typeable v, Data a, Data (v a)) =>
Bootstrap v a -> Constr
forall (v :: * -> *) a.
(Typeable v, Data a, Data (v a)) =>
Bootstrap v a -> DataType
forall (v :: * -> *) a.
(Typeable v, Data a, Data (v a)) =>
(forall b. Data b => b -> b) -> Bootstrap v a -> Bootstrap v a
forall (v :: * -> *) a u.
(Typeable v, Data a, Data (v a)) =>
Int -> (forall d. Data d => d -> u) -> Bootstrap v a -> u
forall (v :: * -> *) a u.
(Typeable v, Data a, Data (v a)) =>
(forall d. Data d => d -> u) -> Bootstrap v a -> [u]
forall (v :: * -> *) a r r'.
(Typeable v, Data a, Data (v a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r
forall (v :: * -> *) a r r'.
(Typeable v, Data a, Data (v a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r
forall (v :: * -> *) a (m :: * -> *).
(Typeable v, Data a, Data (v a), Monad m) =>
(forall d. Data d => d -> m d)
-> Bootstrap v a -> m (Bootstrap v a)
forall (v :: * -> *) a (m :: * -> *).
(Typeable v, Data a, Data (v a), MonadPlus m) =>
(forall d. Data d => d -> m d)
-> Bootstrap v a -> m (Bootstrap v a)
forall (v :: * -> *) a (c :: * -> *).
(Typeable v, Data a, Data (v a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Bootstrap v a)
forall (v :: * -> *) a (c :: * -> *).
(Typeable v, Data a, Data (v a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bootstrap v a -> c (Bootstrap v a)
forall (v :: * -> *) a (t :: * -> *) (c :: * -> *).
(Typeable v, Data a, Data (v a), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Bootstrap v a))
forall (v :: * -> *) a (t :: * -> * -> *) (c :: * -> *).
(Typeable v, Data a, Data (v a), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Bootstrap v a))
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Bootstrap v a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Bootstrap v a))
$cgfoldl :: forall (v :: * -> *) a (c :: * -> *).
(Typeable v, Data a, Data (v a)) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bootstrap v a -> c (Bootstrap v a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bootstrap v a -> c (Bootstrap v a)
$cgunfold :: forall (v :: * -> *) a (c :: * -> *).
(Typeable v, Data a, Data (v a)) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Bootstrap v a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Bootstrap v a)
$ctoConstr :: forall (v :: * -> *) a.
(Typeable v, Data a, Data (v a)) =>
Bootstrap v a -> Constr
toConstr :: Bootstrap v a -> Constr
$cdataTypeOf :: forall (v :: * -> *) a.
(Typeable v, Data a, Data (v a)) =>
Bootstrap v a -> DataType
dataTypeOf :: Bootstrap v a -> DataType
$cdataCast1 :: forall (v :: * -> *) a (t :: * -> *) (c :: * -> *).
(Typeable v, Data a, Data (v a), Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Bootstrap v a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Bootstrap v a))
$cdataCast2 :: forall (v :: * -> *) a (t :: * -> * -> *) (c :: * -> *).
(Typeable v, Data a, Data (v a), Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Bootstrap v a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Bootstrap v a))
$cgmapT :: forall (v :: * -> *) a.
(Typeable v, Data a, Data (v a)) =>
(forall b. Data b => b -> b) -> Bootstrap v a -> Bootstrap v a
gmapT :: (forall b. Data b => b -> b) -> Bootstrap v a -> Bootstrap v a
$cgmapQl :: forall (v :: * -> *) a r r'.
(Typeable v, Data a, Data (v a)) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r
$cgmapQr :: forall (v :: * -> *) a r r'.
(Typeable v, Data a, Data (v a)) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bootstrap v a -> r
$cgmapQ :: forall (v :: * -> *) a u.
(Typeable v, Data a, Data (v a)) =>
(forall d. Data d => d -> u) -> Bootstrap v a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Bootstrap v a -> [u]
$cgmapQi :: forall (v :: * -> *) a u.
(Typeable v, Data a, Data (v a)) =>
Int -> (forall d. Data d => d -> u) -> Bootstrap v a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Bootstrap v a -> u
$cgmapM :: forall (v :: * -> *) a (m :: * -> *).
(Typeable v, Data a, Data (v a), Monad m) =>
(forall d. Data d => d -> m d)
-> Bootstrap v a -> m (Bootstrap v a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Bootstrap v a -> m (Bootstrap v a)
$cgmapMp :: forall (v :: * -> *) a (m :: * -> *).
(Typeable v, Data a, Data (v a), MonadPlus m) =>
(forall d. Data d => d -> m d)
-> Bootstrap v a -> m (Bootstrap v a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Bootstrap v a -> m (Bootstrap v a)
$cgmapMo :: forall (v :: * -> *) a (m :: * -> *).
(Typeable v, Data a, Data (v a), MonadPlus m) =>
(forall d. Data d => d -> m d)
-> Bootstrap v a -> m (Bootstrap v a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Bootstrap v a -> m (Bootstrap v a)
Data)instance(Binarya ,Binary(v a ))=>Binary(Bootstrap v a )whereget :: Get (Bootstrap v a)
get=(a -> v a -> Bootstrap v a)
-> Get a -> Get (v a) -> Get (Bootstrap v a)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2a -> v a -> Bootstrap v a
forall (v :: * -> *) a. a -> v a -> Bootstrap v a
Bootstrap Get a
forall t. Binary t => Get t
getGet (v a)
forall t. Binary t => Get t
getput :: Bootstrap v a -> Put
put(Bootstrap a
fs v a
rs )=a -> Put
forall t. Binary t => t -> Put
puta
fs Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>v a -> Put
forall t. Binary t => t -> Put
putv a
rs instance(FromJSONa ,FromJSON(v a ))=>FromJSON(Bootstrap v a )instance(ToJSONa ,ToJSON(v a ))=>ToJSON(Bootstrap v a )-- | 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.dataEstimator =Mean |Variance |VarianceUnbiased |StdDev |Function (Sample ->Double)-- | Run an 'Estimator' over a sample.estimate ::Estimator ->Sample ->Doubleestimate :: Estimator -> Vector Double -> Double
estimate Estimator
Mean =Vector Double -> Double
forall (v :: * -> *). Vector v Double => v Double -> Double
mean estimate Estimator
Variance =Vector Double -> Double
forall (v :: * -> *). Vector v Double => v Double -> Double
variance estimate Estimator
VarianceUnbiased =Vector Double -> Double
forall (v :: * -> *). Vector v Double => v Double -> Double
varianceUnbiased estimate Estimator
StdDev =Vector Double -> Double
forall (v :: * -> *). Vector v Double => v Double -> Double
stdDev estimate (Function Vector Double -> Double
est )=Vector Double -> Double
est ------------------------------------------------------------------ Resampling------------------------------------------------------------------ | Single threaded and deterministic version of resample.resampleST ::PrimMonadm =>Gen(PrimStatem )->[Estimator ]-- ^ Estimation functions.->Int-- ^ Number of resamples to compute.->U.VectorDouble-- ^ Original sample.->m [Bootstrap U.VectorDouble]resampleST :: forall (m :: * -> *).
PrimMonad m =>
Gen (PrimState m)
-> [Estimator]
-> Int
-> Vector Double
-> m [Bootstrap Vector Double]
resampleST Gen (PrimState m)
gen [Estimator]
ests Int
numResamples Vector Double
sample =do-- Generate resamples[Vector Double]
res <-[Estimator]
-> (Estimator -> m (Vector Double)) -> m [Vector Double]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM[Estimator]
ests ((Estimator -> m (Vector Double)) -> m [Vector Double])
-> (Estimator -> m (Vector Double)) -> m [Vector Double]
forall a b. (a -> b) -> a -> b
$\Estimator
e ->Int -> m Double -> m (Vector Double)
forall (m :: * -> *) a.
(Monad m, Unbox a) =>
Int -> m a -> m (Vector a)
U.replicateMInt
numResamples (m Double -> m (Vector Double)) -> m Double -> m (Vector Double)
forall a b. (a -> b) -> a -> b
$doVector Double
v <-Gen (PrimState m) -> Vector Double -> m (Vector Double)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Gen (PrimState m) -> v a -> m (v a)
resampleVector Gen (PrimState m)
gen Vector Double
sample Double -> m Double
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return(Double -> m Double) -> Double -> m Double
forall a b. (a -> b) -> a -> b
$!Estimator -> Vector Double -> Double
estimate Estimator
e Vector Double
v -- Sort resamples[MVector (PrimState m) Double]
resM <-(Vector Double -> m (MVector (PrimState m) Double))
-> [Vector Double] -> m [MVector (PrimState m) Double]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapMVector Double -> m (MVector (PrimState m) Double)
Vector Double -> m (Mutable Vector (PrimState m) Double)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
v a -> m (Mutable v (PrimState m) a)
unsafeThaw[Vector Double]
res (MVector (PrimState m) Double -> m ())
-> [MVector (PrimState m) Double] -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_MVector (PrimState m) Double -> m ()
forall (m :: * -> *) (v :: * -> * -> *) e.
(PrimMonad m, MVector v e, Ord e) =>
v (PrimState m) e -> m ()
sort[MVector (PrimState m) Double]
resM [Vector Double]
resSorted <-(MVector (PrimState m) Double -> m (Vector Double))
-> [MVector (PrimState m) Double] -> m [Vector Double]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapMMVector (PrimState m) Double -> m (Vector Double)
Mutable Vector (PrimState m) Double -> m (Vector Double)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Mutable v (PrimState m) a -> m (v a)
unsafeFreeze[MVector (PrimState m) Double]
resM [Bootstrap Vector Double] -> m [Bootstrap Vector Double]
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return([Bootstrap Vector Double] -> m [Bootstrap Vector Double])
-> [Bootstrap Vector Double] -> m [Bootstrap Vector Double]
forall a b. (a -> b) -> a -> b
$(Double -> Vector Double -> Bootstrap Vector Double)
-> [Double] -> [Vector Double] -> [Bootstrap Vector Double]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWithDouble -> Vector Double -> Bootstrap Vector Double
forall (v :: * -> *) a. a -> v a -> Bootstrap v a
Bootstrap [Estimator -> Vector Double -> Double
estimate Estimator
e Vector Double
sample |Estimator
e <-[Estimator]
ests ][Vector Double]
resSorted -- | /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@).resample ::GenIO->[Estimator ]-- ^ Estimation functions.->Int-- ^ Number of resamples to compute.->U.VectorDouble-- ^ Original sample.->IO[(Estimator ,Bootstrap U.VectorDouble)]resample :: GenIO
-> [Estimator]
-> Int
-> Vector Double
-> IO [(Estimator, Bootstrap Vector Double)]
resample GenIO
gen [Estimator]
ests Int
numResamples Vector Double
samples =doletixs :: [Int]
ixs =(Int -> Int -> Int) -> Int -> [Int] -> [Int]
forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanlInt -> Int -> Int
forall a. Num a => a -> a -> a
(+)Int
0([Int] -> [Int]) -> [Int] -> [Int]
forall a b. (a -> b) -> a -> b
$(Int -> Int -> Int) -> [Int] -> [Int] -> [Int]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWithInt -> Int -> Int
forall a. Num a => a -> a -> a
(+)(Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicateInt
numCapabilitiesInt
q )(Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicateInt
r Int
1[Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++Int -> [Int]
forall a. a -> [a]
repeatInt
0)where(Int
q ,Int
r )=Int
numResamples Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`quotRem`Int
numCapabilities[MVector RealWorld Double]
results <-(Estimator -> IO (MVector RealWorld Double))
-> [Estimator] -> IO [MVector RealWorld Double]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM(IO (MVector RealWorld Double)
-> Estimator -> IO (MVector RealWorld Double)
forall a b. a -> b -> a
const(Int -> IO (MVector (PrimState IO) Double)
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
Int -> m (MVector (PrimState m) a)
MU.newInt
numResamples ))[Estimator]
ests [Gen RealWorld]
gens <-Int -> GenIO -> IO [GenIO]
splitGen Int
numCapabilitiesGenIO
gen [(Int, Int, Gen RealWorld)]
-> ((Int, Int, Gen RealWorld) -> IO ()) -> IO ()
forall (f :: * -> *) a b. Foldable f => f a -> (a -> IO b) -> IO ()
forConcurrently_([Int] -> [Int] -> [Gen RealWorld] -> [(Int, Int, Gen RealWorld)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3[Int]
ixs ([Int] -> [Int]
forall a. HasCallStack => [a] -> [a]
tail[Int]
ixs )[Gen RealWorld]
gens )(((Int, Int, Gen RealWorld) -> IO ()) -> IO ())
-> ((Int, Int, Gen RealWorld) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\(Int
start ,!Int
end ,Gen RealWorld
gen' )->do-- on GHCJS it doesn't make sense to do any forking.-- JavaScript runtime has only single capability.letloop :: Int
-> [(Vector Double -> Double, MVector RealWorld Double)] -> IO ()
loop Int
k [(Vector Double -> Double, MVector RealWorld Double)]
ers |Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
end =() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return()|Bool
otherwise=doVector Double
re <-GenIO -> Vector Double -> IO (Vector Double)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Gen (PrimState m) -> v a -> m (v a)
resampleVector Gen RealWorld
GenIO
gen' Vector Double
samples [(Vector Double -> Double, MVector RealWorld Double)]
-> ((Vector Double -> Double, MVector RealWorld Double) -> IO ())
-> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_[(Vector Double -> Double, MVector RealWorld Double)]
ers (((Vector Double -> Double, MVector RealWorld Double) -> IO ())
 -> IO ())
-> ((Vector Double -> Double, MVector RealWorld Double) -> IO ())
-> IO ()
forall a b. (a -> b) -> a -> b
$\(Vector Double -> Double
est ,MVector RealWorld Double
arr )->MVector (PrimState IO) Double -> Int -> Double -> IO ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
MU.writeMVector RealWorld Double
MVector (PrimState IO) Double
arr Int
k (Double -> IO ())
-> (Vector Double -> Double) -> Vector Double -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Vector Double -> Double
est (Vector Double -> IO ()) -> Vector Double -> IO ()
forall a b. (a -> b) -> a -> b
$Vector Double
re Int
-> [(Vector Double -> Double, MVector RealWorld Double)] -> IO ()
loop (Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)[(Vector Double -> Double, MVector RealWorld Double)]
ers Int
-> [(Vector Double -> Double, MVector RealWorld Double)] -> IO ()
loop Int
start ([Vector Double -> Double]
-> [MVector RealWorld Double]
-> [(Vector Double -> Double, MVector RealWorld Double)]
forall a b. [a] -> [b] -> [(a, b)]
zip[Vector Double -> Double]
ests' [MVector RealWorld Double]
results )(MVector RealWorld Double -> IO ())
-> [MVector RealWorld Double] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_MVector RealWorld Double -> IO ()
MVector (PrimState IO) Double -> IO ()
forall (m :: * -> *) (v :: * -> * -> *) e.
(PrimMonad m, MVector v e, Ord e) =>
v (PrimState m) e -> m ()
sort[MVector RealWorld Double]
results -- Build resamples[Vector Double]
res <-(MVector RealWorld Double -> IO (Vector Double))
-> [MVector RealWorld Double] -> IO [Vector Double]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapMMVector RealWorld Double -> IO (Vector Double)
Mutable Vector (PrimState IO) Double -> IO (Vector Double)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Mutable v (PrimState m) a -> m (v a)
unsafeFreeze[MVector RealWorld Double]
results [(Estimator, Bootstrap Vector Double)]
-> IO [(Estimator, Bootstrap Vector Double)]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return([(Estimator, Bootstrap Vector Double)]
 -> IO [(Estimator, Bootstrap Vector Double)])
-> [(Estimator, Bootstrap Vector Double)]
-> IO [(Estimator, Bootstrap Vector Double)]
forall a b. (a -> b) -> a -> b
$[Estimator]
-> [Bootstrap Vector Double]
-> [(Estimator, Bootstrap Vector Double)]
forall a b. [a] -> [b] -> [(a, b)]
zip[Estimator]
ests ([Bootstrap Vector Double]
 -> [(Estimator, Bootstrap Vector Double)])
-> [Bootstrap Vector Double]
-> [(Estimator, Bootstrap Vector Double)]
forall a b. (a -> b) -> a -> b
$(Double -> Vector Double -> Bootstrap Vector Double)
-> [Double] -> [Vector Double] -> [Bootstrap Vector Double]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWithDouble -> Vector Double -> Bootstrap Vector Double
forall (v :: * -> *) a. a -> v a -> Bootstrap v a
Bootstrap [Estimator -> Vector Double -> Double
estimate Estimator
e Vector Double
samples |Estimator
e <-[Estimator]
ests ][Vector Double]
res whereests' :: [Vector Double -> Double]
ests' =(Estimator -> Vector Double -> Double)
-> [Estimator] -> [Vector Double -> Double]
forall a b. (a -> b) -> [a] -> [b]
mapEstimator -> Vector Double -> Double
estimate [Estimator]
ests -- | Create vector using resamplesresampleVector ::(PrimMonadm ,G.Vectorv a )=>Gen(PrimStatem )->v a ->m (v a )resampleVector :: forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Gen (PrimState m) -> v a -> m (v a)
resampleVector Gen (PrimState m)
gen v a
v =Int -> m a -> m (v a)
forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v a) =>
Int -> m a -> m (v a)
G.replicateMInt
n (m a -> m (v a)) -> m a -> m (v a)
forall a b. (a -> b) -> a -> b
$doInt
i <-(Int, Int) -> Gen (PrimState m) -> m Int
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
forall (m :: * -> *).
PrimMonad m =>
(Int, Int) -> Gen (PrimState m) -> m Int
uniformR(Int
0,Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)Gen (PrimState m)
gen a -> m a
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return(a -> m a) -> a -> m a
forall a b. (a -> b) -> a -> b
$!v a -> Int -> a
forall (v :: * -> *) a. Vector v a => v a -> Int -> a
G.unsafeIndexv a
v Int
i wheren :: Int
n =v a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.lengthv a
v ------------------------------------------------------------------ Jackknife------------------------------------------------------------------ | /O(n) or O(n^2)/ Compute a statistical estimate repeatedly over a-- sample, each time omitting a successive element.jackknife ::Estimator ->Sample ->U.VectorDoublejackknife :: Estimator -> Vector Double -> Vector Double
jackknife Estimator
Mean Vector Double
sample =Vector Double -> Vector Double
jackknifeMean Vector Double
sample jackknife Estimator
Variance Vector Double
sample =Vector Double -> Vector Double
jackknifeVariance Vector Double
sample jackknife Estimator
VarianceUnbiased Vector Double
sample =Vector Double -> Vector Double
jackknifeVarianceUnb Vector Double
sample jackknife Estimator
StdDev Vector Double
sample =Vector Double -> Vector Double
jackknifeStdDev Vector Double
sample jackknife (Function Vector Double -> Double
est )Vector Double
sample |Vector Double -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.lengthVector Double
sample Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
1=String -> Vector Double
forall a. String -> a
singletonErr String
"jackknife"|Bool
otherwise=(Int -> Double) -> Vector Int -> Vector Double
forall a b. (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b
U.mapInt -> Double
f (Vector Int -> Vector Double)
-> (Vector Double -> Vector Int) -> Vector Double -> Vector Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Vector Double -> Vector Int
forall (v :: * -> *) a. (Vector v a, Vector v Int) => v a -> v Int
indices (Vector Double -> Vector Double) -> Vector Double -> Vector Double
forall a b. (a -> b) -> a -> b
$Vector Double
sample wheref :: Int -> Double
f Int
i =Vector Double -> Double
est (Int -> Vector Double -> Vector Double
forall e. Unbox e => Int -> Vector e -> Vector e
dropAt Int
i Vector Double
sample )-- | /O(n)/ Compute the jackknife mean of a sample.jackknifeMean ::Sample ->U.VectorDoublejackknifeMean :: Vector Double -> Vector Double
jackknifeMean Vector Double
samp |Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
1=String -> Vector Double
forall a. String -> a
singletonErr String
"jackknifeMean"|Bool
otherwise=(Double -> Double) -> Vector Double -> Vector Double
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
G.map(Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
l )(Vector Double -> Vector Double) -> Vector Double -> Vector Double
forall a b. (a -> b) -> a -> b
$(Double -> Double -> Double)
-> Vector Double -> Vector Double -> Vector Double
forall (v :: * -> *) a b c.
(Vector v a, Vector v b, Vector v c) =>
(a -> b -> c) -> v a -> v b -> v c
G.zipWithDouble -> Double -> Double
forall a. Num a => a -> a -> a
(+)(Vector Double -> Vector Double
pfxSumL Vector Double
samp )(Vector Double -> Vector Double
pfxSumR Vector Double
samp )wherel :: Double
l =Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)len :: Int
len =Vector Double -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.lengthVector Double
samp -- | /O(n)/ Compute the jackknife variance of a sample with a-- correction factor @c@, so we can get either the regular or-- \"unbiased\" variance.jackknifeVariance_ ::Double->Sample ->U.VectorDoublejackknifeVariance_ :: Double -> Vector Double -> Vector Double
jackknifeVariance_ Double
c Vector Double
samp |Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
1=String -> Vector Double
forall a. String -> a
singletonErr String
"jackknifeVariance"|Bool
otherwise=(Double -> Double -> Double -> Double -> Double)
-> Vector Double
-> Vector Double
-> Vector Double
-> Vector Double
-> Vector Double
forall (v :: * -> *) a b c d e.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e) =>
(a -> b -> c -> d -> e) -> v a -> v b -> v c -> v d -> v e
G.zipWith4Double -> Double -> Double -> Double -> Double
go Vector Double
als Vector Double
ars Vector Double
bls Vector Double
brs whereals :: Vector Double
als =Vector Double -> Vector Double
pfxSumL (Vector Double -> Vector Double)
-> (Vector Double -> Vector Double)
-> Vector Double
-> Vector Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Double -> Double) -> Vector Double -> Vector Double
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
G.mapDouble -> Double
goa (Vector Double -> Vector Double) -> Vector Double -> Vector Double
forall a b. (a -> b) -> a -> b
$Vector Double
samp ars :: Vector Double
ars =Vector Double -> Vector Double
pfxSumR (Vector Double -> Vector Double)
-> (Vector Double -> Vector Double)
-> Vector Double
-> Vector Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Double -> Double) -> Vector Double -> Vector Double
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
G.mapDouble -> Double
goa (Vector Double -> Vector Double) -> Vector Double -> Vector Double
forall a b. (a -> b) -> a -> b
$Vector Double
samp goa :: Double -> Double
goa Double
x =Double
v Double -> Double -> Double
forall a. Num a => a -> a -> a
*Double
v wherev :: Double
v =Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
-Double
m bls :: Vector Double
bls =Vector Double -> Vector Double
pfxSumL (Vector Double -> Vector Double)
-> (Vector Double -> Vector Double)
-> Vector Double
-> Vector Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Double -> Double) -> Vector Double -> Vector Double
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
G.map(Double -> Double -> Double
forall a. Num a => a -> a -> a
subtractDouble
m )(Vector Double -> Vector Double) -> Vector Double -> Vector Double
forall a b. (a -> b) -> a -> b
$Vector Double
samp brs :: Vector Double
brs =Vector Double -> Vector Double
pfxSumR (Vector Double -> Vector Double)
-> (Vector Double -> Vector Double)
-> Vector Double
-> Vector Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Double -> Double) -> Vector Double -> Vector Double
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
G.map(Double -> Double -> Double
forall a. Num a => a -> a -> a
subtractDouble
m )(Vector Double -> Vector Double) -> Vector Double -> Vector Double
forall a b. (a -> b) -> a -> b
$Vector Double
samp m :: Double
m =Vector Double -> Double
forall (v :: * -> *). Vector v Double => v Double -> Double
mean Vector Double
samp n :: Double
n =Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegralInt
len go :: Double -> Double -> Double -> Double -> Double
go Double
al Double
ar Double
bl Double
br =(Double
al Double -> Double -> Double
forall a. Num a => a -> a -> a
+Double
ar Double -> Double -> Double
forall a. Num a => a -> a -> a
-(Double
b Double -> Double -> Double
forall a. Num a => a -> a -> a
*Double
b )Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
q )Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/(Double
q Double -> Double -> Double
forall a. Num a => a -> a -> a
-Double
c )whereb :: Double
b =Double
bl Double -> Double -> Double
forall a. Num a => a -> a -> a
+Double
br q :: Double
q =Double
n Double -> Double -> Double
forall a. Num a => a -> a -> a
-Double
1len :: Int
len =Vector Double -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.lengthVector Double
samp -- | /O(n)/ Compute the unbiased jackknife variance of a sample.jackknifeVarianceUnb ::Sample ->U.VectorDoublejackknifeVarianceUnb :: Vector Double -> Vector Double
jackknifeVarianceUnb Vector Double
samp |Vector Double -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.lengthVector Double
samp Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
2=String -> Vector Double
forall a. String -> a
singletonErr String
"jackknifeVariance"|Bool
otherwise=Double -> Vector Double -> Vector Double
jackknifeVariance_ Double
1Vector Double
samp -- | /O(n)/ Compute the jackknife variance of a sample.jackknifeVariance ::Sample ->U.VectorDoublejackknifeVariance :: Vector Double -> Vector Double
jackknifeVariance =Double -> Vector Double -> Vector Double
jackknifeVariance_ Double
0-- | /O(n)/ Compute the jackknife standard deviation of a sample.jackknifeStdDev ::Sample ->U.VectorDoublejackknifeStdDev :: Vector Double -> Vector Double
jackknifeStdDev =(Double -> Double) -> Vector Double -> Vector Double
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
G.mapDouble -> Double
forall a. Floating a => a -> a
sqrt(Vector Double -> Vector Double)
-> (Vector Double -> Vector Double)
-> Vector Double
-> Vector Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Vector Double -> Vector Double
jackknifeVarianceUnb pfxSumL ::U.VectorDouble->U.VectorDoublepfxSumL :: Vector Double -> Vector Double
pfxSumL =(KBNSum -> Double) -> Vector KBNSum -> Vector Double
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
G.mapKBNSum -> Double
kbn(Vector KBNSum -> Vector Double)
-> (Vector Double -> Vector KBNSum)
-> Vector Double
-> Vector Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(KBNSum -> Double -> KBNSum)
-> KBNSum -> Vector Double -> Vector KBNSum
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> a) -> a -> v b -> v a
G.scanlKBNSum -> Double -> KBNSum
forall s. Summation s => s -> Double -> s
addKBNSum
forall s. Summation s => s
zeropfxSumR ::U.VectorDouble->U.VectorDoublepfxSumR :: Vector Double -> Vector Double
pfxSumR =Vector Double -> Vector Double
forall (v :: * -> *) a. Vector v a => v a -> v a
G.tail(Vector Double -> Vector Double)
-> (Vector Double -> Vector Double)
-> Vector Double
-> Vector Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(KBNSum -> Double) -> Vector KBNSum -> Vector Double
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
G.mapKBNSum -> Double
kbn(Vector KBNSum -> Vector Double)
-> (Vector Double -> Vector KBNSum)
-> Vector Double
-> Vector Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Double -> KBNSum -> KBNSum)
-> KBNSum -> Vector Double -> Vector KBNSum
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> b) -> b -> v a -> v b
G.scanr((KBNSum -> Double -> KBNSum) -> Double -> KBNSum -> KBNSum
forall a b c. (a -> b -> c) -> b -> a -> c
flipKBNSum -> Double -> KBNSum
forall s. Summation s => s -> Double -> s
add)KBNSum
forall s. Summation s => s
zero-- | Drop the /k/th element of a vector.dropAt ::U.Unboxe =>Int->U.Vectore ->U.Vectore dropAt :: forall e. Unbox e => Int -> Vector e -> Vector e
dropAt Int
n Vector e
v =Int -> Int -> Vector e -> Vector e
forall a. Unbox a => Int -> Int -> Vector a -> Vector a
U.sliceInt
0Int
n Vector e
v Vector e -> Vector e -> Vector e
forall a. Unbox a => Vector a -> Vector a -> Vector a
U.++Int -> Int -> Vector e -> Vector e
forall a. Unbox a => Int -> Int -> Vector a -> Vector a
U.slice(Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)(Vector e -> Int
forall a. Unbox a => Vector a -> Int
U.lengthVector e
v Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)Vector e
v singletonErr ::String->a singletonErr :: forall a. String -> a
singletonErr String
func =String -> a
forall a. HasCallStack => String -> a
error(String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$String
"Statistics.Resampling."String -> ShowS
forall a. [a] -> [a] -> [a]
++String
func String -> ShowS
forall a. [a] -> [a] -> [a]
++String
": not enough elements in sample"-- | Split a generator into several that can run independently.splitGen ::Int->GenIO->IO[GenIO]splitGen :: Int -> GenIO -> IO [GenIO]
splitGen Int
n GenIO
gen |Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
0=[Gen RealWorld] -> IO [Gen RealWorld]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return[]|Bool
otherwise=([Gen RealWorld] -> [Gen RealWorld])
-> IO [Gen RealWorld] -> IO [Gen RealWorld]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap(Gen RealWorld
GenIO
gen Gen RealWorld -> [Gen RealWorld] -> [Gen RealWorld]
forall a. a -> [a] -> [a]
:)(IO [Gen RealWorld] -> IO [GenIO])
-> (IO (Gen RealWorld) -> IO [Gen RealWorld])
-> IO (Gen RealWorld)
-> IO [GenIO]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Int -> IO (Gen RealWorld) -> IO [Gen RealWorld]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM(Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)(IO (Gen RealWorld) -> IO [GenIO])
-> IO (Gen RealWorld) -> IO [GenIO]
forall a b. (a -> b) -> a -> b
$Vector Word32 -> IO (Gen RealWorld)
Vector Word32 -> IO GenIO
forall (m :: * -> *) (v :: * -> *).
(PrimMonad m, Vector v Word32) =>
v Word32 -> m (Gen (PrimState m))
initialize(Vector Word32 -> IO (Gen RealWorld))
-> IO (Vector Word32) -> IO (Gen RealWorld)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<(Gen RealWorld -> Int -> IO (Vector Word32)
forall (m :: * -> *) g a (v :: * -> *).
(PrimMonad m, StatefulGen g m, Uniform a, Vector v a) =>
g -> Int -> m (v a)
uniformVectorGen RealWorld
GenIO
gen Int
256::IO(U.VectorWord32))

AltStyle によって変換されたページ (->オリジナル) /