
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 detnow. 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]true.
lib_to_file(+Lib0, -Lib, -Copy) is det[private]dlopen() and Windows LoadLibrary() expect a
file name. On some systems this can be avoided. Roughly using two
approaches (after discussion with Peter Ludemann):
shm_open() to create an anonymous file in
memory and than fdlopen() to link this.open(), etc. to
make dlopen() work on non-files. This is highly non-portably
though.fuse-zip on Linux.
This however fails if we include the resources as a string in
the executable.
zipper_members_(+Zipper, -Members) is det[private]
compatible_architecture_lib(+Entries, +Name, -CompatibleLib) is det[private]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 qsave:compat_arch/2 hook.
The entries are of the form 'shlib(Arch, Name)'
qsave:compat_arch(Arch1, Arch2) is semidet[multifile]
load_foreign_library(:FileSpec) is det
load_foreign_library(:FileSpec, +Entry:atom) is detinstall_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
current_foreign_library(?File, ?Public)
reload_foreign_libraries
unload_foreign(+File)[private]
win_add_dll_directory(+AbsDir) is det[private]%PATH%.