This commit is contained in:
Vitor Santos Costa 2019-03-06 10:49:55 +00:00
parent 21ff73dd70
commit 32a5158c6b
19 changed files with 101 additions and 115 deletions

View File

@ -3977,6 +3977,7 @@ static void EraseLogUpdCl(LogUpdClause *clau) {
ap->cs.p_code.LastClause = clau->ClPrev->ClCode;
}
}
clau->ClTimeEnd = ap->TimeStampOfPred;
ap->cs.p_code.NOfClauses--;
}
#ifndef THREADS

View File

@ -95,8 +95,9 @@ INLINE_ONLY int VALID_TIMESTAMP(UInt, struct logic_upd_clause *);
INLINE_ONLY int VALID_TIMESTAMP(UInt timestamp,
struct logic_upd_clause *cl) {
// printf("%lu %lu %lu\n",cl->ClTimeStart, timestamp, cl->ClTimeEnd);
return IN_BETWEEN(cl->ClTimeStart, timestamp, cl->ClTimeEnd);
}
}
typedef struct dynamic_clause {
/* A set of flags describing info on the clause */

View File

@ -4,8 +4,8 @@ set (PROGRAMS
problog_lfi.yap
dtproblog.yap
aproblog.yap
problog_lbfgs.yap
problog_learning.yap
problog_lbfgs.yap
problog_learning_lbdd.yap
)

View File

@ -517,15 +517,12 @@ every 5th iteration only.
% directory where simplecudd executable is located
% automatically set during loading -- assumes it is in /usr/local/bin or same place where YAP has
% been installed.)
:- getcwd(PD0),
atom_concat(PD0, '../../bin', PD),
set_problog_path(PD).
:- PD = '/usr/local/bin',
set_problog_path(PD).
:- PD = '$HOME/,local/bin',
set_problog_path(PD).
@ -554,7 +551,10 @@ every 5th iteration only.
%%%%%%%%%%%%
% max number of calls to probabilistic facts per derivation (to ensure termination)
%%%%%%%%%%%%
:- initialization( problog_define_flag(maxsteps, problog_flag_validate_posint, 'max. number of prob. steps per derivation', 1000, inference) ).
:- initialization(
problog_define_flag(maxsteps, problog_flag_validate_posint, 'max. number of prob. steps per derivation', 1000, inference)
).
%%%%%%%%%%%%
% BDD timeout in seconds, used as option in BDD tool
@ -626,7 +626,6 @@ every 5th iteration only.
problog_dir(PD):- problog_path(PD).
%%%%%%%%%%%%%%%%%%%%%%%%
@ -1825,7 +1824,7 @@ eval_dnf(OriTrie1, Prob, Status) :-
;
Trie = OriTrie
),
(problog_flag(bdd_static_order, true) ->
(problog_flag(bdd_static_order, true) ->
get_order(Trie, Order),
problog_flag(static_order_file, SOFName),
convert_filename_to_working_path(SOFName, SOFileName),
@ -2445,7 +2444,7 @@ and the facts used in achieving this explanation.
explanation probability - returns list of facts used or constant 'unprovable' as third argument
problog_max(+Goal,-Prob,-Facts)
uses iterative deepening with samw parameters as bounding algorithm
uses iterative deepening with same parameters as bounding algorithm
threshold gets adapted whenever better proof is found
uses local dynamic predicates max_probability/1 and max_proof/1
@ -2454,8 +2453,8 @@ uses local dynamic predicates max_probability/1 and max_proof/1
problog_max(Goal, Prob, Facts) :-
problog_flag(first_threshold,InitT),
init_problog_max(InitT),
problog_control(off,up), %
problog_max_id(Goal, Prob, FactIDs), %theo todo
problog_control(off,up),
problog_max_id(Goal, Prob, FactIDs),% theo todo
( FactIDs = [_|_] -> get_fact_list(FactIDs, Facts);
Facts = FactIDs).

View File

@ -204,7 +204,7 @@
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% @file problog/flags.yap
%% @file problog/flags
:-module(flags, [problog_define_flag/4,
problog_define_flag/5,
@ -218,7 +218,7 @@
:- use_module(gflags).
:- use_module(os).
:- use_module(logger).
:- use_module(library(system), [file_exists/1, delete_file/1,file_property/2]).
:- use_module(library(system), [file_exists/1, delete_file/1]).
/** @defgroup ProbLogMiscellaneous ProbLog Miscellaneous Predicates

View File

@ -243,7 +243,7 @@
problog_define_flag(refine_anclst, problog_flag_validate_boolean, 'refine the ancestor list with their childs', false, nested_tries),
problog_define_flag(anclst_represent,problog_flag_validate_in_list([list, integer]), 'represent the ancestor list', list, nested_tries)
)).
:- stop_low_level_trace.
trie_replace_entry(_Trie, Entry, E, false):-
trie_get_entry(Entry, Proof),
@ -486,4 +486,3 @@ get_trie(Trie, Label, Ancestors):-
set_trie(Trie, Label, Ancestors):-
recordz(problog_trie_table, store(Trie, Ancestors, Label), _).

View File

@ -265,7 +265,7 @@
:- initialization(
( predicate_property(trie_disable_hash, imported_from(_M)) ->
trie_disable_hash
; true % stop_low_level_trace, print_message(warning,'The predicate trie_disable_hash/0 does not exist. Please update trie library.')
; print_message(warning,'The predicate tries:trie_disable_hash/0 does not exist. Please update trie library.')
)
).
@ -276,7 +276,7 @@
:- initialization((
problog_define_flag(use_db_trie, problog_flag_validate_boolean, 'use the builtin trie 2 trie transformation', false),
problog_define_flag(db_trie_opt_lvl, problog_flag_validate_integer, 'optimization level for the trie 2 trie transformation', 0),
problog_define_flag(compare_opt_lvl, problog_flag_validate_boolean, 'comparison mode for optimizatione level', false),
problog_define_flag(compare_opt_lvl, problog_flag_validate_boolean, 'comparison mode for optimization level', false),
problog_define_flag(db_min_prefix, problog_flag_validate_integer, 'minimum size of prefix for dbtrie to optimize', 2),
problog_define_flag(use_naive_trie, problog_flag_validate_boolean, 'use the naive algorithm to generate bdd scripts', false),
problog_define_flag(use_old_trie, problog_flag_validate_boolean, 'use the old trie 2 trie transformation no nested', true),

View File

@ -15,31 +15,32 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- use_module(library(matrix)).
:- use_module('../problog_learning').
:- use_module(('../problog_learning')).
:- stop_low_level_trace.
%%%%
% background knowledge
%%%%
%%%%
% definition of acyclic path using list of visited nodes
path(X,Y) :- path(X,Y,[X],_).
path(X,X,A,A).
path(X,Y,A,R) :-
X\==Y,
edge(X,Z),
absent(Z,A),
path(X,Y,A,R) :-
X\==Y,
edge(X,Z),
absent(Z,A),
path(Z,Y,[Z|A],R).
% using directed edges in both directions
edge(X,Y) :- dir_edge(Y,X).
edge(X,Y) :- dir_edge(X,Y).
edge(X,Y) :- problog:dir_edge(Y,X).
edge(X,Y) :- problog:dir_edge(X,Y).
% checking whether node hasn't been visited before
absent(_,[]).
absent(X,[Y|Z]):-X \= Y, absent(X,Z).
%%%%
% probabilistic facts
% probabilistic facts
% - probability represented by t/1 term means learnable parameter
% - argument of t/1 is real value (used to compare against in evaluation when known), use t(_) if unknown
%%%%
@ -53,7 +54,7 @@ t(0.7)::dir_edge(5,3).
t(0.2)::dir_edge(5,4).
%%%%%%%%%%%%%%
% training examples of form example(ID,Query,DesiredProbability)
% training examples of form example(ID,Query,DesiredProbability)
%%%%%%%%%%%%%%
example(1,path(1,2),0.94).
@ -79,7 +80,7 @@ example(19,(dir_edge(2,6),dir_edge(6,5)),0.2).
example(20,(dir_edge(1,2),dir_edge(2,3),dir_edge(3,4)),0.432).
%%%%%%%%%%%%%%
% test examples of form test_example(ID,Query,DesiredProbability)
% test examples of form test_example(ID,Query,DesiredProbability)
% note: ID namespace is shared with training example IDs
%%%%%%%%%%%%%%
@ -99,7 +100,7 @@ test_example(33,path(5,4),0.57).
test_example(34,path(6,4),0.51).
test_example(35,path(6,5),0.69).
:- set_problog_flag(init_method,(Query,_,BDD,
problog_exact_lbdd(user:Query,BDD))).
%:- set_problog_flag(init_method,(Query,_,BDD,
% problog_exact(user:Query,_,BDD))).

View File

@ -14,8 +14,7 @@
% will run 20 iterations of learning with default settings
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
:- use_module(library(problog)).
:- use_module(library(problog_learning_lbdd)).
:- use_module(library(problog_learning)).
%%%%
% background knowledge

View File

@ -581,8 +581,7 @@ bdd_input_file(Filename) :-
concat_path_with_filename(Dir,'input.txt',Filename).
init_one_query(QueryID,Query,_Type) :-
writeln(init_one_query(QueryID,Query,_Type)),
% format_learning(3,' ~q example ~q: ~q~n',[Type,QueryID,Query]),
% format_learning(3,' ~q example ~q: ~q~n',[Type,QueryID,Query]),
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% if BDD file does not exist, call ProbLog
@ -593,15 +592,13 @@ writeln(init_one_query(QueryID,Query,_Type)),
format_learning(3,' Reuse existing BDD ~q~n~n',[QueryID])
;
b_setval(problog_required_keep_ground_ids,false),
(QueryID mod 100 =:= 0 -> writeln(QueryID) ; true),
problog_flag(init_method,(Query,N,Bdd,G)),
problog_flag(init_method,(Query,N,Bdd,graph2bdd(X,Y,N,Bdd))),
Query =.. [_,X,Y]
->
Bdd = bdd(Dir, Tree, MapList),
(
G
graph2bdd(X,Y,N,Bdd)
->
rb_new(H0),
maplist_to_hash(MapList, H0, Hash),
@ -611,9 +608,8 @@ writeln(init_one_query(QueryID,Query,_Type)),
% Grad=[]
),
write('.'),
recordz(QueryID,bdd(Dir, Grad, MapList),_)
).
/* ;
recordz(QueryID,bdd(Dir, Grad, MapList),_)
;
problog_flag(init_method,(Query,NOf,Bdd,problog_kbest_as_bdd(Call,NOf,Bdd))) ->
b_setval(problog_required_keep_ground_ids,false),
rb_new(H0),
@ -628,20 +624,20 @@ writeln(init_one_query(QueryID,Query,_Type)),
tree_to_grad(Tree, Hash, [], Grad),
recordz(QueryID,bdd(Dir, Grad, MapList),_)
;
problog_flag(init_method,(Query,NOf,Bdd,_Call)) ,
Query = gene(X,Y),
problog_flag(init_method,(Query,NOf,Bdd,Call)) ->
b_setval(problog_required_keep_ground_ids,false),
rb_new(H0),
Bdd = bdd(Dir, Tree, MapList),
user:graph2bdd(X,Y,1,Bdd),
% trace,
problog:Call,
maplist_to_hash(MapList, H0, Hash),
Tree \= [],
%put_code(0'.),
tree_to_grad(Tree, Hash, [], Grad),
recordz(QueryID,bdd(Dir, Grad, MapList),_).
recordz(QueryID,bdd(Dir, Grad, MapList),_)
).
*/
%========================================================================

View File

@ -1487,10 +1487,12 @@ my_5_min(V1,V2,V3,V4,V5,F1,F2,F3,F4,F5,VMin,FMin) :-
%========================================================================
init_flags :-
writeln(10),
prolog_file_name('queries',Queries_Folder), % get absolute file name for './queries'
prolog_file_name('output',Output_Folder), % get absolute file name for './output'
problog_define_flag(bdd_directory, problog_flag_validate_directory, 'directory for BDD scripts', Queries_Folder,learning_general),
problog_define_flag(output_directory, problog_flag_validate_directory, 'directory for logfiles etc', Output_Folder,learning_general,flags:learning_output_dir_handler),
writeln(10),
problog_define_flag(log_frequency, problog_flag_validate_posint, 'log results every nth iteration', 1, learning_general),
problog_define_flag(rebuild_bdds, problog_flag_validate_nonegint, 'rebuild BDDs every nth iteration', 0, learning_general),
problog_define_flag(reuse_initialized_bdds,problog_flag_validate_boolean, 'Reuse BDDs from previous runs',false, learning_general),
@ -1529,3 +1531,4 @@ init_logger :-
:- initialization(init_flags).
:- initialization(init_logger).

View File

@ -770,6 +770,7 @@ db_files(Fs) :-
'$lf_opt'(imports, TOpts, Imports),
'$import_to_current_module'(File, ContextModule, Imports, _, TOpts),
'$current_module'(Mod, SourceModule),
%`writeln(( ContextModule/Mod )),
set_prolog_flag(verbose_load, VerboseLoad),
H is heapused-H0, '$cputime'(TF,_), T is TF-T0,
print_message(informational, loaded(EndMsg, File, Mod, T, H)),

View File

@ -305,7 +305,7 @@ prolog:when(_,Goal) :-
%
'$declare_when'(Cond, G) :-
generate_code_for_when(Cond, G, Code),
'$$compile'(Code, Module, assertz, Code, _), fail.
'$$compile'(Code, assertz, Code, _), fail.
'$declare_when'(_,_).
%
@ -433,7 +433,6 @@ suspend_when_goals([_|_], _).
%
prolog:'$block'(Conds) :-
generate_blocking_code(Conds, _, Code),
'$yap_strip_module'(Code, Module, NCode),
'$$compile'(Code, assertz, Code, _), fail.
prolog:'$block'(_).

View File

@ -463,8 +463,9 @@ meta_predicate(P) :-
% A4: module for body of clause (this is the one used in looking up predicates)
%
% has to be last!!!
'$expand_a_clause'(MHB, SM0, Cl1, ClO) :- % MHB is the original clause, SM0 the current source, Cl1 and ClO output clauses
'$yap_strip_module'(SM0:MHB, SM, HB), % remove layers of modules over the clause. SM is the source module.
'$expand_a_clause'(MHB, Cl1, ClO) :- % MHB is the original clause, SM0 the current source, Cl1 and ClO output clauses
source_module(SM0),
'$yap_strip_module'(MHB, SM, HB), % remove layers of modules over the clause. SM is the head module.
'$head_and_body'(HB, H, B), % HB is H :- B.
'$yap_strip_module'(SM:H, HM, NH), % further module expansion
'$not_imported'(NH, HM),

View File

@ -450,25 +450,29 @@ export_list(Module, List) :-
!.
'$do_import'(N0/K0-N0/K0, Mod, Mod) :- !.
'$do_import'(N0/K0-N0/K0, _Mod, prolog) :- !.
'$do_import'(_N/K-N1/K, _Mod, ContextMod) :-
recorded('$module','$module'(_F, ContextMod, _SourceF, MyExports,_),_),
once(lists:member(N1/K, MyExports)),
functor(S, N1, K),
% reexport predicates if they are undefined in the current module.
\+ '$undefined'(S,ContextMod), !.
'$do_import'( N/K-N1/K, Mod, ContextMod) :-
functor(G,N,K),
'$one_predicate_definition'(Mod:G,M0:G0),
M0\=prolog,
(Mod\=M0->N\=N1;true),
G0=..[_N0|Args],
% '$do_import'(_N/K-N1/K, _Mod, ContextMod) :-
% recorded('$module','$module'(_F, ContextMod, _SourceF, MyExports,_),_),
% once(lists:member(N1/K, MyExports)),
% functor(S, N1, K),
% % reexport predicates if they are undefined in the current module.
% \+ '$undefined'(S,ContextMod), !.
'$do_import'( N0/K-N1/K, M0, ContextMod) :-
%'$one_predicate_definition'(Mod:G,M0:G0),
% M0\=prolog,
(M0==ContextMod->N0\=N1;true),
functor(G1,N1,K),
(N0 == N1
->
G0=G1
;
G1=..[N1|Args],
recordaifnot('$import','$import'(M0,ContextMod,G0,G1,N1,K),_),
%\+ '$is_system_predicate'(G1, prolog),
%'$compile'((G1:-M0:G0), reconsult,(ContextMod:G1:-M0:G0) , ContextMod, R),
fail.
% always succeed.
'$do_import'(_,_,_).
G0=..[N0|Args]
),
%writeln((ContextMod:G1:-M0:G0)),
recordaifnot('$import','$import'(M0,ContextMod,G0,G1,N1,K),_),
!.
'$do_import'( _,_,_ ).
'$follow_import_chain'(M,G,M0,G0) :-
recorded('$import','$import'(M1,M,G1,G,_,_),_), M \= M1, !,
@ -480,7 +484,7 @@ export_list(Module, List) :-
recorded('$import','$import'(MI, ContextM, _, _, N,K),_R),
% dereference MI to M1, in order to find who
% is actually generating
( '$module_produced by'(M1, MI, N, K) -> true ; MI = M1 ),
( '$module_produced by'(M1, MI, N, K) -> true ; MI = M1 ),
( '$module_produced by'(M2, Mod, N, K) -> true ; Mod = M2 ),
M2 \= M1, !,
'$redefine_import'( M1, M2, Mod, ContextM, N/K).
@ -727,4 +731,5 @@ module_state :-
fail.
module_state.
%% @}
%% @}imports

View File

@ -50,8 +50,8 @@ assert(Clause) :-
'$assert'(Clause, assertz, _).
'$assert'(Clause, Where, R) :-
'$expand_clause'(Clause0,C0,C),
'$$compile'(CC, Where, C0, R).
'$expand_clause'(Clause,C0,C),
'$$compile'(C, Where, C0, R).
/** @pred asserta(+ _C_,- _R_)

View File

@ -388,13 +388,8 @@ or built-in.
*/
predicate_property(Pred,Prop) :-
(
current_predicate(_,Pred),
'$yap_strip_module'(Pred, Mod, TruePred)
;
'$current_predicate'(_,M,Pred,system),
'$yap_strip_module'(M:Pred, Mod, TruePred)
),
'$yap_strip_module'(Pred, Mod, TruePred),
(var(Mod) -> current_module(Mod) ; true ),
'$predicate_definition'(Mod:TruePred, M:NPred),
'$predicate_property'(NPred,M,Mod,Prop).

View File

@ -218,23 +218,22 @@ live :-
'$go_compile_clause'(G, _Vs, _Pos, Where, Source) :-
'$precompile_term'(G, Source, G1),
!,
'$$compile'(G1, M, Where, Source, _).
'$$compile'(G1, Where, Source, _).
'$go_compile_clause'(G,_Vs,_Pos, _Where, _Source) :-
throw(error(system, compilation_failed(G))).
'$$compile'(C, Where, C0, R) :-
'$head_and_body'( M0:C, MH, B ),
'$yap_strip_module'( MH, Mod, H),
'$yap_strip_module'( MB, ModB, BF),
'$head_and_body'( C, H, B ),
'$yap_strip_module'(H,Mod,H0),
(
'$undefined'(H, Mod)
'$undefined'(H0, Mod)
->
'$init_pred'(H, Mod, Where)
'$init_pred'(H0, Mod, Where)
;
trueq
true
),
% writeln(Mod:((H:-B))),
'$compile'((H:-ModB:BF), Where, C0, Mod, R).
'$compile'((H0:-B), Where, C0, Mod, R).
'$init_pred'(H, Mod, _Where ) :-
recorded('$import','$import'(NM,Mod,NH,H,_,_),RI),
@ -784,8 +783,7 @@ Command = (H --> B) ->
'$boot_dcg'( H, B, Where ) :-
'$translate_rule'((H --> B), (NH :- NB) ),
'$yap_strip_module'((NH :- NB), M, G),
'$$compile'(G, M, Where, ( H --> B), _R),
'$$compile'((NH :- NB), Where, ( H --> B), _R),
!.
'$boot_dcg'( H, B, _ ) :-
format(user_error, ' ~w --> ~w failed.~n', [H,B]).
@ -877,8 +875,7 @@ gated_call(Setup, Goal, Catcher, Cleanup) :-
'$precompile_term'(Term, Term, Term).
'$expand_clause'(InputCl, C1, CO) :-
'$yap_strip_module'(InputCl, M, ICl),
'$expand_a_clause'( M:ICl, M, C1, CO),
'$expand_a_clause'( InputCl, C1, CO),
!.
'$expand_clause'(Cl, Cl, Cl).

View File

@ -97,28 +97,17 @@ undefined_query(G0, M0, Cut) :-
'$undefp'([M0|G0],true) :-
% make sure we do not loop on undefined predicates
setup_call_cleanup(
'$undef_setup'(M0:G0, Action,Debug,Current, MGI),
'$get_undefined_predicate'( MGI, MG ),
'$undef_setup'(Action,Debug,Current),
'$get_undefined_predicate'( M0:G0, MG ),
'$undef_cleanup'(Action,Debug,Current)
),
'$undef_error'(Action, M0:G0, MGI, MG).
'$undef_error'(Action, M0:G0, MG).
'$undef_setup'(G0,Action,Debug,Current,G0) :-
'$undef_setup'(Action,Debug,Current) :-
yap_flag( unknown, Action, fail),
yap_flag( debug, Debug, false),
'$stop_creeping'(Current).
'$g2i'(user:G, Na/Ar ) :-
!,
functor(G, Na, Ar).
'$g2i'(prolog:G, Na/Ar ) :-
!,
functor(G, Na, Ar).
'$g2i'(M:G, M:Na/Ar ) :-
!,
functor(G, Na, Ar).
'$undef_cleanup'(Action,Debug, _Current) :-
yap_flag( unknown, _, Action),
yap_flag( debug, _, Debug).
@ -137,22 +126,22 @@ The unknown predicate, informs about what the user wants to be done
*/
'$undef_error'(_, _, _, M:G) :-
'$undef_error'(_, _, M:G) :-
nonvar(M),
nonvar(G),
!,
'$start_creep'([M|G], creep).
'$undef_error'(_, M0:G0, _, MG) :-
'$undef_error'(_, M0:G0, M:G) :-
'$pred_exists'(unknown_predicate_handler(_,_,_,_), user),
'$yap_strip_module'(M0:G0, EM0, GM0),
user:unknown_predicate_handler(GM0,EM0,MG),
user:unknown_predicate_handler(GM0,EM0,M:G),
!,
'$start_creep'([prolog|true], creep).
'$undef_error'(error, Mod:Goal, I,_) :-
'$do_error'(existence_error(procedure,I), Mod:Goal).
'$undef_error'(warning,Mod:Goal,I,_) :-
'$start_creep'([M|G], creep).
'$undef_error'(error, Mod:Goal,_) :-
'$do_error'(existence_error(procedure,Mod:Goal), Mod:Goal).
'$undef_error'(warning,Mod:Goal,_) :-
'$program_continuation'(PMod,PName,PAr),
print_message(warning,error(existence_error(procedure,I), context(Mod:Goal,PMod:PName/PAr))),
print_message(warning,error(existence_error(procedure,Mod:Goal), context(Mod:Goal,PMod:PName/PAr))),
%'$start_creep'([prolog|fail], creep),
fail.
'$undef_error'(fail,_Goal,_,_Mod) :-