{-# LANGUAGE FlexibleContexts #-}
module Statistics.Test.ChiSquared (
chi2test
, chi2testCont
, module Statistics.Test.Types
) where
import Prelude hiding (sum)
import Statistics.Distribution
import Statistics.Distribution.ChiSquared
import Statistics.Function (square)
import Statistics.Sample.Internal (sum)
import Statistics.Test.Types
import Statistics.Types
import qualified Data.Vector as V
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Unboxed as U
chi2test :: (G.Vector v (Int,Double), G.Vector v Double)
=> Int
-> v (Int,Double)
-> Maybe (Test ChiSquared)
chi2test :: Int -> v (Int, Double) -> Maybe (Test ChiSquared)
chi2test Int
ndf v (Int, Double)
vec
| Int
ndf Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = [Char] -> Maybe (Test ChiSquared)
forall a. HasCallStack => [Char] -> a
error ([Char] -> Maybe (Test ChiSquared))
-> [Char] -> Maybe (Test ChiSquared)
forall a b. (a -> b) -> a -> b
$ [Char]
"Statistics.Test.ChiSquare.chi2test: negative NDF " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
ndf
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = Test ChiSquared -> Maybe (Test ChiSquared)
forall a. a -> Maybe a
Just Test :: forall distr. PValue Double -> Double -> distr -> Test distr
Test
{ testSignificance :: PValue Double
testSignificance = Double -> PValue Double
forall a. (Ord a, Num a) => a -> PValue a
mkPValue (Double -> PValue Double) -> Double -> PValue Double
forall a b. (a -> b) -> a -> b
$ ChiSquared -> Double -> Double
forall d. Distribution d => d -> Double -> Double
complCumulative ChiSquared
d Double
chi2
, testStatistics :: Double
testStatistics = Double
chi2
, testDistribution :: ChiSquared
testDistribution = Int -> ChiSquared
chiSquared Int
n
}
| Bool
otherwise = Maybe (Test ChiSquared)
forall a. Maybe a
Nothing
where
n :: Int
n = v (Int, Double) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.length v (Int, Double)
vec Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
ndf Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
chi2 :: Double
chi2 = v Double -> Double
forall (v :: * -> *). Vector v Double => v Double -> Double
sum (v Double -> Double) -> v Double -> Double
forall a b. (a -> b) -> a -> b
$ ((Int, Double) -> Double) -> v (Int, Double) -> v Double
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
G.map (\(Int
o,Double
e) -> Double -> Double
square (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
o Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
e) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
e) v (Int, Double)
vec
d :: ChiSquared
d = Int -> ChiSquared
chiSquared Int
n
{-# INLINABLE chi2test #-}
{-# SPECIALIZE
chi2test :: Int -> U.Vector (Int,Double) -> Maybe (Test ChiSquared) #-}
{-# SPECIALIZE
chi2test :: Int -> V.Vector (Int,Double) -> Maybe (Test ChiSquared) #-}
chi2testCont
:: (G.Vector v (Estimate NormalErr Double, Double), G.Vector v Double)
=> Int
-> v (Estimate NormalErr Double, Double)
-> Maybe (Test ChiSquared)
chi2testCont :: Int
-> v (Estimate NormalErr Double, Double) -> Maybe (Test ChiSquared)
chi2testCont Int
ndf v (Estimate NormalErr Double, Double)
vec
| Int
ndf Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = [Char] -> Maybe (Test ChiSquared)
forall a. HasCallStack => [Char] -> a
error ([Char] -> Maybe (Test ChiSquared))
-> [Char] -> Maybe (Test ChiSquared)
forall a b. (a -> b) -> a -> b
$ [Char]
"Statistics.Test.ChiSquare.chi2testCont: negative NDF " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
ndf
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = Test ChiSquared -> Maybe (Test ChiSquared)
forall a. a -> Maybe a
Just Test :: forall distr. PValue Double -> Double -> distr -> Test distr
Test
{ testSignificance :: PValue Double
testSignificance = Double -> PValue Double
forall a. (Ord a, Num a) => a -> PValue a
mkPValue (Double -> PValue Double) -> Double -> PValue Double
forall a b. (a -> b) -> a -> b
$ ChiSquared -> Double -> Double
forall d. Distribution d => d -> Double -> Double
complCumulative ChiSquared
d Double
chi2
, testStatistics :: Double
testStatistics = Double
chi2
, testDistribution :: ChiSquared
testDistribution = Int -> ChiSquared
chiSquared Int
n
}
| Bool
otherwise = Maybe (Test ChiSquared)
forall a. Maybe a
Nothing
where
n :: Int
n = v (Estimate NormalErr Double, Double) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.length v (Estimate NormalErr Double, Double)
vec Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
ndf Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
chi2 :: Double
chi2 = v Double -> Double
forall (v :: * -> *). Vector v Double => v Double -> Double
sum (v Double -> Double) -> v Double -> Double
forall a b. (a -> b) -> a -> b
$ ((Estimate NormalErr Double, Double) -> Double)
-> v (Estimate NormalErr Double, Double) -> v Double
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
G.map (\(Estimate Double
o (NormalErr Double
s),Double
e) -> Double -> Double
square (Double
o Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
e) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
s) v (Estimate NormalErr Double, Double)
vec
d :: ChiSquared
d = Int -> ChiSquared
chiSquared Int
n