Chapter three of this part of the manual describes the language extensions defined in IS 10514-2 and IS 10514-3. Chapter four of this part of the manual describes the disparities in p1 Modula-2 with respect to the ISO language definition. The changes with respect to earlier versions of the compiler (7.x) are summarized in Appendix II.
Although Programming in Modula-2 by Niklaus Wirth represents the ultimate definition of
the language, it is not altogether to be recommended as an introductory textbook. More
suitable for this purpose is for example
Modula-2 Made Easy by Herbert Schild (McGraw-Hill 1986)
For the experienced Pascal programmer and as a complement to Wirth's book
Modula-2 for Pascal Programmers by Richard Gleaves (Springer 1984)
is highly recommendable. This book emphasizes the differences between Pascal and
Modula-2 and explains Modula-2's main features often better than Wirth.
Both books are based on Modula-2 compilers which have not yet implemented the changes set out in the "Revisions and Amendments" section of the 3rd edition of PIM. This does not detract from the books' quality in any way - after all, only minor improvements are involved.
For those interested in object-oriented programming, we recommend the following
introductory material:
BYTE, Volume 11, Number 8 (August 1986)
This issue of BYTE includes several interesting articles on object-oriented
programming.
Object-Oriented Programming by Brad Cox (Addison-Wesley 1986)
This book is a general introduction to object-oriented programming and is based on
"Objective C".
Object-Oriented Programming for the Macintosh by Kurt Schmucker (Hayden Book
Company 1986).
Kurt Schmucker first presents the general concepts of object-oriented programming and then
concentrates on programming with Object Pascal and MacApp on the Apple Macintosh.
Essential properties of some of these type classes are as follows:
Ordinal types:
These can be used as index types for "ARRAYs", as base types for "SETs" and subrange
types and for the control variables of "FOR" loops. They occupy at most as much memory as
the type "WORD" (32 bits for ppc and i836, 64 bis for x86_64). The standard function "ORD" accepts any
ordinal-type argument.
Scalar types:
The values of scalar types have a predefined order. Comparisons and the standard functions
"MIN" and "MAX" are valid for all these types.
Whole number types:
These represent different ranges of whole numbers. The whole number types are assignment
compatible to each other.
Subrange types:
All expressions involving subrange types are calculated using the subranges' respective base
types; a subrange types is therefore compatible to its base type.
"Variable" types:
The types "ZZ type", "RR type", "CC type" and "SS type" are called variable types. They
cannot be assigned directly by the programmer - the compiler uses them for literals and
constant expressions of indefinite type within the corresponding type group ("ZZ-Typ" for
"INTEGER" / "CARDINAL", "RR-Typ" for "REAL" / "LONGREAL" etc.). They are compatible
with the other types in the same group and cover the combined ranges of all these types.
In particular, the "ZZ type" covers the range "MIN (INTEGER)" to "MAX (CARDINAL)". Calculations in constant expressions can therefore extend over this entire range without overflow.
The "RR type" and the "CC type" are represented in the most accurate floating point format available on all target platforms (IEEE double precision in p1 Modula-2). The result of a constant expression is therefore at least as accurate as the result from corresponding run-time calculations.
The "SS type" is used for string constants. Constants of this type are assignment compatible to any "ARRAY OF CHAR" large enough to contain the entire length of the constant. String concatenation ("+" operator: cf. section 2.3.5) can be used with constants of this type.
"SS type" constants of length 1 are compatible with type "CHAR",
as is the null string ("": SS type, length 0), which then represents the end-of-string
character (cf. section 2.2).
Whole number constants (of "ZZ type") are only ascribed a particular type when they are
actually used, i.e. they can be used without explicit type conversion in any arithmetic
expression involving whole number types. The result type of standard functions returning
whole number constants is also "ZZ type".
Floating point constants also have a variable type ("RR type") and are compatible both to
"REAL" and to "LONGREAL". The type of complex constants formed using "CMPLX" is
fixed if at least one of the two components is of fixed type. If both components are of
variable type then the resulting constant is of "CC type" and is compatible to both
"COMPLEX" and "LONGCOMPLEX".
The NIL pointer ("NIL") is compatible to all pointer and procedure types. Procedure
variables can therefore be initialized to and compared with the value "NIL".
The empty reference ("EMPTY") is compatible to all class types.
String constants are assignment compatible to all arrays having element type "CHAR"
provided the array is large enough to hold the entire length of the string. As well as this,
string constants of length one are compatible to type "CHAR" and so is the null string (""); in
such a case the null string represents the end-of-string character.
All arrays having a particular element type are compatible to open arrays having the
same element type. A variable of this element type does not meet this requirement.
2.2 Type Compatibility
The Modula-2 language definition distinguishes between three kinds of type compatibility:
compatibility in (arithmetic) expressions (compatible), compatibility in assignments
(assignment compatible) and the compatibility of actual parameters to their formal
counterparts (parameter compatible). Compatible types are always assignment and parameter
compatible too, and assignment compatible types are always also parameter compatible as far
as value parameters are concerned.
The compiler issues an error message if the value of a constant in a calculation or an
assignment is outside the range of the target type.
2.3 Changes with Respect to Programming in Modula-2
In the course of standardizing Modula-2, several details not exactly stipulated by Niklaus
Wirth in Programming in Modula-2 (PIM) were clearly defined, and a number of new
features were also incorporated into the language. The smaller changes are summarized in
this chapter; the more extensive ones are handled in their own individual chapters.
2.3.1 Operations on Whole Numbers
The function of the operators "DIV" and "MOD" is quite clear-cut
for operands of type "CARDINAL". For "INTEGER" operands however,
the implementation of division (and therefore also of forming the modulus) almost
always conflicts with the mathematical definition which requires a non-negative modulus
result and does not allow negative divisors. In addition to the "DIV" and
"MOD" operator pair, another pair, "/" and "REM", has
therefore been introduced, so that the two approaches can be differentiated in a
clearly defined way. "DIV" and "MOD" now correspond to the
mathematical definition of forming the modulus, whereas "/" and
"REM" apply the established integer-division and -remainder algorithms.
Hence "MOD" regains its fundamental meaning, and the familiar "/"
can be used for normal integer division. Based on
res := a / b; div := a DIV b;
rem := a REM b; mod := a MOD b;
the two calculation methods can be defined as follows:
a = res * b + rem | a = div * b + mod |
"rem" and "a" have the same sign | "mod" is always greater than or equal to 0 |
"b" may not be 0 | "b" must be greater than 0 |
a | b | a / b | a REM b | a DIV b | a MOD b |
39 | 9 | 4 | 3 | 4 | 3 |
-39 | 9 | -4 | -3 | -5 | 6 |
39 | -9 | -4 | 3 | error | error |
-39 | -9 | 4 | -3 | error | error |
In order to avoid indirect writeaccess, control variables of "FOR" statements may not be modified in an inner procedure even if the procedure is never called from within the "FOR" loop. Otherwise the compiler would have to reconstruct the entire procedure hierarchy to check for this.
The usage of "SYSTEM.ADR" on a control variable is allowed even within the variable's associated "FOR" loop. Responsibility for ensuing side effects rests with the programmer.
The ISO standard provides the data type "PACKEDSET" for this second kind of use. This
data type is coupled to the format used by the host machine to represent numbers. For a
"PACKEDSET" with base type starting at 0 and having the same size as a variable of type
"CARDINAL" the following applies:
CAST (CARDINAL, BITSET {0}) = 1
In p1 Modula-2 all variables of a "PACKEDSET" type having a base type without negative values are implemented so that they reflect the bit numbering from least significant bit to most significant bit (cf. sections 5.3.7 and 5.3.8). This is the reversed order used in the manuals for PPC processors but it is equivalent to the use in most programming languages. The bit numbering of a "SET" type depends on the amount of memory needed to represent it.
Example 1:
DEFINITION MODULE MyIO; IMPORT STextIO; CONST SkipLine = STextIO. SkipLine; (* exported as SkipLine *)
Example 2:
FROM TextIO IMPORT WriteString, WriteLn; IMPORT STextIO; CONST SWriteString = STextIO. WriteString; SWriteLn = STextIO. WriteLn;
Example:
CONST textWithSound = 'This is text with ' + 7C + "sound.";
For complex numbers the four basic arithmetic operations "+", "-", "*" and "/" are defined along with the relational operations "=" and "<>" (or "#"). Other relational operations are not possible, since the values of complex numbers do not have a predefined order.
Complex numbers (including complex constants) can be specified with the function "CMPLX". "RE" and "IM" extract the real and imaginary parts respectively of a complex number (cf. 2.5.2 Standard Procedures).
Pragmas now begin with "<*" and end with "*>". For example:
<* This is a pragma *>
The syntax of the pragmas themselves is left up to the individual implementation. p1 Modula-2's pragma syntax is described in chapters 4.2 and 4.3.
The enhancement affects the syntax of formal parameters:
FormalType | |
Before | [ARRAY OF] qualident. |
Now | {ARRAY OF} qualident. |
PROCEDURE HIGH:
The enhancement also affects the standard function "HIGH", which is used to determine the
actual maximum index of an open array. The function has been extended to handle
multidimensional open arrays too, so that the maximum index of the second, third etc.
dimension can be determined.
"HIGH (ArrayName)" corresponds with the previous definition (from PIM).
"HIGH (ArrayName [constexpr])" returns the maximum index of the second dimension.
"HIGH (ArrayName [constexpr, constexpr])" is the syntax for a third dimension.
Etc.
"constexpr" must be a constant expression of type "CARDINAL". Its value is irrelevant.
The basic syntax of all value constructors is:
TypeName "{" Constructor "}"
The syntax of Constructor is slightly different for each data type.
Example:
TYPE Colors = (black, white, red, orange, yellow, green, blue, violet); ColorSet = SET OF Colors; CONST Set1 = ColorSet {black, white}; BrightColors = ColorSet {red .. violet}; VAR f1, f2: Colors; set: ColorSet; BEGIN f1 := orange; f2 := green; set := ColorSet {f1 .. f2, black};
Example:
TYPE Vector = ARRAY [0 .. 5] OF REAL; CONST nullVector = Vector {0.0 BY 6}; VAR r: REAL; vect: Vector; BEGIN vect := Vector {1.0, r BY 3, 0.0 BY 2};
Examples:
TYPE Point = RECORD (* as in MacTypes.DEF *) CASE : INT16 OF | 1: v: INT16; (*vertical coordinate*) h: INT16; (*horizontal coordinate*) | 2: vh: ARRAY VHSelect OF INT16; END; END; Rect = RECORD (* as in MacTypes.DEF *) CASE : INT16 OF | 1: top: INT16; left: INT16; bottom: INT16; right: INT16; | 2: topLeft: Point; botRight: Point; END; END; Person = RECORD name: ARRAY [0 .. 39] OF CHAR; age: CARDINAL; zip: CARDINAL; residesIn: ARRAY [0 .. 39] OF CHAR; income: REAL; END; CONST origin = Point {1, 0, 0}; VAR age: CARDINAL; inc: REAL; Insert (personList, Person ("Meier", age, 8000, "Munich", inc)); Quickdraw. PaintRect (Rect {1, 0, 0, bottomEdge, rightSide});
Examples:
TYPE Vector = ARRAY [0 .. 3] OF INTEGER; Matrix = ARRAY [0 .. 3] OF Vector; CONST vect = Vector {0, 1, 2, 3}; matrix = Matrix {vect BY 2, {0 BY 4} BY 2}; Quickdraw. PaintRect (Rect {2, origin, {1, bottomEdge, rightSide}});
All procedures accept value parameters of the specified type and of subranges of that type. The result of a function then has the subrange's base type. This is not a restriction because expressions are always evaluated in the corresponding base type anyway.
PROCEDURE CAP (ch: CHAR) : CHAR;
For "ch" in the range ""a" .. "z"", delivers the corresponding capital letter. Any other
character is returned unchanged.
PROCEDURE CHR (x: CARDINAL): CHAR;
Returns the character having ordinal value "x". The following relationship holds:
CHR (x) = VAL (CHAR, x)
PROCEDURE CMPLX (re, im: real type): complex type;
Returns the complex number "re + i * im". The following relationships hold:
re = RE (CMPLX (re, im)) and
im = IM (CMPLX (re, im))
If both parameters are of "RR type" then the result is of "CC type". If at least one of the
parameters is of type "REAL" then the result is of type "COMPLEX", and if at least one of the
parameters is of type "LONGREAL" then the result is of type "LONGCOMPLEX". It is an
error for one parameter to be of type "REAL" and the other to be of type "LONGREAL".
PROCEDURE FLOAT (x: type): REAL;
Converts the value "x" of arbitrary scalar numeric type to a value of type "REAL". The
following relationship holds:
FLOAT (x) = VAL (REAL, x)
PROCEDURE HIGH (VAR a: ARRAY OF type) : CARDINAL;
Returns the maximum index value of the open array "a".
PROCEDURE IM (c: complex type): real type;
Returns the imaginary part of the complex number "c". If "c" is of type "COMPLEX" then
the result is of type "REAL"; if "c" is of type "LONGCOMPLEX" then the result is of type
"LONGREAL". If "c" is of "CC type" then the result is of "RR type"
PROCEDURE INT (x: type): INTEGER;
Converts the value "x" of arbitrary scalar type to a value of type "INTEGER". The following
relationship holds:
INT (x) = VAL (INTEGER, x)
If "x" is a floating point number, "INT" returns the whole number part, simply discarding the
fractional part, i.e. truncation towards zero occurs, e.g.:
INT (7.9) = 7, INT (-1.6) = -1
PROCEDURE ISMEMBER (o1, o2: classtype): BOOLEAN;
Tests whether the typ op "o1" is a son type of or equal to "o2". "o1" and "o2" may denote
either object variables or class names.
PROCEDURE LENGTH (str: ARRAY OF CHAR): CARDINAL;
This procedure returns the number of valid characters (excluding the possible end-of-string
character) making up the character string "str".
PROCEDURE LFLOAT (x: type): LONGREAL;
Converts the value "x" of arbitrary scalar numeric type to a value of type "LONGREAL".
The following relationship holds:
LFLOAT (x) = VAL (LONGREAL, x)
PROCEDURE MAX (type): type;
Returns the maximum value of the scalar type "type". If "type" is a whole number type or a
subrange of one, the result is of indefinite whole number type ("ZZ type").
PROCEDURE MIN (type): type;
Returns the minimum value of the scalar type "type". If "type" is a whole number type or a
subrange of one, the result is of indefinite whole number type ("ZZ type").
Note that in general "MIN (REAL)" is a negative value (in p1 Modula-2 "MIN (REAL) =
-MAX (REAL)") and not the smallest, positive floating point number not equal to zero! The
same applies to "LONGREAL".
PROCEDURE ODD (x: type): BOOLEAN;
Returns "TRUE", if argument "x" is odd. "x" must be of a whole number type.
PROCEDURE ORD (x: type): CARDINAL;
Returns the ordinal value of "x". Any ordinal type is permitted for "x". The following
relationship holds:
ORD (x) = VAL (CARDINAL, x)
PROCEDURE RE (c: complex type): real type;
Returns the real part of the complex number "c". If "c" is of type "COMPLEX" then the
result is of type "REAL"; if "c" is of type "LONGCOMPLEX" then the result is of type
"LONGREAL". If "c" is of "CC type" then the result is of "RR type"
PROCEDURE SIZE (type): ZZ type;
PROCEDURE SIZE (VAR x: type): ZZ type;
If called with a type name or the name of an entire variable (i.e. no dereferencing, indexing or
selectors) other than an open array, this function returns the size of the given type or variable
respectively. In the case of variant records, the size of the largest variant is returned.
PROCEDURE TRUNC (x: type): CARDINAL;
Converts the value "x" of arbitrary scalar type to a value of type "CARDINAL". The
following relationship holds:
TRUNC (x) = VAL (CARDINAL, x)
If "x" is a floating point number, "TRUNC" returns the whole number part, simply discarding
the fractional part, i.e. truncation towards zero occurs, e.g.:
TRUNC (7.9) = 7
PROCEDURE VAL (tType; x: pType): tType
Converts the value "x" of type "pType" to a value of type "tType". The table below shows
which type conversions between scalar types using "VAL" are allowed:
type of the parameter expression ("pType") | |||||||
target type ("tType") | CARDINAL | INTEGER | REAL | LONGREAL | CHAR | BOOLEAN | enumeration |
CARDINAL | ORD | ORD | TRUNC | TRUNC | ORD | ORD | ORD |
INTEGER | * | * | INT | INT | * | * | * |
REAL | FLOAT | FLOAT | * | FLOAT | - | - | - |
LONGREAL | LFLOAT | LFLOAT | LFLOAT | * | - | - | - |
CHAR | CHR | CHR | - | - | * | - | - |
BOOLEAN | * | * | - | - | - | * | - |
enumeration | * | * | - | - | - | - | * |
Key:
The target type may also be a subrange of the type shown for the target type in the table.
xxx | = | legal type conversion; using standard procedure "xxx" yields the same result. |
* | = | legal type conversion; "VAL" is the only procedure available for this conversion. |
- | = | illegal type conversion; only possible indirectly. |
The following declarations:
TYPE Days = (sunday, monday, tuesday, wednesday, thursday, friday, saturday); WorkDay = [monday .. friday]; VAR i, j, z: INTEGER; r: REAL; i := 42; j := -1; z := 0; r := -2.7;
expression | value | type |
VAL (CARDINAL, i) | 42 | CARDINAL |
VAL (CARDINAL, j) | error | |
VAL (CARDINAL, r) | error | |
VAL (INTEGER, i) | 42 | INTEGER |
VAL (INTEGER, r) | -2 | INTEGER |
VAL (REAL, i) | 42.0 | REAL |
VAL (REAL, TRUE) | not allowed | |
VAL (LONGREAL, r) | -2.7 | LONGREAL |
VAL (CHAR, z) | 0C | CHAR |
VAL (CHAR, r) | not allowed | |
VAL (BOOLEAN, z) | FALSE | BOOLEAN |
VAL (Days, 5) | friday | Days |
VAL (WorkDay, 4) | thursday | Days |
VAL (WorkDay, z) | error |
PROCEDURE DEC (VAR x: type);
PROCEDURE DEC (VAR x: type; n: type2);
Replaces "x" by its "n"th predecessor. If "n" is not specified, 1 is assumed. "x" must be of
an ordinal type.
PROCEDURE DESTROY (VAR x: classtyp);
The destructor chain of the object referenced by "x" is executed. Then the
storage occupied by this object is released. "classtyp" has to be a normal
class (cf. 3.1.2); the procedure
"DEALLOCATE" has to be declared or imported (e.g. from "Storage") and have the
following type:
PROCEDURE DEALLOCATE (VAR x: SYSTEM. ADDRESS; size: CARDINAL);
PROCEDURE DISPOSE (VAR x: type);
Disposes of the dynamic variable pointed to by "x". The compiler converts the call
"DISPOSE (x)" into the call "DEALLOCATE (x, SIZE (x^))". "x" must be a pointer variable
and the procedure "DEALLOCATE" must have been declared or imported (e.g. from
"Storage") and have the following type:
PROCEDURE DEALLOCATE (VAR x: SYSTEM. ADDRESS; size: CARDINAL);
PROCEDURE EXCL (VAR s: SET OF type; i: type);
Removes the element "i" from the set "s" (if it is actually there). "s" can be of any set type.
"i" must be an expression which is assignment compatible to the set's base type.
PROCEDURE HALT;
Ends execution of the program. If the current process is still in its initialization phase, control
is passed to the termination code. If the process is already in its termination phase, execution
continues with the next procedure in the termination chain.
NB: "HALT" is not a program abort due to an error but a normal program
termination. In the case of an error an exception condition can be generated with
"RAISE" (cf. sections 2.7.3.2 and
2.10.2). p1 Modula-2 provides in addition "SYSTEM.
BREAK" for debugger calls (cf. section 4.1.4).
PROCEDURE INC (VAR x: type);
PROCEDURE INC (VAR x: type; n: type2);
Replaces "x" by its "n"th successor. If "n" is not specified, 1 is assumed. "x" must be of an
ordinal type.
PROCEDURE INCL (VAR s: SET OF type; i: type);
Includes the element "i" in the set "s" (if it is not already there). "s" can be of any set type.
"i" must be an expression which is assignment compatible to the set's base type.
PROCEDURE NEW (VAR x: pointerType);
Allocates memory for a dynamic variable and stores a reference to it in the pointer variable
"x".
The compiler converts the call "NEW (x)" into the call "ALLOCATE (x, SIZE (x^))". "x"
must be a pointer variable and the procedure "ALLOCATE" must have been declared or
imported (e.g. from "Storage") and have the following type:
PROCEDURE ALLOCATE (VAR x: SYSTEM. ADDRESS; size: CARDINAL);
[IMPLEMENTATION] MODULE Name; <imports, exports, declarations> BEGIN <initialization part> FINALLY <termination part> END Name
Termination code can also be included in internal modules and local modules inside procedures. If there is no termination part, the syntax is as it used to be:
BEGINEND Name
If there is to be a termination part without an initialization part, the keyword "BEGIN" still has to appear - the initialization part is just left empty:
BEGIN FINALLYEND Name
The initialization sequence is clearly laid down in the standard. In a program/-implementation module, first the initialization parts of all the imported modules are executed, in the order the imports appear in the source code. Then the initialization parts of internal modules not inside any procedure (i.e. at root level) are called. Finally the initialization code of the program/-implementation module itself is executed. An global initialization sequence arises from this for each module involved in the program in succession.
When it comes to termination, this chain is now traced backwards. So the termination part of the program module is executed first, followed by the termination parts of its internal modules (if any), followed in turn by that of the module imported last and so on. This also means that the termination part of each actual implementation module is executed before those of its internal modules.
If a procedure does not end due to a (possibly implicit) "RETURN" statement, or an implicit "reraise" at the end of an optional exception handler body but because of a "HALT" or an error, the termination parts of any local modules are not executed. This also applies if the "HALT" or the error occurs in a dynamically more deeply nested procedure.
A call to the procedure "HALT" or the occurrence of an error not handled by the program proper (cf. section 2.7 Exception Handling) ends the initialization phase prematurely and immediately initiates the termination phase. The termination chain is still executed even if the initialization of the program module (i.e. the "actual" program) had not even begun. Of course only the termination parts of those modules are executed for which initialization has already started. So if the termination code of a module has been called, it is therefore certain that the corresponding initialization had at least been started, and, if it did not contain a "HALT" or any errors, had even been completed. Caution is necessary if (imported) procedures are to be called from the initialization part, as it is not possible to say anything in general about the ramifications this may have.
If, in the termination phase, "HALT" is called or an error not handled by the program occurs, the termination part of the module concerned is immediately aborted and the termination is continued with the next module. So it can be guaranteed for every module that its termination is at least started.
This ensures that the execution of every module's termination code is actually started and that that of "error-free" modules is executed at least once in entirety. This fact requires however that the termination code of a module not be dependent on any particular preconditions, since it could be called several times in certain circumstances. This is not a particularly severe restriction, since terminations are usually of the form "if this and that haven't been cleaned up yet, then do this and that". You should only be particularly aware of this when writing general libraries and you do not know everything the future users will get up to with them.
BEGINEXCEPT FINALLY EXCEPT END Name
The body of a procedure with exception handler has the structure:
BEGINEXCEPT END Name
All data structures and procedures needed to define and analyze an exception can be found in module "EXCEPTIONS" (cf. chapter 2.10).
Example:
TYPE MyExceptions = (myFirstException, mySecondException, …); VAR mySource: EXCEPTIONS. ExceptionSource;
The value for the source is defined dynamically in the initialization part like this:
BEGIN EXCEPTIONS. AllocateSource (mySource);
Example:
NEW (ptr); IF ptr = NIL THEN RAISE (mySource, ORD (myFirstException), 'Operation aborted due to lack of memory.'); END(*IF*);"EXCEPTIONS. IsExceptionalExecution" allows to decide, whether a program is in exceptional state or not (e.g. in procedure that are called during normal execution as well as during exceptional execution).
"CurrentNumber" returns the exception number as its function result.
Attention! If "CurrentNumber" is called with an exception source other than the current
source, the exception "exException" is raised.
The analysis part of an exception handler might therefore look like this:
IF IsCurrentSource (mySource) THEN CASE VAL (MyExceptions, Number (mySource)) OF myFirstException: (* take appropriate measures *) | mySecondException: (* take appropriate measures *) : END(*CASE*); ELSE (* not this source: further analysis or pass on *) END(*IF*);
The corresponding parts of a definition/-implementation module pair for the above example are:
DEFINITION MODULE MyLibInterface; TYPE MyExceptions = (myFirstException, mySecondException, ...); PROCEDURE IsMyException (): BOOLEAN; PROCEDURE MyExceptionValue (): MyExceptions; : END MyLibInterface. IMPLEMENTATION MODULE MyLibInterface; IMPORT EXCEPTIONS; VAR mySource: EXCEPTIONS. ExceptionSource; : PROCEDURE IsMyException (): BOOLEAN; BEGIN RETURN EXCEPTIONS. IsCurrentSource (mySource)); END IsMyException ; PROCEDURE MyExceptionValue (): MyExceptions; BEGIN RETURN VAL (MyExceptions, EXCEPTIONS. CurrentNumber (mySource)); END MyExceptionValue ; BEGIN EXCEPTIONS. AllocateSource (mySource); : END MyLibInterface.Notes:
Modula-2's run-time system installs for its own part a global exception handler which is always present. If this handler is activated (because no other exception handler is installed or has handled the exception), it transfers the program from the initialization to the termination phase. If the program is already in the termination phase, execution is continued from the next module to be terminated.
If an exception arises during the handling of an exception (or an exception is deliberately triggered with "RAISE"), the program is continued from the next exception handler. The new exception's details are saved; those of the original exception are lost.
A module body's exception handler is only installed after the initialization of all imported and/-or internal modules has been completed. Exception conditions in module bodies can therefore not be triggered by imports. Internal modules must be protected by their own exception handlers; looked at another way, any initializations that absolutely must have been completed before the module body's own exception handler can become active, can be done in internal modules.
If a procedure is left due to the occurrence of an exception, local modules are not terminated. Leaving a procedure via the implicit "reraise" at the end of an exception handler is treated as "regular" leave, in this case the termination parts of optional local modules are executed.
In p1 Modula-2 the module "SYSTEM" is part of the compiler and is called a pseudo-module. For this reason there is no symbol file for it.
DEFINITION MODULE SYSTEM; (* gives access to system programming facilities that are probably non portable. *) (* the constants and types define the underlying properties of storage. *) CONST BITSPERLOC = 8; LOCSPERWORD = <4 for 32-bit-architectures resp. 8 for x86_64>; TYPE LOC; (* Not opaque, but the smallest addressable unit of storage *) ADDRESS = POINTER TO LOC; WORD = ARRAY [0..LOCSPERWORD-1] OF LOC; CONST LOCSPERBYTE = 1; TYPE BYTE = LOC; PROCEDURE ADDADR (addr: ADDRESS; offset: CARDINAL): ADDRESS; (* Returns address given by (offset + addr), or may raise an exception if this address is not valid. *) PROCEDURE SUBADR (addr : ADDRESS; offset: CARDINAL): ADDRESS; (* Returns address given by (offset - addr), or may raise an exception if this address is not valid. *) PROCEDURE DIFADR (addr1, addr2: ADDRESS): INTEGER; (* Returns the difference between address (addr1 - addr2), or may raise an exception if the arguments are invalid or address space is non-contiguous. *) PROCEDURE MAKEADR (val: zz-type): ADDRESS; (* Returns address constructed from the given value, or may raise an exception if this address is not valid. *) PROCEDURE ADR (VAR v: <anytype>): ADDRESS; (* Return the address of variable v *) PROCEDURE ROTATE (val: <a packed-set type>; num: INTEGER): <type of first parameter>; (* Returns a bit sequence obtained from val by rotating up or down (left or right) by the absolute value of num. The direction is up, if the sign of num is negative, otherwise the direction is down. *) PROCEDURE SHIFT(val: <a packed-set type>; num: INTEGER): <type of first parameter>; (* Returns a bit sequence obtained from val by shifting up or down (left or right) by the absolute value of num. The direction is up, if the sign of num is negative, otherwise the direction is down. *) PROCEDURE CAST(<targettype>; val: <anytype>): <targettype>; (* CAST is a type transfer function. Given the expression denoted by val, it returns a value of the type <targettype>. An invalid value for the target value or a physical address alignment problem may raise an exception. *) PROCEDURE TSIZE (<type>; ...): CARDINAL; (* Returns the number of LOCS used to store a value of the specified <type>. The extra parameters, if present, are used to distinguish variants in a variant record. *) END SYSTEM.
Individual descriptions:
LOCSPERBYTE
Size of a byte expressed in "LOCs".
LOCSPERWORD
Size of a "WORD", expressed in "LOCs". The actual processor register size (32 bit resp. 64 bit)
is used for a "WORD".
BITSPERLOC
The number of bits occupied by a variable of type "LOC". Since a "LOC" has the same
memory size as a byte, this is 8.
LOC
The base memory type.
All expressions which have a memory size of 1 are parameter compatible to parameters of
type "LOC". Absolutely all types are parameter compatible to parameters of type "ARRAY
OF LOC".
Special parameter compatibility also applies to types of the form "ARRAY [0 .. n-1] OF
LOC". Any type of size "n" is parameter compatible to parameters of this type. Any type of
a size that is a whole multiple of "n" is parameter compatible to open arrays of this type. In
this way universal structures can be created for types of any one size. p1 Modula-2 requires
in accordance with the standard that for even "n" the actual parameters must have even
address, which is normally the case for the structures which come into question.
ADDRESS
Universal address type.
"ADDRESS" is compatible to all pointer types. Because of the simple address structure of
the Intel and PowerPC processors, "ADDRESS" is structurally identical to "CARDINAL" in
p1 Modula-2.
BYTE
Predefined memory type, equal to "LOC" (cf. "LOC").
WORD
Predefined memory type: its properties are essentially the same as those of "ARRAY [0 .. n-1]
OF LOC" (cf. "LOC").
ADDADR
Function for performing address arithmetic independently of computer architecture.
In p1 Modula-2 this function is implemented as an inline addition. If the sum "addr + offset"
exceeds "MAX (CARDINAL)", the overflowing high bit is simply discarded (wrap around).
In p1 Modula-2 exceptions are not generated. "ADDADR" can be used in constant
expressions.
SUBADR
Function for performing address arithmetic independently of computer architecture.
In p1 Modula-2 this function is implemented as an inline subtraction. If the difference "addr
- offset" is less then 0, the overflowing high bit is simply discarded (wrap around). In
p1 Modula-2 exceptions are not generated. "SUBADR" can be used in constant expressions.
DIFADR
Universal function for determining the difference between two address values.
In p1 Modula-2 such a difference is calculated in a way which can lead to interpretation
problems if the value of the difference falls outside the range of type "INTEGER". In
p1 Modula-2 exceptions are not generated. "DIFADR" can be used in constant expressions.
MAKEADR
Universal function for constructing a value of type "ADDRESS".
As the types "ADDRESS" and "CARDINAL" / "INTEGER" are structural identical, this
function does not generate any additional code but just hands the given value over as an
address. "MAKEADR (-1)" is equivalent to "MAKEADR (0FFFFFFFFH)" resp. "MAKEADR (0FFFFFFFFFFFFFFFFH)".
"MAKEADR" can be used in constant expressions.
ADR
returns the address of any variable.
CAST
Function for assigning a new type (without reinterpretation).
The function "CAST" was defined in the ISO standard for general type reassignment and
takes the place of the earlier "TypeName(value)" - it does not change any (memory) value but
just assigns the memory contents a new type and therefore a new meaning. The sizes of the
source and destination types need not be identical. If the destination type is larger than the
source type, then the contents of the surplus memory space is not defined.
"CAST" is defined so as normally not to require any extra code. Because of the difference in
the arrangement of bytes in memory compared to that in processor registers on Power processors, in
p1 Modula-2 values are transferred from registers to the stack before the type reassignment if
the destination and source types have different sizes. "CAST" can be used in constant
expressions.
ROTATE
rotates the bits in "val" by the number of places given in "shift".
Positive values of "shift" cause rotation to the right (towards lower-valued bit positions) and
negative values cause rotation to the left. Values of type "LOC",
"BYTE", "WORD16" (cf. 4.1.3.1),
"WORD" and any packed set which occupies a whole number of locs (i.e. lower-
bound MOD 8 = 0, upper-bound MOD 8 = 7; e.g. "PACKEDSET OF [8 .. 63]") are allowed
for the first parameter ("val") of "ROTATE". "ROTATE" can be used in constant
expressions.
SHIFT
shifts the bits in "val" by the number of places given in "shift".
Positive values of "shift" cause a shift to the right (towards lower-valued
bit positions) and negative values cause a shift to the left. Values of type
"LOC", "BYTE", "WORD16" (cf.
4.1.3.1), "WORD" and any packed set which occupies a whole number of locs (i.e. lower-
bound MOD 8 = 0, upper-bound MOD 8 = 7; e.g. "PACKEDSET OF [8 .. 63]") are
allowed for the first parameter ("val") of "SHIFT".
"SHIFT" can be used in constant expressions.
TSIZE
Like "SYSTEM", "COROUTINES" is also a pseudo-module and has no symbol file.
returns the size of the memory space required by a given type in "LOCs".
For variant record types tag field values can also be specified in order to determine the size of
a particular variant. "TSIZE" can be used in constant expressions.
2.9 The Module "COROUTINES"
Since "compiler tricks" do not need to be used in the declaration and use of coroutines, the
handling of coroutines has been removed from module "SYSTEM" and placed into a module
of its own. The name "COROUTINE" was established for the name of the data type, as the
original name "PROCESS" did not exactly reflect the meaning of coroutines and had for that
reason already been discarded by Wirth (in PIM 3).
2.9.1 The Pseudo Definition-Module "COROUTINES"
The module can be considered as having the following definition module:
DEFINITION MODULE COROUTINES;
(* facilities for handling coroutines and interrupts *)
IMPORT SYSTEM;
TYPE
COROUTINE; (* Values of this type are created dynamically by NEWCOROUTINE
and identify the coroutine in subsequent operations *)
INTERRUPTSOURCE = CARDINAL;
PROCEDURE NEWCOROUTINE (procBody: PROC; workspace: SYSTEM. ADDRESS;
size: CARDINAL; VAR cr: COROUTINE;
initprotection: PROTECTION);
(* Creates a new coroutine whose body is given by procBody, and returns the
identity of the coroutine in cr. workspace is a pointer to the work
space allocated to the coroutine; size specifies the extent of this work
space in terms of SYSTEM. LOC. The optional parameter initprotection
specifies the initial protection level of the coroutine.
*)
PROCEDURE TRANSFER (VAR from: COROUTINE; to: COROUTINE);
(* Returns the identity of the calling coroutine in from, and transfers
control to the coroutine specified by to.
*)
PROCEDURE IOTRANSFER (VAR from: COROUTINE; to: COROUTINE);
(* Returns the identity of the calling coroutine in from, and transfers
control to the coroutine specified by to. On occurrence of an
interrupt, associated with the caller, control is transferred back to
the caller, and the identity of the interrupted coroutine is returned in
from. The calling coroutine must be associated with a source of
interrupts.
*)
PROCEDURE ATTACH (source: INTERRUPTSOURCE);
(* Associates the specified source of interrupts with the calling
coroutine.
*)
PROCEDURE DETACH (source: INTERRUPTSOURCE);
(* Dissociates the specified source of interrupts from the calling
coroutine.
PROCEDURE IsATTACHED (source: INTERRUPTSOURCE): BOOLEAN;
(* Return TRUE if and only if the specified source of interrupts is
currently associated with a coroutine; otherwise return FALSE.
*)
PROCEDURE HANDLER (source: INTERRUPTSOURCE): COROUTINE;
(* Return the coroutine, if any, that is associated with the source of
interrupts. The result is undefined if IsATTACHED(source) = FALSE
*)
PROCEDURE CURRENT (): COROUTINE;
(* Returns the identity of the calling coroutine *)
PROCEDURE LISTEN (p: PROTECTION);
(* Momentarily changes the protection of the calling coroutine to p. *)
PROCEDURE PROT (): PROTECTION;
(* returns the protection of the calling coroutine *)
PROCEDURE COROUTINEDONE (cr: COROUTINE);
(* Asserts that the coroutine identified by cr has reached
the end of its lifetime.
*)
END COROUTINES.
INTERRUPTSOURCE
Values of this type identify sources of interrupts. p1 Modula-2 doesn't define any legal source
of interrupts; every value results in an error message of the compiler
(cf. notes).
NEWCOROUTINE
Sets up the descriptor for a new coroutine (= process). The first parameter is a
parameterless procedure containing the code of the process. The second is a pointer
to the new coroutine's workspace (in p1 Modula-2 the workspace is identical to the
stack area; see also section 6.3.5). The third parameter
specifies the size of the workspace (in "LOCs"). The identity of
the new process is returned in the variable passed as fourth parameter.
The fifth parameter is optional. It defines the initial protection of the new process. If it is
omitted, the actual protection is passed as initial protection to the new coroutine.
Caution: "NEWCOROUTINE" just generates a new process - it is started only when
"TRANSFER" is called.
TRANSFER
Transfers control from the current process to the process identified in the second parameter.
After transfer back to the process which made the call (i.e. when the time comes, if ever, to
execute the statement following the original "TRANSFER" call in the source) the identity of
the now again current process is contained in the variable passed as the first parameter.
IOTRANSFER
Interrupts the current process and causes program execution to continue with the process
passed in the first parameter. Any interrupt which then occurs in the interrupt source
belonging to the process which made this "IOTRANSFER" call, triggers an automatic
transfer back to this said calling process. The first parameter then contains the identity of the
process just interrupted.
ATTACH
Attaches the calling process to the specified interrupt source. A call to "ATTACH" is a
necessary prerequisite to the use of "IOTRANSFER".
DETACH
Releases the connection generated by "ATTACH" between a coroutine and an interrupt
source.
IsATTACHED
Indicates whether a process is attached to the specified interrupt source. If so, "HANDLER"
can be used to determine which process is attached.
HANDLER
Returns the coroutine attached to the specified interrupt source. If no coroutine is attached to
this interrupt source, the result is undefined.
CURRENT
Delivers the identity of the current process.
LISTEN
Sets the protection briefly to the given value. This makes it possible for interrupts of lower-
priority processes to be handled.
PROT
Returns the current protection of the current process.
COROUTINEDONE
Signals (to the garbage collector) that the process passed as parameter will no more be activated and that therefore all references contained in the stack of this process are invalid.
Notes regarding implementation in p1 Modula-2:
Like "SYSTEM", "EXCEPTIONS" is also a pseudo-module and therefore does not have a
symbol file in p1 Modula-2.
ExceptionNumber
AllocateSource
RAISE
CurrentNumber
GetMessage
IsCurrentSource
IsExceptionalExecution
Like "SYSTEM", "M2EXCEPTION" is also a pseudo-module and therefore does not have a
symbol file in p1 Modula-2.
2.10.1 The Pseudo Definition-Module "EXCEPTIONS"
The module "EXCEPTIONS" could have a definition module something like this:
DEFINITION MODULE EXCEPTIONS;
(* Provides facilities for raising user exceptions and for making enquiries
concerning the current execution state.
*)
TYPE
ExceptionSource; (* values of this type are used within library modules to
identify the source of raised exceptions *)
ExceptionNumber = CARDINAL;
PROCEDURE AllocateSource (VAR newSource: ExceptionSource);
(* Allocates a unique value of type ExceptionSource. *)
PROCEDURE RAISE (source: ExceptionSource; number: ExceptionNumber;
message: ARRAY OF CHAR);
(* Associates the given values of source, number and message with
the current context and raises an exception.
*)
PROCEDURE CurrentNumber (source: ExceptionSource): CARDINAL;
(* If the current coroutine is in the exceptional execution state because
of the raising of an exception from source, returns the corresponding
number, and otherwise raises an exception.
*)
PROCEDURE GetMessage (VAR text: ARRAY OF CHAR);
(* If the current coroutine is in exceptional execution state, returns the
possibly truncated string associated with the current context.
Otherwise, in normal execution state, returns the empty string.
*)
PROCEDURE IsCurrentSource (source: ExceptionSource): BOOLEAN;
(* If the current coroutine is in the exceptional execution state because
of the raising of an exception from source, returns TRUE, and otherwise
returns FALSE.
*)
PROCEDURE IsExceptionalExecution (): BOOLEAN;
(* If the current coroutine is in the exceptional execution state because
of the raising of an exception, returns TRUE, and otherwise returns
FALSE.
*)
END EXCEPTIONS.
2.10.2 Description
ExceptionSource
This opaque type is used for variables identifying one's own sources of exceptions.
Type for numbering exceptions from sources defined by the programmer.
is for setting up a new exception source.
With "RAISE" it is possible to trigger an exception of one's own in a program deliberately.
The exception source and number must be specified, along with descriptive text.
If an exception comes from the specified source, you can inquire the source specific number
with "CurrentNumber". If not, the exception "exException" is raised.
procures the text associated with the current exception.
With "IsCurrentSource" you can inquire whether an exception comes from the specified
source.
The result of "IsExceptionalExecution" is TRUE, if the current coroutine is in exceptional
execution state, FALSE otherwise.
2.11 The Module "M2EXCEPTION"
This module contains the necessary data types and procedures for identifying the predefined
exceptions (language exceptions). A general description of the mechanism for handling
exception conditions can be found in section 2.7.
2.11.1 The Pseudo Definition-Module "M2EXCEPTION"
The module "M2EXCEPTION" could have a definition module something like this:
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 the raising 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 the raising of a language exception, returns TRUE, and otherwise
returns FALSE.
*)
END M2EXCEPTION.
2.11.2 Description
M2Exceptions
The type "M2Exceptions" identifies all exception conditions defined in the standard. It is the
result type of "M2Exception", the function used to find out the cause of an exception. (see
also section 2.7.3.4).
IsM2Exception
"IsM2Exception" is used to find out whether the cause of the exception is a standard one or
not.
M2Exception
"M2Exception" is used to find out which standard exception has been raised. If no standard
exception has been raised, the exception "exException" is raised.
2.11.3 Predefined Exception Conditions
indexException | the index expression of an array index exceeds its bounds. |
rangeException | on assignment or type conversion ("VAL"), the value exceeds the range of the target type. |
caseSelectException | the selection expression of a CASE statement did not match any label. No "ELSE" is specified. |
invalidLocation | access to a memory location not belonging to the program. This exception is detected by p1 Modula-2 when dereferencing a pointer with value "NIL" or calling a procedure variable containing the value "NILPROC" (cf. 4.7). |
functionException | the body of a function procedure is left without explicit "RETURN". |
wholeValueException | overflow in whole number arithmetic. |
wholeDivException | division by 0 in whole number arithmetic. |
realValueException | overflow or illegal value in real number arithmetic. |
realDivException | division by 0 in real number arithmetic. |
complexValueException | overflow or illegal value in complex number arithmetic. |
complexDivException | division by 0 in complex number arithmetic. |
protException | call of a procedure with a lower protection than the actual protection. |
sysException | exception raised in module "SYSTEM". |
coException | exception raised in module "COROUTNES". |
exException | exception raised in module "EXCEPTIONS" or "M2EXCEPTION". |
Like "SYSTEM", "Termination" is also a pseudo-module and therefore does not have a symbol file in p1 Modula-2.
DEFINITION MODULE TERMINATION; PROCEDURE IsTerminating (): BOOLEAN; (* This predicate yields TRUE iff the initialization code of the program module has completed executing, otherwise FALSE. *) PROCEDURE HasHalted (): BOOLEAN; (* This predicate yields TRUE iff a call to HALT has been made, otherwise FALSE. *) END TERMINATION.
HasHalted
informs whether "HALT" has been called or not.
chapter 1 (compiler) | start page | chapter 3 (compiler) |