Skip to content

Commit 29ba60c

Browse files
author
erlanger
committed
ENHANCED: allow user:exception for missing shlibs, save dependencies
This patch allows the user to load a shared library from the network or from the saved state by means of writing the user:exception hook. It also provides qsave_foreign_libraries/4 to retrieve foreign libraries (for a compatible architecture) from the saved state. This makes it easier to implement the user:exception hook, while abstracting from the internal naming of the shared libraries in the saved state. Accordingly qsave_program/2 is also enhanced to store dependencies for the main shared library. Test cases are also provided.
1 parent 345933c commit 29ba60c

File tree

12 files changed

+449
-65
lines changed

12 files changed

+449
-65
lines changed

library/qsave.pl

Lines changed: 52 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -38,10 +38,13 @@
3838
[ qsave_program/1, % +File
3939
qsave_program/2 % +File, +Options
4040
]).
41+
:- use_module(library(shlib)).
4142
:- use_module(library(lists)).
4243
:- use_module(library(option)).
4344
:- use_module(library(error)).
4445
:- use_module(library(apply)).
46+
:- use_module(library(zip)).
47+
:- use_module(library(prolog_autoload)).
4548

4649
/** <module> Save current program as a state or executable
4750
@@ -927,11 +930,17 @@
927930

928931
save_foreign_libraries1(Arch, RC, _Options) :-
929932
forall(current_foreign_library(FileSpec, _Predicates),
930-
( find_foreign_library(Arch, FileSpec, EntryName, File, Time),
931-
term_to_atom(EntryName, Name),
932-
zipper_append_file(RC, Name, File, [time(Time)])
933+
( find_foreign_library(Arch, FileSpec, Entries),
934+
add_shlibs_to_zip(RC, Entries)
933935
)).
934936

937+
add_shlibs_to_zip(RC, [_{entry: Entry, sofile: File, time: Time}|Entries]) :-
938+
term_to_atom(Entry, Name),
939+
zipper_append_file(RC, Name, File, [time(Time)]),
940+
add_shlibs_to_zip(RC, Entries).
941+
add_shlibs_to_zip(_, []).
942+
943+
935944
%! find_foreign_library(+Architecture, +FileSpec, -EntryName, -File, -Time)
936945
%! is det.
937946
%
@@ -944,17 +953,36 @@
944953
%
945954
% @bug Should perform OS search on failure
946955

947-
find_foreign_library(Arch, FileSpec, shlib(Arch,Name), SharedObject, Time) :-
948-
FileSpec = foreign(Name),
949-
( catch(arch_find_shlib(Arch, FileSpec, File),
956+
find_foreign_library(Arch, FileSpec, [MainEntry|Entries]) :-
957+
( catch(arch_find_shlib(Arch, FileSpec, File, DepFiles),
950958
E,
951959
print_message(error, E)),
952-
exists_file(File)
960+
exists_files([File|DepFiles])
953961
-> true
954962
; throw(error(existence_error(architecture_shlib(Arch), FileSpec),_))
955963
),
964+
time_and_strip_entries(Arch, FileSpec, main, [File], [MainEntry]),
965+
time_and_strip_entries(Arch, FileSpec, dep, DepFiles, Entries).
966+
967+
time_and_strip_entries(Arch, FileSpec, Type, [File|Files],
968+
[ _{ entry: '$shlib'(Arch, FileSpec, BaseName, Type),
969+
sofile: SharedObject,
970+
time: Time}
971+
|Entries]) :-
972+
file_base_name(File, BaseName),
956973
time_file(File, Time),
957-
strip_file(File, SharedObject).
974+
strip_file(File, SharedObject),
975+
time_and_strip_entries(Arch, FileSpec, Type, Files, Entries).
976+
time_and_strip_entries(_, _, _, [], []).
977+
978+
exists_files([File|Files]) :-
979+
( exists_file(File)
980+
-> true
981+
; print_message(error, existence_error(file, File)),
982+
fail
983+
),
984+
exists_files(Files).
985+
exists_files([]).
958986

959987
%! strip_file(+File, -Stripped) is det.
960988
%
@@ -982,24 +1010,29 @@
9821010
shell(Cmd),
9831011
exists_file(Stripped).
9841012

985-
%! qsave:arch_shlib(+Architecture, +FileSpec, -File) is det.
1013+
%! qsave:arch_shlib(+Architecture, +FileSpec, -File, -DepFiles) is det.
9861014
%
987-
% This is a user defined hook called by qsave_program/2. It is used to
988-
% find a shared library for the specified Architecture, named by
989-
% FileSpec. FileSpec is of the form foreign(Name), a specification
990-
% usable by absolute_file_name/2. The predicate should unify File with
991-
% the absolute path for the shared library that corresponds to the
992-
% specified Architecture.
1015+
% This is a user defined hook called by qsave_program/2. It is
1016+
% used to find a shared library and its dependencies for the
1017+
% specified Architecture, named by FileSpec. FileSpec is of the
1018+
% form foreign(Name), a specification usable by absolute_file_name/2.
1019+
% The predicate should unify File with the absolute path for the
1020+
% shared library that corresponds to the specified Architecture, and
1021+
% DepFiles with a list of shared libraries that need to be loaded as
1022+
% dependencies. If there are no dependencies the DepFiles should be
1023+
% bound to [].
9931024
%
9941025
% If this predicate fails to find a file for the specified
9951026
% architecture an `existence_error` is thrown.
9961027

997-
:- multifile arch_shlib/3.
1028+
:- multifile arch_shlib/4.
9981029

999-
arch_find_shlib(Arch, FileSpec, File) :-
1000-
arch_shlib(Arch, FileSpec, File),
1030+
arch_find_shlib(Arch, FileSpec, File, DepFiles) :-
1031+
arch_shlib(Arch, FileSpec, File, DepFiles),
1032+
must_be(list, DepFiles),
1033+
must_be(atom, File),
10011034
!.
1002-
arch_find_shlib(Arch, FileSpec, File) :-
1035+
arch_find_shlib(Arch, FileSpec, File, []) :-
10031036
current_prolog_flag(arch, Arch),
10041037
absolute_file_name(FileSpec,
10051038
[ file_type(executable),

library/shlib.pl

Lines changed: 130 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -45,9 +45,15 @@
4545
use_foreign_library/1, % :LibFile
4646
use_foreign_library/2, % :LibFile, +InstallFunc
4747

48+
qsave_foreign_libraries/4, % ?Arch, +Spec, -Resources, +Options
49+
4850
win_add_dll_directory/1 % +Dir
4951
]).
50-
:- use_module(library(lists), [reverse/2]).
52+
:- use_module(library(lists), [member/2, reverse/2]).
53+
:- use_module(library(error), [must_be/2]).
54+
:- use_module(library(zip)).
55+
:- use_module(library(apply)).
56+
:- use_module(library(option)).
5157
:- set_prolog_flag(generate_debug_info, false).
5258

5359
/** <module> Utility library for loading foreign objects (DLLs, shared objects)
@@ -148,11 +154,10 @@
148154

149155
find_library(Spec, TmpFile, true) :-
150156
'$rc_handle'(Zipper),
151-
term_to_atom(Spec, Name),
152157
setup_call_cleanup(
153158
zip_lock(Zipper),
154159
setup_call_cleanup(
155-
open_foreign_in_resources(Zipper, Name, In),
160+
open_foreign_in_resources(Zipper, Spec, In),
156161
setup_call_cleanup(
157162
tmp_file_stream(binary, TmpFile, Out),
158163
copy_stream_data(In, Out),
@@ -174,8 +179,31 @@
174179
find_library(foreign(Spec), Spec, false) :-
175180
atom(Spec),
176181
!. % use machines finding schema
177-
find_library(Spec, _, _) :-
178-
throw(error(existence_error(source_sink, Spec), _)).
182+
find_library(Spec, Path, Delete) :-
183+
current_prolog_flag(arch, Arch),
184+
try_user_exception(error(existence_error(source_sink, Spec), _),
185+
find_library(Spec, Path, Delete),
186+
_{arch: Arch, file: Spec}).
187+
188+
:- dynamic '$user_exception_called'/2.
189+
try_user_exception(Throw, _RetryGoal, Context) :-
190+
'$user_exception_called'(missing_shared_object, Context),
191+
retractall('$user_exception_called'(missing_shared_object, Context)),
192+
throw(Throw),
193+
!. % Allow only one retry
194+
195+
try_user_exception(Throw, RetryGoal, _{arch: Arch, file: Spec}) :-
196+
( user:exception(missing_shared_object,
197+
_{arch: Arch, file: Spec},
198+
Action)
199+
-> ( Action == retry
200+
-> asserta('$user_exception_called'(missing_shared_object,
201+
_{arch: Arch, file: Spec})),
202+
call(RetryGoal)
203+
; throw(Throw)
204+
)
205+
; throw(Throw)
206+
).
179207

180208
%! lib_to_file(+Lib0, -Lib, -Copy) is det.
181209
%
@@ -208,18 +236,77 @@
208236
lib_to_file(Lib, Lib, false).
209237

210238

211-
open_foreign_in_resources(Zipper, ForeignSpecAtom, Stream) :-
212-
term_to_atom(foreign(Name), ForeignSpecAtom),
213-
zipper_members(Zipper, Entries),
214-
entries_for_name(Name, Entries, Entries1),
215-
compatible_architecture_lib(Entries1, Name, CompatibleLib),
216-
zipper_goto(Zipper, file(CompatibleLib)),
239+
open_foreign_in_resources(Zipper, Spec, Stream) :-
240+
current_prolog_flag(arch, Arch),
241+
qsave_foreign_libraries(Arch, Spec, [CompatLib],
242+
[main, plain]),
243+
zipper_goto(Zipper, file(CompatLib.entry)),
217244
zipper_open_current(Zipper, Stream,
218245
[ type(binary),
219246
release(true)
220247
]).
221248

222-
%! compatible_architecture_lib(+Entries, +Name, -CompatibleLib) is det.
249+
%! qsave_foreign_libraries(+Arch, +FileSpec, -Resources, +Options).
250+
%
251+
% Get list of foreign libraries compatible with Arch in the
252+
% current saved state.
253+
%
254+
% Multi-architecture foreign libraries can be stored in the saved
255+
% state by qsave_program/2. See the `foreign` option. Resources is
256+
% unified with a list of file paths (in the saved state) for the
257+
% foreign library named by FileSpec. FileSpec is of the form
258+
% `foreign(Name)`. Each resource starts with `res://` so it can
259+
% be used with most file predicates, including copy_file/2. The
260+
% predicate can return the main foreign library (which defines
261+
% prolog predicates in a foreign language) and possibly its
262+
% dependencies according to the options.
263+
%
264+
% See qsave_program/2 to find out about how to store the
265+
% dependencies of a shared object.
266+
%
267+
% This predicate also calls the qsave:compat_arch/2 hook to obtain
268+
% files compatible with Arch, see qsave_program/2.
269+
%
270+
% The possible options are:
271+
% * main
272+
% Return only the main foreign library compatible with Arch.
273+
% Resources is a list with one element.
274+
% * main_and_deps
275+
% Return the main foreign lirary and any dependencies that
276+
% were stored in the saved state. Resources is a list in this
277+
% case. This is the default option.
278+
% * plain
279+
% Do not return entries with the `res://` prefix, but
280+
% just the plain entry name in the saved state. This can
281+
% be used if you want to access the object directly using
282+
% `library(zip)`, but this should be rare.
283+
%
284+
% @see qsave_program/2.
285+
qsave_foreign_libraries(Arch, FileSpec, Resources, Options) :-
286+
must_be(list(oneof([main,main_and_deps,deps,plain])), Options),
287+
'$rc_handle'(Zipper),
288+
zipper_members(Zipper, Entries),
289+
entries_for_name(FileSpec, Entries, Entries1),
290+
( option(main, Options)
291+
-> Type = main
292+
; option(main_and_deps, Options)
293+
-> Type = _
294+
; option(deps, Options)
295+
-> Type = dep
296+
; Type = _
297+
),
298+
libs_for_compat_arch(FileSpec, Entries1, Type, Arch, Es),
299+
( option(plain, Options)
300+
-> Resources = Es
301+
; maplist(entry_resource, Es, Resources)
302+
).
303+
304+
entry_resource(EntryDict, ResDict) :-
305+
format(atom(Res), 'res://~w', [EntryDict.entry]),
306+
ResDict = EntryDict.put(entry, Res).
307+
308+
309+
%! lib_for_compat_arch(+Entries, +FileSpec, -CompatibleLib) is det.
223310
%
224311
% Entries is a list of entries in the zip file, which are already
225312
% filtered to match the shared library identified by `Name`. The
@@ -230,17 +317,21 @@
230317
% determined according to the description in qsave_program/2 using the
231318
% qsave:compat_arch/2 hook.
232319
%
233-
% The entries are of the form 'shlib(Arch, Name)'
234-
235-
compatible_architecture_lib([], _, _) :- !, fail.
236-
compatible_architecture_lib(Entries, Name, CompatibleLib) :-
237-
current_prolog_flag(arch, HostArch),
238-
( member(shlib(EntryArch, Name), Entries),
239-
qsave_compat_arch1(HostArch, EntryArch)
240-
-> term_to_atom(shlib(EntryArch, Name), CompatibleLib)
241-
; existence_error(arch_compatible_with(Name), HostArch)
242-
).
320+
% The entries are of the form ''$shlib'(Arch, Name, BaseSoName)'
321+
322+
libs_for_compat_arch(FileSpec, Entries, Type, Arch, Libs) :-
323+
findall(Lib,
324+
lib_for_compat_arch(Arch, Type, Entries, FileSpec, Lib),
325+
Libs).
326+
327+
lib_for_compat_arch(Arch, Type, Entries, FileSpec,
328+
_{entry: Entry, basename: BaseName, type: Type}) :-
329+
LibTerm = '$shlib'(EntryArch, FileSpec, BaseName, Type),
330+
member(LibTerm, Entries),
331+
qsave_compat_arch1(Arch, EntryArch),
332+
term_to_atom(LibTerm, Entry).
243333

334+
:- multifile qsave:compat_arch/2.
244335
qsave_compat_arch1(Arch1, Arch2) :-
245336
qsave:compat_arch(Arch1, Arch2), !.
246337
qsave_compat_arch1(Arch1, Arch2) :-
@@ -258,17 +349,18 @@
258349

259350
qsave:compat_arch(A,A).
260351

261-
shlib_atom_to_term(Atom, shlib(Arch, Name)) :-
262-
sub_atom(Atom, 0, _, _, 'shlib('),
352+
shlib_atom_to_term(Atom, Term) :-
353+
Term = '$shlib'(_Arch, _FileSpec, _BaseSoName, _Type),
354+
sub_atom(Atom, 0, _, _, '''$shlib''('),
263355
!,
264-
term_to_atom(shlib(Arch,Name), Atom).
356+
term_to_atom(Term, Atom).
265357
shlib_atom_to_term(Atom, Atom).
266358

267-
match_filespec(Name, shlib(_,Name)).
359+
match_filespec(FileSpec, '$shlib'(_, FileSpec, _, _)).
268360

269-
entries_for_name(Name, Entries, Filtered) :-
361+
entries_for_name(FileSpec, Entries, Filtered) :-
270362
maplist(shlib_atom_to_term, Entries, Entries1),
271-
include(match_filespec(Name), Entries1, Filtered).
363+
include(match_filespec(FileSpec), Entries1, Filtered).
272364

273365
base(Path, Base) :-
274366
atomic(Path),
@@ -355,12 +447,17 @@
355447
install(Path, Entries)),
356448
_))
357449
).
358-
load_foreign_library(LibFile, _, _) :-
450+
load_foreign_library(LibFile, Module, Entry) :-
451+
current_prolog_flag(arch, Arch),
359452
retractall(loading(LibFile)),
360453
( error(_Path, E)
361454
-> retractall(error(_, _)),
362-
throw(E)
363-
; throw(error(existence_error(foreign_library, LibFile), _))
455+
try_user_exception(E,
456+
load_foreign_library(LibFile, Module, Entry),
457+
_{arch: Arch, file: LibFile})
458+
; try_user_exception(error(existence_error(foreign_library, LibFile), _),
459+
load_foreign_library(LibFile, Module, Entry),
460+
_{arch: Arch, file: LibFile})
364461
).
365462

366463
delete_foreign_lib(true, Path) :-
@@ -557,3 +654,5 @@
557654
[ 'No install function in ~q'-[Lib], nl,
558655
'\tTried: ~q'-[List]
559656
].
657+
658+
% vim: set sw=4 ft=prolog :

man/hack.doc

Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -471,6 +471,38 @@ predicates. See also \prologflag{unknown} and \secref{autoload}.
471471
\arg{Context} is instantiated to the name of the missing global
472472
variable. The hook must call nb_setval/2 or b_setval/2 before returning
473473
with the action \const{retry}.
474+
475+
\termitem{missing_shared_object}{}
476+
\arg{Context} is instantiated to _{ arch: Arch, file: FileSpec },
477+
which points to the required architecture and `FileSpec` for the
478+
missing shared library. \arg{Action} can be unified with error, to
479+
throw an exception or with retry, in order to try to reload the
480+
missing library Normally the hook will obtain the missing library
481+
from the network, or a required dependency from the saved state (see
482+
qsave_foreign_libraries/4), and put them in a directory where the
483+
system dynamic linker can find it. The following example loads a
484+
required depdency from the saved state:
485+
486+
\begin{code}
487+
:- use_foreign_library('input/shlib_with_dep.so').
488+
489+
:- assertz((
490+
user:exception(missing_shared_object,
491+
_{ arch: _, file: Spec },
492+
retry) :-
493+
handle_missing_shlib(Spec)
494+
495+
)).
496+
497+
handle_missing_shlib(Spec) :-
498+
Spec = 'input/shlib_with_dep.so',
499+
qsave_foreign_libraries(Arch, 'input/shlib_with_dep.so', [Dep], [deps]),
500+
copy_file(Dep.entry,'libdep.so'). % linker finds it in current dir
501+
502+
% here put some code that calls predicates in shlib_with_dep.so
503+
504+
\end{code}
505+
474506
\end{description}
475507
\end{description}
476508

0 commit comments

Comments
 (0)