1/*
    2Posterior estimation in Bayesian models.
    3We are trying to estimate the true value of a Gaussian distributed random
    4variable, given some observed data. The variance is known (2) and we
    5suppose that the mean has a Gaussian distribution with mean 1 and variance
    65. We take different measurement (e.g. at different times), indexed
    7with an integer.
    8Given that we observe 9 and 8 at indexes 1 and 2, how does the distribution
    9of the random variable (value at index 0) changes with respect to the case of
   10no observations?
   11From
   12http://www.robots.ox.ac.uk/~fwood/anglican/examples/viewer/?worksheet=gaussian-posteriors
   13*/
   14:- use_module(library(mcintyre)).   15
   16:- if(current_predicate(use_rendering/1)).   17:- use_rendering(c3).   18:- endif.   19:- mc.   20:- begin_lpad.   21
   22val(I,X) :-
   23  mean(M),
   24  val(I,M,X).
   25% at time I we see X sampled from a Gaussian with mean M and variamce 2.0
   26
   27mean(M): gaussian(M,1.0, 5.0).
   28% Gaussian distribution of the mean of the Gaussian of the variable
   29
   30val(_,M,X): gaussian(X,M, 2.0).
   31% Gaussian distribution of the variable
   32
   33
   34:- end_lpad.   35
   36hist_uncond(Samples,NBins,Chart):-
   37  mc_sample_arg(val(0,X),Samples,X,L0),
   38  histogram(L0,Chart,[nbins(NBins)]).
   39% plot an histogram of the density of the random variable before any
   40% observations by taking Samples samples and by dividing the domain
   41% in NBins bins
   42
   43dens_lw(Samples,NBins,Chart):-
   44  mc_sample_arg(val(0,Y),Samples,Y,L0),
   45  mc_lw_sample_arg(val(0,X),(val(1,9),val(2,8)),Samples,X,L),
   46  densities(L0,L,Chart,[nbins(NBins)]).
   47% plot the densities of the random variable before and after
   48% observing 9 and 8 by taking Samples samples using likelihood weighting
   49% and by dividing the domain
   50% in NBins bins
   51
   52dens_part(Samples,NBins,Chart):-
   53  mc_sample_arg(val(0,Y),Samples,Y,L0),
   54  mc_particle_sample_arg(val(0,X),[val(1,9),val(2,8)],Samples,X,L),
   55  densities(L0,L,Chart,[nbins(NBins)]).
   56% plot the densities of the random variable before and after
   57% observing 9 and 8 by taking Samples samples using particle filtering
   58% and by dividing the domain
   59% in NBins bins

?- dens_lw(1000,40,G). % plot the densities of the random variable before and after % observing 9 and 8 using likelihood weighting ?- dens_part(1000,40,G). % plot the densities of the random variable before and after % observing 9 and 8 using particle filtering ?- hist_uncond(10000,40,G). % plot an histogram of the density of the random variable before any % observations ?- mc_lw_expectation(val(0,X),(val(1,9),val(2,8)),1000,X,E). % E = 7.166960047178755 ?- mc_expectation(val(0,X),10000,X,E). % E = 0.9698875384639362.

*/