{-# LANGUAGE ViewPatterns #-}
module Statistics.ConfidenceInt (
poissonCI
, poissonNormalCI
, binomialCI
, naiveBinomialCI
) where
import Statistics.Distribution
import Statistics.Distribution.ChiSquared
import Statistics.Distribution.Beta
import Statistics.Types
poissonNormalCI :: Int -> Estimate NormalErr Double
poissonNormalCI n
| n < 0 = error "Statistics.ConfidenceInt.poissonNormalCI negative number of trials"
| otherwise = estimateNormErr n' (sqrt n')
where
n' = fromIntegral n
poissonCI :: CL Double -> Int -> Estimate ConfInt Double
poissonCI cl@(significanceLevel -> p) n
| n < 0 = error "Statistics.ConfidenceInt.poissonCI: negative number of trials"
| n == 0 = estimateFromInterval m (m1,m2) cl
| otherwise = estimateFromInterval m (m1,m2) cl
where
m = fromIntegral n
m1 = 0.5 * quantile (chiSquared (2*n )) (p/2)
m2 = 0.5 * complQuantile (chiSquared (2*n+2)) (p/2)
naiveBinomialCI :: Int
-> Int
-> Estimate NormalErr Double
naiveBinomialCI n k
| n <= 0 || k < 0 = error "Statistics.ConfidenceInt.naiveBinomialCI: negative number of events"
| k > n = error "Statistics.ConfidenceInt.naiveBinomialCI: more successes than trials"
| otherwise = estimateNormErr p σ
where
p = fromIntegral k / fromIntegral n
σ = sqrt $ p * (1 - p) / fromIntegral n
binomialCI :: CL Double
-> Int
-> Int
-> Estimate ConfInt Double
binomialCI cl@(significanceLevel -> p) ni ki
| ni <= 0 || ki < 0 = error "Statistics.ConfidenceInt.binomialCI: negative number of events"
| ki > ni = error "Statistics.ConfidenceInt.binomialCI: more successes than trials"
| ki == 0 = estimateFromInterval eff (0, ub) cl
| ni == ki = estimateFromInterval eff (lb,0 ) cl
| otherwise = estimateFromInterval eff (lb,ub) cl
where
k = fromIntegral ki
n = fromIntegral ni
eff = k / n
lb = quantile (betaDistr k (n - k + 1)) (p/2)
ub = complQuantile (betaDistr (k + 1) (n - k) ) (p/2)