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(pita)).   14
   15:- if(current_predicate(use_rendering/1)).   16:- use_rendering(c3).   17:- endif.   18
   19:- pita.   20
   21:- set_pita(depth_bound,true).   22:- set_pita(depth,5).   23
   24:- begin_lpad.   25numObj(N, N) :-
   26  \+ more(N).
   27
   28numObj(N, N2) :-
   29  more(N),
   30  N1 is N + 1,
   31  numObj(N1, N2).
   32
   33more(_):0.3.
   34
   35obj(I):-
   36 numObj(0,N),
   37 between(1, N, I).
   38
   39:- end_lpad.

?- prob(obj(2),P). what is the probability that object 2 exists? % expected result 0.08189999999999999 ?- prob(obj(2),P),bar(P,C). what is the probability that object 2 exists? % expected result 0.08189999999999999 ?- prob(numObj(0,2),P). % what is the probability that there are 2 objects? % expected result 0.063

*/