From Modula-2 Reloaded

Spec: Language Report

Copyright © 2010-2015 B.Kowarsch & R.Sutcliffe. All rights reserved. Reproduction requires written permission.
Status: 2015-10-08 (update in progress)

Lexis

Semantics

Compilation Units

Definition Modules

Export

Definitions

Implementation And Program Modules

Statements

Expressions

Operators

Structured Values

Predefined Identifiers

Predefined Constants

Predefined Types

Predefined Procedures

Predefined Functions

Built-in Compile-Time Macros

Primitives

Pragmas

Mandatory Pragmas

Optional Pragmas

Implementation Defined Pragmas


(To do: transfer missing content from PDF version and update)

Semantics

Compilation Units

EBNF | Syntax Diagram

A compilation unit is a sequence of source code that can be independently compiled. There are four kinds.

Any Modula-2 program consists of exactly one program module and zero or more library modules and blueprints.

Program Modules

A program module represents the topmost level of a Modula-2 program.

At minimum it will consist of a body that contains one or more statements that will be executed when the program is run. Additionally, it may define or declare constants, types, variables and procedures and function procedures of its own, or it may use such entities provided by one or more library modules. It does not provide any such entities to other modules.

Library Modules

Library modules represent repositories of constants, types, variables and procedures and function procedures for use by program modules and other library modules. Entities so provided are said to be exported by the library module.

Additionally, library modules may use entities provided by other library modules. In order to use the entities provided by a library module, the use of the library must be explicitly declared. A library whose use is so declared is said to be imported.

The Definition Part of Library Modules

The definition part of a library module represents the public interface of the library module.

Any entities defined or declared in the public interface of a library module are automatically exported.

The Implementation Part of Library Modules

The implementation part of a library module represents the implementation of the entities defined in its public interface.

Any entities defined or declared in a library's definition part are automatically visible and available in its implementation part without import. By contrast, entities declared only within the implementation part are not visible outside the implementation part. Such entities are said to be encapsulated.

Library Blueprints

A library blueprint represents a specification to enforce the consistency and integrity of libraries.

A blueprint defines constraints and requirements which libraries may be required to meet. A library that is required to meet the constraints and requirements of a blueprint is said to declare conformance to the blueprint. When a library declares conformance to a blueprint, its actual conformance is compiler enforced. Certain language features such as binding procedures and functions to operators and built-in syntax are only available to libraries that declare conformance to certain blueprints.

Importing Libraries

Qualified Import

EBNF | Syntax Diagram

Identifiers defined in the interface of a library module may be imported by other modules using an IMPORT directive. The import brings all exported identifiers into the scope of the importing module. Imported identifiers must be qualified with the exporting module's identifier when it is referenced in the importing module. This is called qualified import and it avoids name conflicts when importing identically named identifiers from different libraries.

Example:

 IMPORT FileIO; (* import of module FileIO *)
 VAR status : FileIO.Status; (* qualified identifier *)

Import With Re-Export

By default, an imported library is not re-exported. That is, a library M1 imported in the definition part of a library M2 is only available within the definition and implementation parts of M2, but not within any client module M3 that imports M2.

A library being imported within a definition part of another library may be re-exported by marking it with a re-export tag. Such a re-export tag is denoted by a plus sign trailing the module identifier in an IMPORT directive.

When a library M3 imports another library M2 that re-exports another library M1, both M1 and M2 will be imported into M3.

Example:

 IMPORT Foo+, Bar+, Baz+; (* import and re-export Foo, Bar and Baz *)

Import Aggregation

A library that imports other libraries for the sole purpose of re-exporting them is called an import aggregator. This facility is useful for importing a collection of libraries or a library framework with a single import statement.

Example:

 DEFINITION MODULE FooBarBaz;
 IMPORT Foo+, Bar+, Baz+;
 END FooBarBaz.
 MODULE Client;
 IMPORT FooBarBaz; (* equivalent to: IMPORT Foo, Bar, Baz; *)

Importing Modules as Types

A type defined in the definition part of a library with the same name as the library is called a module type. When a library with a module type is imported, an unqualified alias for the module type is automatically defined in the importing module. This facility is useful in the construction of abstract data types as library modules.

Example:

 DEFINITION MODULE Colour;
 TYPE Colour = ( red, green, blue );
 (* public interface *)
 END Colour.
 IMPORT Colour; (* import module Colour *)
 VAR colour : Colour; (* type referenced as Colour instead of Colour.Colour *)

Unqualified Aliasing

An IMPORT directive for single library may be followed by an ALIAS list. The ALIAS list contains one or more unqualified identifiers of the imported library. Imported identifiers whose unqualified names appear in an ALIAS list may then also be referenced by their unqualified identifiers within the importing module. This is called unqualified aliasing and it may cause name conflicts when aliasing identically named identifiers of different libraries. In the event of a name conflict a compile time error shall occur.

Example:

 IMPORT FileIO ALIAS Status;
 VAR status : Status; (* unqualified alias for FileIO.Status *)

Repeat Import

Import of an Already Imported Module

Import of a module that has already been imported into the same module scope is permissible. Only the first import is significant. Any subsequent imports are redundant. A redundant import has no effect but shall cause a soft compile time warning.

Unqualified Aliasing of an Already Aliased Identifier

Aliasing of a qualified identifier that has already been aliased within the same module scope is permissible. Only the first aliasing is significant. Any subsequent aliasing is redundant. Redundant aliasing has no effect but shall cause a soft compile time warning.


Definition Modules

EBNF | Syntax Diagram

A definition module represents the definition part of a library, that is, its public interface. Any identifier defined in the definition part is available for use without import in the corresponding implementation part of the library and it is automatically exported, that is, it is available for import by other modules.

Example:

 DEFINITION MODULE Counting;
 PROCEDURE LetterCount ( str : ARRAY OF CHAR ) : CARDINAL;
 PROCEDURE DigitCount ( str : ARRAY OF CHAR ) : CARDINAL;
 END Counting.

Definitions

EBNF | Syntax Diagram

Constant Definitions

A constant is an immutable value determined at compile time. Its value is specified by a constant expression in its definition. A constant may not be defined as an alias of a module, a variable, a type or a procedure.

Examples:

 CONST zero = 0; maxInt = TMAX(INTEGER); buffSize = 100 * TSIZE(INTEGER) + 42; 

Variable Declarations

A variable is a container for a mutable value. A variable is always associated with a type and it can only hold values of its type. Its type is specified in its definition. Its definition is immutable. The value of a variable is undetermined when it is allocated. A value may be assigned at runtime. However, variables of pointer types are automatically intialised to hold the invalid pointer value NIL.

Examples:

 VAR ch : CHAR; n, m : CARDINAL; i, j : INTEGER; x, y, z : REAL; 

Global Variables

A variable declared in the top level of a module has a global life span. It exists throughout the runtime of the program. However, it does not have global scope. It is only visible within the module where it is declared, and it it is exported, within modules that import it.

A variable declared in the top level of a library module's definition part is always exported immutable. It may be assigned to within the library module's implementation part but it may not be assigned to within modules that import it. A pointer variable declared in the top level of a definition part shall cause a promotable compile time warning unless it is of an opaque type or a POINTER TO CONST type.

Local Variables

A variable declared within a procedure has local life span and local scope. It only exists during the lifetime of the procedure and it is only visible within the procedure where it is declared and procedures local to the procedure where it is declared.

Type Definitions

Derived Types

A derived type is a nominal derivative of another type. The type it is derived from is called its base type. The base type may be any type. A derived type obtains its properties from its base type, except for its identifier. It is defined using the = symbol followed by the base type in the type constructor.

Examples:

 TYPE Celsius = REAL; Fahrenheit = REAL;

Due to strict name equivalence, derived types and their base types are incompatible because their identifiers are different.

Example:

 VAR celsius : Celsius; fahrenheit : Fahrenheit;
 celsius := fahrenheit; (* compile time error: incompatible types *)

To assign values across type boundaries, type conversion is required.

Example:

 celsius := (fahrenheit :: Celsius - 32.0) * 100.0/180.0; (* type conversion *)

ALIAS Types

An ALIAS type is a nominal equivalence type of another type. The type it is an equivalence type of is called its base type. The base type may be any type. An ALIAS type obtains its properties from its base type, except for its identifier. It is defined using the ALIAS OF type constructor.

Example:

 TYPE INT = ALIAS OF INTEGER;

An ALIAS type and its base type are compatible in every aspect. They may therefore be used interchangeably.

Example:

 VAR i : INT; j : INTEGER;
 i := j; (* i and j are compatible *)

Immutable Types

An immutable type is an immutable equivalence type of a mutable type. The type it is an equivalence type of is called its base type. The base type may be any dynamically allocatable ADT provided that it is not an immutable equivalence type itself. An immutable type obtains its properties from its base type, except for its identifier. It is defined using the CONST type constructor.

Example:

 TYPE ImmutableFooArray = CONST FooArray;

An immutable type is compatible with its base type. Any value of an immutable type is also a legal value of its base type and vice versa. However, instances of an immutable type are immutable, they may not be L-values except for initialisation in a NEW statement and they may not be passed to a formal VAR parameter.

Example:

 VAR array : FooArray; immArray : ImmutableFooArray;
 NEW array; (* initialisation not required *)
 NEW immArray := { foo, bar, baz }; (* initialisation required *)
 COPY array := immArray; (* copying from immutable to mutable *)
 COPY immArray := array; (* compile time error: attempt to modify immutable instance *)

Subrange Types

A subrange type is a subtype of a scalar or ordinal type. The type it is a subtype of is called its supertype. The supertype may be any scalar or ordinal type. A subrange type obtains its properties from its supertype, except for its identifier, and its lower and upper bounds. Both lower and upper bound must be specified in its type definition and they must be legal values of the supertype. A subrange type is defined using a range constructor.

Examples:

 TYPE Radian = [0.0 .. tau] OF REAL;
 TYPE Natural = [1 .. TMAX(CARDINAL)] OF CARDINAL;

A subrange type is upwards compatible with its supertype, but the supertype is not downwards compatible with all of its subrange types. This restriction exists because any value of a subrange type is always a legal value of its supertype, but a value of a supertype is not necessarily a legal value of its subrange type.

Examples:

 VAR natural : Natural; cardinal : CARDINAL;
 natural := cardinal; (* compile time error *)
 cardinal := natural; (* OK *)

The subrange type definition of a scalar type that represents real numbers may specify open bounds. An open lower bound is prefixed by the > symbol. An open upper bound is prefixed by the < symbol. An open bound of a subrange type is not a legal value of the subrange type.

Examples:

 TYPE PosReal = [>0.0 .. TMAX(REAL)] OF REAL;
 TYPE NegReal = [TMIN(REAL) .. <0.0] OF REAL;

Enumeration Types

EBNF | Syntax Diagram

An enumeration type is an ordinal type whose legal values are defined by a list of identifiers. The identifiers are assigned ordinal values from left to right as they appear in the type definition. The ordinal value assigned to the leftmost identifier is always zero.

Example:

 TYPE Colour = ( red, green, blue ); (* ORD(red) => 0 *)

When referencing an enumerated value, its identifier must be qualified with its type identifier, except within a subrange type constructor. This requirement fixes a flaw in classic Modula-2 where the import of an enumeration type could cause name conflicts.

Example:

 TYPE BaseColour = [red .. green] OF Colour; (* unqualified *)
 VAR colour : Colour;  colour := Colour.green; (* qualified *)

Enumeration Type Extension

An enumeration type may be defined as an extension of another by listing the identifier of the base type as the first item in the enumerated value list prefixed by the + symbol. All enumerated values of the base type become legal values of the new type. The base type is downwards compatible with any extended types derived from it, but extensions are not upwards compatible with their base type. This restriction exists because any value of the base type is always a legal value of any extension type derived from it, but not every value of an extension type is also a legal value of the base type.

Example:

 TYPE MoreColour = ( +Colour, orange, magenta, cyan );
 (* equivalent to: MoreColour = ( red, green, blue, orange, magenta, cyan );

The allocation size of an enumeration type is always 16 bit. Its maximum value range is 65536 values.

Set Types

EBNF | Syntax Diagram

A set type is a collection type whose storable values are defined by the legal values of an associated enumeration type of up to 256 values. The values stored in a set are also called elements of the set and the associated enumeration type is called its element type. A set type is defined using the SET OF type constructor.

Example:

 TYPE ColourSet = SET OF Colour;

An instance of a set type may hold multiple elements but any given element may be stored at most once. An element stored in a set is said to be a member of the set. A set is represented as an array of boolean membership values, where the element is the accessor and the membership is the value. A membership value may thus be either TRUE or FALSE.

Examples:

 VAR  colours : ColourSet; isMember : BOOLEAN;
 colours := { Colour.red, Colour.green }; (* assignment *)
 isMember := colours[Colour.green]; (* membership retrieval *)
 colours[Colour.blue] := TRUE; (* membership storage *)

Array Types

EBNF | Syntax Diagram

An array type is an indexed collection type whose values are of a single arbitrary type, called the array's value type. The type's capacity is specified by a value count parameter in the type definition. The capacity must be a whole number value and it may not be zero. Array types are defined using the ARRAY OF type constructor.

Example:

 TYPE IntArray = ARRAY 10 OF INTEGER;

The values of an array instance are addressable by cardinal index using subscript notation. The lowest index is always zero.

Examples:

 VAR array : IntArray; int : INTEGER;
 array := { 0 BY TLIMIT(IntArray) }; (* initialise all values with zero *)
 int := array[5]; (* value retrieval *)
 array[5] := 42; (* value storage *)

Flexible Array Types

An array type may be defined to hold a variable number of values by prefixing the value count parameter in the type's definition with the < symbol. The type's capacity is one less than the specified value count and it may not be zero.

Example:

 TYPE FlexArray = ARRAY < 10 OF INTEGER;

The instance of a rigid array type always holds exactly the number of values that equals the type's capacity. No values may be appended, inserted or removed at runtime. By contrast, the instance of a flexible array type may hold a variable number of values. Within the limits of the type's capacity, values may be appended, inserted and removed at runtime.

Examples:

 VAR array : FlexArray;
 array := { 42, -5, 0 }; (* initialise with three values *)
 APPEND(array, -35); (* append a value *)
 INSERT(array, 0, 11); (* value insertion *)
 REMOVE(array, 3, 1); (* value removal *)

Instances of flexible arrays may further be sliced and concatenated. Flexible array types and their slices are insertion and concatenation compatible as long as the respective value types are compatible.

Examples:

 VAR array1, array2, array3 : FlexArray;
 array2 := { 1, 2, 3, 4 }; array3 := { 7, 8, 9 };
 array1 := array2 & array3; (* concatenation : { 1, 2, 3, 4, 7, 8, 9 } *)
 array1[4..5] := { 5, 6 }; (* sliced insert : { 1, 2, 3, 4, 5, 6, 7, 8, 9 } *)

Character Arrays

For security reasons, array types with value types CHAR and UNICHAR may only be defined as flexible array types. Rigid character array types are not supported. An attempt to define a rigid character array type shall cause a compile time error.

Examples:

 TYPE String = ARRAY 100 OF CHAR; (* compile time error: unsupported definition *)
 TYPE String = ARRAY < 100 OF CHAR; (* OK, supported character array type definition *)

The instances of character array types are initialised with a single NUL character and compliant implementations must ensure that they are NUL terminated after every assign, append and concatenation operation.

Record Types

EBNF | Syntax Diagram

A record type is a compound type whose components are of arbitrary types. The components are called fields. The number of fields is arbitrary. Record types are defined using the RECORD type constructor.

Example:

 TYPE Point = RECORD x, y : REAL END;

An instance of a record type holds exactly one value for each field. Fields are addressable by selector using dot notation.

Examples:

 VAR  point : Point; r : REAL;
 record := { 0.0, 0.0 }; (* initialise all fields with zero *)
 r := point.x; (* field retrieval *)
 point.y := 0.75; (* field storage *)

Record Type Extension

A record type may be defined as an extension of another by giving the identifier of the base type in parentheses before the field list declaration. All fields of the base type become fields of the new type. The field names of the base type may therefore not be reused in the extension type's own field list declaration. The base type is downwards compatible with any extended types derived from it, but type extensions are not upwards compatible with their base type. This restriction exists because any field of the base type is always a field of any extension type derived from it, but not every field of an extension type is also a field of the base type.

Examples:

 TYPE ColourPoint = RECORD ( Point ) colour : Colour END;
 VAR  cPoint : ColourPoint;
 cPoint := { 0.0, 0.0, Colour.red }; (* initialise all fields *)
 cPoint.x := 1.5; cPoint.y := 0.75;

Pointer Types

EBNF | Syntax Diagram

A pointer type is a container for a typed reference to an entity at a memory storage location. The type of the referenced entity is called the target type. The entity referenced by an instance of a pointer type is called the pointer's target. Pointer types are defined using the POINTER TO type constructor.

Example:

 TYPE IntPtr = POINTER TO INTEGER;

Typed references are created using predefined procedure PTR. Instances of pointer types are dereferenced using the pointer dereferencing operator ^.

Example:

 VAR int : INTEGER; intPtr : IntPtr;
 intPtr := PTR(int, IntPtr); (* obtain a typed reference to int *)
 intPtr^ := 0; (* write to int via dereferenced pointer intPtr *)

A pointer type may be defined to restrict the mutability of its target.

Example:

 TYPE ImmIntPtr = POINTER TO CONST INTEGER;

Although the instance of such a pointer itself is mutable, its target is always treated immutable. A dereferenced instance may not be used as an L-value and it may not be passed to a procedure as a VAR parameter. Pointers to mutable and immutable targets are therefore always incompatible. Any violation shall cause a compile time error.

Example:

 VAR int : INTEGER; intPtr : IntPtr; immPtr : ImmIntPtr;
 intPtr := PTR(int, IntPtr); immPtr := PTR(int, ImmIntPtr);
 intPtr^ := 0; (* OK, modifying a mutable target *)
 immPtr^ := 0; (* compile time error due to attempt to modify an immutable target *)

Coroutine Types

EBNF | Syntax Diagram

A coroutine type is a special purpose pointer type whose target is a coroutine. An associated procedure type is part of the type definition. A coroutine procedure is compatible with a coroutine type when it matches the signature of the type's associated procedure type. Coroutine types are defined using the COROUTINE type constructor.

Examples:

 TYPE Iterator = COROUTINE ( IteratorProc );

Procedure Types

EBNF | Syntax Diagram

A procedure type is a special purpose pointer type whose target is a procedure. The procedure's signature is part of the type definition. A procedure is compatible with a procedure type when their signatures match. Procedure types are defined using the PROCEDURE type constructor.

Examples:

 TYPE WriteStrProc = PROCEDURE ( CONST ARRAY OF CHAR );
 TYPE FSM = PROCEDURE ( CONST ARRAY OF CHAR, FSM );

Opaque Types

An opaque type is a type whose internal composition and structure is not accessible outside of the implementation part of the library in which it is defined. Instances of an opaque type may only be operated on by clients of its exporting library through the operations exported by the public interface of the library. There are two kinds of opaque types:

Opaque Pointer Types

An opaque pointer type is a special pointer type used for the construction of ADTs. The definition and declaration of such an ADT is divided between the definition and implementation part of its library. The identifier of the opaque type is defined in the library's definition part and it may be imported from there by clients. It is defined using the OPAQUE type constructor.

Example:

 DEFINITION MODULE Tree;
 TYPE Tree = OPAQUE; (* opaque pointer *)
 (* public interface *)
 END Tree.

The target type of the opaque pointer is declared in the library's corresponding implementation part and it is therefore inaccessible to clients. It is declared using the POINTER TO type constructor.

Example:

 IMPLEMENTATION MODULE Tree;
 TYPE Tree = POINTER TO TreeDescriptor; (* target type specification *)
 TYPE TreeDescriptor = RECORD
   left, right : Tree;
   value : ValueType
 END; (* TreeDescriptor *)
 (* implementation *)
 END Tree.

Instances of an opaque pointer based ADT may only be allocated dynamically at runtime.

Example:

 IMPORT Tree;
 VAR tree : Tree;
 NEW tree := { foo, bar, baz };

Opaque Record Types

An opaque record type is a record type whose identifier is available to client modules that import it but its fields are not. Such a record type is defined with exported restricted fields. An export restricted field is a field that is directly accessible only within the library module in which the type is defined and within any extension library thereof. It is not directly accessible within any other scope. Such a field is declared by prefixing the field declaration with the * symbol.

Example:

 DEFINITION MODULE PascalString;
 TYPE PascalString = RECORD
 * length : OCTET; (* export restricted field *)
 * data : OctetArray255 (* export restricted field *)
 END;
 (* public interface *)
 END PascalString.

Since all record fields are lexically present within the definition part, the allocation size of an opaque record type can be determined at compile time even when no source code is available for the corresponding implementation part. Instances of opaque record types are therefore statically allocatable.

Example:

 IMPORT PascalString;
 VAR str : PascalString; (* allocated on the stack *)

Any attempt to access a restricted field within a scope where it is not accessible shall cause a compile time error.

Example:

 IMPORT PascalString;
 VAR str : PascalString; len : OCTET;
 len := str.length; (* compile time error: access of a restricted field *)
 len := PascalString.Length(str); (* proper use: access via public interface *)

Export restricted fields may be automatically initialised for every instance of the type by suffixing the field declaration with an initialisation expression. The initialisation expression shall be a compile time expression of the type of the field.

Example:

 TYPE PascalString = RECORD
 * length : OCTET = 0; (* auto-initialisation to zero *)
 * data : OctetArray255
 END;

Semi-Opaque Record Types

A record type may contain both public and export restricted fields. Such a record type is called semi-opaque.

Example:

 TYPE SemiOpaque = RECORD
 * i : INTEGER; (* restricted field *)
   j, k : INTEGER (* public fields *)
 END;

When a structured value is assigned to an instance of a semi-opaque record type, it may only contain values for public fields.

Example:

 VAR triplet : SemiOpaque;
 triplet := { 0, 0, 0 }; (* compile time error: access of a restricted field *)
 triplet := { 0, 0 }; (* proper use: only public fields are written to *)

It is safe practise to declare the restricted fields of semi-opaque record types with an initialisation expression.


Implementation and Program Modules

EBNF | Syntax Diagram

Statements

EBNF | Syntax Diagram

A statement is an action that can be executed to cause a transformation of the computational state of a program. Statements are used for their effects only, they do not return any values and they may not occur within expressions. There are twelve kinds of statements:

Memory Management Statements

EBNF | Syntax Diagram

Memory management statements are used to allocate, initialise, retain and release instances of dynamic data types at runtime. There are three kinds of memory management statements:

The NEW Statement

The NEW statement is used to dynamically allocate storage for a new instance of a dynamically allocatable type.

Example:

 VAR dict : SymTable;
 NEW dict; (* allocation without initialisation *)

The RETAIN Statement

The RETAIN statement is used to retain a reference to an instance of a reference counted dynamically allocatable type to prevent its premature deallocation. The RETAIN statement may therefore only be used for instances of reference counted types. Non-compliance shall cause a compile time error.

Example:

 RETAIN dict;

The RELEASE Statement

The RELEASE statement is used to release a reference for an instance of a reference counted dynamically allocatable type and thereby cancel an earlier retain operation. If no further retains are outstanding or if the target is not reference counted, the target is deallocated.

Example:

 RELEASE dict;

Destructive Update Statements

Destructive update statements are used to destructively update instances of mutable data types. There are four kinds:

The Assignment Statement

The assignment statement is used to assign a value to an instance of a mutable type. It consists of a designator followed by the assignment symbol :=, followed by an expression. The designator is called the L-value, the expression is called the R-value. The L-value must be mutable and the types of L-value and R-value must be assignment compatible. If these conditions are not met, a compile time error shall occur.

Examples:

 ch := "a";   str := "foo";   i := -12345;   r := 3.1415926;   z := { 1.2, 3.4 };   array[5] := 0;

The Increment Statement

The increment statement is used to increment the current value of an instance of a whole number type. It consists of a designator followed by the postfix increment symbol ++. The designator is an L-value. It must be mutable and of a whole number type. If these conditions are not met, a compile time error shall occur.

Examples:

 lineCounter++; index++;

The Decrement Statement

The decrement statement is used to decrement the current value of an instance of a whole number type. It consists of a designator followed by the postfix decrement symbol --. The designator is an L-value. It must be mutable and of a whole number type. If these conditions are not met, a compile time error shall occur.

Examples:

 lineCounter--; index--;

The COPY Statement

to do

The Procedure Call Statement

A procedure call statement is used to invoke a procedure. It consists of the procedure's identifier, optionally followed by a list of parameters enclosed in parentheses to be passed to the called procedure. Parameters passed are called actual parameters, those defined in the procedure's header are called formal parameters. In every procedure call, the types of actual and formal parameters must match. If these conditions are not met, a compile time error shall occur. Procedure calls may be recursive, that is, a procedure may call itself within its body. Recursive calls shall be optimised by eliminating tail call recursion.

Examples:

 Insert( tree, "Fred Flintstone", 42 );   ClearBuffers;

The RETURN Statement

The RETURN statement is used within a procedure body to return control to its caller and in the main body of the program to return control to the operating environment that activated the program. A RETURN statement may or may not return a value, depending on the type of the procedure in which it is invoked. When returning from a regular procedure, no value may be returned. When returning from a function procedure a value of the procedure's return type must be returned. Non-compliance shall cause a compile time error.

Example:

 PROCEDURE successor ( n : CARDINAL ) : CARDINAL;
 BEGIN
   RETURN n + 1
 END successor;

The YIELD Statement

The YIELD statement is used within a coroutine procedure body to suspend the coroutine and pass control to its caller. A YIELD statement may or may not yield a value, depending on the type of the coroutine procedure in which it is invoked. When yielding from a regular procedure, no value may be yielded. When yielding from a function procedure a value of the procedure's return type must be yielded. The YIELD statement may only occur within the body of coroutine procedures. Non-compliance shall cause a compile time error.

Example:

 PROCEDURE [COROUTINE] iterator ( CONST array : ARRAY OF INTEGER ) : INTEGER;
 BEGIN
   FOR value IN array DO
     YIELD value
   END;
   RETURN -1
 END iterator;

The IF Statement

EBNF | Syntax Diagram

An IF statement is a conditional flow-control statement. It evaluates a condition in form of a boolean expression. If the condition is true then program control passes to its THEN block. If the condition is false and an ELSIF branch follows, then program control passes to the ELSIF branch to evaluate that branch's condition. Again, if the condition is true then program control passes to the THEN block of the ELSIF branch. If there are no ELSIF branches, or if the conditions of all ELSIF branches are false, and if an ELSE branch follows, then program control passes to the ELSE block. At most one block in the statement is executed. IF-statements must always be terminated with an END.

Example:

 IF i > 0 THEN
   WRITE("Positive")
 ELSIF i = 0 THEN
   WRITE("Zero")
 ELSE
   WRITE("Negative")
 END;

The CASE Statement

EBNF | Syntax Diagram

A CASE statement is a flow-control statement that passes control to one of a number of labeled statements or statement sequences depending on the value of an ordinal expression. Control is passed to the first statement following the case label that matches the ordinal expression. If no label matches, control is passed to the ELSE block.

Example:

 CASE colour OF
 | colour.red   : WRITE("Red")
 | colour.green : WRITE("Green")
 | colour.blue  : WRITE("Blue")
 ELSE
   UNSAFE.HALT(1) (* fatal error -- abort *)
 END;

A case label shall be listed at most once. If a case is encountered at runtime that is not listed in the case label list and if there is no ELSE block, no case label statements shall be executed and no error shall result.

The WHILE Statement

EBNF | Syntax Diagram

A WHILE statement is used to repeat a statement or statement sequence depending on a condition in form of a boolean expression. The expression is evaluated each time before the DO block is executed. The DO block is repeated as long as the expression evaluates to TRUE.

Example:

 WHILE NOT EOF(file) DO READ(file, ch) END;

The REPEAT Statement

EBNF | Syntax Diagram

A REPEAT statement is used to repeat a statement or statement sequence depending on a condition in form of a boolean expression. The expression is evaluated each time after the REPEAT block has executed. the expression evaluates to TRUE the REPEAT block is executed, otherwise not.

Example:

 REPEAT READ(file, ch) UNTIL ch = terminator END;

The LOOP Statement

EBNF | Syntax Diagram

A LOOP statement is used to repeat a statement or statement sequence indefinitely unless explicitly terminated by an EXIT statement.

Example:

 LOOP
   READ(file, ch);
   IF ch IN TerminatorSet THEN
     EXIT
   END (* IF *)
 END; (* LOOP *)

The FOR Statement

EBNF | Syntax Diagram

The FOR statement is used to iterate over an iterable entity and execute a statement or statement sequence during each iteration cycle. It consists of a loop header and a loop body. The loop header consists of one or two loop variants, an optional iteration order, and the iterable expression. The loop body consists of a statement or statement sequence.

The Iterable Expression

EBNF | Syntax Diagram

The iterable expression — or iterable in short – is denoted by a designator if an instance of a collection type or by an identifier of an ordinal type or subrange, an anonymous subrange of an ordinal type. An ordinal type or subrange iterable is always immutable. A collection iterable may be either mutable or immutable.

The Loop Variant Section

EBNF | Syntax Diagram

The loop variant section contains one or two identifiers through which accessors and values of the iterable are referenced within the loop. During the first iteration cycle the loop variant or variants reference that accessor, value or accessor/value pair which is first for the prevailing iteration order. Before each subsequent iteration cycle the loop variant or variants are advanced to its current successor for the prevailing iteration order. Iteration continues until all accessors and/or values have been visited. Loop variant identifiers are only in scope within the loop header and body. Once a FOR loop has terminated, its loop variants are no longer in scope.

The composition of the loop variant section depends on the iterable. If it is an ordinal type or subrange, the loop variant section may only contain a single variant and it is always immutable within the loop body. If the iterable is a collection instance, the loop variant section may contain one or two loop variants representing the collection's accessor, its value or both. If the accessor is to be omitted, the loop variant must be prefixed with VALUE. An accessor is always immutable within the loop body. A value is mutable within the loop body if the iterable is mutable, otherwise immutable.

The Iteration Order

EBNF | Syntax Diagram

If the iterable supports directional iteration, the prevailing iteration order may be imposed by an ascender or descender following the first loop variant. An ascender imposes ascending order and is denoted by the ++ symbol. A descender imposes descending order and is denoted by the -- symbol. When no ascender nor descender is given, the prevailing iteration order is ascending. However, if the iterable does not support directional iteration, the prevailing iteration order is implementation dependent and no ascender and no descender may be given.

Iterating Over Ordinal Types

If the iterable is an ordinal type or a subrange thereof, only one loop variant may be given. The loop variant is immutable. Its type is the ordinal type or subrange given as iterable and the loop iterates over all values of the given iterable. There are three use cases:

Iterating Over The CHAR Type

The iterable is type CHAR or a subrange thereof.

Examples:

 FOR ch IN CHAR DO WRITE(ch) END;
 FOR ch IN ["a".."z"] OF CHAR DO WRITE(ch) END;
Iterating Over An Enumeration Type

The iterable is an enumeration type or a subrange thereof.

Example:

 TYPE Colours = ( red, green, blue, cyan, magenta, ... );
 FOR colour IN Colours DO WRITE(NameOfColour(colour)) END;
 FOR colour IN [red..blue] OF Colours DO WRITE(NameOfColour(colour)) END;
Iterating Over A Whole Number Type

The iterable is a whole number type or a subrange thereof.

Example:

 FOR number IN CARDINAL DO WRITE(BottlesOfBeer(number)) END;
 FOR n IN [0..9] OF CARDINAL DO array[2*n+1] := odd END; (* indices 1, 3, 5, 7, 9 *)
Iterating Over Collections

If the iterable is an instance of a collection type, one or two loop variants may be given. The accessor is always immutable. Its type is the accessor type of the iterable entity. If the iterable entity is mutable, the value is mutable, otherwise immutable. Its type is the value type of the iterable. The loop iterates over all accessor/value pairs of the given iterable. There are four use cases:

Iterating Over A List

The iterable is an instance of a list ADT.

Example:

 FOR listNode IN list DO WRITE(listNode) END;
 FOR VALUE item IN list DO item := foo END;
Iterating Over An Array

The iterable is an instance of an ARRAY OF type or array ADT.

Example:

 FOR index IN array DO array[index] := 0 END;
 FOR index, value IN target DO value := source[index] END;
Iterating Over A Set

The iterable is an instance of a SET OF type or set ADT.

Example:

 FOR elem IN set DO WRITE(elem) END;
 FOR elem, counter IN countedSet DO WRITE(elem); WRITE(" : "); WRITE(counter); WriteLn END;
Iterating Over A Dictionary

The iterable is an instance of a dictionary ADT.

Example:

 FOR key IN dict DO WRITE(key) END;
 FOR key, value IN dict DO WRITE(key); WRITE(" : "); WRITE(value); WriteLn END;

The EXIT Statement

The EXIT statement is used within the body of a WHILE, REPEAT, LOOP or FOR statement to terminate execution of the statement's body and transfer control to the first statement after the loop body. The EXIT statement may only occur within the body of loop statements. Non-compliance shall cause a compile time error.

Example:

 LOOP
   ch := nextChar(stdIn);
   CASE ch OF
   | ASCII.ESC : EXIT
   | (* other case labels ... *)

Expressions

EBNF | Syntax Diagram

An expression is a computational formula that evaluates to a value. An expression may consist of one of more sub-expressions. Sub-expressions consists of operands, operators and optional punctuation.

Evaluation Time

Expressions are classified according to their time of evaluation. An expression that may only be evaluated at runtime is called a runtime expression. An expression that is evaluated at compile time is called a compile time expression or constant expression. Constant expressions consist only of operands whose values are known at compile time and only invoke built-in functions or macros that may be evaluated at compile time.

Evaluation Order

The evaluation order of expressions is determined by operator precedence and punctuation. There are five levels of operator precedence. However, sub-expressions enclosed in parentheses, designators and function calls always take precedence over the evaluation order defined by operator precedence. This constitutes an implicit sixth level of expression evaluation.

Evaluation Level 1

EBNF | Syntax Diagram

Expressions are evaluated at precedence level one. Its sub-expressions are simple expressions. Its operators are the relational operators and the identity operator. Level one has the lowest precedence.

Evaluation Level 2

EBNF | Syntax Diagram

Simple expressions are evaluated at precedence level one. Its sub-expressions are terms. Its operators are the plus and minus operators and the OR operator.

Evaluation Level 3

EBNF | Syntax Diagram

Terms are evaluated at precedence level three. Its sub-expressions are simple terms. Its operators are the asterisk, solidus, DIV, MOD, AND operators and the set difference operator.

Evaluation Level 4

EBNF | Syntax Diagram

Simple terms are evaluated at precedence level four. Its sub-expressions are factors and its operator is the NOT operator.

Evaluation Level 5

EBNF | Syntax Diagram

Factors are evaluated at precedence level five. Its sub-expressions are simple factors and its operator is the type conversion operator.

Evaluation Level 6

EBNF | Syntax Diagram

Simple factors are evaluated at precedence level six. Its sub-expressions are literals, structured values, expressions in parentheses, designators and function calls. Its pseudo-operators are the parentheses of parenthesised expressions and the selectors of designators. Level six has the highest precedence.

Operands

An operand may be a literal, a designator or a sub-expression. Whether any given operand may legally occur at a given position within an expression is determined by expression compatibility. Expression compatibility of operands is dependent on the operator of an expression or sub-expression as each operator defines what operand types it can accept.

Designators

A designator consists of an identifier that refers to a constant, a variable or a function call, followed by an optional designator tail that consists of one or more selectors. The identifier component of a designator may be a qualified identifier.

Selectors

A selector is a suffix to select one or more components from a value. There are four kinds.

The Subscript Selector

to do

The Array Slice Selector

to do

The Record Field Selector

to do

The Pointer Target Selector

to do

Operators

Operators are special symbols or reserved words that represent an operation within an expression. An operator may be unary or binary. Unary operators are prefix or postfix, binary operators are always infix. An operator may be either left-associative or non-associative and it has a precedence level between one and six, where six represents the highest level. Arity, associativity and precedence determine the order of evaluation in expressions that consist of multiple sub-expressions and may contain different operators.

An overview of operators with their operations, arity, associativity and precedence is given below:

OperatorRepresented OperationPositionArityAssociativityPrecedence
^ Pointer Dereferencepostfixunaryleft6 (highest)
:: Type Conversioninfixbinaryleft5
NOT Logical Negationprefixunarynone4
* Multiplication, Set Intersectioninfixbinaryleft3
/ Real Division, Symmetric Set Differenceinfixbinaryleft3
DIV Euclidean Integer Divisioninfixbinaryleft3
MOD Modulus of Euclidean Integer Divisioninfixbinaryleft3
AND Logical Conjunctioninfixbinaryleft3
\ Set Differenceinfixbinaryleft3
+ Addition, Set Unioninfixbinaryleft2
- Sign Inversionprefixunarynone2
Subtractioninfixbinaryleft2
OR Logical Disjunctioninfixbinaryleft2
& Concatenationinfixbinaryleft2
= Equality Testinfixbinarynone1
# Inequality Testinfixbinarynone1
> Greater-Than Test, Proper Superset Testinfixbinarynone1
>= Greater-Than-Or-Equal Test, Superset Testinfixbinarynone1
< Less-Than Test, Proper Subset Testinfixbinarynone1
<= Less-Than-Or-Equal Test, Subset Testinfixbinarynone1
IN Membership Testinfixbinarynone1
== Identity Testinfixbinarynone1

The Pointer Dereferencing Operator

Symbol ^ denotes the pointer dereferencing operator. It is left associative and requires one operand. The operator follows its operand.

Examples:

 int := intPointer^; (* pointer dereference *)
 value := pointer^^; (* double pointer dereference *)

The operator always represents the pointer dereferencing operation. Its operand must be of a pointer type. Its result type is the pointer's target type. Any use of the operator with an operand that is not a pointer type shall cause a compile time error. The pointer dereferencing operator is not bindable.

The Type Conversion Operator

Symbol :: denotes the type conversion operator. It is left associative and requires two operands.

Examples:

 real := int :: REAL; (* integer to real conversion *)
 bcd := real :: BCD; (* real to binary coded decimal conversion *)

The operator always represents the type conversion operation. Its left operand must be of a convertible type. Its right operand indicates the target type and must be a type identifier. Its result type is the target type. Any use of the operator with operands that do not meet these conditions shall cause a compile time error. The type conversion operator is bindable.

The NOT Operator

Reserved word NOT denotes the logical NOT operator. It is non-associative and requires one operand. The operator precedes its operand.

Example:

 inverse := NOT condition; (* logical negation *)

The operator always represents the logical negation operation. Its single operand may be any expression of type BOOLEAN and its result type is BOOLEAN. Any use of the operator with an operand whose type is not BOOLEAN shall cause a compile time error. The NOT operator is not bindable.

The Asterisk Operator

Symbol * denotes a multi-purpose operator. It is left associative and requires two operands.

Examples:

 product := 3.0 * 5.5; (* real multiplication *)
 intersect := { foo, bar, baz } * { bar, baz, bam }; (* set intersection *)

The operator represents different operations, depending on the type of its operands. If the operand type is a numeric type, it represents multiplication. If the operand type is a set type, it represents set intersection. Its operands must be type compatible. Its result type is the operand type. Any use of the operator with incompatible operand types shall cause a compile time error. The asterisk operator is bindable.

The Solidus Operator

Symbol / denotes a multi-purpose operator. It is left associative and requires two operands.

Examples:

 quotient := 7.5 / 3.0; (* real division *)
 symDiff := { foo, bar, baz } / { bar, baz, bam }; (* symmetric set difference *)

The operator represents different operations, depending on the type of its operands. If the operand type is a numeric type, it represents real division. If the operand type is a set type, it represents symmetric set difference. Its operands must be type compatible. Its result type is the operand type. Any use of the operator with incompatible operand types shall cause a compile time error. The slash operator is bindable.

The DIV Operator

Reserved word DIV denotes the Euclidean division operator. It is left associative and requires two operands.

Example:

 quotient := 7 DIV 3; (* Euclidean integer division *)

The operator always represents Euclidean integer division. Its operands must be of a whole number types and they must be type compatible. Its result type is the operand type. Any use of the operator with an operand that is not a whole number type or with incompatible operand types shall cause a compile time error. The DIV operator is bindable.

The MOD Operator

Reserved word MOD denotes the modulus operator. It is left associative and requires two operands.

Example:

 modulus := 7 MOD 3; (* Euclidean modulus *)

The operator always represents the modulus of Euclidean integer division. Its operands must be of a whole number type and they must be type compatible. Its result type is the operand type. Any use of the operator with an operand that is not a whole number type or with incompatible operand types shall cause a compile time error. The MOD operator is bindable.

The AND Operator

Reserved word AND denotes the logical AND operator. It is left-associative and requires two operands.

Example:

 conjunction := foo AND bar; (* logical conjunction *)

The operator always represents the logical conjunction operation. Its operands must be of type BOOLEAN and its result type is BOOLEAN. Any use of the operator with an operand whose type is not BOOLEAN shall cause a compile time error. The AND operator is not bindable.

The Set Difference Operator

Symbol \ denotes the set difference operator. It is left associative and requires two operands.

Example:

 setDiff := { foo, bar, baz } \ { baz }; (* set difference *)

The operator always represents the set difference operation. Its operands must be of a set type and they must be type compatible. Its result type is the operand type. Any use of the operator with an operand that is not a set type or with incompatible operand types shall cause a compile time error. The set difference operator is bindable.

The Plus Operator

Symbol + denotes a multi-purpose operator. It is left associative and requires two operands.

Example:

 nSum := 100 + 42; (* whole number addition *)
 rSum := 7.5 + 1.0; (* real number addition *)
 union := { foo, bar } + { baz, bam }; (* set union *)

The operator represents different operations, depending on the type of its operands. If the operand type is a numeric type, it represents addition. If the operand type is a set type, it represents set union. Its operands must be type compatible. Its result type is the operand type. Any use of the operator with incompatible operand types shall cause a compile time error. The binary plus operator is bindable.

The Minus Operator

Symbol - denotes a multi-purpose operator. There are two variants:

The Unary Minus Operator

The unary minus operator is non-associative and requires one operand. The operator precedes its operand.

Example:

 i := -42; (* sign inversion *)

The operator always represents the sign inversion operation. Its operands must be of a signed numeric type. Its result type is the operand type. Any use of the operator with an operand that is not a signed numeric type shall cause a compile time error. The unary minus operator is bindable using the +/- binding symbol.

The Binary Minus Operator

The binary minus operator is left-associative and requires two operands.

Examples:

 nDiff := 100 - 42; (* whole number subtraction *)
 rDiff := 7.5 - 1.0; (* real number subtraction *)

The operator always represents the subtraction operation. Its operands must be of numeric types and they must be type compatible. Its result type is the operand type. Any use of the operator with an operand that is not a numeric type or with incompatible operand types shall cause a compile time error. The binary minus operator is bindable.

The Concatenation Operator

Symbol & denotes the concatenation operator. It is left-associative and requires two operands.

Example:

 string := "foo" & "bar"; (* concatenation *)

The operator always represents the concatenation operation. Its operands must be collection types and their component types must be compatible. Its result type is the target type of the expression. Any use of the operator with operands that do not meet these conditions shall cause a compile time error. The concatenation operator is not bindable.

The OR Operator

Reserved word OR denotes the logical OR operator. It is left-associative and requires two operands.

Example:

 disjunction := foo OR bar; (* logical disjunction *)

The operator always represents the logical disjunction operation. Its operands must be of type BOOLEAN and its result type is BOOLEAN. Any use of the operator with an operand whose type is not BOOLEAN shall cause a compile time error. The OR operator is not bindable.

The Equality Operator

Symbol = denotes the equality operator. It is non-associative and requires two operands.

Example:

 isEqual := foo = bar; (* equality test *)

The operator always represents the equality test operation. Its operands may be of any type but must be type compatible. Its result type is BOOLEAN. Any use of the operator with incompatible operand types shall cause a compile time error. The equality operator is bindable.

The Inequality Operator

Symbol # denotes the inequality operator. It is non-associative and requires two operands.

Example:

 notEqual := foo # bar; (* inequality test *)

The operator always represents the inequality test operation. Its operands may be of any type but must be type compatible. Its result type is BOOLEAN. Any use of the operator with incompatible operand types shall cause a compile time error. The inequality operator is not bindable.

The > Operator

Symbol > denotes a dual-purpose relational operator. It is non-associative and requires two operands.

Example:

 isGreater := 10 > 5; (* greater-than test *)
 isSuperset := { foo, bar, baz } > { foo, baz }; (* proper superset test *)

The operator represents different operations, depending on the type of its operands. If the operand type is numeric, it represents the greater-than test operation. If it is a set type, it represents the proper-superset test operation. Its operands must be type compatible. Its result type is BOOLEAN. Any use of the operator with incompatible operand types shall cause a compile time error. The > operator is bindable.

The >= Operator

Symbol >= denotes a dual-purpose relational operator. It is non-associative and requires two operands.

Example:

 isGreaterOrEqual := 10 >= 5; (* greater-or-equal test *)
 isSuperset := { foo, bar, baz } >= { foo, baz }; (* superset test *)

The operator represents different operations, depending on the type of its operands. If the operand type is numeric, it represents the greater-or-equal test operation. If it is a set type, it represents the superset test operation. Its operands must be type compatible. Its result type is BOOLEAN. Any use of the operator with incompatible operand types shall cause a compile time error. The >= operator is not bindable.

The < Operator

Symbol < denotes a dual-purpose relational operator. It is non-associative and requires two operands.

Example:

 isLess := 5 < 10; (* less-than test *)
 isSubset := { foo, baz } < { foo, bar, baz }; (* proper subset test *)

The operator represents different operations, depending on the type of its operands. If the operand type is numeric, it represents the less-than test operation. If it is a set type, it represents the proper-subset test operation. Its operands must be type compatible. Its result type is BOOLEAN. Any use of the operator with incompatible operand types shall cause a compile time error. The < operator is bindable.

The <= Operator

Symbol <= denotes a dual-purpose relational operator. It is non-associative and requires two operands.

Example:

 isGreaterOrEqual := 5 <= 10; (* less-or-equal test *)
 isSuperset := { foo, bar, baz } <= { foo, baz }; (* subset test *)

The operator represents different operations, depending on the type of its operands. If the operand type is numeric, it represents the less-or-equal test operation. If it is a set type, it represents the subset test operation. Its operands must be type compatible. Its result type is BOOLEAN. Any use of the operator with incompatible operand types shall cause a compile time error. The <= operator is not bindable.

The IN Operator

Reserved word IN denotes the IN operator. It is non-associative and requires two operands.

Example:

 isMember := foo IN { foo, bar, baz }; (* membership test *)

The operator always represents the membership test operation. Its right operand must be of a collection type and its left operand must be of the component type of said collection type. Its result type is BOOLEAN. Any use of the operator with operands that do not meet these conditions shall cause a compile time error. The membership operator is bindable.

The Identity Operator

Symbol == denotes the identity operator. It is non-associative and requires two operands.

Example:

 isEqual := foo = bar; (* equality test *)

The operator always represents the identity test operation. Its operands must be compatible pointer types. Its result type is BOOLEAN. Any use of the operator with operands that do not meet these conditions shall cause a compile time error. The identity operator is not bindable.

Structured Values

EBNF | Syntax Diagram

A structured value is a compound value that consists of a comma separated list of value components enclosed in braces. A component value may be a value repetition clause, a value range, a literal, a structured value or an identifier denoting a value or structured value. A value repetition clause is a constant expression followed by BY followed by a repetition factor which shall be a constant expression of a whole number type. A value range is an ordinal constant expression representing the start value followed by .. followed by another ordinal constant expression representing the end value, both ordinal values shall be of the same type.

Examples:

 { 0 BY 100 }, { "a" .. "z" }, { 1 .. 31 }
 { 1970, Month.Jan, 1, 0, 0, 0.0, TZ.UTC }
 { "a", "bcd", 123, 456.78, { 9, 10 }, { foo, bar, baz } }

Predefined Identifiers

Predefined identifiers are language defined identifiers that are visible in any lexical scope without import. There are five kinds:

Summary Of Predefined Constants

Invalid pointer value: NIL
Empty collection value: EMPTY
Boolean truth values: TRUE, FALSE

Summary Of Predefined Types

Boolean type: BOOLEAN
Character types: CHAR, UNICHAR
Unsigned whole number types: OCTET, CARDINAL, LONGCARD
Signed whole number types: INTEGER, LONGINT
Real number types: REAL, LONGREAL

Summary Of Predefined Procedures

INSERT(c, ...) inserts values or accessor/value pairs into collection c
APPEND(c, v1, v2, v3) appends values to the end of list or array collection c
REMOVE(c, ...) removes values or key/value pairs from collection c
SORT(t, s, order) sorts values of source collection s into target collection t
SORTNEW(t, s, order) sorts values of source collection s into newly allocated target collection t
READ(f, x) reads value from file or channel f into x
READNEW(f, x) reads value from file or channel f into newly allocated x
WRITE(f, x) writes x unformatted to file or channel f
WRITEF(f, fmtStr, x, ...) writes one or more values formatted to file or channel f
TODO(str) prints str to console, causes warning in DEBUG mode, or error otherwise

Summary Of Predefined Functions

ABS(x) returns the absolute value of x
ODD(x) returns TRUE if x is an odd number
PRED(x, n) returns n-th predecessor of x
SUCC(x, n) returns n-th successor of x
ORD(x) returns the ordinal value of x
CHR(x) returns the character for codepoint x
EXISTS(c, a, v) returns TRUE if value v exists for accessor a in collection c
COUNT(c) returns the number of values stored in collection c
LENGTH(s) returns length of character string s
PTR(v, T) returns typed pointer to variable v if its type is compatible with T
FIRST(c) returns first value of ordered collection c
LAST(c) returns last value of ordered collection c
MIN(v1, v2, v3 ...) returns smallest value of a list of ordinal or scalar values
MAX(v1, v2, v3 ...) returns largest value of a list of ordinal or scalar values

Summary Of Built-in Compile-Time Macros

TMIN(T) replaced by smallest legal value of type T
TMAX(T) replaced by largest legal value of type T
TLIMIT(T) replaced by the capacity of collection type T
TSIZE(T) replaced by allocation size required for type T

Predefined Constants

Constant NIL

The constant NIL represents an invalid pointer. It is compatible with any pointer type. Its value is defined as:

CONST NIL = 0 :: POINTER TO CONST OCTET;

Dereferencing the constant NIL results in a compile time error. Dereferencing a pointer whose value is NIL results in a runtime error.

Constant EMPTY

The constant EMPTY represents an empty collection literal. It is compatible with any collection type. Its value is defined as:

CONST EMPTY = { } | "";

Constants TRUE and FALSE

The constants TRUE and FALSE represent the values of type BOOLEAN. Their values are defined as:

CONST TRUE = BOOLEAN.TRUE;
CONST FALSE = BOOLEAN.FALSE;

ORD(TRUE) = 0
ORD(FALSE) = 1

see also BOOLEAN

Predefined Types

Type BOOLEAN

Type BOOLEAN is an ordinal type for boolean algebra. All boolean expressions evaluate to type BOOLEAN. It is defined as:

TYPE BOOLEAN = ( TRUE, FALSE );

TMIN(BOOLEAN) = BOOLEAN.TRUE
TMAX(BOOLEAN) = BOOLEAN.FALSE
TSIZE(BOOLEAN) = 2 (* 2 octets *)

Type CHAR

Type CHAR is an ordinal type for 7-bit character values and its value range is 0u0 .. 0u7F. It is defined as:

TYPE CHAR = ( CHR(0) .. CHR(127) );

TMIN(CHAR) = CHR(0)
TMAX(CHAR) = CHR(127)
TSIZE(CHAR) = 1 (* 1 octet *)

Type UNICHAR

Type UNICHAR is a container type for Unicode character values. Its size is always 32-bit but its value range is 0u0 .. 0u10FFFF. Type CHAR is upwards compatible with UNICHAR but the reverse is not the case. This restriction exists because every legal value of type CHAR is also a legal value of type UNICHAR but not every value of type UNICHAR is also a legal value of type CHAR.

Type OCTET

Type OCTET is an unsigned whole number type that represents a storage unit of eight bits. Its parameters are:

TMIN(OCTET) = 0
TMAX(OCTET) = 255
TSIZE(OCTET) = 1 (* one octet, eight bits by definition *)

Type CARDINAL

Type CARDINAL is an unsigned integer type large enough to hold any value in the range 0 to 65535 and any value of type SYSTEM.WORD whichever is larger. The type's parameters are:

TMIN(CARDINAL) = 0
TMAX(CARDINAL) = pow(2, TSIZE(CARDINAL) * 8) - 1
TSIZE(CARDINAL) >= MAX(TSIZE(OCTET) * 2, TSIZE(WORD))

Type LONGCARD

Type LONGCARD is an unsigned integer type large enough to hold the size of the largest allocatable storage area measured in octets. The type is defined as:

TMIN(LONGCARD) = 0
TMAX(LONGCARD) = pow(2, TSIZE(LONGCARD) * 8) - 1
TSIZE(LONGCARD) >= (TSIZE(ADDRESS) DIV 8)

Type INTEGER

Type INTEGER is a signed integer type large enough to hold any value in the range -32768 to 32767 and any value of type SYSTEM.WORD whichever is larger. The type is defined as:

TMIN(INTEGER) = (pow(2, TSIZE(INTEGER) * 8) DIV 2) * (-1)
TMAX(INTEGER) = (pow(2, TSIZE(INTEGER) * 8) DIV 2) - 1
TSIZE(INTEGER) = TSIZE(CARDINAL)

Type LONGINT

Type LONGINT is a signed integer type large enough to hold the size of the largest allocatable storage area measured in octets. The type is defined as:

TMIN(LONGINT) = (pow(2, TSIZE(LONGINT) * 8) DIV 2) * (-1)
TMAX(LONGINT) = (pow(2, TSIZE(LONGINT) * 8) DIV 2) - 1
TSIZE(LONGINT) = TSIZE(LONGCARD)

Type REAL

Type REAL is a real number type with implementation defined precision and range.

Type LONGREAL

Type LONGREAL is a real number type with a precision and range equal to or higher than that of type REAL.

No predefined type may be an ALIAS type of another, even if the types share the same implementation.

Predefined Procedures

Predefined procedures are built-in procedures that are bound to predefined identifiers visible in every scope without import.

A predefined procedure differs from a library defined procedure:

Procedure INSERT

Procedure INSERT is a polymorphic procedure to insert one or more values or key/value pairs into an instance of a collection type. It has three signatures:

Inserting Values Into A Set
 PROCEDURE INSERT ( VAR set : <SetType>; elements : ARGLIST >0 OF <ElementType> );
Inserting Key/Value Pairs Into A Dictionary
 PROCEDURE INSERT ( VAR dict : <DictType>; values : ARGLIST >0 OF { key : <KeyType>; value : <ValueType> } );
Inserting Values Into An Array Or List By Index
 PROCEDURE INSERT ( VAR seq : <SeqType>; atIndex : <IndexType>; values : ARGLIST >0 OF <ValueType> );

Procedure APPEND

Procedure APPEND is a polymorphic procedure to append one or more values to an instance of a collection type. It has one signature:

Appending Values To An Array Or List
 PROCEDURE APPEND ( VAR seq : <SeqType>; values : ARGLIST >0 OF <ValueType> );

Procedure REMOVE

Procedure REMOVE is a polymorphic procedure to remove one or more values or all values from an instance of a collection type. It has three signatures:

Removing Values From A Set
 PROCEDURE REMOVE ( VAR set : <SetType>; elements : ARGLIST >0 OF <ElementType> );
Removing Key/Value Pairs From A Dictionary
 PROCEDURE REMOVE ( VAR dict : <DictType>; values : ARGLIST >0 OF <KeyType> } );
Removing Values From An Array Or List By Index
 PROCEDURE REMOVE ( VAR seq : <SeqType>; startIndex, endIndex : <IndexType>;  );

Procedure SORT

Procedure SORT is a polymorphic procedure to sort the values of a collection and copy them into another. It has one signature:

 PROCEDURE SORT ( VAR target : <TargetCollectionType>; source : <SourceCollectionType>;  order : CHAR );

Procedure SORTNEW

Procedure SORTNEW is a polymorphic procedure to initialise an immutable target collection with the sorted values of another collection. It has one signature:

 PROCEDURE SORTNEW ( NEW target : <TargetCollectionType>; source : <SourceCollectionType>;  order : CHAR );

Procedure READ

Procedure READ is a polymorphic procedure to read a value from a file into a target. It has two signatures:

Reading From StdIn
 PROCEDURE READ ( VAR target : <TargetType> );
Reading From A Given File
 PROCEDURE READ ( f : FILE; VAR target : <TargetType> );

Procedure READNEW

Procedure READNEW is a polymorphic procedure to initialise an immutable target with the contents of a file. It has two signatures:

Reading From StdIn
 PROCEDURE READNEW ( NEW target : <TargetType> );
Reading From A Given File
 PROCEDURE READNEW ( f : FILE; NEW target : <TargetType> );

Procedure WRITE

Procedure WRITE is a polymorphic procedure to write a value to a file. It has two signatures:

Writing To StdOut
 PROCEDURE WRITE ( CONST source : <SourceType> );
Writing To A Given File
 PROCEDURE WRITE ( f : FILE; CONST source : <SourceType> );

Procedure WRITEF

Procedure WRITEF is a polymorphic procedure for formatted writing of one or more values to a file. It has two signatures:

Writing To StdOut
 PROCEDURE WRITEF ( CONST fmt : ARRAY OF CHAR; CONST source : ARGLIST >0 OF <SourceType> );
Writing To A Given File
 PROCEDURE WRITE ( f : FILE; CONST fmt : ARRAY OF CHAR; CONST source : ARGLIST >0 OF <SourceType> );

Procedure TODO

Procedure TODO is a dummy procedure to indicate unimplemented code. It causes a compile time warning when compiling in DEBUG mode, otherwise it causes a compile time error, either way printing a user defined compile time message. It has one signature:

 PROCEDURE TODO ( msg : <StringLiteral> );

Predefined Function Procedures

Function Procedure ABS

Function ABS is a polymorphic function to return the absolute value of its operand. Unlike the mathematical definition of abs(x), the ABS function is strictly limited to scalar operands. Its operand shall be of a scalar type. Its return type is the operand type. It has one signature:

 PROCEDURE ABS ( value : <ScalarType> ) : <OperandType>;

Function Procedure ODD

Function ODD is a polymorphic function to test whether its operand is odd. Its operand shall be of a whole number type. Its return type is BOOLEAN. It returns TRUE if its operand is odd, otherwise FALSE. It has one signature:

 PROCEDURE ODD ( value : <WholeNumberType> ) : BOOLEAN;

Function Procedure PRED

Function PRED is a polymorphic function to return the n-th predecessor of its first operand, where n is the second operand, or one if it is omitted. Its first operand shall be of an ordinal type. Its second operand is of type CARDINAL. Its return type is the first operand type. It has two signatures:

Decrement Value One
 PROCEDURE PRED ( value : <OrdinalType> ) : <OperandType>;
Arbitrary Decrement Value
 PROCEDURE PRED ( value : <OrdinalType>; n : CARDINAL ) : <OperandType>;

Function Procedure SUCC

Function SUCC is a polymorphic function to return the n-th successor of its first operand, where n is the second operand, or one if it is omitted. Its first operand shall be of an ordinal type. Its second operand is of type CARDINAL. Its return type is the first operand type. It has two signatures:

Increment Value One
 PROCEDURE SUCC ( value : <OrdinalType> ) : <OperandType>;
Arbitrary Increment Value
 PROCEDURE SUCC ( value : <OrdinalType>; n : CARDINAL ) : <OperandType>;

Function Procedure ORD

Function ORD is a polymorphic function to return the ordinal value of its operand. Its operand shall be of type CHAR or any enumeration type. Its return type is type CARDINAL. It has one signature:

 PROCEDURE ORD ( value : <CharOrEnumType> ) : CARDINAL;

Function Procedure CHR

Function CHR is a polymorphic function to return the character for the code point given by its operand. Its operand shall be of type OCTET or CARDINAL or LONGCARD. If the value of the operand is less than 128 then its return type is CHAR, otherwise it is UNICHAR. It has one signature:

 PROCEDURE CHR ( codePoint : <OctetOrCardinalOrLongcard> ) : <CharOrUnichar>;

Function Procedure EXISTS

Function EXISTS is a polymorphic function to test the presence of a key/value pair in a dictionary. It has three operands. Its first operand is the dictionary to be tested and it shall be of a dictionary ADT. Its second and third operands are the key and value respectively, and they shall be of the dictionary ADT's key and value types, respectively. The function returns TRUE if the key/value pair is present, otherwise FALSE. Its return type is type BOOLEAN.

 It returns TRUE if the value is present, otherwise FALSE. It has one signature:
 PROCEDURE EXISTS ( dict : <DictionaryType>; key : <KeyType>; value : <ValueType> ) : BOOLEAN;

Function Procedure COUNT

Function COUNT is a polymorphic function to return the number of values stored in its operand or the number of actual parameters passed in a formal parameter denoted by its operand. Its return type is type LONGCARD. It has three signatures:

Number Of Values Stored In a Collection

To obtain the number of values stored in a collection, the function is called passing the collection as a single operand. The operand shall be of a collection type.

 PROCEDURE COUNT ( c : <CollectionType> ) : LONGCARD;
Number Of Values Stored For a Key In A Multi-Dictionary

To obtain the number of values stored for a given key in a multi-dictionary, the function is called passing the dictionary as its first operand and the key as its second operand. The first operand shall be of a dictionary ADT. The second operand shall be of the dictionary's key type.

 PROCEDURE COUNT ( c : <DictionaryType>; key : <KeyType> ) : LONGCARD;
Number Of Arguments Passed To A Variadic Parameter

To obtain the number of actual parameters passed to a variadic parameter list within the body of a variadic procedure, the function is called passing the designator of the variadic parameter list.

 PROCEDURE COUNT ( designator : <VariadicFormalParameter> ) : LONGCARD;

Function Procedure LENGTH

Function COUNT is a polymorphic function to return the number of characters stored in its operand. Its operand shall be of a CHAR or UNICHAR array type or a string ADT. Its return type is type LONGCARD. It has one signature:

 PROCEDURE LENGTH ( s : <CharacterStringType> ) : LONGCARD;

Function Procedure PTR

Function PTR is a polymorphic function to return a typed pointer to its first operand. Its return type is given by its second operand. Its first operand shall be a variable of arbitrary type. Its second operand shall be a pointer type whose target type is the type of the first operand. If the first operand is immutable within the scope where PTR is invoked, the second operand shall be a pointer type with immutable target. Otherwise, the second operand may be a pointer type with mutable or immutable target. The function has one signature:

 PROCEDURE PTR ( v : <AnyType>; T : <TypeIdentifier> ) : <T>;

Function Procedure FIRST

Function FIRST is a polymorphic function to return the first value of its operand. Its operand shall be of an ordered collection type. Its return type is the value type of the type of the first operand. It has one signature:

 PROCEDURE FIRST ( c : <OrderedCollectionType> ) : <ValueType>;

Function Procedure LAST

Function LAST is a polymorphic function to return the last value of its operand. Its operand shall be of an ordered collection type. Its return type is the value type of the type of the first operand. It has one signature:

 PROCEDURE LAST ( c : <OrderedCollectionType> ) : <ValueType>;

Function Procedure MIN

Function MIN is a polymorphic function to return the smallest value from a non-empty variadic list of operands. All its operands shall be of the same type. The operand type shall be a scalar or ordinal type. Its return type is the operand type. It has one signature:

 PROCEDURE MIN ( values : ARGLIST >0 OF <ScalarOrOrdinalType> ) : <OperandType>;

Function Procedure MAX

Function MAX is a polymorphic function to return the largest value from a non-empty variadic list of operands. All its operands shall be of the same type. The operand type shall be a scalar or ordinal type. Its return type is the operand type. It has one signature:

 PROCEDURE MAX ( values : ARGLIST >0 OF <ScalarOrOrdinalType> ) : <OperandType>;

Built-in Compile-Time Macros

Macro TMIN

An Invocation of TMIN is replaced by the smallest legal value of its operand. Its operand shall be the type identifier of a scalar or ordinal type. Its replacement value is of the type denoted by its operand. It has one signature:

 PROCEDURE TMIN ( T : <ScalarOrOrdinalTypeIdentifier> ) : <T>;

Macro TMAX

An Invocation of TMAX is replaced by the largest legal value of its operand. Its operand shall be the type identifier of a scalar or ordinal type. Its replacement value is of the type denoted by its operand. It has one signature:

 PROCEDURE TMAX ( T : <ScalarOrOrdinalTypeIdentifier> ) : <T>;

Macro TLIMIT

An Invocation of TLIMIT is replaced by the capacity limit of its operand. Its operand shall be the type identifier of a collection type. Its replacement value is of type LONGCARD. It has one signature:

 PROCEDURE TLIMIT ( T : <CollectionTypeIdentifier> ) : LONGCARD;

Macro TSIZE

An Invocation of TSIZE is replaced by the allocation size required for an instance of a type denoted by its operand. Its operand shall be any type identifier. Its replacement value is of type LONGCARD. It has one signature:

 PROCEDURE TSIZE ( T : <TypeIdentifier> ) : LONGCARD;

Blueprints

EBNF | Syntax Diagram

to do

Type Classification

EBNF | Syntax Diagram

to do

Literal Compatibility

EBNF | Syntax Diagram

to do

Constraints

EBNF | Syntax Diagram

to do

Requirements

EBNF | Syntax Diagram

to do

Primitives

Primitives are built-in polymorphic macros for internal use by the compiler to synthesise various operations for library defined ADTs. They should not need to be invoked directly by library or program code since their functionality becomes available through built-in syntax. Library implementations of ADTs may be required to provide specific implementations and bind them to their respective primitives.

Primitive SXF

Primitive SXF is a polymorphic primitive to serialise a scalar value given by its first operand to scalar exchange format and pass the serialised value back in its second operand. Its first operand shall be of a scalar type. Its second operand shall be an OCTET array large enough to hold the serialised value. It has one signature:

 PROCEDURE SXF ( CONST value : <ScalarType>; VAR sxfValue : ARRAY OF OCTET );

Primitive VAL

Primitive VAL is a polymorphic primitive to convert a serialised scalar value given by its first operand to a value of a scalar type and pass the converted value back in its second operand. Its first operand shall be an OCTET array. Its second operand shall be of the scalar target type. It has one signature:

 PROCEDURE VAL ( CONST sxfValue : ARRAY OF OCTET; VAR value : <ScalarType> );

Primitive STORE

Primitive STORE is a polymorphic primitive to overwrite one or more values in a collection. It has nine signatures:

Overwriting A Single Value In An Array

To overwrite a value at a given index in an array, the primitive is called passing the array as its first operand, the index as its second operand and the value to be written as its third operand. The first operand shall be of an array type. The second operand shall be of the array type's index type. The third operand shall be of the array's value type.

 PROCEDURE STORE ( c : <ArrayType>; atIndex : <IndexType>; value : <ValueType> );
Overwriting A Single Value In A List

To overwrite a value for a given accessor in a list, the primitive is called passing the list as its first operand, the accessor as its second operand and the value to be written as its third operand. The first operand shall be of a list type. The second operand shall be of the list type's accessor type. The third operand shall be of the list's value type.

 PROCEDURE STORE ( c : <ListType>; p : <AccessorType>; value : <ValueType> );
Overwriting Multiple Values In An Array Or List

To overwrite one or more consecutive values starting at a given index in an array or list, the primitive is called passing the array or list as its first operand, the start index as its second operand and the values to be written as its third operand. The first operand shall be of an array or list type. The second operand shall be of the array's index type or in the case of a list, it shall be of type LONGCARD. The third operand shall be a non-empty variadic list of the value type of the array or list.

 PROCEDURE STORE
   ( c : <SeqType>; fromIndex : <IndexType>; values : ARGLIST >0 OF <ValueType> );
Overwriting An Array Or List Or Part Thereof With A Fill-Value

To overwrite one or more consecutive values starting at a given index in an array or list with a fill value, the primitive is called passing the array or list as its first operand, the start index as its second operand, the number of values to be overwritten as its third operand and the fill value as its fourth operand. The first operand shall be of an array or list type. The second operand shall be of the array's index type or in case of a list, it shall be of type LONGCARD. The third operand shall be of type LONGCARD and the fourth operand shall be of the value type of the array or list.

 PROCEDURE STORE
   ( c : <SeqType>; fromIndex : <IndexType>; valueCount : LONGCARD; fillValue : <ValueType> );
Overwriting The Element Counter for A Single Element In A Set

To overwrite the element counter of a given element in a set, the primitive is called passing the set as its first operand, the element as its second operand and the counter value to be written as its third operand. The first operand shall be of a set type. The second operand shall be of the set's element type. The third operand shall be of the set's counter type.

 PROCEDURE STORE ( c : <SetType>; element : <ElementType>; counter : <CounterType> );
Overwriting The Element Counters for Multiple Elements In A Set

To overwrite the element counters of multiple given elements in a set, the primitive is called passing the set as its first operand and a list of element/counter pairs to be written as its second operand. The first operand shall be of a set type. The second operand shall be a non-empty variadic list of element/counter pairs, where the elements are of the set's element type and the counters are of its counter type.

 PROCEDURE STORE
   ( c : <SetType>; entries : ARGLIST >0 OF { element : <ElementType>; counter : <CounterType> } );
Overwriting A Single Value For A Key In A Dictionary

To overwrite a value for a given key in a dictionary, the primitive is called passing the dictionary as its first operand, the key as its second operand and the value to be written as its third operand. The first operand shall be of a dictionary type. The second operand shall be of the dictionary's key type. The third operand shall be of the dictionary's value type.

 PROCEDURE STORE ( c : <DictionaryType>; key : <KeyType>; value : <ValueType> );
Overwriting Multiple Values For Given Keys In A Dictionary

To overwrite multiple values for given keys in a dictionary, the primitive is called passing the dictionary as its first operand and a list of key/value pairs to be written as its second operand. The first operand shall be of a dictionary type. The second operand shall be a non-empty variadic list of key/value pairs, where the keys are of the dictionary's key type and the values are of its value type.

 PROCEDURE STORE
   ( c : <DictionaryType>; entries : ARGLIST >0 OF { key : <KeyType >; value : <ValueType> );
Overwriting The N-th Value For A Key In A Multi-Dictionary

To overwrite the n-th value for a given key in a multi-dictionary, the primitive is called passing the dictionary as its first operand, the key as its second operand, the index of the value to be overwritten as its third operand and the value to be written as its fourth operand. The first operand shall be of a multi-dictionary type. The second operand shall be of the dictionary's key type. The third operand shall be of type CARDINAL. The fourth operand shall be of the dictionary's value type.

 PROCEDURE STORE
   ( c : <DictionaryType>; key : <KeyType>; index : CARDINAL; value : <ValueType> );

Primitive VALUE

Primitive VALUE is a polymorphic primitive to retrieve a value from a collection. It has five signatures:

Retrieving A Value From An Array

To retrieve the value stored at a given index in an array, the primitive is called passing the array as its first operand and the index as its second operand. The first operand shall be of an array type and the second operand shall be of the array's index type. The primitive returns the value stored at the index in the array.

 PROCEDURE VALUE ( VAR c : <ArrayType>; atIndex : <IndexType> ) : <ValueType>;
Retrieving A Value From A List

To retrieve the value stored at a given list element accessor from a list, the primitive is called passing the list as its firs operand and the element accessor as its second operand. The first operand shall be of a list type and the second operand shall be of the list's accessor type. The primitive returns the value stored at the accessor in the list.

 PROCEDURE VALUE ( VAR c : <ListType>; p : <AccessorType> ) : <ValueType>;
Retrieving An Element Counter From A Set

To retrieve the counter for a given element in a set, the primitive is called passing the set as its first operand and the element as its second operand. The first operand shall be of a set type and the second operand shall be of the set's element type. The primitive returns a value indicating how many times the element is stored in the list.

 PROCEDURE VALUE ( VAR c : <SetType>; element : <ElementType> ) : <CounterType>;
Retrieving A Value From A Dictionary

To retrieve the value stored for a given key in a dictionary, the primitive is called passing the dictionary as its first operand and the key as its second operand. The first operand shall be of a dictionary type and the second operand shall be of the dictionary's key type. The primitive returns the value stored for the key in the dictionary.

 PROCEDURE VALUE ( VAR c : <DictionaryType>; key : <KeyType> ) : <ValueType>;
Retrieving The N-th Value For A Key From A Multi-Dictionary

To retrieve the n-th value stored for a key in a multi-dictionary, the primitive is called passing the dictionary as its first operand, the key as its second operand and the index of the value to be retrieved as its third operand. The first operand shall be of a multi-dictionary type. The second operand shall be of the dictionary's key type and the third operand shall be of type CARDINAL. The primitive returns the value stored at the index for the key in the dictionary.

 PROCEDURE VALUE
   ( VAR c : <DictionaryType>; key : <KeyType>; index : CARDINAL ) : <ValueType>;

Primitive SEEK

Primitive SEEK is a polymorphic primitive to obtain accessors to list elements for list traversal. It has two signatures:

Obtaining An Element Accessor By Index

To obtain a list element accessor for the n-th value stored in a list, the primitive is called passing the list as its first operand and the index as its second operand. The first operand shall be of a list type and the second operand shall be of type LONGCARD. The primitive returns an accessor for the list element that stores the value or NIL if no element exists at the given index.

 PROCEDURE SEEK ( c : <ListType>; index : LONGCARD ) : <AccessorType>;
Obtaining An Element Accessor Through Neighbour

To obtain the preceding or succeeding list element accessor of a known accessor in a list, the primitive is called passing the list as its first operand, the known accessor as its second operand and a neighbour selector as its third operand. The first operand shall be of a list type. The second operand shall be of the list's accessor type and the third operand shall be a quoted character literal of type CHAR where "+" selects the succeeding and "-" selects the preceding neighbour. The primitive returns an accessor to the selected neighbour element in the list or NIL if the selected neighbour does not exist.

 PROCEDURE SEEK
   ( c : <ListType>; current : <AccessorType>; plusOrMinus : <CharLiteral> ) : <AccessorType>;

Primitive SUBSET

Primitive SUBSET is a polymorphic primitive to test whether a set is a subset of another. It is called passing the set to be tested as its first operand and the suspected superset as its second operand. Both operands shall be of the same set type. The primitive returns TRUE if the first operand is a subset of the second operand, otherwise FALSE. It has one signature:

 PROCEDURE SUBSET ( subset, superset : <SetType> ) : BOOLEAN;

Pragmas

EBNF | Syntax Diagram

Pragmas are directives to the compiler, used to control or influence the compilation process, but they do not change the meaning of a program. Language defined pragmas and their properties are listed below:

PragmaPurposeScopeAvailabilitySafety
MSGEmit compile time console messagesPragmamandatorysafe
IFConditional compilation, if-branchPragmamandatorysafe
ELSIFConditional compilation, elsif-branchPragmamandatorysafe
ELSEConditional compilation, else-branchPragmamandatorysafe
ENDConditional compilation, terminatorPragmamandatorysafe
INLINESuggest procedure inliningProceduremandatorysafe
NOINLINEInhibit procedure inliningProceduremandatorysafe
OUTPromise to write to a VAR parameterFormal parametermandatorysafe
GENERATEDDate/time stamp of library generationFilemandatorysafe
ENCODINGSpecify source text character encodingFilemandatorysafe
ALIGNSpecify memory alignmentModule, Type, Recordoptionalsafe
PADBITSInsert padding bits into packed recordsRecordoptionalsafe
NORETURNPromise never to returnRegular procedureoptionalsafe
PURITYSpecify procedure purity levelProcedure, Typeoptionalsafe
SINGLEASSIGNMark single-assignment variableGlobal and Local Varoptionalsafe
LOWLATENCYMark latency-critical variableLocal Vsroptionalsafe
VOLATILEMark volatile variableGlobal Varoptionalsafe
DEPRECATEDMark deprecated entityDefinition, Declarationoptionalsafe
FORWARDForward declaration for single-pass compilersPragmaoptionalsafe
ADDRMap procedure or variable to fixed addressDefinition, Declarationoptionalunsafe
FFISpecify foreign function interfaceModuleoptionalunsafe
FFIDENTMap identifier to foreign identifierGlobal Var, Procedureoptionalunsafe

Pragma Scope And Positioning

The position where a pragma may appear in the source text depends on its scope.

ScopeApplies toInsertion Point
Fileentire fileat the beginning of a file or immediately after a BOM
Moduleentire modulebetween module header and its trailing semicolon
Pragmapragma itselfanywhere a block comment may appear
Typearray or procedure type declarationbetween type declaration and its trailing semicolon
Recordinsertion point forwardanywhere a fieldlist may appear within a record
Global Varglobal variable declarationbetween variable declaration and its trailing semicolon
Procedureprocedure declarationbetween procedure header and its trailing semicolon
Formal Parameterformal parameter declarationimmediately after the formal type of the parameter
Local Varlocal variable declarationbetween variable declaration and its trailing semicolon

Pragma Safety

A pragma is safe if it provides a safe facility. It is unsafe if it provides an unsafe facility. The use of an unsafe pragma must be enabled by unqualified import of its identically named enabler. Pragma enablers of supported unsafe pragmas shall be provided by pseudo-module UNSAFE.

Language Defined Pragmas In Detail

Mandatory Pragmas

Pragma MSG

EBNF | Syntax Diagram

Pragma MSG emits four different types of user definable console messages during compilation: informational messages, compilation warnings, compilation error messages and fatal compilation error messages. The type of a message is determined by a message mode selector. Console messages consist of a quoted string literal, the value of a compile time constant or pragma or a comma separated list of these components.

The value of a pragma that represents a compile time setting is denoted by the pragma symbol prefixed with a question mark. Language defined pragmas that represent compile settings are ALIGN and ENCODING.

Examples:

 <*MSG=INFO : "The current alignment is: ", ?ALIGN*> (* emits alignment value *)
 <*MSG=INFO : "The current encoding is: ", ?ENCODING*> (* emits encoding name *)

Only pragmas that represent compile time settings may be queried in this way.

Message Mode INFO

Message mode selector INFO is used to emit user defined information during comilation. Emitting an informational message does not change the warning or error count of the current compilation run and it does not cause comilation to fail or abort. A compiler switch may be provided to silence informational messages.

Example:

 <*MSG=INFO : "Library documentation is available at http://foolib.com"*>
Message Mode WARN

Message mode selector WARN is used to emit user defined warnings during compilation. Emitting a warning message increments the warning count of the current compilation run but it does not cause compilation to fail or abort. Warnings emitted via pragma MSG are always hard compile time warnings.

Example:

 <*MSG=WARN : "foo exceeds maximum value. A default of 100 will be used."*>
Message Mode ERROR

Message mode selector ERROR is used to emit user defined error messages during compilation. Emitting an error message increments the error count of the current compilation run and will ultimately cause compilation to fail but it does not cause an immediate abort. User defined error messages may not be silenced.

Example:

 <*MSG=ERROR : "Value of foo is outside of its legal range of [1..100]."*>
Message Mode FATAL

Message mode selector FATAL is used to emit user defined fatal error messages during compilation. Emitting a fatal error message increments the error count of the current compilation run and causes compilation to fail and abort immediately. User defined fatal error messages may not be silenced. Abort may not be avoided.

Example:

 <*MSG=ABORT : "Unsupported target architecture."*>

Pragmas For Conditional Compilation

EBNF | Syntax Diagram

Conditional compilation pragmas are used to denote conditional compilation sections. A conditional compilation section is an arbitrary portion of source text that is either compiled or ignored, depending on whether or not a given condition in form of a boolean compile time expression within the pragma is met.

A conditional compilation section consists of an initial conditional compilation branch denoted by pragma IF, followed by zero or more alternative branches denoted by pragma ELSIF, followed by an optional default branch denoted by pragma ELSE, followed by closing pragma END.

Example:

 <*IF (TSIZE(INTEGER)=2)*>
 CONST Model = TypeModel.small;
 <*ELSIF (TSIZE(INTEGER)=4)*>
 CONST Model = TypeModel.medium;
 <*ELSIF (TSIZE(INTEGER)=8)*>
 CONST Model = TypeModel.large;
 <*ELSE*> <*MSG=FATAL : "unsupported type model."*>
 UNSAFE.HALT(Errors.UnsupportedTypeModel);
 <*END*>

Conditional compilation sections may be nested up to a maximum nesting level of ten including the outermost conditional compilation section. A fatal compile time error shall occur if this value is exceeded. Pragma IF increments the current nesting level, Pragmas ELSIF and ELSE leave it unchanged and Pragma END decrements it.

Pragma IF

Pragma IF denoted the start of the initial branch of a conditional compilation section. The source text within the initial branch is only processed if the condition specified in the pragma is true, otherwise it is ignored.

Pragma ELSIF

Pragma ELSIF denotes the start of an alternative branch in a conditional compilation section. The source text within an alternative branch is only processed if the condition specified in the pragma is true and the conditions specified for the corresponding initial branch and all preceding alternative branches of the same nesting level are false, otherwise it is ignored.

Pragma ELSE

Pragma ELSE denotes the start of a default branch within a conditional compilation section. The source text within the default branch is only processed if the conditions specified for the initial branch and all preceding alternative branches of the same nesting level are false, otherwise it is ignored.

Pragma END

Pragma END denotes the end of a conditional compilation section.

Pragma INLINE

EBNF | Syntax Diagram

Pragma INLINE represents a suggestion that inlining of a procedure is desirable except for certain scenarios where it is specifically mandated. It shall appear both in the definition and implementation of the procedure. An informational message shall be emitted if the suggestion is not followed.

Example:

 PROCEDURE Foo ( bar : Baz ) <*INLINE*>;

Scenarios where pragma INLINE represents a mandate to inline are procedures with a single statement, such as procedures with a single assignment and functions with a single RETURN statement. This inline guarantee exists to promote the use of data encapsulation. Mutators and accessors tagged with an INLINE pragma shall always be inlined.

Examples:

 (* Mutator with Inline Mandate *)
 PROCEDURE setFoo ( value : Foo ) <*INLINE*>;
 BEGIN
   hiddenFoo := value
 END setFoo;

 (* Accessor with Inline Mandate *)
 PROCEDURE foo : Foo <*INLINE*>;
 BEGIN
   RETURN hiddenFoo
 END foo;

Pragma NOINLINE

EBNF | Syntax Diagram

Pragma NOINLINE represents a mandate that a procedure shall not be inlined. It shall appear both in the definition and implementation of the procedure. The use of pragmas INLINE and NOINLINE is mutually exclusive.

Example:

 PROCEDURE Foo ( bar : Baz ) <*NOINLINE*>;

Pragma BLOCKING

EBNF | Syntax Diagram

Pragma BLOCKING marks a procedure as blocking to indicate that it invokes a procedure or API that may cause it to wait for an event or availability of a shared resource or the completion of an IO operation. If a procedure not marked as blocking calls a procedure that is marked as blocking, a promotable compile time warning shall occur.

Example:

 PROCEDURE Read ( f : File; VAR ch : CHAR ) <*BLOCKING*>;

Pragma OUT

EBNF | Syntax Diagram

Pragma OUT marks a formal VAR parameter p in the header of a procedure P with a promise to write. The promise is kept if it can be proven at compile time that p is written to within the body of P in every possible runtime scenario, either by assignment or by passing p to an OUT marked VAR paramter in a procedure call. A promotable soft compile time warning shall occur if the promise is not kept.

Example:

 PROCEDURE init ( VAR n : OCTET <*OUT*> );

Pragma GENERATED

EBNF | Syntax Diagram

Pragma GENERATED encodes the name of the template a library was generated from and the date and time when it was last generated. The pragma is inserted into the source by the Modula-2 template engine. A conforming implementation shall use the information recorded in the pragma to avoid unnecessary regeneration of libraries.

Example:

 <*GENERATED FROM AssocArrays, 2014-12-31, 23:59:59+0100*>

Pragma ENCODING

EBNF | Syntax Diagram

Pragma ENCODING specifies the encoding of the source file in which it appears. The pragma controls whether in addition to the characters that are permitted by the grammar, any further printable characters are permitted within quoted literals and comments. Any source file that is not strictly 7-bit ASCII encoded must contain an ENCODING pragma to specify its encoding. Semantics are given below.

BOMEncoding PragmaCharacters Permitted in Quoted Literals and Comments
No BOMno encoding pragma in sourceonly printable 7-bit ASCII characters as per grammar
with specifier "ASCII"
with specifier "UTF8"any printable character encodable in UTF8
with implementation defined specifierany printable character encodable in specified encoding
UTF8 BOMno encoding pragma in sourceonly printable 7-bit ASCII characters as per grammar
with specifier "ASCII"
with specifier "UTF8"any printable character encodable in UTF8
Any other BOMuse of pragma is mandatoryany printable character encodable in specified encoding

An implementation that supports ASCII only shall recognise encoding specifier "ASCII". It shall ignore any UTF8 BOM but reject any non-ASCII characters in the source file. An implementation that supports UTF8 shall recognise specifiers "ASCII" and "UTF8". Support for other encodings is implementation defined. Only one encoding pragma per source file is permitted.

Encoding Verification

As an option, pragma ENCODING may provide encoding verification. If supported, a list of arbitrary samples with pairs of quoted characters and their respective code point values may follow the encoding specifier.

If a sample list is specified within the pragma body, a verification is carried out by matching the quoted literals in the sample list against their respective code points. Any mismatching pair in the sample list shall cause a fatal compilation error and compilation to abort immediately. The maximum number of code point samples is implementation defined. A maximum of at least 16 is recommended. Excess samples shall be ignored.

Example:

 <*ENCODING="UTF8" : "é"=0uE9, "©"=0uA9, "€"=0u20AC*>

Optional Pragmas

Optional Pragma ALIGN

EBNF | Syntax Diagram

Pragma ALIGN controls memory alignment. Alignment is specified in octets.

When the pragma is placed in a module header, it has module scope and determines the default alignment within the module. Permitted alignment values range from one to 32 octets.

Example:

 DEFINITION MODULE Foolib <*ALIGN=TSIZE(CARDINAL)*>; (* module scope *)

When the pragma is placed at the end of an array type declaration, it has array scope and determines the alignment of array components. Permitted alignment values range from one to 32 octets.

Example:

 TYPE Array = ARRAY 10 OF OCTET <*ALIGN=4*>; (* array scope *)

When the pragma is placed in the body of a record type declaration, it has field list scope and determines the alignment of record fields following the pragma. Permitted alignment values range from zero to 32 octets.

Example:

 TYPE Aligned = RECORD
 <*ALIGN=2*>  foo, bar : INTEGER;  (* 16 bit aligned *)
 <*ALIGN=4*>  baz, bam : INTEGER;  (* 32 bit aligned *)
 <*ALIGN=0*>  bits, bobs : [0..15] OF OCTET  (* packed *)
 END; (* Aligned *)

A value of zero specifies packing. When packing is specified, the allocation size of a field of an anonymous subrange of type OCTET, CARDINAL and LONGCARD is reduced to the smallest bit width required to encode its value range. Fields of any other type are aligned on octet boundaries when packing is specified.

Optional Pragma PADBITS

EBNF | Syntax Diagram

Pragma PADBITS inserts a specified number of padding bits into a packed record type declaration. The maximum permitted value is 256 bits. The pragma is only permitted where alignment is set to zero.

Example:

 TYPE Packed = RECORD <*ALIGN=0*>
   oneBit    : [0..1] OF OCTET; (* 1 bit *)
 <*PADBITS=2*>           (* unused 2 bits *)
   twoBits   : [0..3] OF OCTET; (* 2 bits *)
   threeBits : [0..7] OF OCTET; (* 3 bits *)
 END; (* Packed *)

Optional Pragma NORETURN

EBNF | Syntax Diagram

Pragma NORETURN marks a regular procedure with a promise never to return in any runtime scenario. A soft compile time warning shall occur if the compiler cannot prove that the promise is kept.

Example:

 PROCEDURE Reboot System? <*NORETURN*>;

Optional Pragma PURITY

EBNF | Syntax Diagram

Pragma PURITY marks a procedure with an intended purity level:
• level 0 : may read and modify global state, may call procedures of any level (Default)
• level 1 : may read but not modify global state, may only call level 1 and level 3 procedures
• level 2 : may not read but modify global state, may only call level 2 and level 3 procedures
• level 3 : pure procedure, may not read nor modify global state, may only call level 3 procedures
An implementation shall emit a promotable soft compile time warning for any purity level violation.

Example:

 PROCEDURE Foo ( bar : Bar) : Baz <*PURITY=3*>; (* pure and side-effect free *)

Optional Pragma SINGLEASSIGN

EBNF | Syntax Diagram

Pragma SINGLEASSIGN marks a variable as a single-assignment variable.

Such a variable should be assigned to only once in every possible runtime scenario. An implementation shall issue a promotable soft compile time warning for any single-assignment violation it may detect.

Example:

 VAR foo : INTEGER <*SINGLEASSIGN*>;

Optional Pragma LOWLATENCY

EBNF | Syntax Diagram

Pragma LOWLATENCY marks a local variable as latency-critical.

Marking a variable latency-critical represents a suggestion that mapping the variable to a machine register is desirable. An informational message shall be emitted if the suggestion is not followed.

Example:

 VAR foo : INTEGER <*LOWLATENCY*>;

Optional Pragma VOLATILE

EBNF | Syntax Diagram

Pragma VOLATILE marks a global variable as volatile.

By marking a variable volatile the author states that its value may change during the life time of a program even if no write access can be deduced from source code analysis. An implementation shall neither eliminate any variable so marked, nor shall it emit any unused variable warning for any variable so marked.

Example:

 VAR foo : INTEGER <*VOLATILE*>;

Optional Pragma DEPRECATED

EBNF | Syntax Diagram

Pragma DEPRECATED marks a constant, variable, type or procedure as deprecated. A promotable soft com- pile time warning shall occur whenever an identifier of a deprecated entity is encountered.

Example:

 PROCEDURE foo ( bar : Baz ) <*DEPRECATED*>;

Optional Pragma FORWARD

EBNF | Syntax Diagram

Pragma FORWARD shall be the only means of forward declaration in a single-pass compiler. Multi-pass compilers shall silently ignore any occurrences of pragma FORWARD without analysis of its contents. Two kinds of forward declarations may be embedded in the pragma: Type and procedure declarations.

Example:

 <*FORWARD TYPE ListNode*>
 TYPE ListNodePtr = POINTER TO ListNode;
 TYPE ListNode = RECORD data : Foo; nextNode : ListNodePtr END;

Optional Pragma ADDR

EBNF | Syntax Diagram

Pragma ADDR maps a procedure or a global variable to a fixed memory address.

Examples:

 PROCEDURE Reset <*ADDR=0x12*>;
 VAR memoryMappedPort : CARDINAL <*ADDR=0x100*>;

Optional Pragma FFI

EBNF | Syntax Diagram

Pragma FFI marks a Modula-2 definition part as the Modula-2 interface to a library implemented in another language. Procedure definitions and type declarations in the definition part shall follow the calling convention of the specified language environment for the current target. Predefined foreign interface specifiers are “C”, “Fortran”, “CLR” and “JVM”. If pragma FFI is provided, at least one foreign interface shall be supported. CLR or JVM support is recommended for implementations that target the CLR or JVM, respectively.

Example:

 DEFINITION MODULE stdio <*FFI=“C”*>;
 FROM UNSAFE IMPORT FFI, VARGLIST;
 PROCEDURE printf ( CONST format : ARRAY OF CHAR; arglist : VARGLIST );

Optional Pragma FFIDENT

EBNF | Syntax Diagram

Pragma FFIDENT maps a Modula-2 identifier of a foreign procedure or variable definition to its respective identifier in the foreign library. It shall be used when the foreign identifier conflicts with Modula-2 reserved words or reserved identifiers. The pragma may only be used within a foreign function interface module.

Examples:

 PROCEDURE Length ( s : ARRAY OF CHAR ) : INTEGER <*FFIDENT=”LENGTH”*>;
 VAR rwMode : [0..3] OF CARDINAL <*VOLATILE*> <*FFIDENT=”foobarlib_rw_mode”*>;

Implementation Defined Pragmas

EBNF | Syntax Diagram

Implementation defined pragmas are compiler specific and generally non-portable.

An implementation defined pragma starts with a pragma symbol, which may be followed by a value assignment. The pragma ends with a mandatory default clause. The pragma symbol is an implementation defined name which shall be all-lowercase or mixed case. It may be qualified with an implementation prefix, indicating the name of the compiler. The value assignment follows if and only if the pragma is defined to hold a value. Such a value may be either a boolean value or a whole number.

Example:

 <*GM2.UnrollLoops=TRUE|WARN*> (* turn loop-unrolling on, ignore but warn if unknown *)

The default clause specifies how the pragma shall be treated by implementations that do not recognise it. Modes INFO and WARN mandate it shall be ignored with an informational or warning message respectively. Modes ERROR and FATAL mandate it shall cause a compile time or fatal compile time error respectively.

Incorrect Pragma Use and Unrecognised Pragmas

A pragma is incorrectly used if it is malformed, misplaced or any other rule for its use is not met. Any incorrect use of a mandatory pragma or a supported optional pragma shall cause a compile time error. Use of an unsafe pragma that is not supported or has not been enabled shall cause a compile time error.

Use of a safe optional pragma that is not supported shall cause a promotable soft compile time warning. An unsupported or unrecognised encoding specifier in pragma ENCODING shall cause a fatal compile time error. A code point sample list within pragma ENCODING shall be ignored if encoding verification is not supported. If a code point sample list or any excess samples are ignored a soft compile time warning shall be emitted. An unsupported or unrecognised language specifier in pragma FFI shall cause a compile time error.

An unrecognised implementation defined pragma shall be treated as specified by its default clause. An implementation defined pragma without a default clause is malformed and shall cause a compile time error.


Downloads


Older Wiki content, parts of which may be reused

Scope
Types
Predefined Identifiers
Retrieved from http://modula-2.net/m2r10/pmwiki.php?n=Spec.LanguageReport
Page last modified on 2015-10-09 22:33