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 -shared -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(). Below is a simple example file mylib.c
, which
prints a "hello" message. Note that we use SWI-Prolog's Sprintf() rather
than C standard printf()
to print the outout through Prolog's
current_output
stream, making the example work in a windowed
environment. The standard C printf()
works in a console environment, but
this bypasses Prolog's output redirection. Also note the use of the
standard C bool
type, which is supported in 9.2.x and more actively
promoted in the 9.3.x development series.
#include <SWI-Prolog.h> #include <SWI-Stream.h> #include <stdbool.h> static foreign_t pl_say_hello(term_t to) { char *s; if ( PL_get_chars(to, &s, CVT_ALL|REP_UTF8) ) { Sprintf("hello %Us", s); return true; } return false; } install_t install_mylib(void) { 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. The generated mylib.so
(or .dll
, etc.)
must be placed in a directory searched for using the Prolog search path
foreign
(see absolute_file_name/3). To load this from the current
directory, we can use the -p alias=dir
option:
swipl -p foreign=. mylib.pl ?- say_hello(world). hello world true.
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.
true
.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.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)
'
install_mylib()
. If the platform
prefixes extern functions with =_=, this prefix is added before
calling. Options provided are below. Other options are passed to
open_shared_object/3.
default(install)
,
which derives the function from FileSpec.... load_foreign_library(foreign(mylib)), ...
%PATH%
.