1/*
    2Flexible probabilities: variable probabilistic annotations.
    3The example models drawing a red ball from an urn with R red and G green balls,
    4where each ball is drawn with uniform probability from the urn.
    5From
    6De Raedt, Luc, and Angelika Kimmig. "Probabilistic (logic) programming concepts." Machine Learning (2015): 1-43.
    7*/
    8
    9:- use_module(library(pita)).   10
   11
   12:- pita.   13
   14:- begin_lpad.   15
   16red(Prob):Prob.
   17
   18draw_red(R, G):-
   19  Prob is R/(R + G),
   20  red(Prob).
   21
   22:- end_lpad.

?- prob(draw_red(3,1),P). % expected result 0.75 */