mkdir and small stuff

This commit is contained in:
Vítor Santos Costa 2015-07-06 12:04:42 +01:00
parent 33de6766a5
commit 1d6f9981e1
26 changed files with 197 additions and 194 deletions

View File

@ -9,6 +9,7 @@ cmake_minimum_required(VERSION 3.0)
# set path to additional CMake modules
set(CMAKE_MODULE_PATH ${CMAKE_SOURCE_DIR}/cmake ${CMAKE_MODULE_PATH})
set(CMAKE_PREFIX_PATH ~/Qt/5.4/clang_64/ ${CMAKE_PREFIX_PATH})
set(configurations Debug)
@ -53,7 +54,7 @@ message(STATUS "Building YAP version ${YAP_VERSION}")
#
include(CheckIncludeFile)
include(CheckIncludeFileCXX)
INCLUDE (CheckIncludeFiles)
include (CheckIncludeFiles)
include(CheckLibraryExists)
include(CheckSymbolExists)
include(CheckFunctionExists)
@ -72,7 +73,7 @@ include(GetGitRevisionDescription)
# Test signal handler return type (mimics AC_TYPE_SIGNAL)
include(TestSignalType) #check if this is really needed as c89 defines this as void
# Test standard headers (mimics AC_HEADER_STDC)
# Test standard headers (mimics AC_HEADER_STDC)
include(TestSTDC)
set(bitness 32)
@ -528,6 +529,7 @@ configure_file ("${PROJECT_SOURCE_DIR}/YapTermConfig.h.cmake"
"${PROJECT_BINARY_DIR}/YapTermConfig.h" )
configure_file("${PROJECT_SOURCE_DIR}/GitSHA1.c.in" "${PROJECT_BINARY_DIR}/GitSHA1.c" @ONLY)
ADD_SUBDIRECTORY(console/terminal)
install (

View File

@ -196,6 +196,7 @@ typedef enum {
#define YAP_CONSULT_MODE 0
#define YAP_RECONSULT_MODE 1
#define YAP_BOOT_MODE 2
typedef struct yap_boot_params {
/* if NON-NULL, path where we can find the saved state */

View File

@ -15,8 +15,9 @@
copy_line/2,
filter/3,
file_filter/3,
file_select/2,
file_filter_with_initialization/5,
file_select/2,
file_filter_with_initialization/5,
file_filter_with_initialization/5 as file_filter_with_init,
process/2
]).

View File

@ -177,7 +177,7 @@ RL_Tree* set_in_rl(RL_Tree* tree,NUM number,STATUS status) {
if ( number >0 && number <=tree->range_max)
set_in(number,ROOT(tree),1,ROOT_INTERVAL(tree),tree->range_max,tree,status);
#ifdef DEBUG
printf("Setting: %ul size=%ul\n",number,tree->size);
printf("Setting: %lu size=%lu\n",number,tree->size);
#endif
/*if (status==IN && !in_rl(tree,number)) {
fprintf(stderr,"Error adding %lu to tree: size=%lu max=%lu\n",number,tree->size,tree->range_max);

View File

@ -211,13 +211,6 @@ Unify _Name_ with a name for the current host. YAP uses the
`GetComputerName` function in WIN32 systems.
*/
/** @pred make_directory(+ _Dir_)
Create a directory _Dir_. The name of the directory must be an atom.
*/
/** @pred mktemp( _Spec_,- _File_)

View File

@ -355,21 +355,6 @@ p_unlink(void)
return(TRUE);
}
static YAP_Bool
p_mkdir(void)
{
char *fd = (char *)YAP_AtomName(YAP_AtomOfTerm(YAP_ARG1));
#if defined(__MINGW32__) || _MSC_VER
if (_mkdir(fd) == -1) {
#else
if (mkdir(fd, 0777) == -1) {
#endif
/* return an error number */
return(YAP_Unify(YAP_ARG2, YAP_MkIntTerm(errno)));
}
return(TRUE);
}
static YAP_Bool
p_rmdir(void)
{
@ -1131,7 +1116,6 @@ init_sys(void)
YAP_UserCPredicate("list_directory", list_directory, 3);
YAP_UserCPredicate("file_property", file_property, 7);
YAP_UserCPredicate("unlink", p_unlink, 2);
YAP_UserCPredicate("mkdir", p_mkdir, 2);
YAP_UserCPredicate("rmdir", p_rmdir, 2);
YAP_UserCPredicate("dir_separator", dir_separator, 1);
YAP_UserCPredicate("p_environ", p_environ, 2);

View File

@ -342,6 +342,7 @@ A STRING F "String"
A Swi N "swi"
A SymbolChar N "symbol_char"
A SyntaxError N "syntax_error"
A SyntaxErrors N "syntax_errors"
A SyntaxErrorHandler N "syntax_error_handler"
A System N "system"
A SystemError N "system_error"

View File

@ -12,6 +12,8 @@ int c_error_stream =2
bool sockets_io =false
bool within_print_message =false
//
// Used by the prompts to check if they are after a newline, and then a
// prompt should be output, or if we are in the middle of a line.
@ -94,7 +96,9 @@ UInt IPredArity =0L
yamop* ProfEnd =NULL
int UncaughtThrow =FALSE
int DoingUndefp =FALSE
Int StartLine =0L
Int StartCharCount =0L
Int StartLineCount =0L
Int StartLinePos =0L
scratch_block ScratchPad InitScratchPad(wid)
#ifdef COROUTINING
Term WokenGoals =0L TermToGlobalAdjust

View File

@ -62,4 +62,3 @@ gen_decl(Inp,Out) :-
%gen_decl(Inp,Out) :-
% split(Inp," ",["F",Name,Arity]), !,
% append([" Functor_",Name,Arity," = Yap_MkFunctor(Atom_",Name,",",Arity,");"],Out).

View File

@ -309,7 +309,7 @@ add_implies(DdManager *manager, DdNode *x1, DdNode *x2)
{
DdNode *tmp;
tmp = Cudd_addApply(manager,Cudd_addLeq,x1,x2);
tmp = Cudd_addConst(manager,Cudd_addLeq(manager,x1,x2));
Cudd_Ref(tmp);
return tmp;
}
@ -878,7 +878,7 @@ p_cudd_print_with_names(void)
DdManager *manager = (DdManager *)YAP_IntOfTerm(YAP_ARG1);
DdNode *n0 = (DdNode *)YAP_IntOfTerm(YAP_ARG2);
const char *s = YAP_AtomName(YAP_AtomOfTerm(YAP_ARG3));
char **namesp;
const char **namesp;
YAP_Term names = YAP_ARG4;
FILE *f;
YAP_Int len;
@ -918,7 +918,7 @@ p_cudd_print_with_names(void)
fclose(f);
while (i > 0) {
i--;
free(namesp[i]);
free((void *)namesp[i]);
}
free( namesp );
return TRUE;

View File

@ -64,7 +64,8 @@
/* turn on director wrapping Callback */
%feature("director") YAPCallback;
%include "yapi.hh"
// %include "yapi.hh"
%include "yapa.hh"

View File

@ -147,7 +147,7 @@ absolute_file_name(File0,File) :-
/* our own local findall */
nb:nb_queue(Ref),
(
'$find_in_path'(File,opts(Extensions,RelTo,Type,Access,Errors,Expand,Debug),TrueFileName,G),
'$find_in_path'(File,opts(Extensions,RelTo,Type,Access,FErrors,Expand,Debug),TrueFileName,G),
nb:nb_queue_enqueue(Ref, TrueFileName),
fail
;
@ -672,4 +672,3 @@ user:file_search_path(path, C) :-
).
%%@}

View File

@ -22,7 +22,7 @@
*/
%
% These are the array built-in predicates. They will only work if
% YAP_ARRAYS is defined in Yap.h.m4.
% YAP_ARRAYS is defined in Yap.h
%
/** @pred array(+ _Name_, + _Size_)

View File

@ -351,7 +351,7 @@ true :- true.
('$exit_undefp' -> true ; true),
prompt1(' ?- '),
set_prolog_flag(debug, false),
% simple trick to find out if this is we are booting from Prolog.
% simple trick to find out if this is we are booting from Prolog.
% boot from a saved state
(
'$undefined'('$init_preds',prolog)
@ -442,7 +442,7 @@ true :- true.
prompt(_,'|: '),
'$system_catch'(read_term(user_input,
Goal,
[variable_names(Bindings)]),
[variable_names(Bindings), syntax_errors(dec10)]),
prolog, E, '$handle_toplevel_error'( E) ).
'$handle_toplevel_error'( syntax_error(_)) :-
@ -1123,10 +1123,6 @@ incore(G) :- '$execute'(G).
'$creep'.
'$enable_debugging'.
'$disable_debugging' :-
'$stop_creeping'.
/** @pred :_P_ , :_Q_ is iso, meta
Conjunction of goals (and).
@ -1365,9 +1361,13 @@ bootstrap(F) :-
user:'$LoopError'(Error, Status)),
!.
'$enter_command'(Stream,Mod,Status) :-
read_term(Stream, Command, [variable_names(Vars), term_position(Pos), syntax_errors(dec10) ]),
'$command'(Command,Vars,Pos,Status).
'$enter_command'(Stream,Mod,top) :- !,
writeln(top),
read_term(Stream, Command, [module(Mod), syntax_errors(dec10),variable_names(Vars), term_position(Pos)]),
'$command'(Command,Vars,Pos,Status).
'$enter_command'(Stream,Mod,Status) :-
read_clause(Stream, Command, [variable_names(Vars), term_position(Pos)]),
'$command'(Command,Vars,Pos,Status).
'$abort_loop'(Stream) :-
'$do_error'(permission_error(input,closed_stream,Stream), loop).
@ -1421,8 +1421,7 @@ bootstrap(F) :-
This predicate is used by YAP for preprocessing each top level
term read when consulting a file and before asserting or executing it.
It rewrites a term _T_ to a term _X_ according to the following
rules: first try term_expansion/2 in the current module, and then try to use the user defined predicate
`user:term_expansion/2`. If this call fails then the translating process
rules: first try term_expansion/2 in the current module, and then try to use the user defined predicate user:term_expansion/2`. If this call fails then the translating process
for DCG rules is applied, together with the arithmetic optimizer
whenever the compilation of arithmetic expressions is in progress.
@ -1568,4 +1567,3 @@ log_event( String, Args ) :-
/**
@}
*/

View File

@ -649,7 +649,6 @@ db_files(Fs) :-
'$extract_minus'([-F|Fs], [F|MFs]) :-
'$extract_minus'(Fs, MFs).
'$do_lf'(ContextModule, Stream, UserFile, File, TOpts) :-
stream_property(OldStream, alias(loop_stream) ),
'$lf_opt'(encoding, TOpts, Encoding),
@ -843,27 +842,29 @@ db_files(Fs) :-
b_getval('$lf_status', TOpts),
'$msg_level'( TOpts, Verbosity),
'$full_filename'(X, Y , ( :- include(X)) ),
writeln((X:Y)),
'$lf_opt'(stream, TOpts, OldStream),
source_location(OldY, L),
'$current_module'(Mod),
( open(Y, read, Stream) ->
true ;
'$do_error'(permission_error(input,stream,Y),include(X))
),
H0 is heapused, '$cputime'(T0,_),
working_directory(Dir, Dir),
file_directory_name(Y, Dir),
H0 is heapused, '$cputime'(T0,_),
working_directory(Dir0, Dir),
'$lf_opt'(encoding, TOpts, Encoding),
set_stream(Stream, [encoding(Encoding),alias(loop_stream)] ),
'$loaded'(Y, X, Mod, OldY, L, include, _, Dir, []),
'$loaded'(Y, X, Mod, _OldY, _L, include, _, Dir, []),
( '$nb_getval'('$included_file', OY, fail ) -> true ; OY = [] ),
nb_setval('$included_file', Y),
print_message(Verbosity, loading(including, Y)),
'$loop'(Stream,Status),
set_stream(OldStream, alias(loop_stream) ),
close(Stream),
close(Stream),
H is heapused-H0, '$cputime'(TF,_), T is TF-T0,
print_message(Verbosity, loaded(included, Y, Mod, T, H)),
nb_setval('$included_file',OY).
working_directory(_Dir, Dir0),
nb_setval('$included_file',OY).
@ -970,6 +971,7 @@ most files in the library are from the Edinburgh Prolog library.
*/
prolog_load_context(directory, DirName) :-
strat_low_level_trace,
( source_location(F, _)
-> file_directory_name(F, DirName) ;
working_directory( DirName, DirName )
@ -997,7 +999,8 @@ prolog_load_context(stream, Stream) :-
'$nb_getval'('$consulting_file', _, fail),
'$current_loop_stream'(Stream).
prolog_load_context(term_position, Position) :-
stream_property( Stream, [alias(loop_stream),position(Position)] ).
'$current_loop_stream'(Stream)
stream_property( Stream, [alias(loop_stream),position(Position)] ).
% if the file exports a module, then we can

View File

@ -848,6 +848,7 @@ be lost.
fail /* to backtrack to spycalls */
)
;
'$stop_creeping',
'$show_trace'(fail,G,Module,GoalNumber,_), /* inform at fail port */
'$continue_debugging'(fail, CalledFromDebugger),
/* fail port */

View File

@ -31,4 +31,3 @@ system_module( '$_depth_bound', [depth_bound_call/2], []).
%write(depth_bound_call(A,D)), nl, fail.
depth_bound_call(A,D) :-
'$execute_under_depth_limit'(A,D).

View File

@ -6,10 +6,17 @@
:- use_system_module( '$_errors', ['$do_error'/2]).
prolog:'$expects_dialect'(yap) :- !,
% @pred expects_dialect(+Dialect)
%
% True if YAP can enable support for a different Prolog dialect.
% Currently there is support for bprolog, hprolog and swi-prolog.
% Notice that this support may be incomplete.
%
% The
prolog:expects_dialect(yap) :- !,
eraseall('$dialect'),
recorda('$dialect',yap,_).
prolog:'$expects_dialect'(Dialect) :-
prolog:expects_dialect(Dialect) :-
check_dialect(Dialect),
eraseall('$dialect'),
load_files(library(dialect/Dialect),[silent(true),if(not_loaded)]),
@ -84,4 +91,3 @@ open_source(File, In) :-
exports(In, Exports) :-
read(In, Term),
Term = (:- module(_Name, Exports)).

View File

@ -139,7 +139,7 @@ considered.
'$exec_directive'(thread_initialization(D), _, M, _, _) :-
'$thread_initialization'(M:D).
'$exec_directive'(expects_dialect(D), _, _, _, _) :-
'$expects_dialect'(D).
expects_dialect(D).
'$exec_directive'(encoding(Enc), _, _, _, _) :-
'$set_encoding'(Enc).
'$exec_directive'(include(F), Status, _, _, _) :-
@ -225,8 +225,8 @@ user_defined_directive(Dir,Action) :-
functor(Dir,Na,Ar),
functor(NDir,Na,Ar),
'$current_module'(M, prolog),
assert_static('$directive'(NDir)),
assert_static(('$exec_directive'(Dir, _, _, _, _) :- Action)),
assert_static(prolog:'$directive'(NDir)),
assert_static(prolog:('$exec_directive'(Dir, _, _, _, _) :- Action)),
'$current_module'(_, M).
'$thread_initialization'(M:D) :-
@ -235,5 +235,3 @@ user_defined_directive(Dir,Action) :-
fail.
'$thread_initialization'(M:D) :-
'$initialization'(M:D).

View File

@ -246,7 +246,7 @@ to allow user-control.
print_message(informational,abort(user)).
'$process_error'(abort, _) :- !,
throw(abort).
'$process_error'(error(thread_cancel(Id), G),top) :- !.
'$process_error'(error(thread_cancel(_Id), _G),top) :- !.
'$process_error'(error(thread_cancel(Id), G), _) :- !,
throw(error(thread_cancel(Id), G)).
'$process_error'(error(permission_error(module,redefined,A),B), Level) :-
@ -352,5 +352,3 @@ print_message(_, Term) :-
flush_output(user_error),
'$messages':prefix(Level, LinePrefix, Stream, LinesF, Lines), !,
print_message_lines(Stream, LinePrefix, LinesF).

View File

@ -221,7 +221,6 @@ rules.
:- dynamic goal_expansion/2.
:- use_module('messages.yap').
:- use_module('hacks.yap').
:- use_module('attributes.yap').
@ -328,12 +327,7 @@ If this hook predicate succeeds it must instantiate the _Action_ argument to th
+ `undefined_global_variable`
_Context_ is instantiated to the name of the missing global variable. The hook must call nb_setval/2 or b_setval/2 before returning with the action retry.
*/
*/
:- multifile user:exception/3.

View File

@ -76,14 +76,6 @@ file_position(user_input,LN) -->
file_position(FileName,LN) -->
[ '~a:~d:0: ' - [FileName,LN] ].
translate_message(Term) -->
generate_message(Term), !.
translate_message(Term) -->
{ Term = error(_, _) },
[ 'Unknown exception: ~p'-[Term] ].
translate_message(Term) -->
[ 'Unknown message: ~p'-[Term] ].
generate_message(Term, Lines, []) :-
user:generate_message_hook(Term, [], Lines), !.
generate_message(Term) -->
@ -679,11 +671,15 @@ pred_arity(H,Name,Arity) :-
functor(H,Name,Arity).
translate_message(Term) -->
generate_message(Term), !.
translate_message(Term) -->
{ Term = error(_, _) },
[ 'Unknown exception: ~p'-[Term] ].
translate_message(Term) -->
[ 'Unknown message: ~p'-[Term] ].
/**
@}
@}
*/

View File

@ -1,3 +1,4 @@
/*************************************************************************
* *
* YAP Prolog *
@ -158,7 +159,7 @@ not at all defined.
'$do_import'/3,
'$extend_exports'/3,
'$get_undefined_pred'/4,
'$imported_pred'/4,
'$imported_predicate'/4,
'$meta_expansion'/6,
'$meta_predicate'/2,
'$meta_predicate'/4,
@ -666,7 +667,15 @@ source_module(Mod) :-
'$expand_modules'((A;B),(A1;B1),(AO;BO),HM,BM,SM,HVars) :- var(A), !,
'$expand_modules'(A,A1,AO,HM,BM,SM,HVars),
'$expand_modules'(B,B1,BO,HM,BM,SM,HVars).
'$expand_modules'((A*->B;C),(A1*->B1;C1),(yap_hacks:current_choicepoint(DCP),AO,yap_hacks:cut_at(DCP),BO; CO),HM,BM,SM,HVars) :- !,
'$expand_modules'((A*->B;C),(A1*->B1;C1),
(
yap_hacks:current_choicepoint(DCP),
AO,
yap_hacks:cut_at(DCP),BO
;
CO
),
HM,BM,SM,HVars) :- !,
'$expand_modules'(A,A1,AOO,HM,BM,SM,HVars),
'$clean_cuts'(AOO, AO),
'$expand_modules'(B,B1,BO,HM,BM,SM,HVars),
@ -724,18 +733,29 @@ source_module(Mod) :-
'$expand_modules'(false,false,false,_,_,_,_) :- !.
% if I don't know what the module is, I cannot do anything to the goal,
% so I just put a call for later on.
'$expand_modules'(M:G,call(M:G),'$execute_wo_mod'(G,M),_,_,_,_) :- var(M), !.
'$expand_modules'(M:G,call(M:G),
'$execute_wo_mod'(G,M),_,_,_,_) :- var(M), !.
'$expand_modules'(M:G,G1,GO,HM,_M,_SM,HVars) :- !,
'$expand_modules'(G,G1,GO,HM,M,M,HVars).
'$expand_modules'(G, G1, GO, HM, BM, SM, HVars) :-
'$expand_goal_modules'(G, G1, GO, HM, BM, SM, HVars).
% is this imported from some other module M1?
'$imported_pred'(G, BM, GG, M1),
'$expand_goal_modules'(G, G1, GO, HM, BM, SM, HVars) :-
'$pred_exists'(G, BM), !,
'$expand_goal_meta'(G, G1, GO, HM, BM, SM, HVars).
'$expand_goal_modules'(G, G1, GO, HM, BM, SM, HVars) :-
'$imported_predicate'(G, BM, GG, M1),
!,
'$expand_modules'(GG, G1, GO, HM, M1, SM, HVars).
'$expand_modules'(G, G1, GO, HM, BM, SM, HVars) :-
'$expand_goal_meta'(GG, G1, GO, HM, M1, SM, HVars).
% we assume that if it is not defined here, it must be elsewhere.
'$expand_goal_modules'(G, G1, GO, HM, BM, SM, HVars) :-
'$expand_goal_meta'(G, G1, GO, HM, BM, SM, HVars).
'$expand_goal_meta'(G, G1, GO, HM, BM, SM, HVars) :-
'$meta_expansion'(G, HM, BM, SM, GI, HVars), !,
'$complete_goal_expansion'(GI, HM, BM, SM, G1, GO, HVars).
'$expand_modules'(G, G1, GO, HM, BM, SM, HVars) :-
'$expand_goal_meta'(G, G1, GO, HM, BM, SM, HVars) :-
'$complete_goal_expansion'(G, HM, BM, SM, G1, GO, HVars).
expand_goal(G, G) :-
@ -823,7 +843,7 @@ expand_goal(G, G).
% be careful here not to generate an undefined exception.
'$imported_pred'(G, ImportingMod, G0, ExportingMod) :-
'$imported_predicate'(G, ImportingMod, G0, ExportingMod) :-
'$enter_undefp',
( var(G) -> true ;
var(ImportingMod) -> true ;
@ -832,7 +852,7 @@ expand_goal(G, G).
'$get_undefined_pred'(G, ImportingMod, G0, ExportingMod),
ExportingMod \= ImportingMod, !,
'$exit_undefp'.
'$imported_pred'(_G, _ImportingMod, _, _) :-
'$imported_predicate'(_G, _ImportingMod, _, _) :-
'$exit_undefp',
fail.
@ -847,26 +867,28 @@ expand_goal(G, G).
'$get_undefined_pred'(G, _ImportingMod, G, user) :-
nonvar(G),
'$pred_exists'(G, user), !.
'$get_undefined_pred'(G, _ImportingMod, G0, ExportingMod) :-
recorded('$dialect',Dialect,_),
Dialect \= yap,
functor(G, Name, Arity),
call(Dialect:index(Name,Arity,ExportingModI,_)), !,
'$continue_imported'(ExportingMod, ExportingModI, G0, G).
% autoload
'$get_undefined_pred'(G, ImportingMod, G0, ExportingMod) :-
yap_flag(autoload, V),
V = true,
functor(G, N, K),
functor(G0, N, K),
'$autoloader_find_predicate'(G0,ExportingMod),
ExportingMod \= ImportingMod,
(recordzifnot('$import','$import'(ExportingMod,ImportingMod,G0,G0, N ,K),_) -> true ; true ).
recorded('$dialect',swi,_),
get_prolog_flag(autoload, true),
'$autoload'(G, ImportingMod, ExportingModI, swi),
'$continue_imported'(ExportingMod, ExportingModI, G0, G).
% autoload
% parent module mechanism
'$get_undefined_pred'(G, ImportingMod, G0, ExportingMod) :-
prolog:'$parent_module'(ImportingMod,ExportingModI),
'$continue_imported'(ExportingMod, ExportingModI, G0, G).
'$autoload'(G, _ImportingMod, ExportingMod, Dialect) :-
functor(G, Name, Arity),
call(Dialect:index(Name,Arity,ExportingMod,_)), !.
'$autoload'(G, ImportingMod, ExportingMod, _Dialect) :-
functor(G, N, K),
functor(G0, N, K),
'$autoloader_find_predicate'(G0,ExportingMod),
ExportingMod \= ImportingMod,
(recordzifnot('$import','$import'(ExportingMod,ImportingMod,G0,G0, N ,K),_) -> true ; true ).
'$autoloader_find_predicate'(G,ExportingModI) :-
'$nb_getval'('$autoloader_set', true, fail), !,
@ -1397,7 +1419,7 @@ export_list(Module, List) :-
'$do_import'(op(Prio,Assoc,Name), _Mod, ContextMod) :-
op(Prio,Assoc,ContextMod:Name).
'$do_import'(N0/K0-N0/K0, Mod, Mod) :- !.
'$do_import'(N0/K0-N0/K0, Mod, prolog) :- !.
'$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)),

View File

@ -574,7 +574,7 @@ predicate_property(Pred,Prop) :-
'$pred_exists'(Pred,Mod), !,
'$predicate_property'(Pred,Mod,Mod,Prop).
'$predicate_property2'(Pred,Prop,Mod) :-
'$imported_pred'(Pred, Mod, NPred, M),
'$imported_predicate'(Pred, Mod, NPred, M),
(
Prop = imported_from(M)
;
@ -679,7 +679,7 @@ current_predicate(A,T) :-
% format('1 ~w ~16r~n', [M:T0,Flags, TFlags]),
\+ '$system_predicate'(T0, M)
;
'$imported_pred'(T0, M, SourceT, SourceMod),
'$imported_predicate'(T0, M, SourceT, SourceMod),
functor(T0, A, _),
% format('2 ~w ~16r~n', [M:T0,Flags]),
\+ '$system_predicate'(SourceT, SourceMod)

View File

@ -237,7 +237,7 @@ qend_program :-
X \= encoding.
'$init_state' :-
recorded('$program_state', P, _), !,
recorded('$program_state', _P, _), !,
'$do_init_state'.
'$init_state'.
@ -325,6 +325,9 @@ qend_program :-
'$init_path_extensions'.
% then we can execute the programs.
'$startup_goals' :-
module(user),
fail.
'$startup_goals' :-
recorded('$startup_goal',G,_),
'$current_module'(Module),