Skip to content

Commit d3f9bc1

Browse files
author
erlanger
committed
FIXED: return exit code if swipl -c fails
1 parent 28a7cac commit d3f9bc1

File tree

2 files changed

+14
-3
lines changed

2 files changed

+14
-3
lines changed

boot/init.pl

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1869,6 +1869,7 @@
18691869
'$must_be'(list, Options),
18701870
'$load_files'(Files, Module, Options).
18711871

1872+
:- dynamic '$load_file_exception'/1.
18721873
'$load_files'(X, _, _) :-
18731874
var(X),
18741875
!,
@@ -1885,15 +1886,19 @@
18851886
List = [_|_],
18861887
!,
18871888
'$must_be'(list, List),
1888-
'$load_file_list'(List, Module, Options).
1889+
'$load_file_list'(List, Module, Options),
1890+
( '$load_file_exception'(E)
1891+
-> throw(E)
1892+
; true
1893+
).
18891894
'$load_files'(File, Module, Options) :-
18901895
'$load_one_file'(File, Module, Options).
18911896

18921897
'$load_file_list'([], _, _).
18931898
'$load_file_list'([File|Rest], Module, Options) :-
18941899
E = error(_,_),
18951900
catch('$load_one_file'(File, Module, Options), E,
1896-
'$print_message'(error, E)),
1901+
assertz('$load_file_exception'(E)) ),
18971902
'$load_file_list'(Rest, Module, Options).
18981903

18991904

boot/toplevel.pl

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -733,13 +733,19 @@
733733
% Toplevel called when invoked with -c option.
734734

735735
'$compile' :-
736+
( catch('$compile_', E, (print_message(error, E), halt(2)))
737+
-> true
738+
; halt(1)
739+
).
740+
741+
'$compile_' :-
736742
'$load_system_init_file',
737743
'$set_file_search_paths',
738744
init_debug_flags,
739745
'$run_initialization',
740746
attach_packs,
741747
use_module(library(qsave)),
742-
catch(qsave:qsave_toplevel, E, (print_message(error, E), halt(1))).
748+
qsave:qsave_toplevel.
743749

744750
%! '$config'
745751
%

0 commit comments

Comments
 (0)