| Copyright | (c) A. V. H. McPhail 2010 2012 2014 | 
|---|---|
| License | BSD3 | 
| Maintainer | haskell.vivian.mcphail <at> gmail <dot> com | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Numeric.Statistics
Description
Useful statistical functions
- type Sample a = Vector a
- type Samples a = Array Int (Vector a)
- covarianceMatrix :: Samples Double -> Matrix Double
- correlationCoefficientMatrix :: Samples Double -> Matrix Double
- meanList :: (Container Vector a, Num (Vector a), Fractional a) => [Sample a] -> Sample a
- meanArray :: (Container Vector a, Num (Vector a), Fractional a) => Samples a -> Sample a
- meanMatrix :: (Container Vector a, Num (Vector a), Fractional a) => Matrix a -> Sample a
- varianceList :: (Container Vector a, Floating (Vector a), Num a, Fractional a) => [Sample a] -> Sample a
- varianceArray :: (Container Vector a, Floating (Vector a), Fractional a) => Samples a -> Sample a
- varianceMatrix :: (Container Vector a, Floating (Vector a), Fractional a) => Matrix a -> Sample a
- centre :: Vector Double -> Vector Double
- cloglog :: Floating a => a -> a
- corcoeff :: Vector Double -> Vector Double -> Double
- cut :: Vector Double -> Vector Double -> Vector Int
- ranks :: (Fractional b, Storable b) => Vector Double -> Vector b
- kendall :: Vector Double -> Vector Double -> Matrix Double
- logit :: (Floating b, Storable b) => Vector b -> Vector b
- mahalanobis :: Samples Double -> Maybe (Sample Double) -> Double
- mode :: Vector Double -> [(Double, Integer)]
- moment :: Integral a => a -> Bool -> Bool -> Vector Double -> Double
- ols :: (Num (Vector t), Field t) => Matrix t -> Matrix t -> (Matrix t, Matrix t, Matrix t)
- percentile :: Double -> Vector Double -> Double
- range :: (Container c e, Num e) => c e -> e
- run_count :: (Num a, Num t, Ord b, Ord a, Container Vector b) => a -> Vector b -> [(a, t)]
- spearman :: Vector Double -> Vector Double -> Double
- studentize :: Vector Double -> Vector Double
Documentation
Arguments
| :: Samples Double | the dimensions of data (each vector being one dimension) | 
| -> Matrix Double | the symmetric covariance matrix | 
the covariance matrix
correlationCoefficientMatrix :: Samples Double -> Matrix Double Source #
the correlation coefficient: (cov x y) / (std x) (std y)
meanList :: (Container Vector a, Num (Vector a), Fractional a) => [Sample a] -> Sample a Source #
the mean of a list of vectors
meanArray :: (Container Vector a, Num (Vector a), Fractional a) => Samples a -> Sample a Source #
the mean of an array of vectors
meanMatrix :: (Container Vector a, Num (Vector a), Fractional a) => Matrix a -> Sample a Source #
the mean of a matrix with data series in rows
varianceList :: (Container Vector a, Floating (Vector a), Num a, Fractional a) => [Sample a] -> Sample a Source #
the variance of a list of vectors
varianceArray :: (Container Vector a, Floating (Vector a), Fractional a) => Samples a -> Sample a Source #
the variance of an array of vectors
varianceMatrix :: (Container Vector a, Floating (Vector a), Fractional a) => Matrix a -> Sample a Source #
the variance of a matrix with data series in rows
cloglog :: Floating a => a -> a Source #
complementary log-log function cloglog :: Vector Double -> Vector Double
corcoeff :: Vector Double -> Vector Double -> Double Source #
corcoeff = covariance x / (std dev x * std dev y)
cut numerical data into intervals, data must fall inside the bounds
ranks :: (Fractional b, Storable b) => Vector Double -> Vector b Source #
return the rank of each element of the vector multiple identical entries result in the average rank of those entries ranks :: Vector Double -> Vector Double
logit :: (Floating b, Storable b) => Vector b -> Vector b Source #
(logit p) = log(p/(1-p)) logit :: Vector Double -> Vector Double
Arguments
| :: Samples Double | the data set | 
| -> Maybe (Sample Double) | (Just sample) to be measured or use mean when Nothing | 
| -> Double | D^2 | 
the Mahalanobis D-square distance between samples columns are components and rows are observations (uses pseudoinverse)
Arguments
| :: Integral a | |
| => a | moment | 
| -> Bool | calculate central moment | 
| -> Bool | calculate absolute moment | 
| -> Vector Double | data | 
| -> Double | 
the p'th moment of a vector
Arguments
| :: (Num (Vector t), Field t) | |
| => Matrix t | X | 
| -> Matrix t | Y | 
| -> (Matrix t, Matrix t, Matrix t) | (OLS estimator for B, OLS estimator for s, OLS residuals) | 
ordinary least squares estimation for the multivariate model Y = X B + e rows are observations, columns are elements mean e = 0, cov e = kronecker s I
compute quantiles in percent
range :: (Container c e, Num e) => c e -> e Source #
the difference between the maximum and minimum of the input
Arguments
| :: (Num a, Num t, Ord b, Ord a, Container Vector b) | |
| => a | longest run to count | 
| -> Vector b | data | 
| -> [(a, t)] | 
 | 
count the number of runs greater than or equal to n in the data