improve error handling

This commit is contained in:
Vítor Santos Costa 2015-09-29 23:49:03 +01:00
parent c61e721e73
commit e8bf2d4349
6 changed files with 62 additions and 20 deletions

View File

@ -1 +1 @@
48 52

View File

@ -112,7 +112,7 @@ q(A):-
A is 22. A is 22.
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
*/ w*/
do_not_compile_expressions :- set_value('$c_arith',[]). do_not_compile_expressions :- set_value('$c_arith',[]).
'$c_built_in'(IN, M, H, OUT) :- '$c_built_in'(IN, M, H, OUT) :-
@ -128,14 +128,12 @@ do_c_built_in(Mod:G, _, H, OUT) :-
var(G1), !, var(G1), !,
do_c_built_metacall(G1, M1, H, OUT). do_c_built_metacall(G1, M1, H, OUT).
do_c_built_in('C'(A,B,C), _, _, (A=[B|C])) :- !. do_c_built_in('C'(A,B,C), _, _, (A=[B|C])) :- !.
do_c_built_in('$do_error'( Error, Goal), M, H, do_c_built_in('$do_error'( Error, Goal), M, Head,
('$p_and_cp'(Goal, Caller), (clause_location(Call, Caller),
functor(H,Na,Ar), strip_module(M:Goal,M1,NGoal),
throw(error(Error, [g=Goal,c=c(M:Na/Ar,File,FilePos),p=Caller])) throw(error(Error, [[g|g(M1:NGoal)],[p|Call],[e|Caller],[h|g(Head)]]))
) )
):- ) :- !.
stream_property( loop_stream, name(File) ),
stream_property( loop_stream, position(FilePos) ).
do_c_built_in(X is Y, M, H, P) :- do_c_built_in(X is Y, M, H, P) :-
primitive(X), !, primitive(X), !,
do_c_built_in(X =:= Y, M, H, P). do_c_built_in(X =:= Y, M, H, P).
@ -157,7 +155,7 @@ do_c_built_in(phrase(NT,Xs0,Xs), Mod, _, NewGoal) :-
'$goal_expansion_allowed'(phrase(NT,Xs0,Xs), Mod), '$goal_expansion_allowed'(phrase(NT,Xs0,Xs), Mod),
Goal = phrase(NT,Xs0,Xs), Goal = phrase(NT,Xs0,Xs),
callable(NT), callable(NT),
catch('$translate_rule'((pseudo_nt --> NT), Rule), catch(prolog:'$translate_rule'((pseudo_nt --> NT), Rule),
error(Pat,ImplDep), error(Pat,ImplDep),
( \+ '$harmless_dcgexception'(Pat), ( \+ '$harmless_dcgexception'(Pat),
throw(error(Pat,ImplDep)) throw(error(Pat,ImplDep))
@ -374,7 +372,7 @@ expand_expr(Op, X, Y, O, Q, P) :-
'$harmless_dcgexception'(type_error(callable,_)). % ex: phrase(27,L) '$harmless_dcgexception'(type_error(callable,_)). % ex: phrase(27,L)
:- set_value('$c_arith',true).
/** /**
@} @}
*/ */

View File

@ -186,6 +186,7 @@ list, since backtracking could not "pass through" the cut.
*/ */
system_module(_init, _SysExps, _Decls) :- !. system_module(_init, _SysExps, _Decls) :- !.
system_module(M, SysExps, Decls) :- system_module(M, SysExps, Decls) :-
'$current_module'(prolog, M), '$current_module'(prolog, M),
@ -286,6 +287,49 @@ private(_).
:- use_system_module( '$_strict_iso', ['$check_iso_strict_clause'/1, :- use_system_module( '$_strict_iso', ['$check_iso_strict_clause'/1,
'$iso_check_goal'/2]). '$iso_check_goal'/2]).
'$prepare_goals'((A,B),(NA,NB),Any) :-
!,
'$prepare_goals'(A,NA,Any),
'$prepare_goals'(B,NB,Any).
'$prepare_goals'((A;B),(NA;NB),Any) :-
!,
'$prepare_goals'(A,NA,Any),
'$prepare_goals'(B,NB,Any).
'$prepare_goals'((A->B),(NA->NB),Any) :-
!,
'$prepare_goals'(A,NA,Any),
'$prepare_goals'(B,NB,Any).
'$prepare_goals'((A*->B),(NA*->NB),Any) :-
!,
'$prepare_goals'(A,NA,Any),
'$prepare_goals'(B,NB,Any).
'$prepare_goals'((\+ A),(\+ NA),Any) :-
!,
'$prepare_goals'(A,NA,Any).
'$prepare_goals'('$do_error'(Error,Goal),
(clause_location(Call, Caller),
writeln(Goal),
strip_module(M:Goal,M1,NGoal),
throw(error(Error, [[g|g(M1:NGoal)],[p|Call],[e|Caller],[h|g(Head)]]))
),
true) :-
!.
'$prepare_goals'(X is AOB,
is(X, IOp, A, B ),
true) :-
var(X),
functor(AOB, Op, 2),
arg(1, AOB, A),
arg(2, AOB, B),
!,
'$binary_op_as_integer'(Op,IOp).
'$prepare_goals'((A,B),(A,B),_Any).
'$prepare_clause'((H :- B), (H:-NB)) :-
'$prepare_goals'(B,NB,Any),
Any==true.
% %
% %
@ -1326,6 +1370,7 @@ bootstrap(F) :-
'$start_consult'(consult, File, LC), '$start_consult'(consult, File, LC),
file_directory_name(File, Dir), file_directory_name(File, Dir),
working_directory(OldD, Dir), working_directory(OldD, Dir),
( (
current_prolog_flag(verbose_load, silent) current_prolog_flag(verbose_load, silent)
-> ->
@ -1452,7 +1497,7 @@ expand_term(Term,Expanded) :-
% Grammar Rules expansion % Grammar Rules expansion
% %
'$expand_term_grammar'((A-->B), C) :- '$expand_term_grammar'((A-->B), C) :-
'$translate_rule'((A-->B),C), !. prolog:'$translate_rule'((A-->B),C), !.
'$expand_term_grammar'(A, A). '$expand_term_grammar'(A, A).
% %

View File

@ -431,8 +431,8 @@ load_files(Files,Opts) :-
b_setval('$source_file', File), b_setval('$source_file', File),
( var(Stream) -> ( var(Stream) ->
/* need_to_open_file */ /* need_to_open_file */
'$full_filename'(File, Y, Call), ( '$full_filename'(File, Y, Call) -> true ; '$do_error'(existence_error(source_sink,File),Call) ),
open(Y, read, Stream) ( open(Y, read, Stream) -> true ; '$do_error'(permission_error(input,stream,Y),Call) )
; ;
stream_property(Stream, file_name(Y)) stream_property(Stream, file_name(Y))
), !, ), !,
@ -446,8 +446,7 @@ load_files(Files,Opts) :-
'$start_lf'(If, Mod, Stream, TOpts, File, Y, Reexport, Imports), '$start_lf'(If, Mod, Stream, TOpts, File, Y, Reexport, Imports),
% stop_low_level_trace, % stop_low_level_trace,
close(Stream). close(Stream).
'$lf'(X, _, Call, _) :-
'$do_error'(permission_error(input,stream,X),Call).
'$start_lf'(not_loaded, Mod, _Stream, TOpts, UserFile, File, Reexport,Imports) :- '$start_lf'(not_loaded, Mod, _Stream, TOpts, UserFile, File, Reexport,Imports) :-
'$file_loaded'(File, Mod, Imports, TOpts), !, '$file_loaded'(File, Mod, Imports, TOpts), !,

View File

@ -78,7 +78,7 @@ Grammar related built-in predicates:
:- use_system_module( '$_errors', ['$do_error'/2]). :- use_system_module( '$_errors', ['$do_error'/2]).
% :- meta_predicate ^(?,0,?). % :- meta_predicate ^(?,0,?).
% ^(Xs, Goal, Xs) :- call(Goal). % ^(Xs, Goal, Xs) :- call(Goal).
% :- meta_predicate ^(?,1,?,?). % :- meta_predicate ^(?,1,?,?).
% ^(Xs0, Goal, Xs0, Xs) :- call(Goal, Xs). % ^(Xs0, Goal, Xs0, Xs) :- call(Goal, Xs).

View File

@ -119,7 +119,7 @@ print_message(_, loaded(F,C,_M,T,H)) :- !,
print_message(_, Msg) :- print_message(_, Msg) :-
format(user_error, '~w ~n', [Msg]). format(user_error, '~w ~n', [Msg]).
:- bootstrap('errors.yap'). :- bootstrap( 'arith.yap').
:- bootstrap('lists.yap'). :- bootstrap('lists.yap').
:- bootstrap('consult.yap'). :- bootstrap('consult.yap').
:- bootstrap('preddecls.yap'). :- bootstrap('preddecls.yap').
@ -129,14 +129,14 @@ print_message(_, Msg) :-
:- bootstrap('atoms.yap'). :- bootstrap('atoms.yap').
:- bootstrap('os.yap'). :- bootstrap('os.yap').
:- bootstrap('absf.yap'). :- bootstrap('absf.yap').
xs%:- start_low_level_trace. %:- Start_low_level_trace.
:-set_prolog_flag(verbose, normal). :-set_prolog_flag(verbose, normal).
:-set_prolog_flag(gc_trace, verbose). :-set_prolog_flag(gc_trace, verbose).
%:- set_prolog_flag( verbose_file_search, true ). %:- set_prolog_flag( verbose_file_search, true ).
:- [ :- [
'arith.yap', 'errors.yap',
'directives.yap', 'directives.yap',
'utils.yap', 'utils.yap',
'control.yap', 'control.yap',