Did you know ... Search Documentation:
Pack plrand -- prolog/prob/crp.pl
PublicShow source

This module provides some building blocks for implementing a family of random processes related to Dirichlet processes, including Pitman Yor processe, the Chinese Restaurant process, and the stick breaking model (GEM). The Dirichlet processes takes a single concentration parameter, representated as dp(Conc), while the Pitman Yor process takes a concentration parameter and a discount parameter, representated as py(Conc,Disc).

gem_param   ---> dp(nonneg) ; py(nonneg,0--1).
gamma_prior ---> gamma(nonneg, nonneg).
beta_prior  ---> beta(nonneg, nonneg).
classes(A)  ---> classes(natural, list(nonneg), list(A)).
action(A)   ---> new ; old(A, class_idx).
action      ---> new ; old(class_idx).

rndstate  == plrand:state
class_idx == natural
prob      == 0--1

param_sampler == pred(+gem_param, -gem_param, +rndstate, -rndstate).

This may seems like a very low-level library for building CRPs, leaving a lot for the implemeenter to do, but this is intentional, to allow the implementer freedom to decide how to manage the states (terms of type classes(_)) of one or more CRPs, as well as the state of the random generator, in whatever way is most appropriate. See the the example implementation of test_crp.pl for one way to do this.

 crp_prob(+GEM:gem_param, +Classes:classes(A), +X:A, +PBase:prob, -Prob:prob) is det
Compute the probability Prob of observing X given a CRP with already observed values in Classes if the probability of drawing X from the base distribution is PBase.
 crp_sample(+GEM:gem_param, +Classes:classes(A), -A:action(A))// is det
crp_sample(+GEM:gem_param, +Classes:classes(A), -A:action(A))// is det
Sample a new value from CRP, Action A is either new, which means that the user should sample a new value from the base distribtion, or old(X,ID), where X is an old value and C is the class index. Operates in random state DCG. of the action choosen.
 crp_sample_obs(+GEM:gem_param, +Classes:classes(A), +X:A, +PBase:prob, -A:action, -P:prob)// is det
 crp_sample_obs(+GEM:gem_param, +Classes:classes(A), +X:A, +PBase:prob, -A:action)// is det
Sample action appropriate for observation of value X. PBase is the probability of X from the base distribution. Action A is new or old(N) where N is the class index. crp_sample_obs//6 additionally returns the probability of the observation, equivalent to calling crp_prob with X BEFORE calling crp_sample_obs//5. Operates in random state DCG.
 crp_sample_rm(+Classes:classes(A), +X:A, -N:class_idx)// is det
Sample appropriate class index N from which to remove value X. Operates in random state DCG.
 empty_classes(-Classes:classes(_)) is det
Unify Classes with an empty classes structure.
 dec_class(+N:class_idx, -C:natural, -X:A, +C1:classes(A), -C2:classes(A)) is det
Decrement count associated with class id N. C is the count after decrementing and X is the value associated with the Nth class.
 inc_class(+N:class_idx, +C1:classes(A), -C2:classes(A)) is det
Increment count associated with class N.
 remove_class(+N:class_idx, +C1:classes(A), -C2:classes(A)) is det
Removes Nth class.
 add_class(+X:A, -ID:class_idx, +C1:classes(A), -C2:classes(A)) is det
Add a class associated with value X. N is the index of the new class.
 dp_sampler_teh(+Prior:gamma_prior, +Counts:list(natural), -S:param_sampler) is det
Prepares a predicate for sampling the concentration parameter of a Dirichlet process. The sampler's gem_prior arguments must be of the form dp(_). Prior specifies the Gamma distribution prior for the concentration parameter, as gamma(a,b), where a is the shape parameter and b is the rate parameter (ie the inverse of the scale parameter).
 py_sampler_teh(+ConcPrior:gamma_prior, +DiscPr:beta_prior, +Counts:list(natural), -S:param_sampler) is det
Prepares a predicate for sampling the concentration and discount parameters of a Pitman-Yor process. The sampler's gem_prior arguments must be of the form py(_,_). See dp_sampler_teh/3 for tha description of the gamma_prior type. DiscPr is a Beta distribution prior for the concentration parameter.

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 crp_sample_obs(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6, Arg7)