Safe Haskell | None |
---|---|
Language | Haskell2010 |
Monoids for calculating various statistics in constant space
Synopsis
- newtype CountG a = CountG {
- calcCountN :: a
- type Count = CountG Int
- asCount :: CountG a -> CountG a
- type Mean = MeanKBN
- asMean :: Mean -> Mean
- type WMean = WMeanKBN
- asWMean :: WMean -> WMean
- data MeanNaive = MeanNaive !Int !Double
- asMeanNaive :: MeanNaive -> MeanNaive
- data MeanKBN = MeanKBN !Int !KBNSum
- asMeanKBN :: MeanKBN -> MeanKBN
- data WMeanNaive = WMeanNaive !Double !Double
- asWMeanNaive :: WMeanNaive -> WMeanNaive
- data WMeanKBN = WMeanKBN !KBNSum !KBNSum
- asWMeanKBN :: WMeanKBN -> WMeanKBN
- data Variance = Variance !Int !Double !Double
- asVariance :: Variance -> Variance
- newtype Max a = Max {}
- newtype Min a = Min {}
- newtype MaxD = MaxD {}
- newtype MinD = MinD {}
- data BinomAcc = BinomAcc {
- binomAccSuccess :: !Int
- binomAccTotal :: !Int
- asBinomAcc :: BinomAcc -> BinomAcc
- data Weighted w a = Weighted w a
Mean & Variance
Number of elements
Calculate number of elements in the sample.
CountG | |
|
Instances
Mean algorithms
Default algorithms
Type alias for currently recommended algorithms for calculation of mean. It should be default choice
type WMean = WMeanKBN Source #
Type alias for currently recommended algorithms for calculation of weighted mean. It should be default choice
Mean
Incremental calculation of mean. It tracks separately number of
elements and running sum. Note that summation of floating point
numbers loses precision and genrally use MeanKBN
is
recommended.
Instances
asMeanNaive :: MeanNaive -> MeanNaive Source #
Incremental calculation of mean. It tracks separately number of elements and running sum. It uses algorithm for compensated summation which works with mantissa of double size at cost of doing more operations. This means that it's usually possible to compute sum (and therefore mean) within 1 ulp.
Instances
Weighted mean
data WMeanNaive Source #
Incremental calculation of weighed mean.
Instances
asWMeanNaive :: WMeanNaive -> WMeanNaive Source #
Incremental calculation of weighed mean. Sum of both weights and elements is calculated using Kahan-Babuška-Neumaier summation.
Instances
Eq WMeanKBN Source # | |
Data WMeanKBN Source # | |
Defined in Data.Monoid.Statistics.Numeric gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WMeanKBN -> c WMeanKBN # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WMeanKBN # toConstr :: WMeanKBN -> Constr # dataTypeOf :: WMeanKBN -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WMeanKBN) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WMeanKBN) # gmapT :: (forall b. Data b => b -> b) -> WMeanKBN -> WMeanKBN # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WMeanKBN -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WMeanKBN -> r # gmapQ :: (forall d. Data d => d -> u) -> WMeanKBN -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WMeanKBN -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WMeanKBN -> m WMeanKBN # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WMeanKBN -> m WMeanKBN # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WMeanKBN -> m WMeanKBN # | |
Show WMeanKBN Source # | |
Generic WMeanKBN Source # | |
Semigroup WMeanKBN Source # | |
Monoid WMeanKBN Source # | |
CalcMean WMeanKBN Source # | |
Defined in Data.Monoid.Statistics.Numeric | |
(Real w, Real a) => StatMonoid WMeanKBN (Weighted w a) Source # | |
type Rep WMeanKBN Source # | |
Defined in Data.Monoid.Statistics.Numeric type Rep WMeanKBN = D1 ('MetaData "WMeanKBN" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.1-Et52IJUUy4YDKplMeouIOs" 'False) (C1 ('MetaCons "WMeanKBN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 KBNSum) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 KBNSum))) |
asWMeanKBN :: WMeanKBN -> WMeanKBN Source #
Variance
Incremental algorithms for calculation the standard deviation [Chan1979].
Instances
asVariance :: Variance -> Variance Source #
Type restricted 'id '
Maximum and minimum
Calculate maximum of sample
Instances
Eq a => Eq (Max a) Source # | |
Data a => Data (Max a) Source # | |
Defined in Data.Monoid.Statistics.Numeric gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Max a -> c (Max a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Max a) # dataTypeOf :: Max a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Max a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Max a)) # gmapT :: (forall b. Data b => b -> b) -> Max a -> Max a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r # gmapQ :: (forall d. Data d => d -> u) -> Max a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Max a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # | |
Ord a => Ord (Max a) Source # | |
Show a => Show (Max a) Source # | |
Generic (Max a) Source # | |
Ord a => Semigroup (Max a) Source # | |
Ord a => Monoid (Max a) Source # | |
(Ord a, a ~ a') => StatMonoid (Max a) a' Source # | |
Defined in Data.Monoid.Statistics.Numeric | |
type Rep (Max a) Source # | |
Defined in Data.Monoid.Statistics.Numeric |
Calculate minimum of sample
Instances
Eq a => Eq (Min a) Source # | |
Data a => Data (Min a) Source # | |
Defined in Data.Monoid.Statistics.Numeric gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Min a -> c (Min a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Min a) # dataTypeOf :: Min a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Min a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Min a)) # gmapT :: (forall b. Data b => b -> b) -> Min a -> Min a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r # gmapQ :: (forall d. Data d => d -> u) -> Min a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Min a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # | |
Ord a => Ord (Min a) Source # | |
Show a => Show (Min a) Source # | |
Generic (Min a) Source # | |
Ord a => Semigroup (Min a) Source # | |
Ord a => Monoid (Min a) Source # | |
(Ord a, a ~ a') => StatMonoid (Min a) a' Source # | |
Defined in Data.Monoid.Statistics.Numeric | |
type Rep (Min a) Source # | |
Defined in Data.Monoid.Statistics.Numeric |
Calculate maximum of sample. For empty sample returns NaN. Any NaN encountered will be ignored.
Instances
Calculate minimum of sample of Doubles. For empty sample returns NaN. Any NaN encountered will be ignored.
Instances
Binomial trials
Accumulator for binomial trials.
BinomAcc | |
|
Instances
Rest
Value a
weighted by weight w
Weighted w a |
Instances
References
- [Welford1962] Welford, B.P. (1962) Note on a method for calculating corrected sums of squares and products. Technometrics 4(3):419-420. http://www.jstor.org/stable/1266577
- [Chan1979] Chan, Tony F.; Golub, Gene H.; LeVeque, Randall J. (1979), Updating Formulae and a Pairwise Algorithm for Computing Sample Variances., Technical Report STAN-CS-79-773, Department of Computer Science, Stanford University. Page 4.