module Statistics.Resampling.Bootstrap
( bootstrapBCA
) where
import Data.Vector.Generic ((!))
import qualified Data.Vector.Unboxed as U
import Statistics.Distribution (cumulative, quantile)
import Statistics.Distribution.Normal
import Statistics.Resampling (Bootstrap(..), jackknife)
import Statistics.Sample (mean)
import Statistics.Types (Sample, CL, Estimate, ConfInt, estimateFromInterval,
estimateFromErr, CL, significanceLevel)
import qualified Statistics.Resampling as R
data T = {-# UNPACK #-} !Double :< {-# UNPACK #-} !Double
infixl 2 :<
bootstrapBCA
:: CL Double
-> Sample
-> [(R.Estimator, Bootstrap U.Vector Double)]
-> [Estimate ConfInt Double]
bootstrapBCA confidenceLevel sample resampledData
= map e resampledData
where
e (est, Bootstrap pt resample)
| U.length sample == 1 || isInfinite bias =
estimateFromErr pt (0,0) confidenceLevel
| otherwise =
estimateFromInterval pt (resample ! lo, resample ! hi) confidenceLevel
where
lo = max (cumn a1) 0
where a1 = bias + b1 / (1 - accel * b1)
b1 = bias + z1
hi = min (cumn a2) (ni - 1)
where a2 = bias + b2 / (1 - accel * b2)
b2 = bias - z1
ni = U.length resample
n = fromIntegral ni
z1 = quantile standard (significanceLevel confidenceLevel / 2)
cumn = round . (*n) . cumulative standard
bias = quantile standard (probN / n)
where probN = fromIntegral . U.length . U.filter (<pt) $ resample
accel = sumCubes / (6 * (sumSquares ** 1.5))
where (sumSquares :< sumCubes) = U.foldl' f (0 :< 0) jack
f (s :< c) j = s + d2 :< c + d2 * d
where d = jackMean - j
d2 = d * d
jackMean = mean jack
jack = jackknife est sample