/* Dirichlet process (DP), see https://en.wikipedia.org/wiki/Dirichlet_process Samples are drawn from a base distribution. New samples have a nonzero probability of being equal to already sampled values. The process depends on a parameter alpha (concentration parameter): with alpha->0, a single value is sampled, with alpha->infinite the distribution is equal to the base distribution. In this example the base distribution is a Gaussian with mean 0 and variance 1, as in https://en.wikipedia.org/wiki/Dirichlet_process#/media/File:Dirichlet_process_draws.svg To model the process, this example uses a stick breaking process: to sample a value, a sample beta_1 is taken from Beta(1,alpha) and a coin with heads probability beta_1 is flipped. If the coin lands heads, a sample from the base distribution is taken and returned. Otherwise, a sample beta_2 is taken again from Beta(1,alpha) and a coin is flipped. This procedure is repeated until a heads is obtained, the index of i beta_i is the index of the value to be returned. The example queries show both the distribution of indexes and values of the DP. Moreover, they show the distribution of unique indexes as in http://www.robots.ox.ac.uk/~fwood/anglican/examples/viewer/?worksheet=nonparametrics/dp-mixture-model */ /** ?- hist(200,100,G). % show the distribution of indexes with concentration parameter 10. ?- hist_val(200,100,G). % show the distribution of values with concentration parameter 10. Should look % like row 2 of https://en.wikipedia.org/wiki/Dirichlet_process#/media/File:Dirichlet_process_draws.svg ?- hist_repeated_indexes(100,40,G). % show the distribution of unique indexes in 100 samples with concentration parameter 10. */ :- use_module(library(mcintyre)). :- if(current_predicate(use_rendering/1)). :- use_rendering(c3). :- endif. :- mc. :- begin_lpad. % dp_n_values(N0,N,Alpha,L) % returns in L a list of N-N0 samples from the DP with concentration parameter % Alpha dp_n_values(N,N,_Alpha,[]):-!. dp_n_values(N0,N,Alpha,[[V]-1|Vs]):- N0