10.12 Exceptions

The facilities mentioned in this section are present only in ISO compliant versions of Modula-2 although they are similar to ones that were used in a few early commercial flavours. Some of the ideas were described in the first of the author's books on Modula-2, and then finally adopted by the ISO committee, though with many syntax changes and additions. These methods constitute a considerable extension of the language itself--they are not simply a collection of library based error handlers or variables. Other languages also make use of exceptions for signalling and handling errors, though the details vary somewhat.

There is a class of error that can not always be anticipated prior to program execution and that in many systems (hardware and software combined sense) cause the program to "crash" in a manner that results in an immediate and premature exit to the surrounding environment.

An exception is a violation of the run-time meaning of a program that when detected automatically alters the normal flow of control in the procedure or module body where it occurs, immediately transferring control to an exception handler for that procedure or module body, if one exists.

As soon as an exception occurs, the procedure or module body in which it takes place loses control of the machine. In some languages, the result is that the program terminates immediately in an error condition. ISO Modula-2, however, makes provision for the detection and possible handling of exceptions within the context of the program itself.

A Modula-2 exception changes the state of the program from normal execution to exceptional execution.
A Modula-2 exception handler is a code clause that may be attached to any procedure.
The change in state to exceptional execution is called raising an exception and it immediately transfers control to the nearest (nested) exception handler.
If an exception is not trapped (handled) even by the program module then termination of the program commences with the program state still exceptional. (Exceptional termination).

This kind of action is the most automatic of all types of error handling. If the procedure or module body being executed at the time the exception is raised has an exception handler of its own, then this will be executed. If it does not, or if its handler raises the same exception or a new one, control exits to the next outer procedure, and in fact will cascade up the chain of calls until it finds a handler. As soon as it does, this handler is automatically invoked--an action which places the burden on the program to ensure that errors causing exceptions are properly handled at the appropriate level. If no handler can be found even in the program module body, the program terminates exceptionally.

What happens after a program terminates in an exceptional state depends on the implementation, but most are likely to have an automatic handler at the outermost level, so that just as control returns to the surrounding environment there will at least be some report made to the user of the program.

There are several stages to this kind of activity:

1. The conditions under which exceptions are raised must be defined.

2. All exceptions must be named.

3. The source of the exception must be defined and registered.

4. The conditions producing the exception must be detected.

5. The exception must be raised, providing the source and a message.

6. Exceptions raised by a program should be handled by the program.

7. Those raised by the language or a library may be handled in the program.

8. Handling exceptions may result in re-trying code that caused them. or

9. It may result in re-raising the same exception for calling code to handle. or

10. It may result in the program terminating (normally or exceptionally).

In order to achieve all this, the ISO committee made some additions to the syntax of Modula-2, for the language as defined by Wirth has no facility like the one just described.

In the sections that follow, the points in the above list will be elaborated, though not entirely in the order given here, which in its entirety applies only to exceptions both defined and detected by user programs.

10.12.1 Language Exceptions

Some exceptions are defined in the language itself, and all ISO Modula-2 implementations are required to be detect them at run time. An example is division by zero.

MODULE ForceException;
VAR
  a : REAL;
BEGIN
  a := 0.0;
  a := 5.0 / a
END ForceException.

Whether or not the program does anything with these exceptions once they do occur depends on whether there has been a handler written into the program. There is none in the code above, and in one ISO compliant system in which it was run, the display in figure 10.9 was produced by the run time system, in accordance with the post-exceptional-termination behaviour defined for that specific implementation :

The complete list of language defined exceptions is found in the System module M2EXCEPTION. Recall that a system module is a segregated part of the compiler; it behaves, however, as if it had a definition module.

DEFINITION MODULE M2EXCEPTION;

 (* Provides facilities for identifying language exceptions *)
TYPE
  M2Exceptions = 
    (indexException, rangeException, caseSelectException,
    invalidLocation, functionException, wholeValueException,
    wholeDivException, realValueException, realDivException,
    complexValueException, complexDivException, protException,
    sysException, coException, exException *)

PROCEDURE M2Exception () : M2Exceptions;
(* If the current coroutine is in the exceptional execution state because of a language exception, returns the corresponding enumeration value, and otherwise raises an exception *)

PROCEDURE IsM2Exception () : BOOLEAN;
(* If the current coroutine is in the exceptional execution state because of a language exception, returns TRUE, and otherwise returns FALSE *)

END M2EXCEPTION.

The particular exception raised by the sample code is realDivException, and as may be readily be seen, there are a variety of others, some with rather obvious meanings in the light of previous discussions in this text (for invalid ranges or array indicies, overflow values, and improper case selection). Others have not yet been encountered, and can await further developments, as can the meaning of the term coroutine in the two procedure definitions. The exception raised by this module itself when it is asked for the number of an exception it is not responsible for is exException. Note that exException need never occur, if the request for the enumeration value is formulated:

IF IsM2Exception ()
  THEN
    exVariable := M2Exception()
  END;

This system module also sheds light on what kind of entity an exception is from a language point of view--it is simply a member of an appropriate enumeration.

10.12.2 Library Exceptions

Similar facilities are incorporated into many standard libraries, and consist of three parts:

1. an enumeration of the possible exceptions,

2. an enquiry function to discover which of those was raised,

3. an enquiry function to determine whether the module did raise one.

For instance, the standard I/O library module IOChan contains the following items not previously mentioned:

TYPE
  ChanExceptions =
    (wrongDevice,      (* device specific operation on wrong device *)
     notAvailable,     (* operation attempted that is not available on that channel *)
     skipAtEnd,        (* attempt to skip data from a stream that has ended *)
     softDeviceError,  (* device specific recoverable error *)
     hardDeviceError,  (* device specific non-recoverable error *)
     textParseError,   (* input data does not correspond to a character or line mark - optional detection *)
     notAChannel       (* given value does not identify a channel - optional detection *)
    );
 
PROCEDURE IsChanException (): BOOLEAN;
  (* Returns TRUE if the current coroutine is in the exceptional execution state because of the raising of an exception from ChanExceptions; otherwise returns FALSE. *)

PROCEDURE ChanException (): ChanExceptions;
  (* If the current coroutine is in the exceptional execution state because of the raising of an exception from ChanExceptions, returns the corresponding enumeration value, and otherwise raises an exception. *)

  (* When a device procedure detects a device error, it raises the exception softDeviceError or hardDeviceError.  If these exceptions are handled, the following facilities may be used to discover an implementation-defined error number for the channel. *)
 
TYPE
  DeviceErrNum = INTEGER;
 
PROCEDURE DeviceError (cid: ChanId): DeviceErrNum;
  (* If a device error exception has been raised for the channel cid, returns the error number stored by the device module. *)

The items marked in the standard as optional may not be detected in some implementations. Likewise, if DeviceErrNum is used, the number obtained after an error on enquiry by DeviceError depends on the implementation. The exception raised by ChanException when asked for an exception that it has not raised is the language exception exException. Once again, this exception need never occur if the user always inquires of IsChanException before calling ChanException.

10.12.3 Handling Exceptions

The material thus far only illuminates the nature of exceptions. This section deals with how to trap (handle) them, gives some suggestions about what can be done once they are detected by the user program, and some better advice about error handling code in final products.

Any procedure or module body can have an EXCEPT clause attached to it. This attachment is immediate; that is, it must come before a FINALLY part, and indeed a FINALLY part can have an EXCEPT clause of its own. In the first example that follows, when the code shown is run in the absence of the file requested, either the optional notAChannel exception or the exception wrongDevice will be raised; the message in the EXCEPT clause will be printed; and the program will exit with the exception still raised. Most systems will then provide a further diagnostic message of their own, as shown in the case of raising the realDivException in 10.11.1 above.

MODULE ExceptionDemo;
(* Written by R.J. Sutcliffe *)
(* to illustrate the trapping of exceptions *)
(* using ISO standard Modula-2 *)
(* last revision 1994 05 09 *)

FROM StreamFile IMPORT
  ChanId, Open, write, Close, OpenResults;
FROM IOChan IMPORT
  IsChanException, ChanException, ChanExceptions;
FROM STextIO IMPORT
  WriteString, WriteLn, SkipLine;

VAR
  outfile : ChanId;
  res : OpenResults;

BEGIN
  Open (outfile, "numbers", write, res); 
  (* some code *)
  Close (outfile);
EXCEPT
  IF IsChanException () AND ((ChanException() = wrongDevice)
                         OR (ChanException() = notAChannel))
    THEN
      WriteString ("Can't close; perhaps file was never opened");
      WriteLn;
      WriteString ("Press return to continue");
      SkipLine;
    END;

END ExceptionDemo.

Two things need to be noticed about this demonstration code. First, the error was preventable. That is, the Open ought to have been followed by

IF res = opened
  THEN

and the exception can only take place because of sloppy logic in the program. However, the presence of such an EXCEPT clause can assist the programmer in discovering such lapses and correcting them before the finished code passes into the hands of a user.

Second, in this example, the exception was caught and described but nothing more. There are three possible results of handling an exception:

1. Control runs off the end of the handler (as here) with the exception still raised. In this case, control passes to the next outer handler, and if nothing more is done, the program will terminate, still in the exceptional state.

2. There is a RETURN from the exception handler, in which case the exception is cleared; normal execution resumes; and control passes back out to the caller of the procedure in which the exception occurred. In the example above, that would have meant a normal termination.

3. There is a RETRY in the exception handler, in which case the exception is cleared; normal execution resumes; and control passes back to the beginning of the procedure in which the exception occurred. In the example above, that would have meant attempting to run the entire module body again (but without re-initializing imported or local module bodies).

In both the second and third cases, the conditions causing the exception are all taken care of, and the logic allows it to be regarded as completely handled. Of course, in the third case, some care must be taken not to cause an infinite loop of exception raising and retrying to be entered--and that is exactly what would have happened if this strategy had been used in the example above.

One might follow the second strategy if the exception were the result of an error after a menu choice, and control could pass back to the menu reliably. Here is an outline:

MODULE ExceptionDemo2;
(* Written by R.J. Sutcliffe *)
(* to illustrate the trapping of exceptions *)
(* using ISO standard Modula-2 *)
(* last revision 1994 05 09 *)

FROM StreamFile IMPORT
  ChanId, Open, write, Close, OpenResults;
FROM IOChan IMPORT
  IsChanException, ChanException, ChanExceptions;
FROM STextIO IMPORT
  WriteString, WriteLn, SkipLine, ReadChar, ReadToken;

VAR
  choice : CHAR;
  outfile : ChanId;
  res : OpenResults;

PROCEDURE OpenFile;
VAR
  name : ARRAY [0..30] OF CHAR;
BEGIN
  WriteString ("What is the file name to open?");
  ReadToken (name);
  SkipLine;
  Open (outfile, name, write, res);
END OpenFile;

PROCEDURE CloseFile;
BEGIN
  Close (outfile);
EXCEPT
  IF IsChanException () AND ((ChanException() = wrongDevice)
                         OR (ChanException() = notAChannel))
    THEN
      WriteString ("Can't close; perhaps file was never opened");
      WriteLn;
      WriteString ("Press return to continue");
      SkipLine;
      RETURN;
    END;
END CloseFile;

BEGIN
  REPEAT
    WriteString ("     MENU");
    WriteLn;
    WriteString ("Do you want to:");
    WriteLn;
    WriteString ("O. Open a new file");
    WriteLn;
    WriteString ("C. Close the file");
    WriteLn;
    (* more choices *)
    WriteLn;
    WriteString ("Q. Quit the program");
    WriteLn;
    WriteString ("Pick one ==>");
    ReadChar (choice);
    SkipLine;
    choice := CAP (choice);
    CASE choice OF
      "O" :
        OpenFile; |
      "C" : 
        CloseFile
      ELSE
      (* default is fall off the end *)
      END;
    UNTIL choice = "Q";
 
END ExceptionDemo2.

Once again, however, the exception detection code is only a stopgap; it would be far better to flag a successful open operation than to detect a failure to close properly.

The third option, RETRY, is outlined in the following sketch--another version of an earlier program for making computations based on Ohm's law. Here, it is supposed that an exception might take place as a result of the operation of a function procedure that returns values directly to a division, resulting in the possibility of a divide-by-zero error. Of course, this error too can be prevented from ever taking place if the code is written a little differently.

MODULE OhmsLaw2;

(* Written by R.J. Sutcliffe *)
(* to illustrate an exception retry *)
(* using ISO Modula-2 *)
(* last revision 1994 05 17 *)

FROM STextIO IMPORT
  WriteString, WriteLn, ReadChar, SkipLine;
FROM SRealIO IMPORT
  ReadReal, WriteFixed;
FROM SIOResult IMPORT
  ReadResult, ReadResults;
FROM M2EXCEPTION IMPORT
  M2Exception, IsM2Exception, M2Exceptions;
IMPORT TermFile,Strings;    
TYPE
  String = ARRAY [0..80] OF CHAR;
  
VAR
  retrys : CARDINAL;

PROCEDURE GetNum (prompt : String) : REAL;
VAR
  readOK : BOOLEAN;
  theNum : REAL;

BEGIN
  REPEAT
    WriteString (prompt);
  WriteLn;
    WriteString ("Type the number here ==> ");
    ReadReal (theNum);
    readOK := (ReadResult() = allRight);
    WriteLn;
    IF NOT readOK
      THEN
        WriteString ("error in input number; try again.");
        WriteLn;
      END;
    SkipLine;
  UNTIL readOK;
  RETURN theNum
END GetNum;

PROCEDURE Ohms;
(* No parameters;  modifies global variables only *)
VAR
  voltage : REAL;
BEGIN
  voltage := GetNum ("What is the current in amperes?")
         / GetNum ("What is the resistance in ohms?");
  WriteString ("This current and resistance ");
  WriteLn;
  WriteString (" produce a voltage of ");
  WriteFixed (voltage, 2, 0);
  WriteString (" volts. ");
  WriteLn;
  WriteLn;
EXCEPT
  IF IsM2Exception () AND (M2Exception() = realDivException)
    THEN
      WriteString ("Can't have zero resistance");
      WriteLn;
      IF (retrys = 0)
        THEN
          WriteString ("There seems to be a little problem.");
          WriteLn;
          WriteString ("Do you want to begin again? (y/n) ");
          ReadChar (answer);
          SkipLine;
          IF CAP(answer) = "Y"
            THEN
              RETURN
            END (* else kill program; persistant offender *)
        ELSE
          DEC (retrys);
          WriteString ("Please try again");
          WriteLn;
          RETRY;
        END;
    END;
END Ohms;

VAR
  answer : CHAR;

BEGIN 
  REPEAT
    retrys := 2;
    Ohms;
    WriteString ( "Type 'Y' to do another ");
    ReadChar (answer);
    SkipLine;
    WriteLn;
  UNTIL CAP (answer) # "Y"    
  
END OhmsLaw2.

Observe the necessity of controlling the RETRY so as to avoid an infinite number of them. (There are other ways to do this, besides keeping track of the number of times tried.) Here is the output from this code, as produced by a logging utility that monitored the information going through the module TermFile.

** Run log starts here **
What is the current in amperes?
Type the number here ==> 4

What is the resistance in ohms?
Type the number here ==> 7

This current and resistance 
 produce a voltage of 0.57 volts. 

Type 'Y' to do another y

What is the current in amperes?
Type the number here ==> 5

What is the resistance in ohms?
Type the number here ==> 0

Can't have zero resistance
Please try again
What is the current in amperes?
Type the number here ==> 5

What is the resistance in ohms?
Type the number here ==> 0

Can't have zero resistance
Please try again
What is the current in amperes?
Type the number here ==> 5

What is the resistance in ohms?
Type the number here ==> 0

Can't have zero resistance
There seems to be a little problem.
Do you want to begin again? (y/n) y
Type 'Y' to do another y

What is the current in amperes?
Type the number here ==> 5

What is the resistance in ohms?
Type the number here ==> 9

This current and resistance 
 produce a voltage of 0.56 volts. 

Type 'Y' to do another n

Clearly, this code could (and should!!) have been written so as to check the data before putting it into the formula. The point is that sometimes it may not be possible to guarantee the validity of data by asking the user to repeat it, and an exception will be raised. This code shows one possible way of handling the exception through a retry of the offending block.

10.12.4 Exceptions and Termination

An exception handler can be attached to the body of a procedure or module, or to the FINALLY clause of a module, or to both. Here is a sketch:

MODULE ExceptionTermination1;

(* imports *)

(* declarations *)

BEGIN
  (* statement sequence *)
EXCEPT
  (* exception handling for main body *)

FINALLY
  (* termination/cleanup code goes here *)
EXCEPT
  (* exception handling for termination time *)

END ExceptionTermination1.

The sequence of events is:

1. If an exception is encountered in the body, control is transferred to the exception handler for that body.

2a. If the exception is handled and there is a RETRY, control reverts to the beginning of the body in which the exception took place.

2b. If the body was that of a procedure, control transfers outward to the caller of the procedure until an exception handler is encountered. If none is, step (2c) applies.

2c. If the body was that of a module, and the exception remains raised, or there is a RETURN, termination commences.

3. Once termination has commenced, control transfers to the FINALLY clause, and this clause executes.

4. If a new exception is raised, it is immediately handled by the exception handler for the FINALLY clause, but if the exception from the main body is still raised, it receives no further handling.

Thus, the module:

MODULE ExceptionTermination2;
IMPORT STextIO;

VAR
  b: CARDINAL;

BEGIN
  b := 0;
  b:= 1/b; (* force an exception *)
EXCEPT
  STextIO.WriteString ("Entered exception handling for main body");
  STextIO.WriteLn;
FINALLY
  STextIO.WriteString ("Program now terminating.");
  STextIO.WriteLn;
EXCEPT
  STextIO.WriteString ("Entered exception handling at termination time.");
  STextIO.WriteLn;

END ExceptionTermination2.

which raises an exception in the main body but does not handle it and terminates in an exceptional state without executing the EXCEPT clause of the FINALLY part, producing the output:

Entered exception handling for main body
Program now terminating.

On the other hand, the module:

MODULE ExceptionTermination3;
IMPORT STextIO;

VAR
  b: CARDINAL;

BEGIN
  b := 0;
  b:= 1/b; (* force an exception *)
EXCEPT
  STextIO.WriteString ("Entered exception handling for main body");
  STextIO.WriteLn;
  RETURN (* kill the first exception and move along *)
FINALLY
  b:= 1/b; (* force another exception *)
  STextIO.WriteString ("Program now terminating.");
  STextIO.WriteLn;
EXCEPT
  STextIO.WriteString ("Entered exception handling at termination time.");
  STextIO.WriteLn;

END ExceptionTermination3.

which raises a new exception at the beginning of the FINALLY clause (and so does not conclude it), and then produces the output:

Entered exception handling for main body
Entered exception handling at termination time.

It would make no difference to the output in this case whether the RETURN were executed or not, as it is the raising of a exception in the FINALLY part that triggers transfer of control to its EXCEPT clause.

In the event that there is no finally clause to a module, but there is an except clause, then the except clause applies to exceptional events regardless of whether they took place during execution of the body of the module, or after termination had been initiated. In such situations, it may be desirable to determine whether one has entered the exception handler prior to or subsequent to the commencement of termination. In order to do this, one could write code as in the following outline:

MODULE ExceptionTermination4;
FROM TERMINATION IMPORT
  IsTerminating, HasHalted;

BEGIN
  (* statement sequence *)
EXCEPT
  IF IsTerminating ()
    THEN
      (* action to handle exception after termination started *)
    IF HasHalted ()
      THEN
        (* specific action to handle exception after HALT *)
    END;
  ELSE
    (* action to handle exception before termination commenced *)
  END;
END ExceptionTermination4.

10.12.5 User-Defined Exceptions

This subsection addresses the first five points in the list at the beginning of section 10.11, and that apply only to code in which user defined exceptions are to be defined, detected, and raised, namely:

1. The conditions under which exceptions are raised must be defined.

2. All exceptions must be named.

3. The source of the exception must be defined and registered.

4. The conditions producing the exception must be detected.

5. The exception must be raised, providing the source and a message.

First, the programmer must determine whether it is necessary to use exceptions at all. As illustrated above, most exceptional circumstances can be avoided. However, the code in a library cannot itself guarantee that the user will always employ its routines correctly, despite the stated preconditions. Thus, it may be necessary for code to be able to raise an exception if it is misused. As in all aspects of planning, it is essential that the logic of this be carefully thought out before being committed to code.

Second, exceptions need to be declared. As illustrated by the interface to the standard libraries, this is just an enumeration:

TYPE
  MyExceptions = (JohnGough, KeithHopper, AlbertMeier);

If this is done as part of a library, enquiry functions should be provided as well, and these may be modeled on the ones found in IOChan. The enumeration, and the second function are of course unnecessary if the library module only has one exception, and both procedures are unnecessary if the exceptions are defined, detected, and raised within the confines of the main program module.

PROCEDURE IsMyException (): BOOLEAN;
  (* Returns TRUE if the current coroutine is in the exceptional execution state because of the raising of an exception from MyExceptions; otherwise returns FALSE. *)

PROCEDURE MyException (): MyExceptions;
  (* If the current coroutine is in the exceptional execution state because of the raising of an exception from MyExceptions, returns the corresponding enumeration value, and otherwise raises an exception. *)

Third, in order to protect the language itself and individual library modules from having their exceptions misused by some code other than that entity entitled to use them, every source of exceptions must register itself with the module EXCEPTIONS (another system module). In so doing, the source will receive a unique value for an identifier of type ExceptionSource that must be supplied whenever actually raising an exception. Since there is no way for another module to discover this value, only the code that registers itself as a source can raise the exceptions that belong to that source. This is all done by

FROM EXCEPTIONS IMPORT
  ExceptionSource, AllocateSource;
VAR
  myExSource : ExceptionSource;
BEGIN
   AllocateSource (myExSource);

Fourth, the conditions determined in the planning stage are coded appropriately.

Fifth, the exception is actually raised as a result of the detected conditions. When this is done, the source must be provided, along with a message. Typically the message is a brief description of the problem that can be printed during the course of handling the exception. These tasks are accomplished using:

FROM EXCEPTIONS IMPORT
  RAISE;  (* in addition to the stuff above *)

and then in the actual code:

(* statement sequence *)
IF brokenAussie
  THEN
    RAISE (myExSource, ORD (JohnGough), "Down under task bad.")
  ELSIF badKiwiError THEN
    RAISE (myExSource, ORD (KeithHopper), "Hopper already Empty")
  ELSIF AlpineSlide THEN
    RAISE (myExSource, ORD (AlbertMeier), "Matterhorn has fallen")
  END;

A FINALLY clause can determine whether the current exception state is exceptional or not, and if so (either it or possibly an exception handler for a module or procedure), can enquire of the module EXCEPTIONS whether or not it is the source of an exception, if so, which one it is, and what is the error message. (The error message may be used by an automatic handler at the outermost level as well). This is done as in the following illustration:

FROM EXCEPTIONS IMPORT
  CurrentNumber, GetMessage, IsCurrentSource, IsExceptionalExecution, ExceptionNumber;
  (* in addition to all the stuff above *)
VAR
  theErrorNumber : ExceptionNumber;  (* just a cardinal *)
  stringVar : ARRAY [0..50] OF CHAR

and in the code

FINALLY
  IF (IsExceptionalExecution() ) AND (IsCurrentSource (myExSource) )
    THEN
      theErrorNumber := CurrentNumber (myExSource);
      GetMessage (stringVar);
      (* take further action *)
    END;

As one might expect, an attempt to obtain a value from CurrentNumber when myExSource is not in fact the source of the exception will in itself cause an exception to be raised, for this is interpreted as an attempt to steal information that belongs to some other source of exceptions. Note, however, that the message of the current exception is accessible to any caller without having to provide a source identity check.

Observe that apart from the enquiry function IsExceptionalExecution (and possible GetMessage), that might be useful in any FINALLY clause, none of the other items in EXCEPTIONS need to be imported unless the code in question is to define, detect, and raise its own exceptions. Indeed, exception handling need not use anything at all from this module.


Contents