20:- use_module(library(phil)). 21:- if(current_predicate(use_rendering/1)). 22:- use_rendering(c3). 23:- use_rendering(lpad). 24:- endif. 25
26:- phil. 27
28:- set_hplp(verbosity, 1). 29
30
31bg([]).
32
33:- begin_in. 34advisedby(A,B):0.3:-
35 student(A),
36 professor(B),
37 project(A,C),
38 project(A,C),
39 hidden_1(A,B,C).
40advisedby(A,B):0.6 :-
41 student(A),
42 professor(B),
43 ta(C,A),
44 taughtby(C, B).
45hidden_1(A,B,C):0.2 :-
46 publication(P, A, C),
47 publication(P, B, C).
48:- end_in. 49
50
51fold(all, [ai]).
52
53output(advisedby/2).
54
55
56input(student/1).
57input(professor/1).
58input(project/2).
59input(publication/3).
60input(taughtby/2).
61input(ta/2).
62
63
64
66begin(model(ai)).
67student(harry).
68professor(ben).
69
70taughtby(c1, ben).
71taughtby(c2, ben).
72ta(c1, harry).
73ta(c2, harry).
74
75project(harry, pr1).
76project(harry, pr2).
77project(ben, pr1).
78project(ben, pr2).
79publication(p1, harry, pr1).
80publication(p2, harry, pr1).
81publication(p3, harry, pr2).
82publication(p4, harry, pr2).
83publication(p1, ben, pr1).
84publication(p2, ben, pr1).
85publication(p3, ben, pr2).
86publication(p4, ben, pr2).
87end(model(ai))
?-
inference_hplp(advisedby(harry, ben),ai,Prob)
. % Prob contains the probability that harry is advised by ben in the ai interpretation ?-inference_hplp(advisedby(harry, ben),ai,Prob,Circuit)
. % Same as the previous query but also returns in Circuit a term representing the arithmetic circuit */