-- |
-- Module    : Statistics.Test.MannWhitneyU
-- Copyright : (c) 2010 Neil Brown
-- License   : BSD3
--
-- Maintainer  : bos@serpentine.com
-- Stability   : experimental
-- Portability : portable
--
-- Mann-Whitney U test (also know as Mann-Whitney-Wilcoxon and
-- Wilcoxon rank sum test) is a non-parametric test for assessing
-- whether two samples of independent observations have different
-- mean.
module Statistics.Test.MannWhitneyU (
    -- * Mann-Whitney U test
    mannWhitneyUtest
  , mannWhitneyU
  , mannWhitneyUCriticalValue
  , mannWhitneyUSignificant
    -- ** Wilcoxon rank sum test
  , wilcoxonRankSums
  , module Statistics.Test.Types
    -- * References
    -- $references
  ) where

import Data.List (findIndex)
import Data.Ord (comparing)
import Numeric.SpecFunctions (choose)
import Prelude hiding (sum)
import Statistics.Distribution (quantile)
import Statistics.Distribution.Normal (standard)
import Statistics.Function (sortBy)
import Statistics.Sample.Internal (sum)
import Statistics.Test.Internal (rank, splitByTags)
import Statistics.Test.Types (TestResult(..), PositionTest(..), significant)
import Statistics.Types (PValue,pValue)
import qualified Data.Vector.Unboxed as U

-- | The Wilcoxon Rank Sums Test.
--
-- This test calculates the sum of ranks for the given two samples.
-- The samples are ordered, and assigned ranks (ties are given their
-- average rank), then these ranks are summed for each sample.
--
-- The return value is (W₁, W₂) where W₁ is the sum of ranks of the first sample
-- and W₂ is the sum of ranks of the second sample.  This test is trivially transformed
-- into the Mann-Whitney U test.  You will probably want to use 'mannWhitneyU'
-- and the related functions for testing significance, but this function is exposed
-- for completeness.
wilcoxonRankSums :: (Ord a, U.Unbox a) => U.Vector a -> U.Vector a -> (Double, Double)
wilcoxonRankSums :: Vector a -> Vector a -> (Double, Double)
wilcoxonRankSums Vector a
xs1 Vector a
xs2 = (Vector Double -> Double
forall (v :: * -> *). Vector v Double => v Double -> Double
sum Vector Double
ranks1, Vector Double -> Double
forall (v :: * -> *). Vector v Double => v Double -> Double
sum Vector Double
ranks2)
  where
    -- Ranks for each sample
    (Vector Double
ranks1,Vector Double
ranks2) = Vector (Bool, Double) -> (Vector Double, Vector Double)
forall (v :: * -> *) a.
(Vector v a, Vector v (Bool, a)) =>
v (Bool, a) -> (v a, v a)
splitByTags (Vector (Bool, Double) -> (Vector Double, Vector Double))
-> Vector (Bool, Double) -> (Vector Double, Vector Double)
forall a b. (a -> b) -> a -> b
$ Vector Bool -> Vector Double -> Vector (Bool, Double)
forall a b.
(Unbox a, Unbox b) =>
Vector a -> Vector b -> Vector (a, b)
U.zip Vector Bool
tags ((a -> a -> Bool) -> Vector a -> Vector Double
forall (v :: * -> *) a.
(Vector v a, Vector v Double) =>
(a -> a -> Bool) -> v a -> v Double
rank a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==) Vector a
joinSample)
    -- Sorted and tagged sample
    (Vector Bool
tags,Vector a
joinSample) = Vector (Bool, a) -> (Vector Bool, Vector a)
forall a b.
(Unbox a, Unbox b) =>
Vector (a, b) -> (Vector a, Vector b)
U.unzip
                      (Vector (Bool, a) -> (Vector Bool, Vector a))
-> Vector (Bool, a) -> (Vector Bool, Vector a)
forall a b. (a -> b) -> a -> b
$ Comparison (Bool, a) -> Vector (Bool, a) -> Vector (Bool, a)
forall (v :: * -> *) e. Vector v e => Comparison e -> v e -> v e
sortBy (((Bool, a) -> a) -> Comparison (Bool, a)
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (Bool, a) -> a
forall a b. (a, b) -> b
snd)
                      (Vector (Bool, a) -> Vector (Bool, a))
-> Vector (Bool, a) -> Vector (Bool, a)
forall a b. (a -> b) -> a -> b
$ Bool -> Vector a -> Vector (Bool, a)
forall b a. (Unbox b, Unbox a) => a -> Vector b -> Vector (a, b)
tagSample Bool
True Vector a
xs1 Vector (Bool, a) -> Vector (Bool, a) -> Vector (Bool, a)
forall a. Unbox a => Vector a -> Vector a -> Vector a
U.++ Bool -> Vector a -> Vector (Bool, a)
forall b a. (Unbox b, Unbox a) => a -> Vector b -> Vector (a, b)
tagSample Bool
False Vector a
xs2
    -- Add tag to a sample
    tagSample :: a -> Vector b -> Vector (a, b)
tagSample a
t = (b -> (a, b)) -> Vector b -> Vector (a, b)
forall a b. (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b
U.map (\b
x -> (a
t,b
x))



-- | The Mann-Whitney U Test.
--
-- This is sometimes known as the Mann-Whitney-Wilcoxon U test, and
-- confusingly many sources state that the Mann-Whitney U test is the same as
-- the Wilcoxon's rank sum test (which is provided as 'wilcoxonRankSums').
-- The Mann-Whitney U is a simple transform of Wilcoxon's rank sum test.
--
-- Again confusingly, different sources state reversed definitions for U₁
-- and U₂, so it is worth being explicit about what this function returns.
-- Given two samples, the first, xs₁, of size n₁ and the second, xs₂,
-- of size n₂, this function returns (U₁, U₂)
-- where U₁ = W₁ - (n₁(n₁+1))\/2
-- and U₂ = W₂ - (n₂(n₂+1))\/2,
-- where (W₁, W₂) is the return value of @wilcoxonRankSums xs1 xs2@.
--
-- Some sources instead state that U₁ and U₂ should be the other way round, often
-- expressing this using U₁' = n₁n₂ - U₁ (since U₁ + U₂ = n₁n₂).
--
-- All of which you probably don't care about if you just feed this into 'mannWhitneyUSignificant'.
mannWhitneyU :: (Ord a, U.Unbox a) => U.Vector a -> U.Vector a -> (Double, Double)
mannWhitneyU :: Vector a -> Vector a -> (Double, Double)
mannWhitneyU Vector a
xs1 Vector a
xs2
  = ((Double, Double) -> Double
forall a b. (a, b) -> a
fst (Double, Double)
summedRanks Double -> Double -> Double
forall a. Num a => a -> a -> a
- (Double
n1Double -> Double -> Double
forall a. Num a => a -> a -> a
*(Double
n1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
1))Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2
    ,(Double, Double) -> Double
forall a b. (a, b) -> b
snd (Double, Double)
summedRanks Double -> Double -> Double
forall a. Num a => a -> a -> a
- (Double
n2Double -> Double -> Double
forall a. Num a => a -> a -> a
*(Double
n2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
1))Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2)
  where
    n1 :: Double
n1 = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Double) -> Int -> Double
forall a b. (a -> b) -> a -> b
$ Vector a -> Int
forall a. Unbox a => Vector a -> Int
U.length Vector a
xs1
    n2 :: Double
n2 = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Double) -> Int -> Double
forall a b. (a -> b) -> a -> b
$ Vector a -> Int
forall a. Unbox a => Vector a -> Int
U.length Vector a
xs2

    summedRanks :: (Double, Double)
summedRanks = Vector a -> Vector a -> (Double, Double)
forall a.
(Ord a, Unbox a) =>
Vector a -> Vector a -> (Double, Double)
wilcoxonRankSums Vector a
xs1 Vector a
xs2

-- | Calculates the critical value of Mann-Whitney U for the given sample
-- sizes and significance level.
--
-- This function returns the exact calculated value of U for all sample sizes;
-- it does not use the normal approximation at all.  Above sample size 20 it is
-- generally recommended to use the normal approximation instead, but this function
-- will calculate the higher critical values if you need them.
--
-- The algorithm to generate these values is a faster, memoised version of the
-- simple unoptimised generating function given in section 2 of \"The Mann Whitney
-- Wilcoxon Distribution Using Linked Lists\"
mannWhitneyUCriticalValue
  :: (Int, Int)     -- ^ The sample size
  -> PValue Double  -- ^ The p-value (e.g. 0.05) for which you want the critical value.
  -> Maybe Int      -- ^ The critical value (of U).
mannWhitneyUCriticalValue :: (Int, Int) -> PValue Double -> Maybe Int
mannWhitneyUCriticalValue (Int
m, Int
n) PValue Double
p
  | Int
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 Bool -> Bool -> Bool
|| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = Maybe Int
forall a. Maybe a
Nothing    -- Sample must be nonempty
  | Double
p' Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
1        = Maybe Int
forall a. Maybe a
Nothing    -- p-value is too small. Null hypothesis couldn't be disproved
  | Bool
otherwise      = (Double -> Bool) -> [Double] -> Maybe Int
forall a. (a -> Bool) -> [a] -> Maybe Int
findIndex (Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
p')
                   ([Double] -> Maybe Int) -> [Double] -> Maybe Int
forall a b. (a -> b) -> a -> b
$ Int -> [Double] -> [Double]
forall a. Int -> [a] -> [a]
take (Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
n)
                   ([Double] -> [Double]) -> [Double] -> [Double]
forall a b. (a -> b) -> a -> b
$ [Double] -> [Double]
forall a. [a] -> [a]
tail
                   ([Double] -> [Double]) -> [Double] -> [Double]
forall a b. (a -> b) -> a -> b
$ [[[Double]]]
alookup [[[Double]]] -> Int -> [[Double]]
forall a. [a] -> Int -> a
!! (Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2) [[Double]] -> Int -> [Double]
forall a. [a] -> Int -> a
!! (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
m Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
  where
    mnCn :: Double
mnCn = (Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) Int -> Int -> Double
`choose` Int
n
    p' :: Double
p'   = Double
mnCn Double -> Double -> Double
forall a. Num a => a -> a -> a
* PValue Double -> Double
forall a. PValue a -> a
pValue PValue Double
p


{-
-- Original function, without memoisation, from Cheung and Klotz:
-- Double is needed to avoid integer overflows.
a :: Int -> Int -> Int -> Double
a u bigN m
  | u < 0            = 0
  | u >= m * n       = bigN `choose` m
  | m == 1 || n == 1 = fromIntegral (u + 1)
  | otherwise        = a  u      (bigN - 1)  m
                     + a (u - n) (bigN - 1) (m-1)
  where
    n = bigN - m
-}

-- Memoised version of the original a function, above.
--
-- Doubles are stored to avoid integer overflow. 32-bit Ints begin to
-- overflow for bigN as small as 33 (64-bit one at 66) while Double to
-- go to infinity till bigN=1029
--
--
-- outer list is indexed by big N - 2
-- inner list by (m-1) (we know m < bigN)
-- innermost list by u
--
-- So: (alookup !! (bigN - 2) !! (m - 1) ! u) == a u bigN m
alookup :: [[[Double]]]
alookup :: [[[Double]]]
alookup = Int -> [[Double]] -> [[[Double]]]
gen Int
2 [Double
1 Double -> [Double] -> [Double]
forall a. a -> [a] -> [a]
: Double -> [Double]
forall a. a -> [a]
repeat Double
2]
  where
    gen :: Int -> [[Double]] -> [[[Double]]]
gen Int
bigN [[Double]]
predBigNList
       = let bigNlist :: [[Double]]
bigNlist = [ [ Int -> Int -> Double
amemoed Int
u Int
m
                          | Int
u <- [Int
0 .. Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
*(Int
bigNInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
m)]
                          ] [Double] -> [Double] -> [Double]
forall a. [a] -> [a] -> [a]
++ Double -> [Double]
forall a. a -> [a]
repeat (Int
bigN Int -> Int -> Double
`choose` Int
m)
                        | Int
m <- [Int
1 .. (Int
bigNInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)]] -- has bigN-1 elements
         in [[Double]]
bigNlist [[Double]] -> [[[Double]]] -> [[[Double]]]
forall a. a -> [a] -> [a]
: Int -> [[Double]] -> [[[Double]]]
gen (Int
bigNInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) [[Double]]
bigNlist
      where
        amemoed :: Int -> Int -> Double
        amemoed :: Int -> Int -> Double
amemoed Int
u Int
m
          | Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
|| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
u Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
          | Bool
otherwise        = [Double]
mList [Double] -> Int -> Double
forall a. [a] -> Int -> a
!! Int
u
                             Double -> Double -> Double
forall a. Num a => a -> a -> a
+ if Int
u Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n then Double
0 else [Double]
predmList [Double] -> Int -> Double
forall a. [a] -> Int -> a
!! (Int
uInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n)
          where
            n :: Int
n = Int
bigN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
m
            ([Double]
predmList : [Double]
mList : [[Double]]
_) = Int -> [[Double]] -> [[Double]]
forall a. Int -> [a] -> [a]
drop (Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2) [[Double]]
predBigNList
            -- Lists for m-1 and m respectively. i-th list correspond to m=i+1
            --
            -- We know that predBigNList has bigN - 2 elements
            -- (and we know that n > 1 therefore bigN > m + 1)
            -- So bigN - 2 >= m, i.e. predBigNList must have at least m elements
            -- elements, so dropping (m-2) must leave at least 2


-- | Calculates whether the Mann Whitney U test is significant.
--
-- If both sample sizes are less than or equal to 20, the exact U critical value
-- (as calculated by 'mannWhitneyUCriticalValue') is used.  If either sample is
-- larger than 20, the normal approximation is used instead.
--
-- If you use a one-tailed test, the test indicates whether the first sample is
-- significantly larger than the second.  If you want the opposite, simply reverse
-- the order in both the sample size and the (U₁, U₂) pairs.
mannWhitneyUSignificant
  :: PositionTest     -- ^ Perform one-tailed test (see description above).
  -> (Int, Int)       -- ^ The samples' size from which the (U₁,U₂) values were derived.
  -> PValue Double    -- ^ The p-value at which to test (e.g. 0.05)
  -> (Double, Double) -- ^ The (U₁, U₂) values from 'mannWhitneyU'.
  -> Maybe TestResult -- ^ Return 'Nothing' if the sample was too
                      --   small to make a decision.
mannWhitneyUSignificant :: PositionTest
-> (Int, Int)
-> PValue Double
-> (Double, Double)
-> Maybe TestResult
mannWhitneyUSignificant PositionTest
test (Int
in1, Int
in2) PValue Double
pVal (Double
u1, Double
u2)
  -- Use normal approximation
  | Int
in1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
20 Bool -> Bool -> Bool
|| Int
in2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
20 =
    let mean :: Double
mean  = Double
n1 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
n2 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2     -- (u1+u2) / 2
        sigma :: Double
sigma = Double -> Double
forall a. Floating a => a -> a
sqrt (Double -> Double) -> Double -> Double
forall a b. (a -> b) -> a -> b
$ Double
n1Double -> Double -> Double
forall a. Num a => a -> a -> a
*Double
n2Double -> Double -> Double
forall a. Num a => a -> a -> a
*(Double
n1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
n2 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
1) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
12
        z :: Double
z     = (Double
mean Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
u1) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
sigma
    in TestResult -> Maybe TestResult
forall a. a -> Maybe a
Just (TestResult -> Maybe TestResult) -> TestResult -> Maybe TestResult
forall a b. (a -> b) -> a -> b
$ case PositionTest
test of
                PositionTest
AGreater      -> Bool -> TestResult
significant (Bool -> TestResult) -> Bool -> TestResult
forall a b. (a -> b) -> a -> b
$ Double
z     Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< NormalDistribution -> Double -> Double
forall d. ContDistr d => d -> Double -> Double
quantile NormalDistribution
standard Double
p
                PositionTest
BGreater      -> Bool -> TestResult
significant (Bool -> TestResult) -> Bool -> TestResult
forall a b. (a -> b) -> a -> b
$ (-Double
z)  Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< NormalDistribution -> Double -> Double
forall d. ContDistr d => d -> Double -> Double
quantile NormalDistribution
standard Double
p
                PositionTest
SamplesDiffer -> Bool -> TestResult
significant (Bool -> TestResult) -> Bool -> TestResult
forall a b. (a -> b) -> a -> b
$ Double -> Double
forall a. Num a => a -> a
abs Double
z Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double -> Double
forall a. Num a => a -> a
abs (NormalDistribution -> Double -> Double
forall d. ContDistr d => d -> Double -> Double
quantile NormalDistribution
standard (Double
pDouble -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2))
  -- Use exact critical value
  | Bool
otherwise = do Double
crit <- Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Double) -> Maybe Int -> Maybe Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int, Int) -> PValue Double -> Maybe Int
mannWhitneyUCriticalValue (Int
in1, Int
in2) PValue Double
pVal
                   TestResult -> Maybe TestResult
forall (m :: * -> *) a. Monad m => a -> m a
return (TestResult -> Maybe TestResult) -> TestResult -> Maybe TestResult
forall a b. (a -> b) -> a -> b
$ case PositionTest
test of
                              PositionTest
AGreater      -> Bool -> TestResult
significant (Bool -> TestResult) -> Bool -> TestResult
forall a b. (a -> b) -> a -> b
$ Double
u2        Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
crit
                              PositionTest
BGreater      -> Bool -> TestResult
significant (Bool -> TestResult) -> Bool -> TestResult
forall a b. (a -> b) -> a -> b
$ Double
u1        Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
crit
                              PositionTest
SamplesDiffer -> Bool -> TestResult
significant (Bool -> TestResult) -> Bool -> TestResult
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Double
forall a. Ord a => a -> a -> a
min Double
u1 Double
u2 Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
crit
  where
    n1 :: Double
n1 = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
in1
    n2 :: Double
n2 = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
in2
    p :: Double
p  = PValue Double -> Double
forall a. PValue a -> a
pValue PValue Double
pVal


-- | Perform Mann-Whitney U Test for two samples and required
-- significance. For additional information check documentation of
-- 'mannWhitneyU' and 'mannWhitneyUSignificant'. This is just a helper
-- function.
--
-- One-tailed test checks whether first sample is significantly larger
-- than second. Two-tailed whether they are significantly different.
mannWhitneyUtest
  :: (Ord a, U.Unbox a)
  => PositionTest     -- ^ Perform one-tailed test (see description above).
  -> PValue Double    -- ^ The p-value at which to test (e.g. 0.05)
  -> U.Vector a       -- ^ First sample
  -> U.Vector a       -- ^ Second sample
  -> Maybe TestResult -- ^ Return 'Nothing' if the sample was too small to
                      --   make a decision.
mannWhitneyUtest :: PositionTest
-> PValue Double -> Vector a -> Vector a -> Maybe TestResult
mannWhitneyUtest PositionTest
ontTail PValue Double
p Vector a
smp1 Vector a
smp2 =
  PositionTest
-> (Int, Int)
-> PValue Double
-> (Double, Double)
-> Maybe TestResult
mannWhitneyUSignificant PositionTest
ontTail (Int
n1,Int
n2) PValue Double
p ((Double, Double) -> Maybe TestResult)
-> (Double, Double) -> Maybe TestResult
forall a b. (a -> b) -> a -> b
$ Vector a -> Vector a -> (Double, Double)
forall a.
(Ord a, Unbox a) =>
Vector a -> Vector a -> (Double, Double)
mannWhitneyU Vector a
smp1 Vector a
smp2
    where
      n1 :: Int
n1 = Vector a -> Int
forall a. Unbox a => Vector a -> Int
U.length Vector a
smp1
      n2 :: Int
n2 = Vector a -> Int
forall a. Unbox a => Vector a -> Int
U.length Vector a
smp2

-- $references
--
-- * Cheung, Y.K.; Klotz, J.H. (1997) The Mann Whitney Wilcoxon
--   distribution using linked lists. /Statistica Sinica/
--   7:805&#8211;813.
-- <http://www3.stat.sinica.edu.tw/statistica/oldpdf/A7n316.pdf>.