ilbfgs
This commit is contained in:
parent
de153bd479
commit
2af4dae017
@ -58,11 +58,6 @@ update_query(QueryID,Symbol,What_To_Update) :-
|
|||||||
)
|
)
|
||||||
).
|
).
|
||||||
|
|
||||||
maplist_to_hash([], H0, H0).
|
|
||||||
maplist_to_hash([I-V|MapList], H0, Hash) :-
|
|
||||||
rb_insert(H0, V, I, H1),
|
|
||||||
maplist_to_hash(MapList, H1, Hash).
|
|
||||||
|
|
||||||
|
|
||||||
prob2log(_X,Slope,FactID,V) :-
|
prob2log(_X,Slope,FactID,V) :-
|
||||||
get_fact_probability(FactID, V0),
|
get_fact_probability(FactID, V0),
|
||||||
@ -73,14 +68,11 @@ log2prob(X,Slope,FactID,V) :-
|
|||||||
sigmoid(V0, Slope, V).
|
sigmoid(V0, Slope, V).
|
||||||
|
|
||||||
bind_maplist([], _Slope, _X).
|
bind_maplist([], _Slope, _X).
|
||||||
bind_maplist([Node-Pr|MapList], Slope, X) :-
|
bind_maplist([Node-(Node-Pr)|MapList], Slope, X) :-
|
||||||
Pr <== X[Node],
|
SigPr <== X[Node],
|
||||||
|
sigmoid(SigPr, Slope, Pr),
|
||||||
bind_maplist(MapList, Slope, X).
|
bind_maplist(MapList, Slope, X).
|
||||||
|
|
||||||
tree_to_grad([], _, Grad, Grad).
|
|
||||||
tree_to_grad([Node|Tree], H, Grad0, Grad) :-
|
|
||||||
node_to_gradient_node(Node, H, GNode),
|
|
||||||
tree_to_grad(Tree, H, [GNode|Grad0], Grad).
|
|
||||||
|
|
||||||
%get_prob(Node, Prob) :-
|
%get_prob(Node, Prob) :-
|
||||||
% query_probability(Node,Prob), !.
|
% query_probability(Node,Prob), !.
|
||||||
@ -97,58 +89,51 @@ gradient(_QueryID, l, _).
|
|||||||
gradient(QueryID, g, Slope) :-
|
gradient(QueryID, g, Slope) :-
|
||||||
recorded(QueryID, BDD, _),
|
recorded(QueryID, BDD, _),
|
||||||
query_gradients(BDD,Slope,I,Grad),
|
query_gradients(BDD,Slope,I,Grad),
|
||||||
% writeln(grad(QueryID:I:Grad)),
|
|
||||||
assert(query_gradient_intern(QueryID,I,p,Grad)),
|
assert(query_gradient_intern(QueryID,I,p,Grad)),
|
||||||
fail.
|
fail.
|
||||||
gradient(QueryID, g, Slope) :-
|
gradient(QueryID, g, Slope) :-
|
||||||
gradient(QueryID, l, Slope).
|
gradient(QueryID, l, Slope).
|
||||||
|
|
||||||
query_probability( DBDD, Slope, X, Prob) :-
|
query_probabilities( DBDD, Prob) :-
|
||||||
DBDD = bdd(Dir, Tree, MapList),
|
DBDD = bdd(Dir, Tree, _MapList),
|
||||||
bind_maplist(MapList, Slope, X),
|
findall(P, evalp(Tree,P), [Prob0]),
|
||||||
run_sp(Tree, Slope, 1.0, Prob0),
|
|
||||||
(Dir == 1 -> Prob0 = Prob ; Prob is 1.0-Prob0).
|
(Dir == 1 -> Prob0 = Prob ; Prob is 1.0-Prob0).
|
||||||
|
|
||||||
|
evalp( Tree, Prob0) :-
|
||||||
|
foldl(evalp, Tree, _, Prob0).
|
||||||
|
|
||||||
query_gradients(bdd(Dir, Tree, MapList),Slope,X,I,Grad) :-
|
query_gradients(bdd(Dir, Tree, MapList),I,IProb,Grad) :-
|
||||||
bind_maplist(MapList, Slope, X),
|
member(I-(_-IProb), MapList),
|
||||||
member(I-_, MapList),
|
% run_grad(Tree, I, Slope, 0.0, Grad0),
|
||||||
run_grad(Tree, I, Slope, 0.0, Grad0),
|
foldl( evalg(I), Tree, _, Grad0),
|
||||||
( Dir = 1 -> Grad = Grad0 ; Grad is -Grad0).
|
( Dir == 1 -> Grad = Grad0 ; Grad is -Grad0).
|
||||||
|
|
||||||
|
evalp( pn(P, _-X, PL, PR), _,P ):-
|
||||||
node_to_gradient_node(pp(P-G,X,L,R), H, gnodep(P,G,X,Id,PL,GL,PR,GR)) :-
|
P is X*PL+ (1.0-X)*(1.0-PR).
|
||||||
rb_lookup(X,Id,H),
|
evalp( pp(P, _-X, PL, PR), _,P ):-
|
||||||
(L == 1 -> GL=0, PL=1 ; L == 0 -> GL = 0, PL=0 ; L = PL-GL),
|
P is X*PL+ (1.0-X)*PR.
|
||||||
(R == 1 -> GR=0, PR=1 ; R == 0 -> GR = 0, PR=0 ; R = PR-GR).
|
|
||||||
node_to_gradient_node(pn(P-G,X,L,R), H, gnoden(P,G,X,Id,PL,GL,PR,GR)) :-
|
evalg( I, pp(P-G, J-X, L, R), _, G ):-
|
||||||
rb_lookup(X,Id,H),
|
( number(L) -> PL=L, GL = 0.0 ; L = PL-GL ),
|
||||||
(L == 1 -> GL=0, PL=1 ; L == 0 -> GL = 0, PL=0 ; L = PL-GL),
|
( number(R) -> PR=R, GR = 0.0 ; R = PR-GR ),
|
||||||
(R == 1 -> GR=0, PR=1 ; R == 0 -> GR = 0, PR=0 ; R = PR-GR).
|
P is X*PL+ (1.0-X)*PR,
|
||||||
|
(
|
||||||
run_sp([], _, P0, P0).
|
I == J
|
||||||
run_sp(gnodep(P,_G, X, _Id, PL, _GL, PR, _GR).Tree, Slope, _, PF) :-
|
->
|
||||||
EP = 1.0 / (1.0 + exp(-X * Slope) ),
|
G is X*GL+ (1.0-X)*GR+PL-PR
|
||||||
P is EP*PL+ (1.0-EP)*PR,
|
;
|
||||||
run_sp(Tree, Slope, P, PF).
|
G is X*GL+ (1.0-X)*GR
|
||||||
run_sp(gnoden(P,_G, X, _Id, PL, _GL, PR, _GR).Tree, Slope, _, PF) :-
|
).
|
||||||
EP is 1.0 / (1.0 + exp(-X * Slope) ),
|
evalg( I, pn(P-G, J-X, L, R), _,G ):-
|
||||||
P is EP*PL + (1.0-EP)*(1.0 - PR),
|
( number(L) -> PL=L, GL = 0.0 ; L = PL-GL ),
|
||||||
run_sp(Tree, Slope, P, PF).
|
( number(R) -> PR=R, GR = 0.0 ; R = PR-GR ),
|
||||||
|
P is X*PL+ (1.0-X)*(1.0-PR),
|
||||||
run_grad([], _I, _, G0, G0).
|
(
|
||||||
run_grad([gnodep(P,G, X, Id, PL, GL, PR, GR)|Tree], I, Slope, _, GF) :-
|
I == J
|
||||||
EP is 1.0/(1.0 + exp(-X * Slope)),
|
->
|
||||||
P is EP*PL+ (1.0-EP)*PR,
|
G is X*GL-(1.0-X)*GR+PL-(1-PR)
|
||||||
G0 is EP*GL + (1.0-EP)*GR,
|
;
|
||||||
% don' t forget the -X
|
G is X*GL- (1.0-X)*GR
|
||||||
( I == Id -> G is G0+(PL-PR)* EP*(1-EP)*Slope ; G = G0 ),
|
).
|
||||||
run_grad(Tree, I, Slope, G, GF).
|
|
||||||
run_grad([gnoden(P,G, X, Id, PL, GL, PR, GR)|Tree], I, Slope, _, GF) :-
|
|
||||||
EP is 1.0 / (1.0 + exp(-X * Slope) ),
|
|
||||||
P is EP*PL + (1.0-EP)*(1.0 - PR),
|
|
||||||
G0 is EP*GL - (1.0 - EP) * GR,
|
|
||||||
( I == Id -> G is G0+(PL+PR-1)*EP*(1-EP)*Slope ; G = G0 ),
|
|
||||||
run_grad(Tree, I, Slope, G, GF).
|
|
||||||
|
|
||||||
|
|
||||||
|
@ -17,7 +17,7 @@
|
|||||||
:- use_module('../problog_lbfgs').
|
:- use_module('../problog_lbfgs').
|
||||||
|
|
||||||
|
|
||||||
%% :- if(true).
|
:- if(true).
|
||||||
|
|
||||||
:- use_module('kbgraph').
|
:- use_module('kbgraph').
|
||||||
|
|
||||||
@ -27,9 +27,9 @@
|
|||||||
%%%%
|
%%%%
|
||||||
% definition of acyclic path using list of visited nodes
|
% definition of acyclic path using list of visited nodes
|
||||||
|
|
||||||
%:- else.
|
:- else.
|
||||||
/*
|
|
||||||
:- set_problog_flag(init_method,(Query,K,Bdd,problog:problog_exact_lbdd(Query,Bdd))).
|
:- Query=path(X,Y), set_problog_flag(init_method,(Query,K,Bdd,problog:problog_exact_lbdd(Query,Bdd))).
|
||||||
|
|
||||||
path(X,Y) :- path(X,Y,[X],_).
|
path(X,Y) :- path(X,Y,[X],_).
|
||||||
|
|
||||||
@ -48,8 +48,8 @@ edge(X,Y) :- dir_edge(X,Y).
|
|||||||
absent(_,[]).
|
absent(_,[]).
|
||||||
absent(X,[Y|Z]):-X \= Y, absent(X,Z).
|
absent(X,[Y|Z]):-X \= Y, absent(X,Z).
|
||||||
|
|
||||||
%:- endif.
|
:- endif.
|
||||||
*/
|
|
||||||
%%%%
|
%%%%
|
||||||
% probabilistic facts
|
% probabilistic facts
|
||||||
% - probability represented by t/1 term means learnable parameter
|
% - probability represented by t/1 term means learnable parameter
|
||||||
@ -84,12 +84,12 @@ example(13,path(4,5),0.57).
|
|||||||
example(14,path(4,6),0.51).
|
example(14,path(4,6),0.51).
|
||||||
example(15,path(5,6),0.69).
|
example(15,path(5,6),0.69).
|
||||||
% some examples for learning from proofs:
|
% some examples for learning from proofs:
|
||||||
%example(16,(dir_edge(2,3),dir_edge(2,6),dir_edge(6,5),dir_edge(5,4)),0.032).
|
/*example(16,(dir_edge(2,3),dir_edge(2,6),dir_edge(6,5),dir_edge(5,4)),0.032).
|
||||||
%example(17,(dir_edge(1,6),dir_edge(2,6),dir_edge(2,3),dir_edge(3,4)),0.168).
|
example(17,(dir_edge(1,6),dir_edge(2,6),dir_edge(2,3),dir_edge(3,4)),0.168).
|
||||||
%example(18,(dir_edge(5,3),dir_edge(5,4)),0.14).
|
example(18,(dir_edge(5,3),dir_edge(5,4)),0.14).
|
||||||
%example(19,(dir_edge(2,6),dir_edge(6,5)),0.2).
|
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).
|
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
|
% note: ID namespace is shared with training example IDs
|
||||||
|
@ -217,7 +217,7 @@
|
|||||||
:- yap_flag(unknown,error).
|
:- yap_flag(unknown,error).
|
||||||
|
|
||||||
% load modules from the YAP library
|
% load modules from the YAP library
|
||||||
:- use_module(library(lists), [member/2,max_list/2, min_list/2, sum_list/2]).
|
:- use_module(library(lists), [member/2,max_list/2, min_list/2, sum_list/2, reverse/2]).
|
||||||
:- use_module(library(system), [file_exists/1, shell/2]).
|
:- use_module(library(system), [file_exists/1, shell/2]).
|
||||||
:- use_module(library(rbtrees)).
|
:- use_module(library(rbtrees)).
|
||||||
:- use_module(library(lbfgs)).
|
:- use_module(library(lbfgs)).
|
||||||
@ -572,20 +572,22 @@ init_one_query(QueryID,Query,_Type) :-
|
|||||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||||
% if BDD file does not exist, call ProbLog
|
% if BDD file does not exist, call ProbLog
|
||||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||||
|
fail,
|
||||||
problog_flag(init_method,(Query,N,Bdd,user:graph2bdd(Query,N,Bdd))),
|
problog_flag(init_method,(Query,N,Bdd,user:graph2bdd(Query,N,Bdd))),
|
||||||
!,
|
!,
|
||||||
b_setval(problog_required_keep_ground_ids,false),
|
b_setval(problog_required_keep_ground_ids,false),
|
||||||
(QueryID mod 100 =:= 0 ->writeln(QueryID) ; true),
|
(QueryID mod 100 =:= 0 ->writeln(QueryID) ; true),
|
||||||
Bdd = bdd(Dir, Tree,MapList),
|
Bdd = bdd(Dir, Tree0,MapList),
|
||||||
user:graph2bdd(Query,N,Bdd),
|
user:graph2bdd(Query,N,Bdd),
|
||||||
rb_new(H0),
|
reverse(Tree0,Tree),
|
||||||
maplist_to_hash(MapList, H0, Hash),
|
%rb_new(H0),
|
||||||
tree_to_grad(Tree, Hash, [], Grad),
|
%maplist_to_hash(MapList, H0, Hash),
|
||||||
|
%tree_to_grad(Tree, Hash, [], Grad),
|
||||||
% ;
|
% ;
|
||||||
% Bdd = bdd(-1,[],[]),
|
% Bdd = bdd(-1,[],[]),
|
||||||
% Grad=[]
|
% Grad=[]
|
||||||
write('.'),
|
write('.'),
|
||||||
recordz(QueryID,bdd(Dir, Grad, MapList),_).
|
recordz(QueryID,bdd(Dir, Tree, MapList),_).
|
||||||
init_one_query(QueryID,Query,_Type) :-
|
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]),
|
||||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||||
@ -594,15 +596,16 @@ init_one_query(QueryID,Query,_Type) :-
|
|||||||
b_setval(problog_required_keep_ground_ids,false),
|
b_setval(problog_required_keep_ground_ids,false),
|
||||||
problog_flag(init_method,(Query,_K,Bdd,Call)),
|
problog_flag(init_method,(Query,_K,Bdd,Call)),
|
||||||
!,
|
!,
|
||||||
Bdd = bdd(Dir, Tree, MapList),
|
Bdd = bdd(Dir, Tree0, MapList),
|
||||||
% trace,
|
% trace,
|
||||||
once(Call),
|
once(Call),
|
||||||
rb_new(H0),
|
reverse(Tree0,Tree),
|
||||||
maplist_to_hash(MapList, H0, Hash),
|
%rb_new(H0),
|
||||||
|
%maplist_to_hash(MapList, H0, Hash),
|
||||||
%Tree \= [],
|
%Tree \= [],
|
||||||
% writeln(Dir:Tree:MapList),
|
% writeln(Dir:Tree:MapList),
|
||||||
tree_to_grad(Tree, Hash, [], Grads),
|
%tree_to_grad(Tree, Hash, [], Grads),
|
||||||
recordz(QueryID,bdd(Dir, Grads, MapList),_).
|
recordz(QueryID,bdd(Dir, Tree, MapList),_).
|
||||||
|
|
||||||
%========================================================================
|
%========================================================================
|
||||||
%=
|
%=
|
||||||
@ -780,22 +783,11 @@ inv_sigmoid(T,Slope,InvSig) :-
|
|||||||
%= probabilities of the examples have to be recalculated
|
%= probabilities of the examples have to be recalculated
|
||||||
%========================================================================
|
%========================================================================
|
||||||
|
|
||||||
:- dynamic index/2.
|
|
||||||
|
|
||||||
save_old_probabilities.
|
save_old_probabilities.
|
||||||
|
|
||||||
mkindex :-
|
|
||||||
retractall(index(_,_)),
|
|
||||||
findall(FactID,tunable_fact(FactID,_GroundTruth),L),
|
|
||||||
foldl(mkindex, L, 0, Count),
|
|
||||||
assert(count_tunables(Count)).
|
|
||||||
|
|
||||||
mkindex(Key,I,I1) :-
|
|
||||||
I1 is I+1,
|
|
||||||
assert(index(Key,I),I1).
|
|
||||||
% vsc: avoid silly search
|
% vsc: avoid silly search
|
||||||
gradient_descent :-
|
gradient_descent :-
|
||||||
mkindex,
|
|
||||||
problog_flag(sigmoid_slope,Slope),
|
problog_flag(sigmoid_slope,Slope),
|
||||||
% current_iteration(Iteration),
|
% current_iteration(Iteration),
|
||||||
findall(FactID,tunable_fact(FactID,_GroundTruth),L),
|
findall(FactID,tunable_fact(FactID,_GroundTruth),L),
|
||||||
@ -808,8 +800,7 @@ mkindex,
|
|||||||
lbfgs_finalize(Solver).
|
lbfgs_finalize(Solver).
|
||||||
|
|
||||||
set_fact(FactID, Slope, P ) :-
|
set_fact(FactID, Slope, P ) :-
|
||||||
index(FactID, I),
|
X <== P[FactID],
|
||||||
X <== P[I],
|
|
||||||
sigmoid(X, Slope, Pr),
|
sigmoid(X, Slope, Pr),
|
||||||
(Pr > 0.99
|
(Pr > 0.99
|
||||||
->
|
->
|
||||||
@ -834,16 +825,26 @@ set_tunable(I,Slope,P) :-
|
|||||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||||
user:evaluate(LLH_Training_Queries, X,Grad,N,_,_) :-
|
user:evaluate(LLH_Training_Queries, X,Grad,N,_,_) :-
|
||||||
%Handle = user_error,
|
%Handle = user_error,
|
||||||
|
N1 is N-1,
|
||||||
|
forall(between(0,N1,I),(Grad[I]<==0.0)),
|
||||||
go( X,Grad, LLs),
|
go( X,Grad, LLs),
|
||||||
sum_list( LLs, LLH_Training_Queries),
|
sum_list( LLs, LLH_Training_Queries).
|
||||||
writeln(LLH_Training_Queries).
|
|
||||||
|
test :-
|
||||||
|
S =.. [f,0-0.9,1-0.8,2-0.6,3-0.7,4-0.5,5-0.4,6-0.7,7-0.2],
|
||||||
|
functor(S,_,N), N1 is N-1,
|
||||||
|
problog_flag(sigmoid_slope,Slope),
|
||||||
|
X <== array[N] of floats,
|
||||||
|
Grad <== array[N] of floats,
|
||||||
|
forall(between(0,N1,I),(Grad[I]<==0.0)),
|
||||||
|
forall(between(1,N,I),(arg(I,S,_-V),inv_sigmoid(V,Slope,V0),I1 is I-1,X[I1]<==V0)),
|
||||||
|
findall(
|
||||||
|
LL,
|
||||||
|
compute_gradient(Grad, X, Slope,LL),
|
||||||
|
LLs
|
||||||
|
), sum_list( LLs, LLH_Training_Queries), writeln(LLH_Training_Queries:LLs ),forall(between(0,N1,I),(G<==Grad[I],writeln(I=G))).
|
||||||
|
|
||||||
|
|
||||||
update_tunables(X) :-
|
|
||||||
tunable_fact(FactID,GroundTruth),
|
|
||||||
set_fact_probability(ID,Prob),
|
|
||||||
fail.
|
|
||||||
update_tunables.
|
|
||||||
|
|
||||||
go( X,Grad, LLs) :-
|
go( X,Grad, LLs) :-
|
||||||
problog_flag(sigmoid_slope,Slope),
|
problog_flag(sigmoid_slope,Slope),
|
||||||
@ -851,29 +852,27 @@ go( X,Grad, LLs) :-
|
|||||||
LL,
|
LL,
|
||||||
compute_gradient(Grad, X, Slope,LL),
|
compute_gradient(Grad, X, Slope,LL),
|
||||||
LLs
|
LLs
|
||||||
),
|
|
||||||
forall(tunable_fact(FactID,_GroundTruth),
|
|
||||||
set_fact( FactID, Slope, X)
|
|
||||||
).
|
).
|
||||||
|
|
||||||
|
|
||||||
compute_gradient( Grad, X, Slope, LL) :-
|
compute_gradient( Grad, X, Slope, LL) :-
|
||||||
|
|
||||||
user:example(QueryID,_Query,QueryProb),
|
user:example(QueryID,_Query,QueryProb),
|
||||||
recorded(QueryID,BDD,_),
|
recorded(QueryID,BDD,_),
|
||||||
query_probability( BDD, Slope, X, BDDProb),
|
BDD = bdd(_,_,MapList),
|
||||||
|
bind_maplist(MapList, Slope, X),
|
||||||
|
query_probabilities( BDD, BDDProb),
|
||||||
LL is (BDDProb-QueryProb)*(BDDProb-QueryProb),
|
LL is (BDDProb-QueryProb)*(BDDProb-QueryProb),
|
||||||
retractall( query_probability_intern( QueryID, _) ),
|
retractall( query_probability_intern( QueryID, _) ),
|
||||||
assert( query_probability_intern( QueryID,BDDProb )),
|
assert( query_probability_intern( QueryID,BDDProb )),
|
||||||
forall(
|
forall(
|
||||||
query_gradients(BDD,Slope,X,I,GradValue),
|
query_gradients(BDD,I,IProb,GradValue),
|
||||||
gradient_pair(BDDProb, QueryProb, Grad, GradValue, Slope, X, I)
|
gradient_pair(BDDProb, QueryProb, Grad, GradValue, I, IProb)
|
||||||
).
|
).
|
||||||
|
|
||||||
gradient_pair(BDDProb, QueryProb, Grad, GradValue, Slope, X, I) :-
|
gradient_pair(BDDProb, QueryProb, Grad, GradValue, I, Prob) :-
|
||||||
G0 <== Grad[I],
|
G0 <== Grad[I],
|
||||||
log2prob(X,Slope,I,Prob),
|
GN is G0-GradValue*Prob*(1-Prob)*2*(QueryProb-BDDProb),
|
||||||
%writeln(Prob=BDDProb),
|
|
||||||
GN is G0+GradValue*BDDProb*(1-BDDProb)*2*(QueryProb-BDDProb),
|
|
||||||
Grad[I] <== GN.
|
Grad[I] <== GN.
|
||||||
|
|
||||||
wrap( X, Grad, GradCount) :-
|
wrap( X, Grad, GradCount) :-
|
||||||
@ -890,10 +889,10 @@ wrap( _X, _Grad, _GradCount).
|
|||||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||||
% stop calculate gradient
|
% stop calculate gradient
|
||||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||||
user:progress(FX,_X,_G, _X_Norm,_G_Norm,_Step,_N,CurrentIteration,_Ls,-1) :-
|
user:progress(FX,_X,_G, _X_Norm,_G_Norm,_Step,_N,_CurrentIteration,_Ls,-1) :-
|
||||||
FX < 0, !,
|
FX < 0, !,
|
||||||
format('stopped on bad FX=~4f~n',[FX]).
|
format('stopped on bad FX=~4f~n',[FX]).
|
||||||
user:progress(FX,X,_G,X_Norm,G_Norm,Step,_N, CurrentIteration,Ls,0) :-
|
user:progress(FX,X,_G,X_Norm,G_Norm,Step,_N, Iteration,Ls,0) :-
|
||||||
assertz(current_iteration(Iteration)),
|
assertz(current_iteration(Iteration)),
|
||||||
problog_flag(sigmoid_slope,Slope),
|
problog_flag(sigmoid_slope,Slope),
|
||||||
forall(tunable_fact(FactID,_GroundTruth), set_tunable(FactID,Slope,X)),
|
forall(tunable_fact(FactID,_GroundTruth), set_tunable(FactID,Slope,X)),
|
||||||
@ -901,7 +900,7 @@ user:progress(FX,X,_G,X_Norm,G_Norm,Step,_N, CurrentIteration,Ls,0) :-
|
|||||||
save_model,
|
save_model,
|
||||||
X0 <== X[0], sigmoid(X0,Slope,P0),
|
X0 <== X[0], sigmoid(X0,Slope,P0),
|
||||||
X1 <== X[1], sigmoid(X1,Slope,P1),
|
X1 <== X[1], sigmoid(X1,Slope,P1),
|
||||||
format('~d. Iteration : (x0,x1)=(~4f,~4f) f(X)=~4f |X|=~4f |X\'|=~4f Step=~4f Ls=~4f~n',[CurrentIteration,P0 ,P1,FX,X_Norm,G_Norm,Step,Ls]).
|
format('~d. Iteration : (x0,x1)=(~4f,~4f) f(X)=~4f |X|=~4f |X\'|=~4f Step=~4f Ls=~4f~n',[Iteration,P0 ,P1,FX,X_Norm,G_Norm,Step,Ls]).
|
||||||
|
|
||||||
|
|
||||||
%========================================================================
|
%========================================================================
|
||||||
|
Reference in New Issue
Block a user