Newest ProbLog version
This commit is contained in:
parent
9a45897308
commit
a442d888de
@ -707,6 +707,7 @@ bdd_optimization(N,EV,Decisions,Status) :-
|
||||
%(problog_flag(verbose,true) -> Debug = ' -d';Debug = ''), % messes up result parsing
|
||||
atomic_concat([ProblogBDD, Param, ' -l ',BDDFile,' -i ',BDDParFile,' -u ',UtilFile,' -m s',LocalPar,Forest,' -t ', BDDTime,' > ', ResultFile],Command),
|
||||
statistics(walltime,_),
|
||||
% format(user,'$ ~w~n',[Command]),
|
||||
shell(Command,Return),
|
||||
(Return =\= 0 ->
|
||||
Status = timeout
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-11-23 11:47:48 +0100 (Tue, 23 Nov 2010) $
|
||||
% $Revision: 5027 $
|
||||
% $Date: 2010-12-15 11:12:48 +0100 (Wed, 15 Dec 2010) $
|
||||
% $Revision: 5138 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
@ -350,16 +350,13 @@
|
||||
:- use_module('problog/mc_DNF_sampling').
|
||||
:- use_module('problog/timer').
|
||||
:- use_module('problog/utils').
|
||||
:- catch(use_module('problog/ad_converter'),_,true).
|
||||
:- use_module('problog/ad_converter').
|
||||
:- catch(use_module('problog/variable_elimination'),_,true).
|
||||
|
||||
% op attaching probabilities to facts
|
||||
:- op( 550, yfx, :: ).
|
||||
:- op( 550, fx, ?:: ).
|
||||
|
||||
% for annotated disjunctions
|
||||
% :- op(1149, yfx, <-- ).
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
% control predicates on various levels
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
@ -509,7 +506,7 @@ problog_dir(PD):- problog_path(PD).
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
init_global_params :-
|
||||
%grow_atom_table(1000000),
|
||||
grow_atom_table(1000000), % this will reserve us some memory, there are cases where you might need more
|
||||
|
||||
%%%%%%%%%%%%
|
||||
% working directory: all the temporary and output files will be located there
|
||||
@ -591,9 +588,9 @@ generate_atoms(N, A):-
|
||||
% dynamic predicate problog_predicate(Name,Arity) keeps track of predicates that already have wrapper clause
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
% converts annotated disjunctions - if loaded
|
||||
term_expansion_intern(A, B, C):-
|
||||
catch(term_expansion_intern_ad(A, B, C), _, false).
|
||||
% converts annotated disjunctions
|
||||
term_expansion_intern(A, Module, C):-
|
||||
term_expansion_intern_ad(A, Module, C).
|
||||
|
||||
% converts ?:: prefix to ? :: infix, as handled by other clause
|
||||
term_expansion_intern((Annotation::Fact), Module, ExpandedClause) :-
|
||||
@ -667,13 +664,12 @@ term_expansion_intern(Head :: Goal,Module,problog:ProbFact) :-
|
||||
)
|
||||
),
|
||||
|
||||
copy_term(((X,Distribution) :: Goal), ((X2,Distribution2) :: Goal2)),
|
||||
% bind_the_variable
|
||||
X2=Distribution2,
|
||||
X=Distribution,
|
||||
|
||||
% find position in term
|
||||
Goal2=..[Name|Args],
|
||||
once(nth1(Pos,Args,Distribution2)),
|
||||
Goal=..[Name|Args],
|
||||
once(nth1(Pos,Args,Distribution)),
|
||||
|
||||
length(Args,Arity),
|
||||
atomic_concat([problogcontinuous_,Name],ProblogName),
|
||||
@ -1165,31 +1161,20 @@ set_continuous_fact_parameters(ID,Parameters) :-
|
||||
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
% writing those facts with learnable parameters to File
|
||||
% writing all probabilistic and continuous facts to Filename
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
export_facts(Filename) :-
|
||||
open(Filename,'write',Handle),
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
( % go over all probabilistic facts
|
||||
P::Goal,
|
||||
format(Handle,'~w :: ~q.~n',[P,Goal]),
|
||||
forall(P::Goal,
|
||||
format(Handle,'~10f :: ~q.~n',[P,Goal])),
|
||||
|
||||
fail; % go to next prob. fact
|
||||
true
|
||||
),
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
( % go over all continuous facts
|
||||
continuous_fact(ID),
|
||||
get_continuous_fact_parameters(ID,Param),
|
||||
format(Handle,'~q. % ~q~n',[Param,ID]),
|
||||
|
||||
fail; % go to next cont. fact
|
||||
true
|
||||
),
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
forall(continuous_fact(ID),
|
||||
(
|
||||
get_continuous_fact_parameters(ID,Param),
|
||||
format(Handle,'~q. % ~q~n',[Param,ID])
|
||||
)
|
||||
),
|
||||
|
||||
close(Handle).
|
||||
|
||||
@ -1946,14 +1931,12 @@ disjoin_hybrid_proofs([GroundID|T]) :-
|
||||
intervals_partition(Intervals,Partition),
|
||||
|
||||
% go over all proofs where this fact occurs
|
||||
(
|
||||
hybrid_proof(ProofID,ID,GroundID,Interval),
|
||||
intervals_disjoin(Interval,Partition,PInterval),
|
||||
assertz(hybrid_proof_disjoint(ProofID,ID,GroundID,PInterval)),
|
||||
|
||||
fail; % go to next proof
|
||||
true
|
||||
),
|
||||
forall(hybrid_proof(ProofID,ID,GroundID,Interval),
|
||||
(
|
||||
intervals_disjoin(Interval,Partition,PInterval),
|
||||
assertz(hybrid_proof_disjoint(ProofID,ID,GroundID,PInterval))
|
||||
)
|
||||
),
|
||||
|
||||
disjoin_hybrid_proofs(T).
|
||||
|
||||
@ -1996,6 +1979,7 @@ problog_low(_, _, LP, Status) :-
|
||||
timer_stop(sld_time,SLD_Time),
|
||||
problog_var_set(sld_time, SLD_Time),
|
||||
nb_getval(problog_completed_proofs, Trie_Completed_Proofs),
|
||||
%print_nested_ptree(Trie_Completed_Proofs),
|
||||
eval_dnf(Trie_Completed_Proofs, LP, Status),
|
||||
(problog_flag(verbose, true)->
|
||||
problog_statistics
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-10-13 17:09:47 +0200 (Wed, 13 Oct 2010) $
|
||||
% $Revision: 4915 $
|
||||
% $Date: 2010-12-13 18:15:14 +0100 (Mon, 13 Dec 2010) $
|
||||
% $Revision: 5125 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
@ -214,51 +214,64 @@
|
||||
]).
|
||||
|
||||
% general yap modules
|
||||
:- use_module(library(lists),[reverse/2]).
|
||||
:- use_module(library(lists),[reverse/2,member/2,append/3]).
|
||||
|
||||
:- use_module(flags).
|
||||
|
||||
:- style_check(all).
|
||||
:- yap_flag(unknown,error).
|
||||
|
||||
:- discontiguous user:ad_intern/2.
|
||||
|
||||
:- op( 550, yfx, :: ).
|
||||
|
||||
% for annotated disjunctions
|
||||
:- op(1149, yfx, <-- ).
|
||||
|
||||
:- initialization(problog_define_flag(show_ad_compilation,problog_flag_validate_boolean,'show compiled code for ADs',false,annotated_disjunctions)).
|
||||
:- initialization(problog_define_flag(ad_cpl_semantics,problog_flag_validate_boolean,'use CP-logics semantics for ADs',true,annotated_disjunctions)).
|
||||
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
term_expansion_intern_ad( (Head<--Body),Module,ad_intern((Head<--Body),ID)) :-
|
||||
proper_tunable_annotated_disjunction(Head),
|
||||
!,
|
||||
compile_tunable_annotated_disjunction(Head,Body,Facts,Bodies,ID),
|
||||
assert_all_ad_facts(Facts,Module),
|
||||
assert_all_ad_bodies(Bodies,Module).
|
||||
term_expansion_intern_ad( (Head<--Body),Module,ad_intern((Head<--Body),ID)) :-
|
||||
proper_annotated_disjunction(Head),
|
||||
!,
|
||||
compile_annotated_disjunction(Head,Body,Facts,Bodies,ID),
|
||||
assert_all_ad_facts(Facts,Module),
|
||||
assert_all_ad_bodies(Bodies,Module).
|
||||
problog_flag(ad_cpl_semantics,AD_CPL_Semantics),
|
||||
(
|
||||
proper_tunable_annotated_disjunction(Head)
|
||||
->
|
||||
compile_tunable_annotated_disjunction(Head,Body,Facts,Bodies,ID,AD_CPL_Semantics);
|
||||
(
|
||||
proper_annotated_disjunction(Head),
|
||||
compile_annotated_disjunction(Head,Body,Facts,Bodies,ID,AD_CPL_Semantics)
|
||||
)
|
||||
),
|
||||
|
||||
forall(member(F,Facts),(once(problog:term_expansion_intern(F,Module,Atom)),
|
||||
assertz(problog:Atom))),
|
||||
forall(member(B,Bodies),assertz(Module:B)),
|
||||
|
||||
problog_flag(show_ad_compilation,Show_AD_compilation),
|
||||
|
||||
(
|
||||
Show_AD_compilation==true
|
||||
->
|
||||
(
|
||||
format('Compiling the annotated disjunction~n ~q~ninto the following code~n',[(Head<--Body)]),
|
||||
format('================================================~n',[]),
|
||||
forall(member(F,Facts),format(' ~q.~n',[F])),
|
||||
format(' - - - - - - - - - - - - - - - - - - - - - - ~n',[]),
|
||||
forall(member(B,Bodies),format(' ~q.~n',[B])),
|
||||
format('================================================~2n',[])
|
||||
);
|
||||
true
|
||||
).
|
||||
|
||||
term_expansion_intern_ad( (Head<--Body),_,_) :-
|
||||
format_to_chars('Error at compiling the annotated disjunction ~q<--Body.',[Head,Body],Error),
|
||||
print_message(error,Error),
|
||||
fail.
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
assert_all_ad_facts([],_).
|
||||
assert_all_ad_facts([F|T],Module) :-
|
||||
once(problog:term_expansion_intern(F,Module,Atom)),
|
||||
assertz(problog:Atom),
|
||||
assert_all_ad_facts(T,Module).
|
||||
|
||||
assert_all_ad_bodies([],_).
|
||||
assert_all_ad_bodies([B|T],Module) :-
|
||||
assertz(Module:B),
|
||||
assert_all_ad_bodies(T,Module).
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
@ -303,22 +316,36 @@ proper_tunable_annotated_disjunction((X;Y)) :-
|
||||
%
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
compile_tunable_annotated_disjunction(Head,Body,Facts2,Bodies2,Extra_ID) :-
|
||||
compile_tunable_annotated_disjunction(Head,Body,Facts2,Bodies2,Extra_ID,AD_CPL_Semantics) :-
|
||||
get_next_unique_id(Extra_ID),
|
||||
|
||||
(
|
||||
AD_CPL_Semantics==true
|
||||
->
|
||||
term_variables(Body,Body_Vars);
|
||||
Body_Vars=[]
|
||||
),
|
||||
|
||||
convert_a_tunable(Head,Extra_ID,[],Facts),
|
||||
convert_b(Head,Body,_NewBody,Extra_ID,[],Bodies),
|
||||
convert_a_tunable(Head,Extra_ID,[],Facts,Body_Vars),
|
||||
convert_b(Head,Body,_NewBody,Extra_ID,[],Bodies,Body_Vars),
|
||||
|
||||
reverse(Facts,Facts2),
|
||||
reverse(Bodies,Bodies2).
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
compile_annotated_disjunction(Head,Body,Facts2,Bodies2,Extra_ID) :-
|
||||
compile_annotated_disjunction(Head,Body,Facts2,Bodies2,Extra_ID,AD_CPL_Semantics) :-
|
||||
get_next_unique_id(Extra_ID),
|
||||
|
||||
(
|
||||
AD_CPL_Semantics==true
|
||||
->
|
||||
term_variables(Body,Body_Vars);
|
||||
Body_Vars=[]
|
||||
),
|
||||
|
||||
convert_a(Head,0.0,_Acc,Extra_ID,[],Facts),
|
||||
convert_b(Head,Body,_NewBody,Extra_ID,[],Bodies),
|
||||
convert_a(Head,0.0,_Acc,Extra_ID,[],Facts,Body_Vars),
|
||||
convert_b(Head,Body,_NewBody,Extra_ID,[],Bodies,Body_Vars),
|
||||
|
||||
reverse(Facts,Facts2),
|
||||
reverse(Bodies,Bodies2).
|
||||
@ -326,16 +353,17 @@ compile_annotated_disjunction(Head,Body,Facts2,Bodies2,Extra_ID) :-
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
convert_a((X;Y),OldAcc,Acc,Extra_ID,OldFacts,Facts) :-
|
||||
convert_a(X,OldAcc,NewAcc,Extra_ID,OldFacts,NewFacts),
|
||||
convert_a(Y,NewAcc,Acc,Extra_ID,NewFacts,Facts).
|
||||
convert_a(P::Atom,OldAcc,NewAcc,Extra_ID,OldFacts,[P1::ProbFact|OldFacts]) :-
|
||||
convert_a((X;Y),OldAcc,Acc,Extra_ID,OldFacts,Facts,Body_Vars) :-
|
||||
convert_a(X,OldAcc,NewAcc,Extra_ID,OldFacts,NewFacts,Body_Vars),
|
||||
convert_a(Y,NewAcc,Acc,Extra_ID,NewFacts,Facts,Body_Vars).
|
||||
convert_a(P::Atom,OldAcc,NewAcc,Extra_ID,OldFacts,[P1::ProbFact|OldFacts],Body_Vars) :-
|
||||
Atom =.. [Functor|AllArguments],
|
||||
append(AllArguments,Body_Vars,NewAllArguments),
|
||||
length(AllArguments,Arity),
|
||||
|
||||
atomic_concat([mvs_fact_,Functor,'_',Arity,'_',Extra_ID],NewAtom),
|
||||
|
||||
ProbFact =.. [NewAtom|AllArguments],
|
||||
ProbFact =.. [NewAtom|NewAllArguments],
|
||||
(
|
||||
P=:=0
|
||||
->
|
||||
@ -351,29 +379,31 @@ convert_a(P::Atom,OldAcc,NewAcc,Extra_ID,OldFacts,[P1::ProbFact|OldFacts]) :-
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
convert_a_tunable((X;Y),Extra_ID,OldFacts,Facts) :-
|
||||
convert_a_tunable(X,Extra_ID,OldFacts,NewFacts),
|
||||
convert_a_tunable(Y,Extra_ID,NewFacts,Facts).
|
||||
convert_a_tunable(P::Atom,Extra_ID,OldFacts,[P::ProbFact|OldFacts]) :-
|
||||
convert_a_tunable((X;Y),Extra_ID,OldFacts,Facts,Body_Vars) :-
|
||||
convert_a_tunable(X,Extra_ID,OldFacts,NewFacts,Body_Vars),
|
||||
convert_a_tunable(Y,Extra_ID,NewFacts,Facts,Body_Vars).
|
||||
convert_a_tunable(P::Atom,Extra_ID,OldFacts,[P::ProbFact|OldFacts],Body_Vars) :-
|
||||
Atom =.. [Functor|AllArguments],
|
||||
append(AllArguments,Body_Vars,NewAllArguments),
|
||||
length(AllArguments,Arity),
|
||||
|
||||
atomic_concat([mvs_fact_,Functor,'_',Arity,'_',Extra_ID],NewAtom),
|
||||
|
||||
ProbFact =.. [NewAtom|AllArguments].
|
||||
ProbFact =.. [NewAtom|NewAllArguments].
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
convert_b((X;Y),OldBody,Body,ExtraID,OldBodies,Bodies) :-
|
||||
convert_b(X,OldBody,NewBody,ExtraID,OldBodies,NewBodies),
|
||||
convert_b(Y,NewBody,Body,ExtraID,NewBodies,Bodies).
|
||||
convert_b(_::Atom,OldBody,NewBody,Extra_ID,OldBodies,[(Atom:-ThisBody)|OldBodies]) :-
|
||||
convert_b((X;Y),OldBody,Body,ExtraID,OldBodies,Bodies,Body_Vars) :-
|
||||
convert_b(X,OldBody,NewBody,ExtraID,OldBodies,NewBodies,Body_Vars),
|
||||
convert_b(Y,NewBody,Body,ExtraID,NewBodies,Bodies,Body_Vars).
|
||||
convert_b(_::Atom,OldBody,NewBody,Extra_ID,OldBodies,[(Atom:-ThisBody)|OldBodies],Body_Vars) :-
|
||||
Atom =.. [Functor|AllArguments],
|
||||
append(AllArguments,Body_Vars,NewAllArguments),
|
||||
|
||||
length(AllArguments,Arity),
|
||||
atomic_concat([mvs_fact_,Functor,'_',Arity,'_',Extra_ID],NewFunctor),
|
||||
|
||||
ProbFact =.. [NewFunctor|AllArguments],
|
||||
ProbFact =.. [NewFunctor|NewAllArguments],
|
||||
tuple_append(OldBody,ProbFact,ThisBody),
|
||||
tuple_append(OldBody,problog_not(ProbFact),NewBody).
|
||||
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-09-28 21:04:43 +0200 (Tue, 28 Sep 2010) $
|
||||
% $Revision: 4838 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-09-28 21:04:43 +0200 (Tue, 28 Sep 2010) $
|
||||
% $Revision: 4838 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-09-28 21:04:43 +0200 (Tue, 28 Sep 2010) $
|
||||
% $Revision: 4838 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-09-28 21:04:43 +0200 (Tue, 28 Sep 2010) $
|
||||
% $Revision: 4838 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-09-28 21:04:43 +0200 (Tue, 28 Sep 2010) $
|
||||
% $Revision: 4838 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-10-11 14:14:11 +0200 (Mon, 11 Oct 2010) $
|
||||
% $Revision: 4892 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-09-28 21:04:43 +0200 (Tue, 28 Sep 2010) $
|
||||
% $Revision: 4838 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-11-03 19:13:53 +0100 (Wed, 03 Nov 2010) $
|
||||
% $Revision: 4986 $
|
||||
% $Date: 2010-12-16 13:33:43 +0100 (Thu, 16 Dec 2010) $
|
||||
% $Revision: 5156 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
@ -211,9 +211,25 @@
|
||||
|
||||
:- module(nestedtries, [nested_trie_to_depth_breadth_trie/4]).
|
||||
|
||||
:- use_module(library(ordsets), [list_to_ord_set/2, ord_subset/2]). % this two might be better to do a custom fast implementation
|
||||
:- use_module(library(lists), [memberchk/2, delete/3]).
|
||||
:- use_module(library(tries), [trie_to_depth_breadth_trie/6, trie_get_depth_breadth_reduction_entry/1, trie_dup/2, trie_close/1, trie_open/1, trie_replace_nested_trie/3, trie_remove_entry/1, trie_get_entry/2, trie_put_entry/3, trie_traverse/2]).
|
||||
:- use_module(library(ordsets), [list_to_ord_set/2,
|
||||
ord_subset/2,
|
||||
ord_union/3,
|
||||
ord_intersection/3]).
|
||||
:- use_module(library(lists), [append/3,
|
||||
memberchk/2,
|
||||
delete/3]).
|
||||
:- use_module(library(tries), [trie_to_depth_breadth_trie/6,
|
||||
trie_get_depth_breadth_reduction_entry/1,
|
||||
trie_dup/2,
|
||||
trie_close/1,
|
||||
trie_open/1,
|
||||
trie_replace_nested_trie/3,
|
||||
trie_remove_entry/1,
|
||||
trie_get_entry/2,
|
||||
trie_put_entry/3,
|
||||
trie_traverse/2,
|
||||
trie_traverse_mode/1,
|
||||
trie_usage/4]).
|
||||
|
||||
:- use_module(flags, [problog_define_flag/5, problog_flag/2]).
|
||||
|
||||
@ -221,18 +237,21 @@
|
||||
:- yap_flag(unknown,error).
|
||||
|
||||
:- initialization((
|
||||
% problog_define_flag(subset_check, problog_flag_validate_boolean, 'perform subset check in nested tries', true, nested_tries),
|
||||
problog_define_flag(loop_refine_ancs, problog_flag_validate_boolean, 'refine ancestors if no loop exists', true, nested_tries)
|
||||
% problog_define_flag(trie_preprocess, problog_flag_validate_boolean, 'perform a preprocess step to nested tries', false, nested_tries),
|
||||
% 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)
|
||||
problog_define_flag(subset_check, problog_flag_validate_boolean, 'perform subset check in nested tries', true, nested_tries),
|
||||
problog_define_flag(loop_refine_ancs, problog_flag_validate_boolean, 'refine ancestors if no loop exists', true, nested_tries),
|
||||
problog_define_flag(trie_preprocess, problog_flag_validate_boolean, 'perform a preprocess step to nested tries', false, nested_tries),
|
||||
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)
|
||||
)).
|
||||
|
||||
|
||||
trie_replace_entry(_Trie, Entry, _E, false):-
|
||||
!, trie_remove_entry(Entry).
|
||||
trie_replace_entry(_Trie, Entry, E, false):-
|
||||
trie_get_entry(Entry, Proof),
|
||||
memberchk(E, Proof), !,
|
||||
trie_remove_entry(Entry).
|
||||
trie_replace_entry(Trie, Entry, E, true):-
|
||||
!, trie_get_entry(Entry, Proof),
|
||||
trie_get_entry(Entry, Proof),
|
||||
memberchk(E, Proof), !,
|
||||
delete(Proof, E, NewProof),
|
||||
(NewProof == [] ->
|
||||
trie_delete(Trie),
|
||||
@ -275,6 +294,12 @@ is_label(Label, ID):-
|
||||
Label = not(NestedLabel),
|
||||
is_label(NestedLabel, ID).
|
||||
|
||||
simplify(not(false), true):- !.
|
||||
simplify(not(true), false):- !.
|
||||
simplify(not(not(A)), B):-
|
||||
!, simplify(A, B).
|
||||
simplify(A, A).
|
||||
|
||||
% Ancestor related stuff
|
||||
|
||||
initialise_ancestors(0):-
|
||||
@ -289,6 +314,13 @@ add_to_ancestors(ID, Ancestors, NewAncestors):-
|
||||
is_list(Ancestors),
|
||||
list_to_ord_set([ID|Ancestors], NewAncestors).
|
||||
|
||||
ancestors_union(Ancestors1, Ancestors2, NewAncestors):-
|
||||
integer(Ancestors1), !,
|
||||
NewAncestors is Ancestors1 \/ Ancestors2.
|
||||
ancestors_union(Ancestors1, Ancestors2, NewAncestors):-
|
||||
is_list(Ancestors1),
|
||||
ord_union(Ancestors1, Ancestors2, NewAncestors).
|
||||
|
||||
ancestor_subset_check(SubAncestors, Ancestors):-
|
||||
integer(SubAncestors), !,
|
||||
SubAncestors is Ancestors /\ SubAncestors.
|
||||
@ -302,17 +334,61 @@ ancestor_loop_refine(Loop, Ancestors, []):-
|
||||
var(Loop), is_list(Ancestors), !.
|
||||
ancestor_loop_refine(true, Ancestors, Ancestors).
|
||||
|
||||
ancestor_child_refine(true, Ancestors, Childs, NewAncestors):-
|
||||
integer(Ancestors), !,
|
||||
NewAncestors is Ancestors /\ Childs.
|
||||
ancestor_child_refine(true, Ancestors, Childs, NewAncestors):-
|
||||
is_list(Ancestors), !,
|
||||
ord_intersection(Ancestors, Childs, NewAncestors).
|
||||
ancestor_child_refine(false, Ancestors, _, Ancestors).
|
||||
|
||||
% Cycle check related stuff
|
||||
% missing synonym check
|
||||
|
||||
cycle_check(ID, Ancestors):-
|
||||
get_negated_synonym_id(ID, SynID),
|
||||
cycle_check_intern(SynID, Ancestors).
|
||||
|
||||
cycle_check_intern(ID, Ancestors):-
|
||||
integer(Ancestors), !,
|
||||
Bit is 1 << (ID - 1),
|
||||
Bit is Bit /\ Ancestors.
|
||||
cycle_check(ID, Ancestors):-
|
||||
cycle_check_intern(ID, Ancestors):-
|
||||
is_list(Ancestors),
|
||||
memberchk(ID, Ancestors).
|
||||
|
||||
get_negated_synonym_id(ID, ID).
|
||||
get_negated_synonym_id(ID, NegID):-
|
||||
tabling:has_synonyms,
|
||||
recorded(problog_table, store(Pred, ID, _, _, _), _),
|
||||
Pred =.. [Name0|Args],
|
||||
atomic_concat(problog_, Name1, Name0),
|
||||
atomic_concat(Name, '_original', Name1),
|
||||
get_negated_name(Name, NotName1),
|
||||
atomic_concat([problog_, NotName1, '_original'], NotName),
|
||||
NegPred =.. [NotName|Args],
|
||||
recorded(problog_table, store(NegPred, NegID, _, _, _), _).
|
||||
|
||||
get_negated_name(Name, NotName1):-
|
||||
recorded(problog_table_synonyms, negated(Name, NotName1), _), !.
|
||||
get_negated_name(Name, NotName1):-
|
||||
recorded(problog_table_synonyms, negated(NotName1, Name), _).
|
||||
|
||||
trie_dup_reverse(Trie, DupTrie):-
|
||||
trie_open(DupTrie),
|
||||
trie_traverse_mode(backward),
|
||||
trie_dup_rev(Trie, DupTrie),
|
||||
trie_traverse_mode(forward).
|
||||
|
||||
trie_dup_rev(Trie, DupTrie):-
|
||||
\+ trie_usage(Trie, 0, 0, 0),
|
||||
trie_traverse(Trie, Entry),
|
||||
trie_get_entry(Entry, Term),
|
||||
trie_put_entry(DupTrie, Term, _),
|
||||
fail.
|
||||
trie_dup_rev(_, _).
|
||||
|
||||
|
||||
preprocess(Index, DepthBreadthTrie, OptimizationLevel, StartCount, FinalEndCount):-
|
||||
problog:problog_chktabled(Index, Trie), !,
|
||||
trie_dup(Trie, CopyTrie),
|
||||
@ -332,7 +408,7 @@ make_nested_trie_base_cases(Trie, t(ID), DepthBreadthTrie, OptimizationLevel, St
|
||||
make_nested_trie_base_cases(Trie, t(ID), DepthBreadthTrie, OptimizationLevel, EndCount, FinalEndCount, NewAncestors)
|
||||
;
|
||||
FinalEndCount = EndCount,
|
||||
get_set_trie(ID, Label, Ancestors)
|
||||
set_trie(ID, Label, Ancestors)
|
||||
).
|
||||
|
||||
nested_trie_to_depth_breadth_trie(Trie, DepthBreadthTrie, FinalLabel, OptimizationLevel):-
|
||||
@ -344,80 +420,69 @@ nested_trie_to_depth_breadth_trie(Trie, DepthBreadthTrie, FinalLabel, Optimizati
|
||||
StartCount = 0
|
||||
),
|
||||
initialise_ancestors(Ancestors),
|
||||
% initialise_ancestors(Childs),
|
||||
(problog_flag(loop_refine_ancs, true) ->
|
||||
trie_2_dbtrie_init(Trie, DepthBreadthTrie, OptimizationLevel, StartCount, _, Ancestors, FinalLabel, _)
|
||||
trie_2_dbtrie_init(Trie, DepthBreadthTrie, OptimizationLevel, StartCount, _, Ancestors, FinalLabel, _, _Childs)
|
||||
;
|
||||
trie_2_dbtrie_init(Trie, DepthBreadthTrie, OptimizationLevel, StartCount, _, Ancestors, FinalLabel, true)
|
||||
trie_2_dbtrie_init(Trie, DepthBreadthTrie, OptimizationLevel, StartCount, _, Ancestors, FinalLabel, true, _Childs)
|
||||
),
|
||||
eraseall(problog_trie_table).
|
||||
|
||||
trie_2_dbtrie_init(ID, DepthBreadthTrie, OptimizationLevel, StartCount, EndCount, Ancestors, Label, ContainLoop):-
|
||||
trie_2_dbtrie_init(ID, DepthBreadthTrie, OptimizationLevel, StartCount, EndCount, Ancestors, Label, ContainLoop, FinalChilds):-
|
||||
initialise_ancestors(Childs),
|
||||
get_trie_pointer(ID, Trie),
|
||||
trie_dup(Trie, CopyTrie),
|
||||
trie_2_dbtrie_intern(CopyTrie, DepthBreadthTrie, OptimizationLevel, StartCount, EndCount, Ancestors, Label, ContainLoop),
|
||||
trie_dup_reverse(Trie, CopyTrie),
|
||||
trie_2_dbtrie_intern(CopyTrie, DepthBreadthTrie, OptimizationLevel, StartCount, EndCount, Ancestors, Label, ContainLoop, Childs, FinalChilds),
|
||||
trie_close(CopyTrie).
|
||||
|
||||
trie_2_dbtrie_intern(Trie, DepthBreadthTrie, OptimizationLevel, StartCount, FinalEndCount, Ancestors, TrieLabel, ContainLoop):-
|
||||
trie_2_dbtrie_intern(Trie, DepthBreadthTrie, OptimizationLevel, StartCount, FinalEndCount, Ancestors, TrieLabel, ContainLoop, Childs, FinalChilds):-
|
||||
trie_to_depth_breadth_trie(Trie, DepthBreadthTrie, Label, OptimizationLevel, StartCount, EndCount),
|
||||
(is_trie(Label, ID) -> % Label might have issues with negation
|
||||
(is_trie(Label, ID) ->
|
||||
problog_flag(refine_anclst, ChildRefineAncestors),
|
||||
trie_get_depth_breadth_reduction_entry(NestedEntry),
|
||||
% check if Trie introduces a loop
|
||||
(cycle_check(ID, Ancestors) ->
|
||||
ContainLoop = true,
|
||||
NewLabel = false,
|
||||
NewEndCount = EndCount,
|
||||
initialise_ancestors(GrandChilds)
|
||||
; get_trie(ID, NewLabel, Ancestors) ->
|
||||
GrandChilds = Ancestors,
|
||||
NewEndCount = EndCount
|
||||
;
|
||||
% check if Trie is resolved and extract it
|
||||
(get_set_trie(ID, NewLabel, Ancestors) ->
|
||||
NewEndCount = EndCount
|
||||
;
|
||||
% calculate the nested trie
|
||||
add_to_ancestors(ID, Ancestors, NewAncestors), % to be able to support 2 representations
|
||||
trie_2_dbtrie_init(ID, DepthBreadthTrie, OptimizationLevel, EndCount, NewEndCount, NewAncestors, NewLabel, NewContainLoop),
|
||||
ancestor_loop_refine(NewContainLoop, Ancestors, RefinedAncestors),
|
||||
get_set_trie(ID, NewLabel, RefinedAncestors),
|
||||
ContainLoop = NewContainLoop
|
||||
)
|
||||
add_to_ancestors(ID, Ancestors, NewAncestors),
|
||||
trie_2_dbtrie_init(ID, DepthBreadthTrie, OptimizationLevel, EndCount, NewEndCount, NewAncestors, DerefLabel, NewContainLoop, GrandChilds),
|
||||
ancestor_loop_refine(NewContainLoop, Ancestors, RefinedAncestors1),
|
||||
ancestor_child_refine(ChildRefineAncestors, RefinedAncestors1, GrandChilds, RefinedAncestors),
|
||||
simplify(DerefLabel, NewLabel),
|
||||
set_trie(ID, NewLabel, RefinedAncestors),
|
||||
ContainLoop = NewContainLoop
|
||||
),
|
||||
trie_replace_entry(Trie, NestedEntry, t(ID), NewLabel), % should be careful to verify that it works also with not(t(ID))
|
||||
trie_2_dbtrie_intern(Trie, DepthBreadthTrie, OptimizationLevel, NewEndCount, FinalEndCount, Ancestors, TrieLabel, ContainLoop)
|
||||
trie_replace_entry(Trie, NestedEntry, t(ID), NewLabel),
|
||||
(ChildRefineAncestors ->
|
||||
add_to_ancestors(ID, Childs, NewChilds1),
|
||||
ancestors_union(NewChilds1, GrandChilds, NewChilds)
|
||||
;
|
||||
NewChilds = Childs
|
||||
),
|
||||
trie_2_dbtrie_intern(Trie, DepthBreadthTrie, OptimizationLevel, NewEndCount, FinalEndCount, Ancestors, TrieLabel, ContainLoop, NewChilds, FinalChilds)
|
||||
;
|
||||
% else we can terminate and return
|
||||
FinalEndCount = EndCount,
|
||||
TrieLabel = Label
|
||||
TrieLabel = Label,
|
||||
FinalChilds = Childs
|
||||
).
|
||||
|
||||
% predicate to check/remember resolved tries
|
||||
% no refiment of ancestor list included
|
||||
|
||||
get_trie_pointer(ID, Trie):-
|
||||
problog:problog_chktabled(ID, Trie), !.
|
||||
get_trie_pointer(Trie, Trie).
|
||||
|
||||
get_set_trie(Trie, Label, Ancestors):-
|
||||
get_trie(Trie, Label, Ancestors):-
|
||||
problog_flag(subset_check, true), !,
|
||||
recorded(problog_trie_table, store(Trie, StoredAncestors, Label), _),
|
||||
(problog_flag(subset_check, true) ->
|
||||
ancestor_subset_check(StoredAncestors, Ancestors)
|
||||
;
|
||||
StoredAncestors == Ancestors
|
||||
), !.
|
||||
get_set_trie(Trie, Label, Ancestors):-
|
||||
ground(Label),
|
||||
ancestor_subset_check(StoredAncestors, Ancestors).
|
||||
get_trie(Trie, Label, Ancestors):-
|
||||
recorded(problog_trie_table, store(Trie, StoredAncestors, Label), _),
|
||||
StoredAncestors == Ancestors.
|
||||
|
||||
set_trie(Trie, Label, Ancestors):-
|
||||
recordz(problog_trie_table, store(Trie, Ancestors, Label), _).
|
||||
|
||||
|
||||
% chk_negated([H|T], ID):-
|
||||
% simplify(H, not(t(ID))), !.
|
||||
% chk_negated([_|T], ID):-
|
||||
% chk_negated(T, ID).
|
||||
|
||||
|
||||
/*
|
||||
chk_negated([], ID, ID).
|
||||
chk_negated([H|T], ID, not(ID)):-
|
||||
simplify(H, not(t(ID))), !.
|
||||
chk_negated([H|T], ID, ID):-
|
||||
simplify(H, t(ID)), !.
|
||||
chk_negated([_|T], ID, FID):-
|
||||
chk_negated(T, ID, FID).*/
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-11-29 10:58:04 +0100 (Mon, 29 Nov 2010) $
|
||||
% $Revision: 5029 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-10-06 12:56:13 +0200 (Wed, 06 Oct 2010) $
|
||||
% $Revision: 4877 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-09-28 21:04:43 +0200 (Tue, 28 Sep 2010) $
|
||||
% $Revision: 4838 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-12-02 14:35:05 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5041 $
|
||||
% $Date: 2010-12-16 13:33:43 +0100 (Thu, 16 Dec 2010) $
|
||||
% $Revision: 5156 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
@ -282,12 +282,7 @@
|
||||
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),
|
||||
problog_define_flag(use_dec_trie, problog_flag_validate_boolean, 'use the decomposition method', false),
|
||||
problog_define_flag(subset_check, problog_flag_validate_boolean, 'perform subset check in nested tries', true),
|
||||
problog_define_flag(deref_terms, problog_flag_validate_boolean, 'deref BDD terms after last use', false),
|
||||
|
||||
problog_define_flag(trie_preprocess, problog_flag_validate_boolean, 'perform a preprocess step to nested tries', false),
|
||||
problog_define_flag(refine_anclst, problog_flag_validate_boolean, 'refine the ancestor list with their childs', false),
|
||||
problog_define_flag(anclst_represent,problog_flag_validate_in_list([list, integer]), 'represent the ancestor list', list)
|
||||
problog_define_flag(deref_terms, problog_flag_validate_boolean, 'deref BDD terms after last use', false)
|
||||
)).
|
||||
|
||||
|
||||
@ -1252,6 +1247,8 @@ add_to_vars(V):-
|
||||
|
||||
variables_in_dbtrie(Trie, []):-
|
||||
empty_ptree(Trie), !.
|
||||
variables_in_dbtrie(Trie, []):-
|
||||
trie_check_entry(Trie, [true], _R), !.
|
||||
variables_in_dbtrie(Trie, L):-
|
||||
all(V, variable_in_dbtrie(Trie,V), L).
|
||||
|
||||
@ -1339,10 +1336,11 @@ is_state(false).
|
||||
nested_trie_to_bdd_trie(A, B, OutputFile, OptimizationLevel, FileParam):-
|
||||
% trie_nested_to_depth_breadth_trie(A, B, LL, OptimizationLevel, problog:problog_chktabled),
|
||||
nested_trie_to_depth_breadth_trie(A, B, LL, OptimizationLevel),
|
||||
(is_label(LL) ->
|
||||
simplify(LL, FLL),
|
||||
(is_label(FLL) ->
|
||||
retractall(deref(_,_)),
|
||||
(problog_flag(deref_terms, true) ->
|
||||
asserta(deref(LL,no)),
|
||||
asserta(deref(FLL,no)),
|
||||
mark_for_deref(B),
|
||||
V = 3
|
||||
;
|
||||
@ -1358,7 +1356,7 @@ nested_trie_to_bdd_trie(A, B, OutputFile, OptimizationLevel, FileParam):-
|
||||
write('@BDD'), write(V), nl,
|
||||
write(VarCNT), nl,
|
||||
write(0), nl,
|
||||
(LL = not(NegL)->
|
||||
(FLL = not(NegL)->
|
||||
atomic_concat('L', NegStep, NegL),
|
||||
number_atom(NegStepN, NegStep),
|
||||
InterStep is NegStepN + 1,
|
||||
@ -1368,19 +1366,18 @@ nested_trie_to_bdd_trie(A, B, OutputFile, OptimizationLevel, FileParam):-
|
||||
write(FL), write(' = ~'), write(NegL), nl,
|
||||
write(FL), nl
|
||||
;
|
||||
atomic_concat('L', InterStep, LL),
|
||||
atomic_concat('L', InterStep, FLL),
|
||||
write(InterStep), nl,
|
||||
trie_write(B, LL),
|
||||
write(LL), nl
|
||||
trie_write(B, FLL),
|
||||
write(FLL), nl
|
||||
),
|
||||
told
|
||||
;
|
||||
(is_state(LL) ->
|
||||
(is_state(FLL) ->
|
||||
Edges = []
|
||||
;
|
||||
Edges = [LL]
|
||||
Edges = [FLL]
|
||||
),
|
||||
writeln(Edges),
|
||||
tell(FileParam),
|
||||
simplify_list(Edges, SEdges),
|
||||
bdd_vars_script(SEdges),
|
||||
@ -1390,12 +1387,11 @@ nested_trie_to_bdd_trie(A, B, OutputFile, OptimizationLevel, FileParam):-
|
||||
write(1), nl,
|
||||
write(0), nl,
|
||||
write(1), nl,
|
||||
(LL = not(_) ->
|
||||
(FLL = not(_) ->
|
||||
write('L1 = ~')
|
||||
;
|
||||
write('L1 = ')
|
||||
),
|
||||
simplify(LL, FLL),
|
||||
get_var_name(FLL, NLL),
|
||||
write(NLL),nl,
|
||||
write('L1'), nl,
|
||||
@ -1830,6 +1826,7 @@ ptree_decomposition(Trie, BDDFileName, VarFileName) :-
|
||||
tmpnam(TmpFile1),
|
||||
nb_setval(next_inter_step, 1),
|
||||
variables_in_dbtrie(Trie, T),
|
||||
|
||||
length(T, VarCnt),
|
||||
tell(VarFileName),
|
||||
bdd_vars_script(T),
|
||||
@ -1860,6 +1857,9 @@ get_next_inter_step(I):-
|
||||
decompose_trie(Trie, _, false):-
|
||||
empty_ptree(Trie), !.
|
||||
|
||||
decompose_trie(Trie, _, 'TRUE'):-
|
||||
trie_check_entry(Trie, [true], _R),!.
|
||||
|
||||
decompose_trie(Trie, [H|[]], Var):-
|
||||
trie_usage(Trie, 1, _, _),
|
||||
get_var_name(H, VarA),
|
||||
@ -1871,9 +1871,6 @@ decompose_trie(Trie, [H|[]], Var):-
|
||||
),
|
||||
!.
|
||||
|
||||
decompose_trie(Trie, _, 'TRUE'):-
|
||||
trie_check_entry(Trie, [true], _R),!.
|
||||
|
||||
decompose_trie(Trie, [H|_T], L3):-
|
||||
trie_open(TrieWith),
|
||||
trie_open(TrieWithNeg),
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-09-28 21:04:43 +0200 (Tue, 28 Sep 2010) $
|
||||
% $Revision: 4838 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-11-09 15:09:33 +0100 (Tue, 09 Nov 2010) $
|
||||
% $Revision: 4992 $
|
||||
% $Date: 2010-12-13 16:29:18 +0100 (Mon, 13 Dec 2010) $
|
||||
% $Revision: 5122 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
@ -298,12 +298,6 @@ problog_table_next_index(Index):-
|
||||
NIndex is Index + 1,
|
||||
nb_setval(problog_tabling_next_index, NIndex).
|
||||
|
||||
makeargs(0, []):-!.
|
||||
makeargs(N, [_Arg|L]):-
|
||||
N > 0,
|
||||
NN is N - 1,
|
||||
makeargs(NN, L).
|
||||
|
||||
problog_table(M:P) :- !,
|
||||
problog_table(P, M).
|
||||
problog_table(P) :-
|
||||
@ -311,21 +305,21 @@ problog_table(P) :-
|
||||
problog_table(P, M).
|
||||
|
||||
problog_table(M:P, _) :-
|
||||
problog_table(P, M).
|
||||
problog_table(P, M).
|
||||
problog_table((P1, P2), M) :-
|
||||
problog_table(P1, M),
|
||||
problog_table(P2, M).
|
||||
problog_table(P1, M),
|
||||
problog_table(P2, M).
|
||||
problog_table(Name/Arity, Module) :-
|
||||
makeargs(Arity, Args),
|
||||
Head =.. [Name|Args],
|
||||
\+ predicate_property(Module:Head, dynamic), !,
|
||||
throw(error('problog_table: Problog tabling currently requires the predicate to be declared dynamic and compiles it to static.')).
|
||||
length(Args,Arity),
|
||||
Head =.. [Name|Args],
|
||||
\+ predicate_property(Module:Head, dynamic), !,
|
||||
throw(error('problog_table: Problog tabling currently requires the predicate to be declared dynamic and compiles it to static.')).
|
||||
problog_table(Name/Arity, Module) :-
|
||||
makeargs(Arity, Args),
|
||||
Head =.. [Name|Args],
|
||||
atom_concat(['problog_', Name, '_original'], OriginalName),
|
||||
atom_concat(['problog_', Name, '_mctabled'], MCName),
|
||||
atom_concat(['problog_', Name, '_tabled'], ExactName),
|
||||
length(Args,Arity),
|
||||
Head =.. [Name|Args],
|
||||
atom_concat(['problog_', Name, '_original'], OriginalName),
|
||||
atom_concat(['problog_', Name, '_mctabled'], MCName),
|
||||
atom_concat(['problog_', Name, '_tabled'], ExactName),
|
||||
|
||||
% Monte carlo tabling
|
||||
catch((table(Module:MCName/Arity),
|
||||
@ -413,8 +407,8 @@ problog_table(Name/Arity, Module) :-
|
||||
erase(Ref),
|
||||
(empty_ptree(HashTrie) ->
|
||||
recordz(problog_table, store(OriginalPred, Hash, HashTrie, SuspTrie, fail), _NRef),
|
||||
delete_ptree(SuspTrie),
|
||||
fail % no justification exists
|
||||
delete_ptree(SuspTrie) %,
|
||||
%fail % no justification exists
|
||||
;
|
||||
recordz(problog_table, store(OriginalPred, Hash, HashTrie, SuspTrie, true), _NRef),
|
||||
merge_ptree(HashTrie, SuspTrie),
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-10-15 17:09:55 +0200 (Fri, 15 Oct 2010) $
|
||||
% $Revision: 4939 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-12-02 14:35:05 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: -1 $
|
||||
% $Date: 2010-12-15 15:52:58 +0100 (Wed, 15 Dec 2010) $
|
||||
% $Revision: 5144 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
@ -211,20 +211,21 @@
|
||||
slice_n/4,
|
||||
sorted_overlap_test/2,
|
||||
prefix_bdd_file_with_header/4,
|
||||
split_list/3]).
|
||||
split_list/3,
|
||||
succeeds_n_times/2,
|
||||
sum_forall/3]).
|
||||
|
||||
:- use_module(library(system), [delete_file/1]).
|
||||
|
||||
% load swi library, at some point vitor will make swi_expand_file_name/2 a built-in
|
||||
:- load_foreign_files([libplstream], [], initIO).
|
||||
|
||||
% load our own modules
|
||||
:- use_module(os).
|
||||
|
||||
:- meta_predicate succeeds_n_times(0,?), sum_forall(?,:,?).
|
||||
|
||||
|
||||
%========================================================================
|
||||
%=
|
||||
%=
|
||||
%= deletes File, if it doesn't exists, it will succeed silently
|
||||
%= delete_file_silently(+File)
|
||||
%========================================================================
|
||||
|
||||
delete_file_silently(File) :-
|
||||
@ -232,9 +233,10 @@ delete_file_silently(File) :-
|
||||
!.
|
||||
delete_file_silently(_).
|
||||
|
||||
|
||||
%========================================================================
|
||||
%=
|
||||
%=
|
||||
%= delete all the files in the list silently
|
||||
%= delete_files_silently(+List)
|
||||
%========================================================================
|
||||
|
||||
delete_files_silently([]).
|
||||
@ -242,23 +244,25 @@ delete_files_silently([H|T]) :-
|
||||
delete_file_silently(H),
|
||||
delete_files_silently(T).
|
||||
|
||||
|
||||
%========================================================================
|
||||
%=
|
||||
%=
|
||||
%= delete all the files matching a certain pattern silently
|
||||
%= i.e. delete_file_pattern_silently('~/a_path/b_path/','*.txt')
|
||||
%=
|
||||
%= delete_file_pattern_silently(+Path,+Pattern)
|
||||
%========================================================================
|
||||
|
||||
delete_file_pattern_silently(Path,Pattern) :-
|
||||
concat_path_with_filename(Path,Pattern,AbsolutePattern),
|
||||
swi_expand_file_name(AbsolutePattern,Files),
|
||||
|
||||
expand_file_name(AbsolutePattern,Files),
|
||||
delete_files_silently(Files).
|
||||
|
||||
|
||||
%========================================================================
|
||||
%= Split a list into the first n elements and the tail
|
||||
%= +List +Integer -Prefix -Residuum
|
||||
%= slice_n(+List, +Integer, -Prefix, -Residuum)
|
||||
%========================================================================
|
||||
|
||||
|
||||
slice_n([],_,[],[]) :-
|
||||
!.
|
||||
slice_n([H|T],N,[H|T2],T3) :-
|
||||
@ -268,9 +272,11 @@ slice_n([H|T],N,[H|T2],T3) :-
|
||||
slice_n(T,N2,T2,T3).
|
||||
slice_n(L,0,[],L).
|
||||
|
||||
|
||||
%========================================================================
|
||||
%= succeeds if the variable V appears exactly once in the term T
|
||||
%========================================================================
|
||||
|
||||
variable_in_term_exactly_once(T,V) :-
|
||||
term_variables(T,Vars),
|
||||
var_memberchk_once(Vars,V).
|
||||
@ -287,6 +293,7 @@ var_memberchk_none([H|T],V) :-
|
||||
var_memberchk_none(T,V).
|
||||
var_memberchk_none([],_).
|
||||
|
||||
|
||||
%========================================================================
|
||||
%= sorted_overlap_test(+L1,+L2)
|
||||
%= L1 and L2 are ground sorted lists
|
||||
@ -314,7 +321,7 @@ sorted_overlap_test([_|T1],[H2|T2]) :-
|
||||
prefix_bdd_file_with_header(BDD_File_Name,VarCount,IntermediateSteps,TmpFile) :-
|
||||
open(BDD_File_Name,write,H),
|
||||
% this is the header of the BDD script for problogbdd
|
||||
format(H, '@BDD1~n~q~n0~n~q~n',[VarCount,IntermediateSteps]),
|
||||
format(H, '@BDD1~n~w~n0~n~w~n',[VarCount,IntermediateSteps]),
|
||||
|
||||
% append the content of the file TmpFile
|
||||
open(TmpFile,read,H2),
|
||||
@ -333,12 +340,15 @@ prefix_bdd_file_with_header(BDD_File_Name,VarCount,IntermediateSteps,TmpFile) :-
|
||||
|
||||
|
||||
%========================================================================
|
||||
%= Split the list L in the two lists L1 and L2 such that
|
||||
%= append(L1,L2,L) holds.
|
||||
%=
|
||||
%= if length of L is even, then L1 and L2 will have the same length
|
||||
%= if length of L is odd, then L1 will be one element longer than L2
|
||||
%=
|
||||
%=
|
||||
%= split_list(+L,-L1,-L2)
|
||||
%========================================================================
|
||||
|
||||
|
||||
split_list([],[],[]).
|
||||
split_list([H|T],L1,L2) :-
|
||||
length([H|T],Len),
|
||||
@ -349,4 +359,35 @@ split_list_intern(0,L,[],L).
|
||||
split_list_intern(N,[H|T],[H|T1],L) :-
|
||||
N>0,
|
||||
N2 is N-1,
|
||||
split_list_intern(N2,T,T1,L).
|
||||
split_list_intern(N2,T,T1,L).
|
||||
|
||||
%========================================================================
|
||||
%= Counts how often Goal succeeds
|
||||
%= (taken from the YAP manual)
|
||||
%========================================================================
|
||||
|
||||
succeeds_n_times(Goal, Times) :-
|
||||
Counter = counter(0),
|
||||
( Goal,
|
||||
arg(1, Counter, N0),
|
||||
N is N0 + 1,
|
||||
nb_setarg(1, Counter, N),
|
||||
fail
|
||||
; arg(1, Counter, Times)
|
||||
).
|
||||
|
||||
|
||||
%========================================================================
|
||||
%=
|
||||
%=
|
||||
%========================================================================
|
||||
|
||||
sum_forall(X,Goal, Sum) :-
|
||||
Temp = sum(0),
|
||||
( Goal,
|
||||
arg(1, Temp, Sum0),
|
||||
Sum is Sum0+X,
|
||||
nb_setarg(1, Temp, Sum),
|
||||
fail
|
||||
; arg(1, Temp, Sum)
|
||||
).
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-12-02 14:35:05 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5041 $
|
||||
% $Date: 2010-12-14 20:30:07 +0100 (Tue, 14 Dec 2010) $
|
||||
% $Revision: 5134 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
@ -209,7 +209,10 @@
|
||||
create_known_values_file_name/2,
|
||||
create_bdd_file_name/3,
|
||||
create_bdd_input_file_name/2,
|
||||
create_bdd_output_file_name/4]).
|
||||
create_bdd_output_file_name/4,
|
||||
create_factprobs_file_name/2,
|
||||
create_test_predictions_file_name/2,
|
||||
create_training_predictions_file_name/2]).
|
||||
|
||||
|
||||
|
||||
@ -249,10 +252,7 @@ empty_output_directory :-
|
||||
delete_file_pattern_silently(Path,'values_*'),
|
||||
delete_file_pattern_silently(Path,'factprobs_*'),
|
||||
delete_file_pattern_silently(Path,'input_*'),
|
||||
delete_file_pattern_silently(Path,'trainpredictions_*'),
|
||||
delete_file_pattern_silently(Path,'testpredictions_*'),
|
||||
delete_file_pattern_silently(Path,'predictions_*').
|
||||
|
||||
empty_output_directory :-
|
||||
throw(error(problog_flag_does_not_exist(output_directory))).
|
||||
|
||||
@ -311,4 +311,47 @@ create_bdd_input_file_name(Iteration,Absolute_File_Name) :-
|
||||
atomic_concat(['input_',Iteration,'.txt'],File_Name),
|
||||
concat_path_with_filename(Path,File_Name,Absolute_File_Name).
|
||||
create_bdd_input_file_name(_,_) :-
|
||||
throw(error(problog_flag_does_not_exist(output_directory))).
|
||||
|
||||
%========================================================================
|
||||
%=
|
||||
%=
|
||||
%========================================================================
|
||||
|
||||
create_factprobs_file_name(Iteration,Absolute_File_Name) :-
|
||||
problog_flag(output_directory,Path),
|
||||
!,
|
||||
|
||||
atomic_concat(['factprobs_',Iteration,'.pl'],File_Name),
|
||||
concat_path_with_filename(Path,File_Name,Absolute_File_Name).
|
||||
create_factprobs_file_name(_,_) :-
|
||||
throw(error(problog_flag_does_not_exist(output_directory))).
|
||||
|
||||
|
||||
%========================================================================
|
||||
%=
|
||||
%=
|
||||
%========================================================================
|
||||
|
||||
create_test_predictions_file_name(Iteration,Absolute_File_Name) :-
|
||||
problog_flag(output_directory,Path),
|
||||
!,
|
||||
|
||||
atomic_concat(['predictions_test_',Iteration,'.pl'],File_Name),
|
||||
concat_path_with_filename(Path,File_Name,Absolute_File_Name).
|
||||
create_test_predictions_file_name(_,_) :-
|
||||
throw(error(problog_flag_does_not_exist(output_directory))).
|
||||
|
||||
%========================================================================
|
||||
%=
|
||||
%=
|
||||
%========================================================================
|
||||
|
||||
create_training_predictions_file_name(Iteration,Absolute_File_Name) :-
|
||||
problog_flag(output_directory,Path),
|
||||
!,
|
||||
|
||||
atomic_concat(['predictions_training_',Iteration,'.pl'],File_Name),
|
||||
concat_path_with_filename(Path,File_Name,Absolute_File_Name).
|
||||
create_training_predictions_file_name(_,_) :-
|
||||
throw(error(problog_flag_does_not_exist(output_directory))).
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-09-28 21:04:43 +0200 (Tue, 28 Sep 2010) $
|
||||
% $Revision: 4838 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-09-28 21:04:43 +0200 (Tue, 28 Sep 2010) $
|
||||
% $Revision: 4838 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
@ -2,8 +2,8 @@
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% $Date: 2010-10-05 18:15:57 +0200 (Tue, 05 Oct 2010) $
|
||||
% $Revision: 4876 $
|
||||
% $Date: 2010-12-02 15:20:15 +0100 (Thu, 02 Dec 2010) $
|
||||
% $Revision: 5043 $
|
||||
%
|
||||
% This file is part of ProbLog
|
||||
% http://dtai.cs.kuleuven.be/problog
|
||||
|
File diff suppressed because it is too large
Load Diff
Reference in New Issue
Block a user