Jump to content

A Description of the Oberon-2 Language: Difference between revisions

From EDM2
mNo edit summary
Ak120 (talk | contribs)
mNo edit summary
 
(2 intermediate revisions by the same user not shown)
Line 1: Line 1:
Written by [[Paul Floyd]]
''Written by [[Paul Floyd]]''
 
===Introduction===


==Introduction==
Usually, Oberon grammar is presented in EBNF (the Extended Backus-Naur Formalism).
Usually, Oberon grammar is presented in EBNF (the Extended Backus-Naur Formalism).


Line 9: Line 8:
Comments are opened by "(*" and closed by "*)".
Comments are opened by "(*" and closed by "*)".


Here is an example of the module syntax: <font color="#0000BB"></font>
Here is an example of the module syntax:
 
<code>
   
  MODULE MyModule; (* MyModule is the name of this module *)
  MODULE MyModule; (* MyModule is the name of this module *)
    IMPORT S := SYSTEM, OS2;
      IMPORT S := SYSTEM, OS2;
    (* Here we import 2 modules, SYSTEM for low-level Oberon functions *)
      (* Here we import 2 modules, SYSTEM for low-level Oberon functions *)
    (* and OS2, an interface to the OS/2 API *)
      (* and OS2, an interface to the OS/2 API *)
    (* Note "S := SYSTEM" allows us to use S as an alias of SYSTEM, so *)
      (* Note "S := SYSTEM" allows us to use S as an alias of SYSTEM, so *)
    (* we can call functions like S.CC() *)
      (* we can call functions like S.CC() *)
   
   
  (* type definitions, constants, variables, procedures *)
(* type definitions, constants, variables, procedures *)
  BEGIN
BEGIN
      (* body of the module goes here *)
    (* body of the module goes here *)
  END MyModule.
END MyModule.
</code>


===Constants===
===Constants===
A section of declared constants starts with the keyword CONST. Constants may be built up from other constants. The assignment of a constant uses "=", unlike that of a variable which uses ":=".
A section of declared constants starts with the keyword CONST. Constants may be built up from other constants. The assignment of a constant uses "=", unlike that of a variable which uses ":=".


Example: <font color="#0000BB"></font>
Example:
 
<code>
   
  CONST
  CONST
    a = 31;
      a = 31;
    m = 12*a; (* will be 372 *)
      m = 12*a; (* will be 372 *)
    s- = "string"; (* read-only exported, as an ARRAY 6 of CHAR *)
      s- = "string"; (* read-only exported, as an ARRAY 6 of CHAR *)
</code>


===Types===
===Types===
You can define your own types from the base types defined in Oberon, and types you have defined. Type declarations begin with the keyword TYPE.
You can define your own types from the base types defined in Oberon, and types you have defined. Type declarations begin with the keyword TYPE.


Line 44: Line 41:
The built in types are: BOOLEAN, CHAR, SHORTINT, INTEGER, LONGINT, REAL, LONGREAL and SET. Most of these are implementation-specific. A SET is a SET of integers.
The built in types are: BOOLEAN, CHAR, SHORTINT, INTEGER, LONGINT, REAL, LONGREAL and SET. Most of these are implementation-specific. A SET is a SET of integers.


Examples of type declarations: <font color="#0000BB"></font>
Examples of type declarations:
 
<code>
   
  TYPE
  TYPE
    Flag = BOOLEAN;
      Flag = BOOLEAN;
    String = ARRAY 32 of CHAR;
      String = ARRAY 32 of CHAR;
    Date = RECORD
      Date = RECORD
              Day, Month, Year: INTEGER
                Day, Month, Year: INTEGER
          END;
            END;
    DatePtr = POINTER TO Date;
      DatePtr = POINTER TO Date;
    SecondOfYear = RECORD (Date) (* this shows inheritance *)
      SecondOfYear = RECORD (Date) (* this shows inheritance *)
                      Hour, Minute, Second: INTEGER
                        Hour, Minute, Second: INTEGER
                  END;
                    END;
    SecondPtr = POINTER TO SecondOfYear;
      SecondPtr = POINTER TO SecondOfYear;
</code>
 
You can use ARRAYs and RECORDs (structures) for compound types. You can declare POINTERs, but they must point to structured types only. ARRAYs need not have their dimension specified, but in this case they must be ARRAYS of POINTERs.
You can use ARRAYs and RECORDs (structures) for compound types. You can declare POINTERs, but they must point to structured types only. ARRAYs need not have their dimension specified, but in this case they must be ARRAYS of POINTERs.


Example: <font color="#0000BB"></font>
Example:
 
<code>
TYPE
    Coordinate = RECORD
                END;
   
   
  TYPE
    CoordinateCartesian = RECORD(Coordinate)
      Coordinate = RECORD
      x, y, z : REAL
                  END;
                          END;
   
   
      CoordinateCartesian = RECORD(Coordinate)
    CoordinateCylindrical = RECORD(Coordinate)
        x, y, z : REAL
      r, h, theta : REAL;
                             END;
                             END;
   
   
      CoordinateCylindrical = RECORD(Coordinate)
    CoordinateSpherical = RECORD(Coordinate)
        r, h, theta : REAL;
      r, phi, theta : REAL;
                              END;
                          END;
   
   
      CoordinateSpherical = RECORD(Coordinate)
    ThreeDim = POINTER TO ARRAY OF ARRAY OF Coordinate;
        r, phi, theta : REAL;
</code>
                            END;
      ThreeDim = POINTER TO ARRAY OF ARRAY OF Coordinate;
 
ThreeDim is now a three dimensional ARRAY of Coordinate values, where the representation might be Cartesian, Spherical or Cylindrical. This is only useful for parameters/methods.
ThreeDim is now a three dimensional ARRAY of Coordinate values, where the representation might be Cartesian, Spherical or Cylindrical. This is only useful for parameters/methods.


Line 87: Line 82:


===Variables===
===Variables===
Declarations of variables start with the VAR keyword, and use either built in types of types created in the TYPE declarations.
Declarations of variables start with the VAR keyword, and use either built in types of types created in the TYPE declarations.


Examples: <font color="#0000BB"></font>
Examples:
 
<code>
   
  VAR
  VAR
    a, b, c : INTEGER;
      a, b, c : INTEGER;
    Matrix : ARRAY 10, 10 OF REAL; (* 2 dimensional array *)
      Matrix : ARRAY 10, 10 OF REAL; (* 2 dimensional array *)
    SP : SecondPtr; (* still need to NEW this before using it *)
      SP : SecondPtr; (* still need to NEW this before using it *)
</code>


===Procedures===
===Procedures===
Procedures basically come in two types, function procedures and proper procedures. Function procedures return a value when called.
Procedures basically come in two types, function procedures and proper procedures. Function procedures return a value when called.


Examples: <font color="#0000BB"></font>
Examples:
 
<code>
PROCEDURE CopyString(instr: ARRAY OF CHAR; VAR outstr ARRAY OF CHAR) ;
(* proper procedure *)
BEGIN
    (* body of procedure *)
    RETURN
END CopyString
   
   
  PROCEDURE CopyString(instr: ARRAY OF CHAR; VAR outstr ARRAY OF CHAR) ;
  PROCEDURE Atan2(x, y: REAL): REAL
  (* proper procedure *)
(* function procedure *)
  BEGIN
BEGIN
      (* body of procedure *)
    (* body of procedure *)
      RETURN
    RETURN answer
  END CopyString
END Atan2
   
</code>
  PROCEDURE Atan2(x, y: REAL): REAL
  (* function procedure *)
  BEGIN
      (* body of procedure *)
      RETURN answer
  END Atan2
 
The parameters that the procedures take are either passed by value (default) or passed by reference (indicated by the VAR keyword). Whether or not a procedure is a function procedure depends on whether the PROCEDURE line is followed by the return type. Note however that the return type cannot be compound. You must either return a pointer or a simple type.
The parameters that the procedures take are either passed by value (default) or passed by reference (indicated by the VAR keyword). Whether or not a procedure is a function procedure depends on whether the PROCEDURE line is followed by the return type. Note however that the return type cannot be compound. You must either return a pointer or a simple type.


===Procedure forward declaration===
===Procedure forward declaration===
 
Oberon compilers are generally one-pass (thus blindingly fast), so if a procedure is used before it is defined, it must be declared first. The caret symbol is used to indicate definition of a procedure. The forward declaration and actual declaration must have the same name, type binding and parameters. Example:
Oberon compilers are generally one-pass (thus blindingly fast), so if a procedure is used before it is defined, it must be declared first. The caret symbol is used to indicate definition of a procedure. The forward declaration and actual declaration must have the same name, type binding and parameters. Example: <font color="#0000BB"></font>
<code>
 
PROCEDURE ^Atan2(x, y: REAL): REAL
   
   
  PROCEDURE ^Atan2(x, y: REAL): REAL
PROCEDURE MathFunction (* a procedure that calls Atan2 *)
   
   
  PROCEDURE MathFunction (* a procedure that calls Atan2 *)
  (* actual declaration of Atan2, as above *)
   
</code>
  (* actual declaration of Atan2, as above *)


===Local procedures===
===Local procedures===
Unlike C/C++, Oberon can have procedures within procedures. In the case of local and greater scope procedures having the same name, the local one will take precedence. The local and greater scope procedures with the same name can't be differentiated by parameter lists. If two such functions exist, and you try to call the outer procedure, then either the compiler will perform type conversion and call the local procedure, or it will say that the parameter lists do not match.
Unlike C/C++, Oberon can have procedures within procedures. In the case of local and greater scope procedures having the same name, the local one will take precedence. The local and greater scope procedures with the same name can't be differentiated by parameter lists. If two such functions exist, and you try to call the outer procedure, then either the compiler will perform type conversion and call the local procedure, or it will say that the parameter lists do not match.


===Type bound procedures===
===Type bound procedures===
The concept of type bound procedures is very important in Oberon-2. They are the equivalent of class methods in C++.
The concept of type bound procedures is very important in Oberon-2. They are the equivalent of class methods in C++.


Firstly, the syntax. Type bound procedures are indicated by declaring the record to which the procedure in parentheses before the procedure name. A name for the module type is also given, which is used for dereferencing components of the module (as compared to the anonymous this in C++). Type bound procedures are not declared with the record itself, but can be declared at any point.
Firstly, the syntax. Type bound procedures are indicated by declaring the record to which the procedure in parentheses before the procedure name. A name for the module type is also given, which is used for dereferencing components of the module (as compared to the anonymous this in C++). Type bound procedures are not declared with the record itself, but can be declared at any point.


Simple example: <font color="#0000BB"></font>
Simple example:
 
<code>
TYPE
    Point = RECORD
      x, y: INTEGER
    END;
   
   
  TYPE
  PROCEDURE (pt: Point)Add(DeltaX, DeltaY: INTEGER)
      Point = RECORD
(* procedure bound to record type Point *)
        x, y: INTEGER
BEGIN
      END;
    (* pt is the instance of the record itself *)
   
    pt.x := pt.x + DeltaX;
  PROCEDURE (pt: Point)Add(DeltaX, DeltaY: INTEGER)
    pt.y := pt.y + DeltaY;
  (* procedure bound to record type Point *)
    RETURN
  BEGIN
END Add;
      (* pt is the instance of the record itself *)
</code>
      pt.x := pt.x + DeltaX;
Type bound procedures may be redefined for records that are extensions. For instance, if we define a three dimensional co-ordinate:
      pt.y := pt.y + DeltaY;
<code>
      RETURN
  TYPE
  END Add;
    Point3D = RECORD(Point)
 
              z: INTEGER
Type bound procedures may be redefined for records that are extensions. For instance, if we define a three dimensional co-ordinate: <font color="#0000BB"></font>
              END;
 
</code>
   
It is then possible to re-define Add:
  TYPE
<code>
      Point3D = RECORD(Point)
  PROCEDURE (pt: Point3D)Add(DeltaX, DeltaY: INTEGER)
        z: INTEGER
BEGIN
      END;
    (* caret indicates that we are calling the base class type bound
 
      procedure *)
It is then possible to re-define Add: <font color="#0000BB"></font>
    pt.Add^(DeltaX, DeltaY);
 
    RETURN
   
END Add;
  PROCEDURE (pt: Point3D)Add(DeltaX, DeltaY: INTEGER)
</code>
  BEGIN
      (* caret indicates that we are calling the base class type bound
        procedure *)
      pt.Add^(DeltaX, DeltaY);
      RETURN
  END Add;
 
It is important to note that the redefined procedure must have the same parameters as the base class one.
It is important to note that the redefined procedure must have the same parameters as the base class one.


===Built-in function procedures===
===Built-in function procedures===
 
;ABS(x):Absolute value (accepts and returns any numeric type)
<font color="#0000BB">
;ASH(x, n):Arithmetic shift left (LONGINT)
 
;CAP(x):Capitalize (CHAR)
;CHR(x):Letter from ASCII value (CHAR)
  ABS(x)     Absolute value (accepts and returns any numeric type)
;ENTIER(x):Integral part of a real number  (LONGINT)
  ASH(x, n)   Arithmetic shift left (LONGINT)
;LEN(v, n):Length of vector n of array v (LONGINT)
  CAP(x)     Capitalize (CHAR)
;LEN(v): = LEN(v, 0)
  CHR(x)     Letter from ASCII value (CHAR)
;LONG(x):Promotes to next greatest numeric type (INTEGER, LOGINT or LONGREAL)
  ENTIER(x)   Integral part of a real number  (LONGINT)
;MAX(T):If T is a type, returns the maximum value for that type
  LEN(v, n)   Length of vector n of array v (LONGINT)
:If T is a SET, the maximum value in that set (INTEGER)
  LEN(v)     = LEN(v, 0)
;MIN(T):As MAX but minimum
  LONG(x)     Promotes to next greatest numeric type (INTEGER, LOGINT or
;ODD(x):Detects odd integers (BOOLEAN)
              LONGREAL)
;ORD(x):ASCII value from character (INTEGER)
  MAX(T)     If T is a type, returns the maximum value for that type
;SHORT(x):Demotes to next lowest numeric type (SHORTINT, INTEGER or REAL)
              If T is a SET, the maximum value in that set (INTEGER)
;SIZE(T):Size of type in bytes (integral type)
  MIN(T)     As MAX but minimum
  ODD(x)     Detects odd integers (BOOLEAN)
  ORD(x)     ASCII value from character (INTEGER)
  SHORT(x)   Demotes to next lowest numeric type (SHORTINT, INTEGER or
              REAL)
  SIZE(T)     Size of type in bytes (integral type)
 
</font>


===Built in proper procedures===
===Built in proper procedures===
 
<code>
<font color="#0000BB">
  COPY(source, dest)      Copy string
 
DEC(i)                  Decrement integer
   
DEC(i, n)              Subtract n from i
  COPY(source, dest)      Copy string
EXCL(v, x)              Remove x from SET v
  DEC(i)                  Decrement integer
HALT(x)                Terminate application
  DEC(i, n)              Subtract n from i
INC(i)                  Increment
  EXCL(v, x)              Remove x from SET v
INC(i, n)              Add n to i
  HALT(x)                Terminate application
NEW(p)                  Allocate a fixed-size object to pointer p
  INC(i)                  Increment
NEW(p, i0, i1, ... in)  Allocate n+1 objects of size ix to pointer p
  INC(i, n)              Add n to i
</code>
  NEW(p)                  Allocate a fixed-size object to pointer p
  NEW(p, i0, i1, ... in)  Allocate n+1 objects of size ix to pointer p
 
</font>


===System functions===
===System functions===
 
Most Oberon compilers have a module SYSTEM which contains low-level functions.
Most Oberon compilers have a module SYSTEM which contains low-level functions. <font color="#0000BB"></font>
  ADR(v)      Address of variable (LONGINT)
 
BIT(a, n)  Test bit n of a (BOOLEAN)
   
CC(n)      Condition n (16 bit)
  ADR(v)      Address of variable (LONGINT)
LSH(x, n)  Logical shift n (type of x)
  BIT(a, n)  Test bit n of a (BOOLEAN)
ROT(x, n)  Rotate n (type of x)
  CC(n)      Condition n (16 bit)
VAL(T, x)  Force x to be expressed as type T (type of T)
  LSH(x, n)  Logical shift n (type of x)
  ROT(x, n)  Rotate n (type of x)
  VAL(T, x)  Force x to be expressed as type T (type of T)


===Expressions===
===Expressions===
 
Expressions consist of operands and operators. Operands consist of procedure calls, string/numeric values, constants or variables. Variables may be simple types, arrays or pointers. A type guard (like a C/C++ cast) may be applied to a variable. Unlike C, where you can do 'useful' things like cast a double to a function call, Oberon type guards only apply to extended records. Using the example from the section on RECORDs above:
Expressions consist of operands and operators. Operands consist of procedure calls, string/numeric values, constants or variables. Variables may be simple types, arrays or pointers. A type guard (like a C/C++ cast) may be applied to a variable. Unlike C, where you can do 'useful' things like cast a double to a function call, Oberon type guards only apply to extended records. Using the example from the section on RECORDs above: <font color="#0000BB"></font>
<code>
 
   VAR
   VAR
       Calendar: DatePtr;
       Calendar: DatePtr;
Line 250: Line 219:
                                           type Date which does not include
                                           type Date which does not include
                                           Hour *)
                                           Hour *)
 
</code>
The operators may be logical (OR & ~) (Why it isn't AND/OR or &/| I'll never know!), arithmetic (+ - * / DIV MOD), set (+ - * /) or relational (= # [not equal] < <= > >= IN [test for set membership] IS [test for type]).
The operators may be logical (OR & ~) (Why it isn't AND/OR or &/| I'll never know!), arithmetic (+ - * / DIV MOD), set (+ - * /) or relational (= # [not equal] < <= > >= IN [test for set membership] IS [test for type]).


===Statements===
===Statements===
Statements may be assignment (x := 1), procedure calls or a compound statement. Compound statements are either the contents of BEGIN and END or one of the built in language statements. Statements are always separated by semicolons.
Statements may be assignment (x := 1), procedure calls or a compound statement. Compound statements are either the contents of BEGIN and END or one of the built in language statements. Statements are always separated by semicolons.


Line 260: Line 228:


====If====
====If====
 
<code>
<font color="#0000BB">
  IF expression THEN
 
    statements
   
[ELSIF expression THEN
  IF expression THEN
    statements]
      statements
[ELSE
  [ELSIF expression THEN
    statements]
      statements]
END
  [ELSE
</code>
      statements]
  END
 
</font>


====Case====
====Case====
 
Here 'label' may be an integral type (or character), a range, indication by two dots (e.g., 0..59), or a CONST. The ELSE clause acts like the default: for a C/C++ switch.
Here 'label' may be an integral type (or character), a range, indication by two dots (e.g., 0..59), or a CONST. The ELSE clause acts like the default: for a C/C++ switch. <font color="#0000BB"></font>
<code>
 
  CASE expression OF
   
    label:
  CASE expression OF
      statements
      label:
[|  label:
        statements
      statements]
  [|  label:
[ELSE
        statements]
      statements]
  [ELSE
END
        statements]
</code>
  END


====While====
====While====
 
  WHILE expression DO
<font color="#0000BB">
    statements
 
END
   
  WHILE expression DO
      statements
  END
 
</font>


====Repeat====
====Repeat====
 
  REPEAT
<font color="#0000BB">
    statements
 
UNTIL expression
   
  REPEAT
      statements
  UNTIL expression
 
</font>


====Loop====
====Loop====
 
  LOOP
<font color="#0000BB">
    statements (* must include an EXIT statement *)
 
END
   
  LOOP
      statements (* must include an EXIT statement *)
  END
 
</font>


====For====
====For====
 
The FOR statement does not exist at all in Oberon-1. WHILE, REPEAT or LOOP statements must be used instead.
The FOR statement does not exist at all in Oberon-1. WHILE, REPEAT or LOOP statements must be used instead. <font color="#0000BB"></font>
<code>
 
  FOR variable := expression TO expression [BY expression] DO
   
    statements
  FOR variable := expression TO expression [BY expression] DO
END
      statements
</code>
  END


====With====
====With====
 
This performs a test on the type of a variable, and executes statements similarly to the CASE statement. If no ELSE clause is supplied and none of the supplied label types match the variable, the program will end.
This performs a test on the type of a variable, and executes statements similarly to the CASE statement. If no ELSE clause is supplied and none of the supplied label types match the variable, the program will end. <font color="#0000BB"></font>
<code>
 
  WITH guard DO
   
    statements
  WITH guard DO
[| guard DO
      statements
    statements]
  [| guard DO
[ELSE
      statements]
    statements]
  [ELSE
END
      statements]
</code>
  END
Example:
 
<code>
Example: <font color="#0000BB"></font>
  WITH Calendar: DatePtr DO
 
    (* statements appropriate to an object of type Date *)
   
| Calendar: SecondOfYear DO
  WITH Calendar: DatePtr DO
    (* statements appropriate to an object of type SecondOfYear *)
      (* statements appropriate to an object of type Date *)
ELSE
  | Calendar: SecondOfYear DO
    (* default statements *)
      (* statements appropriate to an object of type SecondOfYear *)
END
  ELSE
</code>
      (* default statements *)
  END
 
Note that Oberon-1 does not have the option of having more than one guard test in the WITH statement.
Note that Oberon-1 does not have the option of having more than one guard test in the WITH statement.


[[Category:Languages Articles]][[Category:Oberon]]
[[Category:Oberon-2 Articles]]

Latest revision as of 15:18, 7 November 2017

Written by Paul Floyd

Introduction

Usually, Oberon grammar is presented in EBNF (the Extended Backus-Naur Formalism).

The main building block of Oberon applications is the module. Each module has a name. You can import other modules into a module, and can export components of the module so that other modules may import them (i.e., make them public). Variables and functions are tagged as exported by appending a "*" at the end of the name. Read-only export is also possible, this time by appending a "-" at the end of the name. The module can contain the other building blocks described later - type definitions, constants, variables and functions.

Comments are opened by "(*" and closed by "*)".

Here is an example of the module syntax:

MODULE MyModule; (* MyModule is the name of this module *)
   IMPORT S := SYSTEM, OS2;
   (* Here we import 2 modules, SYSTEM for low-level Oberon functions *)
   (* and OS2, an interface to the OS/2 API *)
   (* Note "S := SYSTEM" allows us to use S as an alias of SYSTEM, so *)
   (* we can call functions like S.CC() *)

(* type definitions, constants, variables, procedures *)
BEGIN
   (* body of the module goes here *)
END MyModule.

Constants

A section of declared constants starts with the keyword CONST. Constants may be built up from other constants. The assignment of a constant uses "=", unlike that of a variable which uses ":=".

Example:

CONST
   a = 31;
   m = 12*a; (* will be 372 *)
   s- = "string"; (* read-only exported, as an ARRAY 6 of CHAR *)

Types

You can define your own types from the base types defined in Oberon, and types you have defined. Type declarations begin with the keyword TYPE.

Oberon has single inheritance. A RECORD may have a base type by putting the name of the base type in parentheses after the RECORD declaration of the derived type.

The built in types are: BOOLEAN, CHAR, SHORTINT, INTEGER, LONGINT, REAL, LONGREAL and SET. Most of these are implementation-specific. A SET is a SET of integers.

Examples of type declarations:

TYPE
   Flag = BOOLEAN;
   String = ARRAY 32 of CHAR;
   Date = RECORD
             Day, Month, Year: INTEGER
          END;
   DatePtr = POINTER TO Date;
   SecondOfYear = RECORD (Date) (* this shows inheritance *)
                     Hour, Minute, Second: INTEGER
                  END;
   SecondPtr = POINTER TO SecondOfYear;

You can use ARRAYs and RECORDs (structures) for compound types. You can declare POINTERs, but they must point to structured types only. ARRAYs need not have their dimension specified, but in this case they must be ARRAYS of POINTERs.

Example:

TYPE
   Coordinate = RECORD
                END;

   CoordinateCartesian = RECORD(Coordinate)
      x, y, z : REAL
                         END;

   CoordinateCylindrical = RECORD(Coordinate)
      r, h, theta : REAL;
                           END;

   CoordinateSpherical = RECORD(Coordinate)
      r, phi, theta : REAL;
                         END;

   ThreeDim = POINTER TO ARRAY OF ARRAY OF Coordinate;

ThreeDim is now a three dimensional ARRAY of Coordinate values, where the representation might be Cartesian, Spherical or Cylindrical. This is only useful for parameters/methods.

Which representation you have might be checked by a type guard, which is something completely different than a type cast. It checkes which extension of a base type is the current runtime type.

Variables

Declarations of variables start with the VAR keyword, and use either built in types of types created in the TYPE declarations.

Examples:

VAR
   a, b, c : INTEGER;
   Matrix : ARRAY 10, 10 OF REAL; (* 2 dimensional array *)
   SP : SecondPtr; (* still need to NEW this before using it *)

Procedures

Procedures basically come in two types, function procedures and proper procedures. Function procedures return a value when called.

Examples:

PROCEDURE CopyString(instr: ARRAY OF CHAR; VAR outstr ARRAY OF CHAR) ;
(* proper procedure *)
BEGIN
   (* body of procedure *)
   RETURN
END CopyString

PROCEDURE Atan2(x, y: REAL): REAL
(* function procedure *)
BEGIN
   (* body of procedure *)
   RETURN answer
END Atan2

The parameters that the procedures take are either passed by value (default) or passed by reference (indicated by the VAR keyword). Whether or not a procedure is a function procedure depends on whether the PROCEDURE line is followed by the return type. Note however that the return type cannot be compound. You must either return a pointer or a simple type.

Procedure forward declaration

Oberon compilers are generally one-pass (thus blindingly fast), so if a procedure is used before it is defined, it must be declared first. The caret symbol is used to indicate definition of a procedure. The forward declaration and actual declaration must have the same name, type binding and parameters. Example:

PROCEDURE ^Atan2(x, y: REAL): REAL

PROCEDURE MathFunction (* a procedure that calls Atan2 *)

(* actual declaration of Atan2, as above *)

Local procedures

Unlike C/C++, Oberon can have procedures within procedures. In the case of local and greater scope procedures having the same name, the local one will take precedence. The local and greater scope procedures with the same name can't be differentiated by parameter lists. If two such functions exist, and you try to call the outer procedure, then either the compiler will perform type conversion and call the local procedure, or it will say that the parameter lists do not match.

Type bound procedures

The concept of type bound procedures is very important in Oberon-2. They are the equivalent of class methods in C++.

Firstly, the syntax. Type bound procedures are indicated by declaring the record to which the procedure in parentheses before the procedure name. A name for the module type is also given, which is used for dereferencing components of the module (as compared to the anonymous this in C++). Type bound procedures are not declared with the record itself, but can be declared at any point.

Simple example:

TYPE
   Point = RECORD
      x, y: INTEGER
   END;

PROCEDURE (pt: Point)Add(DeltaX, DeltaY: INTEGER)
(* procedure bound to record type Point *)
BEGIN
   (* pt is the instance of the record itself *)
   pt.x := pt.x + DeltaX;
   pt.y := pt.y + DeltaY;
   RETURN
END Add;

Type bound procedures may be redefined for records that are extensions. For instance, if we define a three dimensional co-ordinate:

TYPE
   Point3D = RECORD(Point)
              z: INTEGER
             END;

It is then possible to re-define Add:

PROCEDURE (pt: Point3D)Add(DeltaX, DeltaY: INTEGER)
BEGIN
   (* caret indicates that we are calling the base class type bound
      procedure *)
   pt.Add^(DeltaX, DeltaY);
   RETURN
END Add;

It is important to note that the redefined procedure must have the same parameters as the base class one.

Built-in function procedures

ABS(x)
Absolute value (accepts and returns any numeric type)
ASH(x, n)
Arithmetic shift left (LONGINT)
CAP(x)
Capitalize (CHAR)
CHR(x)
Letter from ASCII value (CHAR)
ENTIER(x)
Integral part of a real number (LONGINT)
LEN(v, n)
Length of vector n of array v (LONGINT)
LEN(v)
= LEN(v, 0)
LONG(x)
Promotes to next greatest numeric type (INTEGER, LOGINT or LONGREAL)
MAX(T)
If T is a type, returns the maximum value for that type
If T is a SET, the maximum value in that set (INTEGER)
MIN(T)
As MAX but minimum
ODD(x)
Detects odd integers (BOOLEAN)
ORD(x)
ASCII value from character (INTEGER)
SHORT(x)
Demotes to next lowest numeric type (SHORTINT, INTEGER or REAL)
SIZE(T)
Size of type in bytes (integral type)

Built in proper procedures

COPY(source, dest)      Copy string
DEC(i)                  Decrement integer
DEC(i, n)               Subtract n from i
EXCL(v, x)              Remove x from SET v
HALT(x)                 Terminate application
INC(i)                  Increment
INC(i, n)               Add n to i
NEW(p)                  Allocate a fixed-size object to pointer p
NEW(p, i0, i1, ... in)  Allocate n+1 objects of size ix to pointer p

System functions

Most Oberon compilers have a module SYSTEM which contains low-level functions.

ADR(v)      Address of variable (LONGINT)
BIT(a, n)   Test bit n of a (BOOLEAN)
CC(n)       Condition n (16 bit)
LSH(x, n)   Logical shift n (type of x)
ROT(x, n)   Rotate n (type of x)
VAL(T, x)   Force x to be expressed as type T (type of T)

Expressions

Expressions consist of operands and operators. Operands consist of procedure calls, string/numeric values, constants or variables. Variables may be simple types, arrays or pointers. A type guard (like a C/C++ cast) may be applied to a variable. Unlike C, where you can do 'useful' things like cast a double to a function call, Oberon type guards only apply to extended records. Using the example from the section on RECORDs above:

  VAR
     Calendar: DatePtr;
     ExactCalendar: SecondPtr;
  ...
     NEW(ExctCalendar); (* points to SecondOfYear record *)
     Calendar := ExactCalendar; (* Calendar is a pointer to Date, the base
                                class of SecondOfYear *)
     Calendar(ExactCalendar).Hour := 11; (* need the typeguard else the
                                         compiler will assume the static
                                         type Date which does not include
                                         Hour *)

The operators may be logical (OR & ~) (Why it isn't AND/OR or &/| I'll never know!), arithmetic (+ - * / DIV MOD), set (+ - * /) or relational (= # [not equal] < <= > >= IN [test for set membership] IS [test for type]).

Statements

Statements may be assignment (x := 1), procedure calls or a compound statement. Compound statements are either the contents of BEGIN and END or one of the built in language statements. Statements are always separated by semicolons.

The built in statements are as follows. Items in square brackets are optional.

If

IF expression THEN
   statements
[ELSIF expression THEN
   statements]
[ELSE
   statements]
END

Case

Here 'label' may be an integral type (or character), a range, indication by two dots (e.g., 0..59), or a CONST. The ELSE clause acts like the default: for a C/C++ switch.

CASE expression OF
   label:
      statements
[|  label:
      statements]
[ELSE
      statements]
END

While

WHILE expression DO
   statements
END

Repeat

REPEAT
   statements
UNTIL expression

Loop

LOOP
   statements (* must include an EXIT statement *)
END

For

The FOR statement does not exist at all in Oberon-1. WHILE, REPEAT or LOOP statements must be used instead.

FOR variable := expression TO expression [BY expression] DO
   statements
END

With

This performs a test on the type of a variable, and executes statements similarly to the CASE statement. If no ELSE clause is supplied and none of the supplied label types match the variable, the program will end.

WITH guard DO
   statements
[| guard DO
   statements]
[ELSE
   statements]
END

Example:

WITH Calendar: DatePtr DO
   (* statements appropriate to an object of type Date *)
| Calendar: SecondOfYear DO
   (* statements appropriate to an object of type SecondOfYear *)
ELSE
   (* default statements *)
END

Note that Oberon-1 does not have the option of having more than one guard test in the WITH statement.