refactor horus_ground.yap
This commit is contained in:
parent
51eef45b2d
commit
992d06656d
@ -31,24 +31,16 @@
|
|||||||
get_dist_params/2
|
get_dist_params/2
|
||||||
]).
|
]).
|
||||||
|
|
||||||
:- use_module(library('clpbn/ground_factors'),
|
|
||||||
[generate_network/5
|
|
||||||
]).
|
|
||||||
|
|
||||||
:- use_module(library('clpbn/display'),
|
:- use_module(library('clpbn/display'),
|
||||||
[clpbn_bind_vals/3]).
|
[clpbn_bind_vals/3]).
|
||||||
|
|
||||||
:- use_module(library('clpbn/aggregates'),
|
|
||||||
[check_for_agg_vars/2]).
|
|
||||||
|
|
||||||
:- use_module(library(clpbn/numbers)).
|
:- use_module(library(clpbn/numbers)).
|
||||||
|
|
||||||
:- use_module(library(charsio),
|
:- use_module(library(charsio),
|
||||||
[term_to_atom/2]).
|
[term_to_atom/2]).
|
||||||
|
|
||||||
:- use_module(library(pfl),
|
:- use_module(library(pfl),
|
||||||
[skolem/2
|
[skolem/2]).
|
||||||
]).
|
|
||||||
|
|
||||||
:- use_module(library(maplist)).
|
:- use_module(library(maplist)).
|
||||||
|
|
||||||
@ -60,32 +52,38 @@
|
|||||||
|
|
||||||
|
|
||||||
call_horus_ground_solver(QueryVars, QueryKeys, AllKeys, Factors, Evidence, Output) :-
|
call_horus_ground_solver(QueryVars, QueryKeys, AllKeys, Factors, Evidence, Output) :-
|
||||||
call_horus_ground_solver_for_probabilities([QueryKeys], AllKeys, Factors, Evidence, Solutions),
|
init_horus_ground_solver(QueryKeys, AllKeys, Factors, Evidence, Network),
|
||||||
clpbn_bind_vals([QueryVars], Solutions, Output).
|
run_solver(Network, [QueryKeys], Solutions),
|
||||||
|
clpbn_bind_vals([QueryVars], Solutions, Output),
|
||||||
|
finalize_horus_ground_solver(Network).
|
||||||
|
|
||||||
call_horus_ground_solver_for_probabilities(QueryKeys, AllKeys, Factors, Evidence, Solutions) :-
|
|
||||||
get_factors_type(Factors, Type),
|
init_horus_ground_solver(QueryKeys, AllKeys, Factors, Evidence, ground(Network,Hash4,Id4)) :-
|
||||||
keys_to_numbers(AllKeys, Factors, Evidence, Hash4, Id4, FactorIds, EvidenceIds),
|
get_factors_type(Factors, Type),
|
||||||
%writeln(evidence:Evidence), writeln(''),
|
keys_to_numbers(AllKeys, Factors, Evidence, Hash4, Id4, FactorIds, EvidenceIds),
|
||||||
%writeln(evidenceIds:EvidenceIds), writeln(''),
|
cpp_create_ground_network(Type, FactorIds, EvidenceIds, Network),
|
||||||
%writeln(factorIds:FactorIds), writeln(''),
|
%writeln(network:(Type, FactorIds, EvidenceIds, Network)), writeln(''),
|
||||||
cpp_create_ground_network(Type, FactorIds, EvidenceIds, Network),
|
maplist(get_var_information, AllKeys, StatesNames),
|
||||||
maplist(get_var_information, AllKeys, StatesNames),
|
maplist(term_to_atom, AllKeys, KeysAtoms),
|
||||||
maplist(term_to_atom, AllKeys, KeysAtoms),
|
cpp_set_vars_information(KeysAtoms, StatesNames).
|
||||||
%writeln(s1:KeysAtoms:KeysAtoms:StatesNames),
|
|
||||||
cpp_set_vars_information(KeysAtoms, StatesNames),
|
|
||||||
%writeln(network:(Type, FactorIds, EvidenceIds, Network)), writeln(''),
|
run_horus_ground_solver(_QueryVars, Solutions, horus(GKeys, Keys, Factors, Evidence), Solver) :-
|
||||||
run_solver(ground(Network,Hash4,Id4), QueryKeys, Solutions),
|
set_solver(Solver),
|
||||||
cpp_free_ground_network(Network).
|
call_horus_ground_solver_for_probabilities(GKeys, Keys, Factors, Evidence, Solutions).
|
||||||
|
|
||||||
|
|
||||||
|
% TODO this is not beeing called!
|
||||||
|
finalize_horus_ground_solver(ground(Network,_Hash,_Id)) :-
|
||||||
|
cpp_free_ground_network(Network).
|
||||||
|
|
||||||
|
|
||||||
run_solver(ground(Network,Hash,Id), QueryKeys, Solutions) :-
|
run_solver(ground(Network,Hash,Id), QueryKeys, Solutions) :-
|
||||||
%get_dists_parameters(DistIds, DistsParams),
|
%get_dists_parameters(DistIds, DistsParams),
|
||||||
%cpp_set_factors_params(Network, DistsParams),
|
%cpp_set_factors_params(Network, DistsParams),
|
||||||
lists_of_keys_to_ids(QueryKeys, QueryIds, Hash, _, Id, _),
|
lists_of_keys_to_ids(QueryKeys, QueryIds, Hash, _, Id, _),
|
||||||
%writeln(queryKeys:QueryKeys), writeln(''),
|
cpp_run_ground_solver(Network, QueryIds, Solutions).
|
||||||
% writeln(queryIds:QueryIds), writeln(''),
|
|
||||||
cpp_run_ground_solver(Network, QueryIds, Solutions).
|
|
||||||
|
|
||||||
get_factors_type([f(bayes, _, _)|_], bayes) :- ! .
|
get_factors_type([f(bayes, _, _)|_], bayes) :- ! .
|
||||||
get_factors_type([f(markov, _, _)|_], markov) :- ! .
|
get_factors_type([f(markov, _, _)|_], markov) :- ! .
|
||||||
@ -97,47 +95,8 @@ get_var_information(Key, Domain) :-
|
|||||||
skolem(Key, Domain).
|
skolem(Key, Domain).
|
||||||
|
|
||||||
|
|
||||||
finalize_horus_ground_solver(bp(Network, _)) :-
|
%get_dists_parameters([],[]).
|
||||||
cpp_free_ground_network(Network).
|
%get_dists_parameters([Id|Ids], [dist(Id, Params)|DistsInfo]) :-
|
||||||
finalize_horus_ground_solver(horus(_, _, _, _)).
|
% get_dist_params(Id, Params),
|
||||||
|
% get_dists_parameters(Ids, DistsInfo).
|
||||||
%
|
|
||||||
% QVars: all query variables?
|
|
||||||
%
|
|
||||||
%
|
|
||||||
init_horus_ground_solver(QueryKeys, AllKeys, Factors, Evidence, horus(QueryKeys, AllKeys, Factors, Evidence)).
|
|
||||||
|
|
||||||
%
|
|
||||||
% just call horus solver.
|
|
||||||
%
|
|
||||||
run_horus_ground_solver(_QueryVars, Solutions, horus(GKeys, Keys, Factors, Evidence) , Solver) :-
|
|
||||||
set_solver(Solver),
|
|
||||||
call_horus_ground_solver_for_probabilities(GKeys, Keys, Factors, Evidence, Solutions).
|
|
||||||
|
|
||||||
%bp([[]],_,_) :- !.
|
|
||||||
%bp([QueryVars], AllVars, Output) :-
|
|
||||||
% init_horus_ground_solver(_, AllVars, _, Network),
|
|
||||||
% run_horus_ground_solver([QueryVars], LPs, Network),
|
|
||||||
% finalize_horus_ground_solver(Network),
|
|
||||||
% clpbn_bind_vals([QueryVars], LPs, Output).
|
|
||||||
%
|
|
||||||
%init_horus_ground_solver(_, AllVars0, _, bp(BayesNet, DistIds)) :-
|
|
||||||
% %check_for_agg_vars(AllVars0, AllVars),
|
|
||||||
% get_vars_info(AllVars0, VarsInfo, DistIds0),
|
|
||||||
% sort(DistIds0, DistIds),
|
|
||||||
% cpp_create_ground_network(VarsInfo, BayesNet),
|
|
||||||
% true.
|
|
||||||
%
|
|
||||||
%
|
|
||||||
%run_horus_ground_solver(QueryVars, Solutions, bp(Network, DistIds)) :-
|
|
||||||
% get_dists_parameters(DistIds, DistsParams),
|
|
||||||
% cpp_set_factors_params(Network, DistsParams),
|
|
||||||
% vars_to_ids(QueryVars, QueryVarsIds),
|
|
||||||
% cpp_run_ground_solver(Network, QueryVarsIds, Solutions).
|
|
||||||
|
|
||||||
|
|
||||||
get_dists_parameters([],[]).
|
|
||||||
get_dists_parameters([Id|Ids], [dist(Id, Params)|DistsInfo]) :-
|
|
||||||
get_dist_params(Id, Params),
|
|
||||||
get_dists_parameters(Ids, DistsInfo).
|
|
||||||
|
|
||||||
|
Reference in New Issue
Block a user