Skip to content

Latest commit

 

History

History
2021 lines (1647 loc) · 97.6 KB

The_Programming_Language_Oberon+.adoc

File metadata and controls

2021 lines (1647 loc) · 97.6 KB

The Programming Language Oberon+

Based on work by Niklaus Wirth and Hanspeter Mössenböck ([Wi16], [Mo91]).

1. Introduction

Oberon+ (i.e. Oberon with extensions, abbreviated OBX, pronounced obex) is a general-purpose, procedural and object-oriented programming language in the tradition of Oberon-07 [Wi16] and Oberon-2 [Mo91].

The most important features of Oberon+ are block structure, modularity, separate compilation, static typing with strong type checking, generic programming [1], garbage collection, and type extension with type-bound procedures.

A major design goal of Oberon in 1987 was to make the language as simple as possible [Wi87]. Oberon+ follows the same goal, but taking into account the current state of the art. Backwards compatibility remains ensured: each valid Oberon-2 or Oberon-07 program is also a valid Oberon+ program.

The language allows several simplifications compared to previous Oberon versions: reserved words can be written in lower case, all semicolons are optional, and for some reserved words there are shorter variants; a declaration sequence can contain more than one CONST, TYPE and VAR section in arbitrary order, interleaved with procedures.

Furthermore, enumeration types (known as scalar types in Pascal [Wi73]), type-bound procedure types, explicit bit operations and exception handling have been added to the language. IN can be used instead of VAR for constant variable parameters. The length of array type local variable can be specified at runtime (VLA). The foreign function interface (FFI) is a regular feature of the language.

This report is not intended as a programmer’s tutorial. It is intentionally kept concise. Its function is to serve as a reference for programmers, implementors, and tutorial writers. What remains unsaid is mostly left so intentionally, either because it can be derived from stated rules of the language, or because it would require to commit the definition when a general commitment appears as unwise.

Listing 1. Oberon+ example featuring syntactic simplifications and type parameters
module Lists(T)
  type
    List* = ^record
               value* : T
               next*  : List
             end

  proc (l : List) Add* (v : T)
  begin
    new( l.next )
    l.next.value := v
  end Add

  proc (l : List) Print*()
  begin
    println(l.value)
  end Print
end Lists

module ListTest
  import
    L := Lists(integer)
  var
    l : L.List
  begin
    new(l)
    l.value := 123
    l.Add(456)
    l.Print()
    l.next.Print()
end ListTest

See here for more examples.

2. Syntax

An extended Backus-Naur Formalism (EBNF) is used to describe the syntax of Oberon+:

  • Alternatives are separated by |.

  • Brackets [ and ] denote optionality of the enclosed expression.

  • Braces { and } denote its repetition (possibly 0 times).

  • Syntactic entities (non-terminal symbols) are denoted by English words expressing their intuitive meaning.

  • Symbols of the language vocabulary (terminal symbols) are denoted by strings enclosed in quotation marks or by words in capital letters.

3. Vocabulary and Representation

Oberon+ source code is a string of characters encoded using the UTF-8 variable-width encoding as defined in ISO/IEC 10646. Identifiers, numbers, operators, and delimiters are represented using the ASCII character set; strings and comments can be either represented in the ASCII, Latin-1 (as defined in ISO/IEC 8859-1) or the Unicode Basic Multilingual Plane (BMP, plane 0, as defined in ISO/IEC 10646) character set.

The following lexical rules apply: blanks and line breaks must not occur within symbols (except in comments, and blanks in strings); they are ignored unless they are essential to separate two consecutive symbols. Capital and lower-case letters are considered as distinct.

3.1. Identifiers

Identifiers are sequences of letters, digits and underscore. The first character must be a letter or an underscore.

Syntax:
ident  = ( letter | '_' ) { letter | digit | '_' }
letter = 'A' ... 'Z' | 'a' ... 'z'
digit  = '0' ... '9'
Examples:
x
Scan
Oberon_2
_y
firstLetter

3.2. Numbers

Number literals are (unsigned) integer or real constants. The type of an integer literal is the minimal type to which the constant value belongs (see Basic types). If the literal is specified with the suffix H (or h), the representation is hexadecimal otherwise the representation is decimal. If a decimal or hexadecimal literal is specified with the suffix I (or i), then the type is INT32. If a decimal or hexadecimal constant is specified with the suffix L (or l), then the type is INT64.

A real number always contains a decimal point and at least one digit before the point. Optionally it may also contain a decimal scale factor. The letter E, D or S (or e, d or s) means times ten to the power of. A real number is of type LONGREAL, if it has a scale factor containing the letter D, or of type REAL, if it has a scale factor containing the letter S. If the scale factor contains the letter E the type is LONGREAL if the mantissa or exponent are too large to be represented by REAL.

Syntax:
number   = integer | real
integer  = ( digit {digit} | digit {hexDigit} ('H' | 'h') ) ['L' | 'l' | 'I' | 'i']
real     = digit {digit} '.' {digit} [Exponent]
Exponent = ('E' | 'e' | 'D' | 'd' | 'S' | 's') ['+' | '-'] digit {digit}
hexDigit = digit | 'A' ... 'F' | 'a' ... 'f'
digit    = '0' ... '9'
Examples:
1234
0dh              0DH
12.3
4.567e8          4.567E8
0.57712566d-6    0.57712566D-6

3.3. Characters

Character constants are denoted by the ordinal number of the character in hexadecimal notation followed by the letter X (or x).

Syntax:
character = digit {hexDigit} ('X' | 'x')

A character is either encoded as a 8-bit code value using the ISO/IEC 8859-1 Latin-1 encoding scheme or a 16-bit code value using the Unicode BMP scheme.

3.4. Strings

Strings are sequences of printable characters enclosed in single (') or double (") quote marks. The opening quote must be the same as the closing quote and must not occur within the string. A string must not extend over the end of a line. The number of characters in a string is called its length. A string of length 1 can be used wherever a character constant is allowed and vice versa.

Syntax:
string = ''' {character} ''' | '"' {character} '"'
Examples:
'Oberon'
"Don't worry!"
'x'

3.4.1. Hex Strings

Hex strings are sequences of bytes encoded in hexadecimal format and enclosed in dollar signs. The number of hex digits in the string must be even, two hex digits per byte. The number of bytes in a hex string is called its length. Line breaks and other white space between the dollar signs is ignored.

Syntax:
hexstring = '$' {hexDigit} '$'
Examples:
const arrow = $0F0F 0060 0070 0038 001C 000E 0007 8003
			   C101 E300 7700 3F00 1F00 3F00 7F00 FF00$
Note
Hex strings are not specified in [Wi16] but are used by the Project Oberon implementation, e.g. in Display.Mod. Hex strings are useful to represent all kinds of binary resources such as images and icons in the source code.

3.5. Operators and Delimiters

Operators and delimiters are the special characters, or character pairs listed below.

-

,

;

:

:=

.

..

(

)

[

]

{

}

*

/

#

^

+

<=

=

>=

|

~

3.6. Reserved Words

The reserved words consist of either all capital or all lower case letters and cannot be used as identifiers. All words listed below are reserved (only capital letter versions shown).

ARRAY

BEGIN

BY

CASE

CONST

DEFINITION

DIV

DO

ELSE

ELSIF

END

EXIT

FALSE

FOR

IF

IMPORT

IN

IS

LOOP

MOD

MODULE

NIL

OF

OR

POINTER

PROC

PROCEDURE

RECORD

REPEAT

RETURN

THEN

TO

TRUE

TYPE

UNTIL

VAR

WHILE

WITH

Note
WITH, LOOP and EXIT are Oberon-2 reserved words not present in Oberon-07. In contrast TRUE and FALSE are Oberon-07 and Oberon+ reserved words but just predeclared identifiers in Oberon-2. DEFINITION and PROC are Oberon+ reserved words not present in previous Oberon versions. All lower-case versions are only reserved words in Oberon+. The compiler is supposed to offer a dedicated Oberon-2 and Oberon-07 compatibility mode to support legacy code with reserved word collisions.

3.7. Comments

Comments are arbitrary character sequences opened by the bracket (* and closed by *). Comments may be nested. They do not affect the meaning of a program. Oberon+ also supports line comments; text starting with // up to a line break is considered a comment.

4. Declarations and scope rules

Every identifier occurring in a program must be introduced by a declaration, unless it is a predeclared identifier. Declarations also specify certain permanent properties of an object, such as whether it is a constant, a type, a variable, or a procedure. The identifier is then used to refer to the associated object.

The scope of an object x is the whole block (module, procedure, or record) to which the declaration belongs and hence to which the object is local. It excludes the scopes of equally named objects which are declared in nested blocks. The scope rules are:

  1. No identifier may denote more than one object within a given scope (i.e. no identifier may be declared twice in a block);

  2. An object may only be referenced within its scope;

  3. The order of declaration is not significant;

  4. Identifiers denoting record fields (see Record types) or type-bound procedures (see Type-bound procedures) are valid in record designators only.

An identifier declared in a module block may be followed by an export mark (* or -) in its declaration to indicate that it is exported. An identifier x exported by a module M may be used in other modules, if they import M (see Modules). The identifier is then denoted as M.x in these modules and is called a qualified identifier. Identifiers marked with - in their declaration are read-only in importing modules.

Syntax:
qualident = [ident '.'] ident
identdef  = ident ['*' | '-']
Note
Oberon-07 only knows the * export mark; all module variables are exported read-only and exported record fields are writable. Oberon+ and Oberon-2 permit finer writability control of exported variables and fields.

The following identifiers are predeclared; their meaning is defined in the indicated sections; either all capital or all lower case identifiers are supported (only capital versions shown).

ABS

ANYREC

ASH

ASR

ASSERT

BITAND

BITNOT

BITOR

BITS

BITSHL

BITSHR

BITXOR

BOOLEAN

BYTE

BYTES

CAST

CAP

CHAR

CHR

COPY

DEC

DEFAULT

ENTIER

EXCL

FLOOR

FLT

HALT

INC

INCL

INT8

INT16

INT32

INT64

INTEGER

LEN

LONG

LONGINT

LONGREAL

LSL

MAX

MIN

NEW

NUMBER

ODD

ORD

PACK

PCALL

RAISE

REAL

ROR

SET

SHORT

SHORTINT

SIZE

UNPK

WCHR

Note
BYTE, ASR, FLOOR, ROR, LSL, FLT, PACK and UNPK are predeclared identifiers in Oberon-07 and Oberon+, but not in Oberon-2. All lower-case versions are only predeclared in Oberon+.

5. Constant declarations

A constant declaration associates an identifier with a constant value.

Syntax:
ConstDeclaration = identdef '=' ConstExpression
ConstExpression  = expression

A constant expression is an expression that can be evaluated by a mere textual scan without actually executing the program. Its operands are constants (see Operands) or predeclared functions (see Predeclared function procedures) that can be evaluated at compile time. Examples of constant declarations are:

Examples:
N = 100
limit = 2*N - 1
fullSet = {min(set) .. max(set)}
Note
For compile time calculations of values the same rules as for runtime calculation apply. The ConstExpression of ConstDeclaration behaves as if each use of the constant identifier was replaced by the ConstExpression. An expression like MAX(INTEGER)+1 thus causes an overflow of the INTEGER range. To avoid this either LONG(MAX(INTEGER))+1 or MAX(INTEGER)+1L has to be used.

6. Type declarations

A data type determines the set of values which variables of that type may assume, and the operators that are applicable. A type declaration associates an identifier with a type. In the case of structured types (arrays and records) it also defines the structure of variables of this type. A structured type cannot contain itself.

Syntax:
TypeDeclaration = identdef '=' type
type            = NamedType | ArrayType | RecordType
                  | PointerType | ProcedureType | enumeration
NamedType       = qualident
Examples:
Table = array N of real
Tree = pointer to Node
Node = record
  key: integer
  left, right: Tree
end
CenterTree = pointer to CenterNode
CenterNode = record (Node)
  width: integer
  subnode: Tree
end
Function = procedure(x: integer): integer

6.1. Basic types

The basic types are denoted by predeclared identifiers. The associated operators are defined in Operators and the predeclared function procedures in Predeclared procedures. Either all capital or all lower case identifiers are supported (only capital versions shown). There are fixed and variable size basic types. For the fixed size basic types the byte widths and ranges are explicitly specified herein. The variable size basic types are just alternative names for the fixed size integer types.

The values of the given fixed size basic types are the following:

BOOLEAN

1 byte

the truth values true and false

BYTE

1 byte

the integers between 0 and 255

CHAR

1 byte

the characters of the Latin-1 set (0x .. 0ffx)

INT8

1 byte

the integers between -128 and 127

INT16

2 byte

the integers between -32'768 and 32'767

INT32

4 byte

the integers between -2'147'483'648 and 2'147'483'647

INT64

8 byte

the integers between -9'223'372'036'854'775'808 and 9'223'372'036'854'775'807

REAL

32 bit

an IEEE 754 floating point number

LONGREAL

64 bit

an IEEE 754 floating point number

SET

4 byte

the sets of integers between 0 and MAX(SET)

WCHAR

2 byte

the characters of the Unicode BMP set (0x .. 0d7ffx, 0f900x .. 0ffffx)

The values of the given variable size basic types are the following:

SHORTINT

the integers between MIN(SHORTINT) and MAX(SHORTINT)

INTEGER

the integers between MIN(INTEGER) and MAX(INTEGER)

LONGINT

the integers between MIN(LONGINT) and MAX(LONGINT)

Types INT64, INT32, INT16, INT8, LONGINT, INTEGER, SHORTINT and BYTE are integer types, types REAL and LONGREAL are floating point types, and together they are called numeric types. The larger type includes (the values of) the smaller type according to the following relations:

INT64 >= INT32 >= INT16 >= INT8
INT16 >= BYTE
LONGREAL >= REAL
REAL >= INT16
LONGREAL >= INT32
WCHAR >= CHAR
LONGINT >= INTEGER >= SHORTINT
Note
Because of the limited bit precision of the LONGREAL mantissa (which is 52 bits in IEEE 754 double precision representation), a LONGREAL does not fully include INT64. Similarly REAL does not include the full range of INT32. To convert a INT64 to a LONGREAL or an INT32 to a REAL the FLT() built-in function should be used to .

A compiler may support other type inclusion relations in addition to the ones specified herein, but shall at least issue a warning if in a given operation information could be lost. A compiler shall at least support the Oberon 90 and Oberon-2 type inclusion relations in this way.

A compiler may map the variable size integer names to any of the fixed size integers as long as the inclusion relations are obeyed. By default a correspondence of LONGINT with INT64, INTEGER with INT32 and SHORTINT with INT16 is assumed.

Note
Oberon 90 and Oberon-2 specify the following type inclusion relations assuming that LONGINT maps to INT32, INTEGER to INT16 and SHORTINT to INT8: LONGREAL >= REAL >= LONGINT >= INTEGER >= SHORTINT.

6.2. Array types

An array is a structure consisting of a number of elements which are all of the same type, called the element type. The number of elements of an array is called its length. The length is a positive integer. The elements of the array are designated by indices, which are integers between 0 and the length minus 1. Zero array length are supported in declarations, but accessing such arrays halts the program.

Syntax:
ArrayType  = ARRAY [ LengthList ] OF type
	         | '[' [ LengthList ] ']' type
LengthList = length {',' length} | VAR varlength {',' varlength}
length     = ConstExpression
varlength  = expression

A type of the form

array L0, L1, ..., Ln of T

is an abbreviation for

array L0 of array L1 of ... array Ln of T

Arrays declared without length are called open arrays. They are restricted to pointer base types (see Pointer types), element types of open array types, and formal parameter types (see Formal parameters).

Examples:
array 10, N of integer
array of char
[N][M] T

Local variables of array type can have variable lengths calculated at runtime; in this case the LengthList is prefixed with the VAR reserved word; the expression cannot reference other local variables of the same scope.

Note
In contrast to array pointers allocated with new(), variable length arrays (VLA) can be allocated on the stack instead of the heap (depending on the compiler and supported options), which makes them attractive to low-resource embedded applications where dynamic memory allocation is not feasible. It is also interesting to note that already the length/range of ALGOL 60 arrays was defined using an ordinary arithmetic expression and thus could be calculated at runtime; even ALGOL W had this feature, but unfortunately it was removed in Pascal, and even Oberon-07 still uses a const expression for array lengths evaluated at compile time.

Array lengths at least up to MAX(INT32) shall be supported by a compiler, for both constant and variable lengths.

6.3. Record types

A record type is a structure consisting of a fixed number of elements, called fields, with possibly different types. The record type declaration specifies the name and type of each field. The scope of the field identifiers extends from the point of their declaration to the end of the record type, but they are also visible within designators referring to elements of record variables (see Operands). If a record type is exported, field identifiers that are to be visible outside the declaring module must be marked. They are called public fields; unmarked elements are called private fields.

Syntax:
RecordType = RECORD ['(' BaseType ')']
             FieldList { [';'] FieldList} END
BaseType   = NamedType
FieldList  = [ IdentList ':' type ]
IdentList  = identdef { [','] identdef }

Record types are extensible, i.e. a record type can be declared as an extension of another record type. In the example

T0 = record x: integer end
T1 = record (T0) y: real end

T1 is a (direct) extension of T0 and T0 is the (direct) base type of T1 (see Definition of terms). An extended type T1 consists of the fields of its base type and of the fields which are declared in T1. Fields declared in the extended record shadow equally named fields declared in a base type.

Alternatively, a pointer to record type can be used as the BaseType; in this case the record base type of the pointer is used as the base type of the declared record.

Each record is implicitly an extension of the predeclared record type ANYREC. ANYREC does not contain any fields and can only be used in pointer and variable parameter declarations.

Examples:
record
  day, month, year: integer
end

record
  name, firstname: array 32 of char
  age: integer
  salary: real
end

6.4. Pointer types

Variables of a pointer type P assume as values pointers to variables of some type T. T is called the pointer base type of P and must be a record or array type. Pointer types adopt the extension relation of their pointer base types: if a type T1 is an extension of T, and P1 is of type POINTER TO T1, then P1 is also an extension of P (see Definition of terms).

Syntax:
PointerType = ( POINTER TO | '^' ) type

If p is a variable of type P = POINTER TO T, a call of the predeclared procedure NEW(p) (see Predeclared procedures) allocates a variable of type T in free storage. If T is a record type or an array type with fixed length, the allocation has to be done with NEW(p); if T is an n-dimensional open array type the allocation has to be done with NEW(p, e0, …​, en-1) where T is allocated with lengths given by the expressions e0, …​, en-1. In either case a pointer to the allocated variable is assigned to p. p is of type P. The referenced variable p^ is of type T. Any pointer variable may assume the value NIL, which points to no variable at all. All pointer fields or elements of a newly allocated record or array are set to NIL.

Note
Oberon doesn’t support taking the address (i.e. making a pointer) of a variable, parameter or record field. If you need a pointer the record or array has to be allocated using NEW().

6.5. Procedure types

Variables of a procedure type T have a procedure (or NIL) as value. If a procedure P is assigned to a variable of type T, the formal parameter lists and result types (see Formal parameters) of P and T must match (see Definition of terms). A procedure P assigned to a variable or a formal parameter must not be a predeclared, nor a type-bound procedure, nor may it access local variables or parameters declared in outer (type-bound) procedures or call procedure which access local variables or parameters declared in outer (type-bound) procedures.

Note
Oberon 90, 2 and 07 don’t support assignment of procedures local to another procedure to a procedure type variable. Oberon+ doesn’t make this restriction, as long as the local procedure (or one of its nested procedures) isn’t nested and doesn’t depend on local variables or parameters declared in its enclosing procedure.
Syntax:
ProcedureType = PROCEDURE [FormalParameters]

6.6. Enumeration types

An enumeration is a list of identifiers that denote the values which constitute a data type. These identifiers are used as constants in the program. They, and no other values, belong to this type. The values are ordered. and the ordering relation is defined by their sequence in the enumeration. The ordinal number of the first value is O.

Syntax:
enumeration = '('  ident { [','] ident } ')'
Examples:
(red, green, blue)
(club, diamond, heart, spade)
(Monday, Tuesday, Wednesday, Thursday, Friday, Saturday, Sunday)

The ordinal number of an enumeration identifier can be obtained using the ORD predeclared function procedure, or by just assigning/passing to an integer type variable or parameter. CAST is the reverse operation. MIN returns the first and MAX the last ident of the enumeration. INC returns the next and DEC the previous ident. If T is an enumeration type then INC(MAX(T)) and DEC(MIN(T)) are undefined and terminate the program.

7. Variable declarations

Variable declarations introduce variables by defining an identifier and a data type for them.

Syntax:
VariableDeclaration = IdentList ":" type

Record and pointer variables have both a static type (the type with which they are declared - simply called their type) and a dynamic type (the type of their value at run time). For pointers and variable parameters of record type the dynamic type may be an extension of their static type. The static type determines which fields of a record are accessible. The dynamic type is used to call type-bound procedures (see Type-bound procedures).

Examples:
i, j, k: integer
x, y: real
p, q: bool
s: set
F: Function
a: array 100 of real
w: array 16 of record
     name: arra 32 of char
     count: integer
   end
t, c: Tree

8. Expressions

Expressions are constructs denoting rules of computation whereby constants and current values of variables are combined to compute other values by the application of operators and function procedures. Expressions consist of operands and operators. Parentheses may be used to express specific associations of operators and operands.

8.1. Operands

With the exception of set constructors and literal constants (numbers, character constants, or strings), operands are denoted by designators. A designator consists of an identifier referring to a constant, variable, or procedure. This identifier may possibly be qualified by a module identifier (see Declarations and scope rules and Modules) and may be followed by selectors if the designated object is an element of a structure.

Syntax:
designator = qualident {selector}
selector   = '.' ident | '[' ExpList ']' | '^' | '(' qualident ')'
ExpList    = expression {',' expression}

If a designates an array, then a[e] denotes that element of a whose index is the current value of the expression e. The type of e must be an integer type. A designator of the form a[e0, e1, …​, en] is an abbreviation for a[e0][e1]…​[en].

If r designates a record, then r.f denotes the field f of r or the procedure f bound to the dynamic type of r (see Type-bound procedures). If p designates a pointer, p^ denotes the variable which is referenced by p. The designators p^.f and p^[e] may be abbreviated as p.f and p[e], i.e. record and array selectors imply dereferencing.

Dereferencing is also implied if a pointer is assigned to a variable of a record or array type, if a pointer is used as actual parameter for a formal parameter of a record or array type, or if a pointer is used as argument of the standard procedure LEN [2].

If a or r are read-only, then also a[e] and r.f are read-only.

A type guard v(T) asserts that the dynamic type of v is T (or an extension of T), i.e. program execution is aborted, if the dynamic type of v is not T (or an extension of T). Within the designator, v is then regarded as having the static type T. The guard is applicable, if

  1. v is a variable parameter of record type or v is a pointer to record type, and if

  2. T is an extension of the static type of v.

If the designated object is a constant or a variable, then the designator refers to its current value. If it is a procedure, the designator refers to that procedure unless it is followed by a (possibly empty) parameter list in which case it implies an activation of that procedure and stands for the value resulting from its execution. The actual parameters must correspond to the formal parameters as in proper procedure calls (see Formal parameters).

Examples:
i                        // integer
a[i]                     // real
w[3].name[i]             // char
t.left.right             // Tree
t(CenterTree).subnode    // Tree

8.2. Operators

Four classes of operators with different precedences (binding strengths) are syntactically distinguished in expressions. The operator ~ has the highest precedence, followed by multiplication operators, addition operators, and relations. Operators of the same precedence associate from left to right. For example, x-y-z stands for (x-y)-z.

Syntax:
expression       = SimpleExpression [ relation SimpleExpression ]
relation         = '=' | '#' | '<' | '<=' | '>' | '>=' | IN | IS
SimpleExpression = ['+' | '-'] term { AddOperator term }
AddOperator      = '+' | '-' | OR
term             = factor {MulOperator factor}
MulOperator      = '*' | '/' | DIV | MOD | '&'
literal          = number | string | hexstring | hexchar
                   | NIL | TRUE | FALSE | set
factor           = literal | designator [ActualParameters]
	               | '(' expression ')' | '~' factor
ActualParameters = '(' [ ExpList ] ')'
set              = '{' [ element {',' element} ] '}'
element          = expression ['..' expression]

8.2.1. Logical operators

OR

logical disjunction

p or q

if p then TRUE, else q

&

logical conjunction

p & q

if p then q, else FALSE

~

negation

~p

not p

These operators apply to BOOLEAN operands and yield a BOOLEAN result.

8.2.2. Arithmetic operators

+

sum

-

difference

*

product

/

real quotient

DIV

integer quotient

MOD

modulus

The operators `, `-`, `*`, and `/` apply to operands of numeric types. The type of the result is the type of that operand which includes the type of the other operand, except for division (`/`), where the result is the smallest real type which includes both operand types. When used as monadic operators, `-` denotes sign inversion and ` denotes the identity operation. The operators DIV and MOD apply to integer operands only. They are related by the following formulas defined for any x and positive divisors y:

x = (x DIV y) * y + (x MOD y)
0 <= (x MOD y) < y
Examples:
x    y    x DIV y    x MOD y
5    3    1          2
-5   3    -2         1
Note
Oberon+ doesn’t require overflow checks. If the representation of the result of an arithmetic operation would require a wider integer type than provided by the type of the expression, the behaviour is undefined; e.g. MAX(INTEGER)+1 causes an overflow, i.e. the result could be MIN(INTEGER) or anything else (even a termination of the program).

8.2.3. Set Operators

+

union

-

difference (x - y = x * (-y))

*

intersection

/

symmetric set difference (x / y = (x-y) + (y-x))

Set operators apply to operands of type SET and yield a result of type SET. The monadic minus sign denotes the complement of x, i.e. -x denotes the set of integers between 0 and MAX(SET) which are not elements of x. Set operators are not associative ((a+b)-c # a+(b-c)).

A set constructor defines the value of a set by listing its elements between curly brackets. The elements must be integers in the range 0..MAX(SET). A range a..b denotes all integers in the interval [a, b].

8.2.4. Relations

=

equal

#

unequal

<

less

<=

less or equal

>

greater

>=

greater or equal

IN

set membership

IS

type test

Relations yield a BOOLEAN result. The relations =, #, <, <=, >, and >= apply to the numeric types, as well as enumerations, CHAR, strings, and CHAR arrays containing 0x as a terminator. The relations = and # also apply to BOOLEAN and SET, as well as to pointer and procedure types (including the value NIL). x IN s stands for x is an element of s. x must be of an integer type, and s of type SET. v IS T stands for the dynamic type of v is T (or an extension of T ) and is called a type test. It is applicable if

  1. v is a variable parameter of record type, or v is a pointer to record variable (which can be NIL), and if

  2. T is an extension of the static type of v (see Definition of terms).

Examples:
1991                   // integer
i div 3                // integer
~p or q                // boolean
(i+j) * (i-j)          // integer
s - {8, 9, 13}         // set
i + x                  // real
a[i+j] * a[i-j]        // real
(0<=i) & (i<100)       // boolean
t.key = 0              // boolean
k in {i..j-1}          // boolean
w[i].name <= "John"    // boolean
t is CenterTree        // boolean

8.2.5. String operators

+

concatenation

The concatenation operator applies to operands of string types (literals as well as char or wchar arrays). The resulting string consists of the characters of the first operand followed by the characters of the second operand. If a char string (literal or char array) is concatenated with a wchar string (literal or wchar array) the result is a wchar string.

8.2.6. Function Call

A function call is a factor in an expression. In contrast to Procedure calls in a function call the actual parameter list is mandatory. Each expression in the actual parameters list (if any) is used to initialize a corresponding formal parameter. The number of expressions in the actual parameter list must correspond the number of formal parameters. See also Formal parameters.

Syntax:
FunctionCall           = designator ActualParameters
ActualParameters = '(' [ ExpList ] ')'

9. Statements

Statements denote actions. There are elementary and structured statements. Elementary statements are not composed of any parts that are themselves statements. They are the assignment, the procedure call, the return, and the exit statement. Structured statements are composed of parts that are themselves statements. They are used to express sequencing and conditional, selective, and repetitive execution.

Syntax:
statement = [ assignment | ProcedureCall | IfStatement
            | CaseStatement  | WithStatement | LoopStatement
            | ExitStatement | ReturnStatement
	        | RepeatStatement | ForStatement ]

9.1. Statement sequences

Statement sequences denote the sequence of actions specified by the component statements which are optionally separated by semicolons.

Syntax:
StatementSequence = statement { [";"] statement}

9.2. Assignments

Assignments replace the current value of a variable by a new value specified by an expression. The expression must be assignment compatible with the variable (see Definition of terms). The assignment operator is written as := and pronounced as becomes.

Syntax:
assignment = designator ':=' expression

If an expression e of type Te is assigned to a variable v of type Tv, the following happens:

  1. if Tv and Te are record types, only those fields of Te are assigned which also belong to Tv (projection); the dynamic type of v must be the same as the static type of v and is not changed by the assignment;

  2. if Tv and Te are pointer types, the dynamic type of v becomes the dynamic type of e;

  3. if Tv is ARRAY n OF CHAR and e is a string of length m < n, v[i] becomes ei for i = 0..m-1 and v[m] becomes 0X;

  4. if Tv and Te are open or non-open CHAR arrays, v[i] becomes e[i] for i = 0..STRLEN(e); if LEN(v) <= STRLEN(e) or e is not terminated by 0X the program halts;

  5. if Tv is an open CHAR array and e is a string v[i] becomes e[i] for i = 0..LEN(e)-1 and v[LEN(e)] becomes 0X; if LEN(v) <= LEN(e) the program halts;

Examples:
i := 0
p := i = j
x := i + 1
k := log2(i+j)
F := log2
s := {2, 3, 5, 7, 11, 13}
a[i] := (x+y) * (x-y)
t.key := i
w[i+1].name := "John"
t := c

9.3. Procedure calls

A procedure call activates a procedure. It may contain a list of actual parameters which replace the corresponding formal parameter list defined in the procedure declaration (see Procedure declarations). The correspondence is established by the positions of the parameters in the actual and formal parameter lists. There are three kinds of parameters: variable (VAR), IN and value parameters.

If a formal parameter is a VAR or IN parameter, the corresponding actual parameter must be a designator denoting a variable. If it denotes an element of a structured variable, the component selectors are evaluated when the formal/actual parameter substitution takes place, i.e. before the execution of the procedure. If a formal parameter is a value parameter, the corresponding actual parameter must be an expression. This expression is evaluated before the procedure activation, and the resulting value is assigned to the formal parameter (see also Formal parameters).

Syntax:
ProcedureCall = designator [ ActualParameters ]
Examples:
WriteInt(i*2+1)
inc(w[k].count)
t.Insert("John")

9.4. If statements

If statements specify the conditional execution of guarded statement sequences. The boolean expression preceding a statement sequence is called its guard. The guards are evaluated in sequence of occurrence, until one evaluates to TRUE, whereafter its associated statement sequence is executed. If no guard is satisfied, the statement sequence following the symbol ELSE is executed, if there is one.

Syntax:
IfStatement    = IF expression THEN StatementSequence
	             {ElsifStatement} [ElseStatement] END
ElsifStatement = ELSIF expression THEN StatementSequence
ElseStatement  = ELSE StatementSequence
Example:
if (ch >= "A") & (ch <= "Z") then ReadIdentifier
elsif (ch >= "0") & (ch <= "9") then ReadNumber
elsif (ch = "'") OR (ch = '"') then ReadString
else SpecialCharacter
end

9.5. Case statements

Case statements specify the selection and execution of a statement sequence according to the value of an expression. First the case expression is evaluated, then that statement sequence is executed whose case label list contains the obtained value. The case expression must either be of an integer type that includes the types of all case labels, or an enumeration type with all case labels being valid members of this type, or both the case expression and the case labels must be of type CHAR. Case labels are constants, and no value must occur more than once. If the value of the expression does not occur as a label of any case, the statement sequence following the symbol ELSE is selected, if there is one, otherwise the program is aborted.

The type T of the case expression (case variable) may also be a variable parameter of record type or a pointer to record variable. Then each case consists of exactly one case label which must be an extension of T (see Definition of terms), and in the statements Si labelled by Ti, the case variable is considered as of type Ti. If the case variable is of POINTER type, then one case label can also be NIL. The evaluation order corresponds to the case label order; the first statement sequence is executed whose case label meets the condition.

Syntax:
CaseStatement = CASE expression OF ['|'] Case { '|' Case }
	            [ ELSE StatementSequence ] END
Case          = [ CaseLabelList ':' StatementSequence ]
CaseLabelList = LabelRange { ',' LabelRange }
LabelRange    = label [ '..' label ]
label         = ConstExpression
Examples:
case ch of
  "A" .. "Z": ReadIdentifier
| "0" .. "9": ReadNumber
| "'", '"': ReadString
else SpecialCharacter
end

type R  = record a: integer end
	 R0 = record (R) b: integer end
	 R1 = record (R) b: real end
	 R2 = record (R) b: set end
	 P  = ^R
	 P0 = ^R0
	 P1 = ^R1
	 P2 = ^R2
var p: P
case p of
	| P0: p.b := 10
	| P1: p.b := 2.5
	| P2: p.b := {0, 2}
	| NIL: p.b := {}
end

9.6. While statements

While statements specify the repeated execution of a statement sequence while the Boolean expression (its guard) yields TRUE. The guard is checked before every execution of the statement sequence. The ELSIF part is integrated in the loop; as long as any of the Boolean expressions (either the WHILE or ELSIF guard) yields TRUE, the corresponding statement sequence is executed; repetition only terminates, when all guards are FALSE.

Syntax:
WhileStatement = WHILE expression DO StatementSequence
	             {ELSIF expression DO StatementSequence} END
Examples:
while i > 0 do i := i div 2; k := k + 1 end

while (t # nil) & (t.key # i) do t := t.left end

// Euclidean algorithm to compute the greatest common divisor of m and n:
while m > n do
	m := m – n
elsif n > m do
	n := n – m
end
// is equivalent to:
loop
	if m > 0 then
		m := m – n
	elsif n > m then
		n := n – m
	else
		exit
	end
end
Note
The ELSIF part was added to Oberon-07. It is noteably Dijkstra’s form of the WHILE loop. Contrary to intuition, the ELSIF part is not executed only if the first check of the WHILE guard evaluates to FALSE; instead, both parts are checked and executed until both guards evaluate to FALSE.

9.7. Repeat statements

A repeat statement specifies the repeated execution of a statement sequence until a condition specified by a Boolean expression is satisfied. The statement sequence is executed at least once.

Syntax:
RepeatStatement = REPEAT StatementSequence UNTIL expression

9.8. For statements

A for statement specifies the repeated execution of a statement sequence while a progression of values is assigned to a control variable of the for statement. Control variables can be of integer or enumeration types. An explicit BY expression is only supported for integer control variables.

Syntax:
ForStatement = FOR ident ':=' expression TO expression
			   [BY ConstExpression]
	           DO StatementSequence END

The statement

for v := first to last by step do statements end

is equivalent to

temp := last; v := first
if step > 0 then
    while v <= temp do statements; INC(v,step) end
else
    while v >= temp do statements; DEC(v,-step) end
end

temp has the same type as v. For integer control variables, step must be a nonzero constant expression; if step is not specified, it is assumed to be 1. For enumeration control variables, there is no explicit step, but the INC or DEC version of the while loop is used depending on ORD(first) ⇐ ORD(last).

Examples:
for i := 0 to 79 do k := k + a[i] end
for i := 79 to 1 by -1 do a[i] := a[i-1] end

9.9. Loop statements

A loop statement specifies the repeated execution of a statement sequence. It is terminated upon execution of an exit statement within that sequence (see Return and exit statements).

Syntax:
LoopStatement = LOOP StatementSequence END
ExitStatement = EXIT
Example:
loop
  ReadInt(i)
  if i < 0 then exit end
  WriteInt(i)
end

Loop statements are useful to express repetitions with several exit points or cases where the exit condition is in the middle of the repeated statement sequence.

9.10. Return and exit statements

A return statement indicates the termination of a procedure. It is denoted by the symbol RETURN, followed by an expression if the procedure is a function procedure. The type of the expression must be assignment compatible (see Definition of terms) with the result type specified in the procedure heading (see Procedure declarations).

Syntax:
ReturnStatement = RETURN [ expression ]
ExitStatement   = EXIT

Function procedures require the presence of a return statement indicating the result value. In proper procedures, a return statement is implied by the end of the procedure body. Any explicit return statement therefore appears as an additional (probably exceptional) termination point.

Note
The optional expression causes an LL(k) ambiguity which can be resolved in that the parser expects a return expression if the procedure has a return type and vice versa.

An exit statement is denoted by the symbol EXIT. It specifies termination of the enclosing loop statement and continuation with the statement following that loop statement. Exit statements are contextually, although not syntactically associated with the loop statement which contains them.

9.11. With statements

With statements execute a statement sequence depending on the result of a type test and apply a type guard to every occurrence of the tested variable within this statement sequence.

Syntax:
WithStatement = WITH ['|'] Guard DO StatementSequence
	            { '|' Guard DO StatementSequence}
	            [ ELSE StatementSequence ] END
Guard         = qualident ':' qualident

If v is a variable parameter of record type or a pointer to record variable, and if it is of a static type T0, the statement

with v: T1 do S1 | v: T2 do S2 else S3 end

has the following meaning: if the dynamic type of v is T1, then the statement sequence S1 is executed where v is regarded as if it had the static type T1; else if the dynamic type of v is T2, then S2 is executed where v is regarded as if it had the static type T2; else S3 is executed. T1 and T2 must be extensions of T0 (see Definition of terms). If no type test is satisfied and if an else clause is missing the program is aborted.

Example:
with t: CenterTree do i := t.width; c := t.subnode end

9.12. Exception handling

Exception handling in Oberon+ is implemented using the predeclared procedures PCALL and RAISE (see Predeclared proper procedures), without any special syntax. There are no predefined exceptions.

An exception is a record allocated with NEW(). The pointer to this record is passed as an actual argument to RAISE. If the pointer is nil the program execution aborts. RAISE may be called without an argument in which case the compiler provides an allocated record the exact type of which is not relevant. RAISE never returns, but control is transferred from the place where RAISE is called to the nearest dynamically-enclosing call of PCALL. When calling RAISE without a dynamically-enclosing call of PCALL the program execution is aborted.

PCALL executes a protected call of the procedure or procedure type P. P is passed as the second argument to PCALL. P cannot have a return type. P can be a type-bound procedure type. P can be a nested procedure, even if it accesses local variables or parameters of an outer procedure. If P has formal parameters the corresponding actual parameters are passed to PCALL immediately after P. The actual parameters must be parameter compatible with the formal parameters of P (see Definition of terms). The first parameter R of PCALL is a POINTER TO ANYREC; if RAISE(E) is called in the course of P, then R is set to E; otherwise R is set to NIL. The state of VAR parameters of P or local variables or parameters of an outer procedure accessed by P is non-deterministic in case RAISE is called in the course of P.

Listing 2. Example:
module ExceptionExample
  type Exception = record end
  proc Print(in str: array of char)
    var e: pointer to Exception
  begin
    println(str)
    new(e)
    raise(e)
    println("this is not printed")
  end Print
  var res: pointer to anyrec
begin
  pcall(res, Print, "Hello World")
  case res of
  | Exception: println("got Exception")
  | anyrec: println("got anyrec")
  | nil: println("no exception")
  else
    println("unknown exception")
    // could call raise(res) here to propagate the exception
  end
end ExceptionExample

10. Procedure declarations

A procedure declaration consists of a procedure heading and a procedure body. The heading specifies the procedure identifier and the formal parameters (see [Formal Parameters]). For type-bound procedures it also specifies the receiver parameter. The body contains declarations and statements. The procedure identifier must be repeated at the end of the procedure declaration unless it has no body.

There are two kinds of procedures: proper procedures and function procedures. The latter are activated by a function designator as a constituent of an expression and yield a result that is an operand of the expression. Proper procedures are activated by a procedure call. A procedure is a function procedure if its formal parameters specify a result type. Each control path of a function procedure must return a value.

All constants, variables, types, and procedures declared within a procedure body are local to the procedure. Since procedures may be declared as local objects too, procedure declarations may be nested. The call of a procedure within its declaration implies recursive activation.

Objects declared in the environment of the procedure are also visible in those parts of the procedure in which they are not concealed by a locally declared object with the same name. The type of a parameter or local variable declared in an outer procedure and accessed from a nested procedure cannot be a CSTRUCT, CUNION, CARRAY or CPOINTER (see C Types).

Note
Procedures can be nested, and inner procedures have access to the parameters or local variables of outer procedures ("non-local access"). This feature was already supported in ALGOL 60 and adopted by Wirth in Pascal; it is also supported by original Oberon and Oberon-2, but no longer by Oberon-07. Previous versions of Oberon+ followed Oberon-07 and didn’t support this feature, mostly because the "classic" implementation by "static links" doesn’t fit CIL/ECMA-335 or C99 backends; this version of Oberon+ supports an implementation based on hidden var parameters, which is feasible with the mentioned backends.

A procedure body may have no statements in which case the ident after the END reserved word can also be left out; in a function procedure with no statements a return statement with a default value is assumed.

Syntax:
ProcedureDeclaration = ProcedureHeading [';']
                       ProcedureBody END [ ident ]
ProcedureHeading     = ( PROCEDURE | PROC )
					   [Receiver] identdef [ FormalParameters ]
ProcedureBody        = DeclarationSequence
                       [ BEGIN StatementSequence
                       | ReturnStatement [';'] ]
Receiver             = '(' [VAR] ident ':' ident ')'
DeclarationSequence  = { CONST { ConstDeclaration [';'] }
					   | TYPE { TypeDeclaration [';'] }
					   | VAR { VariableDeclaration [';'] }
					   | ProcedureDeclaration [';'] }

If a procedure declaration specifies a receiver parameter, the procedure is considered to be bound to a type (see Type-bound procedures).

10.1. Formal parameters

Formal parameters are identifiers declared in the formal parameter list of a procedure. They correspond to actual parameters specified in the procedure call. The correspondence between formal and actual parameters is established when the procedure is called. There are three kinds of parameters, value, variable (VAR) and IN parameters, indicated in the formal parameter list by the absence or presence of the reserved words VAR and IN.

Value parameters are local variables to which the value of the corresponding actual parameter is assigned as an initial value. VAR parameters correspond to actual parameters that are variables, and they stand for these variables.

IN parameters are like VAR parameters, but they are read-only in the procedure body. If an IN parameters is of ARRAY or RECORD type, then also the elements or fields are transitively read-only in the procedure body.

Note
IN parameters of pointer type are supported, but the dereferenced ARRAY or RECORD is not read-only in the procedure body. IN parameters of pointer type are mostly relevant for generic modules (see Generics).

The scope of a formal parameter extends from its declaration to the end of the procedure block in which it is declared. A function procedure without parameters must have an empty parameter list. It must be called by a function designator whose actual parameter list is empty too. The result type of a procedure cannot be an open array.

Note
In contrast to previous Oberon versions the return type of a procedure may also be a record or array type, and it is possible to ignore the return value of a function procedure call.
Syntax:
FormalParameters = '(' [ FPSection { [';'] FPSection } ] ')'
                   [ ':' ReturnType ]
ReturnType       = type
FPSection        = [ VAR | IN ] ident { [','] ident }
                   ':' FormalType
FormalType       = type

Let Tf be the type of a formal parameter f and Ta the type of the corresponding actual parameter a. If Tf is an open array, then Ta must be array compatible to f; the lengths of f are taken from a. Otherwise Ta must be parameter compatible to f (see Definition of terms).

Note
Also value parameters can have an open array type, but for efficiency reasons (to avoid unneccessary copying) open arrays should be VAR or IN parameters.
Examples:
proc ReadInt(var x: integer)
  var i: integer; ch: char
begin i := 0; Read(ch)
  while ("0" <= ch) & (ch <= "9") do
    i := 10*i + (ord(ch)-ord("0")); Read(ch)
  end
  x := i
end ReadInt

proc WriteInt(x: integer) // 0 <= x <100000
var i: integer; buf: [5]integer
begin i := 0
  repeat buf[i] := x mod 10; x := x div 10; inc(i) until x = 0
  repeat dec(i); Write(chr(buf[i] + ord("0"))) until i = 0
end WriteInt

proc WriteString(s: []char)
  var i: integer
begin i := 0
  while (i < len(s)) & (s[i] # 0x) do Write(s[i]); inc(i) end
end WriteString

proc log2(x: integer): integer
  var y: integer // assume x>0
begin
  y := 0; while x > 1 do x := x div 2; inc(y) end
  return y
end log2

10.2. Type-bound procedures

Procedures may be associated with a record type declared in the same scope. The procedures are said to be bound to the record type. The binding is expressed by the type of the receiver in the heading of a procedure declaration. The receiver may be either a variable (VAR or IN) parameter of record type T or a value parameter of type POINTER TO T (where T is a record type). The procedure is bound to the type T and is considered local to it.

Syntax:
ProcedureHeading = ( PROCEDURE | PROC )
				   [Receiver] identdef [ FormalParameters ]
Receiver         = '(' [VAR|IN] ident ':' ident ')'

If a procedure P is bound to a type T0, it is implicitly also bound to any type T1 which is an extension of T0. However, a procedure P' (with the same name as P) may be explicitly bound to T1 in which case it overrides the binding of P. P' is considered a redefinition of P for T1. The formal parameters of P and P' must match (see Definition of terms). If P and T1 are exported (see Declarations and scope rules), P' must be exported too.

Note
The name of a type-bound procedure must be unique within the type to which it is bound, not within the scope in which it is declared.

If v is a designator and P is a type-bound procedure, then v.P denotes that procedure P which is bound to the dynamic type of v. Note, that this may be a different procedure than the one bound to the static type of v. v is passed to `P’s receiver according to the parameter passing rules specified in Chapter Formal parameters.

If r is the receiver parameter of P declared with type T, r.P^ denotes the (redefined, sometimes calles super) procedure P bound to a base type of T.

Examples:
proc (t: Tree) Insert (node: Tree)
  var p, father: Tree
begin p := t
  repeat father := p
    if node.key = p.key then return end
    if node.key < p.key then
      p := p.left
    else
      p := p.right
    end
  until p = nil
  if node.key < father.key then
    father.left := node
  else
    father.right := node
  end
  node.left := nil; node.right := nil
end Insert

proc (t: CenterTree) Insert (node: Tree) // redefinition
begin
  WriteInt(node(CenterTree).width)
  t.Insert^(node)  // calls the Insert procedure bound to Tree
end Insert

Type-bound procedure declarations may be nested and have access to constants, types and procedures declared in the environment of the type-bound procedure (unless concealed by a local declaration), but they don’t have access to the parameters or local variables of outer procedures.

Note
A type-bound procedure can still include nested procedures which have access to its parameters and local variables.

10.3. Type-bound procedure types

Variables of a type-bound procedure type T have a type-bound procedure or NIL as value. To assign a type-bound procedure P to a variable of a type-bound procedure type T, the right side of the assignment must be a designator of the form v^.P or v.P, where v is a pointer to record and P is a procedure bound to this record. Note, that the dynamic type of v determines which procedure is assigned; this may be a different procedure than the one bound to the static type of v. The formal parameter lists and result types (see Formal parameters) of P and T must match (see Definition of terms). The same rules apply when passing a type-bound procedure to a formal argument of a type-bound procedure type.

Syntax:
ProcedureType = PROCEDURE '(' ( POINTER | '^' ) ')' [FormalParameters]

10.4. Predeclared procedures

The following table lists the predeclared procedures. Some are generic procedures, i.e. they apply to several types of operands. v stands for a variable, x and n for expressions, and T for a type.

10.4.1. Predeclared function procedures

Name Argument type Result type Function

ABS(x)

numeric type

type of x

absolute value

CAP(x)

CHAR

CHAR

corresponding capital letter (only for the ASCII subset of the CHAR type)

BITAND(x,y)

x, y: INT32 or INT64

INT32 or INT64

bitwise AND; result is INT64 if x or y is INT64, else INT32

BITASR(x,n)

x: INT32 or INT64, n: INT32

INT32 or INT64

arithmetic shift right by n bits, where n >= 0 and n < SIZE(x)*8; result is INT64 if x is INT64, else INT32

BITNOT(x)

x: INT32 or INT64

INT32 or INT64

bitwise NOT; result is INT64 if x or y is INT64, else INT32

BITOR(x,y)

x, y: INT32 or INT64

INT32 or INT64

bitwise OR; result is INT64 if x or y is INT64, else INT32

BITS(x)

x: INT32

SET

set corresponding to the integer; the first element corresponds to the least significant digit of the integer and the last element to the most significant digit.

BITSHL(x,n)

x: INT32 or INT64, n: INT32

INT32 or INT64

logical shift left by n bits, where n >= 0 and n < SIZE(x)*8; result is INT64 if x is INT64, else INT32

BITSHR(x,n)

x: INT32 or INT64, n: INT32

INT32 or INT64

logical shift right by n bits, where n >= 0 and n < SIZE(x)*8; result is INT64 if x is INT64, else INT32

BITXOR(x,y)

x, y: INT32 or INT64

INT32 or INT64

bitwise XOR; result is INT64 if x or y is INT64, else INT32

CAST(T,x)

T:enumeration type x:ordinal number

enumeration type

the enum item with the ordinal number x; halt if no match

T,x: integer type

T

convert integer types, accept possible loss of information

T, x: cpointer to cstruct or void

T

unsafe cast of a C pointer (see C Types)

T: integer type, x: cpointer to void

T

convert C pointer to integer (see C Types)

T: cpointer to void, x: integer type

T

reinterpret integer x as a C pointer (see C Types)

CHR(x)

integer type

CHAR

Latin-1 character with ordinal number x

DEFAULT(T)

T = basic type

T

zero for numeric and character types, false for boolean, empty set

T = enumeration type

T

same as MIN(T)

T = pointer/proc type

T

nil

T = record/array type

T

all fields/elements set to their DEFAULT type

FLOOR(x)

x: REAL or LONGREAL

INT32 or INT64

largest integer not greater than x; result is INT64 if x is LONGREAL, else INT32

FLT(x)

x: INT32 or INT64

REAL or LONGREAL

Convert integer to real type; result is LONGREAL if x was INT64, else REAL, accepting potential loss of information

LDCMD(m,c)

m,c: string

PROCEDURE

dynamically loads the command procedure with name c from the Oberon+ module with name m; returns NIL if not successful

LDMOD(n)

n: string

BOOLEAN

dynamically loads the Oberon+ module with the given name n; returns TRUE if successful

LEN(v, n)

v: array n: INT32

INT32

length of v in dimension n (first dimension = 0)

LEN(v)

v: array

INT32

equivalent to LEN(v, 0)

v: string

INT32

length of string (including the terminating 0X)

LONG(x)

x: INT8 or BYTE

INT16

identity

x: INT16

INT32

x: INT32

INT64

x: REAL

LONGREAL

x: CHAR

WCHAR

projection

MAX(T)

T = basic type

T

maximum value of type T

T = SET

INT32

maximum element of a set

T = enumeration type

T

last element of the enumeration

MAX(x,y)

x,y: numeric type

numeric type

greater of x and y, returns smallest numeric type including both arguments

x,y: character type

character type

greater of x and y, returns smallest character type including both arguments

MIN(T)

T = basic type

T

minimum value of type T

T = SET

INT32

0

T = enumeration type

T

first element of the enumeration

MIN(x,y)

x,y: numeric type

numeric type

smaller of x and y, returns smallest numeric type including both arguments

x,y: character type

character type

smaller of x and y, returns smallest character type including both arguments

ODD(x)

integer type

BOOLEAN

x MOD 2 = 1

ORD(x)

x: CHAR or WCHAR

BYTE or SHORT

ordinal number of x

x: enumeration type

INT32

ordinal number of the given identifier

x: BOOLEAN

BYTE

TRUE = 1, FALSE = 0

x: set type

INT32

number representing the set; the first element corresponds to the least significant digit of the number and the last element to the most significant digit.

SHORT(x)

x: INT64

INT32

identity

x: INT32

INT16

identity

x: INT16

INT8

identity

x: LONGREAL

REAL

identity (truncation possible)

x: WCHAR

CHAR

projection (0x if there is no projection)

SIZE(T)

any type

INT32

number of bytes required by T

STRLEN(s)

s: array of char or wchar

INT32

dynamic length of the string up to and not including the terminating 0X

s: string literal

WCHR(x)

integer type

WCHAR

Unicode BMP character with ordinal number x

10.4.2. Deprecated predeclared functions for backward compatibility

Name Argument type Result type Function

ASH(x, n)

x: INT32 or INT64, n: INT32

INT32 or INT64

Same as LSL(x,n) for positive n, same as ASR(x,-n) for negative n

ASR(x, n)

x: INT32 or INT64, n: INT32

INT32 or INT64

signed shift right, x DIV 2n_MOD_w, with w bitwidth of x; result is INT64 if x is INT64, else INT32

ENTIER(x)

real type

INT64

largest integer not greater than x

LSL(x,n)

x: INT32 or INT64, n: INT32

INT32 or INT64

logical shift left, x * 2n_MOD_w, with w bitwidth of x; result is INT64 if x is INT64, else INT32

ROR(x, n)

x, n: INT32

INT32

x rotated right by n bits (where the fading right bits re-appear at the left side)

Note
The functions ENTIER(x) or FLOOR(x) round down to the largest integer not greater than x. The functions are identical, but the former is defined in Oberon-2 and the latter in Oberon-07.
Exampes:
FLOOR(1.5) = 1; FLOOR(-1.5) = -2
Note
The Oberon and Oberon-2 built-in function ASH was replaced by ASR and LSL in Oberon-07; note that ASR(x,-n) gives not the same result as LSL(x,n) for a given n. LSL(x,n) with positive n is identical to BITSHL(x,n), and ASR(x,n) with positive n is identical to BITASR(x,n).

10.4.3. Predeclared proper procedures

Name Argument types Function

ASSERT(x)

x: Boolean expression

terminate program execution if not x

ASSERT(x, n)

x: Boolean expression

terminate program execution if not x

n: integer constant

BYTES(a,n)

a: ARRAY OF BYTE/CHAR; n: numeric or set type

stores the raw memory of n in a; if the length of a is smaller than the number of bytes required to represent n, the program halts

DEC(v)

integer type

v := v - 1

enumeration type

previous ident in enumeration

DEC(v, n)

v, n: integer type

v := v - n

EXCL(v, x)

v: SET; x: integer type

v := v - {x}

HALT(n)

integer constant

terminate program execution

INC(v)

integer type

v := v + 1

enumeration type

next ident in enumeration

INC(v, n)

v, n: integer type

v := v + n

INCL(v, x)

v: SET; x: integer type

v := v + {x}

NEW(v)

pointer to record or

allocate v^

fixed array

NEW(v,x0,…​,xn)

v: pointer to open array

allocate v^ with lengths

xi: integer type

x0..xn

NUMBER(n,a)

n: numeric or set type; a: ARRAY OF BYTE/CHAR

interprets the bytes in a as number of the numeric type of n and assigns it to n; if the length of a is smaller than the number of bytes required to represent n, the program halts

PCALL(e,p,a0,…​,an)

VAR e: pointer to anyrec; p: proper procedure type; ai: actual parameters

call procedure type p with arguments a0…​an corresponding to the parameter list of p; e becomes nil in normal case and gets the pointer passed to RAISE() otherwise

RAISE(e)

e: pointer to anyrec

terminates the last protected function called and returns e as the exception value; RAISE() never returns

In ASSERT(x, n) and HALT(n), the interpretation of n is left to the underlying system implementation.

The predeclared procedure NEW is used to allocate data blocks in free memory. There is, however, no way to explicitly dispose an allocated block. Rather, the Oberon+ runtime uses a garbage collector to find the blocks that are not used any more and to make them available for allocation again. A block is in use as long as it can be reached from a global pointer variable via a pointer chain. Cutting this chain (e.g., setting a pointer to NIL) makes the block collectable.

Note
The procedures BYTES(a,n) and NUMBER(n,a) are a replacement of the VAR ARRAY OF BYTES trick supported by many Oberon implementations, where any numeric type or array of numeric types can be used as actual parameter.

10.4.4. Deprecated predeclared proper procedures for backward compatibility

Name Argument types Function

COPY(x, v)

x: CHAR array, string

v := x

v: CHAR array

PACK(x, n)

VAR x:REAL; n:INT32

pack x and n into x

UNPK(x, n)

VAR x:REAL; VAR n:INT32

unpack x into x and n

The parameter n of PACK represents the exponent of x. PACK(x, y) is equivalent to x := x * 2y. UNPK is the reverse operation. The resulting x is normalized, such that 1.0 <= x < 2.0.

COPY allows the assignment of a string or a CHAR array containing a terminating 0X to another CHAR array. If necessary, the assigned value is truncated to the target length minus one. The target will always contain 0X as a terminator.

11. Modules

A module is a collection of declarations of constants, types, variables, and procedures, together with a sequence of statements for the purpose of assigning initial values to the variables. A module constitutes a text that is compilable as a unit (compilation unit).

Syntax:
module     = MODULE ident [ MetaParams ] [';']
             { ImportList | DeclarationSequence }
	         [ BEGIN StatementSequence ] END ident ['.']
ImportList = IMPORT import { [','] import } [';']
import     = [ ident ':=' ] ImportPath ident [ MetaActuals ]
ImportPath = { ident '.' }

The import list specifies the names of the imported modules. If a module A is imported by a module M and A exports an identifier x, then x is referred to as A.x within M.

If A is imported as B := A, the object x must be referenced as B.x. This allows short alias names in qualified identifiers.

In Oberon+ the import can refer to a module by means of a module name optionally prefixed with an import path. There is no requirement that the import path actually exists in the file system, or that the source files corresponding to an import path are in the same file system directory. It is up to the compiler how source files are mapped to import paths. An imported module with no import path is first looked up in the import path of the importing module.

A module must not import itself.

Identifiers that are to be exported (i.e. that are to be visible in client modules) must be marked by an export mark in their declaration (see Chapter Declarations and scope rules).

The statement sequence following the symbol BEGIN is executed when the module is loaded, which is done after the imported modules have been loaded. It follows that cyclic import of modules is illegal.

Listing 3. Example with original Oberon-2 syntax
MODULE Lists;
	IMPORT Out;
    TYPE
        List*    = POINTER TO ListNode;
        ListNode = RECORD
            value : INTEGER;
            next  : List;
        END;

    PROCEDURE (l : List) Add* (v : INTEGER);
    BEGIN
        IF l = NIL THEN
            NEW(l);           (* create record instance *)
            l.value := v
        ELSE
            l.next.Add(v)
        END
    END Add;

    PROCEDURE (t: List) Write*;
    BEGIN
    	Out.Int(t.value,8); Out.Ln;
    	IF t.next # NIL THEN t.next.Write END;
    END Write;
END Lists.
Listing 4. Same example with syntactic simplifications
module Lists2
	import Out
    type
        List*     = ^record
            value : integer
            next  : List
        end

    proc (l : List) Add* (v : integer)
    begin
        if l = nil then
            new(l)           // create record instance
            l.value := v
        else
            l.next.Add(v)
        end
    end Add

    proc (t: List) Write*
    begin
    	Out.Int(t.value,8); Out.Ln
    	if t.next # nil then t.next.Write end
    end Write
end Lists2

11.1. Generics

Oberon+ supports generic programming. Modules can be made generic by adding formal meta parameters. Meta parameters represent types or constants; the latter include procedures. Meta parameters default to types, but can be explicitly prefixed with the TYPE reserved word; the CONST prefix designates a constant meta parameter. A meta parameter can be constrained with a named type, in which case the actual meta parameter must correspond to this type; the correspondence is established when the generic module is instantiated; the type of the actual meta parameter must be assignment compatible with the constraint type (see Definition of terms).

Generic modules can be instantiated with different sets of meta actuals which enables the design of reusable algorithms and data structures. The instantiation of a generic module occurs when importing it. A generic module can be instantiated more than once in the same module with different actual meta parameters. See also Modules.

Syntax:
MetaParams       = '(' MetaSection { [';'] MetaSection } ')'
MetaSection      = [ TYPE | CONST ] ident { [','] ident } [ ':' TypeConstraint ]
TypeConstraint   = NamedType
MetaActuals      = '(' ConstExpression { [','] ConstExpression } ')'
module = MODULE ident [ MetaParams ] [';'] { ImportList | DeclarationSequence }
	[ BEGIN StatementSequence ] END ident ['.']
ImportList = IMPORT import { [','] import } [';']
import = [ ident ':=' ] ImportPath ident [ MetaActuals ]

Meta parameters can be used within the generic module like normal types or constants. If no type constraint is present, the types and constants can be used wherever no information about the actual type is required; otherwise the type constraint determines the permitted operations. The rules for same types and equal types apply analogously to meta parameters, and subsequently also the corresponding assignment, parameter and array compatibility rules.

Note
It follows that a type meta parameter can only be the base type of a record or a pointer if a record or pointer to record type constraint is present(because in absence of the type constraint we don’t know before instantiation whether the type parameter represents e.g. a record or not); but it is e.g. possible to use a record declared in the same or another generic module as a base type.

See also this example.

11.2. Definitions

A DEFINITION is a special kind of MODULE which only includes public declarations. The export mark * is redundant, but - can be used to mark read-only exports (see Declarations and scope rules).

Definitions can be used when the implementation of a module is not available or done in another programming language than Oberon+.

Syntax:
definition   = DEFINITION ident [';']  [ ImportList ] DeclarationSequence2 END ident ['.']
DeclarationSequence2 = { CONST { ConstDeclaration [';'] }
			   | TYPE { TypeDeclaration [';'] }
			   | VAR { VariableDeclaration [';'] }
			   | ProcedureHeading [';'] }

12. Foreign Function Interface

Oberon+ includes the possibility to call functions from and exchange data with external C shared libraries. To avoid confusion with existing POINTER, ARRAY and RECORD types, Oberon+ includes special C compatible types.

Note
Oberon+ has no SYSTEM module. Use the foreign function interface instead and the predeclared BITop() function procedures to convert basic types to byte arrays and vice versa.

12.1. External Library Modules

An external library module is a DEFINITION module with an attribute list, and with a few more differences to normal DEFINITIONs, which will be discussed in the following.

Syntax
definition = DEFINITION ident attributeList [';'] [ ImportList ] DeclarationSequence3 END ident ['.']
attributeList = '[' [ attribute { ',' attribute }  ] ']'
attribute = ident { ConstExpression }
DeclarationSequence3 =
	{ CONST { ConstDeclaration [';'] }
	| TYPE { TypeDeclaration [';'] }
	| ProcedureHeading [ attributeList ] [';'] }

An external library module can only import other external library modules, but not ordinary or definition modules. Module variables are not supported.

The following attributes are defined on module level:

Name Type, Value Description

extern

string, 'C'

optional; as soon as an attribute list is present (even an empty one), extern 'C' is assumed

dll

string

mandatory; the name of the library; on Windows ".dll" is appended; on Linux "lib" is prepended and ".so" is appended

prefix

string

optional; the name under which a procedure is known in the external library corresponds to the procedure name combined with the prefix

12.2. C Types

In an external library module only C types and named types pointing to C types can be declared. A C type is either a CSTRUCT, CUNION, CARRAY, CPOINTER, procedure type or basic type. Structured C types are not subject to garbage collection and cannot be instantiated with NEW.

Syntax:
C_Type = ( CSTRUCT | CUNION ) FieldList { [';'] FieldList} END
		| ( CPOINTER TO | '*' ) ( C_Type | VOID )
		| CARRAY [ length ] OF C_Type
		| ( PROCEDURE | PROC ) [FormalParameters]
		| BasicType

A CARRAY is a one-dimensional array of C_Types. A CARRAY declared without length is an open array. An open CARRAY can only be used as a CPOINTER base type. LEN(v) is undefined if v is an open CARRAY. An open CARRAY cannot be on the left or right side of an assignment unless the element type is CHAR or WCHAR.

A CPOINTER can point to CSTRUCT, CUNION, CARRAY or VOID.

CSTRUCT and CUNION are the Oberon+ representation of C struct and C union. Field types are restricted to C_Types.

The basic types correspond to the ones defined in [Basic Types]. BOOLEAN and BYTE map to uint8_t, CHAR to the C char type, INT16 to int16_t, WCHAR to uint16_t, INT32 to int32_t, INT64 to int64_t, REAL to float, LONGREAL to double, and SET to uint32_t.

The formal parameter types of a procedure type compatible with an external library module can only be of C_Type. VAR and IN are not supported in external library modules, and CARRAY cannot be passed by value.

Note
Instead of writing cpointer to T one can simply write *T; cpointer to carray of T can be abbreviated by *[]T. In C an out parameter is usually implemented by a pointer; when the value to be put out is itself a pointer, the parameter is a pointer to pointer; Oberon+ doesn’t support pointer to pointer, but the same effect can be achieved by a pointer to an array of length one of the pointer type, e.g. *[1]*T, or just an open array *[]*T for simplicity; but of course one can also write cpointer to carray of cpointer to T, or equivalently CPOINTER TO CARRAY OF CPOINTER TO T.
Note
In Oberon+ POINTER, RECORD and ARRAY are considered safe, whereas CPOINTER, CSTRUCT, CUNION and CARRAY are considered unsafe; of course, it must always be assessed on a case-by-case basis whether a specific application of C_Types is safe or unsafe.

12.3. Type interoperability

ARRAY and RECORD types cannot be used in external library modules, but it is perfectly legal to use C_Types as formal parameter, or local or module variable types in regular Oberon+ modules. CPOINTER (but not structured C_Types) can be used as field or element type in RECORD or ARRAY. Structured C_Types (in contrast to CPOINTER to structured C_Types) cannot be used as formal VAR or IN parameters.

POINTER and CPOINTER are disjoint in what they can point to and it is not possible to assign from a POINTER to a CPOINTER or vice versa.

A CARRAY and an ARRAY are only assignment compatible if both element types are either CHAR or WCHAR. A CARRAY cannot be passed to a parameter of ARRAY type.

12.4. External procedures

The formal parameter types of an external procedure can only be of C_Type. VAR and IN are not supported, and CARRAY cannot be passed by value.

The following attributes can be applied to each procedure:

Name Type, Value Description

dll

string

optional; override of the module wide library name for the given procedure

prefix

string

optional; override of the module wide prefix for the given procedure

alias

string

optional; the name by which the given procedure is known in the external library

varargs

-

optional; if present the given procedure accepts optional arguments (in addition to the ones specified); same as the …​ parameter in C

12.5. Implicit address-of operation

Oberon+ implicitly takes the address of a CSTRUCT, CUNION or CARRAY

  • when passing an actual value of this type to a formal parameter of CPOINTER type,

  • and when assigning a value of this type to a variable of CPOINTER type;

in both cases the CPOINTER base type must be assignment compatible with the actual or assigned value type (see Definition of terms); as an extension to this rule, each structured C_Type is compatible with a CPOINTER TO VOID.

Oberon+ supports passing an actual parameter of ARRAY type or a string literal to a formal parameter of CPOINTER TO CARRAY type of a procedure in an external library module, if the CARRAY and ARRAY element types are assignment compatible; as an extension to this rule, an ARRAY of an unstructured type (including CPOINTER), a string literal or an INT32 (and its included types) is compatible with a CPOINTER TO VOID. The compiler or runtime system in use is free to either create a CARRAY copy of the ARRAY or string literal, or to directly pass the memory address for efficiency reasons; in the latter case the compiler or runtime system assure that the memory address remains valid during the call.

Note
Remember that taking the address of a variable is a potentially unsafe operation because the memory location the address points to could become invalid.

13. Source code directives

Source code directives are used to set configuration variables in the source text and to select specific pieces of the source text to be compiled (conditional compilation). Oberon+ uses the syntax recommended in [Oak95].

13.1. Configuration Variables

Configuration variables can be set or unset in the source code using the following syntax:

Syntax:
directive = '<*' ident ( '+' | '-' ) '*>'

Each variable is named by an ident which follows the syntax specified in Identifiers. Variable names have compilation unit scope which is separate from all other scopes of the program. Configuration variable directives can be placed anywhere in the source code. The directive only affects the present compilation unit, starting from its position in the source code.

Example:
<* WIN32+ *>
<* WIN64- *>
Note
Usually the compiler provides the possibility to set configuration variables, e.g. via command line interface.

13.2. Conditional compilation

Conditional compilation directives can be placed anywhere in the source code. The following syntax applies:

Syntax:
directive = '<*' [ scIf | scElsif | scElse | scEnd ] '*>'
scIf   	  = IF scExpr THEN
scElsif   = ELSIF condition THEN
scElse 	  = ELSE
scEnd 	  = END
condition = scTerm { OR scTerm }
scTerm 	  = scFactor {'&' scFactor}
scFactor  = ident | '(' condition ')' | '~' scFactor

An ELSIF or ELSE directive must be preceded by an IF or another ELSIF directive. Each IF directive must be ended by an END directive. The directives form sections of the source code. Only the section the condition of which is TRUE (or the section framed by ELSE and END directive otherwise) is visible to the compiler. Conditions are boolean expressions. Ident refers to a configuration variable. When a configuration variable is not explicitly set it is assumed to be FALSE. Each section can contain nested conditional compilation directives.

Example:
<* if A then *>
  println("A")
<* elsif B & ~C then *>
  println("B & ~C")
<* else *>
  println("D")
<* end *>

Appendix A: Definition of terms

Integer types

BYTE, INT8, INT16, INT32, INT64, SHORTINT, INTEGER, LONGINT

Real types

REAL, LONGREAL

Numeric types

integer types, real types

Same types

Two variables a and b with types Ta and Tb are of the same type if

  1. Ta and Tb are both denoted by the same type identifier, or

  2. Ta is declared to equal Tb in a type declaration of the form Ta = Tb, or

  3. a and b appear in the same identifier list in a variable, record field, or formal parameter declaration and are not open arrays.

Equal types

Two types Ta and Tb are equal if

  1. Ta and Tb are the same type, or

  2. Ta and Tb are open array types with equal element types, or

  3. Ta and Tb are procedure types whose formal parameters match, or

  4. Ta and Tb are pointer types with equal base types.

Type inclusion

Numeric types include (the values of) smaller numeric types. WCHAR includes the values of CHAR. See here for more information.

Type extension (record)

Given a type declaration Tb = RECORD(Ta)…​END, Tb is a direct extension of Ta, and Ta is a direct base type of Tb. A type Tb is an extension of a type Ta (Ta is a base type of Tb) if

  1. Ta and Tb are the same types, or

  2. Tb is a direct extension of Ta.

  3. Ta is of type ANYREC.

Type extension (pointer)

If Pa = POINTER TO Ta and Pb = POINTER TO Tb , Pb is an extension of Pa (Pa is a base type of Pb) if Tb is an extension of Ta.

Note
The extension relation is between record types or between pointer to record types; there is no extension relation between a pointer to record and a record type or between a record and a pointer to record type.
Assignment compatible

An expression e of type Te is assignment compatible with a variable v of type Tv if one of the following conditions hold:

  1. Te and Tv are the same type;

  2. Te and Tv are numeric or character types and Tv includes Te [3];

  3. Tv is a SET type and Te is of INT32 or smaller type;

  4. Tv is a BYTE type and Te is a Latin-1 character type;

  5. Tv is an integer type and Te is a enumeration type;

  6. Te and Tv are record types and Te is a type extension of Tv and the dynamic type of v is Tv;

  7. Te and Tv are pointer types and Te is a type extension of Tv or the pointers have equal base types;

  8. Tv is a pointer or a procedure type and e is NIL;

  9. Te is an open array and Tv is an array of equal base type;

  10. Tv is an array of WCHAR, Te is a Unicode BMP or Latin-1 string or character array, and STRLEN(e) < LEN(v);

  11. Tv is an array of CHAR, Te is a Latin-1 string or character array, and STRLEN(e) < LEN(v);

  12. Tv is a procedure type and e is the name of a procedure whose formal parameters match those of Tv.

Parameter compatible

An actual parameter a of type Ta is parameter compatible with a formal parameter f of type Tf if

  1. Tf and Ta are equal types, or

  2. f is a value parameter and Ta is assignment compatible with Tf, or

  3. f is an IN or VAR parameter Ta must be the same type as Tf, or Tf must be a record type and Ta an extension of Tf.

Array compatible

An actual parameter a of type Ta is array compatible with a formal parameter f of type Tf if

  1. Tf and Ta are the equal type, or

  2. Tf is an open array, Ta is any array, and their element types are array compatible, or

  3. Tf is an open array of CHAR and Ta is a Latin-1 string, or

  4. Tf is an open array of WCHAR and Ta is a Unicode BMP or Latin-1 string, or

  5. Tf is an open array of BYTE and Ta is a byte string.

Expression compatible

For a given operator, the types of its operands are expression compatible if they conform to the following table (which shows also the result type of the expression). CHAR and WCHAR arrays that are to be compared must contain 0X as a terminator. Type T1 must be an extension of type T0:

operator first operand second operand result type

+ - *

numeric

numeric

smallest numeric type including both operands

/

numeric

numeric

smallest real type type including both operands

+ - * /

SET

SET

SET

DIV MOD

integer

integer

smallest integer type type including both operands

OR & ~

BOOLEAN

BOOLEAN

BOOLEAN

= # <

numeric

numeric

BOOLEAN

<= > >=

CHAR

CHAR

BOOLEAN

CHAR array, string

CHAR array, string

BOOLEAN

= #

BOOLEAN

BOOLEAN

BOOLEAN

SET

SET

BOOLEAN

NIL, pointer type T0 or T1

NIL, pointer type T0 or T1

BOOLEAN

procedure type T, NIL

procedure type T, NIL

BOOLEAN

IN

integer

SET

BOOLEAN

IS

type T0

type T1

BOOLEAN

Matching formal parameter lists

Two formal parameter lists match if

  1. they have the same number of parameters, and

  2. parameters at corresponding positions have equal types, and

  3. parameters at corresponding positions are both either value, VAR or IN parameters.

Matching result types

The result types of two procedures match if they are either the same type or none.

Appendix B: Syntax of Oberon+

Oberon =  module | definition
qualident = [ ident '.' ] ident
identdef = ident [ '*' | '-' ]
ConstDeclaration = identdef '=' ConstExpression
ConstExpression = expression
TypeDeclaration = identdef '=' type
type = NamedType | enumeration
	| ArrayType | RecordType | PointerType | ProcedureType
NamedType = qualident
MetaParams = '(' MetaSection { [';'] MetaSection } ')'
MetaSection = [ TYPE | CONST ] ident { [','] ident } [ ':' NamedType ]
MetaActuals = '(' ConstExpression { [','] ConstExpression } ')'
enumeration = '('  ident { [','] ident } ')'
ArrayType = ARRAY [ LengthList ] OF type
	 | '[' [ LengthList ] ']' type
LengthList = length {',' length} | VAR varlength {',' varlength}
length     = ConstExpression
varlength  = expression
RecordType = RECORD ['(' BaseType ')'] [FieldListSequence]  END
BaseType = NamedType
FieldListSequence = FieldList [ ';' ] { FieldList [ ';' ] }
FieldList = IdentList ':' type
IdentList = identdef { [','] identdef}
PointerType = ( POINTER TO | '^' ) type
ProcedureType = ( PROCEDURE | PROC ) ['(' ( POINTER | '^' ) ')'] [FormalParameters]
VariableDeclaration = IdentList ':' type
designator = qualident {selector}
selector = '.' ident | '[' ExpList ']' | '^' | '(' qualident ')'
ExpList = expression {',' expression}
expression = SimpleExpression [ relation SimpleExpression ]
relation = '=' | '#' | '<' | '<=' | '>' | '>=' | IN | IS
SimpleExpression = ['+' | '-'] term { AddOperator term }
AddOperator = '+' | '-' | OR
term = factor {MulOperator factor}
MulOperator = '*' | '/' | DIV | MOD | '&'
literal = number | string | hexstring | hexchar | NIL
	| TRUE | FALSE | set
factor = literal
	| designator [ActualParameters]
	| '(' expression ')' | '~' factor
set = '{' [ element {',' element} ] '}'
element = expression ['..' expression]
ActualParameters = '(' [ExpList] ')'
statement = [ assignment | ProcedureCall
	| IfStatement | CaseStatement
	| WithStatement | LoopStatement
	| ExitStatement | ReturnStatement
	| WhileStatement | RepeatStatement | ForStatement ]
assignment = designator ':=' expression
ProcedureCall = designator [ActualParameters]
StatementSequence = statement { [";"] statement}
IfStatement = IF expression THEN StatementSequence
	{ElsifStatement} [ElseStatement] END
ElsifStatement = ELSIF expression THEN StatementSequence
ElseStatement = ELSE StatementSequence
CaseStatement = CASE expression OF ['|'] Case { '|' Case }
	[ ELSE StatementSequence ] END
Case = [ CaseLabelList ':' StatementSequence ]
CaseLabelList = LabelRange { ',' LabelRange }
LabelRange = label [ '..' label ]
label = ConstExpression
WhileStatement = WHILE expression DO StatementSequence
	{ElsifStatement2} END
ElsifStatement2 = ELSIF expression DO StatementSequence
RepeatStatement = REPEAT StatementSequence UNTIL expression
ForStatement = FOR ident ':=' expression TO expression
	[ BY ConstExpression ] DO StatementSequence END
WithStatement = WITH ['|'] Guard DO StatementSequence
	{ '|' Guard DO StatementSequence}
	[ ELSE StatementSequence ] END
Guard = qualident ':' qualident
LoopStatement = LOOP StatementSequence END
ExitStatement = EXIT
ProcedureDeclaration = ProcedureHeading [ ';' ]
	ProcedureBody END ident
ProcedureHeading = ( PROCEDURE | PROC ) [Receiver]
	 identdef [ FormalParameters ]
Receiver = '(' [VAR|IN] ident ':' ident ')'
ProcedureBody = DeclarationSequence
	[ BEGIN StatementSequence
	| ReturnStatement [ ';' ] ]
DeclarationSequence =
	{ CONST { ConstDeclaration [';'] }
	| TYPE { TypeDeclaration [';'] }
	| VAR { VariableDeclaration [';'] }
	| ProcedureDeclaration [';'] }
ReturnStatement = RETURN [ expression ]
FormalParameters = '(' [ FPSection { [';'] FPSection } ] ')'
	[ ':' ReturnType ]
ReturnType = type
FPSection = [ VAR | IN ] ident { [','] ident } ':' FormalType
FormalType = type
module = MODULE ident [ MetaParams ] [';'] { ImportList | DeclarationSequence }
	[ BEGIN StatementSequence ] END ident ['.']
ImportList = IMPORT import { [','] import } [';']
import = [ ident ':=' ] ImportPath ident [ MetaActuals ]
ImportPath = { ident '.' }
definition = DEFINITION ident [';']  [ ImportList ]
	DeclarationSequence2 END ident ['.']
DeclarationSequence2 =
	{ CONST { ConstDeclaration [';'] }
	| TYPE { TypeDeclaration [';'] }
	| VAR { VariableDeclaration [';'] }
	| ProcedureHeading [';'] }
Note
The Foreign Function Interface and Source code directives syntax is not included here.

Appendix C: More Code Examples

Listing 5. Procedural programming
module Fibonacci
  proc calc*(n : integer): integer
    var a, b: integer // comma is optional
  begin
    if n > 1 then
      a := calc(n - 1)
      b := calc(n - 2)
      return a + b
    elsif n = 0 then
      return 0
    else
      return 1
    end
  end calc
  var res: integer
begin
  res := calc(21)
  assert(res = 10946)
end Fibonacci
Listing 6. Generic programming
module Collections(T)
  type Deque* = pointer to record
                      data: pointer to array of T
                      size: integer end
  proc createDeque*(): Deque
    const initial_len = 50
    var this: Deque  // this is initialized to nil
  begin
    new(this); new(this.data,initial_len)
             // semicolon is optional
    return this
    // this and data will be garbage collected
  end createDeque

  proc (this: Deque) append*(in element: T)
  begin
    if this.size = len(this.data) then assert(false) end
    this.data[this.size] := element inc(this.size)
  end append

  type Iterator* = record end
  proc (var this: Iterator) apply*(in element: T) end

  proc (this: Deque) forEach*(var iter: Iterator)
    var i: integer
  begin
    for i := 0 to this.size-1 do
      iter.apply(this.data[i])
    end
  end forEach
end Collections
Listing 7. Object-oriented programming
module Drawing
  import F := Fibonacci
         C := Collections(Figure)

  type Figure* = pointer to record
                   position: record
                     x,y: integer end end
  proc (this: Figure) draw*() end

  type
     Circle* = pointer to record (Figure)
                          diameter: integer end
     Square* = pointer to record (Figure)
                          width: integer end
  proc (this: Circle) draw*() end
  proc (this: Square) draw*() end

  var figures: C.Deque
       circle: Circle
       square: Square

  proc drawAll()
    type I = record(C.Iterator) count: integer end
    proc (var this: I) apply( in figure: Figure )
    begin
      figure.draw(); inc(this.count)
    end apply
    var i: I // count is initialized to zero
  begin
    figures.forEach(i)
    assert(i.count = 2)
  end drawAll
begin
  figures := C.createDeque()
  new(circle)
  circle.position.x := F.calc(3)
  circle.position.y := F.calc(4)
  circle.diameter := 3
  figures.append(circle)
  new(square)
  square.position.x := F.calc(5)
  square.position.y := F.calc(6)
  square.width := 4
  figures.append(square)
  drawAll()
end Drawing
Listing 8. Unicode support
module Unicode
  var
    str: array 32 of char
    ustr: array 32 of wchar
begin
  str := "Isto é português"
  ustr := "美丽的世界,你好!" + " " + str
  println(ustr)
  // prints "美丽的世界,你好! Isto é português"
end Unicode

Appendix D: References

TODO: - array literals, e.g. [ 1, 2, 3 ] or [ [1,2], [3,4], [5,6] ] or like ISO Modula like Array1dType{ 1,2,3 } or Array2dType{ {1,2}, {3,4}, {5,6} } which would also support record literals - allow to register a type-bound procedure as a finalzier for a pointer to record - literals and procedure refs as generic arguments, e.g. like ISO Modula - combine generic modules with source code directives so that the directive can check the type of a type param; add built-in compile time functions to check for non anyrec descendant types (isinteger, isnumber, isreal, isboolean) - means to avoid record assignment - underscores or ' in number literals - embedded type declaration, e.g. cast(type cpointer to void, x)


1. generic modules, inspired by [Ada83]
2. adopted from [Om01]
3. character types include strings with length 1