1:- module(prob_tagless,
    2          [ uniform01//1
    3          , uniform//2, uniformP//2
    4          , normal//1
    5          , gaussian//3
    6          , exponential//1
    7          , poisson//2
    8          , stable//3
    9          , dirichlet//2
   10          , discrete//2
   11          , discrete//3
   12          , binomial//3
   13          , beta//3
   14          , zeta//2
   15          , gamma//2
   16          , inv_gamma//2
   17          , bernoulli//2
   18          , students_t//2
   19          , mixture//3
   20          , pair//3
   21          ]).

Random predicates, untagged RNG state

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 /
   32:- module_transparent stream/2.   33
   34:- use_module(library(dcg_core)).   35:- use_module(library(dcg_pair)).   36:- use_module(library(plrand),[]).   37
   38term_expansion(stub(Arity,Name,Pred), Head --> plrand:Body) :-
   39   length(Args, Arity),
   40   Head =.. [Name | Args],
   41   Body =.. [Pred | Args].
 bernoulli(+A:prob, -X:oneof([0,1]))// is det
Sample binary random variable.
   45bernoulli(P,X) --> plrand:sample_Uniform01(U), {U<P->X=1;X=0}.
 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.
   52stub(3,binomial,sample_Binomial).
 poisson(+A:nonneg, -X:float)// is det
Sample from Poisson distribution of rate A.
   57stub(2,poisson,sample_Poisson).
 discrete(+A:list(prob), -X:natural)// is det
Sample from a discrete distribution over natural numbers.
   61discrete(Ps,I) --> {length(Ps,N)}, plrand:sample_Discrete(N,Ps,I).
 discrete(+O:list(T), +A:list(prob), -X:T)// is det
Sample from a discrete distribution over list of objects.
   65discrete(Xs,Ps,X) --> {length(Ps,N)}, plrand:sample_Discrete(N,Ps,I), {nth1(I,Xs,X)}.
 uniform01(-X:float)// is det
Sample X from uniform distribution on [0,1).
   70stub(1,uniform01,sample_Uniform01).
 normal(-X:float)// is det
Sample from zero-mean unit-variance Gaussian.
   74stub(1,normal,sample_Normal).
 exponential(-X:float)// is det
Sample from unit-mean exponential distribution.
   78stub(1,exponential,sample_Exponential).
 stable(+A, +B, -X:float)// is det
Sample from a Levy-stable distribution.
   82stub(3,stable,sample_Stable).
 dirichlet(+A:list(nonneg), -X:list(prob))// is det
Sample from a Dirichlet distribution.
   86dirichlet(A,X) --> {length(A,N)}, plrand:sample_Dirichlet(N,A,X).
 uniform(+Items:list(A), -A)// is det
Uniform distribution over a finite number of items. uniform :: list(A) -> expr(A).
   94uniform(O,X) --> 
   95   {length(O,N)},
   96   plrand:sample_Uniform01(U),
   97   {I is 1+floor(N*U), nth1(I,O,X)}.
 uniformP(+P:dcg(-A), -A)// is det
Sample uniformly from all solutions to call(P,X).
  101:- meta_predicate uniformP(3,-,+,-).  102uniformP(P,X) -->
  103   {findall(Y,call(P,Y),YY)},
  104   uniform(YY,X).
 beta(+A:nonneg, +B:nonneg, -X:prob)// is det
Sample from beta distribution.
  108stub(3,beta,sample_Beta).
 zeta(+A:nonneg, -X:natural)// is det
Sample from zeta (hyperbolic or power law) distribution over natural numbers. NB: Must have A > 1.
  113stub(2,zeta,sample_Zeta).
 gamma(+A:nonneg, -X:float)// is det
Sample from gamma distribution with parameter A.
  117stub(2,gamma,sample_Gamma).
  118
  119
  120% ^ above use plrand samplers and need randstate
  121% ---------------------- DERIVED DISTRIBUTIONS ---------------------
  122% V below do not use state directly.
 gaussian(+Mean:float, +Var:nonneg, -X:float)// is det
gaussian :: \(float, nonneg) -> expr(float). Sample from Gaussian with given mean and variance.
  127gaussian(Mean, Var, X) --> normal(U), {X is Mean + Var*U}.
 inv_gamma(+A:nonneg, -X:float)// is det
Sample from inverse gamma distribution with parameter A.
  131inv_gamma(A,X)  --> gamma(A,Y), {X is 1/Y}.
 pareto(+A:nonneg, -X:float)// is det
Sample from pareto (power-law) distribution over non-negative reals.
  135pareto(A,X)    --> uniform01(Y), { X is (1-Y)**(-1/A) }.
 students_t(+V:nonneg, -X:float)// is det
Sample from student's t distribution with V degrees of freedom.
  139students_t(V,X)--> {V1 is V/2}, normal(Z), gamma(V1,Y), {X is Z*sqrt(V1/Y)}.
 pair(+F:dist(A), +G:dist(B), -X:pair(A,B))// is det
Sample a pair from two independent distributions.
  144pair(F,G,X-Y) --> call(F,X), call(G,Y).
 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).

  153mixture( Sources, Dist, X) -->
  154   discrete(Dist,I),
  155   {nth1(Sources,I,S)},
  156   call(S,X)