1/* 2Meta-calls/nested probability computations. 3Reasoning about the probabilities of queries within a probabilistic program. 4Can be used to implement simple forms of combining rules. 5In this example, max_true(G1,G2) succeeds with the success probability of 6the more likely argument. 7From 8De Raedt, Luc, and Angelika Kimmig. "Probabilistic (logic) programming concepts." Machine Learning (2015): 1-43. 9*/ 10 11 12 13:- use_module(library(pita)). 14 15:- pita. 16 17:- begin_lpad. 18 19 20 21max(A,B,A):- 22 A>=B. 23 24max(A,B,B):- 25 B>=A. 26 27p(P)P. 28 29max_true(G1, G2) :- 30 prob(G1, P1), 31 prob(G2, P2), 32 max(P1, P2, P), p(P). 33 34a0.5. 35b00.7. 36b10.7. 37c0.2. 38 39d :- 40 a, \+ b0. 41 42e :- 43 b1, c. 44:- end_lpad.
?-
prob(max_true(d,e),P)
. % expected result 0.15000000000000002*/