{-# LANGUAGE FlexibleContexts #-}
-- | Pearson's chi squared test.
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



-- | Generic form of Pearson chi squared tests for binned data. Data
--   sample is supplied in form of tuples (observed quantity,
--   expected number of events). Both must be positive.
--
--   This test should be used only if all bins have expected values of
--   at least 5.
chi2test :: (G.Vector v (Int,Double), G.Vector v Double)
         => Int                 -- ^ Number of additional degrees of
                                --   freedom. One degree of freedom
                                --   is due to the fact that the are
                                --   N observation in total and
                                --   accounted for automatically.
         -> v (Int,Double)      -- ^ Observation and expectation.
         -> Maybe (Test ChiSquared)
chi2test :: forall (v :: * -> *).
(Vector v (Int, Double), Vector v Double) =>
Int -> v (Int, Double) -> Maybe (Test ChiSquared)
chi2test Int
ndf v (Int, Double)
vec
  | Int
ndf forall a. Ord a => a -> a -> Bool
<  Int
0  = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Statistics.Test.ChiSquare.chi2test: negative NDF " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Int
ndf
  | Int
n   forall a. Ord a => a -> a -> Bool
> Int
0   = forall a. a -> Maybe a
Just Test
              { testSignificance :: PValue Double
testSignificance = forall a. (Ord a, Num a) => a -> PValue a
mkPValue forall a b. (a -> b) -> a -> b
$ 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 = forall a. Maybe a
Nothing
  where
    n :: Int
n     = forall (v :: * -> *) a. Vector v a => v a -> Int
G.length v (Int, Double)
vec forall a. Num a => a -> a -> a
- Int
ndf forall a. Num a => a -> a -> a
- Int
1
    chi2 :: Double
chi2  = forall (v :: * -> *). Vector v Double => v Double -> Double
sum forall a b. (a -> b) -> a -> b
$ 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 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
o forall a. Num a => a -> a -> a
- Double
e) 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) #-}


-- | Chi squared test for data with normal errors. Data is supplied in
--   form of pair (observation with error, and expectation).
chi2testCont
  :: (G.Vector v (Estimate NormalErr Double, Double), G.Vector v Double)
  => Int                                   -- ^ Number of additional
                                           --   degrees of freedom.
  -> v (Estimate NormalErr Double, Double) -- ^ Observation and expectation.
  -> Maybe (Test ChiSquared)
chi2testCont :: forall (v :: * -> *).
(Vector v (Estimate NormalErr Double, Double), Vector v Double) =>
Int
-> v (Estimate NormalErr Double, Double) -> Maybe (Test ChiSquared)
chi2testCont Int
ndf v (Estimate NormalErr Double, Double)
vec
  | Int
ndf forall a. Ord a => a -> a -> Bool
< Int
0   = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Statistics.Test.ChiSquare.chi2testCont: negative NDF " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Int
ndf
  | Int
n   forall a. Ord a => a -> a -> Bool
> Int
0   = forall a. a -> Maybe a
Just Test
              { testSignificance :: PValue Double
testSignificance = forall a. (Ord a, Num a) => a -> PValue a
mkPValue forall a b. (a -> b) -> a -> b
$ 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 = forall a. Maybe a
Nothing
  where
    n :: Int
n     = forall (v :: * -> *) a. Vector v a => v a -> Int
G.length v (Estimate NormalErr Double, Double)
vec forall a. Num a => a -> a -> a
- Int
ndf forall a. Num a => a -> a -> a
- Int
1
    chi2 :: Double
chi2  = forall (v :: * -> *). Vector v Double => v Double -> Double
sum forall a b. (a -> b) -> a -> b
$ 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 forall a. Num a => a -> a -> a
- Double
e) forall a. Fractional a => a -> a -> a
/ Double
s) v (Estimate NormalErr Double, Double)
vec
    d :: ChiSquared
d     = Int -> ChiSquared
chiSquared Int
n