shlib.pl -- Utility library for loading foreign objects (DLLs, shared objects)
This section discusses the functionality of the (autoload)
library(shlib), providing an interface to manage shared libraries. We
describe the procedure for using a foreign resource (DLL in Windows and
shared object in Unix) called mylib
.
First, one must assemble the resource and make it compatible to
SWI-Prolog. The details for this vary between platforms. The swipl-ld(1)
utility can be used to deal with this in a portable manner. The typical
commandline is:
swipl-ld -o mylib file.{c,o,cc,C} ...
Make sure that one of the files provides a global function
install_mylib()
that initialises the module using calls to
PL_register_foreign(). Here is a simple example file mylib.c, which
creates a Windows MessageBox:
#include <windows.h> #include <SWI-Prolog.h> static foreign_t pl_say_hello(term_t to) { char *a; if ( PL_get_atom_chars(to, &a) ) { MessageBox(NULL, a, "DLL test", MB_OK|MB_TASKMODAL); PL_succeed; } PL_fail; } install_t install_mylib() { PL_register_foreign("say_hello", 1, pl_say_hello, 0); }
Now write a file mylib.pl
:
:- module(mylib, [ say_hello/1 ]). :- use_foreign_library(foreign(mylib)).
The file mylib.pl
can be loaded as a normal Prolog file and provides the
predicate defined in C.
- use_foreign_library(+FileSpec) is det
- use_foreign_library(+FileSpec, +Entry:atom) is det
- Load and install a foreign library as load_foreign_library/1,2 and
register the installation using initialization/2 with the option
now
. This is similar to using::- initialization(load_foreign_library(foreign(mylib))).
but using the initialization/1 wrapper causes the library to be loaded after loading of the file in which it appears is completed, while use_foreign_library/1 loads the library immediately. I.e. the difference is only relevant if the remainder of the file uses functionality of the C-library.
As of SWI-Prolog 8.1.22, use_foreign_library/1,2 is in provided as a built-in predicate that, if necessary, loads library(shlib). This implies that these directives can be used without explicitly loading library(shlib) or relying on demand loading.
- find_library(+LibSpec, -Lib, -Delete) is det[private]
- Find a foreign library from LibSpec. If LibSpec is available as
a resource, the content of the resource is copied to a temporary
file and Delete is unified with
true
. - lib_to_file(+Lib0, -Lib, -Copy) is det[private]
- If Lib0 is not a regular file we need to copy it to a temporary
regular file because
dlopen()
and Windows LoadLibrary() expect a file name. On some systems this can be avoided. Roughly using two approaches (after discussion with Peter Ludemann):- On FreeBSD there is
shm_open()
to create an anonymous file in memory and thanfdlopen()
to link this. - In general, we could redefine the system calls
open()
, etc. to makedlopen()
work on non-files. This is highly non-portably though. - We can mount the resource zip using e.g.,
fuse-zip
on Linux. This however fails if we include the resources as a string in the executable.
- On FreeBSD there is
- zipper_members_(+Zipper, -Members) is det[private]
- Simplified version of zipper_members/2 from library(zip). We already have a lock on the zipper and by moving this here we avoid dependency on another library.
- compatible_architecture_lib(+Entries, +Name, -CompatibleLib) is det[private]
- Entries is a list of entries in the zip file, which are already
filtered to match the shared library identified by Name. The
filtering is done by entries_for_name/3.
CompatibleLib is the name of the entry in the zip file which is compatible with the current architecture. The compatibility is determined according to the description in qsave_program/2 using the compat_arch/2 hook.
The entries are of the form '
shlib(Arch, Name)
' - qsave:compat_arch(Arch1, Arch2) is semidet[multifile]
- User definable hook to establish if Arch1 is compatible with Arch2 when running a shared object. It is used in saved states produced by qsave_program/2 to determine which shared object to load at runtime.
- load_foreign_library(:FileSpec) is det
- load_foreign_library(:FileSpec, +Entry:atom) is det
- Load a shared object or DLL. After loading the Entry
function is called without arguments. The default entry function
is composed from =install_=, followed by the file base-name.
E.g., the load-call below calls the function
install_mylib()
. If the platform prefixes extern functions with =_=, this prefix is added before calling.... load_foreign_library(foreign(mylib)), ...
- unload_foreign_library(+FileSpec) is det
- unload_foreign_library(+FileSpec, +Exit:atom) is det
- Unload a shared object or DLL. After calling the Exit function, the shared object is removed from the process. The default exit function is composed from =uninstall_=, followed by the file base-name.
- current_foreign_library(?File, ?Public)
- Query currently loaded shared libraries.
- reload_foreign_libraries
- Reload all foreign libraries loaded (after restore of a state created using qsave_program/2.
- unload_foreign(+File)[private]
- Unload the given foreign file and all `spontaneous' foreign predicates created afterwards. Handling these spontaneous predicates is a bit hard, as we do not know who created them and on which library they depend.
- win_add_dll_directory(+AbsDir) is det
- Add AbsDir to the directories where dependent DLLs are searched on Windows systems.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.