Skip to content

Language Description

Benjamin Kowarsch edited this page Aug 29, 2019 · 880 revisions

Lexical Entities | Syntactic Entities | Statements | Expressions | Type Compatibility | Predefined Entities | Syntax Binding | Low Level Facilities | Pragmas | Implementation Info | Terms of Reference

Lexical Entities

Reserved Words

ALIAS, AND, ARGLIST, ARRAY, BEGIN, CAPACITY, CASE, CAST, CONST, COPY, DEFINITION, DIV, DO, ELSE, ELSIF, END, EXIT, FOR, IF, IMPLEMENTATION, IMPORT, IN, LOOP, MOD, MODULE, NEW, NOT, OF, OPAQUE, OR, POINTER, PROCEDURE, READ, RECORD, RELEASE, REPEAT, RETAIN, RETURN, SET, THEN, TO, TYPE, UNTIL, VAR, WHILE, WRITE;

Note CAPACITY and CAST are Schrödinger's tokens, both reserved word and built-in identifier.

Special Symbols

Delimiters

( ) [ ] { } ' "

Punctuation

. , : ; = + * @ | .. := ++ -- .*

Operators

= # > >= < <= + - & \ * / :: ^ .

Comment Delimiters

! (* *)

Pragma Delimiters

<* *>

Identifiers

Identifiers denote predefined or user defined names for syntactic entities. A standard Modula-2 identifier starts with a letter and may be followed by letters and digits.

StdIdent := Letter ( Letter | Digit )* ;

A foreign identifier may also contain leading, non-trailing, non-consecutive $ characters and non-leading, non-trailing, non-consecutive _ characters. Foreign identifiers are used in connection with foreign library APIs. Their use is enabled by pragma or compiler option.

ForeignIdent :=
  '$' ( Letter | Digit ) ForeignIdentTail* | StdIdent ForeignIdentTail+ ;

ForeignIdentTail :=
  ( '$' | '_' ) ( Letter | Digit )+ ;

Numeric Literals

Numeric literals denote numeric values, either real number values, whole number values or character code values.

Real Numbers

Real number values are always given in decimal notation, start with an integral part, followed by an optional fractional part, followed by an optional exponent part.

RealNumber := integralPart fractionalPart? exponentialPart? ;

integralPart := '0' | ( '1' .. '9' ) ( DigitSeparator? DigitSequence )? ;

fractionalPart := '.' DigitSequence ;

exponent := 'e' ( '+' | '-' )? DigitSequence ;

DigitSequence := DecimalNumber ;

Whole Numbers

Whole number values may be given in decimal, radix-2 or radix-16 notation. C-style prefixes are used to indicate the radix of non-decimal literals. Prefix 0b indicates radix-2 and prefix 0x indicates radix-16. Digits may be grouped using ' as a digit separator. A digit separator must always be preceded and followed by a digit.

WholeNumber := DecimalNumber | Base2Number | Base16Number ;

DecimalNumber := Digit+ ( DigitSeparator Digit+ )* ;

Base2Number := '0b' Base2Digit+ ( DigitSeparator Base2Digit+ )* ;

Base16Number := '0x' Base16Digit+ ( DigitSeparator Base16Digit+ )* ;

Digit := '0' .. '9' ;

Base2Digit := '0' | '1' ;

Base16Digit := Digit | 'A' .. 'F' ;

alias DigitSeparator = "'" ;

Character Codes

Character code values are always given in radix-16 notation with prefix 0u.

CharacterCode := '0u' Base16Digit+ ( DigitSeparator Base16Digit+ )* ;

Quoted Literals

Quoted literals denote text. They are delimited by single quotes ' or double quotes ".

QuotedLiteral := SingleQuotedLiteral | DoubleQuotedLiteral ;

A single quoted literal may contain double quotes but not single quotes. A double quoted literal may contain single quotes but not double quotes. A quoted literal may contain whitespace but not any control codes. It may not span multiple lines.

SingleQuotedLiteral := "'" ( AnyPrintableExceptSingleQuote | EscSeq )* "'" ;

DoubleQuotedLiteral := '"' ( AnyPrintableExceptDoubleQuote | EscSeq )* '"' ;

Backslash escape sequences may be used to insert newline and tabulator control codes into a quoted literal. Escape sequence \n inserts newline and \t inserts tabulator. A verbatim backslash must be escaped as \\. No other escape sequences shall be supported.

EscSeq := '\' ( 'n' | 't' | '\' ) ;

Non-Semantic Entities

Whitespace

Whitespace ASCII(0x20) terminates a symbol, except within quoted literals, pragmas and comments.

Tabulator

Tabulator ASCII(0x09) terminates a symbol, except within pragmas and comments. It may not occur within quoted literals.

Newline

ASCII-CR, ASCII-LF and ASCII-CR immediately followed by ASCII-LF are interpreted as a single newline. Newline terminates a symbol, except within pragmas and block comments. It may not occur within quoted literals. Newline increments the line counter and resets the column counter for use in informational, warning and error messages.

Comments

Comments are non-semantic symbols ignored by the language processor. They may occur anywhere before or after semantic symbols and are used for documentation and annotation. There are line comments and block comments.

Line Comments

Line comments start with a ! and are terminated by newline.

LineComment := '!' ( AnyPrintable | Tabulator )* Newline ;

Block Comments

Block comments are delimited by block comment delimiters (* and *). Block comments may span multiple lines and may be nested up to a maximum of ten levels including the outermost comment.

BlockComment := '(*' ( BlockComment | AnyPrintable | Tabulator | Newline )* '*)' ;

Pragmas

Pragmas are directives to the language processor to control or influence the compilation process. They are delimited by delimiters <* and *>, may span multiple lines but may not be nested.

Pragma := '<*' PragmaBody '*>' ;

Syntactic Entities

Compilation Units

Modula-2 programs and libraries consist of one or more compilation units called modules. A program consists of exactly one program MODULE and any number of library modules. A library module consists of a definition part, called a DEFINITION MODULE, and an optional implementation part, called an IMPLEMENTATION MODULE. The definition part defines the client interface of the library. The implementation part implements the library according to the interface. The implementation part is strictly accessible through its definition part only.

Identifier Visibility

Identifiers that are predefined by the language are pervasive, that is, they are visible in every scope without import. Identifiers provided by a special built-in module are visible only within a scope into which they are explicitly imported. Identifiers defined within a definition module are visible within the definition module in which they are defined, within the corresponding implementation module and any scope into which they are explicitly imported. Identifiers declared within an implementation or program module are visible only within the scope in which they are declared.

Constants and aliases are visible in the scope in which they are defined or declared from the point forward where they are defined or declared. That is, constants and aliases must be defined or declared before they are referenced.

Types, procedures and variables are visible in the entire scope in which they are defined or declared. That is, they may be referenced before they are defined or declared.

Scope

Scope is a classification of the visibility of identifiers. There are three levels of scope. Global scope, module scope and local scope. Module scope is a sub-scope of global scope and local scope is a sub-scope of module scope.

Global Scope

Global scope encompasses an entire program. Only predefined identifiers have global scope.

Module Scope

Module scope encompasses a module. Identifiers that are defined or declared in, or imported into the top level of a module have module scope.

Local Scope

Local scope encompasses a limited area within a module.

Local scopes may be nested. The surrounding scope in which a local scope is nested is called the outer scope. The nested scope is called the inner scope.

Identifiers that belong only to an outer scope are also visible in an inner scope and may be redefined within the inner scope. Redefining an identifier of an outer scope within an inner scope causes the entity denoted by the identifier to be shadowed. A shadowed entity is no longer addressable through its identifier within the scope in which it has been shadowed and within any of its sub-scopes.

Identifiers that belong only to an inner scope are visible only in the inner scope and any of its sub-scopes but not in any outer scope.

Procedure Scope

The most common local scope is procedure scope. It is created by a procedure declaration.

A procedure scope overlaps with its outer scope. The outer scope extends to the end of the procedure header and continues after the end of the procedure body. The inner scope extends from the beginning of the procedure header to the end of the procedure body. The procedure header thus belongs to both the outer and the inner scope.

The procedure's identifier is visible in both the outer and the inner scope. It may be referenced in either scope and may not be redefined in either scope. The identifiers of formal parameters are components of the procedure. As such they exist in both scopes but may only be referenced within the inner scope and may not be redefined within the inner scope.

FOR Statement Scope

Another common local scope is the scope created by a FOR statement. A FOR statement scope does not overlap with its outer scope. It extends from the beginning of the FOR statement's header to the end of its body. The loop variants declared within the loop header have local scope, they are only visible within the loop.

Import and Export

Identifiers defined within a definition module are automatically exported for import and use by client modules. By contrast, program and implementation modules do not export any identifiers. An IMPORT directive may be used within any kind of module to explicitly import the identifiers exported by definition modules. A definition module does not implicitly re-export imported identifiers.

IMPORT FooLib, BarLib, BazLib;

Duplicate Import

A duplicate import is an import of a library that has already been imported into the same scope. Any such import is ignored and shall cause a compile time warning.

Qualified Import

All imports are qualified. That is, an imported identifier is referenced in the importing module by a qualified identifier. A qualified identifier consists of the module identifier, followed by a period, followed by the actual identifier. Qualification prevents name conflicts between identical identifiers in different libraries.

IMPORT Flintstones, Rubbles;
...
person := Flintstones.Fred;
person.spouse := Flintstones.Wilma;
person.friend := Rubbles.Barney;
person.friend.spouse := Rubbles.Betty;

For brevity, an ALIAS declaration may be used to declare an unqualified alias name for a qualified identifier. This facility replaces unqualified import in earlier versions of Modula‑2.

ALIAS Fred = Flintstones.Fred;
...
person := Fred; (* unqualified alias *)

Abstract Data Type Libraries

An abstract data type library is a library that provides an abstract data type whose identifier matches the identifier of its library module.

DEFINITION MODULE String;

TYPE String = OPAQUE;
...

The identifier of such an abstract data type is implicitly aliased when it is imported and may therefore be used unqualified.

IMPORT String;

VAR s : String; (* alias for String.String *)

Institution

The introduction of a name along with an associated specification of an entity is called institution. There are two kinds:

  • definition
  • declaration

A definition is an institution of interface of an entity, a declaration is an institution of implementation. However, in the case of constants, variables and types other than opaque pointer types and ADTs, interface and implementation are inseparable. For this reason, by convention, any institution within the definition part of a library module is called a definition and any institution within the implementation part of a library module is called a declaration.

Aliases

An alias represents the unqualified name of a qualified identifier. The unqualified name is called alias and the qualified identifier it represents is called its translation. An alias may be instituted within implementation and program modules only. It is visible only within the scope in which it is declared and its translation must be visible within that scope. There are two ways to declare aliases, explicitly by name or implicitly by wildcard.

aliasDeclaration :=
  namedAliasDecl | wildcardAliasDecl
  ;

Named Alias Declaration

A named alias declaration specifies one or more aliases to be declared explicitly by their name. An alias declaration for a single alias specifies its translation explicitly. The alias must match the unqualified identifier of its translation. An alias declaration for multiple aliases specifies their translations implicitly by qualified wildcard.

namedAliasDecl :=
  aliasName ( '=' qualifiedName | ( ',' aliasName )* '=' qualifiedWildcard )
  ;

alias aliasName = StdIdent ;

alias qualifiedName = qualident ;

qualifiedWildcard :=
  qualident '.*'
  ;

A declaration of the form

ALIAS Fred = Flintstone.Fred;

declares a single alias Fred to represent the qualified identifier Flintstone.Fred.

A declaration of the form

ALIAS Fred, Wilma = Flintstone.*;

declares two aliases Fred and Wilma to represent Flintstone.Fred and Flintstone.Wilma respectively.

Wildcard Alias Declaration

A wildcard alias declaration clause declares all aliases matching a qualified wildcard. The qualifying part of the qualified wildcard must reference an enumeration type.

wildcardAliasDecl :=
  '*' '=' qualifiedWildcard
  ;

A wildcard alias declaration within the context and of the form

TYPE Colour = ( Red, Green, Blue );
...
ALIAS * = Colour.*;

declares aliases for every enumerated value in enumeration type Colour. The resulting aliases are Red, Green and Blue representing Colour.Red, Colour.Green and Colour.Blue respectively.

Visibility of Aliases

Unlike unqualified names brought into scope by unqualified import in earlier versions of Modula-2, unqualified names declared by an alias declaration have local scope. They are only visible within the scope in which they are declared, reducing the likelihood of name collision when using unqualified names.

An alias declaration within the context and of the form

TYPE MsgType = ( Info, Warning, Error, Fatal );

(* aliases for MsgType values are not in scope here *)

PROCEDURE EmitMsg ( type : MsgType; CONST text : ARRAY OF CHAR );
ALIAS * = MsgType.*;
BEGIN
  (* aliases for MsgType values are in scope here *)
END EmitMsg;

(* aliases for MsgType values are no longer in scope here *)

declares aliases Info, Warning, Error and Fatal within the local scope of procedure EmitMsg. The aliases are visible only within the scope of procedure EmitMsg.

Constants

A constant is an identifier that represents an immutable value determined at compile time. Its value is specified by a constant expression in its institution clause. A constant may be instituted within definition, implementation and program modules. The syntax of a constant institution clause is

constDefinition :=
  CONST ident '=' constExpression
  ;

alias constDeclaration = constDefinition ;

The expression that specifies the value of the constant must be a constant expression and it may not be a module or type identifier.

Variables

A variable is a named reference to a mutable value. It is always associated with a type and may only hold values of its type. The type is specified in its institution clause and is immutable. A variable may be instituted within definition, implementation and program modules. The syntax of variable definition and declaration clauses differs slightly.

Variable Definition

A variable definition may define variables of named types only.

varDefinition :=
  VAR ( identList ':' typeIdent ';' )+
  ;

Variables defined in a definition module are always exported immutable. They are mutable within the corresponding implementation module but immutable within any other scope.

Variable Declaration

A variable declaration may declare variables of named or anonymous types.

varOrFieldDeclaration :=
  identList ':' ( typeIdent | anonType )
  ;

anonType :=
  ARRAY valueCount OF typeIdent | subrangeType | procedureType
  ;

Variable Initialisation

Variables of pointer types are automatically intialised to hold the invalid pointer value NIL. Variables of other types are not initialised. Their values are undetermined after allocation and must be explicitly initialised by assignment at runtime.

Types

A type is a classification of units of data that determines storage representation, value range and semantics. A type may be instituted within definition, implementation and program modules. The syntax of type definition and declaration clauses differs slightly.

Type Definition

A type definition may specify any type constructor except the indeterminate type constructor.

typeDefClause :=
  TYPE ( typeDefinition ';' )+
  ;

typeDefinition :=
  ident '=' ( OPAQUE | type )
  ;

type :=
  aliasType | derivedType | subrangeType | enumType | setType |
  arrayType | recordType | pointerType | procedureType
  ;

Type Declaration

A type declaration may specify any type constructor except the OPAQUE type constructor.

typeDeclClause :=
  TYPE ( typeDeclaration ';' )+
  ;

typeDeclaration :=
  ident '=' ( indeterminateType | type )
  ;

Opaque Types

An opaque type is a pointer type whose name is public but whose target type is hidden. Its definition is placed in a definition module. It has the following syntax

opaqueTypeDefinition :=
  TYPE ident '=' OPAQUE
  ;

A matching declaration specifying the target type must be placed in the corresponding implementation module. It has the following syntax

opaqueTypeCompletion :=
  TYPE ident '=' POINTER TO targetTypeIdent
  ;

Alias Types

An alias type is a synonym for another type. The type for which it is a synonym is called its base type. The syntax for its institution is

aliasTypeInstitution :=
  TYPE ident '=' ALIAS OF typeIdent
  ;

An alias type and its base type are identical and thus interchangeable.

Derived Types

A derived type is a derivative of another type. The type from which it is derived is called its base type. The syntax for its institution is

derivedTypeInstitution :=
  TYPE ident '=' typeIdent
  ;

The type obtains its properties from its base type, except for its identifier. A derived type and its base type are different types and the two are not interchangeable.

Subrange Types

A subrange type is a subtype of an ordinal type. The type of which it is a subtype is called its base type. A subrange type obtains its properties from its base type, except for its identifier and its value range. The value range of a subrange type is a subset, but not necessarily a strict subset of the value range of its base type. The syntax for its institution is

subrangeTypeInstitution :=
  TYPE ident '=' '[' lowerBound '..' upperBound ']' OF ordinalType
  ;

alias lowerBound, upperBound = constExpression;

alias ordinalType = typeIdent;

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

Enumeration Types

An enumeration type is an ordinal type whose legal values are determined by an identifier list given in its institution clause.

enumTypeInstitution :=
  TYPE ident '=' '(' ( '+' enumTypeToExtend ',' )? identList ')'
  ;

alias enumTypeToExtend = typeIdent;

The identifier list is automatically enumerated, that is, each identifier is assigned an enumeration value. The enumeration value assigned to the leftmost identifier is always zero. The enumeration value assigned to any following identifier is the enumeration value of its predecessor incremented by one.

A type institution clause of the form

TYPE Colour = ( Red, Green, Blue );

institutes an enumeration type Colour with three enumerated values Red, Green and Blue whose enumeration values are 0, 1 and 2 respectively.

Enumeration Type Extension

An enumeration type may be instituted as an extension of another enumeration type. Such a type is called a type extension and the type it extends is called its base type. To institute a type extension of an enumeration type, the identifier list within the institution clause is preceded with the identifier of the base type preceded by the + symbol. An extension type inherits all the enumerated values of its base type along with their enumeration values.

A type institution clause of the form

TYPE MoreColour = ( +Colour, Orange, Magenta, Cyan );

institutes an enumeration type MoreColour as an extension of enumeration type Colour with six enumerated values Red, Green, Blue, Orange, Magenta and Cyan whose enumeration values are 0 to 5 respectively.

An enumeration type is always downwards compatible with any of its type extensions, but an enumeration type extension is not upwards compatible with its base type. This restriction exists because any value of a base type is always a legal value of its extension type but a value of an extension type is not necessarily a legal value of its base type.

The maximum number of values in an enumeration type is implementation defined but must be at least 4096.

Set Types

A set type is a collection type that represents a mathematical set of unique finite values and whose component type is an enumeration type. The syntax for its institution is

setTypeInstitution :=
  TYPE ident '=' SET OF enumTypeIdent
  ;

The component type determines the finite values of the set type. Each value may be stored in the set at most once.

The maximum number of elements in a set type is implementation defined but must be at least 128.

Array Types

An array type is an indexed collection type with a capacity limit and a component type. Capacity limit and component type are specified in its institution clause.

arrayTypeInstitution :=
  TYPE ident '=' ARRAY capacityLimit OF typeIdent
  ;

The capacity limit determines the maximum number of components that can be stored in an instance of the array type. The component type determines the type of the values that can be stored. The index type is always LONGCARD. The index of the first component of an instance of an array type is always zero.

Record Types

A record type is a compound type whose components are of arbitrary types. Components are called fields. The number of fields is arbitrary. The syntax for its institution is

recordTypeInstitution :=
  TYPE ident '=' RECORD ( '(' recTypeToExtend ')' )?
  fieldList ( ';' fieldList )* END
  ;

alias recTypeToExtend = recordTypeIdent ;

alias fieldList = varOrFieldDeclaration ;

A record type may be extensible or non-extensible.

An extensible record type is instituted by specifying a base type enclosed in parentheses following reserved word RECORD in the institution clause. A record type whose definition lacks a base type specification is non-extensible.

An extensible record type that specifies NIL as its base type is a root type. Any extensible record type inherits all the fields from its base type, including any fields the base type may have inherited. A type so defined is also called a type extension of the base type.

A type extension is upwards compatible with its base type, but the base type is not downwards compatible with its type extensions.

Indeterminate Types

An indeterminate type is a pointer type whose target type is a record type whose last field is indeterminate. An indeterminate field is an open array field whose capacity limit cannot be determined from its declaration. Instead it is determined by an allocation statement at runtime. The declaration syntax is

indeterminateType :=
  POINTER TO RECORD ( fieldList ';' )* indeterminateField END
  ;

indeterminateField :=
  '+' ident ':' ARRAY OF typeIdent 
  ;

An indeterminate type contains an immutable hidden field to hold the capacity limit of the indeterminate field. The capacity field is initialised when an instance of an indeterminate type is allocated at runtime. Its value can be obtained using the CAPACITY function.

An instance of an indeterminate type is assignment and copy compatible to another if both are of the same type, regardless of their allocated capacity. However, when copying an instance of indeterminate type to another instance of the same type, the copy operation may overflow the target instance's capacity. In case of overflow, a runtime fault will occur.

Pointer Types

A pointer type is a reference type. Its legal values are references to instances of another type. The type it references is called its target type. The target type is specified within its institution clause

pointerTypeInstitution :=
  TYPE ident '=' POINTER TO typeIdent
  ;

An instance of a pointer type may store any reference to a value of the target type or NIL.

Procedure Types

A procedure type is a reference type whose legal values are references to procedures or functions that match the signature associated with the type. The signature is specified within its institution clause

procedureTypeInstitution :=
  TYPE ident '=' PROCEDURE
    ( '(' formalType ( ',' formalType )* ')' )? ( ':' returnedType )?
  ;

The instance of a procedure type may store any reference to a procedure or function whose signature matches the procedure signature associated with the procedure type or NIL.

The signatures of a procedure and a procedure type match if their respective formal types exactly match, that is, including any formal type attributes and including any return type.

Formal Types

A type specification for a procedure parameter is called a formal type. It may be associated with a formal type attribute. A formal type attribute determines the parameter passing convention of parameters of the formal type.

formalType :=
  ( CONST | VAR )? nonAttrFormalType
  ;

A formal type may be a type identifier, an open array type, a casting formal type or a variadic formal type.

nonAttrFormalType :=
  simpleFormalType | castingFormalType | variadicFormalType
  ;

simpleFormalType :=
  ( ARRAY OF )? typeIdent
  ;

Formal Open Array Types

An open array type is an array type whose capacity limit is indeterminate at compile time. The capacity and value count of a parameter of a formal open array type are determined at runtime when an argument is passed to it.

formalOpenArrayType :=
  ARRAY OF typeIdent
  ;

Casting Formal Types

A casting formal type is a formal type with implicit cast semantics. An argument that is passed to a parameter of a casting formal type is implicitly cast to the formal type. The use of casting formal types must be enabled by importing module UNSAFE.

There are two casting formal types.

castingFormalType :=
  CAST ( ADDRESS | OCTETSEQ )
  ;

Formal type CAST ADDRESS imposes an implicit cast to type ADDRESS of module UNSAFE. Only pointer types are passing compatible to formal type CAST ADDRESS.

Formal type CAST OCTETSEQ imposes an implicit cast to type OCTETSEQ of module UNSAFE. All types are passing compatible to formal type CAST OCTETSEQ.

Note This facility replaces the implicit casting semantics of formal types ARRAY OF BYTE, ARRAY OF WORD and ARRAY OF LOC in earlier versions of Modula-2.

Variadic Formal Types

A variadic formal type is a formal list type whose arity is indeterminate. Its argument count cannot be determined from its declaration and may vary. A parameter of a formal variadic type may be passed a variable number of arguments. The actual argument count is determined when a procedure with a variadic formal parameter is invoked.

variadicFormalType :=
  ARGLIST OF typeIdent
  ;

Procedures

A procedure is a sequence of statements associated with an identifier and it may be invoked from any scope in which its identifier is visible. A procedure has its own local scope in which local entities may be declared. It may have zero or more associated parameters and it may return a result in its own name. A procedure that returns a result in its own name is called a function procedure, or simply a function. A procedure that does not is called a regular procedure. Collectively both are referred to as procedures.

Procedure Definition

A procedure definition specifies a procedure header only.

alias procedureDefinition = procedureHeader ;

procedureHeader :=
  PROCEDURE procedureSignature
  ;

procedureSignature :=
  ident ( '(' formalParams ( ';' formalParams )* ')' )?
  ( ':' returnedType )?
  ;

Procedure Declaration

A procedure declaration specifies a procedure header followed by a procedure body.

procedureDeclaration :=
  procedureHeader ';' block ident
  ;

The Procedure Header

A procedure header consists of a procedure's identifier, its formal parameters if any, and its return type if any. The procedure header represents the interface of the procedure.

The Procedure Body

A procedure body consists of a local block followed by the procedure's identifier. A procedure body represents the implementation of the procedure.

Formal Parameters

Parameter declarations within the parameter list of a procedure header are called the procedure's formal parameters. Formal parameters determine the number, order, type and passing convention of arguments that may be passed to a procedure when it is invoked.

formalParams :=
  ( CONST | VAR )? identList ':' nonAttrFormalType
  ;

The identifier of a formal parameter is the identifier by which the value of the passed in argument or argument list can be referenced within the body of the procedure.

Passing Conventions

There are three parameter passing conventions.

  • pass by value
  • pass by reference, mutable
  • pass by reference, immutable

Pass By Value

The default parameter passing convention is pass by value. It is used when no attribute is specified for a formal parameter or formal parameter list. Any such parameter is called a value parameter. When an argument is passed to a value parameter, a copy is passed to the procedure. The scope of the copy is the procedure's local scope.

Pass By Reference — Mutable

The pass by mutable reference convention is used when the VAR attribute is specified for a formal parameter or formal parameter list. Any such parameter is called a VAR parameter. When an argument is passed to a VAR parameter, a mutable reference to the argument is passed to the procedure. The procedure may or may not modify the argument. Immutable entities may therefore not be passed to VAR parameters.

Pass By Reference — Immutable

The pass by immutable reference convention is used when the CONST attribute is specified for a formal parameter or formal parameter list. Any such parameter is called a CONST parameter. When an argument is passed to a CONST parameter, an immutable reference to the argument is passed to the procedure. The procedure may not modify the argument. That is, within the scope of the procedure the CONST parameter is treated as if it was a constant. Both mutable and immutable entities may be passed to CONST parameters.

Formal Open Array Parameters

A formal open array parameter is a formal parameter of a formal open array type. Its capacity is indeterminate at compile time. Capacity and value count are determined at runtime when an argument is passed to it in a procedure call.

An argument passed to an open array parameter must be an array whose value type is compatible with the value type of the parameter to which it is passed.

Given the declarations

TYPE Chars = ARRAY 100 OF CHAR;
TYPE Buffer = ARRAY 100 OF OCTET;
VAR chars : Chars; buffer : Buffer;
PROCEDURE PadWithZeroes ( VAR array : ARRAY OF OCTET );

variable buffer may be passed to parameter array in a call to procedure PadWithZeroes because their value types match. By contrast, variable chars may not be passed to array because their value types are incompatible.

chars := "abc";
buffer := { 1, 2, 3 };
PadWithZeroes(buffer); (* OK *)
PadWithZeroes(chars); (* compile time error : incompatible type *)

The actual capacity is passed as a hidden parameter immediately preceding the open array parameter.

PROCEDURE PadWithZeroes
  ( (*hiddenCapacity : LONGCARD;*) VAR array : ARRAY OF OCTET );

Its value may be obtained within the procedure body by calling function CAPACITY with the identifier of the open array parameter as argument.

PROCEDURE PadWithZeroes ( VAR array : ARRAY OF OCTET );
BEGIN
  WHILE COUNT(array) < CAPACITY(array) DO
    APPEND(array, 0)
  END (* WHILE *)
END PadWithZeroes;

Casting Formal Parameters

A casting formal parameter is a formal parameter of a casting formal type. It causes an argument passed to it to be cast to its formal type. There are two kinds of casting formal parameters.

An argument passed to a parameter of formal type CAST ADDRESS is cast to type ADDRESS. That is, within the body of the procedure, the argument is interpreted as a value of type ADDRESS. The argument must be of a pointer type.

An argument passed to a parameter of formal type CAST OCTETSEQ is cast to type OCTETSEQ. That is, within the body of the procedure, the parameter is interpreted as a value of type OCTETSEQ. The argument may be of any type.

Variadic Formal Parameters

A variadic formal parameter is a formal parameter of a variadic formal type. to which a variable number of arguments may be passed. Any argument must be passing compatible to the value type of the variadic formal parameter to which it is passed.

PROCEDURE average ( args : ARGLIST OF REAL ) : REAL;
...
v := average(1.2, 3.4, 5.6); (* OK *)
v := average(1.2, 3); (* compile time error: incompatible type *)

The actual argument count is passed as a hidden parameter immediately preceding the argument list.

PROCEDURE average ( (*hiddenArgc : LONGCARD;*) args : ARGLIST OF REAL ) : REAL;

Its value may be obtained within the procedure body by calling function COUNT with the identifier of the formal variadic parameter as argument.

PROCEDURE Variadic ( args : ARGLIST OF T );
BEGIN
  WRITE "number of arguments: ", COUNT(args);

A variadic parameter is an indexed collection. It may be empty. A FOR statement may be used to iterate over its values.

PROCEDURE average ( args : ARGLIST OF REAL ) : REAL;
VAR sum : REAL;
BEGIN
  IF COUNT(args) = 0 THEN
    RETURN 0.0
  END; (* IF *)
  sum := 0.0;
  FOR value IN args DO
    sum := sum + value
  END; (* FOR *)
  RETURN sum / COUNT(args)
END average;

As with other arrays, values may also be addressed by subscript. The index of the first value is always zero.

FOR index, value IN args DO
  (* args[index] is equivalent to value *)
  sum := sum + args[index]
END; (* FOR *)

An argument list passed to a variadic formal parameter may be enclosed in curly braces to delineate it from other arguments. Such delineation is mandatory whenever the arguments in an argument list passed to a variadic formal parameter are not distinguishable by their type from any argument that follows the list.

Given a formal parameter list of the form

PROCEDURE P ( list1, list2 : ARGLIST OF REAL; x : LONGREAL );

arguments to be passed to parameters list1 and list2 in a procedure call to P are not distinguishable from their respective following arguments by type and must therefore be delineated by curly braces.

P({0.1, 2.3}, {3.4, 5.6, 7.8}, 9.0);

Allocation

to do

Type Semantics

Alias Types

An alias type has the same semantics as the type for which it is an alias.

Derived Types

A derived type inherits its semantics from the type from which it is derived.

Subrange Types

A subrange type inherits its semantics from the type of which it is a subrange, except for its lower and upper bound which are defined in the subrange type's definition.

Enumeration Types

TO DO

Sets

TO DO

Arrays

Unlike earlier versions of Modula-2, the number of values stored in an array may change at runtime between zero and the capacity limit of the array type. To this end, the array type is internally represented by a record type that consists of a value count field and a payload field. The value count field holds the number of values stored in the array and the payload field holds the values stored in the array.

Values are stored contiguously from the lowest index which is always zero, up to the highest index which is one less than the array's value count and bounded by the capacity limit of the array type. Values are addressed by their indexed position within the array using subscript notation.

Array types support insert, append, concatenation, slicing and removal operations. A value is insertable and appendable if it is compatible with the array's component type; an array or array slice is insertable, appendable and concatenable if its component type is compatible with the array's component type, provided that the result of the operation will not exceed the capacity of the target array.

For arrays whose component type is not a character type, the value count may be obtained using predefined function COUNT. For arrays whose component type is a character type, the character count may be obtained using predefined function LENGTH which returns the number of characters excluding the NUL terminator.

Records

TO DO

Pointer Types

Same as PIM. Description to do.

Procedure Types

Same as PIM. Description to do.

Statements

A statement represents 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 values and they may not occur within expressions.

The following statements are available:

Assignment, Increment, Decrement, Procedure Call, COPY, RETURN, NEW, RETAIN, RELEASE, IF, CASE, LOOP, WHILE, REPEAT, FOR, EXIT, READ, WRITE;

The Assignment Statement

The assignment statement is a value-mutator statement. It assigns a given value to a mutable value. Its syntax is

assignment :=
  designator ':=' expression
  ;

The designator is called the L-value, the expression is called the R-value. The L-value must be mutable and the R-value must be assignment compatible to the L-value. If these conditions are not met, a compile time error shall occur.

The Increment Statement

The increment statement is a value-mutator statement. It increments the value of an instance of a whole number type by one. It consists of a designator followed by 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.

The Decrement Statement

The decrement statement is a value-mutator statement. It decrements the value of an instance of a whole number type by one. It consists of a designator followed by 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.

The COPY Statement

The COPY statement is a value-mutator statement. It copies values across type boundaries where types have a common or compatible value type. Its syntax is

copyStatement :=
  COPY designator ':=' expression
  ;

The designator is called the L-value, the expression is called the R-value. The L-value must be mutable. The R-value must be copy compatible to the L-value. Both must be non-elementary types. If these conditions are not met, a compile time error shall occur.

Copying Sets

Variables of different set types are not assignment compatible but they are copy compatible if their value types match or one is an extension or subtype of the other.

Given the declarations

TYPE BaseColour = ( Red, Green, Blue );
TYPE ExtColour = ( +BaseColour, Orange, Magenta, Cyan ); 
TYPE BaseColours = SET OF BaseColour; ExtColours = SET OF ExtColour;
VAR baseColours : BaseColours; extColours : ExtColours;

a statement of the form

COPY extColours := baseColours;

copies set baseColours to set extColours.

Copying Arrays

Variables of different array types are not assignment compatible but they are copy compatible if their value types match or one is an extension or subtype of the other.

Given the declarations

TYPE PosInt = [0..TMAX(INTEGER)] OF INTEGER;
TYPE ArrayA = ARRAY 20 OF INTEGER; ArrayB = ARRAY 10 OF PosInt;
VAR arrayA : ArrayA; arrayB : ArrayB;

a statement of the form

COPY arrayA := arrayB;

copies array arrayB to array arrayA.

Copying Between Sets and Arrays

Variables of array and set types are not assignment compatible with each other but they are copy compatible if their value types match or one is an extension or subtype of the other.

Given the declarations

TYPE Token = ( Unknown, Alias, And, Arglist, Array, Begin ... );
TYPE TokenSet = SET OF Token; TokenArray = ARRAY 100 OF Token;
VAR set : TokenSet; array : TokenArray;

A statement of the form

COPY set := array;

copies the Token values stored in array to set.

A statement of the form

COPY array := set;

copies the Token values stored in set to array.

The Procedure Call Statement

A procedure call statement is used to invoke a procedure. It consists of a designator that designates the called procedure, optionally followed by a list of parameters enclosed in parentheses to be passed to the procedure. Parameters passed are called arguments or 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 they don't, 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 tail call elimination (TCE), except when generating source code in a target language that does not support TCE.

The RETURN Statement

The RETURN statement is a flow-control statement 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.

The NEW Statement

The NEW statement is a memory management statement. It allocates storage for a new instance of the target type referenced by the type of its argument. Its syntax is

newStmt :=
  NEW designator ( ':=' initValue | CAPACITY expression )?
  ;

alias initValue = expression;

where designator must be an L-value and initValue must be an R-value.

A statement of the form

NEW p;

allocates a new instance of the target type of p and passes a reference in pointer variable p.

Allocation with Initialisation

By default, a newly allocated instance is not initialised. To initialise a new instance during its allocation, an initialisation value may be specified within a NEW statement.

A statement of the form

NEW array := { a, b, c };

allocates a new instance, initialises it with values a, b and c and passes a reference in array.

Allocation of Instances of Indeterminate Type

A capacity value may be specified to initialise a new instance of an indeterminate type.

A statement of the form

NEW buffer CAPACITY 1000;

allocates a new instance of an indeterminate type with a capacity of 1000 components of the type's indeterminate field and passes a reference in buffer.

The RETAIN Statement

The RETAIN statement is a memory management statement. It prevents premature deallocation of the target referenced by its argument.

The RELEASE Statement

The RELEASE statement is a memory management statement. It cancels a prior invocation of RETAIN for the target referenced by its argument and deallocates the target if all prior invocations of RETAIN for the target have been cancelled.

The IF Statement

The IF statement is a flow-control statement that passes control to one of a number of blocks within its body depending on the value of a boolean expression. 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.

The CASE Statement

The 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. Its syntax is

caseStatement :=
  CASE expression OF ( '|' case )+ ( ELSE statementSequece )? END
  ;

case :=
  caseLabels ( ',' caseLabels )* : StatementSequence
  ;

caseLabels :=
  constExpression ( .. constExpression )?
  ;

Control is passed to the first statement following the case label that matches the ordinal expression. Case labels must be unique. There is no "fall through". At the end of a label, control is passed to the first statement after the CASE statement.

If no case label matches, control is passed to the ELSE block, or, if there is no ELSE block, to the first statement after the CASE statement.

The LOOP Statement

The LOOP statement is a control-flow statement used to repeat a statement or statement sequence indefinitely unless explicitly terminated by an EXIT statement within its body.

The WHILE Statement

The WHILE statement is a control-flow statement 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 unless the statement is explicitly terminated by an EXIT statement within its body.

The REPEAT Statement

The REPEAT statement is is a control-flow statement 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 REPEAT block is repeated as long as the expression evaluates to TRUE unless the statement is explicitly terminated by an EXIT statement within its body.

The FOR Statement

The FOR statement is a flow-control statement that iterates over an iterable entity, executing a statement or statement sequence during each iteration cycle. It consists of a loop header and a loop body. The header consists of one or two loop variants, an optional iteration order, and an iterable expression. The body consists of a statement or statement sequence. Its syntax is

forStatement :=
  FOR forLoopVariants IN iterableExpr DO statementSequence END
  ;

The Loop Variants

The loop variant section contains one or two identifiers through which indices and values of the iterable expression are referenced within the loop. Its syntax is

forLoopVariants :=
  indexOrSoleValue ascOrDesc? ( ',' value )?

alias indexOrSoleValue, value = ident ;

The loop variant identifiers are declared by the loop header and they are only in scope within the header and body. Once a FOR loop has terminated, its loop variants are no longer in scope. The number of possible loop variants depends on the loop's iterable expression.

If the iterable expression is an ordinal type, a subrange of an ordinal type or the designator of a set, the header contains a sole loop variant, immutable within the loop body.

If the iterable expression is the designator of an array a, the header contains a loop variant representing the iteration index i and an optional second loop variant v representing the array component a[i]. Index i is immutable within the loop body. Value v is mutable if array a is mutable, otherwise v is immutable.

During the first iteration cycle the loop variant section references that index, value or index/value pair which is first for the prevailing iteration order. Before each subsequent iteration cycle the loop variant section is advanced to its successor for the prevailing iteration order. Iteration continues until all indices, values or pairs have been visited unless the FOR statement is explicitly terminated by an EXIT statement within its body.

The Iteration Order

The prevailing iteration order may be specified 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.

 ascOrDesc :=
  '++' | '--' ;
  ;

The Iterable Expression

The iterable expression — or iterable in short — is denoted by (1) the identifier or an ordinal or subrange type, (2) an anonymous subrange of an ordinal type or (3) the designator of a set, array or array slice.

iterableExpr :=
  ordinalRange OF ordinalType | designator
  ;

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.

A statement of the form

FOR char IN CHAR DO
  WRITE char
END; (* IF *)

iterates over all values of type CHAR.

Given the declaration

TYPE Colour = ( Red, Green, Blue );

a statement of the form

FOR colour IN Colour DO
  WRITE nameOfColour(colour), "\n"
END; (* IF *)

iterates over all enumerated values of type Colour.

A statement of the form

FOR value-- IN [1..99] OF CARDINAL DO
  WRITE value, " bottles of beer, take one down and pass it around.\n"
END; (* IF *)

iterates over subrange [1..99] of type CARDINAL in descending order.

Iterating over Collections

If the iterable is the designator of a set, only one loop variant may be given. The loop variant is immutable. Its type is the element type of the set and the loop iterates over all values in the set.

A statement of the form

FOR elem IN set DO
  WRITE nameOfElem(elem), "\n"
END; (* IF *)

iterates over all elements stored in set.

If the iterable is the designator of an array or array slice, one or two loop variants may be given. The first loop variant is immutable and it is of type CARDINAL. The optional second loop variant is mutable if the array is mutable, otherwise immutable, its type is the element type of the array. The loop iterates over all components stored in the array.

A statement of the form

FOR index, value IN source DO
  target[index] := value
END; (* IF *)

iterates over all components of array source.

A statement of the form

FOR index, value IN source[n..m] DO
  WRITE "source[", index, "] = ", value, "\n"
END; (* IF *)

iterates over all components in array slice source[n..m].

The EXIT Statement

The EXIT statement is a control-flow statement used within the body of a LOOP, WHILE, REPEAT or FOR statement to terminate execution of the loop 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.

The READ Statement

The READ statement reads one or more values from a communications channel and transfers the values in a non-empty variadic list of designators. Its syntax is

readStmt :=
  READ ( '@' chan ':' )?
  NEW? designator ( ',' designator )*
  ;

where chan is the designator of a communications channel.

A statement of the form

READ @file : foo, bar, baz;

reads three values from channel file and passes them in variables foo, bar and baz.

The communications channel may be omitted in which case a default input channel is used.

A statement of the form

READ foo;

reads a value from the default input channel and passes it in variable foo.

The list of designators may be prefixed by reserved word NEW to allocate new memory for each value read. In this case every designator must designate a value of a pointer type and its value must be NIL.

A statement of the form

READ @file : NEW ptr;

reads a value from channel file, allocates a new instance of ptr and passes the read value in ptr^.

The WRITE Statement

The WRITE statement writes one or more values to a communications channel. Its syntax is

writeStmt :=
  WRITE ( '@' chan ':' )?
  outputArgs ( ',' outputArgs )*
  ;

outputArgs :=
  formattedArgs | unformattedArgs
  ;

formattedArgs :=
  '#' '(' fmtStr, expressionList ')'
  ;

alias unformattedArgs = expressionList;

where chan is the designator of a communications channel and fmtStr is a format specifier string.

A statement of the form

WRITE @file : foo, bar, baz;

writes the values foo, bar and baz to channel file.

The communications channel may be omitted in which case a default output channel is used.

A statement of the form

WRITE foo;

writes the value of foo to the default output channel.

The list of output values may include formatted and unformatted values. A formatted value or value list is preceded by a format specifier, enclosed in parentheses and preceded by #.

A statement of the form

WRITE @file : "Price: ", #("5;2", price), "incl. VAT\n";

writes three values to channel file applying format specifier "5;2" to value price.

Operators and Expressions

Operator Precedence and Associativity

Expressions are evaluated according to the precedence level and associativity of the operators within the expression. Operators of higher precedence are evaluated before operators of lower precedence. Where operators have the same precedence, the associativity determines evaluation order. For left-associative operators of the same precedence the evaluation order is left to right.

The properties of operators are given in the table below:

Operator Math Symbols Arity Position Associativity Precedence
= = binary infix non-associative 1 (lowest)
# binary infix non-associative 1 (lowest)
< < and ≺ and ⊂ binary infix non-associative 1 (lowest)
<= ≤ and ≼ and ⊆ binary infix non-associative 1 (lowest)
> > and ≻ and ⊃ binary infix non-associative 1 (lowest)
>= ≥ and ≽ and ⊇ binary infix non-associative 1 (lowest)
== binary infix non-associative 1 (lowest)
IN binary infix non-associative 1 (lowest)
+ + and ∪ binary infix left-associative 2
- unary prefix non-associative 2
- binary infix left-associative 2
& || binary infix left-associative 2
\ binary infix left-associative 2
OR binary infix left-associative 2
* × and ∩ binary infix left-associative 3
/ ÷ and △ binary infix left-associative 3
DIV ÷ binary infix left-associative 3
MOD binary infix left-associative 3
AND binary infix left-associative 3
NOT ¬ unary prefix non-associative 4
:: binary infix non-associative 5
( ) unary bifix non-associative 6 (highest)
[ ] ai unary postfix left-associative 6 (highest)
^ unary postfix left-associative 6 (highest)
. binary infix left-associative 6 (highest)

Relational Operations

Equality

The binary infix operator = denotes an equality test. An expression of the form a = b returns TRUE if a and b are equal, otherwise FALSE. If both operands are arrays, or both operands are sets, their component types must be the same. Otherwise, both operands must be of the same type.

Inequality

The binary infix operator # denotes an inequality test. An expression of the form a # b returns TRUE if a and b are not equal, otherwise FALSE. If both operands are arrays, or both operands are sets, their component types must be the same. Otherwise, both operands must be of the same type.

Less-Than

The binary infix operator < denotes a less-than comparison when the operands are of a scalar type. An expression of the form a < b returns TRUE if the value of a is less than the value of b, otherwise FALSE. Both operands must be of the same type.

Ranks-Before

The binary infix operator < denotes a ranks-before comparison when the operands represent character strings. An expression of the form a < b returns TRUE if a ranks before b using ASCII collation order, otherwise FALSE.

Strict Subset

The binary infix operator < denotes a strict subset comparison when the operands are of a set type. An expression of the form a < b returns TRUE if ab, otherwise FALSE. The component types of the operands must be of the same type.

Less-Than-Or-Equal

The binary infix operator <= denotes a less-than-or-equal comparison when the operands are of a scalar type. An expression of the form a <= b returns TRUE if the value of a is less than or equal to the value of b, otherwise FALSE. Both operands must be of the same type.

Ranks-Before-Or-Equal

The binary infix operator <= denotes a ranks-before-or-equal comparison when the operands represent character strings. An expression of the form a <= b returns TRUE if a ranks before b or if both rank equally using ASCII collation order, otherwise FALSE.

Subset

The binary infix operator <= denotes a subset comparison when the operands are of a set type. An expression of the form a <= b returns TRUE if ab, otherwise FALSE. The component types of the operands must be of the same type.

Greater-Than

The binary infix operator > denotes a greater-than comparison when the operands are of a scalar type. An expression of the form a > b returns TRUE if the value of a is greater than the value of b, otherwise FALSE. Both operands must be of the same type.

Ranks-After

The binary infix operator > denotes a ranks-after comparison when the operands represent character strings. An expression of the form a > b returns TRUE if a ranks after b using ASCII collation order, otherwise FALSE.

Strict Superset

The binary infix operator > denotes a strict superset comparison when the operands are of a set type. An expression of the form a > b returns TRUE if ab, otherwise FALSE. The component types of the operands must be of the same type.

Greater-Than-Or-Equal

The binary infix operator >= denotes a greater-than-or-equal comparison when the operands are of a scalar type. An expression of the form a >= b returns TRUE if the value of a is greater than or equal to the value of b, otherwise FALSE. Both operands must be of the same type.

Ranks-After-Or-Equal

The binary infix operator >= denotes a ranks-after-or-equal comparison when the operands represent character strings. An expression of the form a >= b returns TRUE if a ranks after b or if both rank equally using ASCII collation order, otherwise FALSE.

Superset

The binary infix operator >= denotes a superset comparison when the operands are of a set type. An expression of the form a > b returns TRUE if ab, otherwise FALSE. The component types of the operands must be of the same type.

Identity

The binary infix operator == denotes an identity test. An expression of the form a == b returns TRUE if ADR(a) equals ADR(b) , otherwise FALSE.

Set Membership

The binary infix operator IN denotes a set membership test. An expression of the form a IN set returns TRUE if aset, otherwise FALSE. The right operand must be of a set type. The left operand must be of the component type of the set type.

Logical Operations

Disjunction

The binary infix operator OR denotes logical disjunction. An expression of the form a OR b returns the logical disjunction ab. Both operands must be of type BOOLEAN.

Conjunction

The binary infix operator AND denotes logical conjunction. An expression of the form a AND b returns the logical conjunction ab. Both operands must be of type BOOLEAN.

Logical Negation

The unary prefix operator NOT denotes logical negation. An expression of the form NOT a returns the logical inverse ¬a. The operand must be of type BOOLEAN.

Arithmetic Operations

Addition

The binary infix operator + denotes addition when its operands are of numeric type. An expression of the form a + b returns the sum of a and b. Both operands must be of compatible numeric types.

Subtraction

The binary infix operator - denotes subtraction. An expression of the form a - b returns the difference of a and b. Both operands must be of compatible numeric types.

Arithmetic Negation

The unary prefix operator - denotes arithmetic negation. An expression of the form -a returns the complement of a. The operand must be of a signed numeric type.

A unary - operator may only appear before a multi-term expression if the expression is enclosed in parentheses. This resolves an ambiguity in earlier versions of Modula-2.

Multiplication

The binary infix operator * denotes multiplication when its operands are of numeric type. An expression of the form a * b returns the product of a and b. Both operands must be of compatible numeric types.

Real Number Division

The binary infix operator / denotes real number division when its operands are of a real number type. An expression of the form a / b returns the quotient of a and b. Both operands must be of compatible real number types.

Integer Division

The binary infix operator DIV denotes Euclidean integer division. An expression of the form a DIV b returns the quotient of a and b. Both operands must be of a compatible whole number type.

Modulus

The binary infix operator MOD denotes the modulus of Euclidean integer division. An expression of the form a MOD b returns the modulus of a and b. Both operands must be of a compatible whole number type.

Set Operations

Set Union

The binary infix operator + denotes set union when its operands are of a set type. An expression of the form a + b returns the set union ab. Both operands must be of a set type. The component types of the operands must be of the same type.

Set Difference

The binary infix operator \ denotes set difference. An expression of the form a \ b returns the set difference ab. Both operands must be of a set type. The component types of the operands must be of the same type.

Set Intersection

The binary infix operator * denotes set intersection when its operands are of a set type. An expression of the form a * b returns the set intersection ab. Both operands must be of a set type. The component types of the operands must be of the same type.

Symmetric Set Difference

The binary infix operator / denotes symmetric set difference when its operands are of a set type. An expression of the form a / b returns the symmetric set difference ab. Both operands must be of a set type. The component types of the operands must be of the same type.

Collection Operations

Insertion

The postfix operator [ ... ..] denotes insertion. An assignment of the form a[i..] := v inserts value v into array a at subscript i. The operand must be of an array type. The insertion designator may only appear as an L-value on the left side of an assignment.

Concatenation

The binary infix operator & denotes concatenation. An expression of the form a & b returns the concatenation product of a and b. Both operands must be of a collection type. The component types of the operands must be of the same type.

Miscellaneous Operations

Type Conversion

The binary infix operator :: denotes type conversion. An expression of the form T :: v converts value v to type T and returns the converted value. The left operand must be a type identifier. The right operand may be a value or expression of any convertible type.

Sub-Expression Precedence

The bifix operator ( ... ) denotes sub-expression precedence. In an expression of the form a ◻ (b ○ c), the evaluation of sub-expression (b ○ c) takes precedence for any arbitrary operators and regardless of their precedence levels.

Designation Operations

Subscript Addressing

The postfix operator [ ... ] denotes subscript addressing. The operator encloses a subscript or a range of subscripts. The operand must be the designator of an array. Subscripts must be of a whole number type.

A sole subscript addresses a single component. An expression of the form a[i] designates the component of a at subscript i.

A subscript range addresses one or more components, called a slice. An expression of the form a[i..j] designates the components of a from subscript i to subscript j.

Non-negative subscripts represent positions relative to the position of the first component. Negative subscripts represent positions relative to the position after the last component.

  • index i = i :: LONGCARDi ∈ { Twhole | 0 ≤ icount ai < capacity a }
  • index i = COUNT(a) - ABS(i) :: LONGCARDn ∈ { Twhole | i < 0 ∧ abs i < count a }

where a is the array operand and i a subscript value.

Pointer Dereference

The unary postfix operator ^ denotes pointer dereference. An expression of the form p^ designates the entity that pointer p references. The operand must be of a pointer type.

Field Selection

The binary infix operator . denotes record field selection when the left operand is an instance of a record type. An expression of the form a.b designates field b of record a.

Name Selection

The binary infix operator . denotes name selection when the left operand is a qualifier of a qualified identifier. An expression of the form a.b designates name b of qualifier a.

Operations By Type

Elementary Types

Operation Tboolean Tchar Tenum Tcardinal Tinteger Treal
=
#
<
<=
>
>=
+ - - -
- x - - - -
x - y - - -
OR - - - - -
* - - -
/ - - - - -
DIV - - - -
MOD - - - -
AND - - - - -
NOT - - - - -
ABS - - - -
ORD -
ODD - - - -
SGN - - - -
POW2 - - - - -
LOG2 - - - - -
ENTIER - - - - -
PRED - - - -
SUCC - - - -

Compound Types

Operation Tset Tarray Tstring Trecord Topaque Tpointer Tproc
=
#
< - - - - -
<= - - - - -
> - - - - -
>= - - - - -
== - - - -
IN - - - - - -
+ - - - - - -
& - - - - -
\ - - - - - -
* - - - - - -
/ - - - - - -
APPEND - - - - -
INSERT - - - -
REMOVE - - - -
CAPACITY - - - -
COUNT - - - - -
LENGTH - - - - - -

UNSAFE Types

Operation BYTE WORD LONGWORD ADDRESS OCTETSEQ
= -
# -
< -
<= -
> -
>= -
ODD -
++ -
-- -
ADD -
SUB -
SHL -
SHR -
^ - - - -
a[i] - - -
LENGTH - - - -
TMIN -
TMAX -
TSIZE always 0
TLIMIT - - - - always 0

Type Compatibility

Type compatibility is a relation between two types T1 and T2 that determines whether an entity e1 of type T1 may be assigned to, copied to, passed to or used together in an expression with an entity e2 of type T2.

Type compatibility thus determines the compatibility of two entities by their associated types. The compatibility relation between any two entities is congruent to the compatibility relation of their types. Any compatibility relation is always transitive, but not necessarily commutative. There are five compatibility relations.

Assignment Compatibility

Assignment compatibility is a relation between two types T1 and T2 that determines whether an entity e1 of type T1 may be assigned to an entity e2 of type T2. The relation is denoted by the =: symbol, pronounced "assignment compatible to".

  • T1 =: T2e1T1e2T2e1 =: e2

Copy Compatibility

Copy compatibility is a relation between two types T1 and T2 that determines whether an entity e1 of type T1 may be copied to an entity e2 of type T2. The relation is denoted by the >: symbol, pronounced "copy compatible to".

  • T1 >: T2e1T1e2T2e1 >: e2

By-Value Passing Compatibility

By-value passing compatibility is a relation between two types T1 and T2 that determines whether an entity e1 of type T1 may be passed to a formal by-value parameter e2 of type T2. The relation is denoted by the ≈: symbol, pronounced "by-value passing compatible to".

  • T1 ≈: T2e1T1e2T2e1 ≈: e2

By-Reference Passing Compatibility

By-reference passing compatibility is a relation between two types T1 and T2 that determines whether an entity e1 of type T1 may be passed to a formal by-reference parameter e2 of type T2. The relation is denoted by the ^: symbol, pronounced "by-reference passing compatible to".

  • T1 ^: T2e1T1e2T2e1 ^: e2

Expression Compatibility

Expression compatibility is a relation between two types T1 and T2 that determines whether two entities e1 of type T1 and e2 of type T2 may be used together in a binary expression. The relation is commutative. It is denoted by the  symbol, pronounced "expression compatible with".

  • T1T2e1T1e2T2e1e2

Hierarchy of Compatibility Relations

Assignment compatibility implies all other compatibility relations. Copy compatibility implies by-value passing compatibility. Passing compatibility implies expression compatibility.

  • T1 =: T2T1 >: T2T1 ≈: T2T1T2
  • T1 =: T2T1 ^: T2T1T2

Type Regimes

A type regime is a set of rules that govern type compatibility.

The following type regimes are in use

Strict Name Equivalence

Under strict name equivalence, types are equivalent if they are identical types.

  • T1 = T2T1 =: T2T2 =: T1

Super-Type Equivalence

Under super-type equivalence, a type is upwards compatible with its super-type, but a super-type is not downwards compatible with its subtype.

  • T1 is-subtype-of T2T1 =: T2 ∧ ¬ T2 =: T1

Value Type Equivalence

Under value type equivalence, collection types are copy compatible if their value types are compatible.

  • T1, T2Tcollectionvalue-type T1 =: value-type T2T1 >: T2T2 >: T1

Target Type Equivalence

Under target type equivalence, pointer types are compatible if their target types are compatible.

  • T1, T2Tpointertarget-type T1 =: target-type T2T1 =: T2

Structural Equivalence

Under structural equivalence, types are compatible if they have identical structure.

  • T1T2 => T1 =: T2T2 =: T1

Limited Equivalence

A type regime is limited if it only applies to a subset of compatibility relations.

Compatibility by Type Classification

Except for type OCTETSEQ, all types follow strict name equivalence by default.

  • T1, T2 ∈ { TanyToctetseq | T1 = T2 } : T1 =: T2T2 =: T1

The type regime may further be relaxed depending on the classification of the type.

Alias Type Compatibility

An alias type is always identical to the type of which it is an alias.

  • T1, T2 ∈ { Tany | T1 is-alias-of T2 } : T1T2

Derived Type Compatibility

A derived type is by definition incompatible with the type from which it is derived.

  • T1, T2 ∈ { Tany | T1 is-derivative-of T2 } : ¬ T1 =: T2 ∧ ¬ T2 =: T1

Anonymous Type Compatibility

Anonymous types with the same canonical type declaration are identical.

  • T1, T2 ∈ { Tanon | T1 is-canonically-equal-to T2 } : T1T2

Enumeration Type Compatibility

Enumeration types follow strict name equivalence.

  • T1, T2 ∈ { Tenum | T1 = T2 } : T1 =: T2T2 =: T1

Enumeration types further follow super-type equivalence.

  • T1, T2 ∈ { Tenum | T2 is-extension-of T1T1 is-subtype-of T2 } : T1 =: T2 ∧ ¬ T2 =: T1

Set Type Compatibility

Set types follow strict name equivalence.

  • T1, T2 ∈ { Tset | T1 = T2 } : T1 =: T2T2 =: T1

Set types further follow value type equivalence.

  • T1, T2 ∈ { Tset | value-type T1 = value-type T2 } : T1 >: T2T2 >: T1
  • T1, T2 ∈ { Tset | value-type T1value-type T2 } : T1 >: T2 ∧ ¬ T2 >: T1

Array Type Compatibility

Array types follow strict name equivalence.

  • T1, T2 ∈ { Tarray | T1 = T2 } : T1 =: T2T2 =: T1

Array types further follow value-type equivalence.

  • T1, T2 ∈ { Tarray | value-type T1 = value-type T2 } : T1 >: T2T2 >: T1
  • T1, T2 ∈ { Tarray | value-type T1value-type T2 } : T1 >: T2 ∧ ¬ T2 >: T1

Record Type Compatibility

Record types follow strict name equivalence.

  • T1, T2 ∈ { Trecord | T1 = T2 } : T1 =: T2T2 =: T1

Extensible record types further follow limited super-type equivalence.

  • T1, T2 ∈ { Textrec | T2 is-extension-of T1 } : T2 ^: T1 ∧ ¬ T1 ^: T2

Pointer Type Compatibility

Opaque pointer types follow strict name equivalence.

  • T1, T2 ∈ { Topaque | T1 = T2 } : T1 =: T2T2 =: T1

Other pointer types follow target type name equivalence.

  • T1, T2 ∈ { TpointerTopaque | target-type T1 = target-type T2 } : T1 =: T2T2 =: T1

Extensible record pointer types follow super-type equivalence.

  • T1, T2 ∈ { Trecptr | T1 is-extension-of T2 } : T1 =: T2 ∧ ¬ T2 =: T1

Given pointer types T1 and T2, T1 is a type extension of T2 if the target type of T1 is a type extension of the target type of T2.

  • T1, T2Trecptr : T1 is-extension-of T2 if T1is-extension-of T2
    where T1′ = target-type T1T2′ = target-type T2

Procedure Type Compatibility

Procedure types follow structural equivalence.

  • any two procedure types are compatible if their signatures match
  • the type of a procedure is the anonymous procedure type that matches its signature

Numeric Type Compatibility

Numeric types follow strict name equivalence.

  • T1, T2 ∈ { Tscalar | T1 = T2 } : T1 =: T2T2 =: T1

Numeric subrange types follow super-type equivalence.

  • T1, T2 ∈ { Tscalar | T1 is-subtype-of T2 } : T1 =: T2 ∧ ¬ T2 =: T1

Machine Type Compatibility

Machine types follow strict name equivalence only.

  • T1, T2 ∈ { Tmachine | T1 = T2 } : T1 =: T2T2 =: T1

Address Type Compatibility

Address types follow strict name equivalence only.

  • T1, T2 ∈ { Taddress | T1 = T2 } : T1 =: T2T2 =: T1

Literal Compatibility

The compatibility of a literal value cannot be determined by type because literals are not associated with any specific type. Instead, literal compatibility is defined as follows:

A literal value L is compatible with type T if L does not overflow T and if

  • L is a character code literal and T is a character type, or
  • L is a whole number literal and T is a machine type, cardinal type or integer type, or
  • L is a real number literal and T is a real number type, or
  • L is a non-empty structured literal and structurally equivalent to T

An empty structured literal L is compatible with type T if

  • L is the empty string "" and TTstring, or
  • L is the empty collection {} and TTsetTarrayTstring

Note A language processor must not assign any type to a literal value until the value is assigned, copied, passed or used in an expression when the target type is known.

Predefined Identifiers

Predefined identifiers are language defined and built-in. They are pervasive, that is, they are visible in every scope without import. Pervasive identifiers do not have qualified names and are always referenced unqualified. Unlike earlier versions of Modula-2, pervasive identifiers are now reserved and may not be redefined.

The following identifiers are predefined:

NIL, TRUE, FALSE, BOOLEAN, OCTET, CHAR, UNICHAR, CARDINAL, LONGCARD, INTEGER, LONGINT, REAL, LONGREAL, APPEND, INSERT, REMOVE, CHR, ORD, ODD, ABS, SGN, MIN, MAX, LOG2, POW2, ENTIER, PRED, SUCC, PTR, CAPACITY, COUNT, LENGTH, NOP, TMIN, TMAX, TSIZE, TLIMIT;

Predefined Constants

NIL

Identifier NIL represents an invalid pointer or address value.

It is per definition compatible with any pointer type, including all opaque pointer types and all procedure types.

TRUE and FALSE

Identifiers TRUE and FALSE represent the values of type BOOLEAN. They are defined as

  • ALIAS TRUE, FALSE = BOOLEAN.*

Predefined Types

BOOLEAN

Type BOOLEAN is an enumerated type. It represents logical truth values used in boolean expressions. It is defined as

TYPE BOOLEAN = ( FALSE, TRUE );

The order is significant. ORD(FALSE) is always zero, ORD(TRUE) is always one.

OCTET

Type OCTET is a cardinal type.

It represents the smallest addressable unit which is per definition 8 bits.

Its value range is always [0..255].

Whole number literals are compatible with type OCTET.

CHAR

Type CHAR is a countable type.

It represents the 7-bit character codes of ISO 646 (aka ASCII).

Its value range is always [0u0..0u7F].

Quoted literals of exactly one ISO 646 code point are compatible with type CHAR.

UNICHAR

Type UNICHAR represents the 32-bit character codes of ISO 10646 UCS-4.

Its value range is [0u0..0u10FFFF].

Quoted literals of exactly one ISO 10646 code point are compatible with type UNICHAR.

CARDINAL

Type CARDINAL is a cardinal type.

It represents unsigned whole numbers.

Its value range is [0..TMAX(CARDINAL)] where

  • TMAX(CARDINAL) = POW2(8*TSIZE(CARDINAL)) - 1

The value of TSIZE(CARDINAL) is implementation defined.

Whole number literals are compatible with type CARDINAL.

LONGCARD

Type LONGCARD is a cardinal type.

It represents unsigned whole numbers with extended range.

Its value range is [0..TMAX(LONGCARD)] where

  • TMAX(LONGCARD) = POW2(8*TSIZE(LONGCARD)) - 1

The value of TSIZE(LONGCARD) is implementation defined where

  • TSIZE(LONGCARD) >= TSIZE(CARDINAL)
  • the type's range is sufficient to express the address range of the target architecture.

Whole number literals are compatible with type LONGCARD.

INTEGER

Type INTEGER is an integer type.

It represents signed whole numbers.

Its value range is [TMIN(INTEGER)..TMAX(INTEGER)].

The internal representation of type INTEGER is always in two's complement. Thus

  • TMIN(INTEGER) = (-1) * POW2(8*TSIZE(INTEGER) - 1)
  • TMAX(INTEGER) = POW2(8*TSIZE(INTEGER) - 1) - 1

The value of TSIZE(INTEGER) is always equal to TSIZE(CARDINAL).

Whole number literals are compatible with type INTEGER.

LONGINT

Type LONGINT is an integer type.

It represents signed whole numbers with extended range.

Its value range is [TMIN(LONGINT)..TMAX(LONGINT)].

The internal representation of type LONGINT is always in two's complement. Thus

  • TMIN(LONGINT) = (-1) * POW2(8*TSIZE(LONGINT) - 1)
  • TMAX(LONGINT) = POW2(8*TSIZE(LONGINT) - 1) - 1

The value of TSIZE(LONGINT) is always equal to TSIZE(LONGCARD).

Whole number literals are compatible with type LONGINT.

REAL

Type REAL is a real number type.

It represents real numbers with standard range and precision.

Its value range is [TMIN(REAL)..TMAX(REAL)].

The internal representation of type REAL is implementation defined where

  • TMIN(REAL) <= TMIN(LONGINT)
  • TMAX(REAL) >= TMAX(LONGCARD)

IEEE 754 single or double precision format is recommended for type REAL.

Real number literals are compatible with type REAL.

LONGREAL

Type LONGREAL is a real number type.

It represents real numbers with extended range or precision or both.

Its value range is [TMIN(LONGREAL)..TMAX(LONGREAL)].

The internal representation of type LONGREAL is implementation defined where

  • TMIN(LONGREAL) <= TMIN(REAL)
  • TMAX(LONGREAL) >= TMAX(REAL)
  • the precision of type REAL must not exceed that of type LONGREAL

IEEE 754 double or quadruple precision format is recommended for type LONGREAL.

Real number literals are compatible with type LONGREAL.

Predefined Procedures

APPEND

Procedure APPEND appends one or more values to an indexed collection.

PROCEDURE APPEND
  ( c : IndexedCollection; values : ARGLIST OF ComponentType );

Values to be appended must be of the component type of the collection.

INSERT

Procedure INSERT inserts one or more values into a collection. It has two alternative definitions, depending on whether the collection is indexed or not.

PROCEDURE INSERT
  ( c : Collection; values : ARGLIST OF ComponentType );
PROCEDURE INSERT
  ( c : IndexedCollection; atIndex : LONGCARD; values : ARGLIST OF ComponentType );

The first argument may be of any collection type that permits insertion and removal operations. Values to be inserted must be of the component type of the collection.

For arguments of opaque types, the procedure acts as a Wirthian macro. An invocation of INSERT with a first argument of an opaque type is replaced with a library call to procedure Insert qualified with the type identifier of the opaque type.

REMOVE

Procedure REMOVE removes one or more values from a collection. It has two alternative definitions depending on whether the collection is indexed or not.

PROCEDURE REMOVE
  ( c : Collection; values : ARGLIST OF ComponentType );
PROCEDURE REMOVE
  ( c : IndexedCollection; atIndex, numberOfValues : LONGCARD );

The first argument may be of any collection type that permits insertion and removal operations. Named values to be removed must be of the component type of the collection.

For arguments of opaque types, the procedure acts as a Wirthian macro. An invocation of REMOVE with a first argument of an opaque type is replaced with a library call to procedure Remove qualified with the type identifier of the opaque type.

Predefined Functions

CHR

Function CHR returns the character whose character code is its argument. Its definition is

PROCEDURE CHR ( n : T ) : CHAR;

where TTcardinaln ∈ { T | 0 ≤ n ≤ 127 }.

ORD

Function ORD returns the ordinal value of its countable argument. Its definition is

PROCEDURE ORD ( value : T ) : LONGCARD;

where TTcountable.

ODD

Function ODD returns TRUE if its argument is odd, otherwise FALSE. Its definition is

PROCEDURE ODD ( value : T ) : BOOLEAN;

where TTwholeTaddressTmachine.

ABS

Function ABS returns the absolute value of its scalar argument. Its definition is

PROCEDURE ABS ( x : T1 ) : T2;

where T1TsignedTscalarT2 = T1.

SGN

Function SGN returns the sign or signum value of its argument. Its definition is

PROCEDURE SGN ( value : T1 ) : T2;

where T1TsignedTscalarT2 = T1.

MIN

Function MIN returns the smallest value in its variadic argument list. Its definition is

PROCEDURE MIN ( values : ARGLIST OF T1 ) : T2;

where T1TscalarTenumT2 = T1.

MAX

Function MAX returns the largest value in its variadic argument list. Its definition is

PROCEDURE MAX ( values : ARGLIST OF T1 ) : T2;

where T1TscalarTenumT2 = T1.

LOG2

Function LOG2 returns the truncated binary logarithm of its argument. Its definition is

PROCEDURE LOG2 ( n : T1 ) : T2;

where T1Tcardinaln ∈ { T1 | n ≠ 0 } ∧ T2 = T1.

POW2

Function POW2 returns the value of its argument raised to the power of 2. Its definition is

PROCEDURE POW2 ( n : T1 ) : T2;

where T1TcardinalT2 = T1.

ENTIER

Function ENTIER returns the largest integer or entier of its argument. Its definition is

PROCEDURE ENTIER ( r : T1 ) : T2;

where T1TrealT2 = T1.

PRED

Function PRED returns the predecessor of its argument. Its definition is

PROCEDURE PRED ( value : T1 ) : T2;

where T1TenumT2 = T1.

SUCC

Function SUCC returns the successor of its argument. Its definition is

PROCEDURE SUCC ( value : T1 ) : T2;

where T1TenumT2 = T1.

PTR

Function PTR returns a pointer to its argument. Its definition is

PROCEDURE PTR ( value : T1 ) : POINTER TO T2;

where T1TanyT2 = T1

CAPACITY

Function CAPACITY returns the capacity of its argument. Its definition is

PROCEDURE CAPACITY ( entity : T ) : LONGCARD;

where TTcollectionTopenarray

COUNT

Function COUNT returns the cardinality or value-count of its argument. Its definition is

PROCEDURE COUNT ( entity : T ) : LONGCARD;

where TTcollectionTstringTTopenarrayTstringTTarglist

The argument must be (1) an instance of a collection type whose component type is not a character type, (2) the identifier of a formal open array parameter whose component type is not a character type or (3) the identifier of a variadic argument list.

For arguments of opaque types, the function acts as a Wirthian macro. An invocation of COUNT with an argument of an opaque type is replaced with a library call to function count qualified with the type identifier of the opaque type.

LENGTH

Function LENGTH returns the length of the character string or octet sequence denoted by its argument. Its definition is

PROCEDURE LENGTH ( s : T ) : LONGCARD;

where TTcollectionTstringTTopenarrayTstringTToctetseq

The argument must be (1) an instance of a collection type that represents a character string or (2) the identifier of a formal open array parameter whose component type is a character type or (3) the identifier of a casting formal parameter of type OCTETSEQ.

For arguments of opaque types, function LENGTH acts as a Wirthian macro. An invocation with an argument of an opaque type is replaced with a library call to function length qualified with the type identifier of the opaque type.

Built-in Macros

NOP

Macro NOP represents an empty statement. An invocation is replaced by a no-operation instruction of the target architecture. Its pseudo-definition is

(*MACRO*) PROCEDURE NOP;

If the target is not an assembly or machine language or if it does not support a no-operation instruction, then NOP shall be translated into an empty statement of the target language. If the target language does not support empty statements, then NOP shall be ignored.

TMIN

An invocation of macro TMIN is replaced by the smallest value of the type denoted by its argument. Its pseudo-definition is

(*MACRO*) PROCEDURE TMIN ( typeIdent ) : ArgType;

The argument must be the identifier of a scalar type. The replacement value is of the argument type.

TMAX

An invocation of macro TMAX is replaced by the largest value of the type denoted by its argument. Its pseudo-definition is

(*MACRO*) PROCEDURE TMAX ( typeIdent ) : ArgType;

The argument must be the identifier of a scalar type. The replacement value is of the argument type.

TSIZE

An invocation of macro TSIZE is replaced by the allocation size of the type denoted by its argument. Its pseudo-definition is

(*MACRO*) PROCEDURE TSIZE ( typeIdent ) : LONGCARD;

The argument must be the identifier of a type.

TLIMIT

An invocation of macro TLIMIT is replaced by the capacity limit of the collection type denoted by its argument. Its pseudo-definition is

(*MACRO*) PROCEDURE TLIMIT ( typeIdent ) : LONGCARD;

The argument must be the identifier of a collection type.

For arguments of opaque types, macro TLIMIT acts as a Wirthian macro. An invocation with an argument of an opaque type is replaced with a library constant CapacityLimit qualified with the type identifier of the opaque type.

Syntax Binding

Syntax Binding is the process of mapping library defined procedures to built-in syntax. A library defined procedure is bound to a given built-in syntax form by including a binding specifier within the procedure’s header. The binding specifier determines to which syntax form the procedure is bound, and it must be included in both the procedure’s definition and declaration.

procedureHeader :=
  PROCEDURE ( '[' bindingSpecifier ']')? procedureSignature
  ;

bindingSpecifier :=
  NEW ( '+' | '#' )? | RETAIN | RELEASE |
  READ ( '*' )? | WRITE ( '#' )?
  ;

A syntax form to which library defined procedures may be bound is said to be bindable. Procedures bound to it are called its bindings. While bindable syntax forms are type agnostic, its bindings are type specific, that is to say, each binding supports arguments of a specific type. For each type to be supported by a bindable syntax form, it requires a binding specific to arguments of the type.

A bindable syntax form S is said to have a binding for type T when a library procedure p that supports arguments of T has been bound to S. Procedure p is said to be bound to S in respect of T.

Syntax Transformation

Bindable syntax forms act as Wirthian macros.

Given a bindable syntax form S with a binding p for type T, an invocation of S with a primary argument or argument list a of type T is replaced by a procedure call to p, passing a.

S a => T.p(a)

Memory Management Bindings

Binding to NEW

Given the binding

PROCEDURE [NEW] New ( VAR p : Foo ); (* in module Foo *)

and declaration

VAR foo : Foo;

a statement of the form

NEW foo;

is replaced by the following I/O library call:

Foo.New(foo);

Given the binding

PROCEDURE [NEW+] NewWithArgs ( VAR p : Foo; initVal : ARGLIST OF Value ); (* in module Foo *)

and declaration

VAR foo : Foo;

a statement of the form

NEW foo := { a, b, c };

is replaced by the following I/O library call:

Foo.NewWithArgs(foo, a, b, c);

Given the binding

PROCEDURE [NEW#] NewWithCapacity ( VAR p : Foo; capacity ); (* in module Foo *)

and declaration

VAR foo : Foo;

a statement of the form

NEW foo CAPACITY n;

is replaced by the following I/O library call:

Foo.NewWithCapacity(foo, n);

Binding to RETAIN

Given the binding

PROCEDURE [RETAIN] Retain ( p : Foo ); (* in module Foo *)

and declaration

VAR foo : Foo;

a statement of the form

RETAIN foo;

is replaced by the following I/O library call:

Foo.Retain(foo);

Binding to RELEASE

Given the binding

PROCEDURE [RELEASE] Release ( VAR p : Foo ); (* in module Foo *)

and declaration

VAR foo : Foo;

a statement of the form

RELEASE foo;

is replaced by the following I/O library call:

Foo.Release(foo);

I/O Bindings

Binding to READ

For each designator in a READ statement, the language processor generates an appropriate I/O library call. Read procedures and default input channels are defined by the I/O library.

Each designator d in a designator list of a READ statement generates a library call to procedure Read qualified by the identifier of the I/O library of the type of d. An I/O library identifier for a type T is derived by appending IO to the type identifier of T.

Given the bindings

PROCEDURE [READ] Read ( ch : Chan; VAR value : Foo ); (* in module FooIO *)
PROCEDURE [READ] Read ( ch : Chan; VAR value : Bar ); (* in module BarIO *)
PROCEDURE [READ] Read ( ch : Chan; VAR value : Baz ); (* in module BazIO *)

and declarations

VAR foo : Foo; bar : Bar; baz : Baz;

a statement of the form

READ @file : foo, bar, baz;

is replaced by the following I/O library calls:

FooIO.Read(file, foo);
BarIO.Read(file, bar);
BazIO.Read(file, baz);

Each designator p in a designator list prefixed by NEW generates a library call to procedure ReadNew qualified by the identifier of the I/O library of the target type of p.

Given the binding

PROCEDURE [READ*] ReadNew ( ch : Chan; VAR p : FooPtr ); (* in module FooIO *)

and the declarations

TYPE FooPtr : POINTER TO Foo;
VAR fooPtr : FooPtr;

a statement of the form

READ @file : NEW fooPtr;

is replaced by the following I/O library call:

FooIO.ReadNew(file, fooPtr);

Binding to WRITE

For each output value in a WRITE statement, the language processor generates an appropriate I/O library call. Write procedures, default output channels and the syntax of format specifiers are defined by the I/O library.

Each unformatted output value v in a WRITE statement generates a library call to procedure Write, qualified by the identifier of the I/O library of the type of v. An I/O library identifier for a type T is derived by appending IO to the type identifier of T.

Given the bindings

PROCEDURE [WRITE] Write ( ch : Chan; value : Foo ); (* in module FooIO *)
PROCEDURE [WRITE] Write ( ch : Chan; value : Bar ); (* in module BarIO *)
PROCEDURE [WRITE] Write ( ch : Chan; value : Baz ); (* in module BazIO *)

and declarations

VAR foo : Foo; bar : Bar; baz : Baz;

a statement of the form

WRITE @file : foo, bar, baz;

is replaced by the following I/O library calls:

FooIO.Write(file, foo);
BarIO.Write(file, bar);
BazIO.Write(file, baz);

Each formatted output value v in a WRITE statement generates a library call to procedure WriteF, qualified by the identifier of the I/O library of the type of v.

Given the bindings

PROCEDURE [WRITE] Write ( ch : Chan; value : Foo ); (* in module FooIO *)
PROCEDURE [WRITE#] WriteF ( ch : Chan; fmt : ARRAY OF CHAR; values : ARGLIST OF Bar ); (* in module BarIO *)
and declarations
```Modula-2
VAR foo : Foo; bar : Bar;

a statement of the form

WRITE @file : foo, #(">10", bar);

is replaced by the following I/O library calls:

FooIO.Write(file, foo);
BarIO.WriteF(file, ">10", bar);

Consecutive formatted output values of the same type that share a format specifier are passed in a single call to procedure WriteF for the type.

Given the declarations

VAR foo1, foo2, foo3 : Foo;

a statement of the form

WRITE @file : foo1, #(">10", foo2, foo3);

is replaced by the following I/O library calls:

FooIO.Write(file, foo1);
FooIO.WriteF(file, ">10", foo2, foo3);

Low-Level Facilities

Low-level facilities are provided by special module UNSAFE. It appears like a library but is built into the language. Its facilities are potentially unsafe, that is to say the use of the facilities may bypass the type regime of the language and they must therefore be used with caution. Although built-in, the module must be imported before its facilities can be used.

The following identifiers are provided:

BitsPerByte, BytesPerWord, BytesPerLongWord, BitsPerAddress, BYTE, WORD, LONGWORD, ADDRESS, OCTETSEQ, ADD, SUB, SETBIT, HALT, ADR, CAST, BIT, SHL, SHR, BWNOT, BWAND, BWOR;

Low-Level Constants

BitsPerByte

Constant BitsPerByte represents the bit width of the smallest addressable machine unit of the target architecture measured in bits. Its value is therefore target architecture dependent. For the overwhelming majority of platforms in use this value will be eight.

Note All memory allocation in Modula-2 is strictly in units of eight bits and multiples thereof. On (legacy) platforms where the smallest addressable machine unit is not eight bits, the mapping of type OCTET to machine bytes is implementation defined.

BytesPerWord

Constant BytesPerWord represents the number of bytes that fit into a machine register of the target architecture smaller than the largest machine register. Its value is target architecture dependent. If the target architecture does not support machine registers of different sizes, the value of BytesPerWord equals that of BytesPerLongWord.

Note The availability of machine registers may be dependent on the memory model of the language processor. The memory model may be implementation defined or it may be user selectable by compiler option or by implementation defined pragma.

BytesPerLongWord

Constant BytesPerLongWord represents the number of bytes that fit into the largest machine register of the target architecture. Its value is target architecture dependent. If the target architecture does not support machine registers of different sizes, the value of BytesPerLongWord equals that of BytesPerWord.

Note The availability of machine registers may be dependent on the memory model of the language processor. The memory model may be implementation defined or it may be user selectable by compiler option or by implementation defined pragma.

BitsPerAddress

Constant BitsPerAddress represents the bit width of the (semi-abstract) reference type ADDRESS, where POW2(BitsPerAddress)-1 is the largest address in the addressable memory space available to the runtime environment.

Low-Level Types

BYTE

Type BYTE is a machine type.

It represents the smallest addressable storage unit of the target architecture.

Its bit width is defined by constant BitsPerByte.

Its value range is [0..POW2(BitsPerByte)-1].

Whole number literals are compatible with type BYTE.

Note Unlike in earlier versions of Modula-2, ARRAY OF BYTE is not a casting formal type. Only arrays of value type BYTE are passing compatible to formal type ARRAY OF BYTE.

WORD

Type WORD is a machine type.

It represents a storage unit equivalent to the size of a machine register of the target architecture.

Its bit width is defined by constants BitsPerByte and BytesPerWord.

Its value range is [0..POW2(BitsPerByte*BytesPerWord)-1].

Whole number literals are compatible with type WORD.

Note Unlike in earlier versions of Modula-2, ARRAY OF WORD is not a casting formal type. Only arrays of value type WORD are passing compatible to formal type ARRAY OF WORD.

LONGWORD

Type LONGWORD is a machine type.

It represents a storage unit equivalent to the size of the largest machine register of the target architecture.

Its bit width is defined by constants BitsPerByte and BytesPerLongWord.

Its value range is [0..POW2(BitsPerByte*BytesPerLongWord)-1].

Whole number literals are compatible with type LONGWORD.

ADDRESS

Type ADDRESS is a (semi-abstract) reference type.

On platforms where the smallest addressable storage unit is eight bits, type ADDRESS represents machine addresses of the target architecture. On (legacy) platforms where the smallest addressable unit is not eight bits, the type represents abstract addresses that need to be mapped to the platform's actual machine addresses. On such platforms, the mapping of ADDRESS values to machine addresses is implementation defined.

Its definition is

TYPE ADDRESS = POINTER TO OCTET;

Its value range is [0..POW2(BitsPerAddress)-1].

Whole number literals and NIL are compatible with type ADDRESS.

An entity a of type ADDRESS may be dereferenced using the ^ operator. An expression of the form a^ is of type OCTET and represents the octet value stored at address a.

VAR a : ADDRESS; x : CARDINAL;

a := ADR(x); x := 0x1234'5678;
FOR offset IN [0..TSIZE(CARDINAL)-1] OF LONGCARD DO
  WRITE "octet value at offset ", offset, " is ", a^;
  a++ (* increment address to next octet *)
END; (* FOR *) 

An entity a of type ADDRESS may also be dereferenced by subscript. An expression of the form a[n] is of type OCTET and represents the octet value stored at address a + n, where n is an offset of type LONGCARD. Negative indices are not permitted.

VAR a : ADDRESS; x : CARDINAL;

a := ADR(x); x := 0x1234'5678;
FOR offset IN [0..TSIZE(CARDINAL)-1] OF LONGCARD DO
  WRITE "octet value at offset ", offset, " is ", a[offset]
END; (* FOR *) 

OCTETSEQ

Type OCTETSEQ is a casting formal type.

It represents a sequence of OCTET values and its length is indeterminate at compile time.

It may only be used as a casting formal type in a procedure or procedure type institution.

It follows that the type may not be the target type in any ALIAS or POINTER type institution and that no variables and no record fields of the type may be instituted.

Any type and any value is passing compatible to formal parameters of type OCTETSEQ, but a parameter of type OCTETSEQ is passing compatible only to formal parameters of type OCTETSEQ.

The only operations supported on parameters of the type are [ ] subscript, FOR iteration and LENGTH. Type transfer to or from type OCTETSEQ is not permitted.

The values of TSIZE(OCTETSEQ) and TLIMIT(OCTETSEQ) are zero by definition.

Low-Level Procedures

ADD

Procedure ADD interprets the bit patterns of its operands as unsigned numbers and adds the value of the second to the first operand, ignoring overflow. Its definition is

PROCEDURE ADD ( VAR x : T1; y : T2 );

where T1,T2TbuiltinTrealToctetseqtsize T2tsize T1

SUB

Procedure SUB interprets the bit patterns of its operands as unsigned numbers and subtracts the value of the second from the first operand, ignoring underflow. Its definition is

PROCEDURE SUB ( VAR x : T1; y : T2 );

where T1,T2TbuiltinTrealToctetseqtsize T2tsize T1

SETBIT

Procedure SETBIT sets the bit at the zero-based index given by its second argument of the value given by its first argument to the bit value given by its third argument. Its definition is

PROCEDURE SETBIT ( VAR target : T1; bitIndex : T2; bit : BOOLEAN );

where T1TbuiltinToctetseqT2Tcardinal ∧ 0 ≤ bitIndex < 8 · tsize T

The bit index of the least significant bit is always zero. A bit value of FALSE represents zero, a value of TRUE represents one.

HALT

Procedure HALT aborts the running program and passes an exit value to its host environment. Its definition is

PROCEDURE HALT ( exitValue : T );

where TTwhole

On platforms that do not support an exit value, the exit value is discarded. On platforms that support an exit value, the interpretation of the value is platform dependent.

Low-Level Functions

ADR

Function ADR returns the address of its argument. Its definition is

PROCEDURE ADR ( value : AnyType ) : ADDRESS;

The argument may be of any type except OCTETSEQ.

CAST

Function CAST represents an unsafe type transfer operation. It returns the value of its second argument, interpreted as if it was of the type given by its first argument, regardless of whether the value makes sense for the target type or not. Its definition is

PROCEDURE CAST ( targetTypeIdent; value : AnyType ) : TargetType;

The first argument must be a type identifier. The second argument may be any constant or variable of any type except OCTETSEQ. The return type is the type indicated by the first argument. If the allocation size of the second argument is smaller than the allocation size of the target type, the higher bits will be filled with zeroes up to the bit width of the target type.

BIT

Function BIT returns TRUE if the bit at the zero-based index given by its second argument of the value given by its first argument is set, otherwise FALSE. Its definition is

PROCEDURE BIT ( value : T1; bitIndex : T2 ) : BOOLEAN;

where T1TbuiltinToctetseqT2Tcardinal

The bit index of the least significant bit is always zero.

SHL

Function SHL returns the value of its first argument bit-shifted to the left by the number of positions passed in its second argument. Its definition is

PROCEDURE SHL ( value : T1; shiftFactor : T2 ) : T3;

where T1TbuiltinToctetseqT2TcardinalT3 = T1

Bits that are shifted out to the left are discarded and will not cause underflow.

SHR

Function SHR returns the value of its first argument bit-shifted logically to the right by the number of positions passed in its second argument. Its definition is

PROCEDURE SHR ( value : T1; shiftFactor : T2 ) : T3;

where T1TbuiltinToctetseqT2TcardinalT3 = T1

Bits that are shifted out to the right are discarded and will not cause overflow.

BWNOT

Function BWNOT returns the bitwise NOT of its argument. Its definition is

PROCEDURE BWNOT ( value : T1 ) : T2;

where T1TbuiltinToctetseqT2 = T1

BWAND

Function BWAND returns the bitwise AND of its first argument and a mask given by its second argument. Its definition is

PROCEDURE BWAND ( value : T1; mask : T2 ) : T3;

where T1TbuiltinToctetseqT2Tcardinaltsize T2 = tsize T1T3 = T1

BWOR

Function BWOR returns the bitwise OR of its first argument and a mask given by its second argument. Its definition is

PROCEDURE BWOR ( value : T1; mask : T2 ) : T3;

where T1TbuiltinToctetseqT2Tcardinaltsize T2 = tsize T1T3 = T1

Pragma Facilities

Pragmas are non-semantic directives — instructions to the language processor to control or influence the compilation process but do not alter the semantics of the compiling source code.

There are two kinds:

  • language defined pragmas
  • implementation defined pragmas.

Language Defined Pragmas

The revised Modula-2 language defines 18 language defined pragmas but the Bootstrap Kernel subset only includes the two pragmas for foreign function interfacing.

FFI Pragma

The FFI pragma follows the module header and establishes the calling convention of the specified foreign API, language and its execution environment for the module.

FFIPragma := '<*' FFI '=' ForeignAPISpecifier '*>' ;

ForeignAPISpecifier := '"C"' | '"CLR"' | '"JVM"' ;

FFIdent Pragma

The FFIdent pragma follows a constant, type, variable or function definition or declaration and maps the identifier to a foreign API identifier given in the pragma.

FFIdentPramga := '<*' FFIdent '=' ForeignIdentifier '*>' ;

alias ForeignIdentifier = QuotedLiteral ;

Implementation Defined Pragmas

Implementation defined pragmas are specific to a language processor and should therefore be ignored by other language processors. An implementation defined pragma may be preceded with an implementation specific prefix in order to distinguish it from other implementation defined pragmas for other processors that may use the same pragma symbol. When a processor does not understand an implementation defined pragma it will emit an informational, warning, error or fatal error message depending on the pragma's message mode suffix.

ImplDefinedPragma :=
  '<*' ( ImplPrefix '.' )? PragmaSymbol ( '=' constExpr )? '|' ctMsgMode '*>' ;

alias ImplPrefix, PragmaSymbol = StdIdent ;

ctMsgMode := INFO | WARN | ERROR | FATAL ;

Implementation Specific Information

Each implementation is required to supply an informational module Implementation. The module must provide constants with implementation specific information. Where any of the required constants are dependent on user selectable compiler options, implementors may choose to implement the module as a special built-in module.

Module Implementation must provide the following constants:

Implementation Identity

Constant Type Meaning
ShortName String literal short name of the language processor
LongName String literal long name of the language processor
VersionMajor Whole number major version of the language processor
VersionMinor Whole number minor version of the language processor
HostEnvironment String literal name of host environment or operating system

Implementation Capability Flags

Boolean Constant indicates whether language processor supports ...
SupportsBSK Modula-2 R10 Bootstrap Kernel (M2BSK) subset
SupportsFullSpec Modula-2 R10 (M2R10) full specification
SupportsUtf8Source source files encoded in UTF-8
SupportsMsgPragma MSG pragma
SupportsInlinePragma INLINE/NOINLINE pragmas
SupportsBlockingPragma BLOCKING pragma
SupportsNoReturnPragma NORETURN pragma
SupportsOutPragma OUT pragma
SupportsForwardPragma FORWARD pragma
SupportsEncodingPragma ENCODING pragma
SupportsAlignPragma ALIGN pragma
SupportsPadBitsPragma PADBITS pragma
SupportsPurityPragma PURITY pragma
SupportsSingleAssignPragma SINGLEASSIGN pragma
SupportsLowLatencyPragma LOWLATENCY pragma
SupportsVolatilePragma VOLATILE pragma
SupportsDeprecationPragma DEPRECATED pragma
SupportsGenTimestampPragma GENERATED pragma
SupportsAddrPragma ADDR pragma
SupportsCFFI C foreign function interface and FFI="C" pragma
SupportsFortranFFI Fortran FFI and FFI="Fortran" pragma
SupportsCLRFFI Microsoft CLR FFI and FFI="CLR" pragma
SupportsJVMFFI Java Virtual Machine FFI and FFI="JVM" pragma
SupportsTCE Tail call elimination

Implementation Target Flags

Boolean Constant indicates whether language processor ...
TargetsC generates C source, may or may not support TCE
TargetsLegacyM2 generates legacy Modula-2 source, may or may not support TCE

Implementation Limits

Whole Number Constant indicates ... required
MaxIdentLength maximum significant length of identifiers ≥ 32
MaxNumLiteralLength maximum length of number literals ≥ 40
MaxStrLiteralLength maximum length of string literals ≥ 120
MaxLineCounter maximum value of line counter for error messages ≥ 32000
MaxColumnCounter maximum value of column counter for error messages ≥ 160
MaxEnumValues maximum number of values of an enumeration type ≥ 4096
MaxSetElements maximum number of elements in an enumerated set ≥ 128
MaxProcNestLevel maximum nesting level of local procedures ≥ 4

Terms of Reference

Allocation Size

The allocation size of a type T, denoted as tsize T is the size of the memory required to allocate an instance of T. It is measured in units of 8 bits called octets.

Capacity

The capacity of a collection c is the maximal number of values that can be stored in c. Its value is determined by the type of of c. Its definition is

  • capacity c = tlimit T where T is the type of c.

The capacity of a pass-by-value open array parameter pval is equivalent to the cardinality or value count of the collection passed to pval. Its definition is

  • capacity pval = count c where c is the collection passed to pval.

The capacity of a pass-by-reference open array parameter pref is equivalent to the capacity of the collection passed to pref. Its definition is

  • capacity pref = capacity c where c is the collection passed to pref.

Capacity Limit

The capacity limit of a collection type T, denoted as tlimit T is the maximum number of items that an instance of T can store. A capacity limit of zero indicates that the collection type does not impose any hard limit.

Cardinality

In mathematics, the cardinality of a set A, denoted as |A| or card A is a measure of the number of elements in A. In this specification, the definition is extended to include collections, open array parameters and variadic argument lists.

  • the cardinality of a collection c is the number of components stored in c
  • the cardinality of an open array parameter p is that of of the collection passed in p
  • the cardinality of a variadic argument list v is the number of arguments passed in v

Compatibility

Compatibility is a property that determines whether one entity may be assigned to, copied to, passed to or used in an expression with another entity.

  • a literal is fully compatible with type T if it is assignment, copy, by‑value and by‑reference passing compatible to and expression compatible with type T
  • type T1 is fully compatible with type T2 if it is assignment, copy, by‑value and by‑reference passing compatible to and expression compatible with type T2

Compatibility, Assignment

Assignment compatibility is a property that determines whether one entity may be assigned to another entity.

  • a literal is assignment compatible to type T if it may be assigned to a value of type T
  • type T1 is assignment compatible to type T2 if an R‑value of type T1 may be assigned to an L‑value of type T2

Compatibility, Copy

Copy compatibility is a property that determines whether one entity may be copied to another entity.

  • a literal is copy compatible to type T if it may be copied to a value of type T
  • type T1 is copy compatible to type T2 if an R‑value of type T1 may be copied to an L‑value of type T2

Compatibility, Passing

Parameter passing compatibility is a property that determines whether an entity may be passed to a formal parameter.

  • a literal is by-value passing compatible to type T if it may be passed to a formal by‑value parameter of type T
  • a literal is by-reference passing compatible to type T if it may be passed to a formal CONST parameter of type T
  • type T1 is by-value passing compatible to type T2 if a value of type T1 may be passed to a formal by‑value parameter of type T2
  • type T1 is by-reference passing compatible to type T2 if a value of type T1 may be passed to a formal by‑reference parameter of type T2

Compatibility, Expression

Expression compatibility is a property that determines whether an entity may be used together with another entity as operands in a binary expression.

  • a literal is expression compatible to type T in respect of operation M if it may be used together with a value of type T as the operands in a binary expression with any operator representing operation M
  • types T1 and T2 are expression compatible in respect of operation M if a value of type T1 and a value of type T2 may be used together as the operands in a binary expression with any operator representing operation M

Constant Expression

A constant expression is an expression that is computable at compile time. A constant expression does not reference any variables nor invoke any library functions.

Fractional Part

The fractional part of a real number x is the value that represents the digits of x after the decimal point if x was to be written out in decimal notation without an exponent.

Its definition is

  • frac x = x - int x

Integral Part

The integral part of a real number x is the value that represents the digits of x before the decimal point if x was to be written out in decimal notation without an exponent.

Its definition is

  • int x = sgn x · entier abs x

Largest Integer or Entier

The entier value of a real number x is the largest integer less than x. Its definition is

  • entier x = max i for i ∈ { ℤ | i < x }

Length

The length of a character string s is the number of characters stored in s excluding its NUL terminator. Its definition is

  • length s = min n for n ∈ { ℕ | sn = ASCII.NUL }

The length of an octet sequence s is the allocation size of the actual parameter p passed in to a formal parameter of type octet sequence. Its definition is

  • length s = tsize p where p passed-to s

Number Sets

In this specification abstract number sets are defined as follows:

  • the set of the abstract natural numbers ℕ = { 0, 1, 2, 3, ... ∞ }
  • the set of the abstract ordinal numbers 𝕆 = { 0, 1, 2, 3, ..., ω, ω+1, ω+2, ... }
  • the set of the abstract whole numbers ℤ = { -∞ ... -3, -2, -1, 0, 1, 2, 3, ... +∞ }

Odd Value

The odd value of a whole number i indicates whether i is odd. Its definition is

  • odd i = true for i ∈ { ℤ | abs i mod 2 = 1 }
  • odd i = false for i ∈ { ℤ | abs i mod 2 = 0 }

Signum Value

The signum or sgn value of a signed number x indicates the sign of x. Its definition is

  • sgn x = 1 for x ∈ { ℝ | x > 0 }
  • sgn x = 0 for x ∈ { ℝ | x = 0 }
  • sgn x = -1 for x ∈ { ℝ | x < 0 }

Type, Any

A type is a classification of storage units defined by a set of three properties: storage representation, value range and semantics.

The set of all types is denoted Tany.

Type, Builtin

A builtin type is a type that is built into the language, that is, either a predefined type or a type provided by builtin module UNSAFE.

The set of all builtin types is denoted Tbuiltin.

Type, Countable

A countable type is a type that represents a set of values with a 1:1 correspondence to the first m ordinal numbers 𝕆 where m ∈ 𝕆.

  • countable T if ∃ f : T → 𝕆;

The set of all countable types is denoted Tcountable.

  • countable T, TTcountable

Type, Enumerated

An enumerated type is a type that represents a finite ordered set of identifiers.

  • enumerated T if ∀ e ∈ { T | identifier e } ∧ ∃ f : T → ℕ

The set of all enumerated types is denoted Tenum.

  • enumerated T, TTenum

Type, Machine

A machine type is a type that represents storage units that precisely match the storage units of the target architecture and have modular arithmetic semantics.

The set of all machine types is denoted Tmachine.

Type, Signed

A signed type is a numeric type that represents both positive and negative scalar numeric values..

  • signed T if ∃ x, y ∈ { T | x < 0 ∧ y > 0 }

The set of all signed types is denoted Tsigned.

  • signed T, TTsigned

Type, Unsigned

An unsigned type is a numeric type that represents non-negative scalar numeric values.

  • unsigned T if ∀ x ∈ { T | x ≥ 0 }

The set of all unsigned types is denoted Tunsigned.

  • unsigned T, TTunsigned

Type, Whole Number

A whole number type is a numeric type that represents a subset of the set of integers ℤ.

  • whole T if ∀ n ∈ { T | n ∈ ℤ }

The set of all whole number types is denoted Twhole.

  • whole T, TTwhole

Type, Real Number

A real number type is a numeric type that represents a subset of the set of real numbers ℝ.

  • real T if ∀ r ∈ { T | r ∈ ℝ }

The set of all real number types is denoted Treal.

  • real T, TTreal

Type, Cardinal

A cardinal type is a numeric type that represents a subset of the unsigned whole numbers ℤ⁺.

  • cardinal T if unsigned Twhole T

The set of all cardinal types is denoted Tcardinal.

  • cardinal T, TTcardinal

Type, Integer

An integer type is a numeric type that represents a subset of the signed whole numbers ℤ.

  • integer T if signed Twhole T

The set of all integer types is denoted Tinteger.

  • integer T, TTinteger

Type, Scalar

A scalar type is a numeric type that represents scalar values.

The set of all scalar types is denoted Tscalar.

Type, Collection

A collection type represents n-tuples of an arbitrary component type, where n is bounded by its capacity.

The set of all collection types is denoted Tcollection.

Type, Array

An array type is an ordered collection type whose components are mapped to the set of the first m ordinal numbers 𝕆 where m is the capacity limit of the array type.

The set of all array types is denoted Tarray.

Type, String

An string type is an array type whose components are characters.

The set of all string types is denoted Tstring.

Type, Record

The set of all record types is denoted Trecord.

Type, Extensible Record

The set of all extensible record types is denoted Textrec.

Type, Extensible Record Pointer

The set of all extensible record pointer types is denoted Trecptr.

  • Trecptr = { TTpointerTopaque | target-type TTextrec }

Type, Opaque

The set of all opaque types is denoted Topaque.

Type, Open Array

An open array type is a formal array type whose capacity is indeterminate at compile time.

The set of all open array types is denoted Topenarray.

Type, Variadic Parameter List

A variadic parameter list is a formal collection type whose cardinality is indeterminate at compile time.

The set of all variadic parameter lists is denoted Targlist.

Value Count

The value count of an entity e is synonym with the cardinality of e. Its definition is

  • count ecard e, where card e is the cardinality of entity e

Wirthian Macro

A Wirthian macro is a built-in syntactic entity whose occurrence is replaced with an appropriate library call, possibly filling in omitted arguments. The macro may be a statement or a built-in procedure or function. The mapped-to library must be explicitly imported.

Wirthian macros allow more convenient syntax than ordinary library calls and make a facility such as memory management or I/O appear to be built into the language even though it is actually provided by a library. Classic examples of Wirthian macros are procedures NEW and DISPOSE in earlier versions of Modula-2.

Clone this wiki locally