|
45 | 45 | use_foreign_library/1, % :LibFile
|
46 | 46 | use_foreign_library/2, % :LibFile, +InstallFunc
|
47 | 47 |
|
| 48 | + qsave_foreign_libraries/4, % ?Arch, +Spec, -Resources, +Options |
| 49 | + |
48 | 50 | win_add_dll_directory/1 % +Dir
|
49 | 51 | ]).
|
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)). |
51 | 57 | :- set_prolog_flag(generate_debug_info, false).
|
52 | 58 |
|
53 | 59 | /** <module> Utility library for loading foreign objects (DLLs, shared objects)
|
|
148 | 154 |
|
149 | 155 | find_library(Spec, TmpFile, true) :-
|
150 | 156 | '$rc_handle'(Zipper),
|
151 |
| - term_to_atom(Spec, Name), |
152 | 157 | setup_call_cleanup(
|
153 | 158 | zip_lock(Zipper),
|
154 | 159 | setup_call_cleanup(
|
155 |
| - open_foreign_in_resources(Zipper, Name, In), |
| 160 | + open_foreign_in_resources(Zipper, Spec, In), |
156 | 161 | setup_call_cleanup(
|
157 | 162 | tmp_file_stream(binary, TmpFile, Out),
|
158 | 163 | copy_stream_data(In, Out),
|
|
174 | 179 | find_library(foreign(Spec), Spec, false) :-
|
175 | 180 | atom(Spec),
|
176 | 181 | !. % 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 | + ). |
179 | 207 |
|
180 | 208 | %! lib_to_file(+Lib0, -Lib, -Copy) is det.
|
181 | 209 | %
|
|
208 | 236 | lib_to_file(Lib, Lib, false).
|
209 | 237 |
|
210 | 238 |
|
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)), |
217 | 244 | zipper_open_current(Zipper, Stream,
|
218 | 245 | [ type(binary),
|
219 | 246 | release(true)
|
220 | 247 | ]).
|
221 | 248 |
|
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. |
223 | 310 | %
|
224 | 311 | % Entries is a list of entries in the zip file, which are already
|
225 | 312 | % filtered to match the shared library identified by `Name`. The
|
|
230 | 317 | % determined according to the description in qsave_program/2 using the
|
231 | 318 | % qsave:compat_arch/2 hook.
|
232 | 319 | %
|
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). |
243 | 333 |
|
| 334 | +:- multifile qsave:compat_arch/2. |
244 | 335 | qsave_compat_arch1(Arch1, Arch2) :-
|
245 | 336 | qsave:compat_arch(Arch1, Arch2), !.
|
246 | 337 | qsave_compat_arch1(Arch1, Arch2) :-
|
|
258 | 349 |
|
259 | 350 | qsave:compat_arch(A,A).
|
260 | 351 |
|
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''('), |
263 | 355 | !,
|
264 |
| - term_to_atom(shlib(Arch,Name), Atom). |
| 356 | + term_to_atom(Term, Atom). |
265 | 357 | shlib_atom_to_term(Atom, Atom).
|
266 | 358 |
|
267 |
| -match_filespec(Name, shlib(_,Name)). |
| 359 | +match_filespec(FileSpec, '$shlib'(_, FileSpec, _, _)). |
268 | 360 |
|
269 |
| -entries_for_name(Name, Entries, Filtered) :- |
| 361 | +entries_for_name(FileSpec, Entries, Filtered) :- |
270 | 362 | maplist(shlib_atom_to_term, Entries, Entries1),
|
271 |
| - include(match_filespec(Name), Entries1, Filtered). |
| 363 | + include(match_filespec(FileSpec), Entries1, Filtered). |
272 | 364 |
|
273 | 365 | base(Path, Base) :-
|
274 | 366 | atomic(Path),
|
|
355 | 447 | install(Path, Entries)),
|
356 | 448 | _))
|
357 | 449 | ).
|
358 |
| -load_foreign_library(LibFile, _, _) :- |
| 450 | +load_foreign_library(LibFile, Module, Entry) :- |
| 451 | + current_prolog_flag(arch, Arch), |
359 | 452 | retractall(loading(LibFile)),
|
360 | 453 | ( error(_Path, E)
|
361 | 454 | -> 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}) |
364 | 461 | ).
|
365 | 462 |
|
366 | 463 | delete_foreign_lib(true, Path) :-
|
|
557 | 654 | [ 'No install function in ~q'-[Lib], nl,
|
558 | 655 | '\tTried: ~q'-[List]
|
559 | 656 | ].
|
| 657 | + |
| 658 | +% vim: set sw=4 ft=prolog : |
0 commit comments