1/*
    2Computing the probability of a path between two nodes in a probabilistic graph.
    3Each edge has a probability of being present.
    4From
    5L. De Raedt, A. Kimmig, and H. Toivonen. ProbLog: A probabilistic Prolog and
    6its application in link discovery. In International Joint Conference on
    7Artificial Intelligence, pages 2462-2467, 2007.
    8*/
    9:- use_module(library(pita)).   10
   11:- if(current_predicate(use_rendering/1)).   12:- use_rendering(c3).   13:- use_rendering(graphviz).   14:- use_rendering(table,[header(['Multivalued variable index','Rule index','Grounding substitution'])]).   15:- endif.   16
   17:- pita.   18
   19:- begin_lpad.   20:- set_pita(depth_bound,true).   21
   22% path(X,Y) is true if there is a path between nodes X and Y
   23% edge(a,b) indicates that there is an edge between a and b
   24
   25path(X,X).
   26% there is surely a path between a node and itself
   27
   28path(X,Y):-
   29  path(X,Z),edge(Z,Y).
   30% there is surely a path between X and Y if there is another node Z such that
   31% there is an edge between X and Z and there is a path between Z and Y
   32
   33edge(a,b):0.2.
   34% there is an edge between a and b with probability 0.2
   35edge(b,e):0.5.
   36edge(a,c):0.3.
   37edge(c,d):0.4.
   38edge(d,e):0.4.
   39edge(a,e):0.1.
   40
   41:- end_lpad.   42
   43graph(digraph(G)):-
   44    findall(edge((A -> B),[label=P]),
   45      clause(edge(A,B,_,_),(get_var_n(_,_,_,[P|_],_),_)),
   46      G).

?- prob(path(a,e),Prob). % what is the probability that a and e are connected? % expected result 0.22888 ?- prob_bar(path(a,e),Prob). % what is the probability that a and e are connected? % expected result 0.22888 ?- graph(G). % shows the probabilistic graph

?- bdd_dot_string(path(a,e),BDD,Var). % What is the BDD for query path(a,e)? % A solid edge indicates a 1-child, a dashed edge indicates a 0-child and % a dotted % edge indicates a negated 0-child. % The table Var contains the associations between the rule groundings and the % multivalued variables.

*/