Did you know ... | Search Documentation: |
Pack plrand -- prolog/prob/crp_tagged.pl |
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.
old(X,ID)
, where X is an old value and C is the class index.
Operates in random state DCG.
of the action choosen.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.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).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.The following predicates are exported, but not or incorrectly documented.