Rework the learning examples
This commit is contained in:
@@ -1,21 +1,31 @@
|
||||
% learn distribution for school database.
|
||||
/* Learn distribution for professor database. */
|
||||
|
||||
:- use_module(library(pfl)).
|
||||
|
||||
:- use_module(library(clpbn/learning/em)).
|
||||
|
||||
%:- clpbn:set_clpbn_flag(em_solver,gibbs).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,jt).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,hve).
|
||||
:- clpbn:set_clpbn_flag(em_solver,ve).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,bp).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,bdd).
|
||||
|
||||
bayes abi(K)::[h,m,l] ; abi_table ; [professor(K)].
|
||||
|
||||
bayes pop(K)::[h,m,l], abi(K) ; pop_table ; [professor(K)].
|
||||
|
||||
abi_table([0.3,0.3,0.4]).
|
||||
abi_table([0.3, 0.3, 0.4]).
|
||||
|
||||
pop_table([0.3,0.3,0.4,0.3,0.3,0.4,0.3,0.3,0.4]).
|
||||
pop_table([0.3, 0.3, 0.4, 0.3, 0.3, 0.4, 0.3, 0.3, 0.4]).
|
||||
|
||||
goal_list([/*abi(p0,h),
|
||||
goal_list([
|
||||
/*
|
||||
abi(p0,h),
|
||||
abi(p1,m),
|
||||
abi(p2,m),
|
||||
abi(p3,m),*/
|
||||
abi(p3,m),
|
||||
*/
|
||||
abi(p4,l),
|
||||
pop(p5,h),
|
||||
abi(p5,_),
|
||||
@@ -32,13 +42,6 @@ professor(p6).
|
||||
professor(p7).
|
||||
professor(p8).
|
||||
|
||||
%:- clpbn:set_clpbn_flag(em_solver,gibbs).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,jt).
|
||||
:- clpbn:set_clpbn_flag(em_solver,hve).
|
||||
:- clpbn:set_clpbn_flag(em_solver,ve).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,bp).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,bdd).
|
||||
|
||||
timed_main :-
|
||||
statistics(runtime, _),
|
||||
main(Lik),
|
||||
@@ -47,13 +50,5 @@ timed_main :-
|
||||
|
||||
main(Lik) :-
|
||||
goal_list(L),
|
||||
% run_queries(L),
|
||||
em(L,0.01,10,_,Lik).
|
||||
|
||||
run_queries([]).
|
||||
run_queries(Q.L) :-
|
||||
call(Q),
|
||||
run_queries(L).
|
||||
|
||||
|
||||
em(L,0.01,10,_,Lik).
|
||||
|
||||
|
File diff suppressed because one or more lines are too long
@@ -1,9 +1,16 @@
|
||||
% learn distribution for school database.
|
||||
/* Learn distribution for a sprinkler database. */
|
||||
|
||||
:- ['../sprinkler.pfl'].
|
||||
|
||||
:- use_module(library(clpbn/learning/em)).
|
||||
|
||||
%:- clpbn:set_clpbn_flag(em_solver,gibbs).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,jt).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,hve).
|
||||
:- clpbn:set_clpbn_flag(em_solver,bdd).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,bp).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,ve).
|
||||
|
||||
data(t,t,t,t).
|
||||
data(_,t,_,t).
|
||||
data(t,t,f,f).
|
||||
@@ -18,12 +25,7 @@ data(t,t,_,f).
|
||||
data(t,f,f,t).
|
||||
data(t,f,t,t).
|
||||
|
||||
%:- clpbn:set_clpbn_flag(em_solver,gibbs).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,jt).
|
||||
:- clpbn:set_clpbn_flag(em_solver,hve).
|
||||
:- clpbn:set_clpbn_flag(em_solver,bdd).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,bp).
|
||||
%:- clpbn:set_clpbn_flag(em_solver,ve).
|
||||
:- dynamic id/1.
|
||||
|
||||
timed_main :-
|
||||
statistics(runtime, _),
|
||||
@@ -33,19 +35,16 @@ timed_main :-
|
||||
|
||||
main(Lik) :-
|
||||
findall(X,scan_data(X),L),
|
||||
em(L,0.01,10,_,Lik).
|
||||
em(L,0.01,10,_,Lik).
|
||||
|
||||
scan_data(I:[wet_grass(W),sprinkler(S),rain(R),cloudy(C)]) :-
|
||||
data(W, S, R, C),
|
||||
new_id(I).
|
||||
|
||||
:- dynamic id/1.
|
||||
|
||||
new_id(I) :-
|
||||
retract(id(I)),
|
||||
I1 is I+1,
|
||||
assert(id(I1)).
|
||||
retract(id(I)),
|
||||
I1 is I+1,
|
||||
assert(id(I1)).
|
||||
|
||||
id(0).
|
||||
|
||||
|
||||
|
Reference in New Issue
Block a user