fix call to ground solvers, both using clpbn style and horus style.

This commit is contained in:
Costa Vitor 2012-08-07 18:33:51 -05:00
parent 51b47d14da
commit e2fa3a3b8a
3 changed files with 100 additions and 37 deletions

View File

@ -16,6 +16,7 @@
op( 500, xfy, with)]). op( 500, xfy, with)]).
:- use_module(library(atts)). :- use_module(library(atts)).
:- use_module(library(bhash)).
:- use_module(library(lists)). :- use_module(library(lists)).
:- use_module(library(terms)). :- use_module(library(terms)).
@ -232,7 +233,7 @@ project_attributes(GVars, _AVars0) :-
use_parfactors(on), use_parfactors(on),
clpbn_flag(solver, Solver), Solver \= fove, !, clpbn_flag(solver, Solver), Solver \= fove, !,
generate_network(GVars, GKeys, Keys, Factors, Evidence), generate_network(GVars, GKeys, Keys, Factors, Evidence),
call_ground_solver(Solver, GVars, GKeys, Keys, Factors, Evidence, _Avars0). call_ground_solver(Solver, GVars, GKeys, Keys, Factors, Evidence).
project_attributes(GVars, AVars) :- project_attributes(GVars, AVars) :-
suppress_attribute_display(false), suppress_attribute_display(false),
AVars = [_|_], AVars = [_|_],
@ -314,8 +315,62 @@ write_out(fove, GVars, AVars, DiffVars) :-
call_horus_lifted_solver(GVars, AVars, DiffVars). call_horus_lifted_solver(GVars, AVars, DiffVars).
% call a solver with keys, not actual variables % call a solver with keys, not actual variables
call_ground_solver(bp, GVars, GoalKeys, Keys, Factors, Evidence, Answ) :- call_ground_solver(bp, GVars, GoalKeys, Keys, Factors, Evidence) :- !,
call_horus_ground_solver(GVars, GoalKeys, Keys, Factors, Evidence, Answ). call_horus_ground_solver(GVars, GoalKeys, Keys, Factors, Evidence, _Answ).
call_ground_solver(Solver, GVars, _GoalKeys, Keys, Factors, Evidence) :-
% traditional solver
b_hash_new(Hash0),
gvars_in_hash(GVars,Hash0, HashI),
keys_to_vars(Keys, AllVars, HashI, Hash1),
evidence_to_vars(Evidence, _EVars, Hash1, Hash),
factors_to_dists(Factors, Hash),
% evidence
retract(use_parfactors(on)),
write_out(Solver, [GVars], AllVars, _),
assert(use_parfactors(on)).
%
% convert a PFL network (without constriants)
% into CLP(BN) for evaluation
%
gvars_in_hash([V|GVars],Hash0, Hash) :-
get_atts(V, [key(K)]),
b_hash_insert(Hash0, K, V, HashI),
gvars_in_hash(GVars,HashI, Hash).
gvars_in_hash([],Hash, Hash).
keys_to_vars([], [], Hash, Hash).
keys_to_vars([K|Keys], [V|Vs], Hash0, Hash) :-
b_hash_lookup(K, V, Hash0), !,
keys_to_vars(Keys, Vs, Hash0, Hash).
keys_to_vars([K|Keys], [V|Vs],Hash0, Hash) :-
b_hash_insert(Hash0, K, V, HashI),
keys_to_vars(Keys, Vs, HashI, Hash).
evidence_to_vars([], [], Hash, Hash).
evidence_to_vars([K=E|Keys], [V|Vs], Hash0, Hash) :-
b_hash_lookup(K, V, Hash0), !,
clpbn:put_atts(V,[evidence(E)]),
evidence_to_vars(Keys, Vs, Hash0, Hash).
evidence_to_vars([K=E|Keys], [V|Vs],Hash0, Hash) :-
b_hash_insert(Hash0, K, V, HashI),
clpbn:put_atts(V,[evidence(E)]),
evidence_to_vars(Keys, Vs, HashI, Hash).
factors_to_dists([], _Hash).
factors_to_dists([f(bayes,_Id,Ks,CPT)|Factors], Hash) :-
keys_to_vars(Ks, Hash, [V|Parents]),
Ks =[Key|_],
pfl:skolem(Key, Domain),
dist(p(Domain,CPT,Parents), DistInfo, Key, Parents),
put_atts(V,[dist(DistInfo,Parents)]),
factors_to_dists(Factors, Hash).
keys_to_vars([], _Hash, []).
keys_to_vars([K|Ks], Hash, [V|Vs]) :-
b_hash_lookup(K,V,Hash),
keys_to_vars(Ks, Hash, Vs).
get_bnode(Var, Goal) :- get_bnode(Var, Goal) :-

View File

@ -58,20 +58,21 @@ call_horus_ground_solver(QueryVars, QueryKeys, AllKeys, Factors, Evidence, Outpu
call_horus_ground_solver_for_probabilities(QueryKeys, _AllKeys, Factors, Evidence, Solutions) :- call_horus_ground_solver_for_probabilities(QueryKeys, _AllKeys, Factors, Evidence, Solutions) :-
attributes:all_attvars(AVars), attributes:all_attvars(AVars),
keys(AVars, AllKeys), keys(AVars, AllKeys),
writeln(AllKeys),
b_hash_new(Hash0), b_hash_new(Hash0),
keys_to_ids(AllKeys, 0, Hash0, Hash), keys_to_ids(AllKeys, 0, Id1, Hash0, Hash1),
get_factors_type(Factors, Type), get_factors_type(Factors, Type),
evidence_to_ids(Evidence, Hash, EvidenceIds), evidence_to_ids(Evidence, Hash1, Hash2, Id1, Id2, EvidenceIds),
factors_to_ids(Factors, Hash, FactorIds), factors_to_ids(Factors, Hash2, Hash, Id2, _, FactorIds),
writeln(queryKeys:QueryKeys), writeln(''), writeln(queryKeys:QueryKeys), writeln(''),
writeln(type:Type), writeln(''), writeln(type:Type), writeln(''),
writeln(allKeys:AllKeys), writeln(''), writeln(allKeys:AllKeys), writeln(''),
sort(AllKeys,SKeys),writeln(allSortedKeys:SKeys), writeln(''), sort(AllKeys,SKeys),writeln(allSortedKeys:SKeys), writeln(''),
keys_to_ids(SKeys, 0, Hash0, Hash), keys_to_ids(SKeys, 0, _, Hash0, Hash),
writeln(factors:Factors), writeln(''), % writeln(factors:Factors), writeln(''),
writeln(factorIds:FactorIds), writeln(''), % writeln(factorIds:FactorIds), writeln(''),
writeln(evidence:Evidence), writeln(''), % writeln(evidence:Evidence), writeln(''),
writeln(evidenceIds:EvidenceIds), writeln(''), % writeln(evidenceIds:EvidenceIds), writeln(''),
cpp_create_ground_network(Type, FactorIds, EvidenceIds, Network), cpp_create_ground_network(Type, FactorIds, EvidenceIds, Network),
get_vars_information(AllKeys, StatesNames), get_vars_information(AllKeys, StatesNames),
terms_to_atoms(AllKeys, KeysAtoms), terms_to_atoms(AllKeys, KeysAtoms),
@ -91,51 +92,59 @@ keys([_V|AVars], AllKeys) :-
run_solver(ground(Network,Hash), QueryKeys, Solutions) :- run_solver(ground(Network,Hash), QueryKeys, Solutions) :-
%get_dists_parameters(DistIds, DistsParams), %get_dists_parameters(DistIds, DistsParams),
%cpp_set_factors_params(Network, DistsParams), %cpp_set_factors_params(Network, DistsParams),
list_of_keys_to_ids(QueryKeys, Hash, QueryIds), list_of_keys_to_ids(QueryKeys, Hash, _, _, _, QueryIds),
%writeln(queryKeys:QueryKeys), writeln(''), %writeln(queryKeys:QueryKeys), writeln(''),
%writeln(queryIds:QueryIds), writeln(''), %writeln(queryIds:QueryIds), writeln(''),
cpp_run_ground_solver(Network, [QueryIds], Solutions). cpp_run_ground_solver(Network, [QueryIds], Solutions).
keys_to_ids([], _, Hash, Hash). keys_to_ids([], Id, Id, Hash, Hash).
keys_to_ids([Key|AllKeys], I0, Hash0, Hash) :- keys_to_ids([Key|AllKeys], I0, I, Hash0, Hash) :-
b_hash_insert(Hash0, Key, I0, HashI), b_hash_insert(Hash0, Key, I0, HashI),
I is I0+1, I1 is I0+1,
keys_to_ids(AllKeys, I, HashI, Hash). keys_to_ids(AllKeys, I1, I, HashI, Hash).
get_factors_type([f(bayes, _, _, _)|_], bayes) :- ! . get_factors_type([f(bayes, _, _, _)|_], bayes) :- ! .
get_factors_type([f(markov, _, _, _)|_], markov) :- ! . get_factors_type([f(markov, _, _, _)|_], markov) :- ! .
list_of_keys_to_ids([], _, []). list_of_keys_to_ids([], H, H, I, I, []).
list_of_keys_to_ids([List|Extra], Hash, [IdList|More]) :- list_of_keys_to_ids([List|Extra], Hash0, Hash, I0, I, [IdList|More]) :-
List = [_|_], !, List = [_|_], !,
list_of_keys_to_ids(List, Hash, IdList), list_of_keys_to_ids(List, Hash0, Hash1, I0, I1, IdList),
list_of_keys_to_ids(Extra, Hash, More). list_of_keys_to_ids(Extra, Hash1, Hash, I1, I, More).
list_of_keys_to_ids([Key|QueryKeys], Hash, [Id|QueryIds]) :- list_of_keys_to_ids([Key|QueryKeys], Hash0, Hash, I0, I, [Id|QueryIds]) :-
b_hash_lookup(Key, Id, Hash), b_hash_lookup(Key, Id, Hash0), !,
list_of_keys_to_ids(QueryKeys, Hash, QueryIds). list_of_keys_to_ids(QueryKeys, Hash0, Hash, I0, I, QueryIds).
list_of_keys_to_ids([Key|QueryKeys], Hash0, Hash, I0, I, [I0|QueryIds]) :-
b_hash_insert(Hash0, Key, I0, Hash1),
I1 is I0+1,
list_of_keys_to_ids(QueryKeys, Hash1, Hash, I1, I, QueryIds).
factors_to_ids([], _, []). factors_to_ids([], H, H, I, I, []).
factors_to_ids([f(_, DistId, Keys, CPT)|Fs], Hash, [f(Ids, Ranges, CPT, DistId)|NFs]) :- factors_to_ids([f(_, DistId, Keys, CPT)|Fs], Hash0, Hash, I0, I, [f(Ids, Ranges, CPT, DistId)|NFs]) :-
list_of_keys_to_ids(Keys, Hash, Ids), list_of_keys_to_ids(Keys, Hash0, Hash1, I0, I1, Ids),
get_ranges(Keys, Ranges), get_ranges(Keys, Ranges),
factors_to_ids(Fs, Hash, NFs). factors_to_ids(Fs, Hash1, Hash, I1, I, NFs).
get_ranges([],[]). get_ranges([],[]).
get_ranges(K.Ks, Range.Rs) :- !, get_ranges(K.Ks, Range.Rs) :- !,
skolem(K,Domain), skolem(K,Domain),
length(Domain,Range), length(Domain,Range),
get_ranges(Ks, Rs). get_ranges(Ks, Rs).
evidence_to_ids([], _, []). evidence_to_ids([], H, H, I, I, []).
evidence_to_ids([Key=Ev|QueryKeys], Hash, [Id=Ev|QueryIds]) :- evidence_to_ids([Key=Ev|QueryKeys], Hash0, Hash, I0, I, [Id=Ev|QueryIds]) :-
b_hash_lookup(Key, Id, Hash), b_hash_lookup(Key, Id, Hash0),
evidence_to_ids(QueryKeys, Hash, QueryIds). evidence_to_ids(QueryKeys, Hash0, Hash, I0, I, QueryIds).
evidence_to_ids([Key=Ev|QueryKeys], Hash0, Hash, I0, I, [I=Ev|QueryIds]) :-
b_hash_insert(Hash0, Key, I0, Hash1),
I1 is I0+1,
evidence_to_ids(QueryKeys, Hash1, Hash, I1, I, QueryIds).
get_vars_information([], []). get_vars_information([], []).

View File

@ -102,9 +102,8 @@ solve_ve([LVs|_], [NVs0|_], Ps) :-
sort(LV0, LV), sort(LV0, LV),
% construct the graph % construct the graph
find_all_table_deps(Tables0, LV), find_all_table_deps(Tables0, LV),
%writeln((Li: LVs: LV)),
process(LVi, LVs, tab(Dist,_,_)), process(LVi, LVs, tab(Dist,_,_)),
%writeln(m:Dist),matrix:matrix_to_list(Dist,LD),writeln(LD), % writeln(m:Dist),matrix:matrix_to_list(Dist,LD),writeln(LD),
%exps(LD,LDE),writeln(LDE), %exps(LD,LDE),writeln(LDE),
% move from potentials back to probabilities % move from potentials back to probabilities
normalise_CPT(Dist,MPs), normalise_CPT(Dist,MPs),