Break Control (Textmode Only)

 

It is important to understand how the break/signal mechanism is implemented in Visual Prolog. Generally, a break does not immediately abort the current execution. Rather, Visual Prolog has an exception handler installed, which sets a flag when activated by the signal. Visual Prolog checks this flag in two different cases:

If the code is compiled with break-checking enabled, the status of the break-flag is examined each time a predicate is entered. Break-checking may be disabled by using the nobreak directive in the source code, through the Options/Compiler Directives/Run-time check menu item, or from the commandline.

Several of the library routines check the break-flag.

If the break-flag is set, the outcome depends on the break-status, set by the predicate break: If break-status is Off, the signal is ignored for the time being, otherwise the code will exit with an appropriate exitcode (discussed below). This exit will of course be caught by a trap, if any is set.

(1) break/1

break enables and disables the sensing of the break-flag during execution. break takes one of the following forms:

    break(on)                        /* (i); enables the BREAK key */
    break(off)
                     /* (i); disables the BREAK key */
    break(BreakStatus)
    /* (o); returns the current BREAK status */

You can read the current break status by calling break with an output variable. This means that, during critical operations, you can disable break and then return to the original break state afterwards. For example:

    update :-
        break(OldBreak),
        break(off),
    /* .... do the updating, */
        break(OldBreak).

For the DOS-related versions, the exitcode resulting from a break will always be 0, as the only signal recognized is the user interrupt. For the UNIX version, SIGINT also results in an exit value of 0, for backwards compatibility with the large base of installed DOS programs written in Visual Prolog. For other signals which the process has been set up to catch, the exitcode is the signal number plus the constant err_signaloffset, defined in the include file ERROR.CON.

(2) breakpressed/0

breakpressed succeeds if the break-flag is set, even when the break-state has been turned off by break(off) or the program compiled with the nobreak option. If successful, breakpressed returns the exitcode generated by the most recently caught signal, and clears the break-flag. For the DOS-related versions of Visual Prolog, this will always be 0; for UNIX, it will be the same value as would otherwise be passed through the exit/trap mechanism, as described above. This too will be 0 if SIGINT is received.

1. Manual Break and Signal Checking in UNIX

This section, down to page 149, only applies to UNIX and may be skipped by users of the DOS-related versions.

A Visual Prolog program may be configured to catch any of the many different signals a UNIX process can receive (see signal(S)). However, as signals may arrive at any time, quite asynchronously from the running process, it's important that they don't interrupt the process while in the middle of something critical, such as memory allocation. The reason for this is that, due to Prolog's modularity, the only means of communication between different predicates is through arguments or through databases. Obviously, an asynchronously executed signal-handler predicate can't communicate to the rest of the program through arguments, leaving only the database. And since databases rely on memory allocation, which invariably is in use by the rest of the program, an asynchronously executed signal-handling predicate could create havoc, if trying to e.g. assert something to indicate that a signal was received, while the interrupted process was in the middle of allocating memory. It really all boils down to Prolog not having global variables, leaving asynchronously executed predicates with no means of communication with the rest of the program.

Therefore, rather than invoking a signal-handling predicate the instant the signal is received, signals are routed through the exit/trap mechanism.

(1) signal/2

Signal-handling in Visual Prolog programs is controlled by the signal predicate, defined in the include file ERROR.PRE:

    GLOBAL DOMAINS
        sighand = determ (integer) - (i) language C

    GLOBAL PREDICATES
        sighand signal(integer,integer) - (i,i) language C as "_BRK_Signal"
        sighand signal(integer,sighand) - (i,i) language C as "_BRK_Signal"

    CONSTANTS
        sig_default = 0
        sig_ignore = 1
        sig_catch = 2

To modify the handling of a specific signal, call signal with the signal exitcode you want to catch, such as err_sigalrm, defined in ERROR.PRE, specifying in the second argument what to do:

sig_default to reset the handling of the signal to the default for the process

sig_ignore to ignore the signal completely

sig_catch to have the signal routed through the exit/trap mechanism

anything else is taken to be the address of a function to be invoked when the signal occurs

The return value of signal is the previous handling of the signal in question, which will be one of the values outlined above. The only cases where you may use the fourth alternative (address of function) is when this value was returned by a previous call to signal, or when the function is one you have written yourself in C, exercising the usual precautions when writing signal handlers. In particular, SIGINT is masked out during the execution of the signal handler, so if you intend to do a longjump from a signal handler you're written in C, SIGINT must be enabled first (see sigprocmask(S)). The validity of the function address is not verified at the time signal is called and results may be highly erratic if it's an invalid address; see signal(S).

Although the name and argument profile of signal matches that of signal(S), it is implemented using sigaction(S) and SIGINT is ignored during execution of installed signal handlers.

By default, Visual Prolog catches the following signals:

SIGINT (user interrupt); results in exit of 0 when detected.

SIGFPE (floating point exception); results in an exit of err_realoverflow immediately after the erroneous calculation.

SIGBUS and SIGSEGV (memory fault); these signals result from attempting to access memory not belonging to the process, typically due to a faulty pointer. A short message, indicating where in the program the error happened, will be printed if possible (see the errorlevel compiler directive), and the process is terminated, leaving a core dump. Unless you have made a mistake in modules you have written yourself in C, this invariably indicates an internal error.

SIGILL (illegal instruction); the processor encountered an unrecognized or illegal instruction. Other details as for SIGBUS and SIGSEGV.

Any signals caught will be routed through the same function as SIGINT. Note that once catching has been enabled for a signal, it remains in effect until explicitly reset by another call to signal. Receiving and catching a signal will not reset the signal handling.

Needless to say, signal catching should be used very carefully, and the break-state should always be turned off if you intend to receive and test for signals without interrupting the program. In particular, a number of operating system calls will be terminated prematurely if a signal is caught while they're executing. When the break-state is off, the reception of the signal will be noted in the break-flag and the interrupted system call called again, meaning the program should work as expected. However, while every care has been taken to ensure the integrity of this scheme, no guarantees can be given. For instance, some versions of SCO UNIX and SCO Open Desktop will allow interrupts of certain terminal I/O functions, without giving any indication that such an interrupt occurred.

Below are two examples, using the alarm clock signal. Both use the breakpressed predicate, which will be described later.

The first example will print the message "Do something!" every three seconds, until the user enters a character. It doesn't turn the break-state off during the central parts of the program, as the whole purpose is to interrupt a system call.

/* Program ch11e14.pro */

 

include error.con"

 

GLOBAL PREDICATES

    alarm(integer) - (i) language C                    % See alarm(S)

 

PREDICATES

    brkclear

    nondeterm repeat

    ehand(integer)

    getchar(char)

 

CLAUSES

    brkclear:-breakpressed,!.              % Clear break-flag, if set

    brkclear.

    repeat.

    repeat:-repeat.

    ehand(2214):-!,

        write("Do something!¡¬n").

    ehand(E):-

        write("¡¬nUnknown exit ",E,'¡¬n'),

        exit(2).

    getchar(C):-

        write("Enter char: "),

        alarm(3),                       % Alarm to go off in 3 seconds

        readchar(C),
            % This will exit with err_sigalrm when receiving SIGALRM

        alarm(0),                        % Cancel pending alarm signal

        break(off),

        brkclear,           % Clear break-flag, in case alarm went off

        break(on).                   % just before cancellation above.

GOAL

        Old=signal(err_sigalrm,sig_catch),     % Declared in error.con

        repeat,

            trap(getchar(C),Err,ehand(Err)),

        !,

        signal(err_sigalrm,Old),

        write("¡¬nYou entered '",C,"'¡¬n").

The next example, which has been deliberately written to be somewhat inefficient, displays program progress during lengthy processing. Break-status is turned off in this program, and the detection of any signals is handled manually, using the breakpressed predicate.

/* Program ch11e15.pro */

 

GLOBAL PREDICATES

    alarm(integer) - (i) language C% See alarm(S)

 

DATABASE

    rcount(unsigned)

    dba(real,real,real)

 

PREDICATES

    nondeterm repeat

    process_dba

    bcheck

    bcheck1(integer)

 

CLAUSES

    repeat.

    repeat:- repeat.

 

    rcount(0).

 

dba(1,1,1).

    

    process_dba:-

        retract(dba(F1,F2,F3)), !, F = F1 * F2 * F3, assert(dba(F,F,F)),

        retract(rcount(N)), !, NN = N+1, assert(rcount(NN)),

        NN = 25000.                      % fail back to repeat in goal

 

    bcheck:-

        Break = breakpressed(),!,

        bcheck1(Break).

    bcheck.

    

    bcheck1(err_sigalrm):-!,

        rcount(N),!,

        time(H,M,S,_),

        writef("¡¬r%:%:% % records   ",H,M,S,N),

        alarm(1). % Next alarm in 1 second

    bcheck1(0):-!,

        write("¡¬nInterrupt¡¬n"),

        exit(1).

    bcheck1(Exit):-

        write("¡¬nUnknown exit ",Exit,"; runtime error?¡¬n"),

        exit(2).

 

GOAL

        break(off),

        Old = signal(err_sigalrm,sig_catch),   % Declared in error.pre

        alarm(1),                            % First alarm in 1 second

        repeat,

        bcheck, process_dba,

        !,

        alarm(0),                               % Cancel pending alarm

        signal(err_sigalrm,Old),

        dba(F1,F2,F3), !,

        write('¡¬n',F1,' ',F2,' ',F3,'¡¬n').

The writef predicate is covered in chapter 12.

2. Critical Error Handling under DOS Textmode

This section applies only to the DOS textmode platform, and are not relevant for VPI programs.

The DOS-version of Visual Prolog's library contains some default routines for handling error situations, but you can actually substitute the default code with your own clauses. In this section, we describe two routines -- criticalerror and fileerror. DOS will call criticalerror when a DOS error occurs. The Visual Prolog system calls fileerror when it gets a file error in the run-time editor. If you define these predicates as global and supply your own clauses for them, the linker will take your code instead of the code from the library. The result is that you gain better control over error situations. Your .EXE program's size might also decrease (because the code for the default routines draw in window routines).

Global declarations for criticalerror and fileerror are given in the include file ERROR.PRE shipped with the Visual Prolog system in the include directory.

(1) criticalerror/4

Visual Prolog defines this routine for handling DOS critical errorscritical errors (DOS interrupt 24H)DOS, interrupt 24H,  but not for OS/2. If you want to use your own version of criticalerror, you should include ERROR.PRE which gives a global declaration as follows:

    GLOBAL PREDICATES
        criticalerror(ErrNo, ErrType, DiskNo, Action) - (i, i, i, o) language c as "_CriticalError_0"

Refer to the chapter 17 for information on how to use global declarations.

The criticalerror predicate must never fail, and it works only from an .EXE file application. The criticalerror predicate replaces the DOS critical error interrupt handler and has the same restriction as the original interrupt handler. (Refer to the DOS Technical Reference for details.) You can only use DOS function calls 01h to 0Ch and 59h ("Get extended error")--that means console I/O and nothing else. If your application uses any other DOS function calls, the operating system is left in an unpredictable state.

Table 11.1: Argument Values for the criticalerror Predicate

Argument

Value

Meaning

ErrNo

=   0

=   1

=   2

=   3

=   4

=   5

=   6

=   7

=   8

=   9

= 10

= 11

 

Attempt to write on write-protected disk

Unknown unit

Drive not ready

Unknown command

CRC error in data

Bad drive request structure length

Seek error

Unknown media type

Sector not found

= 12

Printer out of paper

Write fault

Read fault

General failure

ErrType

=   0

=   1

=   2

Character device error

Disk read error

Disk write error

DiskNo 

=   0-25

Means device A to Z

Action

=   0

=   1

=   2

Abort current operation

Retry current operation

Ignore current operation (this could be very dangerous and is not recommended)

(2) fileerror/2

Visual Prolog will activate the predicate fileerror when a file in the textmode editor action fails.

If you define your own fileerror predicate, it is not allowed to fail, and it works only from an .EXE file application.

The declaration for fileerror in the ERROR.PRE file is:

    GLOBAL PREDICATES
        fileerror(integer, string) - (i, i) language c as "_MNU_FileError"

Note that this declaration is correct -- you must specify language c even though the source code will be in Prolog.