This commit is contained in:
Vitor Santos Costa 2018-10-13 08:42:41 +01:00
parent 67cc23725f
commit a33f2be18b
5 changed files with 47 additions and 37 deletions

View File

@ -1,3 +1,9 @@
2:- use_module( library(lineutils) ).
3
4main :-
5 unix(argv[Dir,Out]),
6 open(Out,write,O),
:- module( prolog, [] ). 7 go(Dir,O).
9go(Dir,O) :-

View File

@ -27,13 +27,13 @@ ECLASS(RESOURCE_ERROR, "resource_error", 2)
/// bad text /// bad text
ECLASS(SYNTAX_ERROR_CLASS, "syntax_error", 1) ECLASS(SYNTAX_ERROR_CLASS, "syntax_error", 1)
/// OS or internal /// OS or internal
ECLASS(SYSTEM_ERROR_CLASS, "system_error", 2) ECLASS(SYSTEM_ERROR_CLASS, "system_error", 1)
/// bad typing /// bad typing
ECLASS(TYPE_ERROR, "type_error", 2) ECLASS(TYPE_ERROR, "type_error", 2)
/// should be unbound /// should be unbound
ECLASS(UNINSTANTIATION_ERROR_CLASS, "uninstantiation_error", 1) ECLASS(UNINSTANTIATION_ERROR_CLASS, "uninstantiation_error", 1)
/// escape hatch /// user defined escape hatch
ECLASS(EVENT, "event", 2) ECLASS(EVENT, "event", 1)
END_ERROR_CLASSES(); END_ERROR_CLASSES();

View File

@ -316,7 +316,7 @@ bool Yap_SetCurInpPos(
} }
Atom Yap_guessFileName(FILE *file, int sno, size_t max) { Atom Yap_guessFileName(FILE *file, int sno, size_t max) {
size_t maxs = Yap_Max(1023, max-1); size_t maxs = Yap_Max(1023, max - 1);
if (!file) { if (!file) {
Atom at = Yap_LookupAtom("mem"); Atom at = Yap_LookupAtom("mem");
return at; return at;
@ -329,24 +329,26 @@ Atom Yap_guessFileName(FILE *file, int sno, size_t max) {
int i = push_text_stack(); int i = push_text_stack();
#if __linux__ #if __linux__
char *path = Malloc(1024), *nameb = Malloc(maxs+1); char *path = Malloc(1024), *nameb = Malloc(maxs + 1);
size_t len; size_t len;
if ((len = snprintf(path, 1023, "/proc/self/fd/%d", f)) >= 0 && if ((len = snprintf(path, 1023, "/proc/self/fd/%d", f)) >= 0 &&
(len = readlink(path, nameb, maxs)) > 0) { (len = readlink(path, nameb, maxs)) > 0) {
nameb[len] = '\0'; nameb[len] = '\0';
Atom at = Yap_LookupAtom(nameb); Atom at = Yap_LookupAtom(nameb);
pop_text_stack(i); pop_text_stack(i);
return at; return at;
} }
#elif __APPLE__ #elif __APPLE__
char *nameb = Malloc(maxs + 1);
if (fcntl(f, F_GETPATH, nameb) != -1) { if (fcntl(f, F_GETPATH, nameb) != -1) {
Atom at = Yap_LookupAtom(nameb); Atom at = Yap_LookupAtom(nameb);
pop_text_stack(i); pop_text_stack(i);
return at; return at;
} }
#else #else
TCHAR *path = Malloc(MAX_PATH + 1); TCHAR *path = Malloc(MAX_PATH + 1), *nameb = Malloc(MAX_PATH + 1);
if (!GetFullPathName(path, MAX_PATH, path, NULL)) {
if (!GetFullPathName(path, MAX_PATH, nameb, NULL)) {
pop_text_stack(i); pop_text_stack(i);
return NULL; return NULL;
} else { } else {
@ -356,8 +358,8 @@ Atom Yap_guessFileName(FILE *file, int sno, size_t max) {
ptr += put_utf8(ptr, path[i]); ptr += put_utf8(ptr, path[i]);
*ptr = '\0'; *ptr = '\0';
Atom at = Yap_LookupAtom(nameb); Atom at = Yap_LookupAtom(nameb);
pop_text_stack(i); pop_text_stack(i);
return at; return at;
} }
#endif #endif
if (!StreamName(sno)) { if (!StreamName(sno)) {
@ -721,7 +723,7 @@ static Int cont_stream_property(USES_REGS1) { /* current_stream */
i = Yap_CheckAlias(AtomOfTerm(args[STREAM_PROPERTY_ALIAS].tvalue)); i = Yap_CheckAlias(AtomOfTerm(args[STREAM_PROPERTY_ALIAS].tvalue));
UNLOCK(GLOBAL_Stream[i].streamlock); UNLOCK(GLOBAL_Stream[i].streamlock);
if (i < 0 || !Yap_unify(ARG1, Yap_MkStream(i))) { if (i < 0 || !Yap_unify(ARG1, Yap_MkStream(i))) {
free(args); free(args);
cut_fail(); cut_fail();
} }
det = true; det = true;
@ -1001,11 +1003,11 @@ static void CloseStream(int sno) {
CACHE_REGS CACHE_REGS
// fflush(NULL); // fflush(NULL);
// __android_log_print(ANDROID_LOG_INFO, "YAPDroid", "close stream <%d>", // __android_log_print(ANDROID_LOG_INFO, "YAPDroid", "close stream <%d>",
// sno); // sno);
VFS_t *me; VFS_t *me;
//fprintf( stderr, "- %d\n",sno); // fprintf( stderr, "- %d\n",sno);
if ((me = GLOBAL_Stream[sno].vfs) != NULL && if ((me = GLOBAL_Stream[sno].vfs) != NULL &&
GLOBAL_Stream[sno].file == NULL) { GLOBAL_Stream[sno].file == NULL) {
if (me->close) { if (me->close) {
me->close(sno); me->close(sno);
@ -1043,7 +1045,8 @@ if ((me = GLOBAL_Stream[sno].vfs) != NULL &&
GLOBAL_Stream[sno].vfs = NULL; GLOBAL_Stream[sno].vfs = NULL;
GLOBAL_Stream[sno].file = NULL; GLOBAL_Stream[sno].file = NULL;
GLOBAL_Stream[sno].status = Free_Stream_f; GLOBAL_Stream[sno].status = Free_Stream_f;
// __android_log_print(ANDROID_LOG_INFO, "YAPDroid", "close stream <%d>", sno); // __android_log_print(ANDROID_LOG_INFO, "YAPDroid", "close stream <%d>",
// sno);
/* if (st->status == Socket_Stream_f|Input_Stream_f|Output_Stream_f) { /* if (st->status == Socket_Stream_f|Input_Stream_f|Output_Stream_f) {
Yap_CloseSocket(); Yap_CloseSocket();
@ -1556,8 +1559,7 @@ FILE *Yap_FileDescriptorFromStream(Term t) {
return rc; return rc;
} }
void Yap_InitBackIO(void) void Yap_InitBackIO(void) {
{
Yap_InitCPredBack("stream_property", 2, 2, stream_property, Yap_InitCPredBack("stream_property", 2, 2, stream_property,
cont_stream_property, SafePredFlag | SyncPredFlag); cont_stream_property, SafePredFlag | SyncPredFlag);
} }

View File

@ -830,17 +830,18 @@ gradient_descent :-
% leash(0),trace, % leash(0),trace,
lbfgs_initialize(N,X,0,Solver), lbfgs_initialize(N,X,0,Solver),
forall(tunable_fact(FactID,GroundTruth), forall(tunable_fact(FactID,GroundTruth),
(XZ is 0.5, X[FactID] <== XZ,set_fact_probability(FactID,XZ))), (XZ is 0.0, X[FactID] <== XZ,sigmoid(XZ,Slope,Pr),set_fact_probability(FactID,Pr))),
problog_flag(sigmoid_slope,Slope), problog_flag(sigmoid_slope,Slope),
lbfgs_set_parameter(min_step, 0.0, Solver), %lbfgs_set_parameter(min_step, 0.0, Solver),
lbfgs_run(Solver,BestF), lbfgs_run(Solver,BestF),
format('~2nOptimization done~nWe found a minimum ~4f.~n',[BestF]), format('~2nOptimization done~nWe found a minimum ~4f.~n',[BestF]),
forall(tunable_fact(FactID,GroundTruth), set_tunable(FactID,X)), forall(tunable_fact(FactID,GroundTruth), set_tunable(FactID,Slope,X)),
set_problog_flag(mse_trainset, BestF), set_problog_flag(mse_trainset, BestF),
lbfgs_finalize(Solver). lbfgs_finalize(Solver).
set_tunable(I,P) :- set_tunable(I,Slope,P) :-
Pr <== P[I], X <== P[I],
sigmoid(X,Slope,Pr),
set_fact_probability(I,Pr). set_fact_probability(I,Pr).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@ -849,12 +850,12 @@ set_tunable(I,P) :-
user:evaluate(LLH_Training_Queries, X,Grad,N,_,_) :- user:evaluate(LLH_Training_Queries, X,Grad,N,_,_) :-
%Handle = user_error, %Handle = user_error,
GradCount <== array[N] of ints, GradCount <== array[N] of ints,
Probs <== array[N] of floats,
problog_flag(sigmoid_slope,Slope), problog_flag(sigmoid_slope,Slope),
Probs = X,
N1 is N-1, N1 is N-1,
forall(between(0,N1,I), forall(between(0,N1,I),
(Grad[I] <== 0.0) %, sigmoid(X[I],Slope,Probs[I]) ) (Grad[I] <== 0.0, S <== X[I], sigmoid(S,Slope, P), Probs[I] <== P)
), ),
findall(LL, findall(LL,
compute_grad(Grad, GradCount, Probs, Slope, LL), compute_grad(Grad, GradCount, Probs, Slope, LL),
@ -876,15 +877,16 @@ compute_grad(Grad, GradCount, Probs, Slope, LL) :-
%writeln( qprobability(BDD,Slope,BDDProb) ), %writeln( qprobability(BDD,Slope,BDDProb) ),
forall( forall(
member(I-_, MapList), member(I-_, MapList),
gradientpair(I, BDD,Slope,BDDProb, QueryProb, Grad, GradCount) gradientpair(I, BDD,Slope,BDDProb, QueryProb, Grad, Probs, GradCount)
). ).
gradientpair(I, BDD,Slope,BDDProb, QueryProb, Grad, GradCount) :- gradientpair(I, BDD,Slope,BDDProb, QueryProb, Grad, Probs, GradCount) :-
qgradient(I, BDD, Slope, FactID, GradValue), qgradient(I, BDD, Slope, FactID, GradValue),
% writeln(FactID), % writeln(FactID),
G0 <== Grad[FactID], G0 <== Grad[FactID],
Prob <== Probs[FactID],
%writeln( GN is G0-GradValue*(QueryProb-BDDProb)), %writeln( GN is G0-GradValue*(QueryProb-BDDProb)),
GN is G0-GradValue*2*(QueryProb-BDDProb), GN is G0-GradValue*2*Prob*(1-Prob)*(QueryProb-BDDProb),
%writeln(FactID:(G0->GN)), %writeln(FactID:(G0->GN)),
GC <== GradCount[FactID], GC <== GradCount[FactID],
GC1 is GC+1, GC1 is GC+1,
@ -978,10 +980,10 @@ bind_maplist([Node-Pr|MapList], Slope, X) :-
% stop calculate gradient % stop calculate gradient
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
user:progress(FX,X,_G,X_Norm,G_Norm,Step,_N,Iteration,Ls,0) :- user:progress(FX,X,_G,X_Norm,G_Norm,Step,_N,Iteration,Ls,0) :-
% problog_flag(sigmoid_slope,Slope), problog_flag(sigmoid_slope,Slope),
X0 <== X[0], X0 <== X[0], sigmoid(X0,Slope,P0),
X1 <== X[1], 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',[Iteration,X0 ,X1,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]).
%======================================================================== %========================================================================

View File

@ -41,7 +41,7 @@ rdir( FRoot ) :-
absolute_file_name( FRoot, [glob(*), solutions(all), file_errors(fail)], File ), absolute_file_name( FRoot, [glob(*), solutions(all), file_errors(fail)], File ),
\+ doskip( File ), \+ doskip( File ),
( (
catch( file_property( File, type(directory) ), _, fail ) cat zzch( file_property( File, type(directory) ), _, fail )
-> ->
assert_new( dir( File ) ), assert_new( dir( File ) ),
assert_new( sub_dir( FRoot, File ) ), assert_new( sub_dir( FRoot, File ) ),