Skip to content

Commit

Permalink
FIXED: return exit code if swipl -c fails
Browse files Browse the repository at this point in the history
  • Loading branch information
erlanger committed Feb 5, 2019
1 parent 28a7cac commit d3f9bc1
Show file tree
Hide file tree
Showing 2 changed files with 14 additions and 3 deletions.
9 changes: 7 additions & 2 deletions boot/init.pl
Original file line number Diff line number Diff line change
Expand Up @@ -1869,6 +1869,7 @@
'$must_be'(list, Options),
'$load_files'(Files, Module, Options).

:- dynamic '$load_file_exception'/1.
'$load_files'(X, _, _) :-
var(X),
!,
Expand All @@ -1885,15 +1886,19 @@
List = [_|_],
!,
'$must_be'(list, List),
'$load_file_list'(List, Module, Options).
'$load_file_list'(List, Module, Options),
( '$load_file_exception'(E)
-> throw(E)
; true
).
'$load_files'(File, Module, Options) :-
'$load_one_file'(File, Module, Options).

'$load_file_list'([], _, _).
'$load_file_list'([File|Rest], Module, Options) :-
E = error(_,_),
catch('$load_one_file'(File, Module, Options), E,
'$print_message'(error, E)),
assertz('$load_file_exception'(E)) ),
'$load_file_list'(Rest, Module, Options).


Expand Down
8 changes: 7 additions & 1 deletion boot/toplevel.pl
Original file line number Diff line number Diff line change
Expand Up @@ -733,13 +733,19 @@
% Toplevel called when invoked with -c option.

'$compile' :-
( catch('$compile_', E, (print_message(error, E), halt(2)))
-> true
; halt(1)
).

'$compile_' :-
'$load_system_init_file',
'$set_file_search_paths',
init_debug_flags,
'$run_initialization',
attach_packs,
use_module(library(qsave)),
catch(qsave:qsave_toplevel, E, (print_message(error, E), halt(1))).
qsave:qsave_toplevel.

%! '$config'
%
Expand Down

0 comments on commit d3f9bc1

Please sign in to comment.