monoid-statistics-1.1.5: Monoids for calculation of statistics of sample
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Monoid.Statistics.Numeric

Description

Monoids for calculating various statistics in constant space

Synopsis

Mean & Variance

Number of elements

newtype CountG a Source #

Calculate number of elements in the sample.

Constructors

CountG 

Fields

Instances

Instances details
Unbox a => Vector Vector (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Unbox a => MVector MVector (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

basicLength :: MVector s (CountG a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (CountG a) -> MVector s (CountG a) #

basicOverlaps :: MVector s (CountG a) -> MVector s (CountG a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (CountG a)) #

basicInitialize :: MVector s (CountG a) -> ST s () #

basicUnsafeReplicate :: Int -> CountG a -> ST s (MVector s (CountG a)) #

basicUnsafeRead :: MVector s (CountG a) -> Int -> ST s (CountG a) #

basicUnsafeWrite :: MVector s (CountG a) -> Int -> CountG a -> ST s () #

basicClear :: MVector s (CountG a) -> ST s () #

basicSet :: MVector s (CountG a) -> CountG a -> ST s () #

basicUnsafeCopy :: MVector s (CountG a) -> MVector s (CountG a) -> ST s () #

basicUnsafeMove :: MVector s (CountG a) -> MVector s (CountG a) -> ST s () #

basicUnsafeGrow :: MVector s (CountG a) -> Int -> ST s (MVector s (CountG a)) #

Data a => Data (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CountG a -> c (CountG a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CountG a) #

toConstr :: CountG a -> Constr #

dataTypeOf :: CountG a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CountG a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CountG a)) #

gmapT :: (forall b. Data b => b -> b) -> CountG a -> CountG a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CountG a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CountG a -> r #

gmapQ :: (forall d. Data d => d -> u) -> CountG a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CountG a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CountG a -> m (CountG a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CountG a -> m (CountG a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CountG a -> m (CountG a) #

Storable a => Storable (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

sizeOf :: CountG a -> Int #

alignment :: CountG a -> Int #

peekElemOff :: Ptr (CountG a) -> Int -> IO (CountG a) #

pokeElemOff :: Ptr (CountG a) -> Int -> CountG a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (CountG a) #

pokeByteOff :: Ptr b -> Int -> CountG a -> IO () #

peek :: Ptr (CountG a) -> IO (CountG a) #

poke :: Ptr (CountG a) -> CountG a -> IO () #

Integral a => Monoid (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

mempty :: CountG a #

mappend :: CountG a -> CountG a -> CountG a #

mconcat :: [CountG a] -> CountG a #

Integral a => Semigroup (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(<>) :: CountG a -> CountG a -> CountG a #

sconcat :: NonEmpty (CountG a) -> CountG a #

stimes :: Integral b => b -> CountG a -> CountG a #

Show a => Show (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

showsPrec :: Int -> CountG a -> ShowS #

show :: CountG a -> String #

showList :: [CountG a] -> ShowS #

Eq a => Eq (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(==) :: CountG a -> CountG a -> Bool #

(/=) :: CountG a -> CountG a -> Bool #

Ord a => Ord (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

compare :: CountG a -> CountG a -> Ordering #

(<) :: CountG a -> CountG a -> Bool #

(<=) :: CountG a -> CountG a -> Bool #

(>) :: CountG a -> CountG a -> Bool #

(>=) :: CountG a -> CountG a -> Bool #

max :: CountG a -> CountG a -> CountG a #

min :: CountG a -> CountG a -> CountG a #

CalcCount (CountG Int) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Real a => CalcNEvt (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Unbox a => Unbox (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Integral a => StatMonoid (CountG a) b Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

addValue :: CountG a -> b -> CountG a Source #

singletonMonoid :: b -> CountG a Source #

newtype MVector s (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s (CountG a) = MV_CountG (MVector s a)
newtype Vector (CountG a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype Vector (CountG a) = V_CountG (Vector a)

asCount :: CountG a -> CountG a Source #

Type restricted id

data CountW Source #

Accumulator type for counting weighted events. Weights are presumed to be independent and follow same distribution \[W\]. In this case sum of weights follows compound Poisson distribution. Its expectation could be then estimated as \[\sum_iw_i\] and variance as \[\sum_iw_i^2\].

Main use of this data type is as accumulator in histograms which count weighted events.

Constructors

CountW !Double !Double 

Instances

Instances details
Monoid CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Semigroup CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Generic CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Associated Types

type Rep CountW :: Type -> Type #

Methods

from :: CountW -> Rep CountW x #

to :: Rep CountW x -> CountW #

Show CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Eq CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(==) :: CountW -> CountW -> Bool #

(/=) :: CountW -> CountW -> Bool #

CalcNEvt CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Unbox CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Real a => StatMonoid CountW a Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Vector Vector CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

MVector MVector CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

IsoUnbox CountW (Double, Double) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep CountW = D1 ('MetaData "CountW" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" 'False) (C1 ('MetaCons "CountW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)))
newtype Vector CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Mean algorithms

Default algorithms

type Mean = MeanKBN Source #

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

data MeanNaive Source #

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.

Constructors

MeanNaive !Int !Double 

Instances

Instances details
Data MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MeanNaive -> c MeanNaive #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MeanNaive #

toConstr :: MeanNaive -> Constr #

dataTypeOf :: MeanNaive -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MeanNaive) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MeanNaive) #

gmapT :: (forall b. Data b => b -> b) -> MeanNaive -> MeanNaive #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MeanNaive -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MeanNaive -> r #

gmapQ :: (forall d. Data d => d -> u) -> MeanNaive -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MeanNaive -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MeanNaive -> m MeanNaive #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MeanNaive -> m MeanNaive #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MeanNaive -> m MeanNaive #

Monoid MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Semigroup MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Generic MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Associated Types

type Rep MeanNaive :: Type -> Type #

Show MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Eq MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcCount MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcMean MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Unbox MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Real a => StatMonoid MeanNaive a Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Vector Vector MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

MVector MVector MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep MeanNaive = D1 ('MetaData "MeanNaive" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" 'False) (C1 ('MetaCons "MeanNaive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)))
newtype Vector MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

data MeanKBN 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.

Constructors

MeanKBN !Int !KBNSum 

Instances

Instances details
Data MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MeanKBN -> c MeanKBN #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MeanKBN #

toConstr :: MeanKBN -> Constr #

dataTypeOf :: MeanKBN -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MeanKBN) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MeanKBN) #

gmapT :: (forall b. Data b => b -> b) -> MeanKBN -> MeanKBN #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MeanKBN -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MeanKBN -> r #

gmapQ :: (forall d. Data d => d -> u) -> MeanKBN -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MeanKBN -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MeanKBN -> m MeanKBN #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MeanKBN -> m MeanKBN #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MeanKBN -> m MeanKBN #

Monoid MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Semigroup MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Generic MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Associated Types

type Rep MeanKBN :: Type -> Type #

Methods

from :: MeanKBN -> Rep MeanKBN x #

to :: Rep MeanKBN x -> MeanKBN #

Show MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Eq MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(==) :: MeanKBN -> MeanKBN -> Bool #

(/=) :: MeanKBN -> MeanKBN -> Bool #

CalcCount MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcMean MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Unbox MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Real a => StatMonoid MeanKBN a Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Vector Vector MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

MVector MVector MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep MeanKBN = D1 ('MetaData "MeanKBN" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" 'False) (C1 ('MetaCons "MeanKBN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 KBNSum)))
newtype Vector MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Weighted mean

data WMeanNaive Source #

Incremental calculation of weighed mean.

Constructors

WMeanNaive !Double !Double 

Instances

Instances details
Data WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WMeanNaive -> c WMeanNaive #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WMeanNaive #

toConstr :: WMeanNaive -> Constr #

dataTypeOf :: WMeanNaive -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WMeanNaive) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WMeanNaive) #

gmapT :: (forall b. Data b => b -> b) -> WMeanNaive -> WMeanNaive #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WMeanNaive -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WMeanNaive -> r #

gmapQ :: (forall d. Data d => d -> u) -> WMeanNaive -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WMeanNaive -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WMeanNaive -> m WMeanNaive #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WMeanNaive -> m WMeanNaive #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WMeanNaive -> m WMeanNaive #

Monoid WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Semigroup WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Generic WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Associated Types

type Rep WMeanNaive :: Type -> Type #

Show WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Eq WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcMean WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Unbox WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Vector Vector WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

MVector MVector WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

(Real w, Real a) => StatMonoid WMeanNaive (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep WMeanNaive = D1 ('MetaData "WMeanNaive" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" 'False) (C1 ('MetaCons "WMeanNaive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)))
newtype Vector WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

data WMeanKBN Source #

Incremental calculation of weighed mean. Sum of both weights and elements is calculated using Kahan-Babuška-Neumaier summation.

Constructors

WMeanKBN !KBNSum !KBNSum 

Instances

Instances details
Data WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

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 #

Monoid WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Semigroup WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Generic WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Associated Types

type Rep WMeanKBN :: Type -> Type #

Methods

from :: WMeanKBN -> Rep WMeanKBN x #

to :: Rep WMeanKBN x -> WMeanKBN #

Show WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Eq WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcMean WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Unbox WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Vector Vector WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

MVector MVector WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

(Real w, Real a) => StatMonoid WMeanKBN (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep WMeanKBN = D1 ('MetaData "WMeanKBN" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" '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)))
newtype Vector WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Variance

data Variance Source #

Incremental algorithms for calculation the standard deviation [Chan1979].

Constructors

Variance !Int !Double !Double 

Instances

Instances details
Monoid Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Semigroup Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Show Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Eq Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcCount Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcMean Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcVariance Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Unbox Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Real a => StatMonoid Variance a Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Vector Vector Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

MVector MVector Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype Vector Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

asVariance :: Variance -> Variance Source #

Type restricted 'id '

Maximum and minimum

newtype Max a Source #

Calculate maximum of sample

Constructors

Max 

Fields

Instances

Instances details
Data a => Data (Max a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

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) #

toConstr :: Max a -> Constr #

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 => Monoid (Max a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Ord a => Semigroup (Max a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(<>) :: Max a -> Max a -> Max a #

sconcat :: NonEmpty (Max a) -> Max a #

stimes :: Integral b => b -> Max a -> Max a #

Generic (Max a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Associated Types

type Rep (Max a) :: Type -> Type #

Methods

from :: Max a -> Rep (Max a) x #

to :: Rep (Max a) x -> Max a #

Show a => Show (Max a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

showsPrec :: Int -> Max a -> ShowS #

show :: Max a -> String #

showList :: [Max a] -> ShowS #

Eq a => Eq (Max a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(==) :: Max a -> Max a -> Bool #

(/=) :: Max a -> Max a -> Bool #

Ord a => Ord (Max a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

compare :: Max a -> Max a -> Ordering #

(<) :: Max a -> Max a -> Bool #

(<=) :: Max a -> Max a -> Bool #

(>) :: Max a -> Max a -> Bool #

(>=) :: Max a -> Max a -> Bool #

max :: Max a -> Max a -> Max a #

min :: Max a -> Max a -> Max a #

(Ord a, a ~ a') => StatMonoid (Max a) a' Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

addValue :: Max a -> a' -> Max a Source #

singletonMonoid :: a' -> Max a Source #

type Rep (Max a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep (Max a) = D1 ('MetaData "Max" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" 'True) (C1 ('MetaCons "Max" 'PrefixI 'True) (S1 ('MetaSel ('Just "calcMax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))

newtype Min a Source #

Calculate minimum of sample

Constructors

Min 

Fields

Instances

Instances details
Data a => Data (Min a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

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) #

toConstr :: Min a -> Constr #

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 => Monoid (Min a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

Ord a => Semigroup (Min a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(<>) :: Min a -> Min a -> Min a #

sconcat :: NonEmpty (Min a) -> Min a #

stimes :: Integral b => b -> Min a -> Min a #

Generic (Min a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Associated Types

type Rep (Min a) :: Type -> Type #

Methods

from :: Min a -> Rep (Min a) x #

to :: Rep (Min a) x -> Min a #

Show a => Show (Min a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

showsPrec :: Int -> Min a -> ShowS #

show :: Min a -> String #

showList :: [Min a] -> ShowS #

Eq a => Eq (Min a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(==) :: Min a -> Min a -> Bool #

(/=) :: Min a -> Min a -> Bool #

Ord a => Ord (Min a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

compare :: Min a -> Min a -> Ordering #

(<) :: Min a -> Min a -> Bool #

(<=) :: Min a -> Min a -> Bool #

(>) :: Min a -> Min a -> Bool #

(>=) :: Min a -> Min a -> Bool #

max :: Min a -> Min a -> Min a #

min :: Min a -> Min a -> Min a #

(Ord a, a ~ a') => StatMonoid (Min a) a' Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

addValue :: Min a -> a' -> Min a Source #

singletonMonoid :: a' -> Min a Source #

type Rep (Min a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep (Min a) = D1 ('MetaData "Min" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" 'True) (C1 ('MetaCons "Min" 'PrefixI 'True) (S1 ('MetaSel ('Just "calcMin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))

newtype MaxD Source #

Calculate maximum of sample. For empty sample returns NaN. Any NaN encountered will be ignored.

Constructors

MaxD 

Fields

Instances

Instances details
Data MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MaxD -> c MaxD #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MaxD #

toConstr :: MaxD -> Constr #

dataTypeOf :: MaxD -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MaxD) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MaxD) #

gmapT :: (forall b. Data b => b -> b) -> MaxD -> MaxD #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MaxD -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MaxD -> r #

gmapQ :: (forall d. Data d => d -> u) -> MaxD -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MaxD -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MaxD -> m MaxD #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MaxD -> m MaxD #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MaxD -> m MaxD #

Monoid MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

mempty :: MaxD #

mappend :: MaxD -> MaxD -> MaxD #

mconcat :: [MaxD] -> MaxD #

Semigroup MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(<>) :: MaxD -> MaxD -> MaxD #

sconcat :: NonEmpty MaxD -> MaxD #

stimes :: Integral b => b -> MaxD -> MaxD #

Generic MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Associated Types

type Rep MaxD :: Type -> Type #

Methods

from :: MaxD -> Rep MaxD x #

to :: Rep MaxD x -> MaxD #

Show MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

showsPrec :: Int -> MaxD -> ShowS #

show :: MaxD -> String #

showList :: [MaxD] -> ShowS #

Eq MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(==) :: MaxD -> MaxD -> Bool #

(/=) :: MaxD -> MaxD -> Bool #

Unbox MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

a ~ Double => StatMonoid MaxD a Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

addValue :: MaxD -> a -> MaxD Source #

singletonMonoid :: a -> MaxD Source #

Vector Vector MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

MVector MVector MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep MaxD = D1 ('MetaData "MaxD" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" 'True) (C1 ('MetaCons "MaxD" 'PrefixI 'True) (S1 ('MetaSel ('Just "calcMaxD") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
newtype Vector MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s MaxD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MinD Source #

Calculate minimum of sample of Doubles. For empty sample returns NaN. Any NaN encountered will be ignored.

Constructors

MinD 

Fields

Instances

Instances details
Data MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MinD -> c MinD #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MinD #

toConstr :: MinD -> Constr #

dataTypeOf :: MinD -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MinD) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MinD) #

gmapT :: (forall b. Data b => b -> b) -> MinD -> MinD #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MinD -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MinD -> r #

gmapQ :: (forall d. Data d => d -> u) -> MinD -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MinD -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MinD -> m MinD #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MinD -> m MinD #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MinD -> m MinD #

Monoid MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

mempty :: MinD #

mappend :: MinD -> MinD -> MinD #

mconcat :: [MinD] -> MinD #

Semigroup MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(<>) :: MinD -> MinD -> MinD #

sconcat :: NonEmpty MinD -> MinD #

stimes :: Integral b => b -> MinD -> MinD #

Generic MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Associated Types

type Rep MinD :: Type -> Type #

Methods

from :: MinD -> Rep MinD x #

to :: Rep MinD x -> MinD #

Show MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

showsPrec :: Int -> MinD -> ShowS #

show :: MinD -> String #

showList :: [MinD] -> ShowS #

Eq MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(==) :: MinD -> MinD -> Bool #

(/=) :: MinD -> MinD -> Bool #

Unbox MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

a ~ Double => StatMonoid MinD a Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

addValue :: MinD -> a -> MinD Source #

singletonMonoid :: a -> MinD Source #

Vector Vector MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

MVector MVector MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep MinD = D1 ('MetaData "MinD" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" 'True) (C1 ('MetaCons "MinD" 'PrefixI 'True) (S1 ('MetaSel ('Just "calcMinD") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
newtype Vector MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s MinD Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Binomial trials

data BinomAcc Source #

Accumulator for binomial trials.

Constructors

BinomAcc 

Instances

Instances details
Data BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinomAcc -> c BinomAcc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinomAcc #

toConstr :: BinomAcc -> Constr #

dataTypeOf :: BinomAcc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinomAcc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinomAcc) #

gmapT :: (forall b. Data b => b -> b) -> BinomAcc -> BinomAcc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinomAcc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinomAcc -> r #

gmapQ :: (forall d. Data d => d -> u) -> BinomAcc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BinomAcc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinomAcc -> m BinomAcc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinomAcc -> m BinomAcc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinomAcc -> m BinomAcc #

Monoid BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Semigroup BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Generic BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Associated Types

type Rep BinomAcc :: Type -> Type #

Methods

from :: BinomAcc -> Rep BinomAcc x #

to :: Rep BinomAcc x -> BinomAcc #

Show BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Eq BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Ord BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Unbox BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

StatMonoid BinomAcc Bool Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Vector Vector BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

MVector MVector BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep BinomAcc = D1 ('MetaData "BinomAcc" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" 'False) (C1 ('MetaCons "BinomAcc" 'PrefixI 'True) (S1 ('MetaSel ('Just "binomAccSuccess") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "binomAccTotal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))
newtype Vector BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s BinomAcc Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

asBinomAcc :: BinomAcc -> BinomAcc Source #

Type restricted id

Rest

data Weighted w a Source #

Value a weighted by weight w

Constructors

Weighted w a 

Instances

Instances details
Bifunctor Weighted Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

bimap :: (a -> b) -> (c -> d) -> Weighted a c -> Weighted b d #

first :: (a -> b) -> Weighted a c -> Weighted b c #

second :: (b -> c) -> Weighted a b -> Weighted a c #

(Real w, Real a) => StatMonoid WMeanKBN (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

(Real w, Real a) => StatMonoid WMeanNaive (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

(Unbox w, Unbox a) => Vector Vector (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

(Unbox w, Unbox a) => MVector MVector (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

basicLength :: MVector s (Weighted w a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Weighted w a) -> MVector s (Weighted w a) #

basicOverlaps :: MVector s (Weighted w a) -> MVector s (Weighted w a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Weighted w a)) #

basicInitialize :: MVector s (Weighted w a) -> ST s () #

basicUnsafeReplicate :: Int -> Weighted w a -> ST s (MVector s (Weighted w a)) #

basicUnsafeRead :: MVector s (Weighted w a) -> Int -> ST s (Weighted w a) #

basicUnsafeWrite :: MVector s (Weighted w a) -> Int -> Weighted w a -> ST s () #

basicClear :: MVector s (Weighted w a) -> ST s () #

basicSet :: MVector s (Weighted w a) -> Weighted w a -> ST s () #

basicUnsafeCopy :: MVector s (Weighted w a) -> MVector s (Weighted w a) -> ST s () #

basicUnsafeMove :: MVector s (Weighted w a) -> MVector s (Weighted w a) -> ST s () #

basicUnsafeGrow :: MVector s (Weighted w a) -> Int -> ST s (MVector s (Weighted w a)) #

Foldable (Weighted w) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

fold :: Monoid m => Weighted w m -> m #

foldMap :: Monoid m => (a -> m) -> Weighted w a -> m #

foldMap' :: Monoid m => (a -> m) -> Weighted w a -> m #

foldr :: (a -> b -> b) -> b -> Weighted w a -> b #

foldr' :: (a -> b -> b) -> b -> Weighted w a -> b #

foldl :: (b -> a -> b) -> b -> Weighted w a -> b #

foldl' :: (b -> a -> b) -> b -> Weighted w a -> b #

foldr1 :: (a -> a -> a) -> Weighted w a -> a #

foldl1 :: (a -> a -> a) -> Weighted w a -> a #

toList :: Weighted w a -> [a] #

null :: Weighted w a -> Bool #

length :: Weighted w a -> Int #

elem :: Eq a => a -> Weighted w a -> Bool #

maximum :: Ord a => Weighted w a -> a #

minimum :: Ord a => Weighted w a -> a #

sum :: Num a => Weighted w a -> a #

product :: Num a => Weighted w a -> a #

Traversable (Weighted w) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

traverse :: Applicative f => (a -> f b) -> Weighted w a -> f (Weighted w b) #

sequenceA :: Applicative f => Weighted w (f a) -> f (Weighted w a) #

mapM :: Monad m => (a -> m b) -> Weighted w a -> m (Weighted w b) #

sequence :: Monad m => Weighted w (m a) -> m (Weighted w a) #

Functor (Weighted w) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

fmap :: (a -> b) -> Weighted w a -> Weighted w b #

(<$) :: a -> Weighted w b -> Weighted w a #

(Data w, Data a) => Data (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Weighted w a -> c (Weighted w a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Weighted w a) #

toConstr :: Weighted w a -> Constr #

dataTypeOf :: Weighted w a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Weighted w a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Weighted w a)) #

gmapT :: (forall b. Data b => b -> b) -> Weighted w a -> Weighted w a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Weighted w a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Weighted w a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Weighted w a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Weighted w a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Weighted w a -> m (Weighted w a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Weighted w a -> m (Weighted w a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Weighted w a -> m (Weighted w a) #

Generic (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Associated Types

type Rep (Weighted w a) :: Type -> Type #

Methods

from :: Weighted w a -> Rep (Weighted w a) x #

to :: Rep (Weighted w a) x -> Weighted w a #

(Show w, Show a) => Show (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

showsPrec :: Int -> Weighted w a -> ShowS #

show :: Weighted w a -> String #

showList :: [Weighted w a] -> ShowS #

(Eq w, Eq a) => Eq (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

(==) :: Weighted w a -> Weighted w a -> Bool #

(/=) :: Weighted w a -> Weighted w a -> Bool #

(Ord w, Ord a) => Ord (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Methods

compare :: Weighted w a -> Weighted w a -> Ordering #

(<) :: Weighted w a -> Weighted w a -> Bool #

(<=) :: Weighted w a -> Weighted w a -> Bool #

(>) :: Weighted w a -> Weighted w a -> Bool #

(>=) :: Weighted w a -> Weighted w a -> Bool #

max :: Weighted w a -> Weighted w a -> Weighted w a #

min :: Weighted w a -> Weighted w a -> Weighted w a #

(Unbox w, Unbox a) => Unbox (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype MVector s (Weighted w a) = MV_Weighted (MVector s (w, a))
type Rep (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

type Rep (Weighted w a) = D1 ('MetaData "Weighted" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" 'False) (C1 ('MetaCons "Weighted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 w) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
newtype Vector (Weighted w a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

newtype Vector (Weighted w a) = V_Weighted (Vector (w, a))

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.