Home Contents Index Summary Previous Next

3.9 Handling signals

As of version 3.1.0, SWI-Prolog is capable to handle software interrupts (signals) in Prolog as well as in foreign (C) code (see section 5.6.11).

Signals are used to handle internal errors (execution of a non-existing CPU intruction, arithmetic domain errors, illegal memory access, resource overflow, etc.), as well as for dealing asynchronous inter-process communication.

Signals are defined by the Posix standard and part of all Unix machines. The MS-Windows Win32 provides a subset of the signal handling routines, lacking the vital funtionality to raise a signal in another thread for achieving asynchronous inter-process (or inter-thread) communication (Unix kill() function).

on_signal(+Signal, -Old, :New)
Determines the reaction on Signal. Old is unified with the old behaviour, while the behaviour is switched to New. As with similar environment-control predicates, the current value is retrieved using on_signal(Signal, Current, Current).

The action description is an atom denoting the name of the predicate that will be called if Signal arrives. on_signal/3 is a meta predicate, which implies that <Module>:<Name> refers the <Name>/1 in the module <Module>.

Two predicate-names have special meaning. throw implies Prolog will map the signal onto a Prolog exception as described in section 3.8. default resets the handler to the settings active before SWI-Prolog manipulated the handler.

After receiving a signal mapped to throw, the exception raised has the structure

error(signal(<SigName>, <SigNum>), <Context>)

One possible usage of this is, for example, to limit the time spent on proving a goal. This requires a little C-code for setting the alarm timer (see chapter 5):


#include <SWI-Prolog.h>
#include <unistd.h>

foreign_t
pl_alarm(term_t time)
{ double t;

  if ( PL_get_float(time, &t) )
  { alarm((long)(t+0.5));

    PL_succeed;
  }

  PL_fail;
}


install_t
install()
{ PL_register_foreign("alarm", 1, pl_alarm, 0);
}

Next, we can define the following Prolog code:


:- load_foreign_library(alarm).

:- on_signal(alrm, throw).

:- module_transparent
        call_with_time_limit/2.

call_with_time_limit(Goal, MaxTime) :-
        alarm(MaxTime),
        catch(Goal, signal(alrm, _), fail), !,
        alarm(0).
call_with_time_limit(_, _) :-
        alarm(0),
        fail.

The signal names are defined by the C-Posix standards as symbols of the form SIG_<SIGNAME>. The Prolog name for a signal is the lowercase version of <SIGNAME>. The predicate current_signal/3 may be used to map between names and signals.

Initially, some signals are mapped to throw, while all other signals are default. The following signals throw an exception: ill, fpe, segv, pipe, alrm, bus, xcpu, xfsz and vtalrm.

current_signal(?Name, ?Id, ?Handler)
Enumerate the currently defined signal handling. Name is the signal name, Id is the numerical identifier and Handler is the currently defined handler (see on_signal/3).

3.9.1 Notes on signal handling

Before deciding to deal with signals in your application, please consider the following: