The Oberon Language (1990)

Dick Pountain/BYTE/Monday Dec 3, 1990

                             

As the triumphal march of C proceeds and language 'inertia' becomes heavier by

the month, the prospects for introducing a new general purpose programming

language like Oberon must seem pretty slim. However Oberon deserves to be

taken very seriously for it is Niklaus Wirth's successor to Modula-2.

Professor Wirth of ETH (Eidgenossische Technische Hochschule) in Zurich,

Switzerland, created both Pascal and Modula-2 and must therefore be considered

one of the most influential language designers in the short history of the

art. What also makes Oberon noteworthy is that, at a time when most software

systems seem to be bloating inexorably into middle-aged spread, Oberon is

actually much smaller and simpler than its predecessor.

The name Oberon did not come directly from Shakespeare's 'A Midsummer Night's

Dream' but rather from the eponymous moon of Neptune whose fly-past by Voyager

was in the news in 1988 when Oberon was born. The superb precision of

Voyager's navigation inspired Wirth to make this linguistic tribute.

Strictly speaking Oberon is more than a language, it's a complete operating

system and environment for a networked 32-bit workstation called Ceres, just

as Modula-2 was the operating environment for the Lilith workstation. Ceres

was entirely designed at ETH and is extensively used by the students in

Wirth's department. However it's likely that in the next few years we shall

see implementations of the Oberon language under other operating systems such

as MS-DOS.


OBERON'S AIMS

Oberon developed out of Modula-2 as a system programming language to implement

the software for the Ceres workstation network. Wirth's intention with Ceres

was to create a simple, reliable and low-cost workstation, and achieving this

meant determining just what was essential and what was expendable in the

hardware realm. This simplifying philosophy soon spilled over into the

software too.

Wirth believes strongly that an operating system should be designed as a

number of separately compiled modules with well-defined interfaces, and that

writing applications is equivalent to extending the operating system by adding

new modules. So Modula-2 was the first choice for the Ceres project because it

has excellent support for such modularity. In the event however Wirth decided

that Modula-2 does not have powerful enough facilities for user extension. In

particular it does not permit the programmer to define new data types as

extensions of older types. So Oberon was born from the decision to add type

extensions to Modula. I shall explain how type extensions work later on.

Another firm requirement of the Ceres project was that the operating system

should have a dynamic central memory allocation scheme, complete with garbage

collection. It would have been possible to add a garbage collector to Modula-

2, and indeed this has been done in the Modula-3 language developed by DEC and

Olivetti [described in Byte Nov 1990, page 385]. However Wirth felt that the

variant record feature, which Modula-2 inherited from Pascal, would have been

an obstacle to secure and efficient garbage collection. This is because both

Pascal and Modula-2 permit the insecure practice of modifying the tag of a

variant record independently of the variant field values (or omitting the tag

field altogether). Since almost all implementations actually overlay the

different variants of a record on the same area of memory, programmers can

defeat the strict typing mechanism in this way, making it impossible for the

language efficiently to discover the actual size of a variant record at

runtime. An automatic garbage collector must be able unambiguously to decide

the size of objects it wishes to discard.

Fortunately the type extension mechanism chosen for Oberon makes variant

records completely redundant, as it can achieve the same flexibility in a

type-safe way. So variant records were dropped. Once the pruning knife was

unsheathed other features of Modula started to look vulnerable and were

dropped, either because they were redundant or not worth the complication they

introduced into compilers. As a result an Oberon compiler can be much smaller

than a Modula-2 compiler; the Oberon implementation of July 1988 involved just

130K of source code, yielding 39K of compiled code and taking 41 seconds to

compile itself.


TYPE EXTENSION

Type extension is the facility to construct a new record type on the basis of

an existing type. For example if you have defined a type Circle like this :-


TYPE   Circle = RECORD

                  x,y,radius: REAL

                END;


then an extension of the type Circle might be :-


      FilledCircle(Circle) = RECORD

                               fillcolor: INTEGER

                             END;


A record of the new type inherits the fields x, y, and radius from its 'base

type' Circle and then adds its own field called fillColor. This mechanism

should be familiar enough to Turbo Pascal 5.5 and C++ users because the syntax

employed is very like that used for defining object hierarchies in these

languages. Indeed you might think of type extension as being a 'half-way

house' to full object orientation, as it provides extensibility for data types

but not for procedures (ie. methods). In Oberon the mechanism for

encapsulating procedures remains the module, just as in Modula-2, and modules

are not extensible.

To clear up some terminology; type FilledCircle is called a 'direct extension'

of type Circle, and Circle is its 'direct base type'. A new type called

BorderedFilledCircle, which extends FilledCircle, would also be an extension

of Circle, but not now a direct extension because FilledCircle intervenes in

the hierarchy. A type is also counted as an extension if it equals the base

type, or more formally: T' extends T if T' = T or T' is a direct extension of

an extension of T.

In Oberon, values of an extended type can be assigned to a variable of any of

their base types. So we could assign records of type FilledCircle to a

variable of type Circle; only the X,Y and Radius values would be assigned.

This is called a 'projection' of the extended type onto the space of the base

type. If we were to define a type 2Point with fields X and Y, then extend it

to type 3Point with fields X,Y and Z, then you can see that projecting a

3Point to a 2Point means just what it means in ordinary speech; the 3-

dimensional point X,Y,Z is projected as if onto a 2-dimensional screen X,Y.

Type extension in Oberon extends across module boundaries, so that you can

import a type from another module and then define extensions to it in the

current one. This is the backbone of Oberon programming technique.

Extension applies also to pointer types, which in Oberon can only be pointers

to record or array types. The type of a pointer to a FilledCircle is an

extension of the type POINTER TO Circle, and so can be assigned to variables

of that type. This has important consequences when building complex dynamic

data structures such as lists and trees. You can write a module which defines

an abstract list structure, a base node type and the procedures to access it.

Then client modules can import and extend the base node type as required, and

add new procedures to access nodes of the extended type. This is very like

object oriented programming in, say C++, except that you must explicitly

import the manipulating procedures rather than having them implicitly

'inherited'.

I'll take an example taken from Wirth's 1988 paper 'From Modula to Oberon'.

Here's part of a module called M which defines a tree structure (which grows

from a variable called 'root' of type Node) and its search procedure :-


TYPE Node =    POINTER TO Object;

     Object =  RECORD

                 key, x, y: INTEGER;

                 left, right: Node

               END;


PROCEDURE Element(k: INTEGER): Node;

VAR p:Node;

BEGIN

  p := root;

  WHILE (p # NIL) & (p.key # k) DO

    IF p.key < k

    THEN p := p.left

    ELSE p := p.right

    END

  END;

  RETURN p

END Element


This module manipulates trees in the abstract. Now we can define a client

module that extends the type Object into some more directly useful types :-


TYPE Rectangle =    POINTER TO RectObject;

     RectObject =   RECORD(Object)

                      width, height: REAL

                    END;

     Circle =       POINTER TO CircleObject;

     CircleObject = RECORD(Object)

                      radius: REAL

                    END


Because of the the type compatibility rules of Oberon, we can assign pointers

of type Rectangle or Circle to variables of type Node and so build trees whose

nodes point to objects of mixed types. However there is still a problem; we

cannot yet retrieve RectObjects or CircleObjects from such nodes. All we can

retrieve are Objects, which are mere projections with none of the interesting

properties we desire. What we need is a way to perform the reverse of

projection and go back to the 'wider' view. ~Oberon offers a type-safe way to

do this via 'type guards'.


TYPE GUARDS

When manipulating structures containing mixed types like the tree we just

considered, we need to be able to discover the actual type a node has become

bound to at ~runtime in order to know what fields it has. If for example a Node

points to a Rectangle we can retrieve its width, but if it points to a Circle

then we want its radius instead. However the assignment compatibility rule of

~Oberon, stated above, allows us to assign a Rectangle to a Node (or a

~RectObject to an Object) but not vice versa. The answer to this problem lies

in 'type tests' and 'type guards'.

The type test 'p IS Rectangle' is a Boolean expression which is true only if p

currently contains a pointer of type Rectangle. In general t IS T' is true if

t (of type T) currently contains a value of type T', and T' is an extension of

T.

Reverse assignments of base types to extended types can be made by applying a

type guard. The assignment t' := t(T'), where t' is of type T' and t is of

type T (a base type of T'), is legal and can succeed if t currently holds a

value of type T'. The (T') is called the type guard of t. If the value of t is

not of type T' (nor an extension of it) then the guard fails and the program

aborts; a failing guard is fatal, like an array bound violation or a failing

CASE selector. Type guards look ~syntactically rather like C typecasts, but

they could hardly be more different in intention; where ~Oberon demands that

this must be the right sort of thing, and stops if it is not, C says 'bend the

thing to make it fit'. The world may well end with a misplaced typecast.

Guards can be applied to assignments of record fields as well as whole

records. All this may be easier to follow with a more concrete example. If W

is a REAL variable then the assignment


W := p(Rectangle).width;


is legal, and succeeds if p does indeed contain a Rectangle pointer. It would

fail and abort the program if p contained a Circle. If we had defined an

extension of Rectangle called ~FilledRectangle, then the assignment would also

succeed when p contained a ~FilledRectangle (which is quite safe because

~FilledRectangles also have a width). Since aborting a program is to be avoided

at all costs, type tests are used to make sure this never occurs. So in the

tree example above, we might write an access procedure that contains lines

like this :-


p := M.Element(K);

IF p # NIL THEN

  IF p IS Rectangle

  THEN Area := p(Rectangle).width * p(Rectangle).height;

  ELSIF p IS Circle

     THEN Area := pi * p(Circle).radius * p(Circle).radius;

  ELSIF ...........


To avoid having to write too many type guards, which is both verbose and

inefficient for the compiler, Oberon employs the WITH statement (which loses

the meaning it had in Modula-2) to assert that a variable has a particular

type throughout a whole sequence of statements; this is called a 'regional

type guard' :-


WITH p: Rectangle DO

  Area := p.width * p.height;

  Perim := 2 * (p.width + p.height);

  .........

END;


This should be enough of a taste of Oberon to show you that variant records

are now completely redundant and that type extensions with guards offer a

safer but also more powerful alternative.

Oberon also displaces the Modula-2 concept of 'opaque types' used for

information hiding, by a more general concept. In a Modula opaque type you

export only the name of a type so that its representation remains hidden from

the users of the type. In Oberon you can hide part or all of a type by only

exporting a partial definition or 'public projection'. For example a type


  Box = RECORD x,y,width,height: REAL END;


might be exported as


  Box = RECORD x,y: REAL END;


so that client programs can only change the position but not the dimensions of

a Box. Of course a client can still define extensions to Box. The type of a

non-exported record field can be hidden too, so you can completely hide a

sensitive data structure while still allowing components of an exported type

to refer to it.

Apart from type extensions, test and guards, the only other additions to

Oberon compared to Modula-2 are multi-dimensional open arrays and 'type

inclusion'. The latter is a hierarchical relaxation of the type compatibility

rules so that if type T includes T', values of type T' are also values of type

T and can be assigned to variables of type T. Oberon supports five numeric

types such that LONGREAL includes REAL, which includes LONGINT, which includes

INTEGER, which includes SHORTINT. Hence you can always assign an INTEGER to a

REAL variable, or a SHORTINT to an INTEGER. This scheme almost removes the

need for type conversions and dispels some of the more irritating aspects of

Modula-2 (for example the incompatibility of INTEGERs, CARDINALs and REALs).


PRUNING MODULA-2

We can now examine what features of Modula-2 are omitted from Oberon, and

understand why it was possible to exclude them. As you will see, far more has

been removed than has been added.

Variant records and opaque types are dropped, since the type extension scheme

is safer, more elegant and more powerful.

Enumeration types, eg. Colors = (red,blue,green), are not supported in Oberon.

They were originally introduced in Pascal to improve program clarity, but it

is now Wirth's opinion that their indiscriminate use leads to an explosion of

type declarations and to verbose programs. The values of an enumeration type

have an uncomfortable, exceptional status; they are neither proper

identifiers, nor are they string constants available at runtime. This causes

an inconsistency in the rules of Modula-2, because unlike other types you

cannot export an enumeration type's identifier without automatically exporting

all its constant identifiers. Enumeration types also posed tricky problems

in type extending them across Oberon's module boundaries.

Subrange types, eg. XCoord = 0..639, have been dropped too; originally

introduced to allow a compiler to generate guards for assignments and to

economize on storage, Wirth now feels their benefits are not worth the

complexity they add to a compiler. Having lost these two types it was natural

to exclude user-defined set types and replace them with a single type SET

whose values are sets of the integers.

Pointer types are confined to record and array types in Oberon. Array index

types are no longer definable and all indices are integers. The lower bound of

all arrays is fixed to 0, so you declare for example ARRAY 10 OF INTEGER. This

simplifies bound checking, especially for dynamic arrays, and removes a rich

source of programmer errors.

The FOR loop has been dropped completely and you must use either REPEAT or

WHILE with an explicit counter variable. We have already seen that the WITH

statement used for record fields in Modula is used in Oberon for type guards.

When accessing record fields you must always fully qualify the field name with

its record name. This principle of full qualification extends to imports too;

the Modula construct FROM M IMPORT x has been abandoned and you must specify

M.x for every occurence of x in your program. Modula-2 experience has shown

that this is preferable when many modules are imported.

The low-level features supported through the SYSTEM module in Modula have been

eliminated along with the type-conversion functions, absolute addressing for

variables and the ADDRESS and WORD types. Oberon implementations are free to

provide system-dependent modules but these do not belong to the language

definition, so no-one can fool themselves that such features are anything but

implementation-specific and non-portable. Concurrency, supported in Modula

through coroutines, has been removed. Wirth stresses that this is not a

rejection of the need for concurrency in general programming, but reflects the

fact that the Oberon-Ceres project was deliberately designed not to employ

concurrency.

The structure of programs has been rationalized in Oberon. Modula's special

main module, which has no definition part, has gone. It was an anomaly because

although actually a package of data and procedures, it had to act as a single

executable procedure to the operating system. All modules in Oberon are equal

and can be compiled and executed. Under the Oberon operating environment any

parameterless procedure within any module can be executed as a 'command' by

typing its qualified name (eg. MyModule.Start); this is how you invoke

programs. If MS-DOS compilers for Oberon appear this feature will present a

problem as DOS has no mechanism for executing parts of an .EXE file in this

fashion.

The reserved words DEFINITION and IMPLEMENTATION have gone and all modules

begin in the same way with the word MODULE. Every module has an interface or

definition text which is just an excerpt from the text of the module,

containing copies of just those constant, type and variable declarations and

procedure headings that are to be exported. Local modules are dropped as

Modula programmers seldom used them and they complicated the scope rules

unnecessarily.

The total effect of these changes is to make Oberon's rules for handling

modules simpler and more orthogonal than those in Modula-2, as every module is

a complete compilable unit.


OBERON AND OBJECT ORIENTATION

Earlier on I said that Oberon was a 'halfway house' to object orientation. You

may well be wondering why Niklaus Wirth did not go the whole way, to a fully

object-oriented system. It is certainly not for any want of experience of OOPS

for as well as sanctioning the development of Modula-3, Wirth and his co-

workers have themselves experimented with object-oriented extensions to both

Modula-2 and Oberon by making modules into first-class objects that can have

methods and instances.

However Wirth remains unconvinced that encapsulated methods offer the best

paradigm for programming large systems. He considers the OOP insistence that

all access procedures must be defined in the same place as the data structures

they work on to be an unwieldy dogma. When developing large systems he

believes it is important to be able to add new procedures in later modules

without being forced to define a whole new sub-class, especially if this would

involve recompiling the original class definition and all its clients.

(To be fair, virtual method systems as used in C++ and Turbo Pascal 5.5 make

such recompilation unnecessary).

In Oberon it is procedure types rather than the procedures themselves that are

contained in data structures (or objects) in the program text, and binding

occurs at runtime by assigning a procedure called a 'handler' to a procedure

type field in a record. Type tests enable a handler to discriminate between

the various extensions of a base type while still maintaining strict data

typing. (Listing 1 shows an example of a handler called EdT.Handle which gets

assigned in the last line of EdT.Open).

Purely object-oriented languages like Smalltalk tend to be typeless. Variables

can hold objects of any class (ie. type) and so the compiler cannot tell you

if the wrong object has been put into a variable. The program may still do

something sensible thanks to polymorphism, which ensures that different

objects can do their 'own thing' in response to the same message. For example

sending a Print message to a Rectangle object prints a rectangle but if a

Circle has got in there by mistake the message will at least print a Circle.

This is close to the way the real world behaves; elephants do elephant things

and oranges do orange things. But if an elephant finds its way into your

orange squeezer it will surely ruin your breakfast, and the fact that it does

elephant things may prove to be a voluminous embarrassment rather than a

consolation.

Until some Oberon compilers become widely available for popular operating

systems like MS-DOS, Mac and Unix we can't sample the Oberon programming style

for ourselves, but I for one am impatient to try it. Above all, I just love

the idea of a compiler that actually got smaller.


REFERENCES

N. Wirth   "From Modula to Oberon",

            Software Practice and Experience vol.18(7), Wiley. July 1988.

           "The Programming Language Oberon" ibid.


J. Gutknecht "The Oberon Guide",

              Bericht 108, Dept fur Informatik, ETH Zurich. June 1989.


Martin Odersky  "Extending Modula-2 for Object-Oriented Programming.

                First International Modula-2 Conference 1989.


------------------------------------------------------------------------------

Listing 1. Extracts from a module by Robert Griesemer and Michael Franz which

adds new functions (auto-indentation and cursor controlled indentation) to the

Oberon editor Edit.


MODULE EdT;

IMPORT

  Display, Viewers, Texts, TextFrames, MenuViewers, Oberon;


CONST

  HT = 9X; LF = 0AX; CR = 0DX; Left = 01CX; Right = 01DX;

  Menu = "System.Close System.Copy System.Grow Edit.Store";


TYPE

  EdTMsg = RECORD(Display.FrameMsg)  (* a type extension *)

              text: Texts.Text;

              beg, end: LONGINT;

              time: LONGINT

            END;

VAR

  W: Texts.Writer;

(* Procedures BegOfLine, Select, Move, Newline defined here... *)


PROCEDURE Handle(F: Display.Frame; VAR msg: Display.FrameMsg);

BEGIN

  WITH F: TextFrames.Frame DO

    IF msg IS Oberon.InputMsg THEN         (* a type test *)

      WITH msg: Oberon.InputMsg DO         (* a regional type guard *)

        IF msg.id = Oberon.consume THEN

          IF    msg.ch = Left  THEN Move(F,-1)

          ELSIF msg.ch = Right THEN Move(F, 1)

          ELSIF F.car > 0 THEN             (* caret set *)

            IF  msg.ch = LF THEN

                msg.ch = CR;

                TextFrames.Handle(F,msg)

            ELSIF msg.ch = CR THEN Newline(F)

            ELSE  TextFrames.Handle(F,msg)

            END

          END

        ELSE TextFrames.Handle(F,msg)

        END

      END

    ELSIF msg IS EdTMsg THEN

      WITH msg: EdTMsg DO

        IF (F.text = msg.text) & (F.sel = 0) THEN

           TextFrames.SetSelection(F, msg.beg, msg.end);

           F.Time := msg.time

        END

      END

    ELSE TextFrames.Handle(F,msg)

    END

  END

END Handle;

PROCEDURE Open;

VAR S: Texts.Scanner;

    T: Texts.Text;

    V: MenuViewers.Viewer;

    x,y: INTEGER;

    beg, end, time: LONGINT;

BEGIN

  Texts.OpenScanner(S, Oberon.Par.text, Oberon.Par.pos);

  Texts.Scan(S);

  IF (S.class = Texts.Char) & ( S.c = "^") OR (S.line # 0) THEN

    Oberon.GetSelection(T, beg, end, time);

    IF time > 0 THEN Texts.OpenScanner(S, T, beg);

                     Texts.Scan (S)

                END

  END

  IF S.class = Texts.Name THEN

    Oberon.AllocateUserViewer(Oberon.Mouse.X, x, y);

    V := MenuViewers.New(TextFrames.NewMenu(S.s, Menu),

                         TextFrames.NewText(TextFrames.Text(S.s), 0),

                         TextFrames.menuH, x, y);

    V.dsc.next.handle := Handle    (* assignment of a handler *)

  END

END Open;

BEGIN  Texts.OpenWriter(W)         (* initialisation *)

END EdT.