init better; problog_low accepts conditional probabilities (untested); accept (p0::a;p1::b).

This commit is contained in:
Vitor Santos Costa 2016-08-05 16:43:11 -05:00
parent 0aeeb726e3
commit b3a11b339a
6 changed files with 123 additions and 121 deletions

View File

@ -1068,7 +1068,8 @@ reset_control :-
problog_control(off,mc), problog_control(off,mc),
problog_control(off,limit), problog_control(off,limit),
% problog_control(off,exact), % problog_control(off,exact),
problog_control(off,remember). problog_control(off,remember),
nb_setval(problog_steps, 1).
:- initialization(reset_control). :- initialization(reset_control).
@ -1105,12 +1106,14 @@ generate_atoms(N, A):-
% converts annotated disjunctions % converts annotated disjunctions
term_expansion_intern((Head<--Body), Module, C):- term_expansion_intern((Head<--Body), Module, C):-
term_expansion_intern_ad((Head<--Body), Module,inference, C). term_expansion_intern_ad((Head<--Body), Module,inference, C).
% converts ?:: prefix to ? :: infix, as handled by other clause % converts ?:: prefix to ? :: infix, as handled by other clause
term_expansion_intern((Annotation::Fact), Module, ExpandedClause) :- term_expansion_intern((Annotation::Fact), Module, ExpandedClause) :-
Annotation == ( '?' ), Annotation == ( '?' ),
term_expansion_intern(((?) :: Fact :- true), Module, ExpandedClause). term_expansion_intern(((?) :: Fact :- true), Module, ExpandedClause).
term_expansion_intern((Annotation::Head; Alternatives), Module, C):-
is_alternatives( Alternatives ),
!,
term_expansion_intern_ad(((Annotation::Head; Alternatives)<--true), Module,inference, C).
% handles decision clauses % handles decision clauses
term_expansion_intern((Annotation :: Head :- Body), Module, problog:ExpandedClause) :- term_expansion_intern((Annotation :: Head :- Body), Module, problog:ExpandedClause) :-
@ -1303,6 +1306,14 @@ sample_initial_value_for_tunable_fact(Goal,LogP) :-
LogP is log(P). LogP is log(P).
is_alternatives( Var ) :-
var( Var ),
!,
fail.
is_alternatives( _Prob::_Alt ).
is_alternatives( ( A1 ; As ) ) :-
is_alternatives( A1 ),
is_alternatives( As ).
% %
@ -1512,15 +1523,15 @@ prove_problog_fact(ClauseID,GroundID,Prob) :-
(problog_control(check,find_decisions) -> (problog_control(check,find_decisions) ->
signal_decision(ClauseID,GroundID) signal_decision(ClauseID,GroundID)
; ;
(Prob = ('?') -> (Prob == ('?') ->
add_to_proof(GroundID,0) % 0 is log(1)! add_to_proof(GroundID,0) % 0 is log(1)!
; ;
% Checks needed for LeDTProbLog % Checks needed for LeDTProbLog
(Prob = always -> (Prob == always ->
% Always true, do not add to trie % Always true, do not add to trie
true true
; ;
(Prob = never -> (Prob == never ->
% Always false, do not add to trie % Always false, do not add to trie
fail fail
; ;
@ -2040,7 +2051,7 @@ init_problog(Threshold) :-
reset_control, reset_control,
LT is log(Threshold), LT is log(Threshold),
b_setval(problog_probability, 0.0), b_setval(problog_probability, 0.0),
b_setval(problog_current_proof, []), nb_setval(problog_current_proof, []),
nb_setval(problog_threshold, LT), nb_setval(problog_threshold, LT),
problog_flag(maxsteps,MaxS), problog_flag(maxsteps,MaxS),
init_tabling, init_tabling,
@ -2064,6 +2075,9 @@ init_problog(Threshold) :-
timer_reset(sld_time), timer_reset(sld_time),
timer_reset(build_tree_low). timer_reset(build_tree_low).
% :- initialization( ( init_problog(0.0),
% reset_control ) ).
% idea: proofs that are refinements of known proof can be pruned as they don't add probability mass % idea: proofs that are refinements of known proof can be pruned as they don't add probability mass
% note that current ptree implementation doesn't provide the check as there's no efficient method known so far... % note that current ptree implementation doesn't provide the check as there's no efficient method known so far...
prune_check(Proof, Trie) :- prune_check(Proof, Trie) :-
@ -2418,7 +2432,7 @@ execute_bdd_tool(BDDFile, BDDParFile, Prob, Status):-
; ;
Param = ParamD Param = ParamD
), ),
convert_filename_to_problog_path('problogbdd', ProblogBDD), convert_filename_to_problog_path('simplecudd', ProblogBDD),
convert_filename_to_working_path(ResultFileFlag, ResultFile), convert_filename_to_working_path(ResultFileFlag, ResultFile),
atomic_concat([ProblogBDD, Param,' -l ', BDDFile, ' -i ', BDDParFile, ' -m p -t ', BDDTime, ' > ', ResultFile], Command), atomic_concat([ProblogBDD, Param,' -l ', BDDFile, ' -i ', BDDParFile, ' -m p -t ', BDDTime, ' > ', ResultFile], Command),
shell(Command, Return), shell(Command, Return),
@ -2600,7 +2614,11 @@ compute_bounds(LP, UP, Status) :-
% same as problog_threshold/5, but lower bound only (no stopped derivations stored) % same as problog_threshold/5, but lower bound only (no stopped derivations stored)
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
problog_low(Goal/Cond, Threshold, _, _) :-
!,
problog_low((Cond,Goal), Threshold, P1, Status)
problog_low( Cond, Threshold, P2, Status)
P is P1/P2.
problog_low(Goal, Threshold, _, _) :- problog_low(Goal, Threshold, _, _) :-
init_problog_low(Threshold), init_problog_low(Threshold),
problog_control(off, up), problog_control(off, up),
@ -3688,7 +3706,7 @@ eval_bdd_forest(N,Probs,Status) :-
; ;
Param = ParamD Param = ParamD
), ),
convert_filename_to_problog_path('problogbdd', ProblogBDD), convert_filename_to_problog_path('simplecudd', ProblogBDD),
problog_flag(bdd_result,ResultFileFlag), problog_flag(bdd_result,ResultFileFlag),
convert_filename_to_working_path(ResultFileFlag, ResultFile), convert_filename_to_working_path(ResultFileFlag, ResultFile),
atomic_concat([ProblogBDD, Param,' -l ', BDDFile, ' -i ', BDDParFile, ' -m p -t ', BDDTime, ' > ', ResultFile], Command), atomic_concat([ProblogBDD, Param,' -l ', BDDFile, ' -i ', BDDParFile, ' -m p -t ', BDDTime, ' > ', ResultFile], Command),
@ -4170,4 +4188,3 @@ user:term_expansion(Term,ExpandedTerm) :-
problog:term_expansion_intern(Term,Mod,ExpandedTerm). problog:term_expansion_intern(Term,Mod,ExpandedTerm).
%% @} %% @}

View File

@ -207,7 +207,7 @@
:- module(ad_converter,[term_expansion_intern_ad/4, :- module(ad_converter,[term_expansion_intern_ad/4,
op(1149, yfx, <-- ), op(1149, yfx, <-- ),
op( 550, yfx, :: ) op( 550, yfx, :: )
]). ƒcrete ]).
% general yap modules % general yap modules
:- use_module(library(lists),[member/2,append/3]). :- use_module(library(lists),[member/2,append/3]).
@ -284,8 +284,6 @@ term_expansion_intern_ad((Head<--Body), Module, Mode, [user:ad_intern((Head<--Bo
; ;
findall(Module:B,member(B,Aux_Clauses),Result,Result_Atoms) findall(Module:B,member(B,Aux_Clauses),Result,Result_Atoms)
), ),
( (
problog_flag(show_ad_compilation,true) problog_flag(show_ad_compilation,true)
-> ->
@ -300,16 +298,11 @@ term_expansion_intern_ad((Head<--Body), Module, Mode, [user:ad_intern((Head<--Bo
; ;
true true
). ).
term_expansion_intern_ad( (Head<--Body),_,_) :- term_expansion_intern_ad( (Head<--Body),_,_) :-
format(chars(Error), 'Error at compiling the annotated disjunction ~q<--~m.',[Head,Body]), format(chars(Error), 'Error at compiling the annotated disjunction ~q<--~m.',[Head,Body]),
print_message(error,Error), print_message(error,Error),
fail. fail.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% proper_ad_head(+Head, +Acc) % proper_ad_head(+Head, +Acc)
% %

View File

@ -76,7 +76,6 @@ grounder_compute_reachable_atoms(A,ID,Success) :-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
( % go over all proofs for A in interpretation ID ( % go over all proofs for A in interpretation ID
tabled_meta_interpreter(A,ID), tabled_meta_interpreter(A,ID),
writeln(A),
bb_put(dep_proven,true), bb_put(dep_proven,true),
fail; % go to next proof fail; % go to next proof
@ -148,8 +147,6 @@ tabled_meta_interpreter(Atom,ID) :-
% ground at query time % ground at query time
current_predicate(user:myclause/3), current_predicate(user:myclause/3),
user:myclause(ID,Atom,Body), user:myclause(ID,Atom,Body),
writeln(Atom:Body),
tabled_meta_interpreter(Body,ID), tabled_meta_interpreter(Body,ID),
% check whether Atom got grounded now, % check whether Atom got grounded now,
@ -250,6 +247,3 @@ grounder_completion_for_atom(Head,InterpretationID,'$atom'(Head)<=>Disjunction)
),Bodies), ),Bodies),
Bodies\==[], Bodies\==[],
list_to_disjunction(Bodies,Disjunction). list_to_disjunction(Bodies,Disjunction).

View File

@ -309,7 +309,8 @@ calc_md5_intern(Filename,MD5) :-
file_to_codes( F, Codes, LF ) :- file_to_codes( F, Codes, LF ) :-
open(F, read, S), open(F, read, S),
get_codes( S, Codes, LF). get_codes( S, Codes, LF),
close(S).
get_codes(S, [C|L], LF) :- get_codes(S, [C|L], LF) :-
get_code(S, C), get_code(S, C),
@ -339,5 +340,3 @@ path_grouping(PathSep) :-
path_separator('\\') :- path_separator('\\') :-
current_prolog_flag( windows, true ). current_prolog_flag( windows, true ).
path_separator('/'). path_separator('/').

View File

@ -1564,7 +1564,7 @@ combine_ancestors(Ancestors, AddAncestors, AllAncestors):-
my_trie_print(T):- my_trie_print(T):-
trie_traverse(T, R), trie_traverse(T, R),
trie_get_entry(R, E), trie_get_entry(R, E),
writeln(E), format('~w~n', [E]),
fail. fail.
my_trie_print(_T). my_trie_print(_T).

View File

@ -615,7 +615,6 @@ init_queries :-
init_one_query(Training_ID,training) init_one_query(Training_ID,training)
) )
), ),
writeln(Training_ID),
forall( forall(
( (
@ -884,7 +883,7 @@ update_query(QueryID,ClusterID ,Method,Command,PID,Output_File_Name) :-
create_bdd_output_file_name(QueryID,ClusterID,Iteration,Output_File_Name), create_bdd_output_file_name(QueryID,ClusterID,Iteration,Output_File_Name),
create_bdd_file_name(QueryID,ClusterID,BDD_File_Name), create_bdd_file_name(QueryID,ClusterID,BDD_File_Name),
convert_filename_to_problog_path('problogbdd_lfi',Absolute_Name), convert_filename_to_problog_path('simplecudd_lfi',Absolute_Name),
atomic_concat([Absolute_Name, atomic_concat([Absolute_Name,
' -i "', Input_File_Name, '"', ' -i "', Input_File_Name, '"',