If Prolog encounters a foreign predicate at run time it will call a
function specified in the predicate definition of the foreign predicate.
The arguments 1, ... , <arity> pass the
Prolog arguments to the goal as Prolog terms. Foreign functions should
be declared of type
foreign_t
. Deterministic foreign functions have two
alternatives to return control back to Prolog:
return TRUE
.
return FALSE
.
By default foreign predicates are deterministic. Using the
PL_FA_NONDETERMINISTIC
attribute (see PL_register_foreign())
it is possible to register a predicate as a non-deterministic predicate.
Writing non-deterministic foreign predicates is slightly more
complicated as the foreign function needs context information for
generating the next solution. Note that the same foreign function should
be prepared to be simultaneously active in more than one goal. Suppose
the natural_number_below_n/2 is a non-deterministic foreign predicate,
backtracking over all natural numbers lower than the first argument. Now
consider the following predicate:
quotient_below_n(Q, N) :- natural_number_below_n(N, N1), natural_number_below_n(N, N2), Q =:= N1 / N2, !. |
In this predicate the function natural_number_below_n/2 simultaneously generates solutions for both its invocations.
Non-deterministic foreign functions should be prepared to handle three different calls from Prolog:
PL_FIRST_CALL
)PL_REDO
)PL_CUTTED
)Both the context information and the type of call is provided by an
argument of type control_t
appended to the argument list
for deterministic foreign functions. The macro PL_foreign_control()
extracts the type of call from the control argument. The foreign
function can pass a context handle using the PL_retry*() macros
and extract the handle from the extra argument using the
PL_foreign_context*() macro.
PL_CUTTED
case and should be aware that the other
arguments are not valid in this case.
PL_FIRST_CALL
the context value is 0L. Otherwise it is the
value returned by the last PL_retry()
associated with this goal (both if the call type is PL_REDO
as PL_CUTTED
).
Note: If a non-deterministic foreign function returns using
PL_succeed or PL_fail, Prolog assumes the foreign function has cleaned
its environment. No call with control argument PL_CUTTED
will follow.
The code of figure 6 shows a skeleton for a non-deterministic foreign predicate definition.
typedef struct /* define a context structure */ { ... } context; foreign_t my_function(term_t a0, term_t a1, foreign_t handle) { struct context * ctxt; switch( PL_foreign_control(handle) ) { case PL_FIRST_CALL: ctxt = malloc(sizeof(struct context)); ... PL_retry_address(ctxt); case PL_REDO: ctxt = PL_foreign_context_address(handle); ... PL_retry_address(ctxt); case PL_CUTTED: free(ctxt); PL_succeed; } } |
The following functions provide for communication using atoms and functors.
Each argument of a foreign function (except for the control argument)
is of type term_t
, an opaque handle to a Prolog term. Three
groups of functions are available for the analysis of terms. The first
just validates the type, like the Prolog predicates var/1, atom/1,
etc and are called PL_is_*(). The second group attempts to
translate the argument into a C primitive type. These predicates take a term_t
and a pointer to the appropriate C-type and return TRUE
or
FALSE
depending on successful or unsuccessful translation.
If the translation fails, the pointed-to data is never modified.
if ( PL_is_atom(t) ) { char *s; PL_get_atom_chars(t, &s); ...; } or char *s; if ( PL_get_atom_chars(t, &s) ) { ...; } |
PL_VARIABLE | An unbound variable. The value of term as such is a unique identifier for the variable. |
PL_ATOM | A Prolog atom. |
PL_STRING | A Prolog string. |
PL_INTEGER | A Prolog integer. |
PL_FLOAT | A Prolog floating point number. |
PL_TERM | A compound term. Note that a list is a compound term ./2 . |
The functions PL_is_<type> are an alternative to PL_term_type().
The test PL_is_variable(term)
is equivalent to
PL_term_type(term) ==
PL_VARIABLE
, but the first is considerably faster. On the other
hand, using a switch over PL_term_type()
is faster and more readable then using an if-then-else using the
functions below. All these functions return either TRUE
or FALSE
.
.
The functions PL_get_*() read information from a Prolog term. Most of them take two arguments. The first is the input term and the second is a pointer to the output value or a term-reference.
BUF_RING
implies, if the data is not static (as from an atom), the data is copied
to the next buffer from a ring of four (4) buffers. This is a convenient
way of converting multiple arguments passed to a foreign predicate to
C-strings. If BUF_MALLOC is used, the data must be freed using free()
when not needed any longer.
CVT_ATOM | Convert if term is an atom |
CVT_STRING | Convert if term is a string |
CVT_LIST | Convert if term is a list of integers between 1 and 255 |
CVT_INTEGER | Convert if term is
an integer (using %d ) |
CVT_FLOAT | Convert if term is a
float (using %f ) |
CVT_NUMBER | Convert if term is a integer or float |
CVT_ATOMIC | Convert if term is atomic |
CVT_VARIABLE | Convert variable to print-name |
CVT_ALL | Convert if term is any of the above, except for variables |
BUF_DISCARDABLE | Data must copied immediately |
BUF_RING | Data is stored in a ring of buffers |
BUF_MALLOC | Data is copied to a new buffer returned by malloc(3) |
PL_get_chars(l, s,
CVT_LIST|flags)
, provided flags
contains no of the CVT_* flags.
The functions from this section are intended to read a Prolog list from C. Suppose we expect a list of atoms, the following code will print the atoms, each on a line:
foreign_t pl_write_atoms(term_t l) { term_t head = PL_new_term_ref(); /* variable for the elements */ term_t list = PL_copy_term_ref(l); /* copy as we need to write */ while( PL_get_list(list, head, list) ) { char *s; if ( PL_get_atom_chars(head, &s) ) Sprintf("%s\n", s); else PL_fail; } return PL_get_nil(list); /* test end for [] */ } |
assign a term-reference
to the head to h and to the tail to t.
assign a term-reference
to the head to h.
assign a term-reference
to the tail to t.
.
Figure 7 shows a simplified definition of write/1 to illustrate the described functions. This simplified version does not deal with operators. It is called display/1, because it mimics closely the behaviour of this Edinburgh predicate.
foreign_t pl_display(term_t t) { functor_t functor; int arity, len, n; char *s; switch( PL_term_type(t) ) { case PL_VARIABLE: case PL_ATOM: case PL_INTEGER: case PL_FLOAT: PL_get_chars(t, &s, CVT_ALL); Sprintf("%s", s); break; case PL_STRING: PL_get_string_chars(t, &s, &len); Sprintf("\"%s\"", s); break; case PL_TERM: { term_t a = PL_new_term_ref(); PL_get_name_arity(t, &name, &arity); Sprintf("%s(", PL_atom_chars(name)); for(n=1; n<=arity; n++) { PL_get_arg(n, t, a); if ( n > 1 ) Sprintf(", "); pl_display(a); } Sprintf(")"); break; default: PL_fail; /* should not happen */ } PL_succeed; } |
Terms can be constructed using functions from the PL_put_*() and PL_cons_*() families. This approach builds the term `inside-out', starting at the leaves and subsequently creating compound terms. Alternatively, terms may be created `top-down', first creating a compound holding only variables and subsequently unifying the arguments. This section discusses functions for the first approach. This approach is generally used for creating arguments for PL_call() and PL_open_query.
Put a string, represented by a length/start pointer pair in the term-reference. The data will be copied. This interface can deal with 0-bytes in the string. See also section 5.6.17.
PL_put_functor(l,
PL_new_functor(PL_new_atom("."), 2))
.
PL_put_atom_chars("[]")
.
animal(gnu, 50)
, use:
term_t a1 = PL_new_term_ref(); term_t a2 = PL_new_term_ref(); term_t t = PL_new_term_ref(); PL_put_atom_chars(a1, "gnu"); PL_put_integer(a2, 50); PL_cons_functor(t, PL_new_functor(PL_new_atom("animal"), 2), a1, a2); |
After this sequence, the term-references a1 and a2 may be used for other purposes.
char **
. The list
is built tail-to-head. The PL_unify_*() functions can be used
to build a list head-to-tail.
void put_list(term_t l, int n, char **words) { term_t a = PL_new_term_ref(); PL_put_nil(l); while( --n >= 0 ) { PL_put_atom_chars(a, words[n]); PL_cons_list(l, a, l); } } |
Note that l can be redefined within a PL_cons_list call as shown here because operationally its old value is consumed before its new value is set.
The functions of this sections unify terms with other terms or translated C-data structures. Except for PL_unify(), the functions of this section are specific to SWI-Prolog. They have been introduced to make translation of old code easier, but also because they provide for a faster mechanism for returning data to Prolog that requires less term-references. Consider the case where we want a foreign function to return the host name of the machine Prolog is running on. Using the PL_get_*() and PL_put_*() functions, the code becomes:
foreign_t pl_hostname(term_t name) { char buf[100]; if ( gethostname(buf, sizeof(buf)) ) { term_t tmp = PL_new_term_ref(); PL_put_atom_chars(tmp, buf); return PL_unify(name, buf); } PL_fail; } |
Using PL_unify_atom_chars(), this becomes:
foreign_t pl_hostname(term_t name) { char buf[100]; if ( gethostname(buf, sizeof(buf)) ) return PL_unify_atom_chars(name, buf); PL_fail; } |
char **
. We could use the example described by
PL_put_list(), followed by a
call to PL_unify(), or we can use
the code below. If the predicate argument is unbound, the difference is
minimal (the code based on PL_put_list()
is probably slightly faster). If the argument is bound, the code below
may fail before reaching the end of the word-list, but even if the
unification succeeds, this code avoids a duplicate (garbage) list and a
deep unification.
foreign_t pl_get_environ(term_t env) { term_t l = PL_copy_term_ref(env); term_t a = PL_new_term_ref(); extern char **environ; char **e; for(e = environ; *e; e++) { if ( !PL_unify_list(l, a, l) || !PL_unify_atom_chars(a, *e) ) PL_fail; } return PL_unify_nil(l); } |
.
The type identifiers are:
PL_VARIABLE
nonePL_FUNCTOR
.
PL_ATOM
atom_t
PL_INTEGER
long
PL_FLOAT
double
PL_STRING
const char *
PL_TERM
term_t
PL_CHARS
const char *char *
,
as in PL_unify_atom_chars().
PL_FUNCTOR
functor_t, ...
PL_LIST
int length, ...For example, to unify an argument with the term language(dutch)
,
the following skeleton may be used:
static functor_t FUNCTOR_language1; static void init_constants() { FUNCTOR_language1 = PL_new_functor(PL_new_atom("language"), 1); } foreign_t pl_get_lang(term_t r) { return PL_unify_term(r, PL_FUNCTOR, FUNCTOR_language1, PL_CHARS, "dutch"); } install_t install() { PL_register_foreign("get_lang", 1, pl_get_lang, 0); init_constants(); } |
The Prolog engine can be called from C. There are to interfaces for this. For the first, a term is created that could be used as an argument to call/1 and next PL_call() is used to call Prolog. This system is simple, but does not allow to inspect the different answers to a non-deterministic goal and is relatively slow as the runtime system needs to find the predicate. The other interface is based on PL_open_query(), PL_next_solution() and PL_cut_query() or PL_close_query(). This mechanism is more powerful, but also more complicated to use.
This section discusses the functions used to communicate about
predicates. Though a Prolog predicate may defined or not, redefined,
etc., a Prolog predicate has a handle that is not destroyed, nor moved.
This handle is known by the type predicate_t
.
This section discusses the functions for creating and manipulating queries from C. Note that a foreign context can have at most one active query. This implies it is allowed to make strictly nested calls between C and Prolog (Prolog calls C, calls Prolog, calls C, etc., but it is not allowed to open multiple queries and start generating solutions for each of them by calling PL_next_solution(). Be sure to call PL_cut_query() or PL_close_query() on any query you opened before opening the next or returning control back to Prolog.
Opens a query and returns an identifier for it. This function always
succeeds, regardless whether the predicate is defined or not. ctx
is the context module of the goal. When NULL
, the
context module of the calling context will be used, or user
if there is no calling context (as may happen in embedded systems). Note
that the context module only matters for module_transparent
predicates. See context_module/1
and module_transparent/1.
The p argument specifies the predicate, and should be the
result of a call to PL_pred() or PL_predicate().
Note that it is allowed to store this handle as global data and reuse it
for future queries. The term-reference t0 is the first of a
vector of term-references as returned by
PL_new_term_refs(n).
The flags arguments provides some additional options concerning debugging and exception handling. It is a bitwise or of the following values:
PL_Q_NORMAL
PL_Q_NODEBUG
PL_Q_CATCH_EXCEPTION
PL_Q_PASS_EXCEPTION
PL_Q_CATCH_EXCEPTION
, but do not invalidate the
exception-term while calling PL_close_query().
This option is experimental.
The example below opens a query to the predicate is_a/2 to find the ancestor of for some name.
char * ancestor(const char *me) { term_t a0 = PL_new_term_refs(2); static predicate_t p; if ( !p ) p = PL_predicate("is_a", 2, "database"); PL_put_atom_chars(a0, me); PL_open_query(NULL, PL_Q_NORMAL, p, a0); ... } |
TRUE
if a solution was found, or FALSE
to
indicate the query could not be proven. This function may be called
repeatedly until it fails to generate all solutions to the query.
TRUE
if the call succeeds, FALSE
otherwise.
Figure 8 shows an example to
obtain the number of defined atoms. All checks are omitted to improve
readability.
The Prolog data created and term-references needed to setup the call and/or analyse the result can in most cases be discarded right after the call. PL_close_query() allows for destructing the data, while leaving the term-references. The calls below may be used to destroy term-references and data. See figure 8 for an example.
It is obligatory to call either of the two closing functions to discard a foreign frame. Foreign frames may be nested.
int count_atoms() { fid_t fid = PL_open_foreign_frame(); term_t goal = PL_new_term_ref(); term_t a1 = PL_new_term_ref(); term_t a2 = PL_new_term_ref(); functor_t s2 = PL_new_functor(PL_new_atom("statistics"), 2); int atoms; PL_put_atom_chars(a1, "atoms"); PL_cons_functor(goal, s2, a1, a2); PL_call(goal, NULL); /* call it in current module */ PL_get_integer(a2, &atoms); PL_discard_foreign_frame(fid); return atoms; } |
Modules are identified via a unique handle. The following functions are available to query and manipulate modules.
NULL
it will be set to the
context module. Otherwise it will be left untouched. The following
example shows how to obtain the plain term and module if the default
module is the user module:
{ module m = PL_new_module(PL_new_atom("user")); term_t plain = PL_new_term_ref(); PL_strip_module(term, &m, plain); ... |
This section discusses PL_exception(), PL_throw()
and
PL_raise_exception(),
the interface functions to detect and generate Prolog exceptions from
C-code. PL_throw() and PL_raise_exception()
from the C-interface to raise an exception from foreign code. PL_throw()
exploits the C-function longjmp() to return immediately to the innermost
PL_next_solution(). PL_raise_exception()
registers the exception term and returns FALSE
. If a
foreign predicate returns FALSE, while and exception-term is registered
a Prolog exception will be raised by the virtual machine.
Calling these functions outside the context of a function implementing a foreign predicate results in undefined behaviour.
PL_exception() may be used after a call to PL_next_solution() fails, and returns a term reference to an exception term if an exception was raised, and 0 otherwise.
If a C-function, implementing a predicate calls Prolog and detects an exception using PL_exception(), it can handle this exception, or return with the exception. Some caution is required though. It is not allowed to call PL_close_query() or PL_discard_foreign_frame() afterwards, as this will invalidate the exception term. Below is the code that calls a Prolog defined arithmetic function (see arithmethic_function/1).
If PL_next_solution() succeeds, the result is analysed and translated to a number, after which the query is closed and all Prolog data created after PL_open_foreign_frame() is destroyed. On the other hand, if PL_next_solution() fails and if an exception was raised, just pass it. Otherwise generate an exception (PL_error() is an internal call for building the standard error terms and calling PL_raise_exception()). After this, the Prolog environment should be discarded using PL_cut_query() and PL_close_foreign_frame() to avoid invalidating the exception term.
static int prologFunction(ArithFunction f, term_t av, Number r) { int arity = f->proc->definition->functor->arity; fid_t fid = PL_open_foreign_frame(); qid_t qid; int rval; qid = PL_open_query(NULL, PL_Q_NORMAL, f->proc, av); if ( PL_next_solution(qid) ) { rval = valueExpression(av+arity-1, r); PL_close_query(qid); PL_discard_foreign_frame(fid); } else { term_t except; if ( (except = PL_exception(qid)) ) { rval = PL_throw(except); /* pass exception */ } else { char *name = stringAtom(f->proc->definition->functor->name); /* generate exception */ rval = PL_error(name, arity-1, NULL, ERR_FAILED, f->proc); } PL_cut_query(qid); /* donot destroy data */ PL_close_foreign_frame(fid); /* same */ } return rval; } |
FALSE
. Below is an example returning an
exception from foreign predicate:
foreign_t pl_hello(term_t to) { char *s; if ( PL_get_atom_chars(to, &s) ) { Sprintf("Hello \"%s\"\n", s); PL_succeed; } else { term_t except = PL_new_term_ref(); PL_unify_term(except, PL_FUNCTOR, PL_new_functor(PL_new_atom("type_error"), 2), PL_CHARS, "atom", PL_TERM, to); return PL_raise_exception(except); } } |
The interface functions below provide for efficient management of Prolog terms in the Prolog database. They provide an alternative to calling asserta/1 or recorda/3 or friends.
SWI-Prolog offers both a C and Prolog interface to deal with software interrupts (signals). The Prolog mapping is defined in section 3.9. This subsection deals with handling signals from C.
If a signal is not used by Prolog and the handler does not call Prolog in any way, the native signal interface routines may be used.
Some versions of SWI-Prolog, notably running on popular Unix
platforms, handle SIG_SEGV
for guarding the Prolog stacks.
If the application whishes to handle this signal too, it should use PL_signal()
to install its handler after initialisating Prolog. SWI-Prolog will pass
SIG_SEGV
to the user code if it detected the signal is not
related to a Prolog stack overflow.
Any handler that wishes to call one of the Prolog interface functions should call PL_signal() for its installation.
After a signal handler is registered using this function, the native signal interface redirects the signal to a generic signal handler inside SWI-Prolog. This generic handler validates the environment, creates a suitable environment for calling the interface functions described in this chapter and finally calls the registered user-handler.
PL_warning() prints a
standard Prolog warning message to the standard error (user_error
)
stream. Please note that new code should consider using PL_raise_exception()
to raise a Prolog exception. See also section 3.8.
]
' and a
newline. Then start the tracer. format and the arguments are
the same as for printf(2). Always returns FALSE
.
PL_ACTION_TRACE
Start Prolog tracer (trace/0). Requires no arguments. PL_ACTION_DEBUG
Switch on Prolog debug mode (debug/0). Requires no arguments. PL_ACTION_BACKTRACE
Print backtrace on current output stream. The argument (an int) is the number of frames printed. PL_ACTION_HALT
Halt Prolog execution. This action should be called rather than Unix exit() to give Prolog the opportunity to clean up. This call does not return. The argument (an int) is the exit code. See halt/1. PL_ACTION_ABORT
Generate a Prolog abort (abort/0). This call does not return. Requires no arguments. PL_ACTION_BREAK
Create a standard Prolog break environment (break/0). Returns after the user types the end-of-file character. Requires no arguments. PL_ACTION_GUIAPP
Win32: Used to indicate the kernel that the application is a GUI application if the argument is not 0 and a console application if the argument is 0. If a fatal error occurs, the system uses a windows messagebox to report this on a GUI application and simply prints the error and exits otherwise. PL_ACTION_WRITE
Write the argument, a char *
to the current output stream.PL_ACTION_FLUSH
Flush the current output stream. Requires no arguments.
PL_QUERY_ARGC
Return an integer holding the number of arguments given to Prolog from Unix. PL_QUERY_ARGV
Return a char ** holding the argument vector given to Prolog from Unix. PL_QUERY_SYMBOLFILE
Return a char * holding the current symbol file of the running process. PL_MAX_INTEGER
Return a long, representing the maximal integer value represented by a Prolog integer. PL_MIN_INTEGER
Return a long, representing the minimal integer value. PL_QUERY_VERSION
Return a long, representing the version as 10,000 × M + 100 × m + p, where M is the major, m the minor version number and p the patch-level. For example, 20717
means2.7.17
.
PL_FA_NOTRACE | Predicate cannot be seen in the tracer |
PL_FA_TRANSPARENT | Predicate is module transparent |
PL_FA_NONDETERMINISTIC | Predicate is non-deterministic. See also PL_retry(). |
PL_extension
is defined as:
typedef struct _PL_extension { char *predicate_name; /* Name of the predicate */ short arity; /* Arity of the predicate */ pl_function_t function; /* Implementing functions */ short flags; /* Or of PL_FA_... */ } PL_extension; |
Here is an example of its usage:
static PL_extension predicates[] = { { "foo", 1, pl_foo, 0 }, { "bar", 2, pl_bar, PL_FA_NONDETERMINISTIC }, { NULL, 0, NULL, 0 } }; main(int argc, char **argv) { PL_register_extensions(predicates); if ( !PL_initialise(argc, argv) ) PL_halt(1); ... } |
The function PL_register_extensions() is the only PL_* function that may be called before PL_initialise(). The functions are registered after registration of the SWI-Prolog builtin foreign predicates and before loading the initial saved state. This implies that initialization/1 directives can refer to them.
For various specific applications some hooks re provided.
PL_DISPATCH_INPUT
indicates Prolog input is available on
file descriptor 0 or PL_DISPATCH_TIMEOUT
to indicate a
timeout. The old hook is returned. The type PL_dispatch_hook_t
is defined as:
typedef int (*PL_dispatch_hook_t)(void); |
PL_abort_hook_t
is defined as:
typedef void (*PL_abort_hook_t)(void); |
FALSE
if no such hook is found, TRUE
otherwise.
This section provides some hints for handling foreign data in Prolog. With foreign data, we refer to data that is used by foreign language predicates and needs to be passed around in Prolog. Excluding combinations, there are three principal options for storing such data
The choice may be guided using the following distinctions
true
and false
.
In this section, we wull outline some examples, covering typical cases. In the first example, we will deal with extending Prolog's data representation with integer-sets, represented as bit-vectors. In the second example, we look at handling a `netmask'. Finally, we discuss the outline of the DDE interface.
Integer sets with not-to-far-apart upper- and lower-bounds can be represented using bit-vectors. Common set operations, such as union, intersection, etc. are reduced to simple and'ing and or'ing the bitvectors. This can be done in Prolog, using a compound term holding integer arguments. Especially if the integers are kept below the maximum tagged integer value (see feature/2), this representation is fairly space-efficient (wasting 1 word for the functor and and 7 bits per integer for the tags). Arithmetic can all be performed in Prolog too.
For really demanding applications, foreign representation will perform better, especially time-wise. Bit-vectors are natrually expressed using string objects. If the string is wrapped in bitvector/1 , lower-bound of the vector is 0, and the upperbound is not defined, an implementation for getting and putting the setes as well as the union predicate for it is below.
#include <SWI-Prolog.h> #define max(a, b) ((a) > (b) ? (a) : (b)) #define min(a, b) ((a) < (b) ? (a) : (b)) static functor_t FUNCTOR_bitvector1; static int get_bitvector(term_t in, int *len, unsigned char **data) { if ( PL_is_functor(in, FUNCTOR_bitvector1) ) { term_t a = PL_new_term_ref(); PL_get_arg(1, in, a); return PL_get_string(a, (char **)data, len); } PL_fail; } static int unify_bitvector(term_t out, int len, const unsigned char *data) { if ( PL_unify_functor(out, FUNCTOR_bitvector1) ) { term_t a = PL_new_term_ref(); PL_get_arg(1, out, a); return PL_unify_string_nchars(a, len, (const char *)data); } PL_fail; } static foreign_t pl_bitvector_union(term_t t1, term_t t2, term_t u) { unsigned char *s1, *s2; int l1, l2; if ( get_bitvector(t1, &l1, &s1) && get_bitvector(t2, &l2, &s2) ) { int l = max(l1, l2); unsigned char *s3 = alloca(l); if ( s3 ) { int n; int ml = min(l1, l2); for(n=0; n<ml; n++) s3[n] = s1[n] | s2[n]; for( ; n < l1; n++) s3[n] = s1[n]; for( ; n < l2; n++) s3[n] = s2[n]; return unify_bitvector(u, l, s3); } return PL_warning("Not enough memory"); } PL_fail; } install_t install() { PL_register_foreign("bitvector_union", 3, pl_bitvector_union, 0); FUNCTOR_bitvector1 = PL_new_functor(PL_new_atom("bitvector"), 1); } |
Netmask's are used with TCP/IP configuration. Suppose we have an application dealing with reasoning about a network configuration. Such an application requires communicating netmask structures from the operating system, reasoning about them and possibly communicate them to the user. A netmask consists of 4 bitmasks between 0 and 255. C-application normally see them as an 4-byte wide unsigned integer. SWI-Prolog cannot do that, as integers are always signed.
We could use the string approach outlined above, but this makes it hard to handle these terms in Prolog. A better choice is a compound term netmask/4, holding the 4 submasks as integer arguments.
As the implementation is trivial, we will omit this here.
The DDE interface (see section 3.43) represents another common usage of the foreign interface: providing communication to new operating system features. The DDE interface requires knowledge about active DDE server and client channels. These channels contains various foreign data-types. Such an interface is normally achieved using an open/close protocol that creates and destroys a handle. The handle is a reference to a foreign data-structure containing the relevant information.
There are a couple of possibilities for representing the handle. The
choice depends on responsibilities and debugging facilities. The
simplest aproach is to using PL_unify_pointer()
and PL_get_pointer(). This
approach is fast and easy, but has the drawbacks of (untyped) pointers:
there is no reliable way to detect the validity of the pointer, not to
verify it is pointing to a structure of the desired type. The pointer
may be wrapped into a compound term with arity 1 (i.e. dde_channel(<Pointer>)
),
making the type-problem less serious.
Alternatively (used in the DDE interface), the interface code can maintain a (preferably variable length) array of pointers and return the index in this array. This provides better protection. Especially for debugging purposes, wrapping the handle in a compound is a good suggestion.
As of version 2.1.0, SWI-Prolog may be embedded in a C-program. To reach at a compiled C-program with SWI-Prolog as an embedded application is very similar to creating a statically linked SWI-Prolog executable as described in section 5.4.1.
The file \ldots/pl/include/stub.c
defines SWI-Prologs
default main program:
int main(int argc, char **argv) { if ( !PL_initialise(argc, argv) ) PL_halt(1); PL_install_readline(); /* delete if you don't want readline */ PL_halt(PL_toplevel() ? 0 : 1); } |
This may be replaced with your own main C-program. The interface function PL_initialise() must be called before any of the other SWI-Prolog foreign language functions described in this chapter. PL_initialise() interprets all the command-line arguments, except for the -t toplevel flag that is interpreted by PL_toplevel().
PL_initialise() returns 1 if all initialisation succeeded and 0 otherwise. Various fatal errors may cause PL_initialise to call PL_halt(1), preventing it from returning at all.