| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Goal.Probability.Statistical
Description
Core types, classes, and functions for working with manifolds of probability distributions.
Synopsis
- newtype Random a = Random (forall s. Gen s -> ST s a)
- class Manifold x => Statistical x where- type SamplePoint x :: Type
 
- type Sample x = [SamplePoint x]
- realize :: Random a -> IO a
- initialize :: (Manifold x, Generative d y, SamplePoint y ~ Double) => (d # y) -> Random (c # x)
- uniformInitialize :: Manifold x => (Double, Double) -> Random (Point c x)
- uniformInitialize' :: Manifold x => Vector (Dimension x) (Double, Double) -> Random (Point c x)
- class Statistical x => Generative c x where- samplePoint :: Point c x -> Random (SamplePoint x)
- sample :: Int -> Point c x -> Random (Sample x)
 
- class Statistical x => AbsolutelyContinuous c x where
- density :: AbsolutelyContinuous c x => Point c x -> SamplePoint x -> Double
- logDensity :: AbsolutelyContinuous c x => Point c x -> SamplePoint x -> Double
- class KnownNat (Cardinality x) => Discrete x where- type Cardinality x :: Nat
- sampleSpace :: Proxy x -> Sample x
 
- pointSampleSpace :: forall c x. Discrete x => (c # x) -> Sample x
- expectation :: forall c x. (AbsolutelyContinuous c x, Discrete x) => Point c x -> (SamplePoint x -> Double) -> Double
- class Statistical x => MaximumLikelihood c x where
- class Manifold x => LogLikelihood c x s where- logLikelihood :: [s] -> (c # x) -> Double
- logLikelihoodDifferential :: [s] -> (c # x) -> c #* x
 
Random
A random variable.
class Manifold x => Statistical x Source #
A Manifold is Statistical if it is a set of probability distributions
 over a particular sample space, where the sample space is a set of the
 specified SamplePoints.
Associated Types
type SamplePoint x :: Type Source #
Instances
type Sample x = [SamplePoint x] Source #
A Sample is a list of SamplePoints.
Initializiation
initialize :: (Manifold x, Generative d y, SamplePoint y ~ Double) => (d # y) -> Random (c # x) Source #
Generates a random point on the target Manifold by generating random
 samples from the given distribution.
uniformInitialize :: Manifold x => (Double, Double) -> Random (Point c x) Source #
Generates an initial point on the target Manifold by generating uniform
 samples from the given vector of bounds.
uniformInitialize' :: Manifold x => Vector (Dimension x) (Double, Double) -> Random (Point c x) Source #
Generates an initial point on the target Manifold by generating uniform
 samples from the given vector of bounds.
Properties of Distributions
class Statistical x => Generative c x where Source #
A distribution is Generative if we can sample from it. Generation is
 powered by mwc-random.
Minimal complete definition
Nothing
Methods
samplePoint :: Point c x -> Random (SamplePoint x) Source #
Instances
class Statistical x => AbsolutelyContinuous c x where Source #
The distributions \(P \in \mathcal M\) in a Statistical Manifold
 \(\mathcal M\) are AbsolutelyContinuous if there is a reference measure
 \(\mu\) and a function \(p\) such that
 \(P(A) = \int_A p d\mu\). We refer to \(p(x)\) as the density of the
 probability distribution.
Minimal complete definition
Nothing
Methods
logDensities :: Point c x -> Sample x -> [Double] Source #
Instances
density :: AbsolutelyContinuous c x => Point c x -> SamplePoint x -> Double Source #
logDensity :: AbsolutelyContinuous c x => Point c x -> SamplePoint x -> Double Source #
class KnownNat (Cardinality x) => Discrete x where Source #
Probability distributions for which the sample space is countable. This affords brute force computation of expectations.
Associated Types
type Cardinality x :: Nat Source #
Methods
sampleSpace :: Proxy x -> Sample x Source #
Instances
| Discrete Bernoulli Source # | |
| Defined in Goal.Probability.Distributions Associated Types type Cardinality Bernoulli :: Nat Source # | |
| KnownNat n => Discrete (Categorical n) Source # | |
| Defined in Goal.Probability.Distributions Associated Types type Cardinality (Categorical n) :: Nat Source # Methods sampleSpace :: Proxy (Categorical n) -> Sample (Categorical n) Source # | |
| KnownNat n => Discrete (Binomial n) Source # | |
| Defined in Goal.Probability.Distributions Associated Types type Cardinality (Binomial n) :: Nat Source # | |
pointSampleSpace :: forall c x. Discrete x => (c # x) -> Sample x Source #
Convenience function for getting the sample space of a Discrete
 probability distribution.
expectation :: forall c x. (AbsolutelyContinuous c x, Discrete x) => Point c x -> (SamplePoint x -> Double) -> Double Source #
expectation computes the brute force expected value of a Finite set
 given an appropriate density.
Maximum Likelihood Estimation
class Statistical x => MaximumLikelihood c x where Source #
mle computes the MaximumLikelihood estimator.
Instances
| Transition Mean c Poisson => MaximumLikelihood c Poisson Source # | |
| Transition Mean c Bernoulli => MaximumLikelihood c Bernoulli Source # | |
| Transition Mean c Normal => MaximumLikelihood c Normal Source # | |
| (KnownNat n, Transition Mean c (Categorical n)) => MaximumLikelihood c (Categorical n) Source # | |
| Defined in Goal.Probability.Distributions Methods mle :: Sample (Categorical n) -> c # Categorical n Source # | |
| (KnownNat n, Transition Mean c (Binomial n)) => MaximumLikelihood c (Binomial n) Source # | |
| (KnownNat n, Transition Mean c (MultivariateNormal n)) => MaximumLikelihood c (MultivariateNormal n) Source # | |
| Defined in Goal.Probability.Distributions.Gaussian Methods mle :: Sample (MultivariateNormal n) -> c # MultivariateNormal n Source # | |
class Manifold x => LogLikelihood c x s where Source #
Average log-likelihood and the differential for gradient ascent.
Methods
logLikelihood :: [s] -> (c # x) -> Double Source #
logLikelihoodDifferential :: [s] -> (c # x) -> c #* x Source #