1/* 2Existence uncertainty/unknown objects. 3This programs models a domain where the number of objects is uncertain. 4In particular, the number of objects follows a geometric distribution 5with parameter 0.7. 6We can ask what is the probability that the object number n exists. 7From 8Poole, David. "The independent choice logic and beyond." Probabilistic 9inductive logic programming. Springer Berlin Heidelberg, 2008. 222-243. 10*/ 11 12 13:- use_module(library(mcintyre)). 14 15:- if(current_predicate(use_rendering/1)). 16:- use_rendering(c3). 17:- endif. 18 19:- mc. 20 21:- begin_lpad. 22numObj(N, N) :- 23 \+ more(N). 24 25numObj(N, N2) :- 26 more(N), 27 N1 is N + 1, 28 numObj(N1, N2). 29 30more(_)0.3. 31 32obj(I):- 33 numObj(0,N), 34 between(1, N, I). 35 36:- end_lpad.
?-
mc_prob(obj(2),P). % what is the probability that object 2 exists? % expected result ~ 0.08992307692307693 ?-mc_prob(obj(2),P),bar(P,C). % what is the probability that object 2 exists? % expected result ~ 0.08992307692307693 ?-mc_prob(obj(5),P). % what is the probability that object 5 exists? % expected result ~ 0.002666 ?-mc_prob(obj(5),P),bar(P,C). % what is the probability that object 5 exists? % expected result ~ 0.002666 ?-mc_prob(numObj(0,2),P). % what is the probability that there are 2 objects? % expected result ~ 0.0656 ?-mc_prob(numObj(0,5),P). % what is the probability that there are 5 objects? % expected result ~ 0.0014 ?-mc_sample(obj(5),1000,P,[successes(T),failures(F)]). % take 1000 samples ofobj(5)?-mc_sample(obj(5),1000,P),bar(P,C). % take 1000 samples ofobj(5)?-mc_sample_arg(numObj(0,N),100,N,O),argbar(O,C). % take 100 samples of L in %findall(N,numObj(N),L)?-mc_sample_arg(obj(I),100,I,O),argbar(O,C). % take 100 samples of L in %findall(I,obj(I),L)??-mc_sample_arg(obj(I),100,I,Values). % take 100 samples of L in %findall(I,obj(I),L)*/