2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								:- module(clpbn, [{}/1,
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
										  clpbn_flag/2,
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
										  set_clpbn_flag/2,
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
										  clpbn_flag/3]).
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								:- use_module(library(atts)).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								:- use_module(library(lists)).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								:- use_module(library(terms)).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								:- op( 500, xfy, with).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								%
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								% avoid the overhead of using goal_expansion/2.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								%
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								:- multifile
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									user:term_expansion/2.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								:- dynamic
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									user:term_expansion/2.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2005-01-15 05:40:38 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								:- attribute key/1, dist/3, evidence/1, starter/0.
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								:- use_module('clpbn/bnt', [dump_as_bnt/2,
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
										    check_if_bnt_done/1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
										    ]).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-11-16 16:38:09 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								:- use_module('clpbn/vel', [vel/3,
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
										    check_if_vel_done/1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
										    ]).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2005-04-27 20:09:26 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								:- use_module('clpbn/gibbs', [gibbs/3,
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
										    check_if_gibbs_done/1
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
										    ]).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								:- use_module('clpbn/graphs', [
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
										    clpbn2graph/1
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
										    ]).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								:- use_module('clpbn/evidence', [
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									store_evidence/1,
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									incorporate_evidence/2
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									]).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2005-08-17 13:34:56 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								:- use_module('clpbn/utils', [
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
										    sort_vars_by_key/3
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
										    ]).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2005-08-15 14:16:38 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								:- dynamic solver/1,output/1,use/1.
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								solver(vel).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								%output(xbif(user_error)).
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-20 21:44:58 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								%output(gviz(user_error)).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								output(no).
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								clpbn_flag(Flag,Option) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									clpbn_flag(Flag, Option, Option).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								set_clpbn_flag(Flag,Option) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									clpbn_flag(Flag, _, Option).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								clpbn_flag(output,Before,After) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									retract(output(Before)),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									assert(output(After)).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								clpbn_flag(solver,Before,After) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									retract(solver(Before)),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									assert(solver(After)).
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								{Var = Key with Dist} :-
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									put_atts(El,[key(Key),dist(Domain,Table,Parents)]),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									extract_dist(Dist, Table, Parents, Domain),
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									add_evidence(Var,El).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2005-12-17 03:25:39 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								extract_dist(V, Tab, Inps, Domain) :- var(V), !,
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									V = p(Domain, Tab, Inps).
							 | 
						
					
						
							
								
									
										
										
										
											2005-09-09 17:22:59 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								extract_dist(p(Domain, trans(L), Parents), Tab, Inps, Domain) :- !,
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									compress_hmm_table(L, Parents, Tab, Inps).
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								extract_dist(p(Domain, Tab, Inps), Tab, Inps, Domain).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								extract_dist(p(Domain, Tab), Tab, [], Domain).
							 | 
						
					
						
							
								
									
										
										
										
											2005-09-09 17:22:59 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								compress_hmm_table(L, Parents, trans(Tab), Inps) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_rid_of_nuls(L,Parents,Tab,Inps).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								get_rid_of_nuls([], [], [], []).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								get_rid_of_nuls([*|L],[_|Parents],NL,NParents) :- !,
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_rid_of_nuls(L,Parents,NL,NParents).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								get_rid_of_nuls([Prob|L],[P|Parents],[Prob|NL],[P|NParents]) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_rid_of_nuls(L,Parents,NL,NParents).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								check_constraint(Constraint, _, _, Constraint) :- var(Constraint), !.
							 | 
						
					
						
							
								
									
										
										
										
											2004-11-16 16:38:09 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								check_constraint((A->D), _, _, (A->D)) :- var(A), !.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								check_constraint((([A|B].L)->D), Vars, NVars, (([A|B].NL)->D)) :- !,
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									check_cpt_input_vars(L, Vars, NVars, NL).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								check_constraint(Dist, _, _, Dist).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								check_cpt_input_vars([], _, _, []).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								check_cpt_input_vars([V|L], Vars, NVars, [NV|NL]) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									replace_var(Vars, V, NVars, NV),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									check_cpt_input_vars(L, Vars, NVars, NL).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								replace_var([], V, [], V).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								replace_var([V|_], V0, [NV|_], NV) :- V == V0, !.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								replace_var([_|Vars], V, [_|NVars], NV) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									replace_var(Vars, V, NVars, NV).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								add_evidence(V,NV) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									nonvar(V), !,
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									clpbn:put_atts(NV,evidence(V)).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								add_evidence(V,V).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								%
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								% called by top-level
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								% or by call_residue/2
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								%
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								project_attributes(GVars, AVars) :-
							 | 
						
					
						
							
								
									
										
										
										
											2005-12-05 17:16:12 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									AVars = [_|_],
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									solver(Solver),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									( GVars = [_|_] ; Solver = graphs), !,
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									sort_vars_by_key(AVars,SortedAVars,DiffVars),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_clpbn_vars(GVars,CLPBNGVars),
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									incorporate_evidence(SortedAVars, AllVars),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									write_out(Solver,CLPBNGVars, AllVars, DiffVars).
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								project_attributes(_, _).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								get_clpbn_vars([],[]).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								get_clpbn_vars([V|GVars],[V|CLPBNGVars]) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_atts(V, [key(_)]), !,
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_clpbn_vars(GVars,CLPBNGVars).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								get_clpbn_vars([_|GVars],CLPBNGVars) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_clpbn_vars(GVars,CLPBNGVars).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								write_out(vel, GVars, AVars, DiffVars) :-
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									vel(GVars, AVars, DiffVars).
							 | 
						
					
						
							
								
									
										
										
										
											2005-04-27 20:09:26 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								write_out(gibbs, GVars, AVars, DiffVars) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									gibbs(GVars, AVars, DiffVars).
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								write_out(bnt, GVars, AVars, _) :-
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									dump_as_bnt(GVars, AVars).
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								write_out(graphs, _, AVars, _) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									clpbn2graph(AVars).
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								get_bnode(Var, Goal) :-
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									get_atts(Var, [key(Key),dist(A,B,C)]),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									(C = [] -> X = tab(A,B) ; X = tab(A,B,C)),
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									dist_goal(X, Key, Goal0),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									include_evidence(Var, Goal0, Key, Goali),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									include_starter(Var, Goali, Key, Goal).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-11-16 16:38:09 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								include_evidence(Var, Goal0, Key, ((Key:-Ev),Goal0)) :-
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_atts(Var, [evidence(Ev)]), !.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								include_evidence(_, Goal0, _, Goal0).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-11-16 16:38:09 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								include_starter(Var, Goal0, Key, ((:-Key),Goal0)) :-
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_atts(Var, [starter]), !.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								include_starter(_, Goal0, _, Goal0).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								dist_goal(Dist, Key, (Key=NDist)) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									term_variables(Dist, DVars),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									process_vars(DVars, DKeys),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									my_copy_term(Dist,DVars, NDist,DKeys).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								my_copy_term(V, DVars, Key, DKeys) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									find_var(DVars, V, Key, DKeys).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								my_copy_term(A, _, A, _) :- atomic(A), !.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								my_copy_term(T, Vs, NT, Ks) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									T =.. [Na|As],
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									my_copy_terms(As, Vs, NAs, Ks),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									NT =.. [Na|NAs].
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								my_copy_terms([], _, [], _).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								my_copy_terms([A|As], Vs, [NA|NAs], Ks) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									my_copy_term(A, Vs, NA, Ks),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									my_copy_terms(As, Vs, NAs, Ks).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								find_var([V1|_], V, Key, [Key|_]) :- V1 == V, !.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								find_var([_|DVars], V, Key, [_|DKeys]) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									find_var(DVars, V, Key, DKeys).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								process_vars([], []).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								process_vars([V|Vs], [K|Ks]) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								        process_var(V, K),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									process_vars(Vs, Ks).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								process_var(V, K) :- get_atts(V, [key(K)]), !. 
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								% oops: this variable has no attributes.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								process_var(V, _) :- throw(error(instantiation_error,clpbn(attribute_goal(V)))).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								%
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								% unify a CLPBN variable with something. 
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								%
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								verify_attributes(Var, T, Goals) :-
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									get_atts(Var, [key(Key),dist(Domain,Table,Parents)]), !,
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									/* oops, someone trying to bind a clpbn constrained variable */
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									Goals = [],
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									bind_clpbn(T, Var, Key, Domain, Table, Parents).
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								verify_attributes(_, _, []).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								bind_clpbn(T, Var, Key, Domain, Table, Parents) :- var(T),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_atts(T, [key(Key1),dist(Doman1,Table1,Parents1)]), !,
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									bind_clpbns(Key, Domain, Table, Parents, Key1, Doman1, Table1, Parents1),
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-05 05:01:45 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									(
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									  get_atts(T, [evidence(Ev1)]) ->
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									    bind_evidence_from_extra_var(Ev1,Var)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									;
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									  get_atts(Var, [evidence(Ev)]) ->
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									    bind_evidence_from_extra_var(Ev,T)
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									;
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									  true).
							 | 
						
					
						
							
								
									
										
										
										
											2005-02-18 21:34:02 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								bind_clpbn(_, Var, _, _, _, _) :-
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									use(bnt),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									check_if_bnt_done(Var), !.
							 | 
						
					
						
							
								
									
										
										
										
											2005-02-18 21:34:02 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								bind_clpbn(_, Var, _, _, _, _) :-
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									use(vel),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									check_if_vel_done(Var), !.
							 | 
						
					
						
							
								
									
										
										
										
											2005-02-18 21:34:02 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								bind_clpbn(T, Var, Key0, _, _, _) :-
							 | 
						
					
						
							
								
									
										
										
										
											2005-04-20 04:02:30 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									get_atts(Var, [key(Key)]), !,
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									(
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									  Key = Key0 -> true
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									;
							 | 
						
					
						
							
								
									
										
										
										
											2005-02-18 21:34:02 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									  add_evidence(Var,T)
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
									).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								fresh_attvar(Var, NVar) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_atts(Var, LAtts),
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									put_atts(NVar, LAtts).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2005-02-18 21:34:02 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								% I will now allow two CLPBN variables to be bound together.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								%bind_clpbns(Key, Domain, Table, Parents, Key, Domain, Table, Parents).
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								bind_clpbns(Key, Domain, Table, Parents, Key1, Domain1, Table1, Parents1) :- 
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									Key == Key1, !,
							 | 
						
					
						
							
								
									
										
										
										
											2005-02-18 21:34:02 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									( Domain == Domain1, Table == Table1, Parents == Parents1 -> true ; throw(error(domain_error(bayesian_domain),bind_clpbns(var(Key, Domain, Table, Parents),var(Key1, Domain1, Table1, Parents1))))).
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								bind_clpbns(_, _, _, _, _, _, _, _) :-
							 | 
						
					
						
							
								
									
										
										
										
											2005-04-27 20:09:26 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									format(user_error, 'unification of two bayesian vars not supported~n', []).
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-05 05:01:45 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
								bind_evidence_from_extra_var(Ev1,Var) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									get_atts(Var, [evidence(Ev0)]),!,Ev0 = Ev1.
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								bind_evidence_from_extra_var(Ev1,Var) :-
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									put_atts(Var, [evidence(Ev1)]).
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								user:term_expansion((A :- {}), ( :- true )) :-	 !, % evidence
							 | 
						
					
						
							| 
								
							 | 
							
								
							 | 
							
								
							 | 
							
							
									prolog_load_context(module, M),
							 | 
						
					
						
							
								
									
										
										
										
											2004-12-16 06:07:07 +00:00
										 
									 
								 
							 | 
							
								
									
										
									
								
							 | 
							
								
							 | 
							
							
									store_evidence(M:A).
							 | 
						
					
						
							
								
									
										
										
										
											2004-07-15 16:23:44 +00:00
										 
									 
								 
							 | 
							
								
							 | 
							
								
							 | 
							
							
								
							 |