1\input texinfo
2@setfilename oberon2.info
3@paragraphindent none
4@exampleindent 1
5@setchapternewpage off
6
7@settitle The Programming Language Oberon-2
8
9@titlepage
10@title The Programming Language Oberon-2
11@author H. Mossenbock, N. Wirth
12@author Institut fur Computersysteme, ETH Zurich
13@author March 1995
14@end titlepage
15
16@contents
17
18@c 1. Introduction
19@chapter Introduction
20
21Oberon-2 is a general-purpose programming language in the tradition of Pascal
22and Modula-2. Its most important features are block structure, modularity,
23separate compilation, static typing with strong type checking (also across
24module boundaries), and type extension with type-bound procedures.
25
26Type extension makes Oberon-2 an object-oriented language. An object is a
27variable of an abstract data type consisting of private data (its state) and
28procedures that operate on this data. Abstract data types are declared as
29extensible records. Oberon-2 covers most terms of object-oriented languages by
30the established vocabulary of imperative languages in order to minimize the
31number of notions for similar concepts.
32
33This report is not intended as a programmer's tutorial. It is intentionally
34kept concise. Its function is to serve as a reference for programmers,
35implementors, and manual writers. What remains unsaid is mostly left so
36intentionally, either because it can be derived from stated rules of the
37language, or because it would require to commit the definition when a general
38commitment appears as unwise.
39
40Appendix A defines some terms that are used to express the type checking rules
41of Oberon-2. Where they appear in the text, they are written in italics to
42indicate their special meaning (e.g. the @emph{same} type).
43
44@c 2. Syntax
45@chapter Syntax
46
47An extended Backus-Naur Formalism (EBNF) is used to describe the syntax of
48Oberon-2: Alternatives are separated by |. Brackets [ and ] denote optionality
49of the enclosed expression, and braces @{ and @} denote its repetition
50(possibly 0 times). Non-terminal symbols start with an upper-case letter (e.g.
51Statement). Terminal symbols either start with a lower-case letter (e.g.
52ident), or are written all in upper-case letters (e.g. @code{BEGIN}), or are
53denoted by strings (e.g. @code{":="}).
54
55@c 3. Vocabulary and Representation
56@chapter Vocabulary and Representation
57
58The representation of (terminal) symbols in terms of characters is defined
59using the ASCII set. Symbols are identifiers, numbers, strings, operators, and
60delimiters. The following lexical rules must be observed: Blanks and line
61breaks must not occur within symbols (except in comments, and blanks in
62strings). They are ignored unless they are essential to separate two
63consecutive symbols. Capital and lower-case letters are considered as distinct.
64
65@enumerate
66
67@item
68@dfn{Identifiers} are sequences of letters and digits. The first character
69must be a letter.
70
71@smallexample
72ident = letter @{letter | digit@}.
73@end smallexample
74
75Examples:
76@smallexample
77x     Scan     Oberon2     GetSymbol     firstLetter
78@end smallexample
79
80@item
81@dfn{Numbers} are (unsigned) integer or real constants. The type of an integer
82constant is the minimal type to which the constant value belongs (@pxref{Basic
83types}). If the constant is specified with the suffix @code{H}, the
84representation is hexadecimal otherwise the representation is decimal.
85
86A real number always contains a decimal point. Optionally it may also contain a
87decimal scale factor. The letter @code{E} (or @code{D}) means "times ten to the
88power of". A real number is of type @code{REAL}, unless it has a scale factor
89containing the letter @code{D}. In this case it is of type @code{LONGREAL}.
90
91@smallexample
92number      = integer | real.
93integer     = digit @{digit@} | digit @{hexDigit@} "H".
94real        = digit @{digit@} "." @{digit@} [ScaleFactor].
95ScaleFactor = ("E" | "D") ["+" | "-"] digit @{digit@}.
96hexDigit    = digit | "A" | "B" | "C" | "D" | "E" | "F".
97digit       = "0" | "1" | "2" | "3" | "4" | "5" | "6" | "7" | "8" | "9".
98@end smallexample
99
100Examples:
101@smallexample
1021991           INTEGER   1991
1030DH            SHORTINT  13
10412.3           REAL      12.3
1054.567E8        REAL      456700000
1060.57712566D-6  LONGREAL  0.00000057712566
107@end smallexample
108
109@item
110@dfn{Character} constants are denoted by the ordinal number of the character
111in hexadecimal notation followed by the letter @code{X}.
112
113@smallexample
114character  = digit @{hexDigit@} "X".
115@end smallexample
116
117@item
118@dfn{Strings} are sequences of characters enclosed in single (@code{'}) or
119double (@code{"}) quote marks. The opening quote must be the same as the
120closing quote and must not occur within the string. The number of characters in
121a string is called its @dfn{length}. A string of length 1 can be used wherever
122a character constant is allowed and vice versa.
123
124@smallexample
125string  = ' " ' @{char@} ' " ' | " ' " @{char@} " ' ".
126@end smallexample
127Examples:
128@smallexample
129     "Oberon-2"     "Don't worry!"     "x"
130@end smallexample
131
132@item
133@dfn{Operators} and @dfn{delimiters} are the special characters, character
134pairs, or reserved words listed below. The reserved words consist exclusively
135of capital letters and cannot be used as identifiers.
136
137@smallexample
138+  :=  ARRAY  IMPORT  RETURN
139-  ^   BEGIN  IN      THEN
140*  =   BY     IS      TO
141/  #   CASE   LOOP    TYPE
142~  <   CONST  MOD     UNTIL
143&  >   DIV    MODULE  VAR
144.  <=  DO     NIL     WHILE
145,  >=  ELSE   OF      WITH
146;  ..  ELSIF  OR
147|  :   END    POINTER
148(  )   EXIT   PROCEDURE
149[  ]   FOR    RECORD
150@{  @}   IF     REPEAT
151@end smallexample
152
153@item
154@dfn{Comments} may be inserted between any two symbols in a program. They are
155arbitrary character sequences opened by the bracket @code{(*} and closed by
156@code{*)}.  Comments may be nested. They do not affect the meaning of a
157program.
158
159@end enumerate
160
161@c 4. Declarations and scope rules
162@node Declarations and scope rules
163@chapter Declarations and scope rules
164
165Every identifier occurring in a program must be introduced by a declaration,
166unless it is a predeclared identifier. Declarations also specify certain
167permanent properties of an object, such as whether it is a constant, a type, a
168variable, or a procedure. The identifier is then used to refer to the
169associated object.
170
171The @dfn{scope} of an object @var{x} extends textually from the point of its
172declaration to the end of the block (module, procedure, or record) to which the
173declaration belongs and hence to which the object is @dfn{local}. It excludes
174the scopes of equally named objects which are declared in nested blocks. The
175scope rules are:
176
177@enumerate
178
179@item
180No identifier may denote more than one object within a given scope (i.e. no
181identifier may be declared twice in a block);
182
183@item
184An object may only be referenced within its scope;
185
186@item
187A type @var{T} of the form @code{POINTER TO} @var{T1} (@pxref{Pointer types})
188can be declared at a point where @var{T1} is still unknown. The declaration of
189@var{T1} must follow in the same block to which @var{T} is local;
190
191@item
192Identifiers denoting record fields (@pxref{Record types}) or type-bound
193procedures (@pxref{Type-bound procedures}) are valid in record designators only.
194
195@end enumerate
196
197An identifier declared in a module block may be followed by an export mark ("
198* " or " - ") in its declaration to indicate that it is exported.
199An identifier @var{x} exported by a module @var{M} may be used in other
200modules, if they import @var{M} (@pxref{Modules}). The identifier is then
201denoted as @var{M.x} in these modules and is called a @dfn{qualified
202identifier}.  Identifiers marked with " - " in their declaration are
203@dfn{read-only} in importing modules.
204
205@smallexample
206Qualident = [ident "."] ident.
207IdentDef  = ident [" * " | " - "].
208@end smallexample
209
210The following identifiers are predeclared; their meaning is defined in the
211indicated sections:
212
213@c It looks like there is not a good way to do this table in texinfo.
214@c Ideally, the section numbers should be cross-references, but texinfo
215@c references are too verbose to make this work. Only real alternative
216@c might be a two-column table with keyword and cross-reference.
217@smallexample
218ABS     (10.3)    LEN      (10.3)
219ASH     (10.3)    LONG     (10.3)
220BOOLEAN (6.1)     LONGINT  (6.1)
221CAP     (10.3)    LONGREAL (6.1)
222CHAR    (6.1)     MAX      (10.3)
223CHR     (10.3)    MIN      (10.3)
224COPY    (10.3)    NEW      (10.3)
225DEC     (10.3)    ODD      (10.3)
226ENTIER  (10.3)    ORD      (10.3)
227EXCL    (10.3)    REAL     (6.1)
228FALSE   (6.1)     SET      (6.1)
229HALT    (10.3)    SHORT    (10.3)
230INC     (10.3)    SHORTINT (6.1)
231INCL    (10.3)    SIZE     (10.3)
232INTEGER (6.1)     TRUE     (6.1)
233@end smallexample
234
235@c 5. Constant declarations
236@chapter Constant declarations
237
238A constant declaration associates an identifier with a constant value.
239
240@smallexample
241ConstantDeclaration  = IdentDef "=" ConstExpression.
242ConstExpression      = Expression.
243@end smallexample
244
245A constant expression is an expression that can be evaluated by a mere textual
246scan without actually executing the program. Its operands are constants
247(@pxref{Expressions}) or predeclared functions (@pxref{Predeclared procedures})
248that can be evaluated at compile time.  Examples of constant declarations are:
249
250@smallexample
251N = 100
252limit = 2*N - 1
253fullSet = @{MIN(SET) .. MAX(SET)@}
254@end smallexample
255
256@c 6. Type declarations
257@node Type declarations
258@chapter Type declarations
259
260A data type determines the set of values which variables of that type may
261assume, and the operators that are applicable. A type declaration associates an
262identifier with a type. In the case of structured types (arrays and records) it
263also defines the structure of variables of this type. A structured type cannot
264contain itself.
265
266@smallexample
267TypeDeclaration  = IdentDef "=" Type.
268Type             = Qualident | ArrayType | RecordType | PointerType | ProcedureType.
269@end smallexample
270
271Examples:
272@smallexample
273Table = ARRAY N OF REAL
274Tree = POINTER TO Node
275Node =  RECORD
276  key : INTEGER;
277  left, right: Tree
278END
279CenterTree = POINTER TO CenterNode
280CenterNode = RECORD (Node)
281  width: INTEGER;
282  subnode: Tree
283END
284Function = PROCEDURE(x: INTEGER): INTEGER
285@end smallexample
286
287@c 6.1 Basic types
288@node Basic types
289@section Basic types
290
291The basic types are denoted by predeclared identifiers. The associated
292operators are defined in @ref{Operators} and the predeclared function
293procedures in @ref{Predeclared procedures}.  The values of the given basic
294types are the following:
295
296@enumerate
297@item
298@code{BOOLEAN}  the truth values @code{TRUE} and @code{FALSE}
299
300@item
301@code{CHAR}  the characters of the extended ASCII set (@code{0X .. 0FFX})
302
303@item
304@code{SHORTINT}  the integers between @code{MIN(SHORTINT)} and @code{MAX(SHORTINT)}
305
306@item
307@code{INTEGER}  the integers between @code{MIN(INTEGER)} and @code{MAX(INTEGER)}
308
309@item
310@code{LONGINT}  the integers between @code{MIN(LONGINT)} and @code{MAX(LONGINT)}
311
312@item
313@code{REAL}  the real numbers between @code{MIN(REAL)} and @code{MAX(REAL)}
314
315@item
316@code{LONGREAL}  the real numbers between @code{MIN(LONGREAL)} and @code{MAX(LONGREAL)}
317
318@item
319@code{SET}  the sets of integers between @code{0} and @code{MAX(SET)}
320
321@end enumerate
322
323Types 3 to 5 are @dfn{integer types}, types 6 and 7 are @dfn{real types}, and
324together they are called @dfn{numeric types}. They form a hierarchy; the
325larger type @dfn{includes} (the values of) the smaller type:
326
327@smallexample
328LONGREAL  >=  REAL  >=  LONGINT  >=  INTEGER  >=  SHORTINT
329@end smallexample
330
331@c 6.2 Array types
332@section Array types
333
334An array is a structure consisting of a number of elements which are all of the
335same type, called the @dfn{element type}. The number of elements of an array
336is called its @dfn{length}. The elements of the array are designated by
337indices, which are integers between 0 and the length minus 1.
338
339@smallexample
340ArrayType  = ARRAY [Length @{"," Length@}] OF Type.
341Length     = ConstExpression.
342@end smallexample
343
344A type of the form
345
346@smallexample
347ARRAY L0, L1, ..., Ln OF T
348@end smallexample
349
350is understood as an abbreviation of
351
352@smallexample
353ARRAY L0 OF
354  ARRAY L1 OF
355  ...
356    ARRAY Ln OF T
357@end smallexample
358
359Arrays declared without length are called @dfn{open arrays}. They are
360restricted to pointer base types (@pxref{Pointer types}), element types of open
361array types, and formal parameter types (@pxref{Formal parameters}). Examples:
362
363@smallexample
364ARRAY 10, N OF INTEGER
365ARRAY OF CHAR
366@end smallexample
367
368@c 6.3 Record types
369@node Record types
370@section Record types
371
372A record type is a structure consisting of a fixed number of elements, called
373@dfn{fields}, with possibly different types. The record type declaration
374specifies the name and type of each field. The scope of the field identifiers
375extends from the point of their declaration to the end of the record type, but
376they are also visible within designators referring to elements of record
377variables (@pxref{Operands}). If a record type is exported, field identifiers
378that are to be visible outside the declaring module must be marked. They are
379called @dfn{public fields}; unmarked elements are called @dfn{private fields}.
380
381@smallexample
382RecordType  = RECORD ["("BaseType")"] FieldList @{";" FieldList@} END.
383BaseType    = Qualident.
384FieldList   = [IdentList ":" Type ].
385@end smallexample
386
387Record types are extensible, i.e. a record type can be declared as an extension
388of another record type. In the example
389
390@smallexample
391T0 = RECORD x: INTEGER END
392T1 = RECORD (T0) y: REAL END
393@end smallexample
394
395@var{T1} is a (direct) @dfn{extension} of @var{T0} and @var{T0} is the
396(direct) @dfn{base type} of @var{T1} (@pxref{Definition of terms}). An extended
397type @var{T1} consists of the fields of its base type and of the fields which
398are declared in @var{T1}. All identifiers declared in the extended record must
399be different from the identifiers declared in its base type record(s).
400
401Examples of record type declarations:
402
403@smallexample
404RECORD
405  day, month, year: INTEGER
406END
407
408RECORD
409  name, firstname: ARRAY 32 OF CHAR;
410  age: INTEGER;
411  salary: REAL
412END
413@end smallexample
414
415@c 6.4 Pointer types
416@node Pointer types
417@section Pointer types
418
419Variables of a pointer type @var{P} assume as values pointers to variables of
420some type @var{T}. @var{T} is called the pointer base type of @var{P} and
421must be a record or array type. Pointer types adopt the extension relation of
422their pointer base types: if a type @var{T1} is an extension of @var{T}, and
423@var{P1} is of type @code{POINTER TO} @var{T1}, then @var{P1} is also an
424extension of @var{P}.
425
426@smallexample
427PointerType = POINTER TO Type.
428@end smallexample
429
430If @var{p} is a variable of type @var{P} = @code{POINTER TO} @var{T}, a call of
431the predeclared procedure @code{NEW(@var{p})} (@pxref{Predeclared procedures})
432allocates a variable of type @var{T} in free storage. If @var{T} is a record
433type or an array type with fixed length, the allocation has to be done with
434@code{NEW(@var{p})}; if @var{T} is an n-dimensional open array type the
435allocation has to be done with @code{NEW(@var{p}, @var{e0}, @var{...},
436@var{en-1})} where @var{T} is allocated with lengths given by the expressions
437@var{e0, ..., en-1}. In either case a pointer to the allocated variable is
438assigned to @var{p}. @var{p} is of type @var{P}.  The @dfn{referenced} variable
439@code{@var{p}^} (pronounced as @emph{p-referenced}) is of type @var{T}. Any
440pointer variable may assume the value @code{NIL}, which points to no variable
441at all.
442
443@c 6.5 Procedure types
444@section Procedure types
445
446Variables of a procedure type @var{T} have a procedure (or @code{NIL}) as
447value. If a procedure @var{P} is assigned to a variable of type @var{T}, the
448formal parameter lists (@pxref{Formal parameters}) of @var{P} and @var{T} must
449@dfn{match} (@pxref{Definition of terms}). @var{P} must not be a predeclared or
450type-bound procedure nor may it be local to another procedure.
451
452@smallexample
453ProcedureType = PROCEDURE [FormalParameters].
454@end smallexample
455
456@c 7. Variable declarations
457@node Variable declarations
458@chapter Variable declarations
459
460Variable declarations introduce variables by defining an identifier and a data
461type for them.
462
463@smallexample
464VariableDeclaration = IdentList ":" Type.
465@end smallexample
466
467Record and pointer variables have both a @dfn{static type} (the type with
468which they are declared - simply called their type) and a @dfn{dynamic type}
469(the type of their value at run time). For pointers and variable parameters of
470record type the dynamic type may be an extension of their static type. The
471static type determines which fields of a record are accessible. The dynamic
472type is used to call type-bound procedures (@pxref{Type-bound procedures}).
473
474Examples of variable declarations (refer to examples in
475@ref{Type declarations}):
476
477@smallexample
478i, j, k: INTEGER
479x, y: REAL
480p, q: BOOLEAN
481s: SET
482F: Function
483a: ARRAY 100 OF REAL
484w: ARRAY 16 OF RECORD
485    name: ARRAY 32 OF CHAR;
486    count: INTEGER
487   END
488t, c: Tree
489@end smallexample
490
491@c 8. Expressions
492@node Expressions
493@chapter Expressions
494
495Expressions are constructs denoting rules of computation whereby constants and
496current values of variables are combined to compute other values by the
497application of operators and function procedures. Expressions consist of
498operands and operators. Parentheses may be used to express specific
499associations of operators and operands.
500
501@c 8.1 Operands
502@node Operands
503@section Operands
504
505With the exception of set constructors and literal constants (numbers,
506character constants, or strings), operands are denoted by @dfn{designators}. A
507designator consists of an identifier referring to a constant, variable, or
508procedure. This identifier may possibly be qualified by a module identifier
509(see @ref{Declarations and scope rules} and @ref{Modules}) and may be followed
510by @dfn{selectors} if the designated object is an element of a structure.
511
512@smallexample
513Designator      = Qualident @{"." ident | "[" ExpressionList "]" | "^" | "(" Qualident ")"@}.
514ExpressionList  = Expression @{"," Expression@}.
515@end smallexample
516
517If @var{a} designates an array, then @var{a[e]} denotes that element of a
518whose index is the current value of the expression @var{e}. The type of
519@var{e} must be an integer type. A designator of the form @var{a[e0, e1, ...,
520en]} stands for @var{a[e0][e1]...[en]}. If @var{r} designates a record, then
521@var{r.f} denotes the field @var{f} of @var{r} or the procedure @var{f} bound
522to the dynamic type of @var{r} (@pxref{Type-bound procedures}). If @var{p}
523designates a pointer, @var{p^} denotes the variable which is referenced by
524@var{p}. The designators @var{p^.f} and @var{p^[e]} may be abbreviated as
525@var{p.f} and @var{p[e]}, i.e. record and array selectors imply dereferencing.
526If @var{a} or @var{r} are read-only, then also @var{a[e]} and @var{r.f} are
527read-only.
528
529A @dfn{type guard} @var{v(T)} asserts that the dynamic type of @var{v} is
530@var{T} (or an extension of @var{T}), i.e. program execution is aborted, if the
531dynamic type of @var{v} is not @var{T} (or an extension of @var{T}).  Within
532the designator, @var{v} is then regarded as having the static type @var{T}.
533The guard is applicable, if
534
535@enumerate
536
537@item
538@var{v} is a variable parameter of record type or @var{v} is a pointer, and if
539
540@item
541@var{T} is an extension of the static type of @var{v}
542
543@end enumerate
544
545If the designated object is a constant or a variable, then the designator
546refers to its current value. If it is a procedure, the designator refers to
547that procedure unless it is followed by a (possibly empty) parameter list in
548which case it implies an activation of that procedure and stands for the value
549resulting from its execution. The actual parameters must correspond to the
550formal parameters as in proper procedure calls (@pxref{Formal parameters}).
551
552Examples of designators (refer to examples in @ref{Variable declarations}):
553
554@smallexample
555i                      (INTEGER)
556a[i]                   (REAL)
557w[3].name[i]           (CHAR)
558t.left.right           (Tree)
559t(CenterTree).subnode  (Tree)
560@end smallexample
561
562@c 8.2 Operators
563@node Operators
564@section Operators
565
566Four classes of operators with different precedences (binding strengths) are
567syntactically distinguished in expressions. The operator ~ has the highest
568precedence, followed by multiplication operators, addition operators, and
569relations. Operators of the same precedence associate from left to right. For
570example, x-y-z stands for (x-y)-z.
571
572@smallexample
573Expression        = SimpleExpression [Relation SimpleExpression].
574SimpleExpression  = ["+" | "-"] Term @{AddOperator Term@}.
575Term              = Factor @{MulOperator Factor@}.
576Factor            = Designator [ActualParameters] |
577                    number | character | string | NIL | Set |
578                    "(" Expression ")" | "~" Factor.
579Set               = "@{" [Element @{"," Element@}] "@}".
580Element           = Expression [".." Expression].
581ActualParameters  = "(" [ExpressionList] ")".
582Relation          = "=" | "#" | "<" | "<=" | ">" | ">=" | IN | IS.
583AddOperator       = "+" | "-" | OR.
584MulOperator       = "*" | "/" | DIV | MOD | "&".
585@end smallexample
586
587The available operators are listed in the following tables. Some operators are
588applicable to operands of various types, denoting different operations. In
589these cases, the actual operation is identified by the type of the operands.
590The operands must be @dfn{expression compatible} with respect to the operator
591(@pxref{Definition of terms}).
592
593@c 8.2.1 Logical operators
594@subsection Logical operators
595
596@smallexample
597OR  logical disjunction   p OR q   "if p then TRUE, else q"
598&   logical conjunction   p & q    "if p then q, else FALSE"
599~   negation              ~ p      "not p"
600@end smallexample
601
602These operators apply to @code{BOOLEAN} operands and yield a @code{BOOLEAN}
603result.
604
605@c 8.2.2 Arithmetic operators
606@subsection Arithmetic operators
607
608@table @asis
609@item +
610sum
611@item -
612difference
613@item *
614product
615@item /
616real quotient
617@item DIV
618integer quotient
619@item MOD
620modulus
621@end table
622
623The operators @code{+}, @code{-}, @code{*}, and @code{/} apply to operands of
624numeric types. The type of the result is the type of that operand which
625includes the type of the other operand, except for division (@code{/}), where
626the result is the smallest real type which includes both operand types. When
627used as monadic operators, @code{-} denotes sign inversion and @code{+} denotes
628the identity operation. The operators @code{DIV} and @code{MOD} apply to
629integer operands only. They are related by the following formulas defined for
630any @var{x} and positive divisors @var{y}:
631
632@smallexample
633x = (x DIV y) * y + (x MOD y)
6340 <= (x MOD y) < y
635@end smallexample
636
637Examples:
638@smallexample
639x  y  x DIV y  x MOD y
6405  3  1  2
641-5  3  -2  1
642@end smallexample
643
644@c 8.2.3 Set Operators
645@subsection Set Operators
646
647@table @asis
648@item +
649union
650@item -
651difference (x - y = x * (-y))
652@item *
653intersection
654@item /
655symmetric set difference (x / y = (x-y) + (y-x))
656@end table
657
658Set operators apply to operands of type @code{SET} and yield a result of type
659@code{SET}. The monadic minus sign denotes the complement of @var{x}, i.e.
660@code{-@var{x}} denotes the set of integers between 0 and @code{MAX(SET)} which
661are not elements of @var{x}. Set operators are not associative @code{((a+b)-c #
662a+(b-c))}.
663
664A set constructor defines the value of a set by listing its elements between
665curly brackets. The elements must be integers in the range 0..@code{MAX(SET)}.
666A range @var{a..b} denotes all integers in the interval @var{[a, b]}.
667
668@c 8.2.4 Relations
669@subsection Relations
670
671@table @asis
672@item =
673equal
674@item #
675unequal
676@item <
677less
678@item <=
679less or equal
680@item >
681greater
682@item >=
683greater or equal
684@item IN
685set membership
686@item IS
687type test
688@end table
689
690Relations yield a @code{BOOLEAN} result. The relations @code{=}, @code{#},
691@code{<}, @code{<=}, @code{>}, and @code{>=} apply to the numeric types,
692@code{CHAR}, strings, and character arrays containing 0X as a terminator. The
693relations @code{=} and @code{#} also apply to @code{BOOLEAN} and @code{SET}, as
694well as to pointer and procedure types (including the value @code{NIL}).
695@code{@var{x} IN @var{s}} stands for "@var{x} is an element of @var{s}".
696@var{x} must be of an integer type, and @var{s} of type @code{SET}.
697@code{@var{v} IS @var{T}} stands for "the dynamic type of @var{v} is @var{T}
698(or an extension of @var{T})" and is called a @dfn{type test}. It is applicable
699if
700
701@enumerate
702
703@item
704@var{v} is a variable parameter of record type or @var{v} is a pointer, and if
705
706@item
707@var{T} is an extension of the static type of @var{v}
708
709@end enumerate
710
711Examples of expressions (refer to examples in @ref{Variable declarations}):
712@smallexample
7131991                 INTEGER
714i DIV 3              INTEGER
715~p OR q              BOOLEAN
716(i+j) * (i-j)        INTEGER
717s - @{8, 9, 13@}       SET
718i + x                REAL
719a[i+j] * a[i-j]      REAL
720(0<=i) & (i<100)     BOOLEAN
721t.key = 0            BOOLEAN
722k IN @{i..j-1@}        BOOLEAN
723w[i].name <= "John"  BOOLEAN
724t IS CenterTree      BOOLEAN
725@end smallexample
726
727@c 9. Statements
728@node Statements
729@chapter Statements
730
731Statements denote actions. There are elementary and structured statements.
732Elementary statements are not composed of any parts that are themselves
733statements. They are the assignment, the procedure call, the return, and the
734exit statement. Structured statements are composed of parts that are
735themselves statements. They are used to express sequencing and conditional,
736selective, and repetitive execution. A statement may also be empty, in which
737case it denotes no action. The empty statement is included in order to relax
738punctuation rules in statement sequences.
739
740@smallexample
741Statement =
742  [ Assignment | ProcedureCall | IfStatement | CaseStatement | WhileStatement |
743    RepeatStatement | ForStatement | LoopStatement | WithStatement |
744    EXIT | RETURN [Expression] ].
745@end smallexample
746
747@section Assignments
748
749Assignments replace the current value of a variable by a new value specified
750by an expression. The expression must be @dfn{assignment compatible} with the
751variable (@pxref{Definition of terms}). The assignment operator is written as
752"@code{:=}" and pronounced as @emph{becomes}.
753
754@smallexample
755Assignment = Designator ":=" Expression.
756@end smallexample
757
758If an expression @var{e} of type @var{Te} is assigned to a variable @var{v} of
759type @var{Tv}, the following happens:
760
761@enumerate
762
763@item
764if @var{Tv} and @var{Te} are record types, only those fields of @var{Te} are
765assigned which also belong to @var{Tv} (@dfn{projection}); the dynamic type
766of @var{v}  must be the same as the static type of @var{v} and  is not changed
767by the assignment;
768
769@item
770if @var{Tv} and @var{Te} are pointer types, the dynamic type of @var{v}
771becomes the dynamic type of @var{e};
772
773@item
774if @var{Tv} is @code{ARRAY @var{n} OF CHAR} and @var{e} is a string of length
775@var{m<n}, @var{v[i]} becomes @var{ei} for @var{i} = 0..@var{m-1} and
776@var{v[m]} becomes @code{0X}.
777
778@end enumerate
779
780Examples of assignments (refer to examples in @ref{Variable declarations}):
781
782@smallexample
783i := 0
784p := i = j
785x := i + 1
786k := log2(i+j)
787F := log2    (* @xref{Formal parameters} *)
788s := @{2, 3, 5, 7, 11, 13@}
789a[i] := (x+y) * (x-y)
790t.key := i
791w[i+1].name := "John"
792t := c
793@end smallexample
794
795@c 9.2 Procedure calls
796@section Procedure calls
797
798A procedure call activates a procedure. It may contain a list of actual
799parameters which replace the corresponding formal parameters defined in the
800procedure declaration (@pxref{Procedure declarations}). The correspondence is
801established by the positions of the parameters in the actual and formal
802parameter lists. There are two kinds of parameters: @dfn{variable} and
803@dfn{value} parameters.
804
805If a formal parameter is a variable parameter, the corresponding actual
806parameter must be a designator denoting a variable. If it denotes an element
807of a structured variable, the component selectors are evaluated when the
808formal/actual parameter substitution takes place, i.e. before the execution of
809the procedure. If a formal parameter is a value parameter, the corresponding
810actual parameter must be an expression. This expression is evaluated before
811the procedure activation, and the resulting value is assigned to the formal
812parameter (@pxref{Formal parameters}).
813
814@smallexample
815ProcedureCall = Designator [ActualParameters].
816@end smallexample
817
818Examples:
819@smallexample
820WriteInt(i*2+1)  (* @xref{Formal parameters} *)
821INC(w[k].count)
822t.Insert("John")  (* @xref{Modules} *)
823@end smallexample
824
825@c 9.3 Statement sequences
826@section Statement sequences
827
828Statement sequences denote the sequence of actions specified by the component
829statements which are separated by semicolons.
830
831@smallexample
832StatementSequence = Statement @{";" Statement@}.
833@end smallexample
834
835@c 9.4 If statements
836@section If statements
837
838@smallexample
839IfStatement =
840  IF Expression THEN StatementSequence
841  @{ELSIF Expression THEN StatementSequence@}
842  [ELSE StatementSequence]
843  END.
844@end smallexample
845
846If statements specify the conditional execution of guarded statement
847sequences. The Boolean expression preceding a statement sequence is called its
848@dfn{guard}. The guards are evaluated in sequence of occurrence, until one
849evaluates to @code{TRUE}, whereafter its associated statement sequence is
850executed.  If no guard is satisfied, the statement sequence following the
851symbol @code{ELSE} is executed, if there is one.
852
853Example:
854@smallexample
855IF (ch >= "A") & (ch <= "Z") THEN ReadIdentifier
856ELSIF (ch >= "0") & (ch <= "9") THEN ReadNumber
857ELSIF (ch = " ' ") OR (ch = ' " ') THEN ReadString
858ELSE SpecialCharacter
859END
860@end smallexample
861
862@c 9.5 Case statements
863@section Case statements
864
865Case statements specify the selection and execution of a statement sequence
866according to the value of an expression. First the case expression is
867evaluated, then that statement sequence is executed whose case label list
868contains the obtained value. The case expression must either be of an
869@dfn{integer type} that @dfn{includes} the types of all case labels, or both
870the case expression and the case labels must be of type @code{CHAR}. Case
871labels are constants, and no value must occur more than once. If the value of
872the expression does not occur as a label of any case, the statement sequence
873following the symbol @code{ELSE} is selected, if there is one, otherwise the
874program is aborted.
875
876@smallexample
877CaseStatement   = CASE Expression OF Case @{"|" Case@} [ELSE StatementSequence] END.
878Case            = [CaseLabelList ":" StatementSequence].
879CaseLabelList   = CaseLabels @{"," CaseLabels@}.
880CaseLabels      = ConstExpression [".." ConstExpression].
881@end smallexample
882
883Example:
884@smallexample
885CASE ch OF
886  "A" .. "Z": ReadIdentifier
887|  "0" .. "9": ReadNumber
888|  " ' ", ' " ': ReadString
889ELSE SpecialCharacter
890END
891@end smallexample
892
893@c 9.6 While statements
894@section While statements
895
896While statements specify the repeated execution of a statement sequence while
897the Boolean expression (its @dfn{guard}) yields @code{TRUE}. The guard is
898checked before every execution of the statement sequence.
899
900@smallexample
901WhileStatement = WHILE Expression DO StatementSequence END.
902@end smallexample
903
904Examples:
905@smallexample
906WHILE i > 0 DO i := i DIV 2; k := k + 1 END
907WHILE (t # NIL) & (t.key # i) DO t := t.left END
908@end smallexample
909
910@c 9.7 Repeat statements
911@section Repeat statements
912
913A repeat statement specifies the repeated execution of a statement sequence
914until a condition specified by a Boolean expression is satisfied. The
915statement sequence is executed at least once.
916
917@smallexample
918RepeatStatement = REPEAT StatementSequence UNTIL Expression.
919@end smallexample
920
921@c 9.8 For statements
922@section For statements
923
924A for statement specifies the repeated execution of a statement sequence while
925a progression of values is assigned to an integer variable called the
926@dfn{control variable} of the for statement.
927
928@smallexample
929ForStatement = FOR ident ":=" Expression TO Expression [BY ConstExpression] DO StatementSequence END.
930@end smallexample
931
932The statement
933@smallexample
934FOR v := beg TO end BY step DO statements END
935@end smallexample
936is equivalent to
937@smallexample
938temp := end; v := beg;
939IF step > 0 THEN
940  WHILE v <= temp DO statements; v := v + step END
941ELSE
942  WHILE v >= temp DO statements; v := v + step END
943END
944@end smallexample
945@var{temp} has the same type as @var{v}. @var{step} must be a nonzero constant
946expression. If @var{step} is not specified, it is assumed to be 1.
947
948Examples:
949@smallexample
950FOR i := 0 TO 79 DO k := k + a[i] END
951FOR i := 79 TO 1 BY -1 DO a[i] := a[i-1] END
952@end smallexample
953
954@c 9.9 Loop statements
955@section Loop statements
956
957A loop statement specifies the repeated execution of a statement sequence. It
958is terminated upon execution of an exit statement within that sequence
959(@pxref{Return and exit statements}).
960
961@smallexample
962LoopStatement = LOOP StatementSequence END.
963@end smallexample
964
965Example:
966@smallexample
967LOOP
968  ReadInt(i);
969  IF i < 0 THEN EXIT END;
970  WriteInt(i)
971END
972@end smallexample
973
974Loop statements are useful to express repetitions with several exit points or
975cases where the exit condition is in the middle of the repeated statement
976sequence.
977
978@c 9.10 Return and exit statements
979@node Return and exit statements
980@section Return and exit statements
981
982A return statement indicates the termination of a procedure. It is denoted by
983the symbol @code{RETURN}, followed by an expression if the procedure is a
984function procedure. The type of the expression must be @dfn{assignment
985compatible} (@pxref{Definition of terms}) with the result type specified in the
986procedure heading (@pxref{Procedure declarations}).
987
988Function procedures must be left via a return statement indicating the result
989value. In proper procedures, a return statement is implied by the end of the
990procedure body. Any explicit return statement therefore appears as an
991additional (probably exceptional) termination point.
992
993An exit statement is denoted by the symbol @code{EXIT}. It specifies
994termination of the enclosing loop statement and continuation with the statement
995following that loop statement. Exit statements are contextually, although not
996syntactically associated with the loop statement which contains them.
997
998@c 9.11 With statements
999@section With statements
1000
1001With statements execute a statement sequence depending on the result of a type
1002test and apply a type guard to every occurrence of the tested variable within
1003this statement sequence.
1004
1005@smallexample
1006WithStatement = WITH Guard DO StatementSequence @{"|" Guard DO StatementSequence@}
1007  [ELSE StatementSequence] END.
1008Guard  = Qualident ":" Qualident.
1009@end smallexample
1010
1011If @var{v} is a variable parameter of record type or a pointer variable, and
1012if it is of a static type @var{T0}, the statement
1013
1014@smallexample
1015WITH v: T1 DO S1 | v: T2 DO S2 ELSE S3 END
1016@end smallexample
1017
1018has the following meaning: if the dynamic type of @var{v} is @var{T1}, then
1019the statement sequence @var{S1} is executed where @var{v} is regarded as if it
1020had the static type @var{T1}; else if the dynamic type of @var{v} is @var{T2},
1021then @var{S2} is executed where @var{v} is regarded as if it had the static
1022type @var{T2}; else @var{S3} is executed. @var{T1} and @var{T2} must be
1023extensions of @var{T0}. If no type test is satisfied and if an else clause is
1024missing the program is aborted.
1025
1026Example:
1027@smallexample
1028WITH t: CenterTree DO i := t.width; c := t.subnode END
1029@end smallexample
1030
1031@c 10. Procedure declarations
1032@node Procedure declarations
1033@chapter Procedure declarations
1034
1035A procedure declaration consists of a @dfn{procedure heading} and a
1036@dfn{procedure body}.  The heading specifies the procedure identifier and the
1037@dfn{formal parameters}. For type-bound procedures it also specifies the
1038receiver parameter. The body contains declarations and statements. The
1039procedure identifier is repeated at the end of the procedure declaration.
1040
1041There are two kinds of procedures: @dfn{proper procedures} and @dfn{function
1042procedures}.  The latter are activated by a function designator as a
1043constituent of an expression and yield a result that is an operand of the
1044expression. Proper procedures are activated by a procedure call. A procedure is
1045a function procedure if its formal parameters specify a result type. The body
1046of a function procedure must contain a return statement which defines its
1047result.
1048
1049All constants, variables, types, and procedures declared within a procedure
1050body are @dfn{local} to the procedure. Since procedures may be declared as
1051local objects too, procedure declarations may be nested. The call of a
1052procedure within its declaration implies recursive activation.
1053
1054Objects declared in the environment of the procedure are also visible in those
1055parts of the procedure in which they are not concealed by a locally declared
1056object with the same name.
1057
1058@smallexample
1059ProcedureDeclaration  = ProcedureHeading ";" ProcedureBody ident.
1060ProcedureHeading      = PROCEDURE [Receiver] IdentDef [FormalParameters].
1061ProcedureBody         = DeclarationSequence [BEGIN StatementSequence] END.
1062DeclarationSequence   = @{CONST @{ConstantDeclaration ";"@}
1063  | TYPE @{TypeDeclaration ";"@}
1064  | VAR @{VariableDeclaration ";"@} @}
1065  @{ProcedureDeclaration ";" | ForwardDeclaration ";"@}.
1066ForwardDeclaration    = PROCEDURE " ^ " [Receiver] IdentDef [FormalParameters].
1067@end smallexample
1068
1069If a procedure declaration specifies a @dfn{receiver} parameter, the procedure
1070is considered to be bound to a type (@pxref{Type-bound procedures}). A
1071@dfn{forward declaration} serves to allow forward references to a procedure
1072whose actual declaration appears later in the text. The formal parameter lists
1073of the forward declaration and the actual declaration must @dfn{match}
1074(@pxref{Definition of terms}).
1075
1076@c 10.1 Formal parameters
1077@node Formal parameters
1078@section Formal parameters
1079
1080Formal parameters are identifiers declared in the formal parameter list of a
1081procedure. They correspond to actual parameters specified in the procedure
1082call. The correspondence between formal and actual parameters is established
1083when the procedure is called. There are two kinds of parameters, @dfn{value}
1084and @var{variable parameters}, indicated in the formal parameter list by the
1085absence or presence of the keyword @var{VAR}. Value parameters are local
1086variables to which the value of the corresponding actual parameter is assigned
1087as an initial value.  Variable parameters correspond to actual parameters that
1088are variables, and they stand for these variables. The scope of a formal
1089parameter extends from its declaration to the end of the procedure block in
1090which it is declared.  A function procedure without parameters must have an
1091empty parameter list. It must be called by a function designator whose actual
1092parameter list is empty too. The result type of a procedure can be neither a
1093record nor an array.
1094
1095@smallexample
1096FormalParameters  = "(" [FPSection @{";" FPSection@}] ")" [":" Qualident].
1097FPSection   = [VAR] ident @{"," ident@} ":" Type.
1098@end smallexample
1099
1100Let @var{Tf} be the type of a formal parameter @var{f} (not an open array) and
1101@var{Ta} the type of the corresponding actual parameter @var{a}. For variable
1102parameters, @var{Ta} must be the same as @var{Tf}, or @var{Tf} must be a record
1103type and @var{Ta} an extension of @var{Tf}. For value parameters, a must be
1104@dfn{assignment compatible} with @var{f} (@pxref{Definition of terms}).
1105
1106If @var{Tf} is an open array, then a must be @dfn{array compatible} with
1107@var{f} (@pxref{Definition of terms}). The lengths of @var{f} are taken from
1108@var{a}.
1109
1110Examples of procedure declarations:
1111
1112@smallexample
1113PROCEDURE ReadInt(VAR x: INTEGER);
1114  VAR i: INTEGER; ch: CHAR;
1115BEGIN i := 0; Read(ch);
1116  WHILE ("0" <= ch) & (ch <= "9") DO
1117    i := 10*i + (ORD(ch)-ORD("0")); Read(ch)
1118  END;
1119  x := i
1120END ReadInt
1121
1122PROCEDURE WriteInt(x: INTEGER); (*0 <= x <100000*)
1123  VAR i: INTEGER; buf: ARRAY 5 OF INTEGER;
1124BEGIN i := 0;
1125  REPEAT buf[i] := x MOD 10; x := x DIV 10; INC(i) UNTIL x = 0;
1126  REPEAT DEC(i); Write(CHR(buf[i] + ORD("0"))) UNTIL i = 0
1127END WriteInt
1128
1129PROCEDURE WriteString(s: ARRAY OF CHAR);
1130  VAR i: INTEGER;
1131BEGIN i := 0;
1132  WHILE (i < LEN(s)) & (s[i] # 0X) DO Write(s[i]); INC(i) END
1133END WriteString;
1134
1135
1136PROCEDURE log2(x: INTEGER): INTEGER;
1137  VAR y: INTEGER; (*assume x>0*)
1138BEGIN
1139  y := 0; WHILE x > 1 DO x := x DIV 2; INC(y) END;
1140  RETURN y
1141END log2
1142@end smallexample
1143
1144@c 10.2 Type-bound procedures
1145@node Type-bound procedures
1146@section Type-bound procedures
1147
1148Globally declared procedures may be associated with a record type declared in
1149the same module. The procedures are said to be @dfn{bound} to the record type.
1150The binding is expressed by the type of the @dfn{receiver} in the heading of a
1151procedure declaration.  The receiver may be either a variable parameter of
1152record type @var{T} or a value parameter of type @code{POINTER TO @var{T}}
1153(where @var{T} is a record type). The procedure is bound to the type @var{T}
1154and is considered local to it.
1155
1156@smallexample
1157ProcedureHeading  = PROCEDURE [Receiver] IdentDef [FormalParameters].
1158Receiver   = "(" [VAR] ident ":" ident ")".
1159@end smallexample
1160
1161If a procedure @var{P} is bound to a type @var{T0}, it is implicitly also bound
1162to any type @var{T1} which is an extension of @var{T0}. However, a procedure
1163@var{P'} (with the same name as @var{P}) may be explicitly bound to @var{T1} in
1164which case it overrides the binding of @var{P}. @var{P'} is considered a
1165@dfn{redefinition} of @var{P} for @var{T1}. The formal parameters of @var{P}
1166and @var{P'} must @dfn{match} (@pxref{Definition of terms}). If @var{P} and
1167@var{T1} are exported (@pxref{Declarations and scope rules}) @var{P'} must be
1168exported too.
1169
1170If @var{v} is a designator and @var{P} is a type-bound procedure, then
1171@var{v.P} denotes that procedure @var{P} which is bound to the dynamic type of
1172@var{v}. Note, that this may be a different procedure than the one bound to the
1173static type of @var{v}. @var{v} is passed to @var{P}'s receiver according to
1174the parameter passing rules specified in @ref{Formal parameters}.
1175
1176If @var{r} is a receiver parameter declared with type @var{T}, @var{r.P^}
1177denotes the (redefined) procedure @var{P} bound to the base type of @var{T}.
1178
1179In a forward declaration of a type-bound procedure the receiver parameter must
1180be of the @dfn{same} type as in the actual procedure declaration. The formal
1181parameter lists of both declarations must @dfn{match}
1182(@pxref{Definition of terms}).
1183
1184Examples:
1185
1186@smallexample
1187PROCEDURE (t: Tree) Insert (node: Tree);
1188  VAR p, father: Tree;
1189BEGIN p := t;
1190  REPEAT father := p;
1191    IF node.key = p.key THEN RETURN END;
1192    IF node.key < p.key THEN p := p.left ELSE p := p.right END
1193  UNTIL p = NIL;
1194  IF node.key < father.key THEN father.left := node ELSE father.right := node END;
1195  node.left := NIL; node.right := NIL
1196END Insert;
1197
1198PROCEDURE (t: CenterTree) Insert (node: Tree);  (*redefinition*)
1199BEGIN
1200  WriteInt(node(CenterTree).width);
1201  t.Insert^ (node)  (* calls the Insert procedure bound to Tree *)
1202END Insert;
1203@end smallexample
1204
1205@c 10.3 Predeclared procedures
1206@node Predeclared procedures
1207@section Predeclared procedures
1208
1209The following table lists the predeclared procedures. Some are generic
1210procedures, i.e. they apply to several types of operands. @var{v} stands for a
1211variable, @var{x} and @var{n} for expressions, and @var{T} for a type.
1212
1213@smallexample
1214Function procedures
1215Name       Argument type         Result type     Function
1216----       -------------         -----------     --------
1217ABS(x)     numeric type          type of x       absolute value
1218ASH(x, n)  x, n: integer type    LONGINT         arithmetic shift (x * 2n)
1219CAP(x)     CHAR                  CHAR            x is letter: corresponding capital letter
1220CHR(x)     integer type          CHAR            character with ordinal number x
1221ENTIER(x)  real type             LONGINT         largest integer not greater than x
1222LEN(v, n)  v: array;             LONGINT         length of v in dimension n
1223           n: integer const.                     (first dimension = 0)
1224LEN(v)     v: array              LONGINT         equivalent to LEN(v, 0)
1225LONG(x)    SHORTINT              INTEGER         identity
1226           INTEGER               LONGINT
1227           REAL                  LONGREAL
1228MAX(T)     T = basic type        T               maximum value of type T
1229           T = SET               INTEGER         maximum element of a set
1230MIN(T)     T = basic type        T               minimum value of type T
1231           T = SET               INTEGER         0
1232ODD(x)     integer type          BOOLEAN         x MOD 2 = 1
1233ORD(x)     CHAR                  INTEGER         ordinal number of x
1234SHORT(x)   LONGINT               INTEGER         identity
1235           INTEGER               SHORTINT        identity
1236           LONGREAL              REAL            identity (truncation possible)
1237SIZE(T)    any type              integer type    number of bytes required by T
1238@end smallexample
1239
1240@smallexample
1241Proper procedures
1242Name           Argument types                    Function
1243----           --------------                    --------
1244ASSERT(x)      x: Boolean expression             terminate program execution if not x
1245ASSERT(x, n)   x: Boolean expression;            terminate program execution if not x
1246               n: integer constant
1247COPY(x, v)     x: character array, string;
1248               v: character array                v := x
1249DEC(v)         integer type                      v := v - 1
1250DEC(v, n)      v, n: integer type                v := v - n
1251EXCL(v, x)     v: SET; x: integer type           v := v - @{x@}
1252HALT(n)        integer constant                  terminate program execution
1253INC(v)         integer type                      v := v + 1
1254INC(v, n)      v, n: integer type                v := v + n
1255INCL(v, x)     v: SET; x: integer type           v := v + @{x@}
1256NEW(v)         pointer to record or fixed array  allocate v ^
1257NEW(v, x0, ..., xn)
1258               v: pointer to open array;
1259               xi: integer type                  allocate v ^ with lengths x0.. xn
1260@end smallexample
1261
1262@code{COPY} allows the assignment of a string or a character array containing a
1263terminating @code{0X} to another character array. If necessary, the assigned
1264value is truncated to the target length minus one. The target will always
1265contain @code{0X} as a terminator. In @code{ASSERT(@var{x}, @var{n})} and
1266@code{HALT(@var{n})}, the interpretation of @var{n} is left to the underlying
1267system implementation.
1268
1269@c 11. Modules
1270@node Modules
1271@chapter Modules
1272
1273A module is a collection of declarations of constants, types, variables, and
1274procedures, together with a sequence of statements for the purpose of assigning
1275initial values to the variables. A module constitutes a text that is compilable
1276as a unit.
1277
1278@smallexample
1279Module   = MODULE ident ";" [ImportList] DeclarationSequence
1280      [BEGIN StatementSequence] END ident ".".
1281ImportList   = IMPORT Import @{"," Import@} ";".
1282Import   = [ident ":="] ident.
1283@end smallexample
1284
1285The import list specifies the names of the imported modules. If a module
1286@var{A} is imported by a module @var{M} and @var{A} exports an identifier
1287@var{x}, then @var{x} is referred to as @var{A.x} within @var{M}. If @var{A} is
1288imported as @var{B := A}, the object @var{x} must be referenced as @var{B.x}.
1289This allows short alias names in qualified identifiers. A module must not
1290import itself. Identifiers that are to be exported (i.e. that are to be visible
1291in client modules) must be marked by an export mark in their declaration
1292(@pxref{Declarations and scope rules}).  The statement sequence following the
1293symbol @code{BEGIN} is executed when the module is added to a system (loaded),
1294which is done after the imported modules have been loaded. It follows that
1295cyclic import of modules is illegal.  Individual (parameterless and exported)
1296procedures can be activated from the system, and these procedures serve as
1297@dfn{commands} (@pxref{Commands}).
1298
1299@smallexample
1300MODULE Trees;   (* exports: Tree, Node, Insert, Search, Write, Init *)
1301  IMPORT Texts, Oberon;  (* exports read-only: Node.name *)
1302
1303  TYPE
1304    Tree* = POINTER TO Node;
1305    Node* = RECORD
1306      name-: POINTER TO ARRAY OF CHAR;
1307      left, right: Tree
1308    END;
1309
1310  VAR w: Texts.Writer;
1311
1312  PROCEDURE (t: Tree) Insert* (name: ARRAY OF CHAR);
1313    VAR p, father: Tree;
1314  BEGIN p := t;
1315    REPEAT father := p;
1316      IF name = p.name^ THEN RETURN END;
1317      IF name < p.name^ THEN p := p.left ELSE p := p.right END
1318    UNTIL p = NIL;
1319    NEW(p); p.left := NIL; p.right := NIL; NEW(p.name, LEN(name)+1); COPY(name, p.name^);
1320    IF name < father.name^ THEN father.left := p ELSE father.right := p END
1321  END Insert;
1322
1323  PROCEDURE (t: Tree) Search* (name: ARRAY OF CHAR): Tree;
1324    VAR p: Tree;
1325  BEGIN p := t;
1326    WHILE (p # NIL) & (name # p.name^) DO
1327      IF name < p.name^ THEN p := p.left ELSE p := p.right END
1328    END;
1329    RETURN p
1330  END Search;
1331  PROCEDURE (t: Tree) Write*;
1332  BEGIN
1333    IF t.left # NIL THEN t.left.Write END;
1334    Texts.WriteString(w, t.name^); Texts.WriteLn(w); Texts.Append(Oberon.Log, w.buf);
1335    IF t.right # NIL THEN t.right.Write END
1336  END Write;
1337
1338  PROCEDURE Init* (t: Tree);
1339  BEGIN NEW(t.name, 1); t.name[0] := 0X; t.left := NIL; t.right := NIL
1340  END Init;
1341
1342BEGIN Texts.OpenWriter(w)
1343END Trees.
1344@end smallexample
1345
1346@c Appendix A: Definition of terms
1347@c Consider replacing @heading with @appendixsec. That would allow definitions to
1348@c be indexed, and references to definitions to be more precisely targetted.
1349@page
1350@node Definition of terms
1351@appendix Definition of terms
1352
1353@heading Integer types
1354
1355  @code{SHORTINT}, @code{INTEGER}, @code{LONGINT}
1356
1357@heading Real types
1358
1359  @code{REAL}, @code{LONGREAL}
1360
1361@heading Numeric types
1362
1363  integer types, real types
1364
1365@heading Same types
1366
1367Two variables @var{a} and @var{b} with types @var{Ta} and @var{Tb} are of the
1368@dfn{same} type if
1369
1370@enumerate
1371@item
1372@var{Ta} and @var{Tb} are both denoted by the same type identifier, or
1373
1374@item
1375@var{Ta} is declared to equal @var{Tb} in a type declaration of the form
1376@var{Ta} = Tb, or
1377
1378@item
1379@var{a} and @var{b} appear in the same identifier list in a variable, record
1380field, or formal parameter declaration and are not open arrays.
1381@end enumerate
1382
1383@heading Equal types
1384
1385Two types @var{Ta} and @var{Tb} are @dfn{equal} if
1386@enumerate
1387@item
1388@var{Ta} and @var{Tb} are the @dfn{same} type,  or
1389@item
1390@var{Ta} and @var{Tb} are open array types with @dfn{equal} element types, or
1391@item
1392@var{Ta} and @var{Tb} are procedure types whose formal parameter lists
1393@dfn{match}.
1394@end enumerate
1395
1396@heading Type inclusion
1397
1398Numeric types @dfn{include} (the values of) smaller numeric types according to
1399the following hierarchy:
1400
1401  @code{LONGREAL} >= @code{REAL} >= @code{LONGINT} >= @code{INTEGER} >= @code{SHORTINT}
1402
1403@heading Type extension (base type)
1404
1405Given a type declaration @var{Tb} = @code{RECORD (@var{Ta}) ... END}, @var{Tb}
1406is a @dfn{direct extension} of @var{Ta}, and @var{Ta} is a @dfn{direct base
1407type} of @var{Tb}. A type @var{Tb} is an @dfn{extension} of a type @var{Ta}
1408(@var{Ta} is a @dfn{base type} of @var{Tb}) if
1409
1410@enumerate
1411@item
1412@var{Ta} and @var{Tb} are the @dfn{same} types, or
1413@item
1414@var{Tb} is a @dfn{direct extension} of an @dfn{extension} of @var{Ta}
1415@end enumerate
1416If @var{Pa} = @code{POINTER TO @var{Ta}} and @var{Pb} = @code{POINTER TO
1417@var{Tb}}, @var{Pb} is an @dfn{extension} of @var{Pa} (@var{Pa} is a @dfn{base
1418type} of @var{Pb}) if @var{Tb} is an @dfn{extension} of @var{Ta}.
1419
1420@heading Assignment compatible
1421
1422An expression @var{e} of type @var{Te} is assignment compatible with a variable
1423@var{v} of type @var{Tv} if one of the following conditions hold:
1424@enumerate
1425@item
1426@var{Te} and @var{Tv} are the @dfn{same} type;
1427@item
1428@var{Te} and @var{Tv} are numeric types and @var{Tv} @dfn{includes} @var{Te};
1429@item
1430@var{Te} and @var{Tv} are record types and @var{Te} is an @dfn{extension} of
1431@var{Tv} and the dynamic type of @var{v} is @var{Tv} ;
1432@item
1433@var{Te} and @var{Tv} are pointer types and @var{Te} is an @dfn{extension} of
1434@var{Tv};
1435@item
1436@var{Tv} is a pointer or a procedure type and @var{e} is @code{NIL};
1437@item
1438@var{Tv} is @code{ARRAY @var{n} OF CHAR}, @var{e} is a string constant with
1439@var{m} characters, and @var{m < n};
1440@item
1441@var{Tv} is a procedure type and @var{e} is the name of a procedure whose
1442formal parameters @dfn{match} those of @var{Tv}.
1443@end enumerate
1444
1445@heading Array compatible
1446An actual parameter @var{a} of type @var{Ta} is @dfn{array compatible} with a
1447formal parameter @var{f} of type @var{Tf} if
1448@enumerate
1449@item
1450@var{Tf} and @var{Ta} are the @dfn{same} type, or
1451@item
1452@var{Tf} is an open array, @var{Ta} is any array, and their element types are
1453@dfn{array compatible}, or
1454@item
1455@var{f} is a value parameter of type @code{ARRAY OF CHAR} and @var{a} is a
1456string.
1457@end enumerate
1458
1459@heading Expression compatible
1460
1461For a given operator, the types of its operands are @dfn{expression compatible}
1462if they conform to the following table (which shows also the result type of the
1463expression). Character arrays that are to be compared must contain 0X as a
1464terminator. Type @var{T1} must be an extension of type @var{T0}:
1465
1466@smallexample
1467operator   first operand  second operand   result type
1468--------   -------------  --------------   -----------
1469+ - *      numeric        numeric          smallest numeric type including both operands
1470/          numeric        numeric          smallest real type including both operands
1471+ - * /    SET            SET              SET
1472DIV MOD    integer        integer          smallest integer type including both operands
1473OR & ~     BOOLEAN        BOOLEAN          BOOLEAN
1474= #
1475< <= > >=  numeric        numeric          BOOLEAN
1476           CHAR           CHAR             BOOLEAN
1477           character array, string  character array, string  BOOLEAN
1478= #        BOOLEAN        BOOLEAN          BOOLEAN
1479           SET            SET              BOOLEAN
1480           NIL, pointer type T0 or T1  NIL, pointer type T0 or T1  BOOLEAN
1481           procedure type T, NIL  procedure type T, NIL  BOOLEAN
1482IN         integer        SET              BOOLEAN
1483IS         type T0        type T1          BOOLEAN
1484@end smallexample
1485
1486@heading Matching formal parameter lists
1487Two formal parameter lists @dfn{match} if
1488@enumerate
1489@item
1490they have the same number of parameters, and
1491@item
1492they have either the @dfn{same} function result type or none, and
1493@item
1494parameters at corresponding positions have @dfn{equal} types, and
1495@item
1496parameters at corresponding positions are both either value or variable parameters.
1497@end enumerate
1498
1499@c Appendix B. Syntax of Oberon-2
1500@page
1501@appendix Syntax of Oberon-2
1502
1503@smallexample
1504Module      =   MODULE ident ";" [ImportList] DeclSeq  [BEGIN StatementSeq] END ident ".".
1505ImportList  =   IMPORT [ident ":="] ident @{"," [ident ":="] ident@} ";".
1506DeclSeq     =   @{ CONST @{ConstDecl ";" @} | TYPE @{TypeDecl ";"@} | VAR @{VarDecl ";"@} @}
1507                @{ ProcDecl ";" | ForwardDecl ";" @}.
1508ConstDecl   =   IdentDef "=" ConstExpr.
1509TypeDecl    =   IdentDef "=" Type.
1510VarDecl     =   IdentList ":" Type.
1511ProcDecl    =   PROCEDURE [Receiver] IdentDef [FormalPars] ";" DeclSeq
1512                [BEGIN StatementSeq] END ident.
1513ForwardDecl =   PROCEDURE "^" [Receiver] IdentDef [FormalPars].
1514FormalPars  =   "(" [FPSection @{";" FPSection@}] ")" [":" Qualident].
1515FPSection   =   [VAR] ident @{"," ident@} ":" Type.
1516Receiver    =   "(" [VAR] ident ":" ident ")".
1517Type        =   Qualident
1518            |   ARRAY [ConstExpr @{"," ConstExpr@}] OF Type
1519            |   RECORD ["("Qualident")"] FieldList @{";" FieldList@} END
1520            |   POINTER TO Type
1521            |   PROCEDURE [FormalPars].
1522FieldList   =   [IdentList ":" Type].
1523StatementSeq =  Statement @{";" Statement@}.
1524Statement   =   [   Designator ":=" Expr
1525            |   Designator ["(" [ExprList] ")"]
1526            |   IF Expr THEN StatementSeq @{ELSIF Expr THEN StatementSeq@}
1527                [ELSE StatementSeq] END
1528            |   CASE Expr OF Case @{"|" Case@} [ELSE StatementSeq] END
1529            |   WHILE Expr DO StatementSeq END
1530            |   REPEAT StatementSeq UNTIL Expr
1531            |   FOR ident ":=" Expr TO Expr [BY ConstExpr] DO StatementSeq END
1532            |   LOOP StatementSeq END
1533            |   WITH Guard DO StatementSeq @{"|" Guard DO StatementSeq@}
1534                [ELSE StatementSeq] END
1535            |   EXIT
1536            |   RETURN [Expr]
1537                ].
1538Case        =   [CaseLabels @{"," CaseLabels@} ":" StatementSeq].
1539CaseLabels  =   ConstExpr [".." ConstExpr].
1540Guard       =   Qualident ":" Qualident.
1541ConstExpr   =   Expr.
1542Expr        =   SimpleExpr [Relation SimpleExpr].
1543SimpleExpr  =   ["+" | "-"] Term @{AddOp Term@}.
1544Term        =   Factor @{MulOp Factor@}.
1545Factor      =   Designator ["(" [ExprList] ")"]
1546            | number | character | string | NIL | Set | "(" Expr ")" | " ~ " Factor.
1547Set         =   "@{" [Element @{"," Element@}] "@}".
1548Element     =   Expr [".." Expr].
1549Relation    =   "=" | "#" | "<" | "<=" | ">" | ">=" | IN | IS.
1550AddOp       =   "+" | "-" | OR.
1551MulOp       =   " * " | "/" | DIV | MOD | "&".
1552Designator  =   Qualident @{"." ident | "[" ExprList "]" | " ^ " | "(" Qualident ")"@}.
1553ExprList    =   Expr @{"," Expr@}.
1554IdentList   =   IdentDef @{"," IdentDef@}.
1555Qualident   =   [ident "."] ident.
1556IdentDef    =   ident [" * " | "-"].
1557@end smallexample
1558
1559@c Appendix C: The module SYSTEM
1560@page
1561@appendix The module SYSTEM
1562
1563The module SYSTEM contains certain types and procedures that are necessary to
1564implement @dfn{low-level} operations particular to a given computer and/or
1565implementation. These include for example facilities for accessing devices that
1566are controlled by the computer, and facilities to break the type compatibility
1567rules otherwise imposed by the language definition. It is strongly recommended
1568to restrict their use to specific modules (called @dfn{low-level} modules).
1569Such modules are inherently non-portable, but easily recognized due to the
1570identifier SYSTEM appearing in their import list. The following specifications
1571hold for the implementation of Oberon-2 on the Ceres computer.
1572
1573Module SYSTEM exports a type BYTE with the following characteristics: Variables
1574of type @code{CHAR} or @code{SHORTINT} can be assigned to variables of type
1575BYTE. If a formal variable parameter is of type @code{ARRAY OF BYTE} then the
1576corresponding actual parameter may be of any type.
1577
1578Another type exported by module SYSTEM is the type PTR. Variables of any
1579pointer type may be assigned to variables of type PTR. If a formal variable
1580parameter is of type PTR, the actual parameter may be of any pointer type.
1581
1582The procedures contained in module SYSTEM are listed in the following tables.
1583Most of them correspond to single instructions compiled as in-line code. For
1584details, the reader is referred to the processor manual. @var{v} stands for a
1585variable, @var{x}, @var{y}, @var{a}, and @var{n} for expressions, and @var{T}
1586for a type.
1587
1588@smallexample
1589Function procedures
1590
1591Name       Argument types          Result type  Function
1592----       --------------          -----------  --------
1593ADR(v)     any                     LONGINT      address of variable v
1594BIT(a, n)  a: LONGINT              BOOLEAN      bit n of Mem[a]
1595           n: integer
1596CC(n)      integer constant        BOOLEAN      condition n (0 <= n <= 15)
1597LSH(x, n)  x: integer, CHAR, BYTE  type of x    logical shift
1598           n: integer
1599ROT(x, n)  x: integer, CHAR, BYTE  type of x    rotation
1600           n: integer
1601VAL(T, x)  T, x: any type          T            x interpreted as of type T
1602@end smallexample
1603
1604@smallexample
1605Proper procedures
1606
1607Name             Argument types                       Function
1608----             --------------                       --------
1609GET(a, v)        a: LONGINT; v: any basic             v := Mem[a]
1610                 type, pointer, procedure type
1611PUT(a, x)        a: LONGINT; x: any basic             Mem[a] := x
1612                 type, pointer, procedure type
1613GETREG(n, v)     n: integer constant; v: any          v := Register n
1614                 basic type, pointer, procedure type
1615PUTREG(n, x)     n: integer constant; x: any          Register n := x
1616                 basic type, pointer, procedure type
1617MOVE(a0, a1, n)  a0, a1: LONGINT; n: integer          Mem[a1.. a1+n-1] := Mem[a0.. a0+n-1]
1618NEW(v, n)        v: any pointer; n: integer           allocate storage block of n bytes
1619                                                      assign its address to v
1620@end smallexample
1621
1622@c Appendix D: The Oberon Environment
1623@page
1624@appendix The Oberon Environment
1625
1626Oberon-2 programs usually run in an environment that provides @dfn{command
1627activation}, @dfn{garbage collection}, @dfn{dynamic loading of modules}, and
1628certain @dfn{run time data structures}. Although not part of the language, this
1629environment contributes to the power of Oberon-2 and is to some degree implied
1630by the language definition. Appendix D describes the essential features of a
1631typical Oberon environment and provides implementation hints. More details can
1632be found in [1], [2], and [3].
1633
1634@c D1. Commands
1635@node Commands
1636@appendixsec Commands
1637
1638A command is any parameterless procedure @var{P} that is exported from a module
1639@var{M}. It is denoted by @var{M.P} and can be activated under this name from
1640the shell of the operating system. In Oberon, a user invokes commands instead
1641of programs or modules. This gives him a finer grain of control and allows
1642modules with multiple entry points. When a command @var{M.P} is invoked, the
1643module @var{M} is dynamically loaded unless it is already in memory (see D2)
1644and the procedure @var{P} is executed. When @var{P} terminates, @var{M} remains
1645loaded. All global variables and data structures that can be reached from
1646global pointer variables in @var{M} retain their values. When @var{P} (or
1647another command of @var{M}) is invoked again, it may continue to use these
1648values.  The following module demonstrates the use of commands. It implements
1649an abstract data structure @var{Counter} that encapsulates a counter variable
1650and provides commands to increment and print its value.
1651
1652@smallexample
1653MODULE Counter;
1654  IMPORT Texts, Oberon;
1655
1656  VAR
1657    counter: LONGINT;
1658    w: Texts.Writer;
1659
1660  PROCEDURE Add*;   (* takes a numeric argument from the command line *)
1661    VAR s: Texts.Scanner;
1662  BEGIN
1663    Texts.OpenScanner(s, Oberon.Par.text, Oberon.Par.pos);
1664    Texts.Scan(s);
1665    IF s.class = Texts.Int THEN INC(counter, s.i) END
1666  END Add;
1667
1668  PROCEDURE Write*;
1669  BEGIN
1670    Texts.WriteInt(w, counter, 5); Texts.WriteLn(w);
1671    Texts.Append(Oberon.Log, w.buf)
1672  END Write;
1673
1674BEGIN counter := 0; Texts.OpenWriter(w)
1675END Counter.
1676@end smallexample
1677
1678The user may execute the following two commands:
1679
1680@smallexample
1681Counter.Add   n   adds the value n to the variable counter
1682Counter.Write     writes the current value of counter to the screen
1683@end smallexample
1684
1685Since commands are parameterless they have to get their arguments from the
1686operating system. In general, commands are free to take arguments from
1687everywhere (e.g. from the text following the command, from the most recent
1688selection, or from a marked viewer). The command @var{Add} uses a scanner (a
1689data type provided by the Oberon system) to read the value that follows it on
1690the command line.
1691
1692When @var{Counter.Add} is invoked for the first time, the module
1693@var{Counter} is loaded and its body is executed. Every call of
1694@var{Counter.Add n} increments the variable counter by @var{n}. Every call of
1695@var{Counter.Write} writes the current value of counter to the screen.
1696
1697Since a module remains loaded after the execution of its commands, there must
1698be an explicit way to unload it (e.g. when the user wants to substitute the
1699loaded version by a recompiled version.) The Oberon system provides a command
1700to do that.
1701
1702@c D2. Dynamic Loading of Modules
1703@appendixsec Dynamic Loading of Modules
1704
1705A loaded module may invoke a command of a still unloaded module by specifying
1706its name as a string. The specified module is then dynamically loaded and the
1707designated command is executed. Dynamic loading allows the user to start a
1708program as a small set of basic modules and to extend it by adding further
1709modules at run time as the need becomes evident.
1710
1711A module @var{M0} may cause the dynamic loading of a module @var{M1} without
1712importing it. @var{M1} may of course import and use @var{M0}, but @var{M0} need
1713not know about the existence of @var{M1}. @var{M1} can be a module that is
1714designed and implemented long after @var{M0}.
1715
1716@c D3. Garbage Collection
1717@appendixsec Garbage Collection
1718
1719In Oberon-2, the predeclared procedure @code{NEW} is used to allocate data
1720blocks in free memory. There is, however, no way to explicitly dispose an
1721allocated block. Rather, the Oberon environment uses a @dfn{garbage collector}
1722to find the blocks that are not used any more and to make them available for
1723allocation again. A block is in use as long as it can be reached from a global
1724pointer variable via a pointer chain. Cutting this chain (e.g., setting a
1725pointer to @code{NIL}) makes the block collectable.
1726
1727A garbage collector frees a programmer from the non-trivial task of
1728deallocating data structures correctly and thus helps to avoid errors. However,
1729it requires information about dynamic data at run time (see D5).
1730
1731@c D4. Browser
1732@appendixsec Browser
1733
1734The interface of a module (the declaration of the exported objects) is
1735extracted from the module by a so-called @dfn{browser} which is a separate tool
1736of the Oberon environment. For example, the browser produces the following
1737interface of the module @var{Trees} from @ref{Modules}.
1738
1739@smallexample
1740DEFINITION Trees;
1741  TYPE
1742    Tree = POINTER TO Node;
1743    Node = RECORD
1744      name: POINTER TO ARRAY OF CHAR;
1745      PROCEDURE (t: Tree) Insert (name: ARRAY OF CHAR);
1746      PROCEDURE (t: Tree) Search (name: ARRAY OF CHAR): Tree;
1747      PROCEDURE (t: Tree) Write;
1748    END;
1749  PROCEDURE Init (VAR t: Tree);
1750END Trees.
1751@end smallexample
1752For a record type, the browser also collects all procedures bound to this type
1753and shows their declaration in the record type declaration.
1754
1755@c D5. Run Time Data Structures
1756@appendixsec Run Time Data Structures
1757
1758Certain information about records has to be available at run time: The dynamic
1759type of records is needed for type tests and type guards. A table with the
1760addresses of the procedures bound to a record is needed for calling them.
1761Finally, the garbage collector needs information about the location of pointers
1762in dynamically allocated records. All that information is stored in so-called
1763@dfn{type descriptors} of which there is one for every record type at run time.
1764The following paragraphs show a possible implementation of type descriptors.
1765
1766The dynamic type of a record corresponds to the address of its type descriptor.
1767For dynamically allocated records this address is stored in a so-called
1768@dfn{type tag} which precedes the actual record data and which is invisible for
1769the programmer. If @var{t} is a variable of type @var{CenterTree} (see example
1770in @ref{Type declarations}) Figure D5.1 shows one possible implementation of
1771the run time data structures.
1772
1773<Insert Figure D5.1>
1774
1775Fig. D5.1  A variable @var{t} of type @var{CenterTree}, the record @var{t^} it
1776points to, and its type descriptor
1777
1778Since both the table of procedure addresses and the table of pointer offsets
1779must have a fixed offset from the type descriptor address, and since both may
1780grow when the type is extended and further procedures and pointers are added,
1781the tables are located at the opposite ends of the type descriptor and grow in
1782different directions.
1783
1784A type-bound procedure @var{t.P} is called as @var{t^.tag^.ProcTab[IndexP]}.
1785The procedure table index of every type-bound procedure is known at compile
1786time. A type test @var{v IS T} is translated into
1787@var{v^.tag^.BaseTypes[ExtensionLevelT] = TypeDescrAdrT}.  Both the extension
1788level of a record type and the address of its type descriptor are known at
1789compile time. For example, the extension level of @var{Node} is 0 (it has no
1790base type), and the extension level of @var{CenterNode} is 1.
1791
1792[1]  N.Wirth, J.Gutknecht: The Oberon System. Software Practice and Experience
179319, 9, Sept. 1989 @*
1794
1795[2]  M.Reiser: The Oberon System. User Guide and Programming Manual.
1796Addison-Wesley, 1991 @*
1797
1798[3]  C.Pfister, B.Heeb, J.Templ: Oberon Technical Notes. Report 156, ETH
1799Zurich, March 1991 @*
1800
1801@bye
1802