goal-probability-0.20: Optimization on manifolds of probability distributions with Goal
Safe HaskellNone
LanguageHaskell2010

Goal.Probability

Description

The main module of goal-probability. Import this module to use all the types, functions, and classes provided by goal-probability.

Synopsis

Package Exports

Stochastic Operations

shuffleList :: [a] -> Random [a] Source #

Shuffle the elements of a list.

resampleVector :: (KnownNat n, KnownNat k) => Vector n x -> Random (Vector k x) Source #

Returns a uniform sample of elements from the given vector with replacement.

subsampleVector :: forall k m v x. (KnownNat k, KnownNat m, VectorClass v x) => Vector v (k + m) x -> Random (Vector v k x) Source #

Take a random, unordered subset of a list.

noisyFunction Source #

Arguments

:: (Generative c x, Num (SamplePoint x)) 
=> Point c x

Noise model

-> (y -> SamplePoint x)

Function

-> y

Input

-> Random (SamplePoint x)

Stochastic Output

Returns a sample from the given function with added noise.

Circuits

minibatcher :: Int -> [x] -> Chain Random [x] Source #

A Circuit that helps fitting data based on minibatches. Essentially, it creates an infinite list out of shuffled versions of the input list, and breaks down and returns the result in chunks of the specified size.

Statistics

estimateMeanVariance :: Traversable f => f Double -> (Double, Double) Source #

Estimate the mean and variance of a sample (with Bessel's correction)

estimateMeanSD :: Traversable f => f Double -> (Double, Double) Source #

Estimate the mean and variance of a sample (with Bessel's correction)

estimateFanoFactor :: Traversable f => f Double -> Double Source #

Estimate the Fano Factor of a sample.

estimateCoefficientOfVariation :: Traversable f => f Double -> Double Source #

Estimate the coefficient of variation from a sample.

estimateCorrelation :: [(Double, Double)] -> Double Source #

Computes the empirical covariance matrix given a sample from a bivariate random variable.

estimateCorrelations :: forall k x v. (VectorClass v x, VectorClass v Double, KnownNat k, Real x) => [Vector v k x] -> Matrix k k Double Source #

Computes the empirical covariance matrix given a sample if iid random vectors.

histograms Source #

Arguments

:: Int

Number of Bins

-> Maybe (Double, Double)

Maybe bin bounds

-> [[Double]]

Datasets

-> ([Double], [[Int]], [[Double]])

Bin centres, counts, and densities for each dataset

Computes histograms (and densities) with the given number of bins for the given list of samples. Bounds can be given or computed automatically. The returned values are the list of bin centres and the binned samples. If bounds are given but are not greater than all given sample points, then an error will be thrown.

Model Selection

akaikesInformationCriterion :: forall c x s. (Manifold x, LogLikelihood c x s) => (c # x) -> [s] -> Double Source #

Calculate the AIC for a given model and sample.

bayesianInformationCriterion :: forall c x s. (LogLikelihood c x s, Manifold x) => (c # x) -> [s] -> Double Source #

Calculate the BIC for a given model and sample.