13:- use_module(library(pita)). 14 15:- if(current_predicate(use_rendering/1)). 16:- use_rendering(graphviz). 17:- endif. 18graph(digraph([rankdir="LR"|G])):- 19 findall(edge(A -> B,[]), 20 clause(trusts(A,B,_,_),_), 21 G). 22 23:- pita. 24 25:- begin_lpad. 26 27:- action has/1. 28 29has(_)0.1. 30 31has(P) 0.4 :- trusts(P, Q), has(Q). 32 33 34 35trusts(2,1). 36trusts(3,1). 37trusts(3,2). 38trusts(4,1). 39trusts(4,3). 40:-end_lpad.
?-
prob(has(4),P)
. P = 0.192146176.?-
prob(has(4),has(2),P)
. P = 0.380740705882353.?-
prob(has(4),do(has(2)),P)
. P = 0.29964160000000006.*/