This module provides a set of predicates for sampling from various
distributions. The state of the random generator is threaded through
using the DCG idiom.
- author
- - Samer Abdallah
- bernoulli(+A:prob, -X:oneof([0,1]))// is det
- Sample binary random variable.
- binomial(+P:float, +N:natural, -X:natural)// is det
- Sample X from a binomial distribution, ie the number of
successful trials out of N trials where the probability
of success of each trial is P.
- poisson(+A:nonneg, -X:float)// is det
- Sample from Poisson distribution of rate A.
- discrete(+A:list(prob), -X:natural)// is det
- Sample from a discrete distribution over natural numbers.
- discrete(+O:list(T), +A:list(prob), -X:T)// is det
- Sample from a discrete distribution over list of objects.
- uniform01(-X:float)// is det
- Sample X from uniform distribution on [0,1).
- normal(-X:float)// is det
- Sample from zero-mean unit-variance Gaussian.
- exponential(-X:float)// is det
- Sample from unit-mean exponential distribution.
- stable(+A, +B, -X:float)// is det
- Sample from a Levy-stable distribution.
- dirichlet(+A:list(nonneg), -X:list(prob))// is det
- Sample from a Dirichlet distribution.
- uniform(+Items:list(A), -A)// is det
- Uniform distribution over a finite number of items.
uniform ::
list(A)
-> expr(A)
.
- uniformP(+P:dcg(-A), -A)// is det
- Sample uniformly from all solutions to
call(P,X)
.
- beta(+A:nonneg, +B:nonneg, -X:prob)// is det
- Sample from beta distribution.
- zeta(+A:nonneg, -X:natural)// is det
- Sample from zeta (hyperbolic or power law) distribution over natural numbers.
NB: Must have A > 1.
- gamma(+A:nonneg, -X:float)// is det
- Sample from gamma distribution with parameter A.
- gaussian(+Mean:float, +Var:nonneg, -X:float)// is det
- gaussian :: \(float, nonneg) ->
expr(float)
.
Sample from Gaussian with given mean and variance.
- inv_gamma(+A:nonneg, -X:float)// is det
- Sample from inverse gamma distribution with parameter A.
- students_t(+V:nonneg, -X:float)// is det
- Sample from student's t distribution with V degrees of freedom.
- product_pair(+F:dist(A), +G:dist(B), -X:pair(A,B))// is det
- Sample a pair from two independent distributions.
- mixture(+Sources:list(expr(A)), +Probs:list(prob), -X:A)// is det
- Sample from discrete distribution over Sources with probabilities Probs
and then sample from the resulting distribution.
mixture :: \(list(expr(A))
, list(prob)
) -> expr(A)
.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
- uniformT(Arg1, Arg2, Arg3, Arg4)
- discreteT(Arg1, Arg2, Arg3, Arg4, Arg5)
- prob(Arg1, Arg2, Arg3)
- prob(Arg1, Arg2)
- pdf(Arg1, Arg2, Arg3)
- pdf(Arg1, Arg2)