Fix typos across code
Change debugger to backtrack more alike byrd model Fix typo in debugger option f git-svn-id: https://yap.svn.sf.net/svnroot/yap/trunk@1782 b08c6af1-5177-4d33-ba66-4b1c6b8b522a
This commit is contained in:
parent
b697f3d34e
commit
b3d9e88802
@ -16,6 +16,7 @@
|
||||
|
||||
<h2>Yap-5.1.2:</h2>
|
||||
<ul>
|
||||
<li> NEW: make debugger more like standard debuggers (obs from Miguel Filgueiras).</li>
|
||||
<li> NEW: glist_void_varx was broken (obs from Marius Filip).</li>
|
||||
<li> NEW: unify_with_occurs_check/2 was broken with extensions (obs from Aline Paes).</li>
|
||||
<li> NEW: stack_dump/0 from Trevor.</li>
|
||||
|
@ -732,7 +732,7 @@ not(G) :- \+ '$execute'(G).
|
||||
).
|
||||
'$call'(\+ X, _CP, _G0, M) :- !,
|
||||
\+ '$execute'(M:X).
|
||||
'$call'(not(X), _CP, _G0, _M) :- !,
|
||||
'$call'(not(X), _CP, _G0, M) :- !,
|
||||
\+ '$execute'(M:X).
|
||||
'$call'(!, CP, _,_) :- !,
|
||||
'$$cut_by'(CP).
|
||||
@ -761,7 +761,7 @@ not(G) :- \+ '$execute'(G).
|
||||
|
||||
'$check_callable'(V,G) :- var(V), !,
|
||||
'$do_error'(instantiation_error,G).
|
||||
'$check_callable'(M:G1,G) :- var(M), !,
|
||||
'$check_callable'(M:_G1,G) :- var(M), !,
|
||||
'$do_error'(instantiation_error,G).
|
||||
'$check_callable'(_:G1,G) :- !,
|
||||
'$check_callable'(G1,G).
|
||||
@ -928,14 +928,14 @@ bootstrap(F) :-
|
||||
'$dir_separator'(D),
|
||||
atom_codes(A,[D]),
|
||||
user:library_directory(Dir),
|
||||
'$extend_path'(Dir, A, File, NFile, Goal),
|
||||
'$extend_path'(Dir, A, File, NFile, compile(library(File))),
|
||||
'$search_in_path'(NFile, NewFile), !.
|
||||
'$find_in_path'(S,NewFile, _) :-
|
||||
S =.. [Name,File], !,
|
||||
'$dir_separator'(D),
|
||||
atom_codes(A,[D]),
|
||||
user:file_search_path(Name, Dir),
|
||||
'$extend_path'(Dir, A, File, NFile, Goal),
|
||||
'$extend_path'(Dir, A, File, NFile, compile(S)),
|
||||
'$search_in_path'(NFile, NewFile), !.
|
||||
'$find_in_path'(File,NewFile,_) :- atom(File), !,
|
||||
'$search_in_path'(File,NewFile),!.
|
||||
|
@ -50,7 +50,7 @@ load_files(Files,Opts) :-
|
||||
'$process_lf_opts'([Opt|Opts],Silent,InfLevel,Expand,Changed,CompilationMode,Imports,Stream,Encoding,SkipUnixComments,Reconsult,Files,Call) :-
|
||||
'$process_lf_opt'(Opt,Silent,InfLevel,Expand,Changed,CompilationMode,Imports,Stream,Encoding,SkipUnixComments,Reconsult,Files,Call), !,
|
||||
'$process_lf_opts'(Opts,Silent,InfLevel,Expand,Changed,CompilationMode,Imports,Stream,Encoding,SkipUnixComments,Reconsult,Files,Call).
|
||||
'$process_lf_opts'([Opt|Opts],_,_,_,_,_,_,_,_,_,_,_,Call) :-
|
||||
'$process_lf_opts'([Opt|_],_,_,_,_,_,_,_,_,_,_,_,Call) :-
|
||||
'$do_error'(domain_error(unimplemented_option,Opt),Call).
|
||||
|
||||
'$process_lf_opt'(autoload(true),_,InfLevel,_,_,_,_,_,_,_,_,_,_) :-
|
||||
@ -70,7 +70,7 @@ load_files(Files,Opts) :-
|
||||
( var(Encoding) ->
|
||||
'$do_error'(instantiation_error,Call)
|
||||
;
|
||||
'$valid_encoding'(Enc, EncCode) ->
|
||||
'$valid_encoding'(Encoding, EncCode) ->
|
||||
true
|
||||
;
|
||||
'$do_error'(domain_error(io_mode,encoding(Encoding)),Call)
|
||||
@ -81,11 +81,11 @@ load_files(Files,Opts) :-
|
||||
'$process_lf_opt'(if(changed),_,_,_,changed,_,_,_,_,_,_,_,_).
|
||||
'$process_lf_opt'(if(true),_,_,_,true,_,_,_,_,_,_,_,_).
|
||||
'$process_lf_opt'(if(not_loaded),_,_,_,not_loaded,_,_,_,_,_,_,_,_).
|
||||
'$process_lf_opt'(imports(all),_,_,_,_,_,_,_,_,_,_,_).
|
||||
'$process_lf_opt'(imports(all),_,_,_,_,_,_,_,_,_,_,_,_).
|
||||
'$process_lf_opt'(imports(Imports),_,_,_,_,_,Imports,_,_,_,_,_,_).
|
||||
'$process_lf_opt'(qcompile(true),_,_,_,_,true,_,_,_,_,_,_,Call) :-
|
||||
'$do_error'(domain_error(unimplemented_option,qcompile),Call).
|
||||
'$process_lf_opt'(qcompile(false),_,_,_,_,false,_,_,_,_,_,_).
|
||||
'$process_lf_opt'(qcompile(false),_,_,_,_,false,_,_,_,_,_,_,_).
|
||||
'$process_lf_opt'(silent(true),Silent,silent,_,_,_,_,_,_,_,_,_,_) :-
|
||||
( get_value('$lf_verbose',Silent) -> true ; Silent = informational),
|
||||
set_value('$lf_verbose',silent).
|
||||
@ -93,7 +93,7 @@ load_files(Files,Opts) :-
|
||||
'$process_lf_opt'(silent(false),_,_,_,_,_,_,_,_,_,_,_,_).
|
||||
'$process_lf_opt'(consult(reconsult),_,_,_,_,_,_,_,_,_,reconsult,_,_).
|
||||
'$process_lf_opt'(consult(consult),_,_,_,_,_,_,_,_,_,consult,_,_).
|
||||
'$process_lf_opt'(stream(Stream),_,_,_,_,_,_,Stream,_,_,_,Files,_) :-
|
||||
'$process_lf_opt'(stream(Stream),_,_,_,_,_,_,Stream,_,_,_,Files,Call) :-
|
||||
/* ( '$stream'(Stream) -> true ; '$do_error'(domain_error(stream,Stream),Call) ), */
|
||||
( atom(Files) -> true ; '$do_error'(type_error(atom,Files),Call) ).
|
||||
|
||||
@ -116,13 +116,13 @@ load_files(Files,Opts) :-
|
||||
'$lf'([F|Fs], Mod,Call,InfLevel,Expand,Changed,CompilationMode,Imports,Stream,Encoding,SkipUnixComments,Reconsult,UseModule) :- !,
|
||||
'$lf'(F,Mod,Call,InfLevel,Expand,Changed,CompilationMode,Imports,Stream,Encoding,SkipUnixComments,Reconsult,_),
|
||||
'$lf'(Fs, Mod,Call,InfLevel,Expand,Changed,CompilationMode,Imports,Stream,Encoding,SkipUnixComments,Reconsult,UseModule).
|
||||
'$lf'(X, Mod, Call,InfLevel,_,Changed,CompilationMode,Imports,Stream,_,Reconsult,SkipUnixComments,UseModule) :-
|
||||
'$lf'(_, Mod, _,InfLevel,_,_,CompilationMode,Imports,Stream,_,Reconsult,SkipUnixComments,UseModule) :-
|
||||
nonvar(Stream), !,
|
||||
'$do_lf'(X, Mod, Stream, InfLevel,CompilationMode,Imports,SkipUnixComments,Reconsult,UseModule).
|
||||
'$lf'(user, Mod, Call,InfLevel,_,Changed,CompilationMode,Imports,_,_,SkipUnixComments,Reconsult,UseModule) :- !,
|
||||
'$do_lf'(user_input, Mod, user_input, InfLevel, CompilationMode,Imports,SkipUnixComments,Reconsult,UseModule).
|
||||
'$lf'(user_input, Mod, Call,InfLevel,_,Changed,CompilationMode,Imports,_,_,SkipUnixComments,Reconsult,UseModule) :- !,
|
||||
'$do_lf'(user_input, Mod, user_input, InfLevel, CompilationMode,Imports,SkipUnixComments,Reconsult,UseModule).
|
||||
'$do_lf'(Mod, Stream, InfLevel,CompilationMode,Imports,SkipUnixComments,Reconsult,UseModule).
|
||||
'$lf'(user, Mod, _,InfLevel,_,_,CompilationMode,Imports,_,_,SkipUnixComments,Reconsult,UseModule) :- !,
|
||||
'$do_lf'(Mod, user_input, InfLevel, CompilationMode,Imports,SkipUnixComments,Reconsult,UseModule).
|
||||
'$lf'(user_input, Mod, _,InfLevel,_,_,CompilationMode,Imports,_,_,SkipUnixComments,Reconsult,UseModule) :- !,
|
||||
'$do_lf'(Mod, user_input, InfLevel, CompilationMode,Imports,SkipUnixComments,Reconsult,UseModule).
|
||||
'$lf'(X, Mod, Call, InfLevel,_,Changed,CompilationMode,Imports,_,Enc,SkipUnixComments,Reconsult,UseModule) :-
|
||||
'$find_in_path'(X, Y, Call),
|
||||
'$open'(Y, '$csult', Stream, 0, Enc), !,
|
||||
@ -139,8 +139,8 @@ load_files(Files,Opts) :-
|
||||
'$file_loaded'(Stream, Mod, Imports), !.
|
||||
'$start_lf'(_, Mod, Stream, _, _, Imports, changed, _, _, _) :-
|
||||
'$file_unchanged'(Stream, Mod, Imports), !.
|
||||
'$start_lf'(X, Mod, Stream, InfLevel, CompilationMode, Imports, _, SkipUnixComments, Reconsult, UseModule) :-
|
||||
'$do_lf'(X, Mod, Stream, InfLevel, CompilationMode, Imports, SkipUnixComments, Reconsult, UseModule).
|
||||
'$start_lf'(_, Mod, Stream, InfLevel, CompilationMode, Imports, _, SkipUnixComments, Reconsult, UseModule) :-
|
||||
'$do_lf'(Mod, Stream, InfLevel, CompilationMode, Imports, SkipUnixComments, Reconsult, UseModule).
|
||||
|
||||
'$close_lf'(Silent) :-
|
||||
nonvar(Silent), !,
|
||||
@ -169,7 +169,7 @@ consult(Fs) :-
|
||||
'$access_yap_flags'(8, 2), % SICStus Prolog compatibility
|
||||
!,
|
||||
'$load_files'(Module:Fs,[],Fs).
|
||||
'$consult'(Fs, Module) :- var(V), !,
|
||||
'$consult'(Fs, Module) :-
|
||||
'$load_files'(Module:Fs,[consult(consult)],Fs).
|
||||
|
||||
reconsult(Fs) :-
|
||||
@ -184,7 +184,7 @@ use_module(F,Is) :-
|
||||
use_module(M,F,Is) :-
|
||||
'$use_module'(M,F,Is).
|
||||
|
||||
'$use_module'(U,F,Is) :- nonvar(U), U = user, !,
|
||||
'$use_module'(U,_F,Is) :- nonvar(U), U = user, !,
|
||||
'$import_to_current_module'(user_input, user, Is).
|
||||
'$use_module'(M,F,Is) :- nonvar(M), !,
|
||||
recorded('$module','$module'(F1,M,_),_),
|
||||
@ -199,10 +199,10 @@ use_module(M,F,Is) :-
|
||||
'$csult'([-F|L], M) :- !, '$load_files'(M:F, [],[-M:F]), '$csult'(L, M).
|
||||
'$csult'([F|L], M) :- '$consult'(F, M), '$csult'(L, M).
|
||||
|
||||
'$do_lf'(F, ContextModule, Stream, InfLevel, _, Imports, SkipUnixComments, Reconsult, UseModule) :-
|
||||
'$do_lf'(ContextModule, Stream, InfLevel, _, Imports, SkipUnixComments, Reconsult, UseModule) :-
|
||||
nb_getval('$system_mode', OldMode),
|
||||
( OldMode == off -> '$enter_system_mode' ; true ),
|
||||
'$record_loaded'(Stream, M),
|
||||
'$record_loaded'(Stream, ContextModule),
|
||||
'$current_module'(OldModule,ContextModule),
|
||||
getcwd(OldD),
|
||||
get_value('$consulting_file',OldF),
|
||||
@ -377,7 +377,7 @@ prolog_load_context(source, FileName) :-
|
||||
prolog_load_context(stream, Stream) :-
|
||||
'$fetch_stream_alias'(Stream,'$loop_stream').
|
||||
prolog_load_context(term_position, Position) :-
|
||||
'$fetch_stream_alias'(Stream,'$loop_stream').
|
||||
'$fetch_stream_alias'(Stream,'$loop_stream'),
|
||||
stream_position(Stream, Position).
|
||||
|
||||
|
||||
@ -389,11 +389,11 @@ prolog_load_context(term_position, Position) :-
|
||||
|
||||
'$ensure_file_loaded'(F, M, Imports) :-
|
||||
recorded('$module','$module'(F1,NM,P),_),
|
||||
recorded('$lf_loaded','$lf_loaded'(F1,_,Age),R),
|
||||
recorded('$lf_loaded','$lf_loaded'(F1,_,_),_),
|
||||
'$same_file'(F1,F), !,
|
||||
'$use_preds'(Imports,P, NM, M).
|
||||
'$ensure_file_loaded'(F, M, _) :-
|
||||
recorded('$lf_loaded','$lf_loaded'(F1,M,Age),R),
|
||||
recorded('$lf_loaded','$lf_loaded'(F1,M,_),_),
|
||||
'$same_file'(F1,F), !.
|
||||
|
||||
|
||||
|
@ -522,7 +522,7 @@ frozen(V, LG) :-
|
||||
'$purge_done_goals'(G0, GF).
|
||||
'$purge_done_goals'(['$redo_freeze'(Done, _, _)|G0], GF) :- nonvar(Done), !,
|
||||
'$purge_done_goals'(G0, GF).
|
||||
'$purge_done_goals'(['$redo_freeze'(Done, _, CallCleanup)|G0], GF) :-
|
||||
'$purge_done_goals'(['$redo_freeze'(_Done, _, CallCleanup)|G0], GF) :-
|
||||
nonvar(CallCleanup),
|
||||
CallCleanup = _:'$clean_call'(_), !,
|
||||
'$purge_done_goals'(G0, GF).
|
||||
|
69
pl/debug.yap
69
pl/debug.yap
@ -320,7 +320,7 @@ debugging :-
|
||||
L1 is L+1, /* bump it */
|
||||
nb_setval('$spy_gn',L1), /* and save it globaly */
|
||||
b_getval('$spy_glist',History), /* get goal list */
|
||||
b_setval('$spy_glist',[info(L,Module,G,Retry,Det)|History]), /* and update it */
|
||||
b_setval('$spy_glist',[info(L,Module,G,_Retry,_Det)|History]), /* and update it */
|
||||
'$loop_spy'(L, G, Module, InControl). /* set creep on */
|
||||
|
||||
% we are skipping, so we can just call the goal,
|
||||
@ -362,11 +362,13 @@ debugging :-
|
||||
'$debug_error'(_).
|
||||
|
||||
|
||||
'$loop_fail'(GoalNumber, G, Module, InControl) :-
|
||||
'$system_catch'(('$trace'(fail, G, Module, GoalNumber,_),
|
||||
fail ),
|
||||
Module, Event,
|
||||
'$loop_spy_event'(Event, GoalNumber, G, Module, InControl)).
|
||||
% just fail here, don't really need to call debugger, the user knows what he
|
||||
% wants to do
|
||||
'$loop_fail'(_GoalNumber, _G, _Module, _InControl) :-
|
||||
write(_G),nl,
|
||||
yap_hacks:stack_dump,
|
||||
'$continue_debugging',
|
||||
fail.
|
||||
|
||||
% if we are in
|
||||
'$loop_spy2'(GoalNumber, G, Module, InControl, CP) :-
|
||||
@ -375,7 +377,7 @@ debugging :-
|
||||
(
|
||||
/* call port */
|
||||
'$enter_goal'(GoalNumber, G, Module),
|
||||
'$spycall'(G, Module, InControl),
|
||||
'$spycall'(G, Module, InControl, Retry),
|
||||
(
|
||||
'$debugger_deterministic_goal'(G) ->
|
||||
Det=true
|
||||
@ -384,6 +386,7 @@ debugging :-
|
||||
),
|
||||
/* go execute the predicate */
|
||||
(
|
||||
Retry = false ->
|
||||
'$show_trace'(exit,G,Module,GoalNumber,Det), /* output message at exit */
|
||||
/* exit port */
|
||||
/* get rid of deterministic computations */
|
||||
@ -400,7 +403,6 @@ debugging :-
|
||||
/* we get here when we want to redo a goal */
|
||||
/* redo port */
|
||||
'$show_trace'(redo,G,Module,GoalNumber,_), /* inform user_error */
|
||||
Retry = true,
|
||||
'$continue_debugging'(InControl,G,Module),
|
||||
fail /* to backtrack to spycalls */
|
||||
)
|
||||
@ -439,46 +441,41 @@ debugging :-
|
||||
number(StopPoint)
|
||||
->
|
||||
StopPoint < GoalNumber
|
||||
;
|
||||
% skip goals and ports (eg, l).
|
||||
StopPoint == spy(StoPoint)
|
||||
->
|
||||
\+ '$pred_being_spied'(G, Module), StopPoint < GoalNumber
|
||||
).
|
||||
|
||||
|
||||
%
|
||||
'$spycall'(G, M, _) :-
|
||||
'$spycall'(G, M, _, _) :-
|
||||
nb_getval('$debug_run',StopPoint),
|
||||
StopPoint \= off,
|
||||
!,
|
||||
'$execute_nonstop'(G, M).
|
||||
'$spycall'(G, M, _) :-
|
||||
'$spycall'(G, M, _, _) :-
|
||||
'$system_predicate'(G,M),
|
||||
\+ '$is_metapredicate'(G,M),
|
||||
!,
|
||||
'$execute_nonstop'(G, M).
|
||||
'$spycall'(G, M, InControl) :-
|
||||
'$spycall'(G, M, InControl, InRedo) :-
|
||||
'$flags'(G,M,F,F),
|
||||
F /\ 0x18402000 =\= 0, !, % dynamic procedure, logical semantics, user-C, or source
|
||||
% use the interpreter
|
||||
CP is '$last_choice_pt',
|
||||
'$clause'(G, M, Cl),
|
||||
'$do_spy'(Cl, M, CP, InControl).
|
||||
'$spycall'(G, M, InControl) :-
|
||||
( '$do_spy'(Cl, M, CP, InControl) ; InRedo = true ).
|
||||
'$spycall'(G, M, InControl, InRedo) :-
|
||||
'$undefined'(G, M), !,
|
||||
'$enter_undefp',
|
||||
(
|
||||
'$find_undefp_handler'(G,M,Goal,NM)
|
||||
->
|
||||
'$spycall'(Goal, NM, InControl)
|
||||
'$spycall'(Goal, NM, InControl, InRedo)
|
||||
).
|
||||
'$spycall'(G, M, InControl) :-
|
||||
'$spycall'(G, M, InControl, InRedo) :-
|
||||
% I lost control here.
|
||||
CP is '$last_choice_pt',
|
||||
'$static_clause'(G,M,_,R),
|
||||
'$continue_debugging'(InControl, G, M),
|
||||
'$execute_clause'(G, M, R, CP).
|
||||
( '$execute_clause'(G, M, R, CP) ; InRedo = true ).
|
||||
|
||||
'$trace'(P,G,Module,L,Deterministic) :-
|
||||
% at this point we are done with leap or skip
|
||||
@ -562,7 +559,6 @@ debugging :-
|
||||
halt.
|
||||
'$action'(0'f,_,CallId,_,_,_) :- !, % f fail
|
||||
'$scan_number'(0'f, CallId, GoalId),
|
||||
nb_setval('$debug,on'),
|
||||
throw('$fail_spy'(GoalId)).
|
||||
'$action'(0'h,_,_,_,_,_) :- !, % h help
|
||||
'$action_help',
|
||||
@ -588,15 +584,15 @@ debugging :-
|
||||
),
|
||||
'$skipeol'(0'd),
|
||||
fail.
|
||||
'$action'(0'l,_,CallNumber,_,_,on) :- !, % l leap
|
||||
'$action'(0'l,_,_,_,_,on) :- !, % l leap
|
||||
'$skipeol'(0'l),
|
||||
nb_setval('$debug_run',spy).
|
||||
'$action'(0'z,_,CallNumber,_,_,zip) :- !, % k zip, fast leap
|
||||
'$action'(0'z,_,_,_,_,zip) :- !, % k zip, fast leap
|
||||
'$skipeol'(0'z),
|
||||
nb_setval('$debug_run',spy).
|
||||
% skip first call (for current goal),
|
||||
% stop next time.
|
||||
'$action'(0'k,_,CallNumber,_,_,zip) :- !, % k zip, fast leap
|
||||
'$action'(0'k,_,_,_,_,zip) :- !, % k zip, fast leap
|
||||
'$skipeol'(0'k),
|
||||
nb_setval('$debug_run',spy).
|
||||
% skip first call (for current goal),
|
||||
@ -646,7 +642,7 @@ debugging :-
|
||||
'$continue_debugging'(_,G,M) :-
|
||||
'$system_predicate'(G,M), !,
|
||||
'$late_creep'.
|
||||
'$continue_debugging'(_,G,M) :-
|
||||
'$continue_debugging'(_,_,_) :-
|
||||
'nb_getval'('$debug_run',Zip),
|
||||
(Zip == nodebug ; number(Zip) ; Zip = spy(_) ), !.
|
||||
'$continue_debugging'(_,_,_) :-
|
||||
@ -676,11 +672,11 @@ debugging :-
|
||||
'$show_ancestor'(_,_,_,_,Det,HowMany,HowMany) :-
|
||||
nonvar(Det), !.
|
||||
% look at retry
|
||||
'$show_ancestor'(GoalNumber, M, G, Retry, Det, HowMany, HowMany1) :-
|
||||
'$show_ancestor'(GoalNumber, M, G, Retry, _, HowMany, HowMany1) :-
|
||||
nonvar(Retry), !,
|
||||
HowMany1 is HowMany-1,
|
||||
'$trace_msg'(redo, G, M, GoalNumber, _), nl(user_error).
|
||||
'$show_ancestor'(GoalNumber, M, G, Retry, Det, HowMany, HowMany1) :-
|
||||
'$show_ancestor'(GoalNumber, M, G, _, _, HowMany, HowMany1) :-
|
||||
HowMany1 is HowMany-1,
|
||||
'$trace_msg'(call, G, M, GoalNumber, _), nl(user_error).
|
||||
|
||||
@ -831,18 +827,27 @@ debugging :-
|
||||
format(user_error,' [~d] ~q~n',[Level,G]).
|
||||
|
||||
'$debugger_deterministic_goal'(G) :-
|
||||
yap_hacks:current_choicepoints(CPs),
|
||||
'$debugger_skip_traces'(CPs,CPs1),
|
||||
'$debugger_skip_loop_spy2'(CPs1,[Catch|_]),
|
||||
yap_hacks:current_choicepoints(CPs0),
|
||||
% $cps(CPs0),
|
||||
'$debugger_skip_traces'(CPs0,CPs1),
|
||||
'$debugger_skip_loop_spy2'(CPs1,CPs2),
|
||||
'$debugger_skip_spycall'(CPs2,CPs3),
|
||||
'$debugger_skip_loop_spy2'(CPs3,[Catch|_]),
|
||||
yap_hacks:choicepoint(Catch,_,prolog,'$catch',3,'$catch'(_,'$loop_spy_event'(_,_,G,_,_),_),_).
|
||||
|
||||
|
||||
'$cps'([CP|CPs]) :-
|
||||
yap_hacks:choicepoint(CP,_,_,_,_,_,_),
|
||||
yap_hacks:choicepoint(CP,A,B,C,D,E,F),
|
||||
write(A:B:C:D:E:F),nl,
|
||||
'$cps'(CPs).
|
||||
'$cps'([]).
|
||||
|
||||
|
||||
'$debugger_skip_spycall'([CP|CPs],CPs1) :-
|
||||
yap_hacks:choicepoint(CP,_,prolog,'$spycall',4,(_;_),_), !,
|
||||
'$debugger_skip_spycall'(CPs,CPs1).
|
||||
'$debugger_skip_spycall'(CPs,CPs).
|
||||
|
||||
'$debugger_skip_traces'([CP|CPs],CPs1) :-
|
||||
yap_hacks:choicepoint(CP,_,prolog,'$trace',4,(_;_),_), !,
|
||||
'$debugger_skip_traces'(CPs,CPs1).
|
||||
|
@ -65,7 +65,7 @@
|
||||
'$discontiguous'(D,M).
|
||||
'$exec_directive'(initialization(D), _, M) :-
|
||||
'$initialization'(M:D).
|
||||
'$exec_directive'(encoding(Enc), _, M) :-
|
||||
'$exec_directive'(encoding(Enc), _, _) :-
|
||||
'$current_encoding'(Enc).
|
||||
'$exec_directive'(parallel, _, _) :-
|
||||
'$parallel'.
|
||||
@ -107,7 +107,7 @@
|
||||
'$load_files'(M:F, [if(not_loaded)],use_module(F)).
|
||||
'$exec_directive'(use_module(F,Is), _, M) :-
|
||||
'$load_files'(M:F, [if(not_loaded),imports(Is)],use_module(F,Is)).
|
||||
'$exec_directive'(use_module(Mod,F,Is), _, M) :-
|
||||
'$exec_directive'(use_module(Mod,F,Is), _, _) :-
|
||||
'$use_module'(Mod,F,Is).
|
||||
'$exec_directive'(block(BlockSpec), _, _) :-
|
||||
'$block'(BlockSpec).
|
||||
|
@ -11,8 +11,11 @@
|
||||
* File: errors.yap *
|
||||
* comments: error messages for YAP *
|
||||
* *
|
||||
* Last rev: $Date: 2006-12-13 16:10:26 $,$Author: vsc $ *
|
||||
* Last rev: $Date: 2007-01-24 14:20:04 $,$Author: vsc $ *
|
||||
* $Log: not supported by cvs2svn $
|
||||
* Revision 1.79 2006/12/13 16:10:26 vsc
|
||||
* several debugger and CLP(BN) improvements.
|
||||
*
|
||||
* Revision 1.78 2006/05/22 16:12:01 tiagosoares
|
||||
* MYDDAS: MYDDAS version boot message
|
||||
*
|
||||
@ -169,7 +172,6 @@
|
||||
'$process_error'(Error, Level),
|
||||
fail.
|
||||
'$LoopError'(_, _) :-
|
||||
current_stream(_, write, S),
|
||||
flush_all_streams,
|
||||
fail.
|
||||
|
||||
@ -296,7 +298,7 @@ print_message(Level, Mss) :-
|
||||
[M,F,N]).
|
||||
'$do_print_message'(breakpoints([])) :- !,
|
||||
format(user_error,'There are no spy-points set.',
|
||||
[M,F,N]).
|
||||
[]).
|
||||
'$do_print_message'(breakpoints(L)) :- !,
|
||||
format(user_error,'Spy-points set on:', []),
|
||||
'$print_list_of_preds'(L).
|
||||
@ -317,7 +319,7 @@ print_message(Level, Mss) :-
|
||||
[From,Pred,To]).
|
||||
'$do_print_message'(leash([])) :- !,
|
||||
format(user_error,'No leashing.',
|
||||
[M,F,N]).
|
||||
[]).
|
||||
'$do_print_message'(leash([A|B])) :- !,
|
||||
format(user_error,'Leashing set to ~w.',
|
||||
[[A|B]]).
|
||||
@ -378,13 +380,13 @@ print_message(Level, Mss) :-
|
||||
'$close_stack_dump'(PEnvs, PCPs).
|
||||
|
||||
'$preprocess_stack'([], _, []).
|
||||
'$preprocess_stack'([G|Gs],40, [overflow]) :- !.
|
||||
'$preprocess_stack'([_|_],40, [overflow]) :- !.
|
||||
'$preprocess_stack'([G|Gs],I, NGs) :-
|
||||
'$pred_for_code'(G,Name,Arity,Mod,Clause),
|
||||
I1 is I+1,
|
||||
'$beautify_stack_goal'(Name,Arity,Mod,Clause,Gs,I1,NGs).
|
||||
|
||||
'$beautify_stack_goal'(Name,Arity,Module,0,Gs,I,NGs) :- !,
|
||||
'$beautify_stack_goal'(_,_,_,0,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs,I,NGs).
|
||||
'$beautify_stack_goal'(Name,Arity,Module,Clause,Gs,I,NGs) :-
|
||||
functor(G,Name,Arity),
|
||||
@ -399,47 +401,47 @@ print_message(Level, Mss) :-
|
||||
'$beautify_hidden_goal'('$query',_,_,_,_,_,[]) :- !.
|
||||
'$beautify_hidden_goal'('$enter_top_level',_,_,_,_,_,[]) :- !.
|
||||
% The user should never know these exist.
|
||||
'$beautify_hidden_goal'('$csult',_,prolog,ClNo,Gs,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$csult',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$use_module',2,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$use_module',2,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$ensure_loaded',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$ensure_loaded',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$continue_with_command',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$continue_with_command',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$spycall_stdpred',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$spycall_stdpred',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$spycalls',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$spycalls',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$spycall',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$spycall',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$do_spy',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$do_spy',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$spy',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$spy',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$do_creep_execute',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$do_creep_execute',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$creep_execute',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$creep_execute',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$direct_spy',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$direct_spy',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$system_catch',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$system_catch',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$execute_command',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$execute_command',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$process_directive',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$process_directive',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$catch',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$catch',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$loop',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$loop',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$consult',3,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$consult',3,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$reconsult',_,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$reconsult',_,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$undefp',1,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$undefp',1,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$use_module',2,prolog,ClNo,Gs,I,NGs) :- !,
|
||||
'$beautify_hidden_goal'('$use_module',2,prolog,_,Gs,I,NGs) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
'$beautify_hidden_goal'('$repeat',0,prolog,ClNo,Gs,I,[cl(repeat,0,prolog,ClNo)|NGs]) :- !,
|
||||
'$preprocess_stack'(Gs, I, NGs).
|
||||
@ -488,7 +490,7 @@ print_message(Level, Mss) :-
|
||||
'$prepare_loc'(Info,Where,Location) :- integer(Where), !,
|
||||
'$pred_for_code'(Where,Name,Arity,Mod,Clause),
|
||||
'$construct_code'(Clause,Name,Arity,Mod,Info,Location).
|
||||
'$prepare_loc'(Info,Where,Info).
|
||||
'$prepare_loc'(Info,_,Info).
|
||||
|
||||
'$print_stack'([]).
|
||||
'$print_stack'([overflow]) :- !,
|
||||
@ -499,7 +501,7 @@ print_message(Level, Mss) :-
|
||||
|
||||
'$show_goal'(-1,Name,Arity,Mod) :- !,
|
||||
format('~n% ~a:~a/~d at indexing code',[Mod,Name,Arity]).
|
||||
'$show_goal'(0,Name,Arity,Mod) :- !.
|
||||
'$show_goal'(0,_,_,_) :- !.
|
||||
'$show_goal'(I,Name,Arity,Mod) :-
|
||||
format(user_error,'~n% ~a:~a/~d at clause ~d',[Mod,Name,Arity,I]).
|
||||
|
||||
@ -773,7 +775,7 @@ print_message(Level, Mss) :-
|
||||
'$output_error_message'(representation_error(max_arity), Where) :-
|
||||
format(user_error,'% REPRESENTATION ERROR- ~w: number too big~n',
|
||||
[Where]).
|
||||
'$output_error_message'(syntax_error(G,0,Msg,[],0,0), Where) :- !,
|
||||
'$output_error_message'(syntax_error(G,0,Msg,[],0,0), _) :- !,
|
||||
format(user_error,'% SYNTAX ERROR: ~a',[G,Msg]).
|
||||
'$output_error_message'(syntax_error(_,_,_,Term,Pos,Start), Where) :-
|
||||
format(user_error,'% ~w ',[Where]),
|
||||
@ -885,7 +887,7 @@ print_message(Level, Mss) :-
|
||||
format(user_error,'~n<==== HERE ====>~n', []),
|
||||
'$dump_syntax_error_term'(10,-1,L).
|
||||
'$dump_syntax_error_term'(_,_,[]) :- !.
|
||||
'$dump_syntax_error_term'(I,J,[T-P|R]) :-
|
||||
'$dump_syntax_error_term'(I,J,[T-_P|R]) :-
|
||||
'$dump_error_token'(T),
|
||||
I1 is I-1,
|
||||
J1 is J-1,
|
||||
|
@ -117,7 +117,7 @@ thread_create(Goal, Id, Options) :-
|
||||
'$thread_option'(Opt, Alias, Stack, Trail, System, Detached, G0),
|
||||
'$thread_options'(Opts, Alias, Stack, Trail, System, Detached, G0).
|
||||
|
||||
'$thread_option'(Option, Alias, _, _, _, _, G0) :- var(Option), !,
|
||||
'$thread_option'(Option, _, _, _, _, _, G0) :- var(Option), !,
|
||||
'$do_error'(instantiation_error,G0).
|
||||
'$thread_option'(stack(Stack), _, Stack, _, _, _, G0) :- !,
|
||||
( \+ integer(Stack) -> '$do_error'(type_error(integer,Stack),G0) ; true ).
|
||||
@ -143,9 +143,10 @@ thread_create(Goal, Id, Options) :-
|
||||
recorda('$thread_sizes', [Id|Sizes], _),
|
||||
recorda('$thread_detached', [Id|Detached], _).
|
||||
|
||||
% vsc: ?????
|
||||
thread_defaults(Defaults) :-
|
||||
nonvar(Defaults), !,
|
||||
'$do_error'(type_error(variable,Id), thread_defaults(Defaults)).
|
||||
'$do_error'(type_error(variable,_Id), thread_defaults(Defaults)).
|
||||
thread_defaults([stack(Stack), trail(Trail), system(System), detached(Detached)]) :-
|
||||
recorded('$thread_defaults',[Stack, Trail, System, Detached], _).
|
||||
|
||||
@ -192,7 +193,7 @@ thread_set_default(Default) :-
|
||||
'$thread_set_default'(stack(Stack), G) :-
|
||||
Stack < 0, !,
|
||||
'$do_error'(domain_error(not_less_than_zero, Stack), G).
|
||||
'$thread_set_default'(stack(Stack), G) :- !,
|
||||
'$thread_set_default'(stack(Stack), _) :- !,
|
||||
recorded('$thread_defaults', [_, Trail, System, Detached], Ref),
|
||||
erase(Ref),
|
||||
recorda('$thread_defaults', [Stack, Trail, System, Detached], _).
|
||||
@ -203,7 +204,7 @@ thread_set_default(Default) :-
|
||||
'$thread_set_default'(trail(Trail), G) :-
|
||||
Trail < 0, !,
|
||||
'$do_error'(domain_error(not_less_than_zero, Trail), G).
|
||||
'$thread_set_default'(trail(Trail), G) :- !,
|
||||
'$thread_set_default'(trail(Trail), _) :- !,
|
||||
recorded('$thread_defaults', [Stack, _, System, Detached], Ref),
|
||||
erase(Ref),
|
||||
recorda('$thread_defaults', [Stack, Trail, System, Detached], _).
|
||||
@ -214,7 +215,7 @@ thread_set_default(Default) :-
|
||||
'$thread_set_default'(system(System), G0) :-
|
||||
System < 0, !,
|
||||
'$do_error'(domain_error(not_less_than_zero, System), G0).
|
||||
'$thread_set_default'(system(System), G) :- !,
|
||||
'$thread_set_default'(system(System), _) :- !,
|
||||
recorded('$thread_defaults', [Stack, Trail, _, Detached], Ref),
|
||||
erase(Ref),
|
||||
recorda('$thread_defaults', [Stack, Trail, System, Detached], _).
|
||||
@ -222,7 +223,7 @@ thread_set_default(Default) :-
|
||||
'$thread_set_default'(detached(Detached), G) :-
|
||||
Detached \== true, Detached \== false, !,
|
||||
'$do_error'(type_error(boolean, Detached), G).
|
||||
'$thread_set_default'(detached(Detached), G) :- !,
|
||||
'$thread_set_default'(detached(Detached), _) :- !,
|
||||
recorded('$thread_defaults', [Stack, Trail, System, _], Ref),
|
||||
erase(Ref),
|
||||
recorda('$thread_defaults', [Stack, Trail, System, Detached], _).
|
||||
@ -579,7 +580,7 @@ thread_sleep(Time) :-
|
||||
|
||||
thread_signal(Id, Goal) :-
|
||||
'$check_thread_or_alias'(Id, thread_signal(Id, Goal)),
|
||||
'$check_callable'(Goal, thread_signal(Id, Goal)).
|
||||
'$check_callable'(Goal, thread_signal(Id, Goal)),
|
||||
'$thread_id_alias'(Id0, Id),
|
||||
( recorded('$thread_signal', [Id0| _], R), erase(R), fail
|
||||
; true
|
||||
|
@ -184,10 +184,10 @@ call_with_args(A,A1,A2,A3,A4,A5,A6,A7,A8,A9,A10) :-
|
||||
|
||||
|
||||
call_cleanup(Goal, Cleanup) :-
|
||||
call_cleanup(Goal, Catcher, Cleanup).
|
||||
call_cleanup(Goal, _Catcher, Cleanup).
|
||||
|
||||
call_cleanup(Goal, Catcher, Cleanup) :-
|
||||
catch('$call_cleanup'(Goal,Cleanup,Result),
|
||||
catch('$call_cleanup'(Goal,Cleanup,_),
|
||||
Exception,
|
||||
'$cleanup_exception'(Exception,Catcher,Cleanup)).
|
||||
|
||||
@ -806,5 +806,5 @@ nth_instance(X,Y,Z) :-
|
||||
'$system_catch'('$query'(once(G), []),Module,Error,user:'$Error'(Error)).
|
||||
|
||||
prolog_current_frame(Env) :-
|
||||
X is $env.
|
||||
Env is '$env'.
|
||||
|
||||
|
11
pl/yio.yap
11
pl/yio.yap
@ -89,9 +89,9 @@ open(F,T,S,Opts) :-
|
||||
N1 is I1\/N0,
|
||||
N2 is I2/\N1,
|
||||
'$process_open_opts'(L,N2,N, Aliases, Encoding).
|
||||
'$process_open_opts'([encoding(Enc)|L], N0, N, Aliases, T, EncCode) :-
|
||||
'$valid_encoding'(Enc, EndCode),
|
||||
'$process_open_opts'(L,N2,N, Aliases, _).
|
||||
'$process_open_opts'([encoding(Enc)|L], N0, N, Aliases, EncCode) :-
|
||||
'$valid_encoding'(Enc, EncCode),
|
||||
'$process_open_opts'(L, N0, N, Aliases, EncCode).
|
||||
'$process_open_opts'([eof_action(T)|L], N0, N, Aliases, Encoding) :-
|
||||
'$value_open_opt'(T,eof_action,I1,I2),
|
||||
N1 is I1\/N0,
|
||||
@ -232,8 +232,9 @@ open(F,T,S,Opts) :-
|
||||
|
||||
'$check_open_encoding'(X, G) :- var(X), !,
|
||||
'$do_error'(instantiation_error,G).
|
||||
'$check_open_encoding'(Encoding,_) :- '$valid_encoding'(Encoding,_), !.
|
||||
'$check_open_eof_action_arg'(Encoding,G) :-
|
||||
'$check_open_encoding'(Encoding,_) :-
|
||||
'$valid_encoding'(Encoding,_), !.
|
||||
'$check_open_encoding'(Encoding,G) :-
|
||||
'$do_error'(domain_error(io_mode,encoding(Encoding)),G).
|
||||
|
||||
'$check_read_syntax_errors_arg'(X, G) :- var(X), !,
|
||||
|
Reference in New Issue
Block a user