{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE BangPatterns #-}
module Statistics.Correlation
(
pearson
, pearsonMatByRow
, spearman
, spearmanMatByRow
) where
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Unboxed as U
import Statistics.Matrix
import Statistics.Sample
import Statistics.Test.Internal (rankUnsorted)
pearson :: (G.Vector v (Double, Double), G.Vector v Double)
=> v (Double, Double) -> Double
pearson :: forall (v :: * -> *).
(Vector v (Double, Double), Vector v Double) =>
v (Double, Double) -> Double
pearson = forall (v :: * -> *).
(Vector v (Double, Double), Vector v Double) =>
v (Double, Double) -> Double
correlation
{-# INLINE pearson #-}
pearsonMatByRow :: Matrix -> Matrix
pearsonMatByRow :: Matrix -> Matrix
pearsonMatByRow Matrix
m
= Int -> (Int -> Int -> Double) -> Matrix
generateSym (Matrix -> Int
rows Matrix
m)
(\Int
i Int
j -> forall (v :: * -> *).
(Vector v (Double, Double), Vector v Double) =>
v (Double, Double) -> Double
pearson forall a b. (a -> b) -> a -> b
$ Matrix -> Int -> Vector
row Matrix
m Int
i forall a b.
(Unbox a, Unbox b) =>
Vector a -> Vector b -> Vector (a, b)
`U.zip` Matrix -> Int -> Vector
row Matrix
m Int
j)
{-# INLINE pearsonMatByRow #-}
spearman :: ( Ord a
, Ord b
, G.Vector v a
, G.Vector v b
, G.Vector v (a, b)
, G.Vector v Int
, G.Vector v Double
, G.Vector v (Double, Double)
, G.Vector v (Int, a)
, G.Vector v (Int, b)
)
=> v (a, b)
-> Double
spearman :: forall a b (v :: * -> *).
(Ord a, Ord b, Vector v a, Vector v b, Vector v (a, b),
Vector v Int, Vector v Double, Vector v (Double, Double),
Vector v (Int, a), Vector v (Int, b)) =>
v (a, b) -> Double
spearman v (a, b)
xy
= forall (v :: * -> *).
(Vector v (Double, Double), Vector v Double) =>
v (Double, Double) -> Double
pearson
forall a b. (a -> b) -> a -> b
$ forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v a -> v b -> v (a, b)
G.zip (forall a (v :: * -> *).
(Ord a, Vector v a, Vector v Int, Vector v Double,
Vector v (Int, a)) =>
v a -> v Double
rankUnsorted v a
x) (forall a (v :: * -> *).
(Ord a, Vector v a, Vector v Int, Vector v Double,
Vector v (Int, a)) =>
v a -> v Double
rankUnsorted v b
y)
where
(v a
x, v b
y) = forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v (a, b) -> (v a, v b)
G.unzip v (a, b)
xy
{-# INLINE spearman #-}
spearmanMatByRow :: Matrix -> Matrix
spearmanMatByRow :: Matrix -> Matrix
spearmanMatByRow
= Matrix -> Matrix
pearsonMatByRow forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Vector] -> Matrix
fromRows forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a (v :: * -> *).
(Ord a, Vector v a, Vector v Int, Vector v Double,
Vector v (Int, a)) =>
v a -> v Double
rankUnsorted forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix -> [Vector]
toRows
{-# INLINE spearmanMatByRow #-}