Rework a bit the examples
This commit is contained in:
parent
91dbd60ad4
commit
bafd7320a5
@ -1,3 +1,8 @@
|
||||
/*
|
||||
Model from the paper "First-order
|
||||
probabilistic inference"
|
||||
*/
|
||||
|
||||
:- use_module(library(pfl)).
|
||||
|
||||
:- set_solver(hve).
|
||||
@ -11,14 +16,14 @@
|
||||
%:- set_solver(lkc).
|
||||
%:- set_solver(lbp).
|
||||
|
||||
:- multifile people/2.
|
||||
:- multifile person/2.
|
||||
:- multifile ev/1.
|
||||
|
||||
people(joe,nyc).
|
||||
people(p2, nyc).
|
||||
people(p3, nyc).
|
||||
people(p4, nyc).
|
||||
people(p5, nyc).
|
||||
person(joe,nyc).
|
||||
person(p2, nyc).
|
||||
person(p3, nyc).
|
||||
person(p4, nyc).
|
||||
person(p5, nyc).
|
||||
|
||||
ev(descn(p2, fits)).
|
||||
ev(descn(p3, fits)).
|
||||
@ -26,41 +31,41 @@ ev(descn(p4, fits)).
|
||||
ev(descn(p5, fits)).
|
||||
|
||||
bayes city_conservativeness(C)::[high,low] ;
|
||||
cons_table ;
|
||||
[people(_,C)].
|
||||
cons_table ;
|
||||
[person(_,C)].
|
||||
|
||||
bayes gender(P)::[male,female] ;
|
||||
gender_table ;
|
||||
[people(P,_)].
|
||||
gender_table ;
|
||||
[person(P,_)].
|
||||
|
||||
bayes hair_color(P)::[dark,bright], city_conservativeness(C) ;
|
||||
hair_color_table ;
|
||||
[people(P,C)].
|
||||
hair_color_table ;
|
||||
[person(P,C)].
|
||||
|
||||
bayes car_color(P)::[dark,bright], hair_color(P) ;
|
||||
car_color_table ;
|
||||
[people(P,_)].
|
||||
car_color_table ;
|
||||
[person(P,_)].
|
||||
|
||||
bayes height(P)::[tall,short], gender(P) ;
|
||||
height_table ;
|
||||
[people(P,_)].
|
||||
height_table ;
|
||||
[person(P,_)].
|
||||
|
||||
bayes shoe_size(P)::[big,small], height(P) ;
|
||||
shoe_size_table ;
|
||||
[people(P,_)].
|
||||
shoe_size_table ;
|
||||
[person(P,_)].
|
||||
|
||||
bayes guilty(P)::[y,n] ;
|
||||
guilty_table ;
|
||||
[people(P,_)].
|
||||
guilty_table ;
|
||||
[person(P,_)].
|
||||
|
||||
bayes descn(P)::[fits,dont_fit], car_color(P),
|
||||
hair_color(P), height(P), guilty(P) ;
|
||||
descn_table ;
|
||||
[people(P,_)].
|
||||
hair_color(P), height(P), guilty(P) ;
|
||||
descn_table ;
|
||||
[person(P,_)].
|
||||
|
||||
bayes witness(C), descn(Joe), descn(P2) ;
|
||||
witness_table ;
|
||||
[people(_,C), Joe=joe, P2=p2].
|
||||
witness_table ;
|
||||
[person(_,C), Joe=joe, P2=p2].
|
||||
|
||||
|
||||
cons_table(
|
||||
@ -109,20 +114,20 @@ witness_table(
|
||||
|
||||
|
||||
runall(G, Wrapper) :-
|
||||
findall(G, Wrapper, L),
|
||||
execute_all(L).
|
||||
findall(G, Wrapper, L),
|
||||
execute_all(L).
|
||||
|
||||
|
||||
execute_all([]).
|
||||
execute_all(G.L) :-
|
||||
call(G),
|
||||
execute_all(L).
|
||||
call(G),
|
||||
execute_all(L).
|
||||
|
||||
|
||||
is_joe_guilty(Guilty) :-
|
||||
witness(nyc, t),
|
||||
runall(X, ev(X)),
|
||||
guilty(joe, Guilty).
|
||||
witness(nyc, t),
|
||||
runall(X, ev(X)),
|
||||
guilty(joe, Guilty).
|
||||
|
||||
|
||||
% ?- is_joe_guilty(Guilty).
|
||||
|
@ -1,3 +1,8 @@
|
||||
/*
|
||||
Model from the paper "Lifted Probabilistic
|
||||
Inference with Counting Formulas"
|
||||
*/
|
||||
|
||||
:- use_module(library(pfl)).
|
||||
|
||||
:- set_solver(hve).
|
||||
@ -10,31 +15,31 @@
|
||||
%:- set_solver(lkc).
|
||||
%:- set_solver(lbp).
|
||||
|
||||
:- multifile c/2.
|
||||
:- multifile reg/2.
|
||||
|
||||
c(p1,w1).
|
||||
c(p1,w2).
|
||||
c(p1,w3).
|
||||
c(p2,w1).
|
||||
c(p2,w2).
|
||||
c(p2,w3).
|
||||
c(p3,w1).
|
||||
c(p3,w2).
|
||||
c(p3,w3).
|
||||
c(p4,w1).
|
||||
c(p4,w2).
|
||||
c(p4,w3).
|
||||
c(p5,w1).
|
||||
c(p5,w2).
|
||||
c(p5,w3).
|
||||
reg(p1,w1).
|
||||
reg(p1,w2).
|
||||
reg(p1,w3).
|
||||
reg(p2,w1).
|
||||
reg(p2,w2).
|
||||
reg(p2,w3).
|
||||
reg(p3,w1).
|
||||
reg(p3,w2).
|
||||
reg(p3,w3).
|
||||
reg(p4,w1).
|
||||
reg(p4,w2).
|
||||
reg(p4,w3).
|
||||
reg(p5,w1).
|
||||
reg(p5,w2).
|
||||
reg(p5,w3).
|
||||
|
||||
markov attends(P), hot(W) ;
|
||||
[0.2, 0.8, 0.8, 0.8] ;
|
||||
[c(P,W)].
|
||||
[0.2, 0.8, 0.8, 0.8] ;
|
||||
[reg(P,W)].
|
||||
|
||||
markov attends(P), series ;
|
||||
[0.501, 0.499, 0.499, 0.499] ;
|
||||
[c(P,_)].
|
||||
[0.501, 0.499, 0.499, 0.499] ;
|
||||
[reg(P,_)].
|
||||
|
||||
?- series(X).
|
||||
% ?- series(X).
|
||||
|
||||
|
@ -1,3 +1,8 @@
|
||||
/*
|
||||
Model from the paper "Lifted First-Order
|
||||
Belief Propagation"
|
||||
*/
|
||||
|
||||
:- use_module(library(pfl)).
|
||||
|
||||
:- set_solver(hve).
|
||||
@ -11,28 +16,29 @@
|
||||
%:- set_solver(lkc).
|
||||
%:- set_solver(lbp).
|
||||
|
||||
:- multifile people/1.
|
||||
:- multifile person/1.
|
||||
|
||||
people @ 5.
|
||||
person @ 5.
|
||||
|
||||
people(X,Y) :-
|
||||
people(X),
|
||||
people(Y),
|
||||
X \== Y.
|
||||
person(X,Y) :-
|
||||
person(X),
|
||||
person(Y)
|
||||
% ,X \== Y
|
||||
.
|
||||
|
||||
markov smokes(X) ; [1.0, 4.0552]; [people(X)].
|
||||
markov smokes(X) ; [1.0, 4.0552]; [person(X)].
|
||||
|
||||
markov cancer(X) ; [1.0, 9.9742]; [people(X)].
|
||||
markov cancer(X) ; [1.0, 9.9742]; [person(X)].
|
||||
|
||||
markov friends(X,Y) ; [1.0, 99.48432] ; [people(X,Y)].
|
||||
markov friends(X,Y) ; [1.0, 99.48432] ; [person(X,Y)].
|
||||
|
||||
markov smokes(X), cancer(X) ;
|
||||
[4.48169, 4.48169, 1.0, 4.48169] ;
|
||||
[people(X)].
|
||||
[4.48169, 4.48169, 1.0, 4.48169] ;
|
||||
[person(X)].
|
||||
|
||||
markov friends(X,Y), smokes(X), smokes(Y) ;
|
||||
[3.004166, 3.004166, 3.004166, 3.004166, 3.004166, 1.0, 1.0, 3.004166] ;
|
||||
[people(X,Y)].
|
||||
[3.004166, 3.004166, 3.004166, 3.004166, 3.004166, 1.0, 1.0, 3.004166] ;
|
||||
[person(X,Y)].
|
||||
|
||||
% ?- friends(p1,p2,X).
|
||||
|
||||
|
@ -1,3 +1,8 @@
|
||||
/*
|
||||
Model from the paper "Lifted Inference Seen
|
||||
from the Other Side: The Tractable Features"
|
||||
*/
|
||||
|
||||
:- use_module(library(pfl)).
|
||||
|
||||
:- set_solver(hve).
|
||||
@ -11,28 +16,29 @@
|
||||
%:- set_solver(lkc).
|
||||
%:- set_solver(lbp).
|
||||
|
||||
:- multifile people/1.
|
||||
:- multifile person/1.
|
||||
|
||||
people @ 5.
|
||||
person @ 5.
|
||||
|
||||
people(X,Y) :-
|
||||
people(X),
|
||||
people(Y).
|
||||
% X \== Y.
|
||||
person(X,Y) :-
|
||||
person(X),
|
||||
person(Y)
|
||||
% ,X \== Y
|
||||
.
|
||||
|
||||
markov smokes(X) ; [1.0, 4.0552]; [people(X)].
|
||||
markov smokes(X) ; [1.0, 4.0552]; [person(X)].
|
||||
|
||||
markov asthma(X) ; [1.0, 9.9742] ; [people(X)].
|
||||
markov asthma(X) ; [1.0, 9.9742] ; [person(X)].
|
||||
|
||||
markov friends(X,Y) ; [1.0, 99.48432] ; [people(X,Y)].
|
||||
markov friends(X,Y) ; [1.0, 99.48432] ; [person(X,Y)].
|
||||
|
||||
markov asthma(X), smokes(X) ;
|
||||
[4.48169, 4.48169, 1.0, 4.48169] ;
|
||||
[people(X)].
|
||||
[4.48169, 4.48169, 1.0, 4.48169] ;
|
||||
[person(X)].
|
||||
|
||||
markov asthma(X), friends(X,Y), smokes(Y) ;
|
||||
[3.004166, 3.004166, 3.004166, 3.004166, 3.004166, 1.0, 1.0, 3.004166] ;
|
||||
[people(X,Y)].
|
||||
[3.004166, 3.004166, 3.004166, 3.004166, 3.004166, 1.0, 1.0, 3.004166] ;
|
||||
[person(X,Y)].
|
||||
|
||||
% ?- smokes(p1,t), smokes(p2,t), friends(p1,p2,X).
|
||||
|
||||
|
@ -1,3 +1,8 @@
|
||||
/*
|
||||
Model from the paper "Lifted Probabilistic
|
||||
Inference with Counting Formulas"
|
||||
*/
|
||||
|
||||
:- use_module(library(pfl)).
|
||||
|
||||
:- set_solver(hve).
|
||||
@ -11,23 +16,23 @@
|
||||
%:- set_solver(lkc).
|
||||
%:- set_solver(lbp).
|
||||
|
||||
:- multifile people/1.
|
||||
:- multifile person/1.
|
||||
|
||||
people @ 5.
|
||||
person @ 5.
|
||||
|
||||
markov attends(P), attr1 ; [0.7, 0.3, 0.3, 0.3] ; [people(P)].
|
||||
markov attends(P), attr1 ; [0.7, 0.3, 0.3, 0.3] ; [person(P)].
|
||||
|
||||
markov attends(P), attr2 ; [0.7, 0.3, 0.3, 0.3] ; [people(P)].
|
||||
markov attends(P), attr2 ; [0.7, 0.3, 0.3, 0.3] ; [person(P)].
|
||||
|
||||
markov attends(P), attr3 ; [0.7, 0.3, 0.3, 0.3] ; [people(P)].
|
||||
markov attends(P), attr3 ; [0.7, 0.3, 0.3, 0.3] ; [person(P)].
|
||||
|
||||
markov attends(P), attr4 ; [0.7, 0.3, 0.3, 0.3] ; [people(P)].
|
||||
markov attends(P), attr4 ; [0.7, 0.3, 0.3, 0.3] ; [person(P)].
|
||||
|
||||
markov attends(P), attr5 ; [0.7, 0.3, 0.3, 0.3] ; [people(P)].
|
||||
markov attends(P), attr5 ; [0.7, 0.3, 0.3, 0.3] ; [person(P)].
|
||||
|
||||
markov attends(P), attr6 ; [0.7, 0.3, 0.3, 0.3] ; [people(P)].
|
||||
markov attends(P), attr6 ; [0.7, 0.3, 0.3, 0.3] ; [person(P)].
|
||||
|
||||
markov attends(P), series ; [0.501, 0.499, 0.499, 0.499] ; [people(P)].
|
||||
markov attends(P), series ; [0.501, 0.499, 0.499, 0.499] ; [person(P)].
|
||||
|
||||
% ?- series(X).
|
||||
|
||||
|
Reference in New Issue
Block a user