% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \subsection{library(shlib): Utility library for loading foreign objects (DLLs, shared objects)} \label{sec:shlib} This section discusses the functionality of the (autoload) \file{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 \const{mylib}. First, one must assemble the resource and make it compatible to SWI-Prolog. The details for this vary between platforms. The swipl-\verb$ld(1)$ utility can be used to deal with this in a portable manner. The typical commandline is: \begin{code} swipl-ld -o mylib file.{c,o,cc,C} ... \end{code} Make sure that one of the files provides a global function \verb$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: \begin{code} #include #include 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); } \end{code} Now write a file \file{mylib.pl}: \begin{code} :- module(mylib, [ say_hello/1 ]). :- use_foreign_library(foreign(mylib)). \end{code} The file \file{mylib.pl} can be loaded as a normal Prolog file and provides the predicate defined in C.\vspace{0.7cm} \begin{description} \predicate[det]{use_foreign_library}{1}{+FileSpec} \nodescription \predicate[det]{use_foreign_library}{2}{+FileSpec, +Options:list} Load and install a foreign library as \predref{load_foreign_library}{1},2 and register the installation using \predref{initialization}{2} with the option \const{now}. This is similar to using: \begin{code} :- initialization(load_foreign_library(foreign(mylib))). \end{code} but using the \predref{initialization}{1} wrapper causes the library to be loaded \textit{after} loading of the file in which it appears is completed, while \predref{use_foreign_library}{1} loads the library \textit{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, \predref{use_foreign_library}{1},2 is in provided as a built-in predicate that, if necessary, loads \file{library(shlib)}. This implies that these directives can be used without explicitly loading \file{library(shlib)} or relying on demand loading. \qpredicate[semidet,multifile]{qsave}{compat_arch}{2}{Arch1, Arch2}User definable hook to establish if \arg{Arch1} is compatible with \arg{Arch2} when running a shared object. It is used in saved states produced by \predref{qsave_program}{2} to determine which shared object to load at runtime. \begin{tags} \tag{See also} \const{foreign} option in \predref{qsave_program}{2} for more information. \end{tags} \predicate[det]{load_foreign_library}{1}{:FileSpec} \nodescription \predicate[det]{load_foreign_library}{2}{:FileSpec, +Options:list} Load a \textit{shared object} or \textit{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 \verb$install_mylib()$. If the platform prefixes extern functions with =_=, this prefix is added before calling. \arg{Options} provided are below. Other options are passed to \predref{open_shared_object}{3}. \begin{description} \termitem{install}{+Function} Installation function to use. Default is \verb$default(install)$, which derives the function from \arg{FileSpec}. \end{description} \begin{code} ... load_foreign_library(foreign(mylib)), ... \end{code} \begin{arguments} \arg{FileSpec} & is a specification for \predref{absolute_file_name}{3}. If searching the file fails, the plain name is passed to the OS to try the default method of the OS for locating foreign objects. The default definition of \predref{file_search_path}{2} searches $<$prolog home$>$/lib/$<$arch$>$ on Unix and $<$prolog home$>$/bin on Windows. \\ \end{arguments} \begin{tags} \tag{See also} \predref{use_foreign_library}{1},2 are intended for use in directives. \end{tags} \predicate[det]{unload_foreign_library}{1}{+FileSpec} \nodescription \predicate[det]{unload_foreign_library}{2}{+FileSpec, +Exit:atom} Unload a \textit{shared object} or \textit{DLL}. After calling the \arg{Exit} function, the shared object is removed from the process. The default exit function is composed from =uninstall_=, followed by the file base-name. \predicate{current_foreign_library}{2}{?File, ?Public} Query currently loaded shared libraries. \predicate{reload_foreign_libraries}{0}{} Reload all foreign libraries loaded (after restore of a state created using \predref{qsave_program}{2}. \end{description}