monoid-statistics-1.1.5: Monoids for calculation of statistics of sample
CopyrightCopyright (c) 20102017 Alexey Khudyakov <alexey.skladnoy@gmail.com>
LicenseBSD3
MaintainerAlexey Khudyakov <alexey.skladnoy@gmail.com>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Monoid.Statistics.Class

Description

 
Synopsis

Monoid Type class and helpers

class Monoid m => StatMonoid m a where Source #

This type class is used to express parallelizable constant space algorithms for calculation of statistics. Statistic is function of type [a]→b which does not depend on order of elements. (for example: mean, sum, number of elements, variance, etc).

For many statistics it's possible to possible to construct constant space algorithm which is expressed as fold. Additionally it's usually possible to write function which combine state of fold accumulator to get statistic for union of two samples.

Thus for such algorithm we have value which corresponds to empty sample, function which which corresponds to merging of two samples, and single step of fold. Last one allows to evaluate statistic given data sample and first two form a monoid and allow parallelization: split data into parts, build estimate for each by folding and then merge them using mappend.

Instance must satisfy following laws. If floating point arithmetics is used then equality should be understood as approximate.

1. addValue (addValue y mempty) x  == addValue mempty x <> addValue mempty y
2. x <> y == y <> x

Minimal complete definition

addValue | singletonMonoid

Methods

addValue :: m -> a -> m Source #

Add one element to monoid accumulator. It's step of fold.

singletonMonoid :: a -> m Source #

State of accumulator corresponding to 1-element sample.

Instances

Instances details
Real a => StatMonoid KB2Sum a Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Real a => StatMonoid KBNSum a Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Real a => StatMonoid KahanSum a Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Real a => StatMonoid MeanKB2 a Source # 
Instance details

Defined in Data.Monoid.Statistics.Extra

Real a => StatMonoid MeanKahan a Source # 
Instance details

Defined in Data.Monoid.Statistics.Extra

Real a => StatMonoid WelfordMean a Source # 
Instance details

Defined in Data.Monoid.Statistics.Extra

StatMonoid BinomAcc Bool Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Real a => StatMonoid CountW a 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 #

Real a => StatMonoid MeanKBN a Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

Real a => StatMonoid MeanNaive a 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 #

Real a => StatMonoid Variance a 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

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

Defined in Data.Monoid.Statistics.Numeric

(Num a, a ~ a') => StatMonoid (Product a) a' Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

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

singletonMonoid :: a' -> Product a Source #

(Num a, a ~ a') => StatMonoid (Sum a) a' Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

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

singletonMonoid :: a' -> Sum a Source #

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 #

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

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

(StatMonoid a x, StatMonoid b x) => StatMonoid (Pair a b) x Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

addValue :: Pair a b -> x -> Pair a b Source #

singletonMonoid :: x -> Pair a b Source #

(StatMonoid m1 a, StatMonoid m2 a) => StatMonoid (m1, m2) a Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

addValue :: (m1, m2) -> a -> (m1, m2) Source #

singletonMonoid :: a -> (m1, m2) Source #

(StatMonoid m1 a, StatMonoid m2 a, StatMonoid m3 a) => StatMonoid (m1, m2, m3) a Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

addValue :: (m1, m2, m3) -> a -> (m1, m2, m3) Source #

singletonMonoid :: a -> (m1, m2, m3) Source #

(StatMonoid m1 a, StatMonoid m2 a, StatMonoid m3 a, StatMonoid m4 a) => StatMonoid (m1, m2, m3, m4) a Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

addValue :: (m1, m2, m3, m4) -> a -> (m1, m2, m3, m4) Source #

singletonMonoid :: a -> (m1, m2, m3, m4) Source #

reduceSample :: forall m a f. (StatMonoid m a, Foldable f) => f a -> m Source #

Calculate statistic over Foldable. It's implemented in terms of foldl'. Note that in cases when accumulator is immediately consumed by polymorphic function such as callMeam its type becomes ambiguous. TypeApplication then could be used to disambiguate.

>>> reduceSample @Mean [1,2,3,4]
MeanKBN 4 (KBNSum 10.0 0.0)
>>> calcMean $ reduceSample @Mean [1,2,3,4] :: Maybe Double
Just 2.5

reduceSampleVec :: forall m a v. (StatMonoid m a, Vector v a) => v a -> m Source #

Calculate statistic over vector. Works in same was as reduceSample but works for vectors.

Ad-hoc type classes for select statistics

Type classes defined here allows to extract common statistics from estimators. it's assumed that quantities in question are already computed so extraction is cheap.

Error handling

Computation of statistics may fail. For example mean is not defined for an empty sample. Maybe could be seen as easy way to handle this situation. But in many cases most convenient way to handle failure is to throw an exception. So failure is encoded by using polymorphic function of type MonadThrow m ⇒ a → m X.

Maybe types has instance, such as Maybe, Either SomeException, IO and most transformers wrapping it. Notably this library defines Partial monad which allows to convert failures to exception in pure setting.

>>> calcMean $ reduceSample @Mean []
*** Exception: EmptySample "Data.Monoid.Statistics.Numeric.MeanKBN: calcMean"
>>> calcMean $ reduceSample @Mean [] :: Maybe Double
Nothing
>>> import Control.Exception
>>> calcMean $ reduceSample @Mean [] :: Either SomeException Double
Left (EmptySample "Data.Monoid.Statistics.Numeric.MeanKBN: calcMean")

Last example uses IO

>>> calcMean $ reduceSample @Mean []
*** Exception: EmptySample "Data.Monoid.Statistics.Numeric.MeanKBN: calcMean"

Deriving instances

Type classes come in two variants, one that allow failure and one for use in cases when quantity is always defined. This is not the case for estimators, but true for distributions and intended for such use cases. In that case CalcViaHas could be used to derive necessary instances.

>>> :{
data NormalDist = NormalDist !Double !Double
  deriving (CalcMean,CalcVariance) via CalcViaHas NormalDist
instance HasMean NormalDist where
  getMean (NormalDist mu _) = mu
instance HasVariance NormalDist where
  getVariance   (NormalDist _ s) = s
  getVarianceML (NormalDist _ s) = s
:}

class CalcCount a where Source #

Value from which we can efficiently extract number of elements in sample it represents.

Methods

calcCount :: a -> Int Source #

Assumed O(1). Number of elements in sample.

Instances

Instances details
CalcCount MeanKahan Source # 
Instance details

Defined in Data.Monoid.Statistics.Extra

CalcCount WelfordMean Source # 
Instance details

Defined in Data.Monoid.Statistics.Extra

CalcCount MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcCount MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcCount Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcCount (CountG Int) Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

class CalcNEvt a where Source #

Type class for accumulators that are used for event counting with possibly weighted events. Those are mostly used as accumulators in histograms.

Minimal complete definition

calcEvtsW, calcEvtsWErr

Methods

calcEvtsW :: a -> Double Source #

Calculate sum of events weights.

calcEvtsWErr :: a -> Double Source #

Calculate error estimate (1σ or 68% CL). All instances defined in library use normal approximation which breaks down for small number of events.

calcEffNEvt :: a -> Double Source #

Calculate effective number of events which is defined as \[N=E(w)^2/\operatorname{Var}(w)\] or as number of events which will yield same estimate for mean variance is they all have same weight.

Instances

Instances details
CalcNEvt Int32 Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

CalcNEvt Int64 Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

CalcNEvt Word32 Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

CalcNEvt Word64 Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

CalcNEvt CountW Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcNEvt Int Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

CalcNEvt Word Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

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

Defined in Data.Monoid.Statistics.Numeric

class CalcMean a where Source #

Value from which we can efficiently calculate mean of sample or distribution.

Methods

calcMean :: MonadThrow m => a -> m Double Source #

Assumed O(1) Returns Nothing if there isn't enough data to make estimate or distribution doesn't have defined mean.

\[ \bar{x} = \frac{1}{N}\sum_{i=1}^N{x_i} \]

Instances

Instances details
CalcMean MeanKB2 Source # 
Instance details

Defined in Data.Monoid.Statistics.Extra

CalcMean MeanKahan Source # 
Instance details

Defined in Data.Monoid.Statistics.Extra

CalcMean WelfordMean Source # 
Instance details

Defined in Data.Monoid.Statistics.Extra

CalcMean MeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcMean MeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcMean Variance Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcMean WMeanKBN Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

CalcMean WMeanNaive Source # 
Instance details

Defined in Data.Monoid.Statistics.Numeric

HasMean a => CalcMean (CalcViaHas a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

class CalcMean a => HasMean a where Source #

Same as CalcMean but should never fail

Methods

getMean :: a -> Double Source #

Instances

Instances details
HasMean a => HasMean (CalcViaHas a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

class CalcVariance a where Source #

Values from which we can efficiently compute estimate of sample variance or distribution variance. It has two methods: one which applies bias correction to estimate and another that returns maximul likelyhood estimate. For distribution they should return same value.

Minimal complete definition

calcVariance, calcVarianceML | calcStddev, calcStddevML

Methods

calcVariance :: MonadThrow m => a -> m Double Source #

Assumed O(1) Calculate unbiased estimate of variance:

\[ \sigma^2 = \frac{1}{N-1}\sum_{i=1}^N(x_i - \bar{x})^2 \]

calcVarianceML :: MonadThrow m => a -> m Double Source #

Assumed O(1) Calculate maximum likelihood estimate of variance:

\[ \sigma^2 = \frac{1}{N}\sum_{i=1}^N(x_i - \bar{x})^2 \]

calcStddev :: MonadThrow m => a -> m Double Source #

Calculate sample standard deviation from unbiased estimation of variance.

calcStddevML :: MonadThrow m => a -> m Double Source #

Calculate sample standard deviation from maximum likelihood estimation of variance.

Deriving via

Exception handling

newtype Partial a Source #

Identity monad which is used to encode partial functions for MonadThrow based error handling. Its MonadThrow instance just throws normal exception.

Constructors

Partial a 

Instances

Instances details
Applicative Partial Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

pure :: a -> Partial a #

(<*>) :: Partial (a -> b) -> Partial a -> Partial b #

liftA2 :: (a -> b -> c) -> Partial a -> Partial b -> Partial c #

(*>) :: Partial a -> Partial b -> Partial b #

(<*) :: Partial a -> Partial b -> Partial a #

Functor Partial Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

fmap :: (a -> b) -> Partial a -> Partial b #

(<$) :: a -> Partial b -> Partial a #

Monad Partial Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

(>>=) :: Partial a -> (a -> Partial b) -> Partial b #

(>>) :: Partial a -> Partial b -> Partial b #

return :: a -> Partial a #

MonadThrow Partial Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

throwM :: Exception e => e -> Partial a #

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

Defined in Data.Monoid.Statistics.Class

Methods

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

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

toConstr :: Partial a -> Constr #

dataTypeOf :: Partial a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Partial a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Associated Types

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

Methods

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

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

Read a => Read (Partial a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

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

Defined in Data.Monoid.Statistics.Class

Methods

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

show :: Partial a -> String #

showList :: [Partial a] -> ShowS #

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

Defined in Data.Monoid.Statistics.Class

Methods

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

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

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

Defined in Data.Monoid.Statistics.Class

Methods

compare :: Partial a -> Partial a -> Ordering #

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

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

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

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

max :: Partial a -> Partial a -> Partial a #

min :: Partial a -> Partial a -> Partial a #

type Rep (Partial a) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

type Rep (Partial a) = D1 ('MetaData "Partial" "Data.Monoid.Statistics.Class" "monoid-statistics-1.1.5-3Ws7u7NExusHdAWFdMpnBd" 'True) (C1 ('MetaCons "Partial" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

partial :: HasCallStack => Partial a -> a Source #

Convert error to IO exception. This way one could for example convert case when some statistics is not defined to an exception:

>>> calcMean $ reduceSample @Mean []
*** Exception: EmptySample "Data.Monoid.Statistics.Numeric.MeanKBN: calcMean"

data SampleError Source #

Exception which is thrown when we can't compute some value

Constructors

EmptySample String

EmptySample function: We're trying to compute quantity that is undefined for empty sample.

InvalidSample String String

InvalidSample function descripton quantity in question could not be computed for some other reason

Data types

data Pair a b Source #

Strict pair. It allows to calculate two statistics in parallel

Constructors

Pair !a !b 

Instances

Instances details
(Unbox a, Unbox b) => Vector Vector (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

basicUnsafeFreeze :: Mutable Vector s (Pair a b) -> ST s (Vector (Pair a b)) #

basicUnsafeThaw :: Vector (Pair a b) -> ST s (Mutable Vector s (Pair a b)) #

basicLength :: Vector (Pair a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Pair a b) -> Vector (Pair a b) #

basicUnsafeIndexM :: Vector (Pair a b) -> Int -> Box (Pair a b) #

basicUnsafeCopy :: Mutable Vector s (Pair a b) -> Vector (Pair a b) -> ST s () #

elemseq :: Vector (Pair a b) -> Pair a b -> b0 -> b0 #

(Unbox a, Unbox b) => MVector MVector (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

basicLength :: MVector s (Pair a b) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Pair a b) -> MVector s (Pair a b) #

basicOverlaps :: MVector s (Pair a b) -> MVector s (Pair a b) -> Bool #

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

basicInitialize :: MVector s (Pair a b) -> ST s () #

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

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

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

basicClear :: MVector s (Pair a b) -> ST s () #

basicSet :: MVector s (Pair a b) -> Pair a b -> ST s () #

basicUnsafeCopy :: MVector s (Pair a b) -> MVector s (Pair a b) -> ST s () #

basicUnsafeMove :: MVector s (Pair a b) -> MVector s (Pair a b) -> ST s () #

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

(Data a, Data b) => Data (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

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

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

toConstr :: Pair a b -> Constr #

dataTypeOf :: Pair a b -> DataType #

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

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

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

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

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

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

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

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

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

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

(Monoid a, Monoid b) => Monoid (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

mempty :: Pair a b #

mappend :: Pair a b -> Pair a b -> Pair a b #

mconcat :: [Pair a b] -> Pair a b #

(Semigroup a, Semigroup b) => Semigroup (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

(<>) :: Pair a b -> Pair a b -> Pair a b #

sconcat :: NonEmpty (Pair a b) -> Pair a b #

stimes :: Integral b0 => b0 -> Pair a b -> Pair a b #

Generic (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Associated Types

type Rep (Pair a b) :: Type -> Type #

Methods

from :: Pair a b -> Rep (Pair a b) x #

to :: Rep (Pair a b) x -> Pair a b #

(Show a, Show b) => Show (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

showsPrec :: Int -> Pair a b -> ShowS #

show :: Pair a b -> String #

showList :: [Pair a b] -> ShowS #

(Eq a, Eq b) => Eq (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

(==) :: Pair a b -> Pair a b -> Bool #

(/=) :: Pair a b -> Pair a b -> Bool #

(Ord a, Ord b) => Ord (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

compare :: Pair a b -> Pair a b -> Ordering #

(<) :: Pair a b -> Pair a b -> Bool #

(<=) :: Pair a b -> Pair a b -> Bool #

(>) :: Pair a b -> Pair a b -> Bool #

(>=) :: Pair a b -> Pair a b -> Bool #

max :: Pair a b -> Pair a b -> Pair a b #

min :: Pair a b -> Pair a b -> Pair a b #

(Unbox a, Unbox b) => Unbox (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

(StatMonoid a x, StatMonoid b x) => StatMonoid (Pair a b) x Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

Methods

addValue :: Pair a b -> x -> Pair a b Source #

singletonMonoid :: x -> Pair a b Source #

newtype MVector s (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

newtype MVector s (Pair a b) = MV_Pair (MVector s (a, b))
type Rep (Pair a b) Source # 
Instance details

Defined in Data.Monoid.Statistics.Class

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

Defined in Data.Monoid.Statistics.Class

newtype Vector (Pair a b) = V_Pair (Vector (a, b))