OOCref_10.html100664 1750 1750 106761 6753666056 11310 0ustar sagsag The OOC Reference Manual - Oakwood Compliant Modules

Go to the first, previous, next, last section, table of contents.


Oakwood Compliant Modules

In order to support the Oakwood Guildlines, OOC provides a set of basic library modules that comply with the Oakwood specification. (Note that all Oakwood modules may not be available.) All Oakwood compliant modules begin with the prefix "Oak".

Module OakStrings

Module Strings provides a set of operations on strings (i.e., on string constants and character arrays, both of which contain the character 0X as a terminator). All positions in strings start at 0.

(The Oakwood Guildlines remark that string assignments and string comparisons are already supported by the language Oberon-2.)

Procedures

Function: Length (s: ARRAY OF CHAR): INTEGER
Returns the number of characters in s up to and excluding the first 0X.

Procedure: Insert (src: ARRAY OF CHAR; pos: INTEGER; VAR dst: ARRAY OF CHAR)
Inserts the string src into the string dst at position pos (0<=pos<=Length(dst)). If pos=Length(dst), src is appended to dst. If the size of dst is not large enough to hold the result of the operation, the result is truncated so that dst is always terminated with a 0X.

Procedure: Append (s: ARRAY OF CHAR; VAR dst: ARRAY OF CHAR)
Has the same effect as Insert(s, Length(dst), dst).

Procedure: Delete (VAR s: ARRAY OF CHAR; pos, n: INTEGER)
Deletes n characters from s starting at position pos (0<=pos<=Length(s)). If n>Length(s)-pos, the new length of s is pos.

Procedure: Replace (src: ARRAY OF CHAR; pos: INTEGER; VAR dst: ARRAY OF CHAR)
Has the same effect as Delete(dst, pos, Length(src)) followed by
Insert(src, pos, dst).

Procedure: Extract (src: ARRAY OF CHAR; pos, n: INTEGER; VAR dst: ARRAY OF CHAR)
Extracts a substring dst with n characters from position pos (0<=pos<= Length(src)) in src. If n>Length(src)-pos, dst is only the part of src from pos to the end of src, i.e. Length(src)-1. If the size of dst is not large enough to hold the result of the operation, the result is truncated so that dst is always terminated with a 0X.

Function: Pos (pat, s: ARRAY OF CHAR; pos: INTEGER): INTEGER
Returns the position of the first occurrence of pat in s. Searching starts at position pos. If pat is not found, `-1' is returned.

Procedure: Cap (VAR s: ARRAY OF CHAR)
Replaces each lower case letter within s by its upper case equivalent.

Module OakFiles

Module `OakFiles' provides operations on files and the file directory.

The Oakwood Guildlines define the type File as representing a stream of bytes ususally stored on an external medium. A File has a certain length as well as the date and time of its last modification.

A file directory is a mapping from file names to files. A file that is not registered in the directory is considered temporary.

The type Rider holds a read/write position in a file (positions start with 0). There may be multiple riders set to the same file. The field eof is set to TRUE if an attempt was made to read beyond the end of the file. The field res reports the success of ReadBytes and WriteBytes operations. Writing data overwrites old data at the rider position. When data is written beyond the end of the file, the file length increases.

Operations for Unformatted Input and Output

In general, all operations must use the following format for external representation:

Example:

  VAR f: Files.File; r: Files.Rider; ch: CHAR;

Reading from an existing file:

  f := Files.Old ("xxx");
  IF f # NIL THEN
    Files.Set (r, f, 0);
    Files.Read (r, ch);
    WHILE ~ r.eof DO
      Files.Read (r, ch)
    END
  END

Writing to a new file yyy:

  f := Files.New ("yyy");
  Files.Set (r, f, 0);
  Files.WriteInt (r, 8);
  Files.WriteString (r, " bytes");
  Files.Register (f)

Please note: This module implements virtual file descriptors; that is, an unlimited number of files can be open at the same time. These files share the limited number of file descriptors provided by the operating system.

Remarks

The Oakwood Guildlines provide the following specifications:

WriteNum and ReadNum, should use the following encoding algorithms for conversion to and from external format:

PROCEDURE WriteNum (VAR r: Rider; x: LONGINT);
BEGIN
   WHILE (x < - 64) OR (x > 63) DO 
       Write(r, CHR(x MOD 128 + 128)); x := x DIV 128
   END;
   Write(r, CHR(x MOD 128))
END WriteNum;

PROCEDURE ReadNum (VAR r: Rider; VAR x: LONGINT);
   VAR s: SHORTINT; ch: CHAR; n: LONGINT;
BEGIN 
   s := 0; n := 0;
   Read(r, ch);
   WHILE ORD(ch) >= 128 DO
      INC(n, ASH(ORD(ch) - 128, s) );
      INC(s, 7);
      Read(r, ch)
   END;
   x := n + ASH(ORD(ch) MOD 64 - ORD(ch) DIV 64 * 64, s)
END ReadNum;

The reason for the specification of the file name in the operation New is to allow allocation of the file on the correct medium from the beginning (if the operating system supports multiple media).

The operations Read, Write, ReadBytes and WriteBytes require the existence of a type SYSTEM.BYTE with the following characteristics:

Types

Data type: File = POINTER TO FileDesc

Record: FileDesc = RECORD

Record: Rider = RECORD
Field: eof-: BOOLEAN
Set to TRUE if an attempt was made to read beyond the end of the file.
Field: res-: INTEGER
See ReadBytes and WriteBytes below for possible values of res.

Operations on Files and the File Directory

Function: Old (name: ARRAY OF CHAR): File
Old(name) searches for the name in the directory and returns the corresponding file. If the name is not found, it returns NIL.

Function: New (name: ARRAY OF CHAR): File
New(name) creates and returns a new file. The name is remembered for the later use of the operation Register. The file is only entered into the directory when Register is called.

Procedure: Register (f: File)
Register(f) enters the file f into the directory together with the name provided in the operation New that created f. The file buffers are written back. Any existing mapping of this name to another file is overwritten.

Procedure: Close (VAR f: File)
Close(f) writes back the file buffers of f. The file is still accessible by its handle f and the riders positioned on it. If a file is not modified, it is not necessary to close it.

Please note: The above holds only for permanentClose=FALSE. Otherwise, the buffers are flushed and the file handle is deallocated (and f is set to NIL); at this time, all riders on this file become invalid. This behaviour, and the variable permanentClose, are not part of The Oakwood Guidelines.

Procedure: Purge (f: File)
Purge(f) resets the length of file f to 0.

Procedure: Delete (name: ARRAY OF CHAR; VAR res: INTEGER)
Delete(name, res) removes the directory entry for the file name without deleting the file. If res=0 the file has been successfully deleted. If there are variables referring to the file while Delete is called, they can still be used.

Procedure: Rename (old, new: ARRAY OF CHAR; VAR res: INTEGER)
Rename(old, new, res) renames the directory entry old to new. If res=0, the file has been successfully renamed. If there are variables referring to the file while Rename is called, they can still be used.

Function: Length (f: File): LONGINT
Length(f) returns the number of bytes in file f.

Procedure: GetDate (f: File; VAR t, d: LONGINT)
GetDate(f, t, d) returns the time t and date d of the last modification of file f.

The encoding is as follows:

hour = t DIV 4096; 
minute = t DIV 64 MOD 64; 
second = t MOD 64; 

year = d DIV 512; 
month = d DIV 32 MOD 16; 
day = d MOD 32.

Operations on Riders

Procedure: Set (VAR r: Rider; f: File; pos: LONGINT)
Set(r, f, pos) sets the rider r to position pos in file f. The field r.eof is set to FALSE. The operation requires that 0 <= pos <= Length(f).

Function: Pos (VAR r: Rider): LONGINT
Pos(r) returns the position of the rider r.

Function: Base (VAR r: Rider): File
Base(r) returns the file to which the rider r has been set.

Reading

Procedure: Read (VAR r: Rider; VAR x: SYSTEM.BYTE)
Read(r, x) reads the next byte x from rider r and advances r accordingly.

Procedure: ReadInt (VAR r: Rider; VAR i: INTEGER)
ReadInt(r, i) reads a integer number i from rider r and advances r accordingly.

Procedure: ReadLInt (VAR r: Rider; VAR i: LONGINT)
ReadLInt(r, i) reads a long integer number i from rider r and advances r accordingly.

Procedure: ReadReal (VAR r: Rider; VAR x: REAL)
ReadReal(r, x) reads a real number x from rider r and advances r accordingly.

Procedure: ReadLReal (VAR r: Rider; VAR x: LONGREAL)
ReadLReal(r, x) reads a long real number x from rider r and advances r accordingly.

Procedure: ReadNum (VAR r: Rider; VAR i: LONGINT)
ReadNum(r, i reads an integer number i from rider r and advances r accordingly. The number i is compactly encoded (see the "Remarks" section above).

Procedure: ReadString (VAR r: Rider; VAR s: ARRAY OF CHAR)
ReadString(r, s) reads a sequence of characters (including the terminating 0X) from rider r and returns it in s. The rider is advanced accordingly. The actual parameter corresponding to s must be long enough to hold the character sequence plus the terminating 0X.

Procedure: ReadSet (VAR r: Rider; VAR s: SET)
ReadSet(r, s) reads a set s from rider r and advances r accordingly.

Procedure: ReadBool (VAR r: Rider; VAR b: BOOLEAN)
ReadBool(r, b) reads a Boolean value b from rider r and advances r accordingly.

Procedure: ReadBytes (VAR r: Rider; VAR buf: ARRAY OF SYSTEM.BYTE; n: LONGINT)
ReadBytes(r, buf, n) reads n bytes into buffer buf starting at the rider position r. The rider is advanced accordingly. If less than n bytes could be read, r.res contains the number of requested but unread bytes.

Writing

Procedure: Write (VAR r: Rider; x: SYSTEM.BYTE)
Write(r, x) writes the byte x to rider r and advances r accordingly.

Procedure: WriteInt (VAR r: Rider; i: INTEGER)
WriteInt(r, i) writes the integer number i to rider r and advances r accordingly.

Procedure: WriteLInt (VAR r: Rider; i: LONGINT)
WriteLInt(r, i) writes the long integer number i to rider r and advances r accordingly.

Procedure: WriteReal (VAR r: Rider; x: REAL)
WriteReal(r, x) writes the real number x to rider r and advances r accordingly.

Procedure: WriteLReal (VAR r: Rider; x: LONGREAL)
WriteLReal(r, x) write the long real number x to rider r and advance r accordingly.

Procedure: WriteNum (VAR r: Rider; i: LONGINT)
WriteNum(r, i) writes the integer number i to rider r and advances r accordingly. The number i is compactly encoded (see the "Remarks" section above).

Procedure: WriteString (VAR r: Rider; s: ARRAY OF CHAR)
WriteString(r, s) writes the sequence of characters s (including the terminating 0X) to rider r and advances r accordingly.

Procedure: WriteSet (VAR r: Rider; s: SET)
WriteSet(r, s) writes the set s to rider r and advances r accordingly.

Procedure: WriteBool (VAR r: Rider; b: BOOLEAN)
WriteBool(r, b) writes the Boolean value b to rider r and advances r accordingly.

Procedure: WriteBytes (VAR r: Rider; VAR buf: ARRAY OF SYSTEM.BYTE; n: LONGINT)
WriteBytes(r, buf, n) writes the first n bytes from buf to rider r and advances r accordingly. r.res contains the number of bytes that could not be written (e.g., due to a disk full error).

Module OakIn

Module `In' provides a set of basic routines for formatted input of characters, character sequences, numbers, and names. It assumes a standard input stream with a current position that can be reset to the beginning of the stream. A call to procedure Open initializes module `In' and sets it to read from the standard input channel StdChannels.stdin (see section Module StdChannels)

Module `In' has a concept of a current position, which is the character position in the input stream from where the next symbol is read. Open (re)sets it to the beginning of the input stream. After reading a symbol, the current position is set to the position immediately after this symbol. Before the first call to Open, the current position is undefined.

Variables

Read-only Variable: Done: BOOLEAN
Indicates the success of an input operation. If Done is TRUE after an input operation, the operation was successful and its result is valid. An unsuccessful input operation sets Done to FALSE; it remains FALSE until the next call to Open. In particular, Done is set to FALSE if an attempt is made to read beyond the end of the input stream.

Procedures

Procedure: Open
(Re)sets the current position to the beginning of the input stream. Done indicates if the operation was successful.

Procedure: Char (VAR ch: CHAR)
Returns the character ch at the current position.

Procedure: LongInt (VAR n: LONGINT)
Returns the long integer constant n at the current position according to the format:
IntConst = digit {digit} | digit {hexDigit} "H".

Procedure: Int (VAR n: INTEGER)
Returns the integer constant n at the current position according to the format:
IntConst = digit {digit} | digit {hexDigit} "H".

Procedure: LongReal (VAR n: LONGREAL)
Returns the long real constant n at the current position according to the format:
LongRealConst = digit {digit} ["." {digit} 
                [("D" | "E") ("+" | "-") digit {digit}]].

Procedure: Real (VAR n: REAL)
Returns the real constant n at the current position according to the format:
RealConst = digit {digit} ["." {digit} 
            ["E" ("+" | "-") digit {digit}]].

Procedure: String (VAR s: ARRAY OF CHAR)
Returns the string s at the current position according to the format:
StringConst = '"' char {char} '"'.

The string must not contain characters less than blank such as EOL or TAB.

Procedure: Name (VAR s: ARRAY OF CHAR)
Returns the name s at the current position according to the file name format of the underlying operating system (e.g., "lib/My.Mod" under Unix). Note: This implementation defines a name as `Name = char {char}', where `char' is any character greater than blank.

Module OakOut

Module `Out' provides a set of basic routines for formatted output of characters, numbers, and strings. It assumes a standard output stream to which the symbols are written.

Procedure: Open
Initializes the output stream.

Procedure: Char (ch: CHAR)
Writes the character ch to the end of the output stream.

Procedure: String (s: ARRAY OF CHAR)
Writes the null-terminated character sequence s to the end of the output stream (without 0X).

Procedure: Int (i, n: LONGINT)
Writes the integer number i to the end of the output stream. If the textual representation of i requires m characters, i is right adjusted in a field of Max(n, m) characters padded with blanks at the left end. A plus sign is not written.

Procedure: Real (x: REAL; n: INTEGER)
Writes the real number x to the end of the output stream using an exponential form. If the textual representation of x requires m characters (including a two-digit signed exponent), x is right adjusted in a field of Max(n, m) characters padded with blanks at the left end. A plus sign of the mantissa is not written.

Procedure: LongReal (x: LONGREAL; n: INTEGER)
Writes the long real number x to the end of the output stream using an exponential form. If the textual representation of x requires m characters (including a three-digit signed exponent), x is right adjusted in a field of Max(n, m) characters padded with blanks at the left end. A plus sign of the mantissa is not written.

Procedure: Ln
Writes an end-of-line symbol to the end of the output stream.

Modules OakMath and OakMathL

Constants

The Oakwood Guildlines requires the definition of the following mathematical constants (i.e., implementation-defined approximations):

Constant: pi

Constant: e

Procedures

Function: sqrt (x: REAL): REAL
Function: sqrt (x: LONGREAL): LONGREAL
sqrt(x) returns the square root of x, where x must be positive.

Function: sin (x: REAL): REAL
Function: sin (x: LONGREAL): LONGREAL
sin(x) returns the sine value of x, where x is in radians.

Function: cos (x: REAL): REAL
Function: cos (x: LONGREAL): LONGREAL
cos(x) returns the cosine value of x, where x is in radians.

Function: tan (x: REAL): REAL
Function: tan (x: LONGREAL): LONGREAL
tan(x) returns the tangent value of x, where x is in radians.

Function: arcsin (x: REAL): REAL
Function: arcsin (x: LONGREAL): LONGREAL
arcsin(x) returns the arcsine value in radians of x, where x is in the sine value.

Function: arccos (x: REAL): REAL
Function: arccos (x: LONGREAL): LONGREAL
arcos(x) returns the arcos value in radians of x, where x is in the cosine value.

Function: arctan (x: REAL): REAL
Function: arctan (x: LONGREAL): LONGREAL
arctan(x) returns the arctan value in radians of x, where x is in the tangent value.

Function: power (x, base: REAL): REAL
Function: power (x, base: LONGREAL): LONGREAL
power(x, base) returns the x to the power base.

Function: round (x: REAL): REAL
Function: round (x: LONGREAL): LONGREAL
round(x) if fraction part of x is in range 0.0 to 0.5, then the result is the largest integer not greater than x, otherwise the result is x rounded up to the next highest whole number. Note that integer values cannot always be exactly represented in LONGREAL or REAL format.

Function: ln (x: REAL): REAL
Function: ln (x: LONGREAL): LONGREAL
ln(x) returns the natural logarithm (base e) of x.

Function: exp (x: REAL): REAL
Function: exp (x: LONGREAL): LONGREAL
exp(x) is the exponential of x base e. x must not be so small that this exponential underflows nor so large that it overflows.

Function: log (x, base: REAL): REAL
Function: log (x, base: LONGREAL): LONGREAL
log(x, base) is the logarithm of x base base. All positive arguments are allowed. The base base must be positive.

Function: arctan2 (xn, xd: REAL): REAL
Function: arctan2 (xn, xd: LONGREAL): LONGREAL
arctan2(xn,xd) is the quadrant-correct arc tangent `atan(xn/xd)'. If the denominator xd is zero, then the numerator xn must not be zero. All arguments are legal except xn = xd = 0.

Function: sinh (x: REAL): REAL
Function: sinh (x: LONGREAL): LONGREAL
sinh(x) is the hyperbolic sine of x. The argument x must not be so large that exp(|x|) overflows.

Function: cosh (x: REAL): REAL
Function: cosh (x: LONGREAL): LONGREAL
cosh(x) is the hyperbolic cosine of x. The argument x must not be so large that exp(|x|) overflows.

Function: tanh (x: REAL): REAL
Function: tanh (x: LONGREAL): LONGREAL
tanh(x) is the hyperbolic tangent of x. All arguments are legal.

Function: arcsinh (x: REAL): REAL
Function: arcsinh (x: LONGREAL): LONGREAL
arcsinh(x) is the arc hyperbolic sine of x. All arguments are legal.

Function: arccosh (x: REAL): REAL
Function: arccosh (x: LONGREAL): LONGREAL
arccosh(x) is the arc hyperbolic cosine of x. All arguments greater than or equal to 1 are legal.

Function: arctanh (x: REAL): REAL
Function: arctanh (x: LONGREAL): LONGREAL
arctanh(x) is the arc hyperbolic tangent of x. |x| < 1 - sqrt(em), where `em' is machine epsilon. Note that |x| must not be so close to 1 that the result is less accurate than half precision.


Go to the first, previous, next, last section, table of contents. OOCref_11.html100664 1750 1750 127547 6753666110 11305 0ustar sagsag The OOC Reference Manual - Exception Handling

Go to the first, previous, next, last section, table of contents.


Exception Handling

An exception is an event that may require special processing by a user program (or by the underlying implementation). Exceptions may be raised by the computer's error-detection mechanisms, explicit activations (e.g., HALT and ASSERT), failed runtime checks, or by actions external to the program. The pair of modules `Exception' and `Signal' give the programmer control over the handling of these exceptions. `Exception' provides the basic exception handling mechanism for user programs, whereas `Signal' provides the means to connect signal handlers to that mechanism.

A signal is an externally generated software interrupt delivered to a process (or program). These are generally produced by the underlying operating system as a means of reporting exceptional situations to executing processes. However, it is also possible for one process to signal another process.

Module Exception

The primary use of this module is to provide error handling and to allow programmer control over both system and language (HALT and ASSERT) exception handling. The programmer may define handlers, which can be used in place of those defined by the implementation.

There are two states of program execution: normal and exceptional. A program remains in the normal execution state until an exception is raised by a call to RAISE, HALT, or ASSERT, or after a failed run-time check. After that, the program remains in the exceptional execution state until ACKNOWLEDGE or RETRY is called.

An exception affects the control flow of a program; raising an exception implies transfer of control to some sort of handler, even across procedure invocations. An exception handler is a statement sequence that is executed when an exception occurs. In OOC, an exception handler is set up as part of an execution context. Both normal and exceptional execution blocks can be set up within the same procedure, or exceptions can be allowed to propogate up the call stack and handled by a calling procedure. A execution context, and exception handler, is typically set up like

Exception.PUSHCONTEXT (e);
IF (e = NIL) THEN
  (* normal execution *)
ELSE  (* an exception was raised *)
  (* handle the exception raised during normal execution *)
END;
Exception.POPCONTEXT;

Please note: Wherever the word "thread" appears below, it should be read as "program" for the moment. Multi-threading isn't supported yet.

Exception Facilities

The facilities provided by module `Exception' allow the user to raise exceptions and query the current execution state (normal or exceptional). Exceptions are identified uniquely by a pair (Source, Number).

The programmer is responsible for managing the stack of exception handlers; this is because Oberon-2 does not provide direct language support for exceptions, and therefore exception handling in OOC is done through a library module. The stack is manipulated primarily through the procedures PUSHCONTEXT and POPCONTEXT. The only other action that changes the stack is raising an exception while the program is an exceptional execution state; this pops the topmost context (that was responsible for the exception) from the stack before moving control to the then topmost execution context. Raising an exception in the state of normal execution does not change the stack.

Data type: Number = LONGINT
Values of this type are used to distinguish between different exceptions from the same source.

Data type: Source = POINTER TO SourceDesc
Values of this type are used to identify the source of exceptions raised; that is, a Source is defined and allocated to establish a particular set of exceptions.

Procedure: PUSHCONTEXT (VAR source: Source)
This procedure pushes the current execution context onto the exception handler stack and sets source to NIL; if the context is later reactivated by raising an exception, source is set to the exception's source (see section Exception Examples). At most one context can be pushed per procedure at a time. During a single procedure evaluation, two successive calls to PUSHCONTEXT without a POPCONTEXT in between are not allowed and result in undefined program behaviour.

Please note: When the context is activated again (by raising an exception), the value of non-global variables of enclosing procedures that were modified after the initial call to PUSHCONTEXT are undefined.

Procedure: POPCONTEXT
This procedure removes the exception handler from the top of the stack; if the stack is empty an exception is raised. If the program is in an exceptional execution state at the point where POPCONTEXT is called, the exception is raised again, thereby passing it along to the next higher exception handler. During the execution of a procedure, the dynamic number of calls to POPCONTEXT has to balance the ones to PUSHCONTEXT.

Procedure: RETRY
If the current thread is in the exceptional execution state, a call to this procedure reactivates the context on top of the stack of exception handlers, and resets the execution state to normal. This looks as if the corresponding call of PUSHCONTEXT returns again, with the parameter source set to NIL. This allows the "normal" part to be re-executed. Be very careful when using this because all local variables of the enclosing procedure(s) that were modified after the initial call to PUSHCONTEXT are undefined when activating the context again.

If the current thread is in the normal execution state, calling RETRY raises an exception.

Procedure: ACKNOWLEDGE
If the current thread is in the exceptional execution state, a call to this procedure places it back in the state of normal execution. Calling this procedure indicates that an exception has been handled without retrying the "normal" part.

If the current thread is in the normal execution state, calling ACKNOWLEDGE raises an exception.

Procedure: AllocateSource (VAR newSource: Source)
This procedure allocates a unique value of type Source. If an unique value cannot be allocated, an exception is raised.

Procedure: RAISE (source: Source; number: Number; message: ARRAY OF CHAR)
A call to this procedure associates the given values of source, number, and message with the current context and raises an exception. This means that the current thread switches into the exceptional execution state and activates an execution context from the stack of exception handlers. If the program is in the normal execution state at the time of the call to RAISE, the context on top of the stack is activated; if it was already in the exceptional execution state, the stack is popped before activating the context. Activating the execution context looks as if the corresponding call to PUSHCONTEXT returns a second time, except this time returning with source (of PUSHCONTEXT) set to source (of RAISE) (see section Exception Examples).

Using a value of NIL for source raises an exception.

The message should have the format "[<module>] <description>"; it may be truncated by RAISE to an implementation-defined length.

Function: CurrentNumber (source: Source): Number
If the current thread is in the exceptional execution state because of the raising of an exception from source, this function returns the corresponding number; otherwise, it raises an exception.

Procedure: GetMessage (VAR text: ARRAY OF CHAR)
If the current thread is in the exceptional execution state, this procedure returns the (possibly truncated) string associated with the current context. Otherwise, in normal execution state, it returns the empty string.

Function: IsExceptionalExecution (): BOOLEAN
If the current thread is in the exceptional execution state because of the raising of an exception, this function returns TRUE; otherwise, it returns FALSE.

Restrictions on PUSHCONTEXT

There are a number of important restrictions on the use of PUSHCONTEXT:

  1. Within a procedure, at most one context can be active at a time (i.e., contexts cannot be nested). This allows for an efficient implementation of the context stack without falling back on heap objects. If nested contexts are required, local procedures can be used to set up a new exception context.
  2. The state of all non-global variables that were modified after a PUSHCONTEXT is undefined if the context is activated again by raising an exception or calling RETRY. The reason is that, while the compiler ensures that the evaluation of a piece of code delivers the correct results in the end, it does not ensure that the state of an interrupted computation is correctly reflected by the memory contents at the time of the interruption.
  3. For exceptions that are not initiated by an explicit call to RAISE (i.e., failed run-time checks and external signals), the place where the exception was raised is undefined. That is, the programmer cannot be certain of the exact set of intructions that were completed before the exception was raised. The reason is that a sequence of instructions as specified in the source code may be evaluated in a different order or in an overlapped fashion in the emitted machine code.
  4. Every call to PUSHCONTEXT must have exactly one matching call to POPCONTEXT within the same procedure, assuming that the program parts in between are completed without raising an exception. If a stack underflow occurs when POPCONTEXT is called, an exception is raised. If an execution context is left on the stack that doesn't correspond to a valid procedure (i.e., a procedure doing a PUSHCONTEXT returns without doing a matching POPCONTEXT), activating the context by raising an exception transfers the program into a completely undefined state. Most likely, the program abort due to a segmentation violation or a comparable error, or the stack of execution contexts is rolled back until a valid context is reached. There is no way to check for such a situation. Any programmer should be aware that an invalid context stack can cause considerable grief.

Predefined Exception Sources

Several exception sources are predefined in module `Exception'. These are available for handling exceptions generated through Oberon-2 language constructs and other run-time exceptions.

Read-only Variable: halt: Source
Read-only Variable: assert: Source
These two exception variables are associated to the standard predefined procedures HALT and ASSERT; HALT(n) is equivalent to RAISE (halt, n, ""), and ASSERT(FALSE, n) to RAISE (assert, n, "").

Read-only Variable: runtime: Source
This exception source is used to report failed run-time checks.

Runtime Exception Numbers

The source runtime is used to report failed run-time checks, and the following exception numbers are associated with it. These numbers signify the corresponding failed run-time checks, which are described fully in section Illegal Operations.

Constant: derefOfNIL
A dereference of NIL or type test on NIL.

Constant: realDivByZero
Real division by zero.

Constant: integerDivByZero
Integer division by zero.

Constant: realOverflow
Real overflow (during either conversion or arithmetic operation).

Constant: integerOverflow
Integer overflow (during either conversion or arithmetic operation).

Constant: illegalLength
NEW was called with a negative length for an open array pointer type.

Constant: outOfMemory
NEW could not allocate the requested memory.

Constant: indexOutOfRange
Array index out of range.

Constant: elementOutOfRange
Set element out of range.

Constant: endOfFunction
The end of a function procedure is reached without encountering a RETURN statement.

Constant: noMatchingLabel
No matching label in CASE construct, and there is no ELSE part.

Constant: noValidGuard
All guards of WITH failed, and there is no ELSE part.

Constant: typeGuardFailed
Type guard failed.

Constant: typeAssertFailed
The target of a record assignment does not have compatible type.

Constant: stackOverflow
Stack overflow.

Exception Examples

Typically, one exception source is defined per module. Exception numbers are then used to distinguish between the actual exceptions raised against that source. Those exceptions can then be handled either within that module itself, as is generally the case in OOC Library modules that use `Exception', or the source and related constants can be exported and then handled externally. Because exception sources assert, halt, and runtime are defined within `Exception', failed assertions, and so forth, can be handled just like any other exception.

A Simple Example

The following example is meant to show how to define and use an exception source. Two instances are given where exceptions are raised against that source; note that the exception is handled in only one of these.

MODULE SimpleException;
 
IMPORT  Exception, Err;
 
CONST
  genericException = 1;

VAR  src: Exception.Source;
  
  PROCEDURE RaiseIt;
  BEGIN
    Exception.RAISE (src, genericException, 
                     "[SimpleException] An exception is raised")
  END RaiseIt;
 
  PROCEDURE HandleIt;
    VAR e: Exception.Source;
  BEGIN
    Exception.PUSHCONTEXT (e);
    IF (e = NIL) THEN  (* normal execution *)
      RaiseIt
    ELSE  (* an exception was raised *)
      Err.String ("Caught the exception."); Err.Ln;
      Exception.ACKNOWLEDGE
    END;
    Exception.POPCONTEXT;
  END HandleIt;
 
  PROCEDURE LetItGo;
  BEGIN
    RaiseIt
  END LetItGo;
  
BEGIN
  Exception.AllocateSource (src);
  HandleIt;
  LetItGo;
END SimpleException.

The exception source src is allocated (and initialized) by the call to AllocateSource in the body of the module. Procedure RaiseIt raises an exception against that source.

In procedure HandleIt, an exception context is established, and then any exceptions that are raised in the scope of that context are handled. Note the use of ACKNOWLEDGE to indicate the exception was handled, and POPCONTEXT to end the context and clean up after it.

In procedure LetItGo, the raised exception is not handled, so the exception propagates up the call stack, and finding no enclosing context handler, finally terminates the program. The output of this program should look something like

Caught the exception.
##
## Unhandled exception (#1):
## [SimpleException] An exception is raised
##

Differentiating Exceptions

To identify different exceptions, and provide different handling depending on the exception raised, both the exception Source and Number need to be considered. The pair (Source, Number) uniquely identify the exception that has been raised. For example,

MODULE MultiExcept;
 
IMPORT
  Exception, Out;
 
CONST
  genericException = 1;
  zeroException = 2;
  negativeException = 3;
  
VAR
  src: Exception.Source;
  
  PROCEDURE RaiseIt;
  BEGIN
    Exception.RAISE (src, genericException, 
                     "[MultiExcept] An exception is raised")
  END RaiseIt;
 
  PROCEDURE Test (c: INTEGER);
  BEGIN
    Out.String ("Testing value="); Out.Int (c, 0); Out.Ln;
    IF (c = 0) THEN
      Exception.RAISE (src, zeroException, 
                       "[MultiExcept] Value is zero")
    ELSIF (c < 0) THEN
      Exception.RAISE (src, negativeException, 
                       "[MultiExcept] Value less than zero")
    ELSE
      RaiseIt
    END;
  END Test;
 
  PROCEDURE p (i: INTEGER);
     VAR
       e: Exception.Source;
       str: ARRAY 256 OF CHAR;
   BEGIN
     Exception.PUSHCONTEXT (e);
     IF (e = NIL) THEN
       Test(i);
     ELSE
       IF (e = src) THEN (* identify the exception source *) 
         IF (Exception.CurrentNumber(e) = zeroException) THEN
           Exception.GetMessage(str);
           Out.String ("Caught exception: "); Out.String(str); Out.Ln;
           Exception.ACKNOWLEDGE
         ELSIF (Exception.CurrentNumber(e) = negativeException) THEN
           Exception.GetMessage(str);
           Out.String ("Caught exception: "); Out.String(str); Out.Ln;
           Exception.ACKNOWLEDGE
         END;
       END;  (* Note: No ELSE part; *)
     END;    (* all other exceptions are re-raised. *)
     Exception.POPCONTEXT;
   END p;

BEGIN
  Exception.AllocateSource (src);
  p(-4);
  p(0);
  p(3); 
END MultiExcept.

Exception numbers genericException, zeroException, and negativeException are defined for src. In procedure p, two of these exceptions are handled, and all other exceptions, including genericException, are simply re-raised. The output of this program looks like

Testing value=-4
Caught exception: [MultiExcept] Value less than zero
Testing value=0
Caught exception: [MultiExcept] Value is zero
Testing value=3
##
## Unhandled exception (#1):
## [MultiExcept] An exception is raised
##

Assertions and Exceptions

The previous two examples are somewhat contrived; you probably wouldn't use exceptions quite that way. Those examples were meant to show how the exception mechanisms work, not necessarily how you would use them in a real situation. So for this next set of examples, let us look at a more practical problem. Consider the following module, which performs a typical programming task: reading from one file, processing the information, and writing the result out to another file. Note that, in this version, no error checking is done.

MODULE FileFilter;

IMPORT Files, TextRider;

  PROCEDURE Process(inFileName:  ARRAY OF CHAR; 
                    outFileName: ARRAY OF CHAR);
    VAR r: TextRider.Reader;
        w: TextRider.Writer;
        fin, fout: Files.File;
        res: INTEGER;
  BEGIN
    fin := Files.Old(inFileName, {Files.read}, res);
    r := TextRider.ConnectReader(fin); 

    fout := Files.New(outFileName, {Files.write}, res);
    w := TextRider.ConnectWriter(fout); 

    (* Process the files... *)
    
    fin.Close; 
    fout.Close;
  END Process;
  
BEGIN
  Process("in.txt", "out.txt");
END FileFilter.

There are a number of places where things might go wrong. For instance, suppose `in.txt' does not exist; running the program would result in the following output:

##
## Unhandled exception (#1) in module TextRider at pos 45930:
## Dereference of NIL
##

Please note: The exception is only raised if `TextRider' was compiled with run-time checks enabled; they are disabled by default. In general, it is not a good idea to assume that library modules raise "proper" exceptions when they are fed illegal values. For instance, nstead of a deref-of-nil exception, they might cause the OS to signal a SIGSEGV (or something similar). Some modules (everything implemented in C) cannot be forced to handle run-time checks gracefully at all.

This exception occurs because Files.Old failed and returned a value of NIL, and that value was passed to ConnectReader. This situation should be checked for; Oberon-2 provides a predefined procedure ASSERT that could be used in this situation. The following version adds error checking to the program:

  PROCEDURE Process(inFileName:  ARRAY OF CHAR; 
                    outFileName: ARRAY OF CHAR);
    VAR r: TextRider.Reader;
        w: TextRider.Writer;
        fin, fout: Files.File;
        res: INTEGER;
  BEGIN
    fin := Files.Old(inFileName, {Files.read}, res);
    ASSERT(res = Files.done);
    
    r := TextRider.ConnectReader(fin); 
    ASSERT(r # NIL);

    fout := Files.New(outFileName, {Files.write}, res);
    ASSERT(res = Files.done);

    w := TextRider.ConnectWriter(fout); 
    ASSERT(w # NIL);

    (* Process the files... *)
    
    IF fin # NIL THEN fin.Close END; 
    IF fout # NIL THEN fout.Close END;
  END Process;

Running this program under the same conditions (i.e., `in.txt' does not exist) produces the following result:

##
## Unhandled exception (#1) in module FileFilter2 at pos 299:
## Assertion failed
##

This is slightly better than the first version; at least the unhandled exception message now shows the relative location of the exception in the source text. But, it would be even better, especially if this kind of file processing were done from an interactive program, if there were a way to recover from this situation. The next version shows how failed assertions can be caught:

  PROCEDURE Process(inFileName:  ARRAY OF CHAR; 
                    outFileName: ARRAY OF CHAR);
    CONST
        finError = 1; rError = 2; foutError = 3; wError = 4;
    VAR r: TextRider.Reader;
        w: TextRider.Writer;
        fin, fout: Files.File;
        res: INTEGER;
        e: Exception.Source;
  BEGIN
    fin := NIL; fout := NIL;
    Exception.PUSHCONTEXT (e);
    IF (e = NIL) THEN    
      fin := Files.Old(inFileName, {Files.read}, res);
      ASSERT(res = Files.done, finError);
    
      r := TextRider.ConnectReader(fin); 
      ASSERT(r # NIL, rError);

      fout := Files.New(outFileName, {Files.write}, res);
      ASSERT(res = Files.done, foutError);

      w := TextRider.ConnectWriter(fout); 
      ASSERT(w # NIL, wError);

    (* Process the files... *)
    ELSE
      IF e = Exception.assert THEN
        CASE Exception.CurrentNumber(e) OF
          finError: 
            (* ... *)
            Exception.ACKNOWLEDGE
        | rError: 
            (* ... *)
            Exception.ACKNOWLEDGE
        | foutError: 
            (* ... *)
            Exception.ACKNOWLEDGE
        | wError:
            (* ... *)
            Exception.ACKNOWLEDGE
        ELSE  (* exception is not acknowledged otherwise. *)
        END;        
      END;  (* all other exceptions are re-raised. *)
    END;
    Exception.POPCONTEXT;
    
    IF fin # NIL THEN fin.Close END; 
    IF fout # NIL THEN fout.Close END;
  END Process;

When an exception occurs (indicated by a failed assertion) special processing can be done based on the exception number: finError, rError, foutError, or wError. Note that the calls to Close occur outside of the exception context, so that the files can still be closed when an exception occurs (as long as they are not NIL). An else clause is included as part of the CASE to prevent a misleading noMatchingLabel exception.

This example shows how the exception mechanism can be used in conjunction with ASSERT. If more fine-grained control is required, an exception source can be defined and calls to RAISE used in place of ASSERT.

Module Signal

The module `Signal' provides the means to connect signals to the exception handling mechanism defined by module `Exception'. A signal reports the occurrence of an exceptional event to an executing program; that is, a signal is an externally generated software interrupt. The following are examples of events that can generate a signal: Program or operation errors, or external events such as alarms or job control events; one process can also send a signal to another process.

Full coverage of the use of signals is beyond the scope of this manual. To learn more about signals, most books on the Unix operating system have sections describing signals. Otherwise, The GNU C Library Reference Manual (available to download in various formats--say, as "info" files--or in print with ISBN 1-882114-53-1) is an excellent source of information on the use of signals.

Signals can also be set up to be handled independently of exceptions. The procedure SetHandler is used to install a handler procedure for when a specific signal occurs. The procedure Raise can be used to raise a particular signal, which is then handled in the same way as system generated signals (i.e., either an exception is raised or the signal's action is activated).

A signal's action can be set to handlerException, which means that an occurance of the given signal raises an exception. Unless specified otherwise, signals trigger their respective default actions.

A generic handler, which could be used to handle different kinds of signals, might look something like this:

PROCEDURE GenericHandler(sigNum: Signal.SigNumber);
  VAR dummy: Signal.SigHandler;
BEGIN
  Err.String("Handling signal="); Err.LongInt(sigNum, 0); Err.Ln;
  
  dummy := Signal.SetHandler(sigNum, GenericHandler);
    (* sigNum's action might be reset by the system to  
     * `handlerDefault', so we explicitly reset our own 
     *  signal action here.  See note below.  *)

  IF sigNum = Signal.Map(Signal.sigint) THEN
    (* Actions applicable to `sigint'. *)
  ELSIF sigNum = Signal.Map(Signal.sigsegv) THEN
    (* Actions applicable to `sigsegv'.  
     * HALT() would probably be good here. *)
  ELSIF sigNum = ...
    ...
  ELSE
    (* For other signals that have this procedure as their action,
     * but are not handled by an ELSIF branch, reset the action
     * as default, and raise it again. *) 
    dummy := Signal.SetHandler(sigNum, Signal.handlerDefault);
    Signal.Raise(sigNum)
  END;
END GenericHandler;

Please note: Resetting the signal's action to the current handler is only necessary for System V systems. For BSD or POSIX, the current signal handler is kept. Also note that with System V there is a race condition: There is no guarantee that the signal isn't raised again after the handler is cleared by the system, but before the called handler has reinstalled itself.

This handler would be installed for various signals (probably in a module's BEGIN block) as follows:

oldHandler := Signal.SetHandler(Signal.Map(Signal.sigint), 
                                GenericHandler);
oldHandler := Signal.SetHandler(Signal.Map(Signal.sigsegv), 
                                GenericHandler);
...

Signal Facilities

Constants

The following constants define symbolic names for signals. Because signal numbers vary from system to system, the numbers below cannot be passed directly to a system call; a number has to be mapped to the system's numbering scheme first by the function Map. Multiple names can be mapped to a single signal number; for example on most systems, the signals sigiot and sigabrt are aliases. Not all signals are available on all systems. If a signal is not defined for the current system, Map will return the value unknownSignal.

Program error signals:

Constant: sigfpe
Fatal arithmetic error.

Constant: sigill
Illegal instruction.

Constant: sigsegv
Segmentation violation.

Constant: sigbus
Bus error.

Constant: sigabrt
Program abortion.

Constant: sigiot
I/O trap, usually just another name for sigabrt.

Constant: sigtrap
Program breakpoint.

Constant: sigemt
Emulator trap.

Constant: sigsys
Bad system call.

Constant: sigstkflt
Stack fault.

Termination signals:

Constant: sigterm
Generic way to cause program termination.

Constant: sigint
Program interrupt (usually caused by C-c).

Constant: sigquit
Program interrupt (usually caused by C-\).

Constant: sigkill
Immediate program termination.

Constant: sighup
"Hang-up" signal.

Alarm signals:

Constant: sigalrm
Typically indicates expiration of a timer.

Constant: sigvtalrm
Virtual timerO.

Constant: sigio
File descriptor is ready to perform input or output.

Constant: sigurg
"Urgent" or out-of-band data arrived at socket.

Constant: sigpoll
System V signal name, similar to sigio.

Job control signals:

Constant: sigchld
Child process terminates or stops.

Constant: sigcld
Obsolete name for sigchld.

Constant: sigcont
Continue process.

Constant: sigstop
Stop process.

Constant: sigtstp
Interactive stop signal.

Constant: sigttin
Background process reads from terminal.

Constant: sigttou
Background process writes to terminal.

Operation error signals:

Constant: sigpipe
Broken pipe.

Constant: siglost
Resource lost.

Constant: sigxcpu
CPU time limit exceeded.

Constant: sigxfsz
File size limit exceeded.

Constant: sigpwr
Power state indication.

Miscellaneous signals:

Constant: sigusr1
User defined signal 1.

Constant: sigusr2
User defined signal 2.

Constant: sigwinch
Window size change.

Constant: siginfo
Information request.

Constant: sigdil
???

Other:

Constant: unknownSignal
Result of Map for invalid signal names.

Types

The following types are declared in module `Signal':

Data type: SigNumber
A system dependant integer type used to represent signal numbers.

Procedure type: SigHandler = PROCEDURE (signum: SigNumber)
The procedure type used as the signature of a signal handler, which is installed with the procedure SetHandler. A procedure variable of this type is activated upon the arrival of the signal, and the system dependent signal number is passed to the signum parameter.

Variables

The following variables are defined for use with facilities provided in module `Signal':

Read-only Variable: handlerDefault: SigHandler
Setting a signal's action to this handler specifies that the signal should invoke the default action when raised.

Read-only Variable: handlerIgnore: SigHandler
Setting a signal's action to this handler specifies that the signal should be ignored. Note that, the signals sigkill and sigstop cannot be ignored.

Read-only Variable: handlerError: SigHandler
The value of this variable is returned from from SetHandler to indicate an error.

Read-only Variable: handlerException: SigHandler
Setting a signal's action to this handler specifies that the signal should raise an exception. Upon arrival of the signal signum, the handler will install itself again as action for the given signal number, and then activate Exception.RAISE with Signal.exception as source, the message string `[Signal] Caught signal number <signum>', and the system dependent value of signum as exception number.

If the exception isn't handled by the user, the default exception handler will print the usual message to stderr, reset the signal's handler to the default action, and raise the signal again. If the latter doesn't terminate the program, the default handler will terminate the program like a failed run-time check.

Read-only Variable: exception: Exception.Source
This is used as the exception source for signals that are set to raise an exception via handlerException.

Procedures

The following procedures are provided for setting signal handlers and raising signals:

Function: Map (signum: SigNumber): SigNumber
Maps a signal name from the above list onto the system dependent signal number associated with that name. If the signal isn't defined for the system, unknownSignal is returned. More than one signal may be mapped onto the same number.

Function: SetHandler (signum: SigNumber; action: SigHandler): SigHandler
Installs the signal handler action for the signal number signum. The signal number must be mapped to the system's number scheme first; that is, the names defined above can't be used directly, but have to be passed through Map first. The behaviour of this procedure is undefined if the given number does not correspond to a legal signal.

If the signal can be handled, the next occurence of the given signal will activate the procedure in action, passing the system specific signal number via the procedure's signum parameter. Calling this procedure with action = NIL is equivalent to calling it with action = handlerDefault. The system might, as in the case of System V systems, reset the signal handler to the default action before calling action. On other systems, notably POSIX and BSD, the current action is kept. So, it is generally a good idea to explicitly set the signal handler again as part of action.

On success, the SetHandler function returns the action that was previously in effect for the specified signum. This value can be saved and later restored by calling SetHandler again.

On failure, the value handlerError is returned. Possible errors are an invalid signum, or an attempt to ignore or provide a handler for the signals sigkill or sigstop.

Please note: In oo2c, this function is just a wrapper around the C function signal. For more details, check the specification of this function (e.g., its man page or the relevant chapter of libc info).

Procedure: Raise (signum: SigNumber)
Raises a signal associated with signum for the current process. See SetHandler for the restrictions regarding the values of signum.

Initial actions for all signals within a program are usually either handlerDefault or handlerIgnore. A check should be done when establishing new signal handlers to be sure that the original action was not handlerIgnore.

Example:

MODULE SigTest;

IMPORT Signal, ...;

VAR
  oldHandler: Signal.SigHandler;
  
  PROCEDURE CleanUp(sigNum: Signal.SigNumber);
  (* Set the handler back to default, clean up (e.g., close 
   * files), and then resend the signal.  *)
  BEGIN
    oldHandler := Signal.SetHandler(sigNum, Signal.handlerDefault);
    (* Do the clean up stuff. *)
    Signal.Raise(sigNum);
  END CleanUp;

BEGIN
  oldHandler := Signal.SetHandler(Signal.Map(Signal.sigint), CleanUp);

  (* Check to make sure the signal was not set to be ignored.  *)
  IF oldHandler = Signal.handlerIgnore THEN
    oldHandler := Signal.SetHandler(Signal.Map(Signal.sigint), 
                                    Signal.handlerIgnore);
  END;  

  ...   (* Other program termination signals, like sighup and 
         * sigterm, might also be set to do the CleanUp action.  
         *)
END SigTest.

Certain signals might not occur when normal run-time checks are enabled. For example, index checks are normally done when accessing array elements, so a segmentation violation should never occur because of accessing out-of-bounds array elements. However, if these run-time checks are disabled, appropriate signal handlers can be set up to capture error conditions.

Example:

<* IndexCheck := FALSE *>
...

PROCEDURE PrintIt(sigNum: Signal.SigNumber);
BEGIN
  oldHandler := Signal.SetHandler(sigNum, PrintIt);
  Err.String("Resetting program and exiting...");  Err.Ln;
  (* Cleanup stuff *)
  HALT(1);
END PrintIt;

...

oldHandler := Signal.SetHandler(Signal.Map(Signal.sigsegv), PrintIt);

It is often very difficult to recover from serious events that trigger signals. This is why the exception handling module `Exception' has been tied into `Signal'; a program can be set up to handle the error via an exception handler.

Example:

MODULE SigExcept;
<* IndexCheck := FALSE *>

IMPORT Signal, Exception, ...;

VAR
  oldHandler: Signal.SigHandler;
  
  PROCEDURE RunIt;
    VAR 
        ...
        e: Exception.Source;
  BEGIN
    Exception.PUSHCONTEXT (e);
    IF (e = NIL) THEN    
      ...  (* Normal excecution part *)
    ELSE
      IF e = Signal.exception THEN
        IF Exception.CurrentNumber(e) = Signal.Map(Signal.sigsegv) THEN
            ...
            Exception.ACKNOWLEDGE
        ELSE
        END
      END
    END
    Exception.POPCONTEXT;
  END RunIt;

BEGIN
  oldHandler := Signal.SetHandler(Signal.Map(Signal.sigsegv), 
                                  Signal.handlerException);
  ...
  RunIt
END SigExcept.


Go to the first, previous, next, last section, table of contents. OOCref_12.html100664 1750 1750 2454 6753666121 11235 0ustar sagsag The OOC Reference Manual - Localization

Go to the first, previous, next, last section, table of contents.


Localization

Module Locales

Module LocStrings

Module LocNumConv

Module LocNumStr

Module LocTextRider

Module LocText


Go to the first, previous, next, last section, table of contents. OOCref_13.html100664 1750 1750 1550 6753666131 11233 0ustar sagsag The OOC Reference Manual - Part II: The OOC Compiler

Go to the first, previous, next, last section, table of contents.


Part II: The OOC Compiler


Go to the first, previous, next, last section, table of contents. OOCref_14.html100664 1750 1750 127374 6753666170 11314 0ustar sagsag The OOC Reference Manual - Language

Go to the first, previous, next, last section, table of contents.


Language

The Oberon-2 language as implemented by OOC is based on the paper

The Programming Language Oberon-2
H. Moessenboeck, N. Wirth
Institut fuer Computersysteme, ETH Zurich, March 1995
ftp://ftp.inf.ethz.ch/pub/Oberon/Docu/Oberon2.Report.ps.gz

This paper describes the language in just 16 pages. Additional appendices cover implementation details of Oberon-2 and its implementation as part of the Oberon operating system for the Ceres workstation. These appendices are system dependent, and are only partially implemented by OOC.

This chapter is intended as a supplement to the language report. Together with the report, it describes the programming language accepted by OOC compilers. It specifies details left open by the report and those features of OOC that go beyond the scope of the language report.

Specifications

Length limits of Identifiers and Strings

OOC does not impose a limit on the length of identifiers or string literals. The Oakwood guidelines suggest that a compiler should support at least 23 significant characters for identifiers, but there is no such suggestion for strings. The pragma variables `IdentLength' and `StringLength' control the length of identifiers and string literals accepted by the compiler (see section Option and Pragma Variables). Note that other compilers may impose arbitrary limits on identifiers and strings.

Basic Types

The basic types of OOC are defined as follows:

=============================================================
Name       Size in Bytes             MIN(T)            MAX(T)
-------------------------------------------------------------
BOOLEAN         1                      n/a                n/a
CHAR            1                       0X               0FFX
SHORTINT        1                     -128                127
INTEGER         2                   -32768              32767
LONGINT         4              -2147483648         2147483647
HUGEINT         8                    -2^63             2^63-1
REAL            4          -3.40282347E+38     3.40282347E+38
LONGREAL        8         -1.79769313D+308    1.79769313D+308
SET             4                        0                 31
-------------------------------------------------------------

The integer type HUGEINT is required to be implemented only by compilers for 64-bit target architectures; that is, for targets whose address size is 8 bytes. HUGEINT is optional for all other implementations of OOC.

The size and extreme values of the real numeric types depend on the floating point representation used on the target system. For the vast majority of modern systems, this will be based on the IEEE standard 754-1985. In this case, REAL is encoded as IEEE single precision number in 4 bytes, and LONGREAL as double precision number in 8 bytes. The numbers given in the table above assume IEEE representation for real numeric types. Note that the extreme values as shown for LONGREAL are truncated; for the exact absolute value, refer to the constant LowLReal.large.

Empty String

The string constant `""' and the character constant `0X' are interchangeable. This implies that a string constant cannot contain the character `0X'.

Array Types of Length Zero

Arrays of length zero are permitted, but the compiler will emit a warning if it detects such an array during compilation (unless warnings are disabled).

So, a declaration of the form TYPE T=ARRAY 0 OF CHAR is allowed, and variables of type T can be defined, but any attempt to access elements in the array will cause an `index out of range' error either during compilation (if detectable) or at run-time. Similarly, open array instances of length zero can be created (by passing a length of zero to NEW), but, of course, no elements can be accessed.

Note that, in any case, specifying a negative length will trigger an error either during compilation or at program run-time.

Extension Limit of Record Types

OOC does not impose any limit on the number of levels a record type may be extended. The Oakwood guidelines suggest that the number of levels of type extension should not be less than 8 levels, including the base type.

Ordering Restrictions for Type-bound Procedures

If an extended record type redefines a type-bound procedure, then the redefinition must appear after the base declaration in the source text. The following example violates this rule:

TYPE
  R0 = RECORD END;
  R1 = RECORD (R0) END;

PROCEDURE (VAR r: R1) P; END P;
PROCEDURE (VAR r: R0) P; END P;

In order to make this example legal, the order of declaration of the two procedures must be reversed. Note that this problem can only arise if the record types, and their corresponding type-bound procedures, are defined in the same module. This restriction is inherently present in many Oberon-2 compilers, although it is not stated in the language report.

Large Hexadecimal Constants

Hexadecimal constants can be specified over the full unsigned range of the largest integer type. A constant value greater than the maximum value of the largest signed integer type is mapped onto a negative value by interpreting it as an unsigned representation of an integer number.

For example, if the compiler does not support the HUGEINT type, hexadecimal constants in the range `08000000H..0FFFFFFFFH' are mapped into the range `MIN(LONGINT)..-1' by matching the bit pattern of the constant onto the negative value. However, if HUGEINT constants are supported by the compiler, these values are mapped into the positive range `2^31..2^32-1'. This means that the interpretation of such constants is compiler-dependent. Without special precautions, modules using this constant representation are not portable to systems that support additional, larger integer types.

Note that the extended mapping of constant literals applies only to values given in hexadecimal format; a decimal integer constant will cause an overflow if it exceeds the maximum integer value. Special handling of hexadecimal constants is not part of the language report, but is implemented in many Oberon-2 compilers, presumably to ease the implementation of low-level modules that need a convenient way to define bit pattern values of word size.

Specification of DIV and MOD

The results of integer division and modulus are defined as

x=(x DIV y)*y + x MOD y

where `0 <= x MOD y < y' or `y < x MOD y <= 0'.

Example:

=================================
  x    y       x DIV y   x MOD y
---------------------------------
  5    3          1         2   
  5   -3         -2        -1   
 -5    3         -2         1   
 -5   -3          1        -2   
---------------------------------

Note that with this definition the equation `x DIV y = ENTIER (x/y)' holds.

Predefined Procedure NEW

There are two points of clarification regarding OOC's implementation of NEW:

Predefined Procedures HALT and ASSERT

The statements `HALT(n)' and `ASSERT(FALSE, n)' are equivalent to the C function invocation `exit(n)' unless the raised exception is caught explicitly. The value of `n' must be from the range `[0..255]'. The statement `ASSERT(FALSE)' is equivalent to `ASSERT(FALSE, 1)'.

Predefined Procedure SYSTEM.MOVE

There are several points to consider when using SYSTEM.MOVE:

Also note that, due to the way OOC represents source code internally, SYSTEM.MOVE should not be applied to local scalar variables of a procedure. OOC will not recognize such a memory-level copy as a defining instruction of a variable. The generated code would be valid, but it is possible that a warning will be emitted, stating that the variable is not defined before its use.

Non-conformant Mode

OOC has two, slightly different, modes of operation: conformant mode and non-conformant mode. Conformant mode emulates the behaviour of ETH compilers, whereas non-conformant mode is generally closer to the language report. The mode in use is determined by the boolean pragma variable `ConformantMode' (see section Option and Pragma Variables); non-conformant mode is the default setting. The differences between both modes are described in the following sections.

Implementation of WITH

In older ETH compilers, the implementation of the WITH statement is faulty. If a guarded variable is a formal parameter, the formal parameter type is actually modified by the WITH statement; that is, the interface of the procedure is changed for any calls to it within the scope of the regional type guard.

Example:

MODULE TestWith;

TYPE
  R0 = RECORD END;       P0 = POINTER TO R0;  
  R1 = RECORD (R0) END;  P1 = POINTER TO R1;
  
PROCEDURE Proc0 (VAR r: R0);
  VAR r0: R0;
  BEGIN
    WITH r: R1 DO  Proc0 (r0)  END
  END Proc0;

PROCEDURE Proc1 (p: P0);
  VAR p0: P0;
  BEGIN
    WITH p: P1 DO  Proc1 (p0)  END
  END Proc1;

END TestWith.

In conformant mode, the compiler warns that the formal parameter type is modified by a WITH statement, and two errors are issued: the argument of the first procedure call `Proc0 (r0)' is not compatible to a formal parameter of type `R1', and in the second call `Proc1 (p0)', the argument is not assignment compatible to type `P1'. This example module is legal in non-conformant mode.

Comparing Procedure Values

The language report specifies that a variable of pointer type cannot be compared with a procedure constant. Appendix A states that, for an expression `p0 = p1' where `p0' and `p1' are procedure values, both operands have to have the same type. However, the type rules imply that the type of any one procedure is distinct from all other types.

Example:

MODULE ProcCmp;

VAR p0, p1: PROCEDURE; bool: BOOLEAN;
  
PROCEDURE P; END P;

BEGIN
  p0 := P;
  bool := (p0 = P)
END ProcCmp.

The assignment to `p0' is legal, but the comparison between the procedure variable and the procedure value is not. Oberon-2 relaxes the type rules for assignments involving procedure types by requiring only structural equivalence rather than name equivalence. It would be natural to extend this to comparisons of procedure values as well. Because omitting this extension is most likely an oversight by the language designers, OOC implements the less restrictive rule. This means, that a comparison like in the example is legal in non-conformant mode, but will be marked as faulty in conformant mode.

Specification of INC and DEC

The report defines `INC(v, n)' to be functionally equivalent to `v := v + n', and gives a similar definition for `DEC(v, n)'. It does not specify any type rules for these predefined procedures. ETH compilers implement the procedures in such a way that `INC(v, n)' is legal, if

Because this implementation is questionable when compared with the language report, OOC applies a less restrictive rule in non-conformant mode; `INC(v, n)' and `DEC(v, n)' are valid if the type of `n' is included in that of `v', regardless of `n' being a constant value or not. In conformant mode, the more restrictive interpretation of the ETH compilers is applied.

Redefinition of Type-bound Procedures

The language report specifies that, when redefining a type-bound procedure, the formal parameters of the original procedure and the redefinition must match. OOC enfores this rule in conformant mode. However, in non-conformant mode, the compiler applies a less restrictive rule that was first introduced by Oberon/F: If P' is a redefinition of the type-bound procedure P, the formal parameters of P and P' must match with the exception of the function result of P', which may be an extension of the result of P.

Example:

MODULE Redef;

TYPE
  R0 = RECORD END;      P0 = POINTER TO R0;
  R1 = RECORD (R0) END; P1 = POINTER TO R1;

PROCEDURE (p: P0) Copy(): P0; ... END Copy;
PROCEDURE (p: P1) Copy(): P1; ... END Copy;

END Redef.

In conformant mode, the compiler will complain that the formal parameters of the second procedure do not match the ones of the first. Conformant mode requires the result type of the second procedure to be `P0', whereas non-conformant mode allows the extended type `P1' as valid.

By allowing the less restrictive rule for return types, it is possible to design class hierachies distributed over several modules where an extended class can be used without direct knowledge of the base class. An example of this is found in the module `Files': If adhering to the report, the type-bound procedures `NewReader' and `NewWriter' would need to return types imported from module `Channel'. Any module using these procedures would also need to import `Channel' to define variables to hold the result of these procedures. With the relaxed redefinition rule, the procedures can return types from module `Files', and can therefore be used separately from the base module `Channel'.

Additional Data Types

OOC provides several data types beyond the standard types of Oberon-2. They are introduced to add Unicode support and to ease interfacing to foreign code and migration to 64-bit target architectures.

LONGCHAR and Long Strings

In order to support the Unicode character set, OOC adds the type LONGCHAR and introduces the concept of long strings. The character types are now CHAR and LONGCHAR, and string constants can be either String or LongString.

The basic character types are as follows:

CHAR
the characters of the ISO-Latin-1 (i.e., ISO-8859-1) character set (0X..0FFX)
LONGCHAR
the characters of the Unicode character set (0X..0FFFFX)

The character type LONGCHAR includes the values of type CHAR according to the following hierarchy:

  LONGCHAR >= CHAR

Character constants are denoted by the ordinal number of the character in hexadecimal notation followed by the letter `X'. The type of a character constant is the minimal type to which the constant value belongs. (i.e., If the constant value is in the range `0X..0FFX', its type is CHAR; otherwise, it is LONGCHAR.)

String constants are sequences of characters enclosed in single (') or double (") quote marks; strings can also be represented using the string concatenation operator `+' and a combination of characters or string constants. String constants that consist solely of characters in the range `0X..0FFX' are of type String, all others are of type LongString. For example, the following is of type LongString:

Example:

  CONST
     aLongString = 0C0ACX + 0C6A9X + " " + 0C2E4X + 0D328X; 

The string type LongString includes the values of type String according to the following hierarchy:

    LongString => String

This means that a string constant composed of CHAR range values can be used in place of a constant string composed of LONGCHAR range values. The expected implicit type conversion rules (similar to integer types) apply to character values and string constants, too; that is, it is possible to compare a LongString with a String, or assign a String to an ARRAY OF LONGCHAR variable. (CHAR and Strings are promoted to LONGCHAR and LongString when necessary.)

The following predeclared function procedures support these additional operations:

Name        Argument type        Result type  Function
CAP(x)      CHAR                 CHAR         if x is a letter,
            LONGCHAR             LONGCHAR     corresponding capital
                                              letter; otherwise, 
                                              identity (see note below).

LONG(x)     CHAR                 LONGCHAR     identity 
            String               LongString   identity 

LONGCHR(x)  integer type         LONGCHAR     long character with
                                              ordinal value x

ORD(x)      LONGCHAR             LONGINT      ordinal value of x

SHORT(x)    LONGCHAR             CHAR         projection 
            LongString           String       projection 

Please note:

CAP(x) maps lower case letters in the ISO-Latin-1 range to the capital counterparts and produces identity for all other characters (meaning that most Unicode characters are mapped to identity). There are two exceptions: `U+00DF' (LATIN SMALL LETTER SHARP S) whose uppercase version is the two letter sequence `SS', and `U+00FF' (LATIN SMALL LETTER Y WITH DIARESIS) whose capital version is outside the ISO-Latin-1 range (it has the code `U+0178'); these two characers are also mapped onto themselves.

SHORT(x), where x is of type LONGCHAR, can result in overflow, which triggers a compilation or run-time error. The result of an operation that causes an overflow, but is not detected as such, is undefined.

The predeclared procedure COPY(x, v) also supports LongStrings:

 Name            Argument type                 Function
 COPY(x, v)      x: character array, string    v := x
                 v: character array

Note that, COPY(x, v) is invalid if x is of type ARRAY OF CHAR, and v is of type LongString or ARRAY OF LONGCHAR.

Assignment Compatibility

Characters, string constants, and arrays of characters are assignment compatible as follows:

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

  1. Tv and Te are character types and Tv includes Te;
  2. Tv is an ARRAY n OF LONGCHAR, Te is a string constant with m characters, and m < n;
  3. Tv is an ARRAY n OF CHAR, Te is a String with m characters, and m < n;

Array Compatibility

String constants and arrays of characters are array compatible as follows:

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

  1. f is a value parameter of type ARRAY OF CHAR and a is a String, or
  2. f is a value parameter of type ARRAY OF LONGCHAR and a is a string constant.

Expression Compatibility

Character and string types are expression compatible as follows:

Operator        First operand   Second operand  Result type
= # < <= > >=   character type  character type  BOOLEAN
                string type     string type     BOOLEAN

Please note: Implicit type conversion rules apply to both character values and constant strings. They do not apply to character arrays.

Library support for LONGCHAR

The following modules provide support for LONGCHAR and LongString:

`BinaryRider'
Reading and writing of LONGCHAR and LongString as binary data.
`Calendar'
Procedures TimeToLStr and LStrToTime.
`LongStrings'
Similar to module `Strings'.
`LongRider [ABSTRACT]'
Abstract text mapper classes for LONGCHAR and LongString.
`UnicodeRider'
Concrete text mapper classes giving Unicode support.

Additional mapper classes, which are extended from TextRider and UnicodeRider, can be added to handle additional 8- and 16-bit encodings. These classes are used to map from another encoding (e.g., "KSC5601", a standard Korean character encoding) to Unicode or Latin-1 (as appropriate), and vice versa. Here "encoding" means both the encoding of n bit values in byte streams and translation of character codes between the two standards. (See section Standard Mappers.)

Additional Set Types

In addition to the standard set type SET, module SYSTEM defines several other set types: SET8, SET16, SET32, and--optionally---SET64. The set type SET64 is required to be implemented only by compilers for 64-bit target architectures. Note that the type SET32 is an alias for the standard type SET.

=============================================================
Name       Size in Bytes             MIN(T)            MAX(T)
-------------------------------------------------------------
SET8            1                        0                  7
SET16           2                        0                 15
SET32           4                        0                 31
SET64           8                        0                 63
-------------------------------------------------------------

To assign a value to a variable of one of these set types, prefix the set constructor with the type name.

Example:

set8  := SYSTEM.SET8{0..3};
set16 := SYSTEM.SET16{0, 8..x}; 

Operations for the additional set types are defined just like their counterparts for SET. However, both sides of a dyadic operator must be of the same type. That is, set operations such as intersection, union, and so on, are only permitted if both the left and right side are of the same set type.

The predefined procedures EXCL, INCL, and the membership test IN are applicable to all set types. The predefined function LONG converts a set value to the identic value of the next larger set type (if available), whereas SHORT converts to the next smaller set (if available). SHORT will remove all elements that are not included in the smaller type.

Variables of type SET8 can be assigned to variables of type BYTE. If a formal variable parameter is of type BYTE, then the corresponding actual parameter can be of type SET8.

Data Types for 64-bit Machines

The Oberon-2 language specification does not give fixed values for the size of its basic data types. Any actual language implementation, in the form of a compiler, has to define the size of its types as fixed values. Most modern Oberon-2 compilers use the type sizes listed in the table in section Specifications. However, problems arise when changing to a 64-bit target system.

Unfortunately, the pseudo module SYSTEM as defined in the language report uses an integer type, LONGINT, to represent memory addresses. For a 64-bit machine a 64-bit integer type is required to represent addresses. Defining LONGINT to be a 8 byte type on those machines introduces a number of problems:

Therefore, OOC introduces a new integer type called HUGEINT, and leaves existing integer types unchanged. Values of type HUGEINT are stored in 8 bytes, with a minimum value of `-2^63' and a maximum of `2^63-1'. This extends the integer type inclusion hierachy at its upper end. All integer operations also apply to HUGEINT.

The integer type HUGEINT is required to be implemented only by compilers for 64-bit target architectures; that is, for targets whose address size is 8 bytes. HUGEINT is optional for all other implementations of OOC. 64-bit systems are also required to implement the set type SYSTEM.SET64, which is of the same size as HUGEINT.

Address Type

The pseudo module SYSTEM declares the type ADDRESS. On 32-bit systems, it is an alias for LONGINT, and on 64-bit machines, it is an alias for HUGEINT. The following relation holds for all systems:

SIZE(SYSTEM.ADDRESS) = SIZE(POINTER) = SIZE(SYSTEM.PTR).

The predefined function ADR returns a value of type ADDRESS. Likewise, the type of the address arguments of MOVE, GET, PUT, and BIT is ADDRESS. Note that, for 32-bit systems, this corresponds to the language report because ADDRESS is an alias for LONGINT on these systems.

Experimental Language Extensions

Language extensions are implemented by OOC in the framework of system flags (see section System Flags). Instead of extending the syntax of the language Oberon-2, additional flags are defined to specify non-standard attributes of data types and declarations. To enable any OOC specific extensions for a module, the module must be declared with the `OOC_EXTENSIONS' flag:

MODULE Foo [OOC_EXTENSIONS];

To convert a module employing OOC specific extensions to standard Oberon-2, use the command oocn --filter --strip-system-flags (see section Source Code Analysis and Transformation).

Abstract Classes

Please note: This section was contributed by Stewart Greenhill.

Abstract classes are an important technique for separating interfaces from their implementations. Abstract classes allow the methods of a class to be defined without specifying an implementation of those methods. An abstract class can never be instantiated because its behaviour is undefined. Only concrete (non-abstract) extensions of an abstract class can be instantiated; these must define an implementation for each abstract method.

The Oberon-2 language lacks a mechanism for abstract classes, so typically, abstract classes are simulated using concrete types: HALT statements are used in the body of "abstract" methods, so that a run-time exception occurs if the class is accidentally instantiated and an abstract method is called. This is not a safe solution to the problem. To preserve the semantics of abstract classes, it is expected that the compiler will:

  1. Allow the programmer to differentiate between abstract and concrete classes in declarations.
  2. Prohibit the instantiation of abstract classes.
  3. Prohibit the calling of abstract methods.
  4. Ensure that concrete classes implement all the required abstract methods.

This section describes an extension to the OOC compiler that supports these essential features. The extension does not change the Oberon-2 language itself, but instead uses the `ABSTRACT' flag to distinguish abstract classes and methods. Compilers that do not recognise the flag should ignore it and compile the code as normal. Code that compiles correctly using the OOC abstract classes model should work correctly under other Oberon-2 compilers.

The following rules describe the semantics of abstract classes, as implemented by the compiler:

  1. Any record type may be declared with the `ABSTRACT' flag. Such abstract records have the following properties:
  2. A procedure bound to an abstract record may be declared with the `ABSTRACT' flag. The body of such a procedure must be empty and must not contain a BEGIN statement.
  3. When a non-abstract record extends an abstract record, it must implement each abstract method inherited from its base type. The compiler generates an error for each non-implemented abstract procedure.
  4. It is illegal to call an abstract method via a super call.
  5. Any method marked `ABSTRACT' must have an export flag.

These rules ensure that non-implemented methods are never called, which ensures safety of the system. OOC permits classes to be partially abstract, that is, to have a mixture of concrete and abstract methods. OOC also permits concrete classes to have abstract extensions. The following example illustrates some of the features of this mechanism:

MODULE Abstract [OOC_EXTENSIONS];

TYPE
  PtrA = POINTER TO A;
  A* = RECORD [ABSTRACT] END;   (* abstract type *)

  PtrB = POINTER TO B;
  B* = RECORD (A) END;          (* concrete extension of A *)

VAR
  vA: A;                       (* illegal! *)
  pA: PtrA;
  pB: PtrB;

(* abstract definition of F *)
PROCEDURE (VAR v: A) [ABSTRACT] F*;
  END F;

(* implementation of F *)
PROCEDURE (VAR v: B) F*;
  BEGIN
  END F;

BEGIN
  NEW(pA);                      (* illegal! *)
  NEW(pB);
  pB.F;
  pB.F^;                        (* illegal! *)
  pA := pB;
  pA.F;
END Abstract.

Another example of the use of abstract classes is the module `Channel' (see section Module Channel). All record types and most of the methods defined in this module are declared abstract.

Avoiding Local Copies of Value Parameters

When invoking a procedure, local copies are created for all arguments that are passed to value parameters. If the value parameter is a large array or an open array parameter, allocating storage for the variable and creating the copy can be expensive in both stack space and execution time. During compile-time, OOC tries to detect situations where it can avoid the local copy and access the original variable instead. The algorithm used cannot detect all situations where this is possible; it must conservatively choose in favor of a local copy if there is the slightest chance that omitting it would change the semantics of the procedure. This can be overidden by the programmer by setting the flag `NO_COPY' for the value parameter in question. The flag can be applied only to value parameters of structured type.

Example:

MODULE Out [OOC_EXTENSIONS];

PROCEDURE String* (s[NO_COPY]: ARRAY OF CHAR);
  BEGIN
    writer. WriteString (s)
  END String;

END Out.  

Because the procedure `Out.String' is just a wrapper for the channel's `WriteString' function, there is no need to create a local copy of any arguments passed to parameter `s'.

If used without care, the flag `NO_COPY' can create a parameter that is neither variable nor value. It should be applied only in situations where

An example for a situation where `NO_COPY' cannot be used is OOC's implementation of `Strings.Append'. If the parameter `source' would be marked with `NO_COPY', the procedure would break for calls that use the same variable for both `source' and `destination'.

Illegal Operations

During the execution of a program, it is possible for an operation to be performed that is either illegal or that leaves the program in an undefined state. This sort of operation is usually not intended by the programmer, and should therefore be brought to his attention. For this reason, a typical Oberon-2 run-time system provides mechanisms to detect illegal or undefined operations and report them to the user.

For OOC, an invalid operation is signaled by the facilities defined in module Exception (see section Exception Handling). If detected, such an operation will raise an exception of source Exception.runtime with an exception number from the list defined in Exception. If the raised exception is not handled by the program, it will cause the run-time system to emit an appropriate error message and terminate the program.

The following is a list of exception numbers, which indicate run-time errors and are applicable to source Exception.runtime:

`derefOfNIL'
Indicates an attempt to dereference a pointer or procedure variable that holds a value of NIL. Such a dereference can happen as a result of one of the following:
`indexOutOfRange'
The value used in an array designator's index selector is not in the range `[0..len-1]', where `len' denotes the array's length.
`elementOutOfRange'
Triggered if one of the set operations IN, INCL, or EXCL is given an element value that is not a member of the set type being used. Note that an element of the standard set type SET has to be in the range `0..31'.
`realDivByZero'
Signaled when an operation `x / y' is performed when `y' is zero.
`integerDivByZero'
Signaled when an operation `x DIV y' or `x MOD y' is performed when `y' is zero.
`realOverflow'
Raised whenever a real operation produces a value that cannot be represented in the target type format. Please note: It is possible that floating point calculations are performed internally with higher precision than the type of their arguments. This means that the overflow may occur only when attempting to write the result back into a memory using the smaller type of the arguments. Also, as a note of warning, intermediate results of operations may overflow unnoticed as long as the end result can be stored in the required representation.
`integerOverflow'
Signals that an integer operation has produced a result that cannot be represented in the target type format.
`endOfFunction'
Raised when the evaluation of a function procedure reaches the end of the procedure without encountering a RETURN statement.
`noMatchingLabel'
Raised if the selection value of a CASE does not match any label of the listed branches and there is no ELSE part.
`typeGuardFailed'
Raised when a type guard does not hold during evaluation of a designator. This means that the dynamic type of the guarded variable differs from the type it is guarded against. Note that an `derefOfNil' exception is raised if the tested variable is a pointer with a value of NIL.
`typeAssertFailed'
A type assertion is an implicit type guard added for the left side of assignments dealing with record values. It ensures that the dynamic type of the target is equal to its static type. If the types differ, an `typeAssertFailed' exception is raised.
`noValidGuard'
Raised if none of the guards of a WITH statement is valid and there is no ELSE part.
`stackOverflow'
The data of procedure activations is stored in a special memory area called the stack. If too much data is pushed onto the stack, or too many procedures are active at the same time, the stack overflows and program execution cannot continue; this raises an `stackOverflow' exception.
`illegalLength'
Raised if the predefined procedure NEW is invoked for an open array pointer type with a negative value for one of the array's lengths. This run-time check cannot be disabled.
`outOfMemory'
Raised if a call to NEW or SYSTEM.NEW failed because of insufficient memory. NEW guarantees that the pointer variable will refer to a valid heap object after completion; if this fails, an outOfMemory exception is raised. This run-time check cannot be disabled.

During compilation, each run-time check (except the checks performed for NEW) can be enabled or disabled by a pragma variable. If the corresponding pragma variable is set to TRUE, appropriate code is generated to catch the class of errors in question. If it is FALSE, and such an error occurs at run-time, it might go by unnoticed, lead to unexpected program results, or even cause program termination in the form of a core dump.

The performance impact of run-time checks depends mostly on the target system. Testing for an illegal operation might be done efficiently on one target architecture, but be very costly on another. Not all run-time checks are supported by all OOC compilers. For example, oo2c does not support overflow checks for integer or real operations.

A special note should be made about operations on strings. Recall that the Oberon-2 definition of a string is a character array that contains the character 0X as a terminator. Oberon-2 string operations (COPY, `=', `#', `<', etc.) are undefined for unterminated character arrays. Here OOC follows the Oakwood guidelines, and does not provide any checks to guard against such undefined operations. For instance, if the source of a COPY operation is not terminated by a character 0X, the contents of the target array are undefined after completion.


Go to the first, previous, next, last section, table of contents. OOCref_15.html100664 1750 1750 44524 6753666210 11263 0ustar sagsag The OOC Reference Manual - Pragmas

Go to the first, previous, next, last section, table of contents.


Pragmas

A pragma is a directive embedded in the source code of an Oberon-2 module. Although a pragma is not part of a module's declarations or executable code, it influences how the module is translated by the compiler. Pragmas provide mechanisms for conditional compilation of pieces of source code, for embedding code generation directives into a module, and for selection of language features.

Pragmas are not defined as part of the programming language Oberon-2; they are an extension added to OOC. Pragmas are embedded in the source code by special delimiters <* and *>. Like comments, they are ignored by the parser, but they can change variables that control the compiler's behavior and they can "remove" text from a module's source code by excluding a piece of source text from the translation process. Superficially, pragmas resemble preprocessor directives, as known from the programming language C, but they are much more restricted, and they are tightly integrated into the OOC compiler.

Pragma Syntax

A pragma statement is either a variable definition, an assignment, a conditional statement, or a save/restore command.

A pragma sequence consists of zero or more pragma statements, which are separated by semicolons.

A pragma starts with a `<*', followed by a pragma sequence, and ends with a `*>'.

The full syntax for pragmas in EBNF is as follows:

Pragma        = "<*" PragmaSeq "*>".
PragmaSeq     = PragStatement {";" PragStatement}.
PragStatement = [Assignment | Definition | SaveRestore | Condition].

Assignment    = ident ":=" Expr.
Definition    = "DEFINE" ident ":=" Expr.
SaveRestore   = "PUSH" | "POP".

Condition     = IfPart {ElsifPart} [ElsePart] EndIfPart.
IfPart        = "IF" Expr "THEN" PragmaSeq.
ElsifPart     = "ELSIF" Expr "THEN" PragmaSeq.
ElsePart      = "ELSE" PragmaSeq.
EndIfPart     = "END".

Expr          = SimpleExpr [Relation SimpleExpr].
Relation      = "=" | "#" | "<" | "<=" | ">" | ">=".
SimpleExpr    = Term {"OR" term}.
Term          = Factor {"&" Factor}.
Factor        = "TRUE" | "FALSE" | "(" Expr ")" | "~" Factor |
                string | integer | ident.

The symbols `ident', `string', and `integer' are defined like their Oberon-2 counterparts. An underscore is permitted as part of an `ident' in place of a character. No Oberon-2 keyword, nor the pragma keywords TRUE, FALSE, PUSH, POP, or DEFINE can be used as the name of a variable.

Any Oberon-2 string (including the empty string) and all integer numbers (including hexadecimal numbers) are valid values. Character constants (like `20X') are equivalent to string constants of length 1 (or length 0 in the case of `0X'). Hexadecimal constants are interpreted just like Oberon-2 constant literals.

Example:

<* DEFINE CpuType := "AMD" *>

<* IF CpuType="AMD" THEN *>
IMPORT AMDPrimitives;
<* ELSIF CpuType="Motorola" THEN *>
IMPORT MotorolaPrimitives;
<* END *>

Here a variable `CpuType' is introduced and set to the value `"AMD"'. The variable can then be used to switch between two code variants: The first variant is used if `CpuType' is set to `"AMD"', and the other is used if it is set to `"Motorola"'. Neither of the variants is used if `CpuType' has any other value.

Pragma Semantics

A pragma (the entire sequence of characters starting with `<*' and ending with `*>') can end with a pragma statement, or between the parts of a Condition. The parts of a condition, and all other pragma statements, must be textually complete within a single pragma:

<* DEFINE CpuType := "AMD" *>        (* Legal *)
<* DEFINE CpuType := *> <* "AMD" *>  (* Illegal! *)

<* IF b THEN *>                      (* Legal *)
<* IF b *> <* THEN *>                (* Illegal! *)

Also, note that

Conditional Compilation

Conditions are a special type of pragma statement; the parts of a condition can extend over several pragmas. That is, conditions can be, and usually are, interspersed with plain Oberon-2 source text, and potentially additional pragmas as well. This provides for conditional compilation, which allows lines of source text to be skipped or eliminated by the compiler based on the evaluation of a boolean condition.

Pragma conditions assume the various forms of IF statements: they consist of an opening `IfPart', any number of `ElsifParts', an optional `ElsePart', and a terminating `EndIfPart'. Nested condition statements are allowed.

If the `Expr' of the `IfPart' is true, the text that follows is fully interpreted until reaching the next corresponding `ElsifPart', `ElsePart', or `EndIfPart'; in this case, any remaining text (i.e., any ElsifPart and ElsePart clauses) is skipped until encountering the corresponding `EndIfPart'. If the `Expr' of the `IfPart' is false, the text immediately following the `IfPart' is skipped. If the next condition is an `ElsifPart', its `Expr' is tested, and so on. If no condition holds, the text following the `ElsePart' is interpreted.

"Skipping" of text means that no interpretation is done except recognition of comments and condition statements. That is, although the pragma syntax in the skipped text is checked, the meaning of the pragmas is not recognized. This implies that type errors, or references to undefined variables, are ignored in skipped pragmas.

Note that a pragma sequence can appear as part of a condition:

<* IF Cpu = "Intel" THEN
  DEFINE HaveManyRegisters := FALSE;
  DEFINE InsertFunnyRandomBehaviour := TRUE
END *>

The parts of a condition may exist within a single pragma, or may extend across several pragmas. Both of the following are legal:

<* IF b THEN END *>
<* IF b THEN *><* END *>

Boolean Operators and Relations

The Oberon-2 type rules apply to boolean operators and relations. The expressions in an `IfPart' and `ElsifPart' have to be of boolean type.

The boolean operators & and OR are evaluated like their Oberon-2 counterparts: if evaluation of the left side is sufficient to know the result, the right side is not evaluated. Expressions are always checked syntactically, even if they are not evaluated; this works exactly like pragmas that are skipped due to conditional compilation.

Pragma Variables

New pragma variables are defined by the definition statement `DEFINE var := value'. The identifier `var' must not be already known, or an error message is produced. That is, one cannot override existing variables that are predefined by the compiler, or were defined earlier. But once it is defined, the value can be changed with an assignment. The scope of a variable defined in a module extends from the point of its definition to the end of the module.

PUSH and POP

The pragma statements PUSH and POP operate on a stack. PUSH saves the current state of all pragma variables, both predefined and user-defined. POP restores the values of saved variables as set by the corresponding PUSH, and removes the associated states from the stack. Variables introduced after the PUSH operation are not affected by this; a POP does not return variables to an undefined state.

Predefined Pragma Variables

Every implementation of OOC predefines a number of pragma variables. These

The compiler provides safe defaults for all predefined variables. That is, all useful run-time checks are enabled and all compiler specific options are disabled. These values can be redefined in the initialization file, and by command line options. Predefined variables can also be changed through pragma assignments.

Example:

<* IndexCheck := TRUE *>     
  generate code for index check
<* RangeCheck := FALSE *>
  switch off detection of invalid set elements

All run-time checks supported by the particular compiler are enabled by default. The compiler issues a warning when an attempt is made to

The following tables lists the pragma variables that control the generation of run-time checks by the compiler. All variables are of type boolean. Setting such a variable to `TRUE' enables the appropriate run-time check; this means that code is inserted to raise an exception if the tested condition fails. Setting the variable to `FALSE' disables the checks.

`CaseSelectCheck'
Raise an exception if the value of the selection expression of a CASE statement does not match any of the labels and no ELSE part is specified.
`IndexCheck'
Raise an exception if the value of an array index is not in the range `0 <= index < LEN(array)'.
`DerefCheck'
Raise an exception if a pointer of value NIL is dereferenced. Note that applying a type test or type guard to NIL, or an attempt to activate a procedure value of NIL, also triggers this exception.
`FunctResult'
Raise an exception if the end of a function procedure is reached without executing a RETURN statement.
`RealOverflowCheck'
Raise an exception if a real number operation overflows.
`RealDivCheck'
Raise an exception when attempting to divide a real number by zero.
`RangeCheck'
Raise an exception if a set element is outside the range of possible values for the applicable set type. This applies to INCL(), EXCL(), IN, and the set constructor `{a..b}'.
`OverflowCheck'
Raise an exception if the result of an integer operation overflows.
`IntDivCheck'
Raise an exception when attempting to divide an integer number by zero. Note that this applies to both DIV and MOD.
`TypeGuard'
Raise an exception if a type guard fails.
`StackCheck'
Raise an exception on stack overflow. More precisely, if StackCheck = TRUE, stack overflows are detected when entering a procedure body `B'. Note that, even if `B' is compiled with StackCheck = TRUE, procedures called from `B' might still overflow the stack undetected, unless they have also been compiled with this run-time check enabled. On most systems, stack overflows are detected by the operating system without any need for special software stack checks by the program.

The following pragma variables adjust semantical checks and code generation of the compiler:

`ConformantMode'
Selects one of two slightly different language variants. Setting this to `TRUE' enables conformant mode, which tells the compiler to behave like an ETH compiler; modules compiled with conformant mode enabled should generally work with any compiler. Changing the variable to `FALSE' (the default) produces results that more closely match the language report. See section Non-conformant Mode, for reasons why non-conformant mode is considered preferable.
`IdentLength'
An integer value that determines the maximum number of characters allowed in an identifier. Negative values produce warnings (whereas positive values generate errors) when `Length(ident) > ABS(IdentLength)'. The default value is `MIN(LONGINT)' (i.e., no length restriction at all). The Oakwood Guidelines suggest that compilers should support a minimum of 23 significant characters.
`StringLength'
An integer value that sets the maximum number of characters allowed in a literal string. This works like `IdentLength'.
`Assertions'
If set to `FALSE', all ASSERT statements are discarded. The default value is `TRUE'. Caution: Disabling assertions also discards the boolean expression being asserted, including all its side-effects. Therefore, tested expressions in assertions should never produce side-effects.
`Initialize'
If set to `TRUE', variables and memory blocks are automatically initialized to zero. The default is `FALSE'.
`Warnings'
Tells the compiler whether to generate warnings. The default is `FALSE', which disables warning messages.

Pragma variables with the name prefix `COMPILER' identify the compiler in use. Unlike the variables above, changing them has no effect on the compilation process. They should be considered read-only variables, and never be modified by the user.

`COMPILER'
A string describing the compiler or family of compilers. All implementations of OOC define this to `"OOC"'.
`COMPILER_VERSION'
A string containing the compiler version, for example `"1.4.5"'.
`COMPILER_MAJOR'
Major version number of the compiler. That is, the first number from the version string in integer representation.
`COMPILER_MINOR'
Minor version number of the compiler. That is, the second number from the version string in integer representation.

Information about the target system is provided by variables with the name prefix `TARGET'. In this context the term target system refers to the run-time environment for the execution of a compiled program.

`TARGET_OS'
This string describes the target operating system, for example `"Unix"'.
`TARGET_ARCH'
The value of this variable identifiers the target architecture, that is, the CPU family. Examples are `"ix86"', `"PPC"', `"Alpha"', or, for oo2c, `"ANSI-C"'.
`TARGET_ARCH_MINOR'
If the compiler is set to emit code that only runs on a subclass of the general CPU family, this variable names that subset of the family. For example, the `"ix86"' family could be subdivided into `"i386"', `"i486"', and so on. If the generated code works for all members of the target architecture, this variable holds the empty string.
`TARGET_INTEGER'
This is the number of bits in the largest integer type supported for the target. The basic types HUGEINT and SET64 are supported if it is `64' or more.
`TARGET_ADDRESS'
Number of bits used to represent a memory address of the target architecture.
`TARGET_BYTE_ORDER'
This string describes the byte order convention used by the target system. For a little endian target, like `"ix86"', this is `"0123"', for a big endian target, like `"m68k"', it is `"3210"'. If the byte order is not known beforehand, as is the case with oo2c, the variable is set to `"unknown"'.


Go to the first, previous, next, last section, table of contents. OOCref_16.html100664 1750 1750 365551 6753666312 11315 0ustar sagsag The OOC Reference Manual - OO2C

Go to the first, previous, next, last section, table of contents.


OO2C

What is oo2c?

oo2c is the first complete working compiler of the OOC project. Instead of translating Oberon-2 modules to machine code, it generates code for the most portable assembler in existence: ANSI-C. The compiler was initially intended as a prototype backend for OOC, which could then be used to evaluate and debug the frontend and the optimization modules. However, it is now a full-fledged development system, and among other things, it is being used to develop native code OOC backends.

The choice of a high-level language as intermediate code has one distinct advantage: portability. Given a working ANSI-C compiler, oo2c runs on most modern Unix workstations; porting it to other platforms is possible with minimal effort. With oo2c, programs can be developed that run without modification on all major Unix brands. Differences between the systems are masked by the implementation of low-level modules, which take system peculiarities into account.

The special pre-compiler nature of oo2c also has its disadvantages. The user should be aware of these points:

Installing oo2c

Preparing for Installation

oo2c can use two add-on packages to expand its own capabilities: Hans-J. Boehm's conservative garbage collector gc and GNU libtool. The garbage collector extends oo2c's run-time system with the ability to free unused heap objects. With the help of libtool, oo2c can create shared and static libraries from a set of modules.

Although both packages are optional, their use is highly recommended. If either one of these packages is not available, configure will abort with an error. To install oo2c without them, each package must be explicitly disabled by setting `--disable-gc' or `--disable-libs'.

Preparing the garbage collector

If gc is installed as a library on the system, configure detects this and uses it automatically.

Otherwise, get the garbage collector sources from Boehm's server

http://reality.sgi.com/employees/boehm_mti/gc_source/

and unpack the tar file in oo2c's top-level directory.

Check the files `README' and `Makefile' in the newly created subdirectory `gc' in case the gc package needs some special adjustments. When installing oo2c, the garbage collector sources are detected, and are compiled and installed automatically. Please note: The garbage collector subdirectory is not affected by running oo2c's configure script; only the environment variable CC is overridden when calling make.

To install oo2c without a garbage collector, the option `--disable-gc' must be passed to configure. The drawback is, of course, that programs cannot free memory that has been dynamically allocated using NEW. For short running programs, which request only a small amount of memory, this is not a severe problem. However, process size for long running, memory intensive programs can grow without bound until memory resources are exhausted.

During the installation process, a long running, memory intensive program is started: oo2c is used to compile all of its own sources in a single run. The process size of such a bootstrap without garbage collection can grow beyond 100MB. The process might run out of memory, or you might decide to kill it with Ctrl-C because the system thrashes wildly. In this case, simply start make again to finish the job. oo2c detects files that have already been compiled successfully, and does not try to compile them again. This way, oo2c can be installed on any system without garbage collection.

Installing GNU libtool

libtool can be obtained from any GNU server, e.g. ftp://ftp.gnu.org/pub/gnu/. The package's home page is http://www.profitpress.com/libtool/.

Unpack the tar file and follow the directions in the file `INSTALL' to install libtool on your system. oo2c's installation process detects libtool, and uses it to create a static and, if possible, a shared library for the OOC standard modules.

Basic Installation Procedure

The basic way to build and install the oo2c package is as follows:

  1. cd to the directory containing the package's source code and type ./configure to configure oo2c for your system. If you're using `csh' on an old version of System V, you might need to type sh ./configure instead to prevent `csh' from trying to execute configure itself. If you want to install oo2c without garbage collector support, run configure using the option `--disable-gc', and if libtool is not available, use `--disable-libs'. Running configure takes awhile. While running, it prints some messages telling which features it is checking for.
  2. Type make to compile the package.
  3. Type make install to install the programs and any data files and documentation. make install-strip additionally removes any debug information from the installed executable programs.
  4. You can remove the program binaries and object files from the source code directory by typing make clean. To also remove the files that configure created, type make distclean.

If all went well, you should now have a working Oberon-2 compiler. Since ancient times, this joyous event is celebrated by writing a little program saying "Hello World!". Tradition is important, so here is a step-by-step description of how to do it:

  1. Change to a directory of your choice, preferably an empty one.
  2. Create a file `Hello.Mod' with the following contents:
    MODULE Hello;  
    (* Author: Anonymous; program believed to be in the public domain *)
    IMPORT Out;
    BEGIN
      Out.String ("Hello World!"); Out.Ln
    END Hello.
    
  3. Type oo2c -Mv Hello. The option -M tells oo2c to make an executable program, and -v tells it to be more verbose with messages while doing this. Now, you should have quite a few files in the directory: `Hello.Mod', `Hello.Sym', `Hello', and some files ending in `.c', `.h', `.d', or `.o'. See section Initialization Files on how to automatically move these intermediate files into other directories.
  4. Run the program by typing ./Hello. If you do not see the traditional compiler birth cry of `Hello World!' on your screen, something is obviously wrong.

Specifying C Compiler and Options

Some systems require unusual options for compiling or linking that the configure script cannot address. You can give configure initial values for variables by setting them in the environment. Using a Bourne-compatible shell, this can be done at the command line as follows:

CC=c89 CFLAGS=-O2 LIBS=-lposix ./configure

Or on systems that have the env program,

env LDFLAGS=-s ./configure

If gcc is not available on your system, and cc is a K&R compiler, try passing CC=c89 to configure. Some systems provide a separate ANSI-C compliant compiler under this name.

The values of `CC' (the C compiler), `CFLAGS' (additional command line options to the C compiler), and `LDFLAGS' (additional linker flags) determined by configure are used by oo2c as its default settings.

Setting Installation Paths and Program Names

By default, make install installs the package's files in the directories `/usr/local/bin', `/usr/local/man', and so forth. You can specify an installation prefix, other than `/usr/local', by giving configure the option `--prefix=PATH'.

You can specify separate installation prefixes for architecture specific files and architecture independent files. If you give configure the option `--exec-prefix=PATH', the package uses `PATH' as the prefix for installing programs and libraries. If only `--exec-prefix' is set, documentation and other data files will still use the regular prefix.

In addition, if you use an unusual directory layout, you can give options such as `--bindir=PATH' to specify different values for particular kinds of files. Run configure --help for a list of the directories that can be set, and what kinds of files go in them.

Program names and the name of the installation directory can be changed upon installation. This is achieved by giving configure the option `--program-prefix=PREFIX' or `--program-suffix=SUFFIX'. For example, after

./configure --prefix=/usr --program-suffix=-1.4.5

make install would install the binaries as `oo2c-1.4.5', `oob-1.4.5', and so on in `/usr/bin', and the rest of the compiler's files are put into `/usr/lib/oo2c-1.4.5'.

Installing with Run-Time Checks

For performance reasons, run-time checks and assertions are disabled for all library modules and binaries built during installation.

The drawback to this is that any error in the compiler will most likely show itself as a core dump rather than the usual run-time error message. Likewise, programs that pass invalid parameters to one of the library modules might either crash, show strange results, or even, in some cases, work as expected by sheer luck.

As an example of invalid input giving "expected" results, consider an unterminated character array (an ARRAY OF CHAR that is not terminated by 0X) passed as an input parameter to one of the procedures of module Strings. If run-time checks are enabled, the procedure stops with an error message when it tries to access an index past the end of the array. Without run-time checks, it simply continues to process characters beyond the end of the array until it reaches a 0X somewhere in memory. Under these circumstances, the procedure's result is undefined.

To install oo2c with full run-time checks enabled, remove the whole section PRAGMAS ... END from `oo2crc.stage1.mk.in' in the top-level directory before running configure. This builds the library modules and executable programs with run-time checks and assertions enabled. Please note that this has no affect on foreign modules written in C, like `Files', `Exception', `Types', and so forth.

A simple way to ensure that a single program, say `foo', is created with full run-time checks is to build it once with oo2c --make --all foo. This compiles all modules imported directly or indirectly by module `foo', including the library modules it uses (see section Invoking the Compiler). Afterwards, the newly created object files take precedence over the ones built during installation, and will be linked into all programs.

Command Line Options for Compiler and Tools

The following sections summarize the command line options accepted by the programs of the oo2c package (oo2c, oob, ooef, and oowhereis). Some options have two equivalent names: one is a single letter preceded by `-', and the other is a long name preceded by `--'. Multiple single letter options (unless they take an argument) can be combined into a single command line word; for example, `-MA' is equivalent to `-M -A'. The special option `--' denotes the end of the option list. That is, any argument after `--' is not treated as an option even if it begins with `-'.

Each of these programs first evaluates the global initialization file, and then parses the command line options from left to right. In the default installation, the global initialization file is `/usr/local/lib/oo2c/oo2crc'. This can be changed by setting the environment variable OOC_CONFIG or using the option `--config'. How an environment variable is set depends on the shell:

  bash: export OOC_CONFIG=my_config_file
  csh : setenv OOC_CONFIG my_config_file

The option `--config <file>' supersedes both the hard coded file name and the value in the environment variable OOC_CONFIG. This option takes effect before the initialization file is read, which is different from all other options. There should be at most one `--config' statement. However, by using the option `--include-config <file>', it is possible to specify additional files to be evaluated for configuration. Specifying the empty string as initialization file (e.g., with `--config ""') disables parsing of all default files.

All programs use the same initialization file. Most of the configuration data pertains just to the compiler, but the `PATHS' section is also utilized by the other tools. `PATHS' defines a list of file patterns and paths describing where the programs should look for files, and destination directories for any files that are created. For details on file name resolution see section Initialization Files. Except for the compiler, all programs accept the option `--help' (or `-h' for short).

Invoking the Compiler

The compiler oo2c performs a number of different functions depending on the command line options it was invoked with.

Primary compiler operations

The primary functions of the compiler and the options that trigger them are listed below.

oo2c [options] <module>...
Compile one or more modules. That is, do syntactical and semantical checks and translate the listed files from Oberon-2 source code to ANSI-C.
oo2c (--make|-M) [options] <module>
Make an executable program. That is, create up to date versions of all the necessary object files, which contribute to the given main module, and link them into an executable program.
oo2c (--make-lib|--install-lib) [options] <module>
Turn a set of modules into a single static or shared library, and install the new library in the applicable target directory. Note that both the static and shared library can be created at the same time, depending on the configuration of libtool. See section Creating Shared or Static Libraries.
oo2c --makefile <file-name> [options] <module>
Write a `Makefile' that tells make how to perform the necessary steps to create an executable program from a set of intermediate C files.

If none of the special flags listed above is present, oo2c assumes that all arguments are names of source files and tries to compile them to ANSI-C code. Compiling a single module in this way can be used to check the syntax of a module, or selectively force recompilation of modules. If a file name argument has no directory part, the compiler searches in the directories listed in the `PATHS' sections of the initialization files (see section Paths of Input and Output Files). Any errors encountered while parsing a source file are written to `stdout' like this:

In file foo.Mod:
<pos>: <num> <error message>

Here <pos> refers to the position of the error in the file (the first character has position 0), <num> is the error number, and the rest is a plain text error message. The message format can be changed with the filter program ooef (see section Converting Error Messages).

The option `--make' (or `-M' for short) turns a set of Oberon-2 modules into an executable program. The single argument can be either the name of a module or a module's file name. Again, the compiler searches the directories in `PATHS' if the file name has no directory part. The compiler inspects all modules imported directly or indirectly by the given main module. For every module that is compiled, the compiler decides whether it needs to be translated to C or not. A module is compiled (or recompiled) if

In the next step, all necessary object files are generated by invoking the C compiler. Typically, this is the most time consuming part of the translation process. The final step links object files and libraries into an executable program with the same name as the main module. Note that, unlike the Oberon System, there is no notion of commands (i.e., parameterless exported procedures, which can be activated directly by the user). Instead, the module body of the main module specifies the program's execution sequence.

Sometimes, it is desirable to recompile all modules contributing to a program because, for example, some intermediate files were corrupted or a different set of options needs to be applied to all modules. In this case, the option `--all' (or `-A' for short) should be used together with `--make'. This forces oo2c to recompile every module, from scratch, that is part of the program and whose source code is available. Another option modifying the behaviour of `--make' is `--no-build', which causes the make process to stop after the C code is written, but before the C compiler is invoked to create the object files.

With `--makefile <file-name>', a so-called `Makefile' is written to the specified file. This option takes a single argument: the name of a module or a file name. The generated file contains the rules necessary to use the make utility to build an executable program for the main module from existing C code. This feature is typically used to transfer a program to a system on which oo2c is not installed. By default, the file contains only rules to compile C code into an executable program. Specifying `--oc-rules' also writes rules that will run oo2c and produce, one at a time, the necessary C files from their Oberon-2 code.

Standard Command Line Options

The following command line options can be used with every mode of operation for oo2c. The variable names shown with some of the options refer to the configuration variable associated with that option (see section Option and Pragma Variables).

`--optimize' or `-O', option variable: `optimize'
Try harder to optimize the intermediate code. In addition to the usual code improving transformations, further time consuming optimizations are enabled, and certain optimizations are run more than once. Also, add the contents of `coptflags' to C compiler invocations.
`--no-rtc'
Remove all run-time checks from the generated code. This speeds up programs considerably. On the other hand, illegal program states might go by unnoticed or lead to program termination in the form of a core dump. For the list of supported run-time checks, see section Option and Pragma Variables.
`--version'
Write program version and exit.
`--write-config'
Write current configuration data to `stdout' and exit. Note that the configuration data also includes the effects of command line options.
`--verbose' or `-v', option variable: `verbose'
Be more verbose during compilation. In particular, the name of the file currently compiled, changes in symbol files, and all external program invocations are written to `stdout'.
`--warnings' or `-w', pragma variable: `Warnings'
Include warnings in error listings.
`--options <string>'
Add the given string to the initialization file section `OPTIONS'. Example: `--options "optimize:=TRUE; verbose:=FALSE"'. See section Option and Pragma Variables.
`--pragmas <string>'
Add the given string to the initialization file section `PRAGMAS'. Example: `--pragmas "Warnings:=TRUE; Assertions:=FALSE"'. See section Option and Pragma Variables.
`--define <string>'
Define a new variable for the initialization file section `PRAGMAS'. This introduces a new variable and sets it to the given value. Example: `--define "FooVar:=TRUE"', which is equivalent to `--pragmas "DEFINE FooVar:=TRUE"'.

C Compiler Options

oo2c needs a C compiler to translate its ANSI-C code to object files, and to link object files and libraries into an executable program. The following options specify the name of the C compiler and the options that are passed to it. Every command line option modifies the value of a variable of the initialization section `OPTIONS'. For example, writing `--cc gcc' in the command line is equivalent to adding the assignment `cc := "gcc"' to the `OPTIONS' section. The default values for the various variables are set by configure when installing the compiler. With the exception of `gcflags' and `valueStack', the variables listed here have no effect as long as oo2c is only called to translate single modules. They are the building blocks for the argument list passed to the C compiler when generating an object file, linking a program or a library, or writing a makefile.

`--cc <string>', option variable: `cc'
The name of the C compiler.
`--cflags <string>', option variable: `cflags'
These flags are added to the C compiler's argument list when translating a C file into an object file.
`--coptflags <string>', option variable: `coptflags'
Like `--cflags' these flags are added to the argument list, but only if the option `--optimize' is set. This lets the user request activation of time consuming optimization flags of the C compiler only when such optimizations are desired.
`--ldflags <string>', option variable: `ldflags'
The value of this string is appended to the link command.
`--gcflags <string>', option variable: `gcflags'
This specifies the linker command that adds the garbage collector code to the executable program. Garbage collection is disabled by setting the variable to the empty string. This variable affects both C code generation and linkage.
option variable: `valueStack' (integer)
oo2c supports two mechanisms to allocate space for a procedure's value parameters of open array type. The first works with a fixed block of heap memory as auxiliary stack, and the second uses the function alloca() to reserve the necessary space on the normal stack. The advantages of alloca() are efficiency, elegance, and, in practice, unlimited stack space. The disadvantage is that it is not an ANSI-C function, but rather a BSD extension, which is not available on some systems. The alloca() variant is chosen by setting `valueStack' to `-1'. Specifying a positive integer value for `valueStack' tells oo2c to allocate a block of heap memory of the given size to store open array value parameters. The size is then hard coded into the program and is fixed throughout program execution; this size must be chosen carefully in order to avoid stack overflows. If the C compiler doesn't support alloca(), the default value of `valueStack' is 64KB. All modules contributing to a program should be compiled using one of these two mechanisms: either for alloca() or for the auxiliary stack. It is not recommended that they be mixed within the same program.

Creating Shared or Static Libraries

A library file (or simply library) is a type of file archive, which contains a group of object files. Library files may be either static or shared.

oo2c depends on GNU libtool for the creation and installation of libraries. This package is available for a wide variety of systems, and it handles all system specific details of libraries. Support for particular systems may vary, but in practice libtool supports static libraries on all systems, and shared libraries on most systems. The oo2c package includes libtool. If necessary, it is automatically installed, under the name oolibtool. If a version of libtool already exists on the system, it is used instead of oolibtool by default.

Static libraries are used by the link editor, which combines libraries with other object files to create a single executable program.

On the other hand, shared libraries (also called dynamic libraries) are not stored in the executable program file itself, but are loaded into memory by the run-time loader just prior to execution of a program. Only one instance of a shared library needs to be loaded into memory at any particular time, even when more than one program is using it. This can be beneficial especially if several programs share a large number of modules, as it can provide a substantial savings in both memory usage and disk space. But keep in mind that libtool, and therefore oo2c, does not support shared libraries on all systems.

The `--make-lib' function of oo2c turns a set of modules into a library. Just like `--make', it takes a single argument: the name of a module or a file name. The main module must look like this:

MODULE FooLib [LIBRARY "foo" "1:2:3"; INTERFACE "C"];
IMPORT ...;
END FooLib.

This creates a library `foo' with version number `1.2.3' from all modules imported directly or indirectly by module `FooLib'. Modules that are already a part of another library are not be included in `foo'. Both a shared library and a static library are built, or, if the system does not support shared libraries, just the static version. For information about the version number and how it has to be maintained, see section `Library Interface Versions' in Libtool Manual. To install a newly created library use `--install-lib'. This command takes the same arguments as `--make-lib', and invokes libtool to install the library in the target directory.

Subsequent import of any module that is part of the library causes oo2c to link against the library file instead of the module's object file. Note that recompilation of such a module, either through an explicit command or during a make, will undo this. The compiled module and all modules importing it will then be linked against the object files.

Linking against libraries that haven't yet been moved to their final destination is slightly tricky. Some systems encode the absolute path to the shared library directly in the executable program, and libtool has to do some special magic to produce a program that works both before and after the libraries have been installed.

To link against uninstalled libraries, the option `--libtool-link' must be used. This modifies the linker invocation to link against libtool libraries from the current directory (for example `libfoo.la'), instead of the library itself. The resulting command string is then passed to libtool.

If uninstalled shared libraries are involved, libtool places the executable program in the directory `./.libs', and a wrapper script of the same name is placed in the current directory. Until the libraries are installed, only the wrapper script can be executed. If only static libraries are involved, the program is placed directly in the current directory. When installing the program, the user should take the file from `./.libs' if it exists, and the one in the current directory otherwise.

Use of libtool and the installation path can be adjusted with these options:

`--lib-path <string>', option variable: `libpath'
Specify the directory where the libraries should be installed. Note that the same destination directory has to be used for both library creation (with `--make-lib') and library installation (with `--install-lib'). The reason is that some systems hard code the path to a shared library into the library binary itself. The default path is the same `lib' directory used when installing the compiler.
`--libtool-cmd <string>', option variable: `libtoolCmd'
Set the name of the libtool script, which is used with `--make-lib' and `--install-lib'. Note that the default value of `libtoolCmd' depends on how libtool was installed on the system: If libtool was installed prior to the oo2c package, its path is used for `libtoolCmd'; otherwise, `libtoolCmd' is set to oolibtool.
`--install-cmd <string>', option variable: `installCmd'
Set the command prefix to be used when installing files with `--install-lib'. If the system offers an install command, the default prefix is defined to be something like `/usr/bin/install -c -m 644'. Otherwise, oo2c uses a replacement script with similar functionality.
`--libtool-link', option variable: `libtoolLink'
When used with `--make', invoke libtool to do final linking. This option is provided for linking against libraries that have not yet been moved to their final destination.

Debugging Options

There are a number of ways to inspect the inner workings of the compiler during the optimization steps and in the backend. The following command switches are specific to oo2c; it is unlikely that other implementations of OOC will share even a subset of them.

`--checks', option variable: `checks'
Do some consistency checks after every optimization. This is used to discover invalid code transformations that violate structural requirements of the intermediate code.
`--stupid', option variable: `stupidCodeGen'
Disable all code transformations. Feed output of frontend directly to backend.
`--translate proc|gproc|module|program', option variable: `translationBasis'
Specify how much source code is read before running optimizations and generating code. Setting a higher structural level of the translation basis allows for more optimizations to be run. `proc' reads a single procedure at a time, `gproc' a single global procedure including all its nested procedures, `module' a whole module, and `program' the entire set of program code. `gproc' is the default setting for oo2c, `proc' and `program' are not supported yet, and (at the moment) `module' has no noticeable benefits compared to `gproc'.
`--opt <string>', option variable: `optimizers'
Set the sequence of code transformations. Every character in the given string represents a transformation. (To get the entire list of available choices use some illegal selection, like `--opt .'.) Without the special value `0', a final dead code elimination is done before the code is given to the backend. The character `?' writes the intermediate code to `stdout'. For example, the command line arguments `--opt "?CD?"' write the code as emitted by the frontend, run common subexpression elimination and dead code elimination, and write the resulting code to `stdout' again. The following options modify the output format of the intermediate code:
`--gsa-qnames', option variable: `writeQualNames'
Include qualified names in the output.
`--gsa-opnd-pos', option variable: `writeOpndPos'
As much as possible, print source file positions of operands. Note that many operands do not correspond directly to file positions.
`--gsa-instr-pos', option variable: `writeInstrPos'
Print source file positions of instructions.
`--gsa-assign', option variable: `writeAssignHints'
Try to show how the intermediate code reflects assignments in the source code. This is only useful as long as no optimizations are enabled; that is, together with `--opt "?"'. Note that setting this option might utterly confuse the backend, and result in corrupted C code.
`--gsa-gate-old', option variable: `writeGateOld'
Extend the output of `gate' instructions to include their `oldValue' field. Very useful when debugging certain parts of the frontend; otherwise, it serves no purpose.
`--cgsa', option variable: `writeGSAC'
Write intermediate code annotated by backend specific information to `stdout'. This is done just before control flow of the intermediate code is converted from guarded commands to the more conventional form of explicit jumps and branches. After this final transformation, the ANSI-C files are written. The output can be adjusted with the following options:
`--cgsa-qnames', option variable: `writeLocC'
Include qualified names in the output.
`--cgsa-loc', option variable: `writeQualNamesC'
Add location values (i.e., variable names) to statements. This makes it considerably easier to match fragments of intermediate code with emitted C code.

Note that the above table is not exhaustive; other undocumented options may exist that are of interest only to the compiler writers.

Files used by the Compiler

The location of global files depends on the installation. The file names below assume that the default setting --prefix=/usr/local was used.

`/usr/local/lib/oo2c/oo2crc'
Default path to primary initialization file.
`~/.oo2crc'
Default user level initialization file. Included from the primary initialization file.
`.Mod'
Source code of an Oberon-2 module.
`.Sym'
Symbol file describing the public interface of a compiled module.
`.h'
Header file describing the interface of a module on C level.
`.c'
`.d'
Translated ANSI-C code of a module. The file `.d' holds global definitions, `.c' the C functions.
`.o'
Object file derived from `.d' and `.c' by the C compiler.
`.Lib'
Library description with information about inter-library dependencies.
`/usr/local/lib/oo2c/Errors.short'
List of error messages.
`/usr/local/lib/oo2c/lib/__*.c'
`/usr/local/lib/oo2c/lib/__*.h'
Auxiliary files with C definitions. These need to reside in one of the paths listed in the initialization files or compilation of C code will fail.

Using the Symbol File Browser

The symbol file browser oob displays the interface definition of a module as seen by the compiler.

oob [-x|--extended] <module-name>

The program accepts a single argument: the name of a module or a file name, which is stripped of its directory part and any suffix. The symbol file for the resulting module name is located using the `PATHS' section of the configuration data. Once found, the contents of the symbol file are written to `stdout' in a format resembling that of a module.

With option `--extended' (or `-x' for short), the output of oob for extended records includes the names of the base types, the inherited record fields, and the inherited type-bound procedures. Every definition of a type-bound procedure is listed, even if it is redefined on subsequent extension levels.

The output differs from a true Oberon-2 module, in particular from the original source code, in a number of ways:

Interface definitions can also be extracted from a module's source text; the command oocn -d <module> extracts the public interface of a module (see section Source Code Analysis and Transformation).

Source Code Analysis and Transformation

The tool oocn operates on the source code of Oberon-2 modules to produce various manipulations of the text. These include the following: rewriting the source text, converting it into different formats, creating cross-reference information, and extracting the public interface of the module. It is invoked like this:

oocn <mode> [options] <module>...

The `<mode>' argument determines the operation performed by oocn; for example, `--html' sets the mode to translate to HTML. No more than one mode can be specified at at time. If no mode is specified, oocn produces usage information, which lists all modes and options.

The `[options]' are used in addition to `<mode>' to modify the behaviour of oocn.

The `<module>...' argument is a list of one or more modules, or file names of modules. If it is a file name, the directory part and extension are discarded. Modules are then located by means of the `PATHS' section of the compiler's initialization file.

Except for its use of initialization files, oocn shares no code with the compiler proper. In particular, oocn does very limited error checking. It reports only a small subset of the errors that are detected by the compiler, and it accepts malformed Oberon-2 sources, as long as the errors do not interfere with its own operation.

Modes

The following is a list of available modes:

`--modules' or `-M'
List the names of all modules that are directly or indirectly imported by the given modules (and also list the given modules themselves). The modules are written in an order defined by the IMPORT relation; that is, module `Bar' is written before module `Foo' if `Foo' depends on `Bar'. For example, the invocation oocn --module Foo lists the names of all modules that are used to build the program `Foo', writing the name of the most basic module first, and `Foo' last. With option `--no-internal', the pseudo module `SYSTEM' is omitted from the output. Please note: This function implicitly adds the option `--closure'.
`-d'
Write the interface of the given modules to `stdout'. Here the term interface means the module's source text stripped of all private declarations and all procedure bodies. Comments in the remaining text are preserved. This mode is an abbreviation of `--def-txt -o -'.
`--html' or `-H'
Convert the given set of modules to HTML text. For every module `Foo', a file `<output-dir>/Foo.html' is created. The default output directory is the current working directory. The HTML text preserves the format of the source text, but adds colours for keywords, comments, strings, and procedure declarations. Identifiers of exported declaration are set in bold. Hyper-links are inserted Note that links to all record fields and type-bound procedures can be inserted only if oocn was called with the option `--closure'.
`--xref' or `-X'
Create cross-reference information for the given set of modules. This mode creates a set of HTML files, just like `--html', and adds hyper-links from every declaration into a companion file `<output-dir>/Foo_xref.html'. The cross-reference file lists all uses of each declaration in the scope of the scanned modules. For a redefining type-bound procedure, it includes a link to the base definition, and for an original type-bound procedure definition, it lists all redefinitions and their uses. Please note: This function implicitly adds the option `--closure'.
`--uses <decl>' or `-U <decl>'
The mode `--uses' acts as a command line interface to the cross-reference data. That is, it locates all references to the specified object and writes them to `stdout' in the format of oo2c's error messages. The argument `<decl>' is a string describing a declared object; the string must be the name of a predefined object, or a module name followed by a (possibly empty) sequence of names, with the names separated by dots. The selector `foo.bar' designates the object `bar' in scope `foo', where `foo' is either The command `oocn --uses bar' lists all appearances of the named object `bar' in the scope of the set of modules specified on the command line. The uses of module names, predefined objects, and objects from the pseudo module `SYSTEM' can also be listed in this way. Uses within inactive conditional compilation clauses are ignored. Example:
oocn --uses TextRider.Reader.SetEol.i TextRider
   => 
       In file /usr/local/lib/oo2c/lib/TextRider.Mod:
       12345: declaration
       12551: use
       12597: use
       12693: use
       12706: use
The above command looks for uses of object `i', which belongs to the type-bound procedure SetEol of type Reader declared in module `TextRider', within module `TextRider' (and modules it imports). If the designated object is a type-bound procedure, `--uses' lists the base definition of the procedure, all of its redefinitions, and all calls to the type-bound procedure in the scope of the inspected modules. Example:
oocn --uses Files.Reader.Pos liboo2c
   => 
       In file lib/Channel.Mod: 
       11906: base definition
       In file lib/BinaryRider.Mod: 
       2462: use
       In file lib/TextRider.Mod: 
       9240: use
       In file backend/ansi-c/lib/PosixFileDescr.Mod: 
       5963: redefinition
       In file backend/ansi-c/lib/ProgramArgs.Mod: 
       2487: redefinition
       4175: use
Please note: This function implicitly adds the option `--closure'.
`--def-txt', `--def-html', `--def-xref'
Using the specified format, write the interface of the given modules to a file in the current output directory. The output format is either plain text in file `Foo_def.txt', HTML text in `Foo_def.html', or cross-referenced HTML text in `Foo_def.html' and `Foo_def_xref.html'. The output directory can be changed using option `-o <dir>'.
`--def-texi'
Create draft version of the public interface of the modules in Texinfo format. The output file is named `Foo_def.texi'. Unlike the other `--def-*' variants, the output has little resemblance to the original input text, and it will probably need manual intervention to turn it into something more readable. The output file is formatted as follows:
`--filter' or `-F'
Copy the Oberon-2 source code from the input module `Foo.Mod' to the file `Foo.txt' in the output directory, possibly applying some code transformation on the way. All symbols are copied as is, without any change to their textual representation. This includes text in comments, pragmas, and program code in inactive conditional compilation clauses. Outside these special symbols, horizontal tabulators are converted to spaces, using a tabulator width of 8. All trailing whitespace is removed from lines, as are any empty lines at the end of the module. This mode is usually used in conjunction with one or more of the code transformation options, like `--strip-pragmas' or `--mod2foreign'.

Options

Use the following options to modify the behaviour of each mode:

`-o <dir>'
Set the output directory for all commands that write to files. The name `-' specifies `stdout'.
`-v'
Select verbose mode. This writes the names of input and output files to `stdout'.
`--closure' or `-C'
Operate on all modules that are imported, either directly or indirectly, by the modules given on the command line. For example, the command
oocn --html --closure Foo
will produce HTML files for all modules contributing to program `Foo'. Please note: For some modes, the option `--closure' is enabled by default.
`--no-internal'
Omit all pseudo modules that are internal to the compiler from the output of `--modules'. At the moment, this means that `SYSTEM' does not appear in the module list.
`--line-num'
Prepend the line number from the original source file to every line of output. This option affects all commands that produce text or HTML directly from the source code.
`--colors <name>'
Select color set to use when writing HTML text. Currently available variants: `hilit' (default) and `font-lock'.
`--strip-comments'
Remove all comments from the source text before processing it. Comments starting with (** are not discarded, use option `--strip-doc-strings' for this.
`--strip-doc-strings'
Remove all documentation strings, that is, comments starting with (**, from the source text.
`--strip-pragmas'
Remove all pragmas from the source text. Any program text appearing in inactive conditional compilation clauses is also discarded. The evaluation of the guards of conditional compilation clauses uses the current values of the pragma variables. Therefore, applying this filter reduces the source file to the program text that is actually seen by the compiler when translating the module, assuming that the same settings are used for the pragma variables.
`--strip-system-flags'
Remove all system flags from the source text. For example, if a module uses any of the flags that are enabled by `OOC_EXTENSIONS', applying this filter reduces the module to standard Oberon-2 code.
`--mod2foreign'
This code transformation is intended for advanced users, who want to write `FOREIGN' modules (see section FOREIGN Modules). It turns any Oberon-2 module into a `FOREIGN' module, by removing all procedures bodies and the module's initialization code, and by adding appropriate default system flags to the module's header.
`--foreign2mod'
This is the reverse operation to `--mod2foreign'. It adds empty bodies to all procedures in the module, and replaces the module's system flags with `[OOC_EXTENSIONS]'.

oocn also understands the following additional command line options, which function in the same way as they do for oo2c:

`--config'
`--include-config'
`--options'
`--pragmas'

Converting Error Messages

Error messages emitted by oo2c refer to a character position in the source file. The first character has index `0'. Take, for example, this slightly faulty program:

MODULE Hello;
IMPORT Out;
BEGIN
  Ou.String ("Hello World!") Out.Ln
END Hello.

Compiling it with oo2c produces this output:

In file ./Hello.Mod: 
34:197 Undeclared identifier
60:139 `;' expected

File position `34' refers to the first character of `Ou', and `60' to the character to the right of the closing parenthesis. This format is slightly awkward if there is no support from the editor to locate the designated points in the source code.

Because of this awkward format, the filter program ooef can be used to transform error messages into a more convenient form. ooef reads the output of oo2c from `stdin', and writes a modified version to `stdout'. Error messages are rewritten, and the rest of the input is echoed. The filter should be invoked like this:

oo2c ... | ooef [option]

The output format is selected with the following options:

`--context' or `-c'
Write an extract of the source text and insert additional lines to point to the error position. This is the default setting. Lines are numbered starting at `1'. Example:
~$ oo2c Hello.Mod | ooef
In file ./Hello.Mod:
MODULE Hello;
IMPORT Out;
BEGIN
  Ou.String ("Hello World!") Out.Ln
#-^
# 4: 197 Undeclared identifier
#---------------------------^
# 4: 139 `;' expected
END Hello.
`--line' or `-l'
Write errors as `file:line:error'. This will only give an approximation of the exact error position. The first line has the index `1'. Example:
~$ oo2c Hello.Mod | ooef -l
./Hello.Mod:4:197 Undeclared identifier
./Hello.Mod:4:139 `;' expected
`--linecol' or `-L'
Write errors as `file:line,column:error'. The first line has the number `1', likewise the first column. Example:
~$ oo2c Hello.Mod | ooef -L
./Hello.Mod:4,3:197 Undeclared identifier
./Hello.Mod:4,29:139 `;' expected

To get the file position of a run-time error, pass the module name and the error position to ooef as arguments:

ooef [option] <module> <pos>

In this mode, ooef does not act as a filter. It generates its output based on the given command line arguments instead. The module's source file must be in the standard search path.

Example: Suppose the run-time system reports an index out of range error in module `Strings' at file position 2531. The command ooef Strings 2531 lists the corresponding lines of the file `Strings.Mod', highlighting the instruction whose run-time check failed:

In file /usr/local/lib/oo2c/lib/Strings.Mod:
    i: INTEGER;
  BEGIN
    i := 0;
    WHILE (stringVal[i] # 0X) DO
#--------------------^
# 68: 
      INC (i)
    END;
    RETURN i

Using the File Finder

oowhereis can be used to locate files given their name. This is a command line interface to the mechanism used by the compiler to find its files. Among other things, it is used by the Emacs mode to determine the file names of modules listed in IMPORT statements.

The program expects a single argument, the name of a file. If a matching file is found in any of the directories listed in the initialization file, the full path (including the directory part) is written to `stdout'. In this case, the exit code is `0'. Otherwise, nothing is written, and the program returns with an exit code of `1'.

For source files with an associated RCS master file, the name of the working file is returned (unless no working file is checked out and the option `--rcs-master', or `-r', is used). By default, the name of the working file is returned even if this file does not currently exist.

Initialization Files

oo2c's configuration mechanism manages a number of things: options that control the compiler's workings, pragma variables that are available during compilation, and the redirection table that specifies the directories used for file access. This mechanism provides the means to create a hierarchy of configuration settings: system wide, user based, and project specific. Initialization files give full access to the configuration database, whereas command line options provide shortcuts for only some, albeit often used, settings.

An initialization file is composed of sections; each section is introduced by its keyword, followed by data in a section-dependent formant, and terminated by the keyword `END'. The following sections are known to the compiler: `OPTIONS', `PRAGMAS', `PATHS', `NEWFILES', and `INCLUDE'. An initialization file may contain an arbitrary number of these sections as explained in the rest of this chapter.

Comments are permitted within an initialization file. A comment starts with a `#' character and extends to the end of the line.

Option and Pragma Variables

Both the `OPTIONS' and the `PRAGMAS' sections define a set of (name, value) pairs. Names must follow the rules of Oberon-2 identifiers (i.e., a character followed by a sequence of characters or digits), and the value has to be a literal value of type boolean, integer, or string. Valid values are as follows: `TRUE' and `FALSE' for boolean literals, any valid LONGINT value for integer literals (including negative numbers), and strings are delimited by either `"' or `'' and cannot contain characters below ASCII code `20X'.

The EBNF syntax of these sections is defined as follows:

options_section = "OPTIONS" option_list "END".
pragmas_section = "OPTIONS" option_list "END".
option_list     = [option] { ";" [option]}.
option          = [ assignment | define ].
assignment      = name ":=" value.
define          = "DEFINE" assignment.

For an example of how this looks in practice, see section An Example Initialization File.

A new variable is defined by prefixing an assignment with the keyword `DEFINE'. No variable of the same name may exist beforehand. The definition also assigns a type to the variable based on the value on the right hand side of the assignment. A variable can be defined only once, but its value can be changed through subsequent assignments.

Any further assignments change the value of an existing variable; the new value has to be of the same type as the old. For example, once a variable is defined to be of type integer, all subsequent assignments can assign only other integer values to it. Note that assignments are valid only for existing variables; that is, it must be a predefined compiler variable or a variable that was previously introduced by a variable definition.

Options and pragmas differ in two points:

  1. Options are specific to oo2c (or rather, each implementation of OOC), whereas the entire set of pragma variables is defined for all OOC compilers.
  2. Options cannot appear within embedded pragma statements in source code, but pragma variables can be used in pragma statements inside Oberon-2 modules.

For the complete set of option variables see section Invoking the Compiler. Variable names are listed, where applicable, beside the command line option that can change it. For the built-in pragma variables of the compiler see section Predefined Pragma Variables.

Pragma variables can be set from the command line by using the switch `--pragmas <string>'. For example, specifying

--pragmas "IndexCheck:= FALSE; DerefCheck := FALSE"

has the same effect as adding

PRAGMAS
  IndexCheck := FALSE; DerefCheck := FALSE
END

to an initialization file. The command line option `--options <string>' does the same for `OPTIONS'.

Paths of Input and Output Files

Even though Oberon-2 has only a single name space for module names, it would be inconvenient if the source code for all modules had to reside within a single directory. Also, considering the number of intermediate files oo2c produces for a single module, the situation could be even worse.

oo2c provides a way to distribute source code over a number of directories, and thus "stash away" intermediate files in a more suitable place. When looking for a particular file, oo2c searches the directories defined in the `PATHS' sections of the initialization files. The `PATHS' section lists a number of wildcard strings, which are used to determine which directories should be scanned for matching file names.

The syntax of a `PATHS' section is defined like this:

paths_section  = "PATHS" {source_pattern} "END".
source_pattern = "GET" wildcard_list "FROM" path {path}.
wildcard_list  = wildcard {[","] wildcard}.
wildcard       = name | string.
path           = ( name | string ) [";"].

A wildcard may contain the special characters `*' and `?'. A `*' matches an arbitrary number of characters (including none at all), whereas `?' matches exactly one character. Writing `[RCS]' after a wildcard signals that a file matching the pattern might be under control of the Revision Control System (RCS), and should be checked out if no working file exists.

Any non-absolute path (i.e., all path strings not starting with a `/' or a `~') is interpreted relative to the directory the compiler, or tool, was started from. Whenever a program is invoked from a different directory, these relative path names will then resolve differently. If the intention is to always use the exact same directories for all invocations, all paths in the initialization file must be absolute.

When looking for a particular file, say `foo', the list of patterns is scanned from top to bottom. For every match, the list of directories is tested from left to right. The first directory that contains a file with the requested name is used. If the file cannot be found in any of these directories, the simple file name is used. If RCS support is enabled for `foo', then the files `<dir>/RCS/foo,v' and `<dir>/foo,v' are also searched for in these directories.

Example:

PATHS 
GET *.Mod [RCS] FROM .; /usr/local/foo
GET *.c FROM obj; /usr/local/bar
END

This tells oo2c, when looking for files with the extension `Mod', search the current directory (`.') and then the directory `/usr/local/foo'; for files with the extension `c', search in the `obj' subdirectory (under the current working directory), and then the directory `/usr/local/bar'.

For instance, when searching for the file `foo.c', the matching pattern is `*.c', and so files `obj/foo.c' and `/usr/local/bar/foo.c' are tested, in that order, for existence. The first match is taken; that is, if `obj/foo.c' exists, then that is the file used. If neither of these files exist, the name `foo.c' is used as a last resort. If this file exists in the current working directory, it is used; otherwise an appropriate error message is written.

As another example, when looking for `Foo.Mod', and the file `./RCS/Foo.Mod,v' exists, but not `./Foo.Mod', then the RCS master `./RCS/Foo.Mod,v' is checked out. Then, the working file `./Foo.Mod' is created, and subsequently used.

Note that, if a module name is passed as argument from the command line, the standard suffix `.Mod' is appended, and the resulting file name is searched for using the above mechanism. Also, if a file name that contains a directory part is used, no searching is done at all; the file name is used exactly as specified.

When trying to decide where to place a generated file (e.g., one of the numerous intermediate files with C code), oo2c uses a simplified version of the mechanism described above. It looks for the first matching wildcard, and uses the first directory in that list; the newly created file is written to this directory. It does not matter if the file exists beforehand or not, or if a file of the same name exists in any of the other listed directories. To use the above example again, any file ending in `.Mod' would be put into the current working directory (a hypothetical case since the compiler never writes a new module), and all files ending in `.c' are placed in the directory `obj'.

For files that are only written and not subsequently read, it is possible to specify a destination directory in a special section `NEWFILES'. Its syntax is somewhat simpler than `PATHS'.

  new_files_section = "NEWFILES" {dest_pattern} "END".
  dest_pattern      = "PUT" wildcard_list "INTO" path.

When writing a new file, the paths in `NEWFILES' take precedence over the ones in `PATHS'. But when searching for files, `NEWFILES' is ignored. Because most of the files oo2c is dealing with are either input-only or are written out to be used again at a later stage, use of `NEWFILES' is effectively limited to provide directories for executable programs. If paths for executable programs are not set in either `NEWFILES' or `PATHS', they are placed in the current working directory.

The following example shows how the installation scripts of oo2c place the listed executable files in the subdirectory `stage2':

Example:

NEWFILES
PUT oo2c, oob, oowhereis, ooef, LibSummary, UpdateX11 INTO stage2
END

Selecting Initialization Files

By default, all programs use the initialization file that was created when the compiler package was installed. The initialization file lists all options needed for the system's C compiler, holds various system specific settings, and specifies paths to the library files installed along with the compiler (see section An Example Initialization File). The global initialization file is shared by all users, unless a particular user provides his own primary initialization file instead. A user can do this by defining an environment variable OOC_CONFIG or by using the command line option `--config' (see section Command Line Options for Compiler and Tools).

More control over the configuration data is allowed by the special initialization file section `INCLUDE'. It is a simple, but efficient, way to add personalized or project specific configuration details to the global default settings. The format of an `INCLUDE' section is simply `INCLUDE <file> END', which causes the entire contents of `<file>' to be processed as if those contents had appeared in place of the `INCLUDE' statement.

For example, the default initialization file contains the following statement to include a user's personalized settings:

INCLUDE ~/.oo2crc END

The file `.oo2crc' from the user's home directory is then parsed just as though it were part of the initialization file at the place of the `INCLUDE' statement. If a user decides that he needs even more control, he could add a line to `~/.oo2crc' like this:

INCLUDE ./.oo2crc_local END

Then, the contents of the file `.oo2crc_local', located in the current working directory, are also added to the configuration database. Provided that the user has a separate working directory for every project, this mechanism allows specification of additional settings, beyond the global and the personalized ones, for each project. Supplementary initialization files should be included after the `OPTIONS' and `PRAGMAS' sections, but before `PATHS'. This way, the specialized files override all option and pragma variables, and their own paths then take precedence over the more global ones.

Option `--include-config <file>' can be used to include initialization files from the command line.

The compiler emits a warning if it cannot find the global initialization file. On the other hand, no message is produced when the compiler fails to find a file listed in an `INCLUDE' section.

An Example Initialization File

The file below is a slightly modified version of the primary initialization file of a vanilla installation after `configure --prefix=/usr' on a Linux system.

OPTIONS
  verbose := FALSE;
  errorMessages := "/usr/lib/oo2c/Errors.short";
  optimize := FALSE;

  cc := "gcc"; cflags := "-pipe"; coptflags := "-O2";
  ldflags := "-L/usr/lib"; gcflags := "/usr/lib/oo2c/gc.a";
  valueStack := -1;

  libtoolCmd := "oolibtool";
  installCmd := "/usr/bin/install -c -m 644  ";
  libpath := "/usr/lib";

  DEFINE LibX11Prefix := " -L/usr/X11R6/lib  -lSM -lICE";
  DEFINE LibX11Suffix := "";
END

PRAGMAS
  Warnings := FALSE; Assertions := TRUE; Initialize := FALSE;
  StackCheck := TRUE; ConformantMode := FALSE;

  CaseSelectCheck := TRUE; IndexCheck := TRUE;
  RangeCheck := TRUE; DerefCheck := TRUE;
  FunctResult := TRUE; TypeGuard := TRUE;
  OverflowCheck := FALSE; IntDivCheck := TRUE;
  RealOverflowCheck := TRUE; RealDivCheck := TRUE
END

INCLUDE ~/.oo2crc END

PATHS
GET *.Mod [RCS] FROM .;/usr/lib/oo2c/lib
GET *.Sym, *.Lib FROM .;/usr/lib/oo2c/sym
GET *.h, *.d, *.c FROM .;/usr/lib/oo2c/obj;/usr/lib/oo2c/lib
GET *.o FROM .;/usr/lib/oo2c/obj
END

The paths for error messages and library files are set by configure when installing the compiler package. Likewise, configure also specifies the options for the C compiler, system commands, and external libraries. In this example, one item was changed manually; gcc's optimization flags were moved from `cflags' to `coptflags'. With the exception of the `PATHS' section, this initialization file reflects the values hard coded into the compiler during installation.

Interfacing to C Code

Unlike many of the other Oberon systems, OOC does not try to provide a closed development environment or, as in some cases, an entire operating system. Instead, it provides a set of tools that can be used to write portable software for a number of operating systems. OOC is meant to coexist with the target OS and its system libraries. In the case of oo2c, this means interfacing with the Unix operating system and its libraries, which are mostly written in the C programming language.

Using Foreign Code

Access to foreign code (like object files, static or shared libraries, modules, etc.) should be transparent to Oberon-2 modules. Using foreign types, reading and writing to foreign variables, and calling foreign procedures should look exactly like normal Oberon-2 entities. Therefore, all foreign constructs have to be mapped to their Oberon-2 counterparts. That is, each C type is mapped onto an Oberon-2 type, each C function onto an Oberon-2 procedure, and so on. This mapping is accomplished by using special definition modules, which in turn can be imported and used just like any other Oberon-2 module.

Problems can arise when a foreign construct does not map directly onto an Oberon-2 construct. For instance, one construct could carry more information or attributes than the other. An example of this is the Oberon-2 pointer type, which is associated with a type tag (for records) or a length (for open arrays). In C, a pointer is simply an address. So in this case, the mapping must be extended to cover semantic attributes that are not actually defined in the Oberon-2 language (but rather, these are implementation details).

So, the mapping mechanism must provide a way of modifying the semantics of standard Oberon-2 constructs (because we do not want to modify our definition of Oberon-2 to include, say, a C-like struct type). For instance, a C pointer type is mapped to an Oberon-2 pointer that is marked as having no associated type tag or length information.

Note that this approach generally works only for languages whose list of features is approximately a subset of those in Oberon-2. For example, complicated constructs like C++ classes cannot be adequately mapped to standard Oberon-2.

Please note: All foreign modules should be considered unsafe, low-level, and system (or compiler) dependent. Any module accessing such a module could also inherit those dependencies, so care must be taken when using any foreign module.

System Flags

To attach non-standard attributes to Oberon-2 constructs, so-called system flags are introduced. System flags are applied either to the declaration of an object (like variable, procedure, parameter) or to a type constructor (record, array, formal parameter list, etc.). Syntactically, a system flag is defined using a left bracket `[', followed by a implementation-defined statement sequence (which may consist of list of keywords, strings, separators, etc.), and is terminated by a right bracket `]'. Placement of each system flag associates it with a specific Oberon-2 construct.

Example:

MODULE Xutil [INTERFACE "C"];
MODULE Files [FOREIGN "C"; LINK FILE "Files.c" END];
MODULE liboo2c [LIBRARY "oo2c" "0:0:0"; INTERFACE "C"];
TYPE R = RECORD [UNION] ... END;
VAR argc- ["_program_argc"]: C.int;
PROCEDURE Foo* (VAR status_in_out[NIL_COMPAT]: INTEGER): INTEGER;

Three types of system flags are permitted: module, declaration, and type.

Declaration flags are written to the right of the name and the export mark. Type flags are placed after the keyword starting the type constructor. Procedure declarations are a special case; declaration flags are placed before the procedure name, and type flags are written in front of its formal parameter list.

Example:

PROCEDURE [decl flags...] Foo* [type flags...] (bar: T; ...);

Splitting the system flags in this way is done to allow a syntactical distinction between properties of the object and properties of the object's type. For example, the linkage name of the procedure is an attribute of the object, whereas the procedure's calling convention influences things like assignment compatibility to procedure variables, and is therefore an attribute of the procedure's type.

System flags are not permitted in standard Oberon-2 modules; they are restricted exclusively to foreign modules. For oo2c, this means they can only be used in modules declared `INTERFACE' or `FOREIGN'.

Module Flags

Module flags have the most complex syntax of the system flags. The extended module header is defined like this:

Module         = "MODULE" ident [ModuleFlags] ";" ...
ModuleFlags    = 
  "[" ["LIBRARY" LibName Version ";"]
      [ "INTERFACE" | "FOREIGN"] CallingConvention {"," ModuleFlag}
      [ ";" "LINK" LinkSection {";" LinkSection} "END" ] "]".
CallingConvention = string.  
ModuleFlag     = "CODE_FILE" | "INIT_FCT" | "GCC_ATTRIB_STDCALL".
LinkSection    = File | Object | Library.
File           = "FILE" string [Options].
Object         = "OBJ" string.
Library        = "LIB" string [DependenceList] [Options].
Options        = "ADD_OPTION" ident ["," ident].
DependenceList = "(" string {"," string} ")".
LibName        = string.
Version        = string.

`INTERFACE' modules are used to access existing C code, and are not required to follow the Oberon-2 typing and heap conventions (see section INTERFACE Modules). On the other hand, `FOREIGN' modules behave exactly like standard Oberon-2 modules, but are implemented in another language (see section FOREIGN Modules). Both of these describe external modules; that is, modules containing declarations of various objects whose actual implementation is provided by means such as C code or a system library. `LIBRARY' headers are used when creating new shared or static libraries with oo2c, and are explained in section Creating Shared or Static Libraries.

The "calling convention" string specifies how procedures declared in this module are to be activated by the compiler. At the moment, the only calling convention supported for all target operating systems is "C". If the target operating system is `Win32', then the calling convention "Pascal" is also available. The default calling convention used is "C" for all targets.

The implementation of a module can be taken from a number of sources: an uncompiled C file, an object file, a library, or an arbitrary mix of these input formats. The `LINK' directive specifies which files must be included, and its options are as follows:

`FILE "foo.c"'
Use external C code from file `foo.c'. oo2c calls the C compiler for this file if either the object file `foo.o' is missing or the source `foo.c' is more recent than `foo.o'. Note that oo2c cannot detect if a file included into `foo.c' has changed. In this case, the user has to remove `foo.o' by hand to trigger a recompilation of the source file. If additional options must be passed to the C compiler to translate the file `foo.c', the necessary arguments can be added to the command line with `ADD_OPTION'. The keyword `ADD_OPTION' is followed by one or two (comma separated) identifiers, which refer to oo2c compiler OPTIONS variables of string type. The values of the variables (if they exist) are added to the argument list of the C compiler invocation.
`OBJ "foo.o"'
Include object file `foo.o' when linking the program. Note that this directive cannot be used in modules that contribute to a library created with `--make-lib'. In other words, only foreign code that is available as source text can be included in `--make-lib' libraries.
`LIB "foo"'
Link the program against library `foo'; that is, add the option `-lfoo' to the argument list when invoking the linker. The user must make sure that the library is in the linker's search path, either by setting the appropriate environment variable, by adjusting the `--ldflags' option, or by using the `ADD_OPTION' mechanism (see below). The last method, `ADD_OPTION', is preferred. All other libraries used directly by library `foo' must also be included in the LIB option, and are listed in parentheses after `foo'. This determines the order of `-l...' arguments for the linker. For example, a library `B' uses definitions from another library `A', and therefore, it must be declared as `LIB "B" ("A")'. That is, `B' relies on `A' and they are to be linked in using `-lB -lA'. To adjust the linker's search path using `ADD_OPTION', the library name is followed by the keyword `ADD_OPTION' and one or two (comma separated) identifiers, which refer to oo2c compiler OPTIONS variables of string type. The value of the first identifier is called the prefix string, and the second is called the suffix string. During compilation, the prefix string is inserted before the linker argument for the library, and if a suffix string is present, its value is inserted after the linker argument. For example, if compiler options are defined as follows:
DEFINE LibX11Prefix := " -L/usr/X11R6/lib -lSM -lICE";
DEFINE LibX11Suffix := "-lsocket -lnsl";
Then, the following command may be used to link in the library `X11':
LINK LIB "X11" ADD_OPTION LibX11Prefix, LibX11Suffix
which translates to the linker flags
 -L/usr/X11R6/lib -lSM -lICE -lX11 -lsocket -lnsl
The prefix string is usually used to extend the linker's library search path, whereas the suffix string is, in this particular case, filled by the configure program with system specific options.

Please note: The file names given after `FILE' or `OBJ' are subject to the usual file search mechanism, unless a directory part is included.

The following flags can be set for a module:

`CODE_FILE'
This flag indicates that a module should be translated into header and code files. For example, the file `Foo.Mod' would be translated both into a header `Foo.h' and code files `Foo.c' and `Foo.d'. The module can contain Oberon-2 procedures with non-empty bodies, which could then be used to provide Oberon-2 implementations of C macros. Without this option, only a header `Foo.h' with the C interface to the declarations in the module is written by the compiler.
`INIT_FCT'
The `INIT_FCT' flag signals that module `Foo.Mod' links in a function void Foo__init(void), which will be called during program startup as part of the normal module initialization.

Type Flags

The following flags can be applied to type definitions:

`NOT_EXTENSIBLE'
The record type cannot be used as base type of another record.
`NO_DESCRIPTOR'
The record or array type has no type descriptor.
`UNION'
Translates the record type into a C union instead of a struct.
`NO_LENGTH_INFO'
The open array type has no length information. Such an array cannot have another open array as its element type.
`STATIC_POINTER'
The pointer has no type tag. If the pointer's base type is a record or an open array with `NO_DESCRIPTOR', this flag is automatically set for the pointer type.
`DISABLE_NEW'
The predefined procedure NEW cannot be applied to this pointer type. To allocate storage for a pointer variable of this type, SYSTEM.NEW or a suitable low-level function of the operating system must be used. This flag is automatically set if the pointer or the base type is marked with `NO_DESCRIPTOR', `NO_LENGTH_INFO', or `STATIC_POINTER'.
`ALIGN1, ALIGN2, ALIGN4, ALIGN8'
Determines the alignment of record fields. By default, record fields of scalar type are aligned at addresses that are a multiple of the type's size in bytes(1). Specifying `ALIGNn' forces the alignment to be at most `n' bytes; that is, all fields that would be aligned with more than `n' bytes are instead aligned at `n' byte boundaries. `ALIGN1' effectively disables all padding between record fields.
`CSTRING'
Setting this flag for a pointer type whose base type is a character array enables C-style array assignment semantics for variables derived from this type. Assigning a character array or string constant to such a pointer variable is legal, and assigns the address (but not the contents) of the array or string to the variable. With this feature, external C functions with string parameters can be called without reverting to the cumbersome SYSTEM.VAL(P,SYSTEM.ADR(a)) construction.

Procedure types and procedure declarations inherit the calling convention specified at the beginning of the module. This can be overridden by including a string as part of the system flags of the type, which indicates the procedure's calling convention.

The special parameter `...' is allowed as the last formal parameter of any procedure declaration without a body part. This parameter corresponds to variable arguments parameters in C, as used, for example, by printf().

With the extended semantics of parameters, it is necessary to adjust the rules for matching parameter lists: two corresponding parameters are required to share the same system flags in order to match.

oo2c uses the default calling convention of the target operating system for standard Oberon-2 procedures. This means that any matching C function can be assigned to an Oberon-2 procedure variable unless the function's calling convention has been overidden. The compiler will prevent an assignment if the calling convention of the procedure variable differs from that of the procedure.

Declaration Flags

The following table lists non-standard properties that apply to declarations in external modules:

Variable Declarations
`NO_DESCRIPTOR'
Applies to variables of record type. A record with this property cannot appear in type tests and type guards, and it cannot be passed to formal parameters that need a type tag.
`STATIC_POINTER'
Applies to record pointers, and means that the pointer's dynamic type is always equal to its static type.
`NO_LENGTH_INFO'
Applies to variables of open array type, and means that the predefined function LEN cannot be called on this variable. Also, the array value cannot be passed to a formal open array parameter that expects to get the length of any open dimensions.
Parameter Declarations
`NO_TYPE_TAG'
Applies to formal variable parameters of record type, and means that it is not accompanied by a type tag. Such a parameter cannot appear in a type test or type guard, and it cannot be passed to a formal parameter that expects to get a type tag. This flag is implicitly set if the record type is marked with `NO_DESCRIPTOR'.
`NO_LENGTH_TAG'
Applies to open array parameters, and means that it cannot be passed as first argument to LEN and cannot be passed to a formal open array parameter that expects to get the length of any open dimensions. If such a parameter is used in a normal Oberon-2 procedure, the compiler cannot create a local copy of the array argument. This means that it cannot guarantee the normal semantics of value parameters. (Recall that value parameters normally follow these rules: local modifications to the parameter stay local, and modifications to the variable that was passed to the parameter are not reflected in the parameter's local value.) In this case, instead of the standard behaviour, the compiler treats the parameter like a read-only variable and prevents local changes to the parameter's value. However, any changes to the original array variable, which was passed to the parameter in the first place, are reflected by the parameter's value. This resembles the semantics of the keyword const when applied to C pointer types. If the array type is marked with `NO_LENGTH_INFO', this flag is implicitly set.
`NIL_COMPAT'
Can be applied to any formal parameter passed by reference, and means that the value NIL can be passed to it.
Linkage Names
Linkage names can be specified by a string literal, which is included in the list of system flags of a variable or procedure declaration. This sets the declaration's C level name. This means that the specified string is used in the emitted C code instead of the name generated by oo2c (usually module name plus two underscores plus declaration name).
Oberon-2 Procedures
Normally, a procedure declaration in an external module is taken to be a declaration of an externally linked procedure definition. That is, such procedure declarations usually have no body. By writing `CODE_FILE' into the module header, it is possible to define standard Oberon-2 procedures, which have a non-empty body part in the module. Such procedures have to be marked with `HAS_BODY'.
Special Code Procedures
A procedure's list of system flags may contain the directive `PROC_ID=n', where `n' is a positive integer constant. This signals the compiler to insert code pattern `n' for every call to this procedure. This is used to implement direct calls of math functions built into the processor, or procedures that cannot be implemented in the usual way (like the oo2c implementation of Exceptions.PUSHCONTEXT). This flag is of use only when the backend is extended to emit code for the new pseudo procedure.

INTERFACE Modules

An interface module describes the Oberon-2 interface to a piece of existing software. In the case of oo2c, this can be a file with C code, an object file, or a library. The existing code is not required to follow the Oberon-2 typing and heap conventions. Therefore, one must assume that the semantics of types, variables, and procedures in such a module are different from their Oberon-2 counterparts.

Names declared in an interface module, with the exception of the module name itself, can contain underscores `_' in place of a character. The default linkage names of variables and procedures are the same as their Oberon-2 names, but without a module prefix. All other names appearing in the module's C header file get a prefix built from the module name followed by two underscores.

None of the record types defined in the module have a type descriptor, and they cannot be extended. Likewise, array types have no type descriptor and open arrays carry no length information. Pointer types have no type tag or length information, meaning that type tests, type guards, and LEN cannot be applied to them. Parameters are passed without any implicit arguments containing a type tag or length information.

The special parameter `...' is permitted as last argument in the formal parameter list of the declaration of a procedure or a procedure type. Note that, in this case, the parameter list has to include at least one normal parameter.

The following examples are taken from the Oberon-2 module `X11.Mod', which defines the interface to the X11 library. The module header looks like this:

MODULE X11 [INTERFACE "C"; 
            LINK LIB "X11" ADD_OPTION LibX11Prefix, LibX11Suffix END];

The first example highlights the basic translation process from a C header file to an Oberon-2 module, but be aware that the translation patterns shown are far from exhaustive. The Oberon-2 counterparts to the base C types in the header are taken from the standard module `C.Mod', which also provides two often used character array types.

From C.Mod:
char* => TYPE charPtr1d* = POINTER TO ARRAY OF char;
char** => TYPE charPtr2d* = POINTER TO ARRAY OF charPtr1d;

typedef unsigned long XID;
=> TYPE XID* = C.longint;

#define None 0L
=> CONST None* = 0;

#define NoEventMask  0L
#define KeyPressMask (1L<<0)  
=> CONST NoEventMask* = {};
=> CONST KeyPressMask* = {0};

#define Bool int
=> TYPE Bool* = C.int;

typedef struct {
        int depth;       /* this depth (Z) of the depth */
        int nvisuals;    /* number of Visual types at this depth */
        Visual *visuals; /* list of visuals possible at this depth */
} Depth;
=> TYPE
  DepthPtr* = POINTER TO Depth;
  Depth* = RECORD
    depth*: C.int;       (* this depth (Z) of the depth *)
    nvisuals*: C.int;    (* number of Visual types at this depth *)
    visuals*: VisualPtr; (* list of visuals possible at this depth *)
  END;
  
extern XFontStruct *XLoadQueryFont(
    Display* display, _Xconst char* name);
=> PROCEDURE XLoadQueryFont* (
    display: DisplayPtr; name: ARRAY OF C.char): XFontStructPtr;

extern char *XFetchBytes(
    Display* display, int* nbytes_return);
=> PROCEDURE XFetchBytes* (
    display: DisplayPtr; VAR nbytes_return: C.int): C.charPtr1d;

extern Status XGetAtomNames(
    Display* dpy, Atom* atoms, int count, char** names_return);
=> PROCEDURE XGetAtomNames* (
    dpy: DisplayPtr; VAR atoms: ARRAY OF Atom;
    count: C.int; VAR names_return: C.charPtr2d): Status;

Most of this kind of interface conversion is fairly straightforward. The most challenging aspect is the handling of pointer types in parameter lists. A C pointer argument can be translated into a number of things: an Oberon-2 pointer type, a variable parameter of the pointer's base type, an open array parameter, or an array pointer. The decision is made depending on the use of the argument in question. We can only give rough guidelines here.

Take, for example, the C function definition

void f(int *a) {...};

The formal parameter `a' could be either an IN/OUT or an OUT argument, which translates to

PROCEDURE f* (VAR a: C.int) ...                      (1)

Or, it could be an array parameter, or an array pointer. In that case, it translates to one of the following alternatives:

PROCEDURE f* (VAR a: ARRAY OF C.int) ...             (2)
PROCEDURE f* (a: POINTER TO ARRAY OF C.int) ...      (3)
PROCEDURE f* (a: ARRAY OF C.int) ...                 (4)

The choice depends on how the function `f' accesses the argument `a', and on whether values passed to this argument are mostly taken from variables or from the heap. If `*a' is used as simple integer variable, it translates to (1). But if `a' refers to an integer array, variant (2) is used, and if it is an integer array stored exclusively on the heap, number (3) might be used. If the array argument passed to `f' is not modified by the function, it can be passed as a value array like in (4); in this case, the C declaration typically adds the prefix const to the parameter.

Now, consider a pointer argument of a structured based type `T':

void f(T *a) {...};

which offers one additional translation variant:

PROCEDURE f* (a: POINTER TO T) ...

Again, whether a pointer value or the variable parameter is used depends on the primary source of the argument. If it is taken exclusively from heap objects, the pointer value is more convenient. Otherwise, it has to be defined as variable parameter of type `T'.

Note that the Oberon-2 declarations shown above are not completely accurate in that it is not possible to use a POINTER type constructor in a formal parameter list. Instead, such types have to be declared beforehand and their name used in the parameter list.

FOREIGN Modules

A foreign module describes the interface of a standard Oberon-2 module implemented in a non-standard way, say, in assembler or C. By default, all declarations are assumed to comply to standard Oberon-2 semantics. All types defined in such a module behave exactly like standard Oberon-2 types, and all the normal operations are applicable to objects declared in a foreign module. The user cannot distinguish a foreign module from a normal Oberon-2 module that has been implemented in the conventional way.

Care must be taken when integrating the implementation of a foreign module with the compiler's run-time system. This is typically done by writing an empty Oberon-2 module with the desired interface, compiling it to C code, and then editing the resulting files.

As a recommended guide, the following steps should be used when writing foreign modules:

  1. Write an empty module `Foo.Mod' with all exported declarations.
  2. Compile it.
  3. Copy the generated file `Foo.c' to a suitable place, and check that the copied file is the one actually used by the compiler, for example, by invoking oowhereis Foo.c.
  4. In `Foo.c', replace the line `#include "Foo.d"' with the contents of the file `Foo.d'.
  5. Modify the module header of `Foo.Mod' to include the proper `FOREIGN' directive, and remove all procedure bodies (including the procedures' END parts). For a module `Foo', the header should look like this:
    MODULE Foo [FOREIGN "C"; LINK FILE "Foo.c" END];
    
    The command oocn --filter --mod2foreign Foo.Mod performs the required changes automatically and writes them into the file `Foo.txt' (see section Source Code Analysis and Transformation).
  6. Fill in all the empty functions in `Foo.c'. Note that all type declarations in function headers should use the `#defines' from `__StdTypes.h' (i.e., CHAR, BOOLEAN, SHORTINT, etc.).

For examples of foreign modules, refer to the implementation of the library modules `Signal', `PosixFileDesc', or `Files'.

Large Arrays of Constants

Some algorithms need large arrays of constant values that cannot be computed by the program itself. Examples of this are the tables used to approximate mathematical functions, or the table of hexadecimal digits of pi used by the Blowfish encryption algorithm. Because such tables are an integral part of these algorithms, it is not acceptable to simply read them from external files.

In Oberon-2, there is basically only one way to create these tables. That is, declare an array variable and write a huge list of assignments to fill the table with the desired values. The problem with this approach is that it is highly inefficient. It usually takes a long time for OOC to compile such a list of assignments, and the generated code is a highly redundant C file that is translated into a large object file.

While it is pointless to undertake any major effort to remedy the former problem (large tables of constants are too infrequent to make it worthwhile), it is possible to enhance the code generator to deal with the latter. Therefore, oo2c has been extended to detect certain kinds of constant tables and translate them to array definitions with initialization parts. However, there are some restrictions:

  1. This mechanism only works for global array variables.
  2. The code to fill the array has to be placed in the module body, preferably at its very beginning.
  3. The code cannot be part of an conditional or loop statement; due to the peculiarities of OOC's intermediate code representation this also implies that it cannot be placed after an ASSERT or HALT.
  4. Any assignment placed after code that might affect the variable is ignored, for example, after a procedure call with unknown side-effects. To be safe, all assignments should be placed at the very beginning of the module body.
  5. There is a fixed upper limit on the number of constant entries (currently this is one million elements).
  6. This mechanism cannot initialize an array of strings; this case is translated into a sequence of string assignments as usual.

An example of this is the module Blowfish(2). In the module body, it initializes a two-dimensional array of LONGINTs with over a thousand elements. All of these assignments are removed by the backend from the code file `Blowfish.c'. Instead, they appear as part of the definition of the array variable in `Blowfish.d', reducing the size of the object file by a significant amount.

Limitations of oo2c

Because the implementation of oo2c is a pre-compiler translating to a high-level language, some run-time checks are only partial supported, or are not supported at all. For the complete list of run-time checks see section Option and Pragma Variables.

`RealOverflowCheck'
oo2c only detects an overflow when using SHORT() to convert a LONGREAL value to REAL. Other overflows might trigger a floating-point exception signal (`SIGFPE') and dump core, or might go by unnoticed, depending on the system.
`OverflowCheck'
oo2c does not support any overflow checks for integers.
`StackCheck'
oo2c cannot detect an overflow of the program stack. If array parameters are managed on a separate stack (see section C Compiler Options), enabling this run-time check makes it possible for the program to detect an overflow of the auxiliary stack.

The error reporting of the math modules `LowReal', `LowLReal', `RealMath', and `LRealMath' is not implemented as described in this reference manual. This is a problem of the math modules, not of the manual. There is no practical reason why the math modules cannot adhere to the specifications; but due to lack of time, correct error reporting has not been implemented yet.

Emacs Mode

oo2c comes with a Oberon-2 major mode for the Free Software Foundation's GNU Emacs, which helps manage Oberon-2 source code. It offers various keyboard shortcuts to insert skeletons for Oberon-2 constructs, locate Oberon-2 files and declarations, compile modules, and to display error messages. It can make the task of writing an Oberon-2 program considerably easier.

All configuration commands mentioned in the subsequent sections are also listed in the file `o2-default.el'. In the distribution archive, it resides in the `src/tools/emacs' directory. After installation, it can be found in the same directory as the file `oberon2.el'.

Installing the Oberon-2 Package

To use the Oberon-2 emacs major-mode, add the following lines to your Emacs initialization file (`~/.emacs'):

;; set load-path to incorporate directory with oberon2.el
(setq load-path (cons "/usr/local/lib/oo2c" load-path))
;; auto load oberon2.el if oberon-2-mode is called
(autoload 'oberon-2-mode "oberon2" "The Oberon-2 major mode." t)
;; set oberon-2-mode as major mode for all files ending in ".Mod"
(setq auto-mode-alist 
        (cons '("\\.Mod$" . oberon-2-mode) auto-mode-alist))

The file `oberon2.el' is installed during installation of OOC, and so it may reside in another location than the path given above; modify the `load-path' setting accordingly. If you are using Emacs version 19.22 or older, replace `"oberon2"' with `"oberon2_18"' in the line `(autoload ...)'. The package `oberon2.el' works only with the `compile.el' package of Emacs 19.28 (or above, I hope). Note that `oberon2_18.el' is an older version of the package, and is no longer maintained; it does not support all the features of the current version.

If you have write permissions to system directories, a simple way to install the Oberon-2 mode for all users on the system is to copy `oberon2.el' into one of the directories of Emacs's load path (e.g., `/usr/lib/emacs/site-lisp'). (To get the list of searched directories on your system, type C-h v load-path in Emacs.) Then, add the above commands for `autoload' and `auto-mode-alist' to the file `default.el'. If no default file exists, you can create one somewhere in Emacs's load path, say, the same directory you used for `oberon2.el'. You could also consider adding the contents of file `o2-default.el' to `default.el'; among other things, it contains the `autoload' commands given above. Assuming that the permissions of both files are correct, all users on the system should have access to the Oberon-2 mode without needing to change any personal initialization files.

Functions of the Oberon-2 Mode

The keyboard shortcuts listed below are available for every buffer in Oberon-2 mode. This list is also available online by pressing C-h m in such a buffer.

Indentation:

RET
Make a newline, but indent like the previous line.
TAB
Indent o2-indent spaces. With a numeric prefix, indent region.
DEL
Convert tabs to spaces while moving backward.
C-c TAB
Add/remove indentation level(s) to region [deprecated, use TAB].

The variable o2-ident determines how many spaces are inserted per indentation level (the default is 2).

Inserting Oberon-2 constructs:

C-c C-c
Comment region.
C-c C-v
Uncomment text around point.
C-c m
MODULE outline.
C-c p
PROCEDURE outline.
C-c t
Type-bound PROCEDURE outline.
C-c C-t
Redefinition of type-bound PROCEDURE.
C-c i
IF ... THEN statement.
C-c C-e
Insert ELSIF.
C-c c
CASE statement.
C-c C-w
WITH statement.
C-c e
Insert ELSE.
C-c b
Insert a |.
C-c f
FOR statement.
C-c w
WHILE statement.
C-c r
REPEAT ... UNTIL statement.
C-c l
LOOP statement.
C-c C-r
RECORD constructor.
C-c h
Comment with various information about the module.

Move by procedure headings:

C-c C-n
Move to next procedure.
C-c C-p
Move to previous procedure.
C-c C-u
Move to procedure in which the present one is nested.
M-C-h
Put mark at end of procedure, and point at the beginning.

Functions to hide procedure bodies and declarations:

C-c C-h
Hide whole procedure.
C-c C-s
Show whole procedure again.
C-c C-l
Hide bodies of all local procedures.
M-x o2-hide-proc
Hide local declarations and the procedure body.
M-x o2-show-proc
Show local declarations and body again.
M-x o2-hide-all
Hide all of buffer except procedure headings.
M-x o2-show-all
Make all text in the buffer visible again.

Managing source code:

C-c C-f
Find file for a given module name.
C-c 4 f
Like C-c C-f, but display in another window.
C-c 5 f
Like C-c C-f, but display in another frame.
C-c C-d
Generate and display the definition of a module.
C-c 4 d
Like C-c C-d, but display in another window.
C-c 5 d
Like C-c C-d, but display in another frame.
C-c .
Display (same window) the definition of an identifier.
C-c 4 .
Display (other window) the definition of an identifier.
C-c 5 .
Display (other frame) the definition of an identifier.
C-c /
Display, and blink to, declaration of identifier under cursor.
C-c ,
Display (same window) a procedure bound to a given type.
C-c 4 ,
Display (other window) a procedure bound to a given type.
C-c 5 ,
Display (other frame) a procedure bound to a given type.
C-c u
Step through all uses of a declaration with C-c '.

All the above functions accept a module's alias name (as declared in the current buffers IMPORT list) instead of the real module name. For further information on C-c . or C-c , use C-h k.

Any of the functions that display files in another window or frame do not change the selected window if the C-u prefix is set. For example, C-u C-c 4 . displays the source of the definition of the given identifier in another window, but the current window stays selected and point stays at the current position.

S-mouse-3 (i.e., shift with right mouse button), similar to C-c /, invokes C-u C-c 4 . with the qualified identifier under the mouse cursor as argument and blink to the found position.

Compiling:

M-c
Compile current buffer.
C-u M-c
Prompt for compile command and compile current buffer.
M-C-c
Run a make on a module.
C-c '
Display the next error.
C-c g
Prompt for module and error position, goto position.

Also, please note the following:

Additional Tips&Tricks

Add `(setq o2-cwd (expand-file-name "dir"))' to `~/.emacs' if you want Emacs to execute oo2c, oob, and so forth in the directory `dir', regardless of the working directory the editor was started from.

Typically, the most often used function is the one that places the cursor at the next error position after a compile. This is bound to the 2-key sequence C-c ' (or C-c `). To bind this function to a single key, say F8, add one of the following lines to `~/.emacs':

   (global-set-key [f8] 'o2-next-error)

which works under X and recent (>=19) versions of Emacs, or

   (global-set-key "[19~" 'o2-next-error)

for text terminals and older versions of Emacs (replace the cryptic string `[19~' by the one that Emacs produces when pressing C-q F8).

If you are working with an X color display, you might try to add the following piece of code to your `~/.emacs' file (for version 19+). It enables the `Font Lock' minor mode for Oberon-2 buffers, colorizing procedure headers, keywords, comments, pragmas, and strings:

(add-hook 'oberon-2-mode-hook 
	  (lambda ()
	    ;(o2-font-lock-hilit-colors)
	    (turn-on-font-lock)))
(setq font-lock-maximum-decoration t)

In case you prefer the color scheme of the `hilit19' package, you should uncomment the function inside the lambda clause above. Note that this will change the colors for all buffers with `Font Lock' enabled, though. `Font Lock' supports different levels of fontification, with rendering of higher levels taking more time to display. The value t selects maximum (and slowest) decoration.

As another option it is possible to enable a pull-down index menu for comfortable navigation in a source module. The index lists all record, procedure, and type-bound procedure declarations of the module. Selecting a menu item will move the cursor to the place of the declaration. This command enables this feature, adding a "Index" pull-down menu to the left of the "Oberon-2" menu:

(add-hook 'oberon-2-mode-hook
          (lambda ()
            (imenu-add-to-menubar "Index")))

Other possible additions to `~/.emacs' are the commands listed below. They put compilation shells into special frames instead of splitting the current frame. The special frames are of height 10 and placed in the upper right corner of the display; they use a smaller font, menu and scroll bars are disabled, and the frame raises itself to the foreground when the mouse cursor enters it and lowers itself when left by the mouse cursor. Please note: This only works with Emacs versions 19.31 and higher. These settings are included in file `o2-default.el'

(if window-system
    (let ((o2-frame-params 
           '((height . 10)
             (unsplittable . t) (menu-bar-lines . 0)
             (left . (- 0)) (top . 0) (user-position . t)
             (font . "5x7") (width . 60) (auto-raise . t) 
             (vertical-scroll-bars . nil) (auto-lower . t)
             (name . "o2-compilation"))))
      (setq special-display-regexps
            `(("^\\*o2-compile.*\\*$" . ,o2-frame-params)
              ("^\\*o2-make.*\\*$" . ,o2-frame-params)))))


Go to the first, previous, next, last section, table of contents. OOCref_17.html100664 1750 1750 6670 6753666342 11253 0ustar sagsag The OOC Reference Manual - Syntax of Text Tokens

Go to the first, previous, next, last section, table of contents.


Syntax of Text Tokens

This section describes the accepted syntax for text tokens used by the various modules within the OOC library. These definitions apply to read operations on text, and to modules like section Module IntStr, section Module RealStr, and section Module LRealStr, which convert between string values and numeric representation.

These may also apply to write operations for text, but there are some cases (like writer.WriteString in section Class Writer (TextRider)) that do not strictly adhere to these definitions. Also note that internal representation of strings is different from text representation of strings.

An identifier, sometimes referred to as a name, has the form

  letter {letter | decimal_digit}

(Note that an underscore `_' is not considered to be part of an identifier, nor is a selector `.')

A string has the form

  """ {non_control_char} """ |
  "'" {non_control_char} "'".

where a non-control char is any character with an ordinal value greater than or equal to a space character (i.e., `non_control_char >= 20X').

A signed whole number (used to represent an integer value) has the form

  ["+" | "-"] decimal_digit {decimal_digit}.

An unsigned hexadecimal number (used to represent an integer value) has the form

  ["+" | "-"] decimal_digit {hex_digit}.

where a hex digit is one of `0..9' or `A..F'. (Note that lower-case letters, `a..f', are not valid hex digits.)

A signed fixed-point real number has the form

  ["+" | "-"] decimal_digit {decimal_digit} ["." {decimal_digit}].

A signed floating-point real number has the form

  ["+" | "-"] decimal_digit {decimal_digit} ["." {decimal_digit}]
              ("E" | "e") ["+" | "-"] decimal_digit {decimal_digit}.

A set constructor has the form

  "{" [set_element {"," set_element}] "}".

where a set element has the form

  set_value [".." set_value].

with set value being an integer number in the range `0..MAX(SET)'.


Go to the first, previous, next, last section, table of contents. OOCref_18.html100664 1750 1750 1517 6753666357 11255 0ustar sagsag The OOC Reference Manual - SYSTEM module

Go to the first, previous, next, last section, table of contents.


SYSTEM module


Go to the first, previous, next, last section, table of contents. OOCref_19.html100664 1750 1750 155157 6753666420 11317 0ustar sagsag The OOC Reference Manual - OOC Error Messages

Go to the first, previous, next, last section, table of contents.


OOC Error Messages

All implementations of OOC try to provide error messages that are as helpful as possible; the problem causing the message should be readily identifiable. Counter examples to this approach are most C compilers. They combine a cryptic error text with a line number and leave it to the programmer to find out what might be wrong.

OOC tries to precisely mark the faulty construct triggering an error. It provides an exact position in the given piece of source code. The error message has to interpreted relative to the context of this file position. Without knowing the reference point, most error messages don't make sense. Therefore, we strongly suggest to use an editor or other tool to display errors together with their context.

Compilation continues after errors. This usually works quite well, but sometimes error recovery will fail and many meaningless error messages will be emitted in succession. Certain kinds of syntax errors can send the compiler down a completely wrong path. In such cases, all but the very first error message should be ignored.

Some of the error texts listed below contain the placeholder character `%'. The compiler will replace the placeholders with identifiers, numbers, or text fragments.

Implementations of OOC may introduce their own errors and warnings, starting at number 500 and ending at 998.

`1: Comment not terminated'
While reading the source code, the scanner found a `(*' with no matching `*)', even after searching to the end of the file.
`2: Illegal character in string'
An unprintable ASCII control code appears in the string. That is, a character with an ASCII code in the range `00X..1FX'. This restriction isn't explicitly stated in the Oberon-2 report, but it is implemented this way by the ETH compilers. Please note: The character `0X' is actually interpreted as end of file marker by the scanner and a string containing it will generate the message `String not terminated'.
`3: String not terminated'
No terminating quote character was found before reaching the end of the line, which matched the one that started the string. Keep in mind that it is not possible to embed the string's quote character in the string (i.e., a `"' cannot occur in `"..."', nor `'' in `'...'') and that a string can't stretch over multiple lines. Please note: This message will also be generated if the string contains the ASCII character `0X', which the scanner uses to mark the end of the file.
`4: No comment started'
The character sequence `*)' was found outside a comment. Because no legal Oberon-2 program can contain this as a symbol sequence, it is assumed that it was intended to terminate a comment.
`5: Illegal cipher'
Any symbol starting with a decimal cipher is considered to be a number. It extends to the first character not in the ranges `0..9' or `A..F', plus a possible suffix `X' or `H'. Without one of those suffixes, only decimal digits are allowed and any character from `A..F' will be considered as an invalid cipher. For a real number's exponent, only the characters `0..9' are valid.
`6: Number out of range'
The value of the numeric constant is too large to be converted into the internal representation. Four cases have to be distinguished: Caution: Hex constants in the range `08000000H..0FFFFFFFFH' would exceed MAX(LONGINT) when interpreted as positive and are actually mapped onto negative values in the range `MIN(LONGINT)..-1' matching the bit pattern of the unsigned constant.
`7: Not a valid character constant'
Character constants have to be in the range `0X' to `0FFX'.
`8: Illegal symbol'
All characters that have no special meaning in Oberon-2 (such as `!', `%', etc.) cause this error message when they appear in the symbol stream. They are only permitted as part of comments or string constants.
`9: Illegal exponent format'
The exponent following the mantissa of a real number has to comply to the syntax `[D|E][+|-]digit{digit}'. This means the exponent marker (`D' for LONGREAL, `E' for REAL) must be followed by an optional sign and a non-empty sequence of decimal digits.
`10: Illegal character'
An underscore cannot be used in identifiers except for within INTERFACE modules and when refering to objects declared in INTERFACE modules.
`11: No pragma command started'
The character sequence `*>' was found without a preceding `<*'.
`12: Nested `<*' not allowed'
The token `<*' was found inside a pragma, although a pragma inside another pragma is not permitted.
`13: IF statement lacks END'
An IF statement appears inside a pragma, but there is no matching END before the end of the file.
`14: No open IF statement'
An ELSIF, ELSE, or END statement appears inside a pragma without any preceding (and still open) IF statement.
`15: ELSE part already defined'
The indicated ELSIF or ELSE statement is part of an IF statement that already defines an ELSE statement.
`16: Pragma stack empty'
At the place of the POP statement, the stack of pragma variables is empty. In order to do a POP, a PUSH has to be done beforehand. Having more PUSHs than POPs is allowed, but the reverse isn't true.
`17: Undeclared pragma variable'
A pragma variable has to be defined before being used in an expression or for the left hand side of a (non-defining) assignment. Such a definition can be done in the configuration file, or in a pragma, by prefixing an assignment statement with the keyword DEFINE. There is also a command line option to introduce defines.
`18: Pragma variable already defined'
Each pragma variable can only be defined exactly once. After its definition, all subsequent assignments have to be non-defining ones. That is, they must not be prefixed with DEFINE.
`19: Value cannot be assigned to % variable'
The initial definition of a pragma variable assigns a type (boolean, integer, or string) to it. All subsequent assignments have to assign values of the same type.
`20: Boolean expression expected'
The expression at the indicated location must evaluate to a boolean value.
`21: Illegal variable name'
The pragma keywords TRUE, FALSE, PUSH, POP, and DEFINE cannot be used as names of pragma variables.
`30: String too long (maximum is % characters)'
The given string value exceeds the hard limit the compiler imposes on the length of string constants. You'll have to split the constant into several smaller ones and concatenate them together in a character array variable.
`31: Warning: String longer than % characters'
The given string value exceeds the soft limit for the length of string constants. Check the documentation of your particular compiler implementation for the implications.
`32: Identifier too long (maximum is % characters)'
The indicated identifier exceeds the hard limit the compiler imposes on the length of identifiers. Replace the name with a smaller one.
`33: Warning: Identifier longer than % characters'
The indicated identifier exceeds the soft limit for the length of identifiers. Check the documentation of your particular compiler implementation for the implications.
`34: Warning: Hexadecimal constant is mapped to negative value'
When hexadecimal constants are greater than the maximum value of the largest integer type, they are mapped onto negative values. For example, if the compiler does not support the HUGEINT type, hex constants in the range `08000000H..0FFFFFFFFH' are mapped onto negative values in the range `MIN(LONGINT)..-1' matching the bit pattern of the constant. If HUGEINT constants are available they are mapped onto the positive HUGEINT values `2^31..2^32-1'. This means that the interpretation of such constants depends on the compiler. Without special precautions modules using them are not portable to systems that support additional, larger integer types.
`35: Malformed module identifier'
A module identifier with a non-empty path prefix must satisfy the regular expression `[a-zA-Z][a-zA-Z0-9]*(:[a-zA-Z][a-zA-Z0-9]*)*'.

The following error messages indicate that the compiler expected a different symbol at the indicated position than it actually got. In other words, the current symbol doesn't fit into the current syntactical context.

`100: Identifier expected'
`109: `=' expected'
`118: `.' expected'
`119: `,' expected'
`120: `:' expected'
`122: `)' expected'
`123: `]' expected'
`124: `}' expected'
`125: OF expected'
`126: THEN expected'
`127: DO expected'
`128: TO expected'
`130: `(' expected'
`134: `:=' expected'
`137: String expected'
`139: `;' expected'
`141: END expected'
`144: UNTIL expected'
`163: MODULE expected'
`166: `*>' expected'
`180: Unexpected symbol'
`181: Factor starts with illegal symbol'
`182: Data type expected'
`183: Statement expected'
`197: Undeclared identifier'
The indicated identifier is not associated to any definition. With the exception of names used as pointer base types (e.g., the name `T' in `POINTER TO T'), all identifiers have to be declared prior to their use. This declaration has to appear in the local scope or in one of the enclosing scopes textually before any using occurrence of the name.
`198: Identifier `%' expected'
The identifier given at the end of a procedure or module has to be the same as the name that was assigned to the respective procedure or module in its heading.
`199: %'
This error message can be filled by the compiler with arbitrary text.
`200: Export only possible on top level'
Only declarations on a module's top level can be part of the public interface of the module. All names defined inside a procedure are local to their respective procedure and are not visible outside.
`201: Can only be exported with `*''
Constants, types, and procedures cannot be exported with `-' because the notion of a restricted, read-only access doesn't make sense for these objects.
`202: Has to be exported like inherited declaration'
A redefinition of a type-bound procedure in an extended type has to be exported if the base definition was marked as exported. In other words, if the type-bound procedure `P' in `T' is exported, then all redefinitions of `P' in extensions of `T' have to be exported as well.
`203: Can't use type constructor here'
Oberon-2 type rules prevent calls of a procedure whose parameter's type is defined by a type constructor. Such a formal parameter won't match any actual parameter. The only exception to this rule is open array parameters, where the actual parameter is required to be array compatible (see Appendix A of the language report) with the formal one.
`204: Receiver has to be a record or a record pointer'
The type of the receiver parameter of a type-bound procedure is restricted to record or record pointer types. In the former case, the receiver has to be a variable parameter, and a value parameter in the latter.
`205: Illegal type for function result'
An Oberon-2 function cannot return a structured result. If a procedure has to pass a record or array value back to the caller, a variable parameter has to be used instead.
`206: Can't use type constructor here'
The type expression denoting the result type of a function procedure has to be the name of an unstructured type. Otherwise, the Oberon-2 type rules would prevent the use of the function as part of an expression.
`207: Illegal pointer base type'
Pointers can only refer to record or array types. An open array can be used as pointer base type. It is not possible to define a pointer to one of the predefined types, to a procedure type, or another pointer.
`208: Open array can't be used here'
Oberon-2 imposes certain restrictions on the use of open array types. Such a type can only appear as type of a procedure parameter (to relax the rules for passing array values to procedures), as pointer base type (to be able to allocate arrays of arbitrary size on the heap), and as element type of another open array (to implement multi-dimensional open arrays). All other applications of open arrays are illegal. An open array type can have a name. That is, a declaration of the form `TYPE S=ARRAY OF CHAR;' is legal.
`209: This has to be an integer constant'
This applies to two cases: Note that wherever a constant value is required, a constant expression can be used.
`210: Arrays of negative length are not allowed'
The length specified for a dimension of an array type has to be a non-negative integer value. A length of zero is allowed even though it isn't possible to access an element of such a variable.
`211: Data type expected'
The name at the indicated location has to refer to a type definition.
`212: This record type cannot be extended'
The given name refers to a record type that cannot serve as a base type for extension. This usually means that the record was defined as part of an interface module for another language (e.g., C). Such a foreign type is not associated with any kind of meta information (i.e., type descriptor), which is necessary to implement type extension.
`213: This has to be a record type'
The name given inside parenthesis after the keyword `RECORD' has to refer to a record type.
`214: Receiver of pointer type has to be a value parameter'
If the type of the receiver of a type-bound procedure is a record pointer, it has to be defined as a value parameter.
`215: Receiver of record type has to be a variable parameter'
If the type of the receiver of a type-bound procedure is a record, it has to be defined as a variable parameter.
`216: Illegal receiver type'
The type of a receiver parameter is restricted to record or pointer to record.
`217: This has to be a top level type'
Any record type serving as an anchor to a type-bound procedure has to be defined on the top level of the current module. It cannot be imported because this would imply a modification of the interface of a type that isn't defined in (and under the control of) the local module. Also, a record defined inside a procedure cannot serve as receiver type because all type-bound procedures have to be global. This is required for the same reason that only global procedures can be assigned to variables: a nested procedure can only be executed in the context of its enclosing procedure, whereas type-bound procedures (and procedure variables) can be activated anywhere.
`218: Type-bound procedure has to be declared on top level'
A type-bound procedure has to be declared on the global level of the module that defines its anchor record. This is required for the same reason that only global procedures can be assigned to variables: a nested procedure can only be executed in the context of its enclosing procedure, whereas type-bound procedures and procedure variables can be activated anywhere.
`219: Multiple forward declaration of same name'
A procedure is forward declared multiple times.
`220: Formal parameters don't match forward declaration'
The formal parameters of the procedure definition do not match the ones of the previous forward declaration. This means that there is a difference in the number of parameters, one of the parameter types or mode (i.e., value or variable), or the result type.
`221: Receiver doesn't match forward declaration'
The receiver type of the procedure definition does not match the previous forward declaration. With the language restrictions on receivers, this can only mean that the forward declaration uses a pointer receiver and the declaration a record, or vice versa; both must use the same kind of receiver.
`222: Export mark differs from forward declaration'
The export status of a procedure definition has to match the forward declaration (if present). Either both of them must have an export mark, or neither.
`223: Formal parameters don't match inherited declaration'
One of the base types of the type-bound procedure's anchor record declares a procedure of the same name, but the formal parameters of both procedures do not match. If the current declaration is intended to be a redefinition of the previous procedure, it is necessary to adjust the formal parameter list. If it is intended as a new procedure, the name has to be changed.
`224: Receiver doesn't match inherited declaration'
One of the base types of the type-bound procedure's anchor record declares a procedure of the same name, but with a receiver of a different mode. With the restrictions on receivers, this can only mean that the base declaration uses a pointer receiver and the current declaration a record, or vice versa. Both must use the same kind of receiver.
`225: Field of this name already declared in extension `%''
The name of the indicated type-bound procedure conflicts with that of a field defined in one of the extensions of its receiver's anchor record. In other words, the type-bound procedure `P' is bound to the record `R' and a record `R0' extending `R' (in the local module) defines a field that is also called `P'. This would imply that the record `R0' actually contains two objects called `P': its own record field and an inherited type-bound procedure. This violates the rule that an identifier has to refer to an unique object in its scope.
`226: This procedure has already been declared in extension `%''
The name of the indicated type-bound procedure conflicts with that of a previously declared procedure bound to one of the extensions of its receiver's anchor record. In other words, the type-bound procedure `P' is bound to the record `R' and a record `R0' extending `R' (in the local module) also defines a type-bound procedure `P', but the latter procedure is declared first. If the order of declaration of the two procedures is reversed (i.e., the procedure bound to the extension declared after the one of the base type), the former would be recognized as a redefinition of the latter and everything would be fine. But when written in the wrong sequence, the single-pass compiler cannot handle this properly and flags it as error.
`227: Not a record (is %)'
The left side of a field or type-bound procedure selector has to be a record or a record pointer value.
`228: Not a pointer (is %)'
The left side of a dereference operator has to be a pointer value.
`229: `%' has no base type'
For a super call of the form `x.P^()', the type of `x' has to be a true extension of another type that also defines the type-bound procedure `P'.
`230: Procedure `%' not declared in base type'
For a super call of the form `x.P^()', the type of `x' has to be a true extension of another type, which provides the the original definition of the type-bound procedure `P'.
`231: Operator not applicable to type `%''
The indicated operator cannot take a value of the given type as an operand.
`232: Value expected instead of a data type'
The name given as an operand refers to a type instead of a value. Type names are only applicable in type constructors, variable and parameter declarations, and certain predefined functions like MIN, MAX, SIZE, and SYSTEM.VAL.
`233: Operand incompatible to left hand side `%''
The operator is not applicable to values of the given types. See Appendix A of the language report for a list of legal argument types for the operator.
`234: % expression expected (instead of %)'
This applies to the following cases:
`235: This item has no memory address'
SYSTEM.ADR is only applicable to variables, procedure names, and string constants.
`236: Lower bound has to be less or equal to upper bound'
If both bounds `a' and `b' of a set constructor `{a..b}' are constant, then `a <= b' has to hold. The compiler assumes `a > b' to be an error because otherwise the result would be the empty set `{}'---which is most likely not what the programmer wanted in the first place. The same holds for a range of labels in a CASE statement.
`237: This has to be a character constant'
If the select expression of a CASE statement is a character value, then the labels of the case branches have to be character constants.
`238: This has to be a constant expression'
The language requires constant values to be used for the right side of a constant declaration, an array's length, the step constant of a FOR statement, and the labels of a CASE statement. A constant expression may contain constant values and applications of predefined operators and functions. For example, the declaration `CONST m=10*MAX(SET);' would be legal and equivalent to `m=310'. Note that every integer constant expression is assigned the smallest integer type containing the given value after the whole expression has been evaluated. For the above example, `m' would be of type INTEGER.
`239: Not assignment compatible to type `%''
The referenced expression is not assignment compatible to a variable of the indicated type. The right side of an assignment statement has to be assignment compatible with the variable on the left side, an argument of a procedure call corresponding to formal value parameter has to be assignment compatible with the type of the parameter, and the argument of an RETURN statement has to be assignment compatible with the result type of its function. Appendix A of the language report lists the rules for assignment compatibility.
`240: This isn't a function procedure'
The definition of proper procedure cannot contain RETURN statements with an argument.
`241: Missing function result'
Every RETURN statement appearing as part of the definition of a function procedure has to have an argument describing the function's result value. The argument has to be assignment compatible to the function's result type.
`242: EXIT not within a LOOP'
The indicated EXIT statement is not part of a LOOP statement. EXIT can only be used inside a LOOP, although it may be nested arbitrarily deep into other statements. An EXIT always refers to the nearest enclosing LOOP.
`243: Not an array (is %)'
The element selector `[...]' may not be used on a variable designator that isn't of array or array pointer type.
`244: This isn't a variable designator'
This applies to the following cases: Note that dereferencing a read-only pointer variable will grant unrestricted access to the pointer's contents.
`245: This is imported read-only'
This applies to the left side of an assignment statement and to variables passed to a VAR parameter as part of a procedure call. This means that the destination variable (or designator) has to be either
  1. imported as read-write (and no following selector accesses a read-only record field), or
  2. the value of a dereferenced pointer variable.
Contrary to a pointer dereference, an element of a read-only array is read-only, just like a field of a read-only record variable.
`246: Too many parameters (maximum is %)'
The number of declared parameters exceeds the compiler's limit. You will have to reduce their number; for example, by moving some of the parameters into a single record, and passing this record to the callee.
`247: Not a procedure (is %)'
The designator to the left of an argument list does not denote a procedure or a procedure variable.
`248: More actual than formal parameters'
The argument list of the procedure call contains more parameters than specified in the procedure's formal parameter list.
`249: Parameter expected'
The argument list of the procedure call contains fewer parameters than specified in the procedure's formal parameter list.
`250: Not array compatible to formal parameter `%''
The actual parameter of the procedure call is not array compatible to the formal value parameter specified in the procedure heading. The formal and actual parameter must either
  1. have the same type, or
  2. the formal parameter is an open array and their element types are array compatible, or
  3. the formal parameter is an ARRAY OF CHAR and the actual parameter a string constant.
Note that a character constant (e.g., "a" or `41X') is also a string constant. For details see Appendix A of the language report.
`251: Not compatible to formal variable parameter `%''
The indicated argument cannot be passed to the corresponding formal variable parameter specified in the procedure heading. For the type of the formal parameter Tf and the type of the actual parameter Ta one of the following statements has to hold: Note that special rules apply for the arguments of predefined procedures of the language.
`252: This isn't a proper procedure'
A function procedure cannot be activated as if it were a proper procedure. That is, unlike C, Oberon-2 does not discard the function's result automatically. In such a case, the result may be discarded by assigning it to an unused variable.
`253: This isn't a function procedure'
A proper procedure cannot be activated as if it were a function.
`254: This has to be a simple identifier'
The control variable of a FOR statement is restricted to local variables (or parameters) of the current procedure, of enclosing procedures, or the module. It is not possible to use an imported variable or a variable designator containing any selectors.
`255: Has to be a nonzero integer constant'
The increment value of a FOR statement must be a nonzero constant value.
`256: Too large with respect to control variable of type `%''
The increment value of a FOR statement has to be included within the range of the type of the control variable.
`257: This variable has no dynamic type'
A type test is only applicable to variables whose dynamic type (i.e., the type during run time) may differ from their static one (i.e., the type specified when compiling). This means that the variable either has to be a record pointer, a dereferenced record pointer, or a variable parameter of record type. Note that record types defined as part of an interface module for another language will lack any Oberon-2 run-time type information. Those records (and pointer types derived from them) cannot be subjected to type tests or type guards.
`258: This isn't a record pointer'
Only record pointers (and variable parameters of record type) can be subjected to type tests or type guards.
`259: This type is no extension of the variable's type'
A type used for a type test or type guard has to be an extension of the tested variable's type. For a record, this means that the variable's type has to be a direct or indirect base type of the given type. For a pointer, this relation has to hold for the pointer base types. Note that testing a variable against its own type is possible, but redundant.
`260: Integer or character expression expected'
The select expression of a CASE statement must be either of type integer, or of type character; boolean, real, or complex expressions are not allowed.
`261: Case label not included in type of case selector'
The case label lies outside the range of values the select expression can possibly assume.
`262: Case labels (%..%) already used'
The given range of values is already assigned to another CASE branch. The labels of any two branches have to be distinct.
`263: Has to be a (qualified) identifier'
The language only allows application of a regional type guard to simple variables. Complex designators (variables followed by a nonempty list of selectors) are not permitted. However, the variable can be imported from another module.
`264: This type has no MIN/MAX value'
The predefined functions MIN and MAX are only applicable to integer, real, and set types. For the numeric types, they return, respectively, the smallest and largest values a variable of the given type can assume. For set types, they return the smallest and largest valid set elements.
`265: Value incompatible with variable'
The second argument of an activation of INC or DEC must be a value that is included in the type of the first argument. If conformant mode is enabled, and the second argument is a non-constant expression, the second argument has to have the same type as the first argument.
`266: This type has no fixed size'
The predefined function SIZE cannot be applied to open array types because these types represent a set of arbitrarily sized variable instantiations during run time. In other words, such types don't have a size. Variables of those types do have a fixed size, but SIZE is not applicable to variables. To get the size of an open array variable, you would have to multiply the size of the array element type by the array's length.
`267: Illegal definition for a previously used pointer base type'
If the base type `T' of a type `POINTER TO T' is defined later in the text, `T' has to be declared as a legal pointer base type. That is, it must be a record or an array type.
`268: Cannot copy this value to `%''
The predefined procedure COPY cannot copy a string composed of LONGCHAR characters to an array of CHAR elements. It can copy towards an array using the same character type, and to a larger character type. In the latter case the function LONG is applied to every character.
`269: Cannot modify value parameter that has no local copy'
For an open array value parameter with `NO_LENGTH_TAG', the compiler cannot create a local copy of the array argument. This means that it cannot guarantee the normal semantics of value parameters. (Recall that value parameters normally follow these rules: local modifications to the parameter stay local, and modifications to the variable that was passed to the parameter are not reflected in the parameter's local value.) In this case, instead of the standard behaviour, the compiler treats the parameter like a read-only variable and prevents local changes to the parameter's value. However, any changes to the original array variable, which was passed to the parameter in the first place, are reflected by the parameter's value. This resembles the semantics of the keyword const when applied to C pointer types.
`280: No information on length of variable available'
It is attempted to perform an operation on an array variable that needs to compute the array's length. This error can occur only in connection with types or procedures defined in interface modules to other languages.
`281: This type has no type descriptor'
An attempted operation on a record variable needs to compute the record's dynamic type, and that type information is not available. This error can occur only in connection with types or procedures defined in interface modules to other languages.
`282: NEW cannot allocate memory for this type'
The predefined function NEW is not applicable to non-standard types; that is, types that do not follow the rules of Oberon-2. Such types are usually introduced by interface modules providing access to programs written in other languages. If the interface does not provide a way to allocate heap objects of this type, you will have to use SYSTEM.NEW.
`300: Unresolved forward declaration'
This applies to both forward declarations of procedures, and to base types of pointers. Every forward declaration of a procedure has to be resolved by a procedure definition of the same name within the same scope. The definition's formal parameters must match the ones of the forward declaration, and both declarations have to share the same export status. For every undeclared type `T' appearing as base type of a `POINTER TO T', there has to be a definition of T as a record or array type within the same scope.
`301: Multiple declaration of same name'
Within a single scope multiple declarations share the same name. This conflicts with the Oberon-2 rule that every object has an unique name within its scope.
`302: `%' imports `%' with illegal key'
The symbol file of the first module contains a key for second module that differs from the one read from the second's symbol file. This usually means that these symbol files are out of sync. Normally, the make facility ensures that the exported and the imported interfaces match, although direct manipulations of the (compiler generated) files and problems with files' time stamps may defeat it. The latter case can happen when different clocks apply for source files and generated files; for example, when the sources are read over NFS and the compiler generated files are put onto a local hard disk. If nothing else helps, the compiler should be run with `--make --all', forcing recompilation of all files whose sources are available.
`303: Can't open/read symbol file of module `%''
The symbol file for this module either does not exist, or the user has no read permissions for it. In the first case, it can be compiled by hand, or by telling the compiler to do a make. The latter case probably means that something is amiss in the compiler installation (contact the person who installed your compiler) or the local setup (check the configuration files and compiler options).
`304: Symbol file `%' starts with illegal key'
The compiler found a file that should contain a module's exported interface, but the file does not start with the required magic number. The file was probabably corrupted and should be deleted.
`305: Unexpected end of symbol file `%''
The symbol file ends without containing all the data expected by the compiler. The file was probably corrupted and should be deleted.
`306: A module cannot import itself'
The name of a module cannot appear as part of its own import list.
`307: Can't find module `%''
During a make, the indicated module name appears in an import list, but neither the module's symbol file nor its sources can be found.
`308: Invalid symbol file format (format id is %)'
The format identifier of the symbol file is not supported by the compiler. This usually means that symbol files of compilers for different target architectures have been mixed up.
`309: This name is already defined in base type `%''
The field name conflicts with the name of a field or type-bound procedure inherited from one of the record's base types. Note that multiple fields, and type-bound procedures, can share the same name as long as their declarations in the base type are not visible within the current module. That is, when the base type is defined in another module and the declarations in question aren't exported.
`310: Invalid symbol file version (version is %)'
The version number of the symbol file format doesn't match the compiler. This usually means that the symbol file was written with an older version of the compiler and that the new compiler has changed the file format. The out-of-date symbol file should be deleted.
`350: Overflow during constant folding'
Evaluation of the constant expression resulted in a value that cannot be represented by the compiler. For an integer expression, this means that the result is not a valid LONGINT (or possibly HUGEINT) value. If it is a real expression, then the resulting value isn't representable for the given real type.
`351: Division by zero'
A constant expression (real or integer) divides by zero.
`352: Constant not representable as %'
An attempt is made to convert a constant expression to a type that cannot hold the expression's value.
`353: Set element out of range %'
Any element index of a set operation has to satisfy the relation `MIN(S) <= e <= MAX(S)', where `S' is the applicable set type. Such errors are detected during compilation if the element index is a constant expression. Otherwise, the compiler inserts appropriate run-time checks (unless disabled).
`354: Index out of range %'
The constant index doesn't denote a valid array element.
`355: Constant parameter out of range %'
A constant value in a valid range is required by the predefined procedures LEN for its dimension argument, and ASSERT and HALT for their trap number argument. For LEN, the constant has to satisfy `0 <= c < dim(T)', where `T' is the type of the array variable. For HALT and ASSERT, the limits depend on the target system.

The following items are warnings generated by the compiler. The only difference to errors is that a warning will not cause termination of a make.

Some explanations regarding warnings about uninitialized variables should be considered: The compiler will try to detect possible uses of a variable in a procedure or module body where the variable has an undefined value. This means that the variable could take on different values depending on the program state and environment, causing the program to behave randomly. In this case, a warning is emitted based upon examination of the possible paths through the statement sequence. The warning is not necessarily appropriate because the analysis does not take guards of conditional statements into account, but rather assumes that every path through an conditional statement can be combined with all paths through any of the subsequent statements. Note that the compiler only checks the data flow of scalar values this way; record and array variables are ignored. The compiler also ignores variable definitions by means of SYSTEM.MOVE when looking for uninitialized variables.

`400: Warning: Module name differs from file name `%''
Although strict correspondence between a module's name and the name of its source file is not required, a name mismatch might lead to confusion. The name given in a module's header determines the names for the generated (symbol and object) files. Also, when the make facility parses an import list, it uses the name from the list to derive the file name. A name mismatch might lead to the situation that a module called `X' is imported as module `Y'. It is advisable to keep module and file names the same.
`401: Warning: Symbol file imported as `%' calls itself `%''
While reading a symbol file for a module `X', it is discovered that the imported module as been compiled with the name `Y'. See warning `400' for reasons to avoid such a name conflict.
`402: Warning: Ignoring last % bytes of file `%''
The symbol file has been parsed successfully, but there are still bytes left in the file. The file has probably been corrupted and should be deleted.
`403: Warning: Parameter name differs from forward declaration'
The language report states that formal parameters of a forward declaration must match that of the procedure definition. However, corresponding parameter names are not required to match. A warning is issued because using different names might lead to confusion.
`404: Warning: Variable is used uninitialized'
The compiler detected the use of a variable that has not been assigned a value beforehand.
`405: Warning: Variable may be used uninitialized'
The compiler detected the potential use of a variable that might not have been assigned a value beforehand.
`406: Warning: Function procedure contains no RETURN statement'
If a function procedure does not contain a RETURN statement, it cannot be left in a legal way. Reaching the end of the function will trigger a run-time check (unless disabled).
`407: Warning: Control reaches end of function procedure'
The compiler detected a potential path through a function procedure that does not end in a RETURN statement. This means that under certain circumstances the end of the function could be reached without a proper return value. Like warnings about undefined variables, this message might not be totally accurate.
`408: Warning: Loop will never terminate'
The LOOP statement does not have any associated EXIT statement, and it also does not contain a RETURN statement. This means that the loop will never terminate unless the program as a whole is aborted.
`409: Warning: Redundant type guard'
This type guard is the same as the static type of the variable. Because the guard asserts that the variable's dynamic type is the same as its static type (or an extension of the static type), this will always be true (unless the variable's value is NIL). In these cases, the type guard can usually be safely removed.
`410: Warning: Type test always evaluates to TRUE'
This type test is the same as the static type of the variable. Because the type test asserts that the variable's dynamic type is the same as its static type (or an extension of the static type), this will always evaluate to TRUE (unless the variable's value is NIL).
`411: Warning: Formal parameter type modified by WITH statement'
This warning is emitted only if conformant mode is enabled. In this case, care must be taken when a regional type guard is applied to a formal parameter. The WITH statement will not only change the parameter's type locally, but also its type in the procedure's formal parameter list. This in turn might break recursive calls to the procedure from within the regional type guard that depend on the type of the parameter as stated in the procedure heading. Note that this is implemented in OOC because OP2 based ETH compilers handle it this way. (This strange behaviour is not warranted by the language report in our opinion.) Disabling conformant mode will restrict effects of WITH statements to the inside of the statement without modifying any formal parameter list.
`412: Warning: Guard never reached'
Whenever testing a variable successively with a regional type guard, it is easy to construct one with branches that will never be reached. Example: `WITH v: P1 DO ... | v: P2 DO ... END', where `P2' is an extension of `P1'. Because `v IS P2' implies `v IS P1', a variable of dynamic type `P2' will always take the first branch and never reach the second. Simply swapping the branches, writing the one that tests for the most special case first, will fix this.
`413: Warning: Cast converts between types of different size'
The results are unpredictable if a type cast (i.e., SYSTEM.VAL) casts between types of different sizes. Such a cast depends on the storage layout and the byte ordering of the target system and generally should be avoided.
`414: Warning: Procedure may read uninitialized `%''
The compiler detected the potential use of a local variable during the activation of a nested procedure that might not have been assigned a value beforehand. [NOTE: This warning has been disabled because it is also emitted if a local procedure writes to a variable of the caller that isn't defined at the place of the call, even if the called procedure never reads this undefined variable. For technical reasons the compiler can't currently suppress this misleading warning.]
`415: Warning: Variable parameter may be used uninitialized'
The compiler detected the potential use of a local variable through a variable parameter that might not have been assigned a value beforehand.
`416: Warning: Call may change guarded variable `%''
It is possible to circumvent a regional type guard by calling a procedure that has direct access (through the scoping rules) to the guarded variable. Because the called procedure may assign any value to the variable, it can change its dynamic type at will, invalidating the guard after the procedure call. The compiler is able to detect that the call of a nested procedure changes a guarded variable and issues this warning. It normally does not recognize such a situation if the called procedure has been imported from another module.
`417: Warning: Cast converts to type with higher alignment'
Casting a variable of, say, alignment 2, to a type with an alignment of 4 may cause a run-time error if the variable is only 2-aligned by chance and the target architecture does not allow misaligned accesses. Generally such a situation should be avoided.
`418: Warning: Defining an array of size zero'
The indicated type definition specifies a length of zero for one of the array dimensions. This will create an array of size zero. While such an array variable is legal, it isn't possible to access an element of a variable of this type. However, such a variable can be passed to an open array parameter.
`419: Warning: Allocating an array of size zero'
The indicated call to NEW allocates an array with a length of zero for the given dimension. This will allocate an array of size zero. While this isn't considered an error, it isn't possible to access an element of a heap object of this type. However, such an object can be passed to an open array parameter.
`420: Warning: Unused object'
The designated name is never used anywhere in the program. Therefore, its declaration can safely be removed without invalidating the module. Note that the compiler only checks that there is no using occurrence of the name anywhere. If one exists, the declaration is assumed to be used. For this reason, recursive data types are never marked as unused because the record type refers to the pointer type and vice versa, providing uses for both the record and the pointer type even if they don't appear anywhere else.
`450: Type must not be abstract'
The indicated type is abstract and cannot be instantiated. Abstract types cannot be used for variable, record field, or array type declarations. A pointer to an abstract type cannot be used as an argument to the NEW procedure.
`451: Type-bound procedure `%' still abstract'
The indicated type is concrete and has not implemented the named inherited abstract method. Concrete types must implement all inherited abstract methods.
`452: Receiver type is not declared "abstract"'
The indicated procedure is declared abstract, but is bound to a concrete type. Abstract procedures may only be bound to abstract types.
`453: No BEGIN section permitted in abstract procedure'
The indicated `BEGIN' statement is illegal because it occurs in an abstract procedure. Abstract procedures cannot contain an implementation.
`454: Super call to abstract procedure'
The indicated procedure is abstract in the base class. It is illegal to call an abstract method via a super call.
`455: Abstract procedure must be exported'
All abstract procedures must be declared with an export mark.
`999: Unexpected compiler termination'
Either the process was killed by an external signal, or the compiler aborted due to an internal run-time error. The latter case should not happen; but if it does, check the compiler's `README' file for information how to report such a bug to the authors.


Go to the first, previous, next, last section, table of contents. OOCref_2.html100664 1750 1750 1532 6753664143 11152 0ustar sagsag The OOC Reference Manual - Part I: The OOC Library

Go to the first, previous, next, last section, table of contents.


Part I: The OOC Library


Go to the first, previous, next, last section, table of contents. OOCref_20.html100664 1750 1750 1764 6753666431 11243 0ustar sagsag The OOC Reference Manual - Copying

Go to the first, previous, next, last section, table of contents.


Copying

For information regarding the GNU General Public License, write to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.


Go to the first, previous, next, last section, table of contents. OOCref_21.html100664 1750 1750 44664 6753666450 11273 0ustar sagsag The OOC Reference Manual - Concept Index

Go to the first, previous, next, last section, table of contents.


Concept Index

6

  • 64-bit data types
  • a

  • abstract class
  • abstract class (definition)
  • ABSTRACT flag
  • abstract method
  • abstract riders, abstract riders
  • ADDRESS
  • arbitrary precision integers
  • ASCII
  • ASCII characters
  • ASSERT
  • Assertions
  • b

  • backspace
  • bell
  • binary input
  • binary readers
  • binary riders, connecting to channels
  • binary riders, constants
  • binary writers
  • browser
  • c

  • carriage return
  • CaseSelectCheck
  • channels
  • channels, abstract class
  • channels, base type
  • channels, binary input
  • channels, constants
  • channels, error
  • channels, in
  • channels, opening
  • channels, out
  • channels, procedures
  • channels, standard
  • channels, text input
  • character arrays
  • character classification
  • character testing
  • character types
  • characters, characters
  • class (definition)
  • classification of characters
  • clock, system
  • code optimization
  • command line options
  • compilation
  • COMPILER
  • compiler operations
  • COMPILER_MAJOR
  • COMPILER_MINOR
  • COMPILER_VERSION
  • complex numbers
  • COMPLEX, mathematical functions
  • conformant mode
  • ConformantMode
  • connecting binary riders to channels
  • connecting text riders to channels
  • connecting unicode riders to channels
  • constants for binary riders
  • constants for text riders
  • constants for unicode riders
  • constants, for files
  • control character
  • conventions
  • converting, integers
  • converting, integers/strings
  • converting, reals, converting, reals
  • converting, reals/strings, converting, reals/strings
  • converting, types
  • d

  • data type (definition)
  • date conversions
  • days, julian
  • DEC
  • delete
  • digit character
  • DIV
  • e

  • Emacs
  • empty string
  • end of line character
  • error filter
  • error message format
  • error messages
  • escape
  • exception examples
  • exception facilities
  • exception handling
  • exception sources, predefined
  • external code
  • f

  • file finder
  • file paths
  • files
  • files, class
  • files, constants
  • files, features
  • files, locators
  • files, methods
  • files, other operations
  • files, reader
  • files, writer
  • FOREIGN module
  • foreign modules
  • form feed
  • FunctResult
  • g

  • garbage collector
  • gc
  • h

  • HALT
  • hexadecimal constants
  • horizontal tabulator
  • i

  • i/o concepts
  • identifier length
  • IdentLength
  • illegal operations
  • INC
  • IndexCheck
  • initialization file
  • Initialize
  • IntDivCheck
  • integer conversions, low level
  • integer conversions, strings
  • integers, arbitrary precision
  • INTERFACE module
  • interfacing with C code
  • iso-latin-1
  • j

  • julian days
  • l

  • language extensions
  • letter character
  • library
  • libtool
  • line feed
  • locators
  • locators, for files
  • long strings
  • LONGCHAR
  • LONGCOMPLEX, mathematical functions
  • LONGREAL, low-level properties
  • LONGREAL, mathematical functions
  • lower-case character
  • m

  • make
  • makefile
  • mappers
  • mappers, standard
  • mappers, text
  • mathematical functions, mathematical functions
  • method (definition)
  • MOD
  • n

  • naming conventions
  • NEW
  • NO_COPY flag
  • non-conformant mode
  • numeric character
  • o

  • Oberon-2 major mode
  • oberon2.el
  • object (definition)
  • object-oriented terms
  • oo2c limitations
  • oo2c, C compiler invocation
  • oo2c, command line options
  • oo2c, configuration
  • oo2c, debugging options
  • oo2c, input files
  • oo2c, installation
  • oo2c, installation flags
  • oo2c, installation paths
  • oo2c, installing garbage collector
  • oo2c, installing libraries
  • oo2c, installing libtool
  • oo2c, installing with run-time checks
  • oo2c, intermediate files
  • oo2c, output files
  • oo2c, system files
  • OOC_EXTENSIONS flag
  • operations, on files
  • option variable
  • OPTIONS
  • OverflowCheck
  • p

  • pragma variable
  • PRAGMAS
  • predefined pragmas
  • predicates on characters
  • procedure redefinition
  • procedure values
  • program arguments
  • program arguments channel
  • r

  • random numbers
  • RangeCheck
  • reader, for files
  • readers, abstract class
  • readers, abstract text, readers, abstract text
  • readers, base type
  • readers, binary
  • readers, text
  • readers, unicode
  • real conversions, low level, real conversions, low level
  • real conversions, strings, real conversions, strings
  • REAL, low-level properties
  • REAL, mathematical functions
  • RealDivCheck
  • RealOverflowCheck
  • record (definition)
  • redirection table
  • riders
  • riders, abstract, riders, abstract
  • riders, binary
  • riders, long
  • riders, text, riders, text
  • riders, unicode
  • run-time checks
  • runtime exception numbers
  • s

  • scanners, abstract text, scanners, abstract text
  • scanners, text
  • scanners, unicode
  • set types
  • shared library
  • signals
  • size of basic types
  • source code analysis
  • source code transformation
  • StackCheck
  • standard channels
  • standard error channel
  • standard input channel
  • standard mappers
  • standard output channel
  • standards
  • static library
  • string constants
  • string conversion types
  • string length
  • string terminator character
  • StringLength
  • strings
  • strings, capitalizing
  • strings, comparing
  • strings, concatenation
  • strings, copying
  • strings, integer conversions
  • strings, length
  • strings, long, strings, long
  • strings, real conversions, strings, real conversions
  • strings, searching
  • symbol file
  • syntax for text tokens
  • system flags
  • SYSTEM.MOVE
  • t

  • TARGET_ADDRESS
  • TARGET_ARCH
  • TARGET_ARCH_MINOR
  • TARGET_BYTE_ORDER
  • TARGET_INTEGER
  • TARGET_OS
  • text (unicode) riders, connecting to channels
  • text (unicode) riders, constants
  • text input
  • text readers
  • text readers, abstract, text readers, abstract
  • text readers, long, text readers, long
  • text riders, connecting to channels
  • text riders, constants
  • text scanners
  • text scanners, abstract, text scanners, abstract
  • text scanners, long, text scanners, long
  • text tokens, syntax
  • text writers
  • text writers, abstract, text writers, abstract
  • text writers, long
  • time conversions
  • time intervals
  • time stamps
  • TypeGuard
  • u

  • unicode, unicode
  • unicode (text) riders, connecting to channels
  • unicode (text) riders, constants
  • upper-case character
  • v

  • vertical tabulator
  • w

  • Warnings
  • whitespace character
  • WITH
  • writer, for files
  • writers, abstract class
  • writers, abstract text, writers, abstract text
  • writers, base type
  • writers, binary
  • writers, text
  • writers, unicode
  • z

  • zero-length arrays

  • Go to the first, previous, next, last section, table of contents. OOCref_22.html100664 1750 1750 6465 6753666510 11246 0ustar sagsag The OOC Reference Manual - Type Index

    Go to the first, previous, next, last section, table of contents.


    Type Index

    c

  • Channel, Channel
  • CompareResults
  • COMPLEX
  • ConvResults, ConvResults, ConvResults, ConvResults, ConvResults, ConvResults, ConvResults
  • d

  • DateTime
  • f

  • File, File
  • FileDesc
  • i

  • Integer
  • Interval
  • l

  • LONGCOMPLEX
  • LongString, LongString
  • m

  • Modes
  • n

  • Number
  • r

  • Reader, Reader, Reader, Reader, Reader, Reader, Reader
  • Rider
  • s

  • ScanClass
  • Scanner, Scanner, Scanner, Scanner
  • ScanState
  • SigHandler
  • SigNumber
  • Source
  • String, String
  • t

  • TimeStamp
  • w

  • Writer, Writer, Writer, Writer, Writer, Writer, Writer

  • Go to the first, previous, next, last section, table of contents. OOCref_23.html100664 1750 1750 45567 6753666525 11303 0ustar sagsag The OOC Reference Manual - Procedure Index

    Go to the first, previous, next, last section, table of contents.


    Procedure Index

    a

  • abs, abs
  • Abs
  • ACKNOWLEDGE
  • add, add
  • AllocateSource
  • Append, Append, Append
  • arccos, arccos, arccos, arccos, arccos, arccos
  • arccosh, arccosh
  • arcsin, arcsin, arcsin, arcsin, arcsin, arcsin
  • arcsinh, arcsinh
  • arctan, arctan, arctan, arctan, arctan, arctan
  • arctan2, arctan2
  • arctanh, arctanh
  • arg, arg
  • Assign, Assign
  • b

  • Base
  • Bool, Bool
  • c

  • CanAppendAll, CanAppendAll
  • CanAssignAll, CanAssignAll
  • CanConcatAll, CanConcatAll
  • CanDeleteAll, CanDeleteAll
  • CanExtractAll, CanExtractAll
  • CanGetClock
  • CanInsertAll, CanInsertAll
  • CanReplaceAll, CanReplaceAll
  • CanSetClock
  • Cap
  • Capitalize, Capitalize
  • Char, Char, Char, Char
  • ClearError, ClearError
  • Close
  • CMPLX, CMPLX
  • Compare, Compare, Compare
  • Concat, Concat
  • conj, conj
  • ConnectReader, ConnectReader, ConnectReader
  • ConnectScanner, ConnectScanner
  • ConnectWriter, ConnectWriter, ConnectWriter
  • ConvertFromString
  • ConvertToString
  • Copy, Copy
  • cos, cos, cos, cos, cos, cos
  • cosh, cosh
  • currentMode
  • CurrentNumber
  • d

  • DateToDays
  • DateToJD
  • DateToTJD
  • DayOfWeek
  • DayOfYear
  • DaysPerMonth
  • DaysToDate
  • Delete, Delete, Delete, Delete
  • Difference
  • Digits10Of
  • div, div
  • Done, Done
  • e

  • Entier
  • Equal, Equal
  • ErrorDescr, ErrorDescr
  • Exists
  • exp, exp, exp, exp, exp, exp
  • exponent, exponent
  • Externalize
  • Extract, Extract, Extract
  • f

  • Factorial
  • FindDiff, FindDiff
  • FindNext, FindNext
  • FindPrev, FindPrev
  • Float
  • Flush
  • FormatInt
  • FormatReal, FormatReal
  • fraction, fraction
  • fractpart, fractpart
  • g

  • GCD
  • GetClock
  • GetDate
  • GetMessage
  • GetModTime
  • GetSeed
  • GetTimeStamp
  • h

  • Hex, Hex
  • i

  • Identifier
  • ImagPart, ImagPart
  • InitInterval
  • InitTimeStamp
  • Insert, Insert, Insert
  • Int, Int, Int, Int
  • Internalize
  • intpart, intpart
  • IntToStr
  • IsCMathException
  • IsControl
  • IsEOL
  • IsExceptionalExecution
  • IsInfinity, IsInfinity
  • IsIntConvException
  • IsLeapYear
  • IsLetter
  • IsLower
  • IsLowException
  • IsNaN, IsNaN
  • IsNumeric
  • IsRConvException, IsRConvException
  • IsRMathException
  • IsUpper
  • IsValidDateTime
  • IsWhiteSpace
  • j

  • JDToDate
  • l

  • Length, Length, Length, Length
  • LengthEngReal, LengthEngReal
  • LengthFixedReal, LengthFixedReal
  • LengthFloatReal, LengthFloatReal
  • LengthInt
  • Line
  • ln, ln, ln, ln, ln, ln
  • Ln, Ln
  • log, log
  • Long
  • LongInt, LongInt, LongInt
  • LongReal, LongReal, LongReal, LongReal
  • LongRealEng
  • LongRealFix
  • m

  • MakeLocalTime
  • Map
  • mul, mul
  • n

  • Name
  • New, New
  • o

  • Odd
  • Old, Old
  • Open, Open
  • p

  • polarToComplex, polarToComplex
  • POPCONTEXT
  • Pos, Pos
  • Power
  • power, power, power, power, power, power
  • pred, pred
  • Product
  • Purge
  • PUSHCONTEXT
  • PutSeed
  • q

  • QuoRem
  • Quotient
  • r

  • Raise
  • RAISE
  • Random
  • Read
  • ReadBool
  • ReadBytes
  • ReadInt
  • ReadLInt
  • ReadLReal
  • ReadNum
  • ReadReal
  • ReadSet
  • ReadString
  • Real, Real, Real, Real
  • RealEng
  • RealFix
  • RealPart, RealPart
  • RealToEng, RealToEng
  • RealToFixed, RealToFixed
  • RealToFloat, RealToFloat
  • RealToStr, RealToStr
  • Register
  • Remainder
  • Rename
  • Replace, Replace, Replace
  • RETRY
  • RND
  • round, round, round, round, round, round
  • s

  • scalarMult, scalarMult
  • scale, scale
  • ScanInt
  • ScanReal, ScanReal
  • Set, Set, Set
  • SetClock
  • SetGregorianStart
  • SetHandler
  • SetLocalTime
  • setMode
  • SetModTime
  • SetReader
  • SetTimeStamp
  • SetUTC
  • SetWriter
  • Short
  • ShortInt, ShortInt
  • sign, sign
  • Sign
  • sin, sin, sin, sin, sin, sin
  • sinh, sinh
  • sqrt, sqrt, sqrt, sqrt, sqrt, sqrt
  • String, String, String, String
  • StrToInt
  • StrToReal, StrToReal
  • StrToTime
  • sub, sub
  • succ, succ
  • Sum
  • synthesize, synthesize
  • t

  • tan, tan, tan, tan, tan, tan
  • tanh, tanh
  • ThisDigit10
  • TimeToStr
  • TJDToDate
  • Tmp
  • trunc, trunc
  • u

  • ulp, ulp
  • v

  • ValueInt
  • ValueReal, ValueReal
  • w

  • WeekNumber
  • Write
  • WriteBool
  • WriteBytes
  • WriteInt
  • WriteLInt
  • WriteLReal
  • WriteNum
  • WriteReal
  • WriteSet
  • WriteString

  • Go to the first, previous, next, last section, table of contents. OOCref_24.html100664 1750 1750 35536 6753666541 11275 0ustar sagsag The OOC Reference Manual - Variable & Constant Index

    Go to the first, previous, next, last section, table of contents.


    Variable & Constant Index

    a

  • accessDenied
  • ack
  • active
  • anonymousFile
  • april
  • args
  • assert:
  • august
  • b

  • bel
  • bigEndian
  • bool, bool
  • bs
  • c

  • can
  • channelClosed, channelClosed
  • char, char
  • closeError, closeError
  • cr
  • d

  • dc1
  • dc2
  • dc3
  • dc4
  • december
  • defReaderOptions, defReaderOptions
  • defScannerOptions, defScannerOptions
  • defWriterOptions, defWriterOptions
  • del
  • derefOfNIL
  • directoryFull
  • dirWriteDenied
  • dle
  • done, done, done, done, done
  • Done:
  • e

  • e
  • elementOutOfRange
  • em
  • endOfFunction
  • enq
  • eol, eol
  • eot
  • equal
  • error, error
  • esc
  • etb
  • etx
  • exception
  • exception:
  • exp1
  • expoMax
  • expoMin
  • extend
  • f

  • february
  • ff
  • fileError
  • freeErrorCode
  • friday
  • fs
  • g

  • greater
  • gs
  • gUnderflow
  • h

  • halt:
  • handlerDefault:
  • handlerError:
  • handlerException:
  • handlerIgnore:
  • ht
  • i

  • i
  • ident, ident
  • IEC559
  • illegalLength
  • inactive
  • indexOutOfRange
  • int, int
  • integerDivByZero
  • integerOverflow
  • interpretBools, interpretBools
  • interpretSets, interpretSets
  • interpretStrings, interpretStrings
  • invalid, invalid, invalid
  • invalidChannel, invalidChannel
  • invalidFormat, invalidFormat, invalidFormat, invalidFormat, invalidFormat
  • invalidTime
  • isDirectory
  • j

  • january
  • july
  • june
  • l

  • large
  • lchar
  • less
  • lf
  • LIA1
  • lident
  • line, line
  • linkLoop
  • littleEndian
  • lline
  • localTime
  • lstring
  • ltab
  • m

  • march
  • maxLengthEol, maxLengthEol, maxLengthEol, maxLengthEol
  • maxSecondParts
  • may
  • modulo
  • monday
  • msecPerDay
  • msecPerHour
  • msecPerMin
  • msecPerSec
  • n

  • nak
  • nameTooLong
  • nativeEndian
  • nModes
  • noBuffering, noBuffering
  • noLength, noLength
  • noMatchingLabel
  • noModTime, noModTime
  • noPosition, noPosition
  • noReadAccess, noReadAccess
  • noRoom, noRoom
  • noSuchFile
  • notDirectory
  • noTmpName, noTmpName
  • notOwner
  • noValidGuard
  • november
  • noWriteAccess, noWriteAccess
  • nul
  • null
  • o

  • october
  • one
  • outOfMemory
  • outOfRange, outOfRange
  • p

  • padding
  • pi, pi
  • places
  • r

  • radix
  • read
  • readAfterEnd, readAfterEnd, readAfterEnd
  • reader
  • readError, readError
  • readOnlyFileSystem
  • real, real
  • realDivByZero
  • realOverflow
  • returnCtrlChars, returnCtrlChars
  • rounds
  • rs
  • runtime:
  • s

  • saturday
  • september
  • set, set
  • si
  • sigabrt
  • sigalrm
  • sigbus
  • sigchld
  • sigcld
  • sigcont
  • sigdil
  • sigemt
  • SigFigs, SigFigs
  • sigfpe
  • sighup
  • sigill
  • siginfo
  • sigint
  • sigio
  • sigiot
  • sigkill
  • siglost
  • sigpipe
  • sigpoll
  • sigpwr
  • sigquit
  • sigsegv
  • sigstkflt
  • sigstop
  • sigsys
  • sigterm
  • sigtrap
  • sigtstp
  • sigttin
  • sigttou
  • sigurg
  • sigusr1
  • sigusr2
  • sigvtalrm
  • sigwinch
  • sigxcpu
  • sigxfsz
  • small
  • so
  • soh
  • sp
  • stackOverflow
  • startMJD
  • startTJD
  • stderr
  • stdin
  • stdout
  • strAllRight
  • strEmpty
  • string, string
  • strOutOfRange
  • strWrongFormat
  • stx
  • sub
  • sunday
  • syn
  • systemEol
  • t

  • tab, tab
  • terminator
  • thursday
  • tooManyFiles
  • tryRead
  • tryWrite
  • tuesday
  • typeAssertFailed
  • typeGuardFailed
  • u

  • undefined, undefined
  • unknown
  • unknownSignal
  • unknownZone
  • us
  • UseGregorian
  • useSignedNumbers, useSignedNumbers
  • v

  • valid
  • valueOutOfRange, valueOutOfRange
  • vt
  • w

  • wednesday
  • write
  • writeError, writeError
  • writer
  • x

  • xoff
  • xon
  • z

  • zero
  • zoneMax
  • zoneMin

  • Go to the first, previous, next, last section, table of contents. OOCref_25.html100664 1750 1750 5632 6753666551 11251 0ustar sagsag The OOC Reference Manual - Program and File Index

    Go to the first, previous, next, last section, table of contents.


    Program and File Index

    a

  • Ascii
  • b

  • BinaryRider
  • c

  • Calendar
  • Channel
  • CharClass
  • ComplexMath
  • ConvTypes
  • e

  • Err
  • f

  • Files
  • i

  • In
  • IntConv
  • Integers
  • IntStr
  • j

  • JulianDay
  • l

  • LComplexMath
  • LongRider
  • LongStrings
  • LowLReal
  • LowReal
  • LRealConv
  • LRealMath
  • o

  • oo2c
  • oob
  • oocn
  • ooef
  • oolibtool
  • oowhereis
  • Out
  • p

  • ProgramArgs
  • r

  • RandomNumbers
  • RealConv
  • RealMath
  • RealStr
  • Rider
  • s

  • StdChannels
  • Strings
  • SysClock
  • t

  • TextRider
  • Time
  • u

  • UnicodeRider

  • Go to the first, previous, next, last section, table of contents. OOCref_3.html100664 1750 1750 14465 6753664156 11210 0ustar sagsag The OOC Reference Manual - OOC Library Overview

    Go to the first, previous, next, last section, table of contents.


    OOC Library Overview

    This part of the manual describes the OOC library, and provides a reference as to the use of these facilities with the OOC compiler.

    The Oberon-2 programming language does not provide built-in facilities for performing common operations such as input/output, string manipulation, mathematical functions and so forth. These facilities are instead implemented in library modules. As such, much of learning about a new Oberon-2 compiler, such as OOC, is discovering how to use those library facilities.

    The designers of the OOC library have attempted to make all modules as easy to use and understand as possible. Module definitions can be viewed with the browser that comes with the OOC compiler; this is an easy way to see what facilities are available in each module.

    However, module definitions are generally not sufficient for a good understanding of all facilities. This manual provides a more comprehensive guide to the OOC library. As with all Oberon-2 modules, library modules must always be imported before they can be used within a client module.

    Standards

    The only available standard for Oberon-2 is described in The Oakwood Guildlines for Oberon-2 Compiler Developers, which will be referred to subsiquently as Oakwood. The Oakwood library does not provide the kind of functionality that OOC's designers wished to provide. However, because Oakwood is the only available standard, these modules have been provided in the OOC library. The names of the Oakwood modules for OOC all begin with "Oak" (e.g., OakIn, OakOut).

    The OOC library also provides replacements for Oakwood modules that contain expanded functionality. That is, OOC provides modules In, Out, Files, and so forth.

    Also, in order to provide consistency, the OOC library attempts to follow these naming conventions:

    ================================================================
    Names for              Start with              Examples
    ----------------------------------------------------------------
    Constants, variables   Lower-case noun         version, wordSize
                           Lower-case adjective    full
     
    Types                  Upper-case noun         File, TextFrame
     
    Procedures             Upper-case verb         WriteString
     
    Functions              Upper-case noun         Position
                           Upper-case adjective    Empty, Equal
     
    Modules                Upper-case noun         Files, TextFrames
    ----------------------------------------------------------------
    

    Definition of Terms

    Standard Oberon-2 terminology closely follows "conventional" programming practices. The Oberon-2 language report describes things using words like procedure and type. Special object-oriented (OO) terms like class and method aren't typically used by the Oberon community. These OO ideas can be described using various combinations of conventional terms; for instance, extensible record or type-bound procedure.

    But it isn't always convenient to use these conventional terms; the object-oriented terms are often more concise and handier to use. Also, there are notable distinctions in the OOC library between modules that provide things like a collection of mathematical functions (that operate on existing types) and true extensible abstract data types (e.g., channels and riders). For these reasons, this section defines how certain terms are to be used throughout the rest of this manual.

    A data type is a simple Oberon-2 type declaration. It may be any type whose internal structure is of no importance to the user, or an alias type that declares an alias name for a basic type like INTEGER.

    A record is a normal Oberon-2 record type declaration. It generally can be used directly to define variables. Operations on records (i.e., procedures) are declared external to the type (e.g., SysClock.DateTime see section Module SysClock)

    A class differs from normal records in that they are extensible and their operations are implemented as type-bound procedures. These are usually declared as a pointer plus record combination and the two types should be considered as a single class. Generally, it is pointless to create a variable of the record type--you can't use it; its contents are undefined.

    A method is simply another term for a type-bound procedure.

    An object is an instance of a class (i.e., a variable whose type is a class).

    An abstract class serves as a pattern from which other classes can be derived. Abstract classes provide an interface, but no implementation (or perhaps a partial implementation). They can never be used to create objects; rather, they must be extended to form concrete subclasses that inherit the interface and then go on to complete the implementation. Abstract classes ensure a consistent design for their subclasses.


    Go to the first, previous, next, last section, table of contents. OOCref_4.html100664 1750 1750 116057 6753664203 11222 0ustar sagsag The OOC Reference Manual - Character & String Handling

    Go to the first, previous, next, last section, table of contents.


    Character & String Handling

    Operations on strings and characters are an important part of many programs. The Oberon-2 language provides various built-in operations on characters and strings, but the OOC library goes on to extend the native facilities of Oberon-2 with a useful set of modules for character and string manipulation.

    Module Ascii

    The Oberon-2 language report defines characters using ASCII (American Standard Code for Information Exchange) representation. Because of this, and for convenience, OOC provides module `Ascii', which defines useful constants corresponding to certain ASCII characters.

    Note that OOC does support the full ISO-Latin-1 character set, which is a strict superset of ASCII, as well as Unicode (via LONGCHAR---see section Additional Data Types)

    ASCII characters can be printable characters, such as letters and digits, and also non-printing characters such as tab and linefeed. ASCII only truly defines 128 characters; this means that the interpretation of the range from `80X' to `0FFX' may vary.

    Constants for all of the standard ASCII names for non-printing characters are provided in module `Ascii':

    CONST
      nul = 00X;     soh = 01X;     stx = 02X;
      etx = 03X;     eot = 04X;     enq = 05X;
      ack = 06X;     bel = 07X;     bs  = 08X;
      ht  = 09X;     lf  = 0AX;     vt  = 0BX;
      ff  = 0CX;     cr  = 0DX;     so  = 0EX;
      si  = 0FX;     dle = 01X;     dc1 = 11X;
      dc2 = 12X;     dc3 = 13X;     dc4 = 14X;
      nak = 15X;     syn = 16X;     etb = 17X;
      can = 18X;     em  = 19X;     sub = 1AX;
      esc = 1BX;     fs  = 1CX;     gs  = 1DX;
      rs  = 1EX;     us  = 1FX;     del = 7FX;
    

    The most commonly used ASCII names have the following meanings:

     bel -- bell
     bs  -- backspace
     ht  -- horizontal tabulator
     vt  -- vertical tabulator
     lf  -- line feed
     ff  -- form feed
     cr  -- carriage return
     esc -- escape
     del -- delete
    

    Also, some often used synonyms are declared in module Ascii:

    CONST 
      sp   = " ";
      xon  = dc1;
      xoff = dc3;
    

    Module CharClass

    Programs that deal with characters and strings often need to perform tests that "classify a character." Is the character a letter? A digit? A whitespace character? and so forth.

    Module CharClass provides a set of boolean function procedures that are used for such classification of values of the type CHAR. All procedures accept a single argument of type CHAR and return a BOOLEAN result.

    Recall that Oberon-2 is defined so that characters are ordered the in the same manner as defined by ASCII. Specifically, all the digits precede all the upper-case letters, and all the upper-case letters precede all the lower-case letters. This assumption is carried over into module CharClass. Also, note that CharClass uses constants defined in module Ascii within many of its procedures (see section Module Ascii)

    For example, the function IsLetter is used to test whether a particular character is one of `A' through `Z' or `a' through `z':

    Out.String("The character '");
    IF CharClass.IsLetter(c) THEN
       Out.Char(c); 
       Out.String("' is a letter."); 
    ELSE
       Out.Char(c); 
       Out.String("' isn't a letter."); 
    END;
    Out.Ln
    

    Please note: None of these predicates are affected by the current localization setting. For example, IsUpper will always test for "A"<=ch & ch<="Z" regardless of whether the locale specifies that additional characters belong to this set or not. The same holds for the compare and capitalization procedures in module Strings.

    Constant: eol
    The implementation-defined character used to represent end-of-line internally by OOC (see section Module Ascii)

    Read-only Variable: systemEol
    An implementation defined string that represents the end-of-line marker used by the target system for text files. systemEol may be more than one character in length, and is not necessarily equal to eol. Note that systemEol is a string; it is always terminated by 0X (i.e., systemEol cannot contain the character `0X').

    Function: IsNumeric (ch: CHAR): BOOLEAN
    Returns TRUE if, and only if, ch is classified as a numeric character (i.e., a decimal digit---`0' through `9').

    Function: IsLetter (ch: CHAR): BOOLEAN
    Returns TRUE if, and only if, ch is classified as a letter.

    Function: IsUpper (ch: CHAR): BOOLEAN
    Returns TRUE if, and only if, ch is classified as an upper-case letter.

    Function: IsLower (ch: CHAR): BOOLEAN
    Returns TRUE if, and only if, ch is classified as a lower-case letter.

    Function: IsControl (ch: CHAR): BOOLEAN
    Returns TRUE if, and only if, ch represents a control function (that is, an ASCII character that is not a printing character).

    Function: IsWhiteSpace (ch: CHAR): BOOLEAN
    Returns TRUE if, and only if, ch represents a space character or other "format effector". IsWhiteSpace returns TRUE for only these characters:

    ` ' -- space (i.e., `Ascii.sp')
    
    `Ascii.ff' -- formfeed
    
    `Ascii.cr' -- carriage return
    
    `Ascii.ht' -- horizontal tab
    
    `Ascii.vt' -- vertical tab
    

    Function: IsEOL (ch: CHAR): BOOLEAN
    Returns TRUE if, and only if, ch is the implementation-defined character used to represent end of line internally.

    Modules Strings and LongStrings

    As string manipulation is so common to programming problems, the OOC library provides additional string operations to those built into Oberon-2. The Oberon-2 language defines a string as a character array containing 0X as an embedded terminator. This means that an ARRAY OF CHAR isn't necessarily a string. The module `Strings' provides string manipulation operations for use on terminated character arrays, whereas module `LongStrings' has operations for terminated arrays of long characters (LONGCHAR---see section Additional Data Types)

    Recall that string literals are sequences of characters enclosed in single (') or double (") quote marks. The opening quote must be the same as the closing quote and must not occur within the string. Passing a string literal of length n as an argument to a procedure expecting an ARRAY OF CHAR delivers n+1 characters to the parameter.

    The number of characters in a string (up to the terminating 0X) is called its length. A string literal of length 1 can be used wherever a character constant is allowed and vice versa.

    Please note: All procedures reading and producing strings expect termination with 0X. The behaviour of a procedure is undefined if one of its input parameters is an unterminated character array. Behavior is also undefined if a negative value is used as an input parameter that represents an array position or a string length.

    Copying and Concatenation

    This section describes procedures that construct a string value, and attempt to assign it to a variable parameter. All of these procedures have the property that if the length of the constructed string value exceeds the capacity of the variable parameter, a truncated value is assigned. The constructed string always ends with a string terminator 0X.

    Also described are procedures that provide for pre-testing of the operation-completion conditions for the copying and concatenation procedures.

    Procedure: Assign (source: ARRAY OF CHAR; VAR destination: ARRAY OF CHAR)
    Procedure: Assign (source: ARRAY OF LONGCHAR; VAR destination: ARRAY OF LONGCHAR)
    This procedure copies the string value of source to destination. It is equivalent to the predefined procedure COPY. Unlike COPY, this procedure can be assigned to a procedure variable.

    Function: CanAssignAll (sourceLength: INTEGER; VAR destination: ARRAY OF CHAR): BOOLEAN
    Function: CanAssignAll (sourceLength: INTEGER; VAR destination: ARRAY OF LONGCHAR): BOOLEAN
    Returns TRUE if a number of characters, indicated by sourceLength, will fit into destination; otherwise returns FALSE.

    Pre-condition: sourceLength is not negative.

    Example:

    VAR source:      ARRAY 6 OF CHAR; 
        destination: ARRAY 4 OF CHAR; 
    
    source := ""; 
    Strings.CanAssignAll (Strings.Length (source), destination);  
       => TRUE
    Strings.Assign (source, destination);  
       => destination = ""
    
    source := "abc"; 
    Strings.CanAssignAll (Strings.Length (source), destination);
       => TRUE
    Strings.Assign (source, destination);  
       => destination = "abc"
    
    source := "abcd"; 
    Strings.CanAssignAll (Strings.Length (source), destination);  
       => FALSE
    Strings.Assign (source, destination);  
       => destination = "abc"
    

    Procedure: Extract (source: ARRAY OF CHAR; startPos, numberToExtract: INTEGER; VAR destination: ARRAY OF CHAR)
    Procedure: Extract (source: ARRAY OF LONGCHAR; startPos, numberToExtract: INTEGER; VAR destination: ARRAY OF LONGCHAR)
    This procedure copies at most numberToExtract characters from source to destination, starting at position startPos in source. An empty string value will be extracted if startPos is greater than or equal to Length(source).

    Pre-condition: startPos and numberToExtract are not negative.

    Function: CanExtractAll (sourceLength, startPos, numberToExtract: INTEGER; VAR destination: ARRAY OF CHAR): BOOLEAN
    Function: CanExtractAll (sourceLength, startPos, numberToExtract: INTEGER; VAR destination: ARRAY OF LONGCHAR): BOOLEAN
    Returns TRUE if there are numberToExtract characters starting at startPos and within the sourceLength of some string, and if the capacity of destination is sufficient to hold numberToExtract characters; otherwise returns FALSE.

    Pre-condition: sourceLength, startPos, and numberToExtract are not negative.

    Example:

    VAR source:      ARRAY 6 OF CHAR; 
        destination: ARRAY 4 OF CHAR; 
    
    source := "abcde"; 
    
    Strings.CanExtractAll (Strings.Length (source), 0, 3, destination);
       => TRUE
    Strings.Extract (source, 0, 3, destination);  
       => destination = "abc"
     
    Strings.CanExtractAll (Strings.Length (source), 3, 2, destination);  
       => TRUE
    Strings.Extract (source, 3, 2, destination);  
       => destination = "de"
    
    Strings.CanExtractAll (Strings.Length (source), 0, 4, destination);  
       => FALSE
    Strings.Extract (source, 0, 4, destination);  
       => destination = "abc"
    
    Strings.CanExtractAll (Strings.Length (source), 2, 4, destination);  
       => FALSE
    Strings.Extract (source, 2, 4, destination);  
       => destination = "cde"
    
    Strings.CanExtractAll (Strings.Length (source), 5, 1, destination);  
       => FALSE
    Strings.Extract (source, 5, 1, destination);  
       => destination = ""
    
    Strings.CanExtractAll (Strings.Length (source), 4, 0, destination);  
       => TRUE
    Strings.Extract (source, 4, 0, destination);  
       => destination = ""
    

    Procedure: Delete (VAR stringVar: ARRAY OF CHAR; startPos, numberToDelete: INTEGER)
    Procedure: Delete (VAR stringVar: ARRAY OF LONGCHAR; startPos, numberToDelete: INTEGER)
    Deletes at most numberToDelete characters from stringVar, starting at position startPos. The string value in stringVar is not altered if startPos is greater than or equal to Length(stringVar).

    Pre-condition: startPos and numberToDelete are not negative.

    Function: CanDeleteAll (stringLength, startPos, numberToDelete: INTEGER): BOOLEAN
    Function: CanDeleteAll (stringLength, startPos, numberToDelete: INTEGER): BOOLEAN
    Returns TRUE if there are numberToDelete characters starting at startPos and within the stringLength of some string; otherwise returns FALSE.

    Pre-condition: stringLength, startPos and numberToDelete are not negative.

    Example:

    VAR stringVar: ARRAY 6 OF CHAR; 
        startPos:  INTEGER; 
     
    stringVar := "abcd";
    Strings.CanDeleteAll (Strings.Length (stringVar), 0, 4);   
       => TRUE
    Strings.Delete (stringVar, 0, 4);   
       => stringVar = ""
     
    stringVar := "abcd";
    Strings.CanDeleteAll (Strings.Length (stringVar), 1, 2);   
       => TRUE
    Strings.Delete (stringVar, 1, 2);   
       => stringVar = "ad"
     
    stringVar := "abcd";
    Strings.CanDeleteAll (Strings.Length (stringVar), 0, 5);   
       => FALSE
    Strings.Delete (stringVar, 0, 5);   
       => stringVar = ""
    

    Procedure: Insert (source: ARRAY OF CHAR; startPos: INTEGER; VAR destination: ARRAY OF CHAR)
    Procedure: Insert (source: ARRAY OF LONGCHAR; startPos: INTEGER; VAR destination: ARRAY OF LONGCHAR)
    Inserts source into destination at position startPos. After the call, destination contains the string that is contructed by first splitting destination at the position startPos and then concatenating the first half, source, and the second half. The string value in destination is not altered if startPos is greater than Length(source). If startPos=Length(source), then source is appended to destination.

    Pre-condition: startPos is not negative.

    Function: CanInsertAll (sourceLength, startPos: INTEGER; VAR destination: ARRAY OF CHAR): BOOLEAN
    Function: CanInsertAll (sourceLength, startPos: INTEGER; VAR destination: ARRAY OF LONGCHAR): BOOLEAN
    Returns TRUE if there is room for the insertion of sourceLength characters from some string into destination starting at startPos; otherwise returns FALSE.

    Pre-condition: sourceLength and startPos are not negative.

    Example:

    VAR source:      ARRAY 6 OF CHAR; 
        destination: ARRAY 8 OF CHAR; 
    
    source := "abc";
    destination := "012"; 
    
    Strings.CanInsertAll (Strings.Length (source), 1, destination);  
       => TRUE
    Strings.Insert (source, 1, destination);  
       => destination = "0abc12"
    
    Strings.CanInsertAll (Strings.Length (source), 3, destination);  
       => TRUE
    Strings.Insert (source, 3, destination);  
       => destination = "012abc"
    
    Strings.CanInsertAll (Strings.Length (source, 4, destination);  
       => FALSE
    Strings.Insert (source, 4, destination);  
       => destination = "012"
     
    source := "abcde"; 
    destination := "012356"; 
    
    Strings.CanInsertAll (Strings.Length (source), 0, destination);  
       => FALSE
    Strings.Insert (source, 0, destination);  
       => destination = "abcde01"
     
    Strings.CanInsertAll (Strings.Length (source), 4, destination);  
       => FALSE
    Strings.Insert (source, 4, destination);  
       => destination = "0123abc"
    

    Procedure: Replace (source: ARRAY OF CHAR; startPos: INTEGER; VAR destination: ARRAY OF CHAR)
    Procedure: Replace (source: ARRAY OF LONGCHAR; startPos: INTEGER; VAR destination: ARRAY OF LONGCHAR)
    Copies source into destination starting at position startPos. The existing character values of destination are overwritten (i.e., replaced by) source's values. Copying stops when all of source has been copied, or when the last character of the string value in destination has been replaced. The string value in destination is not altered if startPos is greater than or equal to Length(source).

    Notice that Replace does not continue past the string terminator 0X in destination. That is, Length(destination) will never be changed by Replace.

    Pre-condition: startPos is not negative.

    Function: CanReplaceAll (sourceLength, startPos: INTEGER; VAR destination: ARRAY OF CHAR): BOOLEAN
    Function: CanReplaceAll (sourceLength, startPos: INTEGER; VAR destination: ARRAY OF LONGCHAR): BOOLEAN
    Returns TRUE if there is room for the replacement of sourceLength characters in destination starting at startPos; otherwise returns FALSE.

    Pre-condition: sourceLength and startPos are not negative.

    Example:

    VAR source, destination: ARRAY 6 OF CHAR; 
    
    source := "ab"; destination := "1234"; 
    Strings.CanReplaceAll (Strings.Length (source), 0, destination);  
       => TRUE
    Strings.Replace (source, 0, destination);  
       => destination = "ab34"
     
    source := "abc"; destination := "1234"; 
    Strings.CanReplaceAll (Strings.Length (source), 2, destination);  
       => FALSE
    Strings.Replace (source, 2, destination);  
       => destination = "12ab"
     
    source := ""; destination := "1234"; 
    Strings.CanReplaceAll (Strings.Length (source), 4, destination);  
       => TRUE
    Strings.Replace (source, 4, destination);  
       => destination = "1234"
    
    source := ""; destination := "1234"; 
    Strings.CanReplaceAll (Strings.Length (source), 5, destination);  
       => FALSE
    Strings.Replace (source, 5, destination);  
       => destination = "1234"
    

    Procedure: Append (source: ARRAY OF CHAR; VAR destination: ARRAY OF CHAR)
    Procedure: Append (source: ARRAY OF LONGCHAR; VAR destination: ARRAY OF LONGCHAR)
    Appends source to destination.

    Function: CanAppendAll (sourceLength: INTEGER; VAR destination: ARRAY OF CHAR): BOOLEAN
    Function: CanAppendAll (sourceLength: INTEGER; VAR destination: ARRAY OF LONGCHAR): BOOLEAN
    Returns TRUE if there is sufficient room in destination to append a string of length sourceLength to the string in destination; otherwise returns FALSE.

    Pre-condition: sourceLength is not negative.

    Example:

    VAR source, destination: ARRAY 6 OF CHAR; 
    
    source := "12"; destination := "abc"; 
    Strings.CanAppendAll (Strings.Length (source), destination);  
       => TRUE
    Strings.Append (source, destination);  
       => destination = "abc12"
    
    source := "123"; destination := "abc"; 
    Strings.CanAppendAll (Strings.Length (source), destination);  
       => FALSE
    Strings.Append (source, destination);  
       => destination = "abc12"
    
    source := "123"; destination := "abcde"; 
    Strings.CanAppendAll (Strings.Length (source), destination);  
       => FALSE
    Strings.Append (source, destination);  
       => destination = "abcde"
    

    Procedure: Concat (source1, source2: ARRAY OF CHAR; VAR destination: ARRAY OF CHAR)
    Procedure: Concat (source1, source2: ARRAY OF LONGCHAR; VAR destination: ARRAY OF LONGCHAR)
    Concatenates source2 onto source1 and copies the result into destination. Note that any previous contents of destination are destroyed by Concat.

    Function: CanConcatAll (source1Length, source2Length: INTEGER; VAR destination: ARRAY OF CHAR): BOOLEAN
    Function: CanConcatAll (source1Length, source2Length: INTEGER; VAR destination: ARRAY OF LONGCHAR): BOOLEAN
    Returns TRUE if there is sufficient room in destination for a two strings of lengths source1Length and source2Length; otherwise returns FALSE.

    Pre-condition: source1Length and source2Length are not negative.

    Example:

    VAR source1, source2: ARRAY 5 OF CHAR; 
        destination: ARRAY 6 OF CHAR; 
    
    source1 := "12"; source2 := "abc"; 
    Strings.CanConcatAll (Strings.Length (source1), 
                          Strings.Length (source2), destination);  
       => TRUE
    Strings.Concat (source1, source2, destination);  
       => destination = "12abc"
     
    source1 := "123"; source2 := "abc"; 
    Strings.CanConcatAll (Strings.Length (source1), 
                          Strings.Length (source2), destination);  
       => FALSE
    Strings.Concat (source1, source2, destination);  
       => destination = "123ab"
    
    source1 := ""; source2 := "abc"; 
    Strings.CanConcatAll (Strings.Length (source1), 
                          Strings.Length (source2), destination);  
       => TRUE
    Strings.Concat (source1, source2, destination);  
       => destination = "abc"
    

    Comparing & Searching Strings

    These procedures provide for the comparison of string values, and for the location of substrings within strings.

    Function: Compare (stringVal1, stringVal2: ARRAY OF CHAR): CompareResults
    Function: Compare (stringVal1, stringVal2: ARRAY OF LONGCHAR): CompareResults
    Returns less, equal, or greater, according as stringVal1 is lexically less than, equal to, or greater than stringVal2.

    Please note: Oberon-2 already contains predefined comparison operators on strings.

    Data type: CompareResults = SHORTINT
    CompareResults and its related constants are used with procedure Compare. The following constants are defined for its value:
    Constant: less
    Constant: equal
    Constant: greater

    Example:

    VAR stringVal1, stringVal2: ARRAY 4 OF CHAR; 
    
    stringVal1 := "abc"; stringVal2 := "abc"; 
    Strings.Compare (stringVal1, stringVal2);  
       => equal
     
    stringVal1 := "abc"; stringVal2 := "abd"; 
    Strings.Compare (stringVal1, stringVal2);  
       => less
     
    stringVal1 := "ab"; stringVal2 := "abc"; 
    Strings.Compare (stringVal1, stringVal2);  
       => less
     
    stringVal1 := "abd"; stringVal2 := "abc"; 
    Strings.Compare (stringVal1, stringVal2);  
       => greater
    

    Function: Equal (stringVal1, stringVal2: ARRAY OF CHAR): BOOLEAN
    Function: Equal (stringVal1, stringVal2: ARRAY OF LONGCHAR): BOOLEAN
    Returns stringVal1=stringVal2. That is, Equal returns TRUE if the string value of stringVal1 is the same as the string value of stringVal2; otherwise, it returns FALSE. Unlike the predefined operator =, this procedure can be assigned to a procedure variable.

    Example:

    VAR stringVal1, stringVal2: ARRAY 4 OF CHAR; 
     
    stringVal1 := "abc"; stringVal2 := "abc"; 
    Strings.Equal (stringVal1, stringVal2);  
       => TRUE
     
    stringVal1 := "abc"; stringVal2 := "abd"; 
    Strings.Equal (stringVal1, stringVal2);  
       => FALSE
     
    stringVal1 := "ab"; stringVal2 := "abc"; 
    Strings.Equal (stringVal1, stringVal2);  
       => FALSE
    

    Procedure: FindNext (pattern, stringToSearch: ARRAY OF CHAR; startPos: INTEGER; VAR patternFound: BOOLEAN; VAR posOfPattern: INTEGER)
    Procedure: FindNext (pattern, stringToSearch: ARRAY OF LONGCHAR; startPos: INTEGER; VAR patternFound: BOOLEAN; VAR posOfPattern: INTEGER)
    This procedure is used to locate a pattern string within another string. It searches forward through stringToSearch for next occurrence of pattern; startPos is the starting position of the search (within stringToSearch).

    If startPos<Length(stringToSearch) and pattern is found, patternFound is returned as TRUE and posOfPattern contains the start position in stringToSearch of pattern (i.e., posOfPattern is in the range

    [startPos..Length(stringToSearch)-1])

    Otherwise, patternFound is returned as FALSE and posOfPattern is unchanged.

    If startPos>Length(stringToSearch)-Length(pattern), then patternFound is returned as FALSE.

    Pre-condition: startPos is not negative.

    Example:

    VAR pattern:        ARRAY 4 OF CHAR; 
        stringToSearch: ARRAY 9 OF CHAR; 
        found: BOOLEAN; 
        posOfPattern: INTEGER; 
    
    pattern := "ab"; stringToSearch := "ababcaba"; 
    Strings.FindNext (pattern, stringToSearch, 0, found, posOfPattern);  
       => TRUE, posOfPattern = 0
    Strings.FindNext (pattern, stringToSearch, 1, found, posOfPattern);  
       => TRUE, posOfPattern = 2
    Strings.FindNext (pattern, stringToSearch, 2, found, posOfPattern);  
       => TRUE, posOfPattern = 2
    Strings.FindNext (pattern, stringToSearch, 3, found, posOfPattern);  
       => TRUE, posOfPattern = 5
    Strings.FindNext (pattern, stringToSearch, 4, found, posOfPattern);  
       => TRUE, posOfPattern = 5
    Strings.FindNext (pattern, stringToSearch, 5, found, posOfPattern);  
       => TRUE, posOfPattern = 5
    Strings.FindNext (pattern, stringToSearch, 6, found, posOfPattern);  
       => FALSE, posOfPattern unchanged
     
    pattern := ""; stringToSearch := "abc"; 
    Strings.FindNext (pattern, stringToSearch, 2, found, posOfPattern);  
       => TRUE, posOfPattern = 2
    Strings.FindNext (pattern, stringToSearch, 3, found, posOfPattern);  
       => FALSE, posOfPattern unchanged
    

    Procedure: FindPrev (pattern, stringToSearch: ARRAY OF CHAR; startPos: INTEGER; VAR patternFound: BOOLEAN; VAR posOfPattern: INTEGER)
    Procedure: FindPrev (pattern, stringToSearch: ARRAY OF LONGCHAR; startPos: INTEGER; VAR patternFound: BOOLEAN; VAR posOfPattern: INTEGER)
    This procedure is used to locate a pattern string within another string. It searches backward through stringToSearch for a previous occurrence of pattern; startPos is the starting position of the search (within stringToSearch).

    If pattern is found, patternFound is returned as TRUE and posOfPattern contains the start position in stringToSearch of pattern (i.e., posOfPattern is in the range [0..startPos]).

    Otherwise, patternFound is returned as FALSE and posOfPattern is unchanged (in this case, the pattern might be found at startPos).

    The search will fail if startPos is negative.

    If startPos>Length(stringToSearch)-Length(pattern) the whole string value is searched.

    Example:

    VAR pattern:        ARRAY 4 OF CHAR; 
        stringToSearch: ARRAY 9 OF CHAR; 
        found: BOOLEAN; 
        posOfPattern: INTEGER; 
    
    pattern := "abc"; stringToSearch := "ababcaba"; 
    Strings.FindPrev(pattern, stringToSearch, 1, found, posOfPattern);
       => FALSE, posOfPattern unchanged
    Strings.FindPrev(pattern, stringToSearch, 2, found, posOfPattern);
       => TRUE, posOfPattern = 2
    Strings.FindPrev(pattern, stringToSearch, 3, found, posOfPattern);
       => TRUE, posOfPattern = 2
     
    pattern := "ab"; stringToSearch := "ababcaba"; 
    Strings.FindPrev(pattern, stringToSearch, 0, found, posOfPattern);
       => TRUE, posOfPattern = 0
    Strings.FindPrev(pattern, stringToSearch, 1, found, posOfPattern);
       => TRUE, posOfPattern = 0
    Strings.FindPrev(pattern, stringToSearch, 2, found, posOfPattern);
       => TRUE, posOfPattern = 2
    Strings.FindPrev(pattern, stringToSearch, 3, found, posOfPattern);
       => TRUE, posOfPattern = 2
    Strings.FindPrev(pattern, stringToSearch, 4, found, posOfPattern);
       => TRUE, posOfPattern = 2
    Strings.FindPrev(pattern, stringToSearch, 5, found, posOfPattern);
       => TRUE, posOfPattern = 5
     
    pattern := ""; stringToSearch := "abc"; 
    Strings.FindPrev(pattern, stringToSearch, -1, found, posOfPattern);
       => FALSE, posOfPattern unchanged
    Strings.FindPrev(pattern, stringToSearch, 0, found, posOfPattern);
       => TRUE, posOfPattern = 0
    Strings.FindPrev(pattern, stringToSearch, 4, found, posOfPattern);
       => TRUE, posOfPattern = 3
    

    Procedure: FindDiff (stringVal1, stringVal2: ARRAY OF CHAR; VAR differenceFound: BOOLEAN; VAR posOfDifference: INTEGER)
    Procedure: FindDiff (stringVal1, stringVal2: ARRAY OF LONGCHAR; VAR differenceFound: BOOLEAN; VAR posOfDifference: INTEGER)
    Compares the string values in stringVal1 and stringVal2 for differences. If they are equal, differenceFound is returned as FALSE; and TRUE otherwise.

    If differenceFound is TRUE, posOfDifference is set to the position of the first difference; otherwise posOfDifference is unchanged.

    Example:

    VAR stringVal1, stringVal2: ARRAY 4 OF CHAR; 
        diffFound: BOOLEAN;
        posOfDiff: INTEGER; 
    
    stringVal1 := "abc"; stringVal2 := "abc"; 
    Strings.FindDiff(stringVal1, stringVal2, diffFound, posOfDiff);
       => FALSE, posOfDifference unchanged
     
    stringVal1 := "ab"; stringVal2 := "ac"; 
    Strings.FindDiff(stringVal1, stringVal2, diffFound, posOfDiff);
       => TRUE, posOfDifference = 1
     
    stringVal1 := "ab"; stringVal2 := "a"; 
    Strings.FindDiff(stringVal1, stringVal2, diffFound, posOfDiff);
       => TRUE, posOfDifference = 1
    

    Miscellaneous Strings Procedures

    Function: Length (stringVal: ARRAY OF CHAR): INTEGER
    Function: Length (stringVal: ARRAY OF LONGCHAR): INTEGER
    Returns the string length of stringVal. This is equal to the number of characters in stringVal up to and excluding the first 0X.

    Example:

    Strings.Length("Hello, world"); 
        => 12
    
    VAR stringVal: ARRAY 6 OF CHAR; 
    stringVal := ""; 
    Strings.Length(stringVal);
        => 0
    stringVal := "12"; 
    Strings.Length(stringVal);
        => 2
    

    Recall that if you instead need the total size of the character array, you should use the standard Oberon-2 function procedure LEN:

    VAR aString: ARRAY 32 OF CHAR;
    aString := "Hello, world";
    LEN(aString)
        => 32
    

    Procedure: Capitalize (VAR stringVar: ARRAY OF CHAR)
    Procedure: Capitalize (VAR stringVar: ARRAY OF LONGCHAR)
    Applies the function CAP to each character of the string value in stringVar.

    Example:

    VAR stringVar: ARRAY 6 OF CHAR; 
    
    stringVar := "abc"; 
    Strings.Capitalize (stringVar);   
       => stringVar = "ABC"
     
    stringVar := "0aB";
    Strings.Capitalize (stringVar);   
       => stringVar = "0AB"
    


    Go to the first, previous, next, last section, table of contents. OOCref_5.html100664 1750 1750 21376 6753664422 11205 0ustar sagsag The OOC Reference Manual - Integer/String Conversion

    Go to the first, previous, next, last section, table of contents.


    Integer/String Conversion

    The OOC Library supplies various procedures to convert between string values and numeric representation. These include procedures for conversions of both INTEGER and LONGINT variables to and from string format.

    As module IntConv is low-level, the average application programmer will most likely find module IntStr more interesting and useful.

    Module ConvTypes

    Module ConvTypes declares common types, and appropriate related constants, which are used in the various string conversion modules.

    Data type: ConvResults = SHORTINT
    Values of type ConvResults are used to express the status of attempts to format a string via the string-to-number conversion procedures. The following constants are defined for its value:

    Constant: strAllRight
    The string format is correct for the corresponding conversion.

    Constant: strOutOfRange
    The string is well-formed but the value cannot be represented.

    Constant: strWrongFormat
    The string is in the wrong format for the conversion.

    Constant: strEmpty
    The given string is empty.

    Data type: ScanClass = SHORTINT
    Values of the type ScanClass are used to classify input to finite state scanners. The following constants are defined for its value:

    Constant: padding
    A leading or padding character at this point in the scan - ignore it.

    Constant: valid
    A valid character at this point in the scan - accept it.

    Constant: invalid
    An invalid character at this point in the scan - reject it.

    Constant: terminator
    A terminating character at this point in the scan (not part of token).

    Data type: ScanState = POINTER TO ScanDesc
    ScanState is the type of lexical scanning control procedures. It has a single field of PROCEDURE type:

    Field: p: PROCEDURE (ch: CHAR; VAR cl: ScanClass; VAR st: ScanState)

    Module IntConv

    Module IntConv provides low-level integer/string conversions.

    Data type: ConvResults
    ConvResults is a local equivalent to ConvTypes.ConvResults. This type has associated constants with the same meanings as in module ConvTypes (see section Module ConvTypes)

    Constants strAllRight, strOutOfRange, strWrongFormat, and strEmpty are all valid values for ConvResults.

    Procedure: ScanInt (inputCh: CHAR; VAR chClass: ConvTypes.ScanClass; VAR nextState: ConvTypes.ScanState)
    Represents the start state of a finite state scanner for signed whole numbers--assigns class of inputCh to chClass and a procedure representing the next state to nextState (see section Module ConvTypes)

    Please note: ScanInt is used by procedures FormatInt and ValueInt.

    Function: FormatInt (str: ARRAY OF CHAR): ConvResults
    Returns the format of the string value for conversion to LONGINT.

    Procedure: ValueInt (str: ARRAY OF CHAR): LONGINT
    If str is well-formed, returns the value corresponding to the signed whole number represented by the string value str. Otherwise, its behavior is undefined.

    Procedure: LengthInt (int: LONGINT): INTEGER
    Returns the number of characters in the string representation of int. This value corresponds to the capacity of an array str, which is of the minimum capacity needed to avoid truncation of the result in the call IntStr.IntToStr(int,str) (see section Module IntStr)

    Procedure: IsIntConvException (): BOOLEAN
    This function returns TRUE if the current process is in the exceptional execution state because of the raising of the IntConv exception; otherwise, it returns FALSE.

    Module IntStr

    Module IntStr provides integer-number/ string conversions for numbers in the form of signed whole numbers (see section Syntax of Text Tokens).

    Data type: ConvResults
    ConvResults is a local equivalent to ConvTypes.ConvResults. This type has associated constants with the same meanings as in module ConvTypes (see section Module ConvTypes)

    Constants strAllRight, strOutOfRange, strWrongFormat, and strEmpty are all valid values for ConvResults.

    Procedure: StrToInt (str: ARRAY OF CHAR; VAR int: LONGINT; VAR res: ConvResults)
    This procedure converts a string to an integer value. StrToInt ignores any leading spaces in str. If the subsequent characters in str are in the format of a signed whole number, it assigns a corresponding value to int.

    res indicates the result of the conversion based on the format of str.

    Example:

    VAR stringVar: ARRAY 32 OF CHAR; 
        intVar:    LONGINT;
        res:       IntStr.ConvResults;
    
    stringVar := "   54321"; 
    IntStr.StrToInt(stringVar, intVar, res);
       => intVar = 54321, res = strAllRight
    
    stringVar := "12345678901234567890"; 
    IntStr.StrToInt(stringVar, intVar, res);
       => intVar is undefined, res = strOutOfRange
    
    stringVar := "54321.0"; 
    IntStr.StrToInt(stringVar, intVar, res);
       => intVar is undefined, res = strWrongFormat
    
    stringVar := "   "; 
    IntStr.StrToInt(stringVar, intVar, res);
       => intVar is undefined, res = strEmpty
    

    Procedure: IntToStr (int: LONGINT; VAR str: ARRAY OF CHAR)
    This procedure converts the value of int to string form and copies the possibly truncated result to str.

    Example:

    VAR stringVar: ARRAY 6 OF CHAR; 
        intVar:    LONGINT;
    
    intVar := 54321;
    IntStr.IntToStr(intVar, stringVar);
       => stringVar = "54321"
    
    intVar := 1234567890;
    IntStr.IntToStr(intVar, stringVar);
       => stringVar = "12345"
    


    Go to the first, previous, next, last section, table of contents. OOCref_6.html100664 1750 1750 56034 6753665077 11214 0ustar sagsag The OOC Reference Manual - Real/String Conversion

    Go to the first, previous, next, last section, table of contents.


    Real/String Conversion

    The OOC Library supplies various procedures to convert between string values and numeric representation (see section Integer/String Conversion) The modules described in this chapter have procedures to convert both REAL and LONGREAL values to and from string format.

    The modules RealConv and LRealConv are both low-level and the average application programmer will most likely find modules RealStr and LRealStr more interesting and useful.

    (Also see section Module ConvTypes)

    Please note: When using the procedures described in this chapter, keep in mind that computer representations of REAL and LONGREAL values are of finite precision. That is, only a limited number of significant digits are stored.

    Module RealConv

    Module RealConv provides low-level REAL/string conversions.

    Constant: SigFigs
    A value representing the accuracy of REALs.
    Data type: ConvResults
    ConvResults is a local equivalent to ConvTypes.ConvResults. This type has associated constants with the same meanings as in module ConvTypes (see section Module ConvTypes)

    Constants strAllRight, strOutOfRange, strWrongFormat, and strEmpty are all valid values for ConvResults.

    Procedure: ScanReal (VAR inputCh: CHAR; VAR chClass: Conv.ScanClass; VAR nextState: ConvTypes.ScanState)
    Represents the start state of a finite state scanner for real numbers--assigns class of inputCh to chClass and a procedure representing the next state to nextState (see section Module ConvTypes)

    Function: FormatReal (VAR str: ARRAY OF CHAR): ConvResults
    Returns the format of the string value for conversion to REAL.

    Function: ValueReal (VAR str: ARRAY OF CHAR): REAL
    If str is well-formed, returns the value corresponding to the real number represented by the string value str. Otherwise, its behavior is undefined.

    Function: LengthFloatReal (VAR real: REAL; VAR sigFigs: INTEGER): INTEGER
    Returns the number of characters in the floating-point string representation of real with sigFigs significant figures. This value corresponds to the capacity of an array str which is of the minimum capacity needed to avoid truncation of the result in the call

    RealStr.RealToFloat(real,sigFigs,str)

    Function: LengthEngReal (VAR real: REAL; VAR sigFigs: INTEGER): INTEGER
    Returns the number of characters in the floating-point engineering string representation of real with sigFigs significant figures. This value corresponds to the capacity of an array str which is of the minimum capacity needed to avoid truncation of the result in the call

    RealStr.RealToEng(real,sigFigs,str)

    Function: LengthFixedReal (VAR real: REAL; VAR place: INTEGER): INTEGER
    Returns the number of characters in the fixed-point string representation of real rounded to the given place relative to the decimal point. This value corresponds to the capacity of an array str which is of the minimum capacity needed to avoid truncation of the result in the call

    RealStr.RealToFixed(real,sigFigs,str)

    Function: IsRConvException (): BOOLEAN
    This function returns TRUE if the current process is in the exceptional execution state because of the raising of the RealConv exception; otherwise, returns FALSE.

    Module RealStr

    Module RealStr provides real number/ string conversions for REAL values. Two text formats for real numbers are supported: signed fixed-point real and signed floating-point (see section Syntax of Text Tokens)

    The valid string format of a signed fixed-point real number is

    Data type: ConvResults
    ConvResults is a local equivalent to ConvTypes.ConvResults. This type has associated constants with the same meanings as in module ConvTypes (see section Module ConvTypes)

    Constants strAllRight, strOutOfRange, strWrongFormat, and strEmpty are all valid values for ConvResults.

    Procedure: StrToReal (VAR str: ARRAY OF CHAR; VAR real: REAL; VAR res: ConvResults)
    This procedure converts a string to a real value. StrToReal ignores any leading spaces in str and, depending on the subsequent characters in str, the values of real and res are set as follows:

    If res = strAllRight, str represents a complete signed real number in the range of REAL. The value of this number is assigned to real.

    If res = strOutOfRange, str represents a complete signed real number, but its value is out of the range of REAL. MAX(REAL) or MIN(REAL) is assigned to real depending on the sign of the number.

    If res = strWrongFormat, str is not in the form of a complete signed real number. The value of real is undefined.

    If res = strEmpty, there are no remaining characters in str. The value of real is undefined.

    Example:

    VAR stringVar: ARRAY 36 OF CHAR; 
        realVar:   REAL;
        res:       RealStr.ConvResults;
        
    stringVar := "   76.54321";
    RealStr.StrToReal(stringVar, realVar, res);
       => realVar = 76.54321, res = strAllRight
    
    stringVar := " 76.543E+100";
    RealStr.StrToReal(stringVar, realVar, res);
       => realVar is undefined, res = strOutOfRange
    
    stringVar := "76_54321";
    RealStr.StrToReal(stringVar, realVar, res);
       => realVar is undefined, res = strWrongFormat
    
    stringVar := "   ";
    RealStr.StrToReal(stringVar, realVar, res);
       => realVar is undefined, res = strEmpty
    

    Procedure: RealToFloat (VAR real: REAL; VAR sigFigs: INTEGER; VAR str: ARRAY OF CHAR)
    RealToFloat converts the value of real to floating-point string format and copies the possibly truncated result to str.

    If the value of sigFigs is greater than 0, that number of significant digits is included. Otherwise, an implementation-defined number of significant digits is included. The decimal point is not included if there are no significant digits in the fractional part.

    The number is scaled with one digit in the whole number part. A sign is included only for negative values.

    Example:

    VAR stringVar: ARRAY 32 OF CHAR; 
        realVar:   REAL;
        
    realVar := 3923009;
    RealStr.RealToFloat(realVar, 0, stringVar);
       => stringVar = "3.923009E+6"
    
    RealStr.RealToFloat(realVar, -1, stringVar);
       => stringVar = "3.923009E+6"
    
    RealStr.RealToFloat(realVar, 1, stringVar);
       => stringVar = "4E+6"
    RealStr.RealToFloat(realVar, 2, stringVar);
       => stringVar = "3.9E+6"
    RealStr.RealToFloat(realVar, 5, stringVar);
       => stringVar = "3.9230E+6"
    
    realVar := -39.23009;
    RealStr.RealToFloat(realVar, 1, stringVar);
       => stringVar = "-4E+1"
    RealStr.RealToFloat(realVar, 2, stringVar);
       => stringVar = "-3.9E+1"
    RealStr.RealToFloat(realVar, 5, stringVar);
       => stringVar = "-3.9230E+1"
    
    realVar := 0.0003923009;
    RealStr.RealToFloat(realVar, 1, stringVar);
       => stringVar = "4E-4"
    RealStr.RealToFloat(realVar, 2, stringVar);
       => stringVar = "3.9E-4"
    RealStr.RealToFloat(realVar, 5, stringVar);
       => stringVar = "3.9230E-4"
    

    Procedure: RealToEng (VAR real: REAL; VAR sigFigs: INTEGER; VAR str: ARRAY OF CHAR)
    RealToEng converts the value of real to floating-point string format and copies the possibly truncated result to str.

    If the value of sigFigs is greater than 0, that number of significant digits is included. Otherwise, an implementation-defined number of significant digits is included. The decimal point is not included if there are no significant digits in the fractional part.

    The number is scaled with one to three digits in the whole number part and with an exponent that is a multiple of three. A sign is included only for negative values.

    Example:

    VAR stringVar: ARRAY 32 OF CHAR; 
        realVar:   REAL;
        
    realVar := -3923009;
    RealStr.RealToEng(realVar, 1, stringVar);
       => stringVar = "-4E+6"
    RealStr.RealToEng(realVar, 2, stringVar);
       => stringVar = "-3.9E+6"
    RealStr.RealToEng(realVar, 5, stringVar);
       => stringVar = "-3.9230E+6" 
    
    realVar := 39.23009;
    RealStr.RealToEng(realVar, 1, stringVar);
       => stringVar = "40"
    RealStr.RealToEng(realVar, 2, stringVar);
       => stringVar = "39"
    RealStr.RealToEng(realVar, 5, stringVar);
       => stringVar = "39.230" 
    
    realVar := 0.0003923009;
    RealStr.RealToEng(realVar, 1, stringVar);
       => stringVar = "400E-6"
    RealStr.RealToEng(realVar, 2, stringVar);
       => stringVar = "390E-6"
    RealStr.RealToEng(realVar, 5, stringVar);
       => stringVar = "392.30E-6" 
    

    Procedure: RealToFixed (VAR real: REAL; VAR place: INTEGER; VAR str: ARRAY OF CHAR)
    RealToFixed converts the value of real to fixed-point string format and copies the possibly truncated result to str.

    The value is rounded to the given value of place relative to the decimal point. The decimal point is suppressed if place is less than 0.

    The number will have at least one digit in the whole number part. A sign is included only for negative values.

    Example:

    VAR stringVar: ARRAY 32 OF CHAR; 
        realVar:   REAL;
       
    realVar := 3923009;
    RealStr.RealToFixed(realVar, -5, stringVar);
       => stringVar = "3920000"  (* rounded to the ten-thousands place *)
    RealStr.RealToFixed(realVar, -2, stringVar);
       => stringVar = "3923010"  (* rounded to the tens place *)
    RealStr.RealToFixed(realVar, 1, stringVar);
       => stringVar = "3923009.0"
    RealStr.RealToFixed(realVar, 4, stringVar);
       => stringVar = "3923009.0000" 
    
    realVar := 3923.5;
    RealStr.RealToFixed(realVar, -1, stringVar);
       => stringVar = "3924"  (* rounded to the "ones" place *)
    RealStr.RealToFixed(realVar, 0, stringVar);
       => stringVar = "3924."  (* same as above, 
                            but writes a decimal point *)
    
    realVar := -39.23009;
    RealStr.RealToFixed(realVar, 1, stringVar);
       => stringVar = "-39.2"
    RealStr.RealToFixed(realVar, 4, stringVar);
       => stringVar = "-39.2301"
    
    realVar := 0.0003923009;
    RealStr.RealToFixed(realVar, 1, stringVar);
       => stringVar = "0.0"
    RealStr.RealToFixed(realVar, 4, stringVar);
       => stringVar = "0.0004"
    

    Procedure: RealToStr (VAR real: REAL; VAR str: ARRAY OF CHAR)
    RealToStr converts the value of real to string format and copies the possibly truncated result to str.

    If the sign and magnitude of real can be shown within the capacity of str, RealToStr behaves exactly the same as RealToFixed with a number of decimal places chosen to fill exactly the remainder of str.

    Otherwise, RealToStr behaves as RealToFloat with at least one significant digit. The actual number of significant digits is limited to the number that can be included together with the sign and exponent part in str.

    Example:

    VAR str32Var: ARRAY 32 OF CHAR;
        str10Var: ARRAY 10 OF CHAR;
        realVar:   REAL;
        
    realVar := 3.0;
    RealStr.RealToStr(realVar, str32Var);
       => str32Var = "3.00000000000000000000000000000"  
    RealStr.RealToStr(realVar, str10Var);
       => str10Var = "3.0000000"
    
    realVar := 3.1;
    RealStr.RealToStr(realVar, str32Var);
       => str32Var = "3.10000000000000000000000000000"  
    RealStr.RealToStr(realVar, str10Var);
       => str10Var = "3.1000000"
    
    realVar := 32923009999.;
    RealStr.RealToStr(realVar, str32Var);
       => str32Var = "3923010000.00000000000000000000"
    RealStr.RealToStr(realVar, str10Var);
       => str10Var = "3.9230E+9"
    
    realVar := -39.23009999E+30;  
    RealStr.RealToStr(realVar, str32Var);
       => str32Var = "-3.923010000000000000000000E+31"
    RealStr.RealToStr(realVar, str10Var);
       => str10Var = "-3.92E+31"
    
    realVar := 0.00032923009999;
    RealStr.RealToStr(realVar, str32Var);
       => str32Var = "0.00032923010000000000000000000"
    RealStr.RealToStr(realVar, str10Var);
       => str10Var = "3.9230E-4"
    

    Module LRealConv

    Module LRealConv provides low-level LONGREAL/string conversions.

    Constant: SigFigs
    A value representing the accuracy of LONGREALs.
    Data type: ConvResults
    ConvResults is a local equivalent to ConvTypes.ConvResults. This type has associated constants with the same meanings as in module ConvTypes (see section Module ConvTypes)

    Constants strAllRight, strOutOfRange, strWrongFormat, and strEmpty are all valid values for ConvResults.

    Procedure: ScanReal (VAR inputCh: CHAR; VAR chClass: Conv.ScanClass; VAR nextState: ConvTypes.ScanState)
    Represents the start state of a finite state scanner for real numbers--- assigns class of inputCh to chClass and a procedure representing the next state to nextState (see section Module ConvTypes)

    Function: FormatReal (VAR str: ARRAY OF CHAR): ConvResults
    Returns the format of the string value for conversion to LONGREAL.

    Function: ValueReal (VAR str: ARRAY OF CHAR): LONGREAL
    If str is well-formed, returns the value corresponding to the real number represented by the string value str. Otherwise, its behavior is undefined.

    Function: LengthFloatReal (VAR real: LONGREAL; VAR sigFigs: INTEGER): INTEGER
    Returns the number of characters in the floating-point string representation of real with sigFigs significant figures. This value corresponds to the capacity of an array str which is of the minimum capacity needed to avoid truncation of the result in the call

    LRealStr.RealToFloat(real,sigFigs,str)

    Function: LengthEngReal (VAR real: LONGREAL; VAR sigFigs: INTEGER): INTEGER
    Returns the number of characters in the floating-point engineering string representation of real with sigFigs significant figures. This value corresponds to the capacity of an array str which is of the minimum capacity needed to avoid truncation of the result in the call

    LRealStr.RealToEng(real,sigFigs,str)

    Function: LengthFixedReal (VAR real: LONGREAL; VAR place: INTEGER): INTEGER
    Returns the number of characters in the fixed-point string representation of real rounded to the given place relative to the decimal point. This value corresponds to the capacity of an array str which is of the minimum capacity needed to avoid truncation of the result in the call

    LRealStr.RealToFixed(real,sigFigs,str)

    Function: IsRConvException (): BOOLEAN
    This function returns TRUE if the current process is in the exceptional execution state because of the raising of the LRealConv exception; otherwise, it returns FALSE.

    Module LRealStr

    Please note: Because module LRealStr is very similar to module RealStr and in order to avoid redundancy, full descriptions of procedures and examples of their use are not provided in this section. Refer back to module RealStr for more information (see section Module RealStr)

    Module LRealStr provides real number/ string conversions for LONGREAL values. Two text formats for real numbers are supported: signed fixed-point real and signed floating-point (see section Syntax of Text Tokens)

    Data type: ConvResults
    ConvResults is a local equivalent to ConvTypes.ConvResults. This type has associated constants with the same meanings as in module ConvTypes (see section Module ConvTypes)

    Constants strAllRight, strOutOfRange, strWrongFormat, and strEmpty are all valid values for ConvResults.

    Procedure: StrToReal (VAR str: ARRAY OF CHAR; VAR real: LONGREAL; VAR res: ConvResults)
    This procedure converts a string to a real value. StrToReal ignores any leading spaces in str and, if the subsequent characters in str are in the format of a signed real number, the value is assigned to real. res is assigned a value indicating the format of str.

    Procedure: RealToFloat (VAR real: LONGREAL; VAR sigFigs: INTEGER; VAR str: ARRAY OF CHAR)
    RealToFloat converts the value of real to floating-point string format, with sigFigs significant digits, and copies the possibly truncated result to str.

    Procedure: RealToEng (VAR real: LONGREAL; VAR sigFigs: INTEGER; VAR str: ARRAY OF CHAR)
    RealToEng converts the value of real to floating-point string format, with sigFigs significant digits, and copies the possibly truncated result to str.

    The number is scaled with one to three digits in the whole number part and with an exponent that is a multiple of three.

    Procedure: RealToFixed (VAR real: LONGREAL; VAR place: INTEGER; VAR str: ARRAY OF CHAR)
    RealToFixed converts the value of real to fixed-point string format, rounded to the given value of place relative to the decimal point, and copies the possibly truncated result to str.

    The number will have at least one digit in the whole number part.

    Procedure: RealToStr (VAR real: LONGREAL; VAR str: ARRAY OF CHAR)
    RealToStr converts the value of real to string format and copies the possibly truncated result to str.

    If the sign and magnitude of real can be shown within the capacity of str, RealToStr behaves exactly the same as RealToFixed with a number of decimal places chosen to fill exactly the remainder of str.

    Otherwise, RealToStr behaves as RealToFloat with at least one significant digit. The actual number of significant digits is limited to the number that can be included together with the sign and exponent part in str.


    Go to the first, previous, next, last section, table of contents. OOCref_7.html100664 1750 1750 752435 6753665253 11241 0ustar sagsag The OOC Reference Manual - I/O Subsystem

    Go to the first, previous, next, last section, table of contents.


    I/O Subsystem

    Most programs need to perform input (reading data), output (writing data), or both in order to be useful. The OOC library attempts to simplify these Input/Output (I/O) operations by providing several related abstractions that relate to I/O.

    The two primary abstractions are channels and riders. The entire I/O Subsystem of the OOC library revolves around these two concepts.

    Input/Output Overview

    In order to provide uniform access to different sorts of devices (files, program arguments, sockets, and so forth) the I/O subsystem consists of several interrelated class hierarchies of related abstractions. The two primary abstractions are channels and riders.

    The intention of these abstractions is to allow similar handling of devices; even, potentially, to the level of such exotic devices as a screen pixelmap, a windowing system, or a speech output device.

    The benefit of this unified I/O handling approach allows a programmer to write procedures that operate on any kind of I/O channel. A program writing to stdout could be easily converted to allow writing into a file instead. Or, similarly, it could serve as a remote telnet connection.

    All channels can share the same operations for text based I/O (ReadInt, WriteInt, and so forth). Riders (readers and writers) can then be attached to the channel, allowing standard I/O, regardless of the actual device used.

    I/O Concepts

    There are several conceptual layers to the I/O process that are modeled by various abstractions in the OOC library. Their relationships are shown here:

      data locations - where data resides (raw data).  
          |  (e.g., hard disk, memory block, keyboard port, RS232 links)
          |
          |
      channels - connections to data locations in the form of byte streams.  
          |  (e.g., files - on disk and in memory, pipes, 
          |   TCP/IP connections)
          |
      basic riders - basic operations on bytes.  
          | (e.g., SetPos, ReadByte, ReadBytes, WriteByte, WriteBytes)
          |
          |
      mappers - translations of high level data to and from a byte stream.  
            (e.g., binary reader/writer, text reader/writer)
    

    A data location (or simply location) is a source of input data or destination of output data. It it the physical or logical place where data exists; say a hard disk, or keyboard buffer.

    A channel is a connection to a data location. A channel is envisioned as a contiguous sequence, or stream, of bytes. Channels may be sequential as in the case of terminal I/O, a TCP stream, pipes, and so forth; or positionable like Files and ProgramArgs.

    Riders are associated with a channel and provide read and write access of a location; they operate directly on a stream of bytes (i.e., a channel). Multiple readers and writers can exist for a single channel.

    A mapper is a high-level rider; it operates on a particular format of data, like textual or binary representation of elementary data types. Mappers rely on the primitive operations of basic riders to build more complex operations.

    The benefit of differentiating these layers is allowing a way to distinguish between the simple access layer, that doesn't know a thing about the byte stream being read or written, and the interpretation layer that transforms bytes into useful data.

    Riders and Mappers

    The term rider can be used to describe any operator that provides read or write operations on channels. However, there is a distinction between low-level (basic riders) and high-level operations (mappers).

    Basic riders are associated directly with a particular channel type. Notice that the rider, not the channel, has a position property (the place where reading or writing occurs). Several riders can operate on the same channel at the same time. Riders may provide sequential or positionable (i.e., random) access depending on the type of channel.

    In general, there are only two types of basic riders: readers and writers.

    Mappers are similar to basic riders and, like riders, may be either readers or writers. They translate between a sequence of data items and an uninterpreted sequence of bytes. But mappers may also provide more sophisticated read/write operations; for instance, scanners are mappers that can distinguish between different types of data within a particular format, and then read in that data based on the type. See section Module TextRider and See section Module BinaryRider for descriptions of the simplest mappers.

    Please note: a basic rider is dependent on the implementation of its channel, (e.g., a file rider must know how to position itself within a file). When a channel type is extended, usually the rider must be extended as well.

    Mappers, on the other hand, are independent of a particular channel's implementation; mappers use riders in their implementation. This independence means that every mapper may be used on any compatible rider without the need to implement all combinations of mappers and riders individually.

    Locators and Opening Channels

    Before reading or writing to a location, a connection must be created by opening a channel on the location. The operations for opening channels are collectively called locators. The primary function of locators is to resolve a data location (as specified by a file name, URL, etc.), and then open a channel to that location.

    Locators may be simply a set of functions; for instance:

      PROCEDURE New* (...): ChannelType;
    
      PROCEDURE Old* (...): ChannelType;
    

    For channels that correspond to a location that can be both read and changed, New() will create a new channel for the given data location, deleting all data previously contained in it. Old() will open a channel to existing data.

    For channels representing a unidirectional byte stream (like output to/ input from terminal, or a TCP stream), only a procedure New() is provided. It will create a connection with the designated location.

    The formal parameters of these procedures will normally include some kind of reference to the data being opened (e.g., a file name) and, optionally, flags that modify the way the channel is opened (e.g., read-only, write-only, etc). Their use (and therefore, interface) depends on the type of channel to be opened.

    In more complex circumstances, actual locator types may be required; in that case, the locator type might provide type-bound procedures Old and New to create a new channel.

    When finished reading to or writing from the location, the connection can be terminated by closing the channel ((each channel provides a Close method for this purpose; locators do not supply any close operations). This will free all resources allocated by the system for the channel. Once a channel is closed, no further input or output operations can be performed on it.

    Please note: A channel implementation may limit the number of channels that can be open simultaneously. It's common for an OS to only support a limited number of open files or open sockets at the same time. See individual channel types for these limitations (if such limitations exist for that type).

    Channels

    This section describes the channel types provided by the OOC library. Each module contains both the channel and its associated basic riders. Constant values that are relevant to a particular channel type are also declared within the defining module.

    Module Channel

    Module Channel provides three abstract classes: Channel, Reader, and Writer.

    All types and procedures declared in this module are considered abstract; they are never instanciated or called. Module Channel is of interest, however, because like all abstract classes, its types define the interface elements that are required for any concrete classes, which are derived from them.

    Abstract class Channel is the base for all channel types.

    Abstract classes Reader and Writer are the required basic rider types that must be declared for each channel. Notice that these define only read/ write operations for sequences of bytes (see section Riders and Mappers)

    See the various concrete channel classes for more detail and examples of usage (like section Module Files, section Module StdChannels, or section Module ProgramArgs). In particular, the chapter about Files can be read without any prior knowledge about channels.

    Abstract Class Channel

    Abstract Class: Channel = POINTER TO ChannelDesc
    This is the abstract base channel type. Channel types are used to connect to data locations (see section Input/Output Overview). Channel contains the following fields:

    Field: res-: INTEGER
    res is the result (i.e., error flag) signalling failure of a call to NewReader, NewWriter, Flush, Close, etc. res is initialized to done when the channel is created. Every operation sets this to done if successful, or otherwise, to an appropriate error value to indicate the cause of the error (use method ErrorDescr to get a plain text error description). See section Summary of Channel Constants for a list of applicable error codes.
    Field: readable-: BOOLEAN
    readable is set to TRUE if, and only if, readers can be attached to this channel with NewReader.
    Field: writable-: BOOLEAN
    writable is set to TRUE if, and only if, writers can be attached to this channel with NewWriter.
    Field: open-: BOOLEAN
    open indicates the channel's status; that is, it is set to TRUE on channel creation, and set to FALSE by a call to Close. Closing a channel prevents all further read or write operations on it.
    Method: (ch: Channel) Length (): LONGINT
    Length returns the number of bytes of data for the channel ch. If ch represents a file, then this value is the file's size. If ch has no fixed length (e.g., because it's interactive), it returns noLength.
    Method: (ch: Channel) GetModTime (VAR mtime: Time.TimeStamp)
    GetModTime retrieves the modification time of the data location accessed by channel ch. If no such information is available, ch.res is set to noModTime; otherwise it is set to done.
    Method: (ch: Channel) NewReader (): Reader
    This method attaches a new reader to the channel ch. The reader's position is set to the beginning of the channel, and its res field is initialized to done. ch.res is set to done on success and the new reader is returned. Otherwise, it returns NIL and ch.res is set to indicate the error cause. Please note: if the channel does not support multiple reading positions, the same reader is always returned.
    Method: (ch: Channel) NewWriter (): Writer
    This method attaches a new writer to the channel ch. The writer's position is set to the beginning of the channel, and its res field is initialized to done. ch.res is set to done on success and the new writer is returned. Otherwise, it returns NIL and ch.res is set to indicate the error cause. Please note: if the channel does not support multiple writing positions, the same writer is always returned.
    Method: (ch: Channel) Flush
    Flushes all buffers related to this channel. Any pending write operations are passed to the underlying OS and all buffers are marked as invalid. The next read operation will get its data directly from the channel instead of the buffer. If a writing error occurs, the field ch.res will be changed to writeError, otherwise it's assigned done. Please note: you must check the channel's res flag after an explicit Flush; none of the attached writers will indicate a write error in this case.
    Method: (ch: Channel) Close
    Flushes all buffers associated with ch, closes the channel, and frees all system resources allocated to it. This invalidates all riders attached to ch; they can't be used further. On success, if all read and write operations (including Flush) have completed successfully, ch.res is set to done. An opened channel can only be closed once, successive calls of Close are undefined. Please note: unlike the Oberon System all opened channels have to be closed explicitly. Otherwise resources allocated to them will remain blocked.
    Method: (ch: Channel) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why the previous operation (NewReader, NewWriter, Flush, Close, etc.) failed. The string starts with a capital letter and does not include any termination punctuation. descr should be large enough to hold a multi-line message (256 characters should suffice). If r.res = done, then descr is assigned the empty string.
    Method: (ch: Channel) ClearError
    Sets the result flag ch.res to done.

    Abstract Class Reader

    Abstract Class: Reader = POINTER TO ReaderDesc
    This is the abstract base reader type. Reader types are used to perform read operations on channels (see section Input/Output Overview). Reader contains the following fields:

    Field: base-: Channel
    base refers to the channel the reader is connected to.
    Field: res-: INTEGER
    res is a result (error) flag that signals failure of a call to ReadByte, ReadBytes, or SetPos. res is initialized to done when creating a reader or by calling ClearError. The first failed read operation (or SetPos) changes this to indicate the error, all further calls to ReadByte, ReadBytes, or SetPos will be ignored until ClearError resets this flag. This means that the successful completion of an arbitrary complex sequence of read operations can be ensured by asserting that res equals done beforehand and also after the last operation. Use the method ErrorDescr to get a plain text error description of this error code. See section Summary of Channel Constants for a list of applicable error codes.
    Field: bytesRead-: LONGINT
    bytesRead is set by ReadByte and ReadBytes to indicate the number of bytes that were successfully read.
    Field: positionable-: BOOLEAN
    positionable is set to TRUE if, and only if, the reader can be moved to another position with SetPos; for channels that can only be read sequentially, like input from the keyboard, this is set to FALSE.
    Method: (r: Reader) Pos (): LONGINT
    Returns the current reading position associated with the reader r in channel r.base, i.e., the index of the first byte that is read by the next call to ReadByte or ReadBytes. This procedure returns noPosition if the reader has no concept of a reading position (e.g., if it corresponds to input from keyboard), otherwise the result is non-negative.
    Method: (r: Reader) Available (): LONGINT
    Returns the number of bytes available for the next reading operation. For a file this is the length of the channel r.base minus the current reading position, for an sequential channel (or a channel designed to handle slow transfer rates) this is the number of bytes that can be accessed without additional waiting. The result is -1 if Close() was called for the channel (or the channel has been otherwise disconnected), or no more bytes are available. Please note: the number returned may be an approximation of the number of bytes that could be read at once; it could be lower than the actual value. For some channels or systems, this value may be as low as 1 even if more bytes are waiting to be processed.
    Method: (r: Reader) SetPos (newPos: LONGINT)
    Sets the reading position to newPos. Using a negative value of newPos, or calling this procedure for a reader that doesn't allow positioning, will set r.res to outOfRange. A value larger than the channel's length is legal, but the next read operation will most likely fail with an readAfterEnd error (unless the channel has grown beyond this position in the meantime). Calls to this procedure while r.res # done will be ignored; in particular, a call with r.res = readAfterEnd error will not reset res to done.
    Method: (r: Reader) ReadByte (VAR x: SYSTEM.BYTE)
    Reads a single byte from the channel r.base at the reading position associated with r and places it in x. The reading position is moved forward by one byte on success, otherwise r.res is changed to indicate the error cause. Calling this procedure with the reader r placed at the end (or beyond the end) of the channel will set r.res to readAfterEnd. r.bytesRead will be 1 on success and 0 on failure. Calls to this procedure while r.res # done will be ignored.
    Method: (r: Reader) ReadBytes (VAR x: ARRAY OF SYSTEM.BYTE; start, n: LONGINT)
    Reads n bytes from the channel r.base at the reading position associated with r and places them in x beginning at index start. The reading position is moved forward by n bytes on success, otherwise r.res is changed to indicate the error cause. Calling this procedure with the reader r positioned less than n bytes before the end of the channel will will set r.res to readAfterEnd. r.bytesRead will hold the number of bytes that were actually read (being equal to n on success). Calls to this procedure while r.res # done will be ignored. Pre-condition: n and start are non-negative. Also, there is enough space in array x, starting at index start, to hold n bytes.
    Method: (r: Reader) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations (SetPos, ReadByte, or ReadBytes) failed. The string starts with a capital letter and does not include any termination punctuation. descr should be large enough to hold a multi-line message (256 characters should suffice). If r.res = done, then descr is assigned the empty string.
    Method: (r: Reader) ClearError
    Sets the result flag r.res to done, re-enabling further read operations on r.

    Abstract Class Writer

    Abstract Class: Writer = POINTER TO WriterDesc
    This is the abstract base writer type. Writer types are used to perform write operations on channels (see section Input/Output Overview). Writer contains the following fields:

    Field: base-: Channel
    This field refers to the channel the writer is connected to.
    Field: res-: INTEGER
    res is a result (error) flag that signals failure of a call to WriteByte, WriteBytes, or SetPos. It is initialized to done when creating a writer or by calling ClearError. The first failed writing (or SetPos) operation changes res to indicate the error, all further calls to WriteByte, WriteBytes, or SetPos will be ignored until ClearError resets this flag. This means that the successful completion of an arbitrary complex sequence of write operations can be ensured by asserting that res equals done beforehand and also after the last operation. Use the method ErrorDescr to get a plain text error description of this error code. See section Summary of Channel Constants for a list of applicable error codes. Please note: due to buffering, a write error may occur when flushing or closing the underlying channel; you have to check the channel's res field after any Flush() or the final Close() because a writer's res field may not indicate a write error in that case.
    Field: bytesWritten-: LONGINT
    Set by WriteByte and WriteBytes to indicate the number of bytes that were successfully written.
    Field: positionable-: BOOLEAN
    TRUE if, and only if, the writer can be moved to another position with SetPos; for channels that can only be written sequentially, like output to a terminal, this is FALSE.
    Method: (w: Writer) Pos (): LONGINT
    Returns the current writing position associated with the writer w in channel w.base, i.e., the index of the first byte that is written by the next call to WriteByte or WriteBytes. This procedure returns noPosition if the writer has no concept of a writing position (e.g., if it corresponds to output to terminal), otherwise the result is non-negative.
    Method: (w: Writer) SetPos (newPos: LONGINT)
    Sets the writing position to newPos. A negative value of newPos, or calling this procedure for a writer that doesn't allow positioning, will set w.res to outOfRange. A value larger than the channel's length is legal, however, the next write operation zero fills the intervening space. That is, the gap from the previous end of the channel to newPos are filled with 0X bytes. Calls to this procedure while w.res # done are ignored.
    Method: (w: Writer) WriteByte (x: SYSTEM.BYTE)
    Writes a single byte x to the channel w.base at the writing position associated with w. The writing position is moved forward by one byte on success, otherwise w.res is set to indicate the error cause. w.bytesWritten will be 1 on success and 0 on failure. Calls to this procedure while w.res # done are ignored.
    Method: (w: Writer) WriteBytes (VAR x: ARRAY OF SYSTEM.BYTE; start, n: LONGINT)
    Writes n bytes from x, beginning at index start, to the channel w.base at the writing position associated with w. The writing position is moved forward by n bytes on success, otherwise w.res is set to indicate the error cause. w.bytesWritten will hold the number of bytes that were actually written (being equal to n on success). Calls to this procedure while w.res # done are ignored. Pre-condition: n and start are non-negative. Also, this method requires that accessing n bytes in array x, starting from index start, will not go past the end of the array.
    Method: (w: Writer) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations (SetPos, WriteByte, or
    WriteBytes) failed. The string starts with a capital letter and does not include any termination punctuation. descr should be large enough to hold a multi-line message (256 characters should suffice). If r.res = done, then descr is assigned the empty string.
    Method: (w: Writer) ClearError
    Sets the result flag w.res to done, re-enabling further write operations on w.

    Channel Procedures

    Procedure: ErrorDescr (res: INTEGER; VAR descr: ARRAY OF CHAR)
    Translates this module's error codes into strings (see section Summary of Channel Constants). The string starts with a capital letter and does not include any termination punctuation. descr should be large enough to hold a multi-line message (256 characters should suffice).

    If res=done, then descr is assigned the empty string.

    Note: This procedure should only be used to determine the result code of a failed attempt to create a new instance of a channel (i.e., whenever one of the functions New() or Old() returned NIL). You should use the type-bound ErrorDescr procedures (individual class' methods) for all other situations.

    Summary of Channel Constants

    Constant: noLength
    A result value for Channel.Length.

    Constant: noPosition
    A possible return value for Reader.Pos() or Writer.Pos() meaning that the reader or writer has no concept of a position (e.g., if it corresponds to input from keyboard or output to a terminal).

    A specific channel implementation (e.g., see section Module Files) defines its own list of codes, containing aliases for the codes below (where appropriate) plus error codes of its own. Every module provides a procedure ErrorDescr to translate any code into a human readable message, and type-bound procedures for its Channel, Reader, and Writer types for the same purpose.

    The user should use the type-bound procedures whenever possible.

    The following values may appear in the res field of Channel, Reader, or Writer. Please note: These codes only cover the most typical errors.

    Constant: done
    This indicates successful completion of the last operation.

    Constant: invalidChannel
    The channel isn't valid. For example, because it wasn't opened in the first place or was somehow corrupted.

    Constant: writeError
    A write error occured; usually this error happens with a writer, but for buffered channels this may also occur during a Flush or a Close.

    Constant: noRoom
    A write operation failed because there isn't any space left on the device. For example, the disk is full or you exeeded your quota; usually this error happens with a writer, but for buffered channels this may also occur during a Flush or a Close.

    The following constants only apply to Reader.res and Writer.res:

    Constant: outOfRange
    SetPos has been called with a negative argument or it has been called on a rider that doesn't support positioning.

    Constant: readAfterEnd
    A call to ReadByte or ReadBytes has tried to access a byte beyond the end of the channel. This means that there weren't enough bytes left or the read operation started at (or after) the end.

    Constant: channelClosed
    The rider's channel has been closed, preventing any further read or write operations. This means there was a call to Channel.Close() (in which case, you probably made a programming error), or the channel has been otherwise disconnected (e.g., the process at the other end of the channel, say a pipe or TCP stream, closed the connection).

    Constant: readError
    An unspecified read error.

    Constant: invalidFormat
    Set by a mapper (e.g., TextRiders.Reader) if the byte stream at the current reading position doesn't represent an object of the requested type.

    The following constants only apply to Channel.res:

    Constant: noReadAccess
    NewReader was called to create a reader on a channel that doesn't allow read access.

    Constant: noWriteAccess
    NewWriter was called to create a writer on a channel that doesn't allow write access.

    Constant: closeError
    An attempt to close the channel failed.

    Constant: noModTime
    No modification time is available for the given channel.

    Constant: noTmpName
    Creation of a temporary file failed because the system was unable to assign an unique name to it (closing or registering an existing temporary file beforehand might help in this case).

    Constant: freeErrorCode
    Free error code number. This is provided so that a specific channel implemenatation can start defining new error codes from this value.

    Module Files

    Most computer systems provide some way of storing persistent data--- information that exists between one program activation and the next. The most common way of accessing persistent data is through a file system. A file is generally a collection of data that is held on some physical medium like a hard disk or magnetic tape. A file system provides a means to manage files; grouping them logically into entities called directories, and otherwise accessing them through file names. As these are typical, basic computer concepts, this document will assume some familiarity with file systems.

    Module Files provides facilities for accessing files using channel and rider abstractions. Files provides three related classes: File, Reader, and Writer. These classes are concrete subclasses of their conterparts in module Channel (see section Module Channel).

    Class File is derived from the base channel type and adds additional methods for file specific operations. Files are probably the most frequently used channel implementation and, at the same time, the first channel to be used by a novice user. Therefore the description below incorporates all the relevant parts from the chapter about the abstract base type Channel.

    As with all basic riders, Reader and Writer operate on sequences of bytes. Consequently, most of the time, after a file is opened, a mapper would be attached to provide more useful read/write operations (see section Module BinaryRider and section Module TextRider)

    Please note: Most Unix systems only allow a fixed number of files (and sockets) to be open simultaneously. If this limit is reached, no new file can be opened or socket be created until an old file/socket is closed. For any POSIX compliant system at least 16 open files are supported, most implementations provide a much larger number.

    Class File

    Class File allows access to files as contiguous sequences of bytes.

    Example:

    VAR  f: Files.File;
    
    f := Files.Old ("example.dat", {Files.read, Files.write}, res);
    IF (res # Files.done) THEN
        (* Error processing: failed to open "old" file.  *)
    END; ...
    
    f.Close; (* Be sure to close the file so that resources are freed. *)
    

    Class: File = POINTER TO FileDesc
    This is the concrete subclass of Channel that corresponds to actual files. File inherits the following fields:

    Field: res-: INTEGER
    res is the result (i.e., error flag) signalling failure of a call to NewReader, NewWriter, Flush, Close, etc. res is initialized to done when the file is created. Every operation sets this to done if successful, or otherwise, to an appropriate error value to indicate the cause of the error (use the method ErrorDescr to get a plain text error description). See section Summary of File Constants for a list of applicable error codes.
    Field: readable-: BOOLEAN
    readable is set to TRUE if, and only if, readers can be attached to this file with NewReader.
    Field: writable-: BOOLEAN
    writable is set to TRUE if, and only if, writers can be attached to this file with NewWriter.
    Field: open-: BOOLEAN
    open indicates the file's status; that is, it is set to TRUE on file creation, and set to FALSE by a call to Close. Closing a file prevents all further read or write operations on it.

    File inherits the following methods from the abstract class Channel:

    Method: (f: File) Length (): LONGINT
    Length returns the number of bytes of data for the file f. If f represents a genuine file, this value is the file's size. If f has no fixed length (e.g., because it's a FIFO special file), it returns noLength. Example:
    (* For file,
     -rw-rw-r--   1 nikitin      8641 Jun  6 08:14 misc.txt
    *)
    
    VAR len: LONGINT;
    
    len := f.Length();
        => len = 8641
    
    Method: (f: File) GetModTime (VAR mtime: Time.TimeStamp)
    GetModTime retrieves the modification time of the data location accessed by file f. If no such information is available, f.res is set to noModTime; otherwise to done. For more on time stamps See section Module Time. Example:
    (* For file,
     -rw-rw-r--   1 nikitin      8641 Jun  6 08:14 misc.txt
    *)
    
    VAR fTime: Time.TimeStamp;
    
    f.GetModTime(fTime);
        => fTime.days = 50605
        => fTime.msecs = 44064000
    
    Method: (f: File) NewReader (): Reader
    This method attaches a new (basic) reader to the file f (you will most likely never need to call this directly; you'd normally connect a mapper instead). The reader's position is set to the beginning of the file, and its res field is initialized to done. f.res is set to done on success and the new reader is returned. Otherwise, it returns NIL and f.res is set to indicate the error cause. Please note: if the file does not support multiple reading positions (e.g., because it's a FIFO special file), the same reader is always returned. Example:
    VAR r: Files.Reader;
    
    r := f.NewReader();
    IF (f. res # Files.done) THEN
       (* Error processing:  failed to attach a new reader.  *)
    END; 
    
    Method: (f: File) NewWriter (): Writer
    This method attaches a new writer to the file f (you will most likely never need to call this directly; you'd normally connect a mapper instead). The writer's position is set to the very start of the file, and its res field is initialized to done. f.res is set to done on success and the new writer is returned. Otherwise, it returns NIL and f.res is set to indicate the error cause. Please note: if the file does not support multiple writing positions (e.g., because it's a FIFO special file), the same writer is always returned. Example:
    VAR w: Files.Writer;
    
    w := f.NewWriter();
    IF (f. res # Files.done) THEN
       (* Error processing:  failed to attach a new writer.  *)
    END; 
    
    Method: (f: File) Flush
    Flushes all buffers related to this file. Any pending write operations are passed to the underlying OS and all buffers are marked as invalid. The next read operation will get its data directly from the channel instead of the buffer. If a writing error occurs, the field f.res will be changed to writeError, otherwise it's assigned done. Please note: you must check the file's res flag after an explicit Flush; none of the attached writers will indicate a write error in this case. Example:
    f.Flush;
    IF (f.res # Files.done) THEN
       (* Error processing:  write error when flushing buffers. *)
    END; 
    
    Method: (f: File) Close
    Flushes all buffers associated with f, closes the file, and frees all system resources allocated to it. This invalidates all riders attached to f; they can't be used further. On success, if all read and write operations (including Flush) have completed successfully, f.res is set to done. An opened file can only be closed once, successive calls of Close are undefined. Please note: unlike the Oberon System all opened Files have to be closed explicitly. Otherwise resources allocated to them will remain blocked. Example:
    f.Close;
    IF (f. res # Files.done) THEN
       (* Error processing:  error occured as file was closed.  *)
    END; 
    
    Method: (f: File) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why the previous operation (NewReader, NewWriter, Flush, Close, etc.) failed. The string starts with a capital letter and does not include any termination punctuation. descr should be large enough to hold a multi-line message (256 characters should suffice). If r.res = done, then descr is assigned the empty string. Example:
    (* Attempting to connect a writer to a file opened 
       only for reading *)
    
    f := Files.Old ("example.dat", {Files.read}, res);
    
    w := f. NewWriter();
       => f.res = noWriteAccess
    f.ErrorDescr (str);
       => str = "No write permission for file"
    
    Method: (f: File) ClearError
    Sets the result flag f.res to done. Example:
    f.ClearError;
       => f.res = done
    

    Besides its inherited methods, File has the following additional method:

    Method: (f: File) Register
    Registers the file f in the directory structure if it has been created with the Tmp procedure (see section File Locators). Registration happens atomically, i.e., it is guaranteed that any previously existing file is replaced by the newly registered one without any "in between" state. If the operation is interrupted, then either the old file still exists on the file system, or it has been replaced completely by the new one. Calling Tmp and Register successively has the same effect as calling New. Calling this procedure has no effect if the file f has been created with New or has been registered previously. Registration fails with an anonymousFile error if it was created by calling Tmp with an empty file name, and with a channelClosed error if f is closed. Example:
    (* open named temporary file *)
    f := Files.Tmp ("temp.fil", {Files.write}, res);
    
    f.Close;
    f.Register;
       => f.res = channelClosed
    f.ErrorDescr (str);
       => str = "File has been closed"
    
    (* open anonymous temporary file *)
    f := Files.Tmp ("", {Files.write}, res); 
    
    f.Register;
       => f.res = anonymousFile
    f.ErrorDescr (str);
       => str = "Can't register anonymous file"
    

    Class Reader

    Class Reader provides primitive read operations on Files; that is, reading of bytes from a file. Most programmers would not use this class directly; a mapper class like BinaryRider.Reader or TextRider.Reader would be used instead (see section Module BinaryRider and section Module TextRider)

    Class: Reader = POINTER TO ReaderDesc
    This is a concrete rider type for reading bytes from files. Reader inherits the following fields from the base reader type:

    Field: base-: Channel.Channel
    base refers to the file the reader is connected to.
    Field: res-: INTEGER
    res is a result (error) flag that signals failure of a call to ReadByte, ReadBytes, or SetPos. res is initialized to done when creating a reader or by calling ClearError. The first failed read operation (or SetPos) changes this to indicate the error, all further calls to ReadByte, ReadBytes, or SetPos will be ignored until ClearError resets this flag. This means that the successful completion of an arbitrary complex sequence of read operations can be ensured by asserting that res equals done beforehand and also after the last operation. Use method ErrorDescr to get a plain text error description of this error code. See section Summary of File Constants for a list of applicable error codes.
    Field: bytesRead-: LONGINT
    bytesRead is set by ReadByte and ReadBytes to indicate the number of bytes that were successfully read.
    Field: positionable-: BOOLEAN
    positionable is set to TRUE if, and only if, the reader can be moved to another position with SetPos; for files that can only be read sequentially, this is set to FALSE.

    Reader inherits the following methods from the abstract reader class:

    Method: (r: Reader) Pos (): LONGINT
    Returns the current reading position associated with the reader r in file r.base, i.e., the index of the first byte that is read by the next call to ReadByte or ReadBytes. This procedure returns a non-negative result.
    Method: (r: Reader) Available (): LONGINT
    Returns the number of bytes available for the next reading operation. For a file this is the length of the file r.base minus the current reading position. The result is -1 if Close() was called for the file (or the file has been otherwise closed), or no more bytes are available.
    Method: (r: Reader) SetPos (newPos: LONGINT)
    Sets the reading position to newPos. Using a negative value of newPos, or calling this procedure for a reader that doesn't allow positioning, will set r.res to outOfRange. A value larger than the file's length is legal, but the following read operation will most likely fail with an readAfterEnd error (unless the file has grown beyond this position in the meantime). Calls to this procedure while r.res # done will be ignored, in particular a call with r.res = readAfterEnd error will not reset res to done. Example:
    (* For file,
     -r--r--r--   1 nikitin     12265 Jun  9 11:16 test.dat
    *)
    
    VAR pos, avail: LONGINT;
        r: Files.Reader;
        f: Files.File;
    
    f := Files.Old("test.dat", {Files.read}, res);
    r := f. NewReader();
    
    pos := r.Pos();
       => pos = 0
    
    avail := r.Available();
       => avail = 12265
    
    r.SetPos(6000);
    
    pos := r.Pos();
       => pos = 6000
    
    avail := r.Available();
       => avail = 6265
    
    Method: (r: Reader) ReadByte (VAR x: SYSTEM.BYTE)
    Reads a single byte from the file r.base at the reading position associated with r and places it in x. The reading position is moved forward by one byte on success, otherwise r.res is changed to indicate the error cause. Calling this procedure with the reader r placed at the end (or beyond the end) of the file will set r.res to readAfterEnd. r.bytesRead will be 1 on success and 0 on failure. Calls to this procedure while r.res # done will be ignored. Example:
    (* OOC assumes that SIZE(SYSTEM.BYTE) = SIZE(SHORTINT) *)
    VAR byte: SHORTINT;
        ch  : CHAR;
    
    r.ReadByte(byte);
    r.ReadByte(ch);
    
    Method: (r: Reader) ReadBytes (VAR x: ARRAY OF SYSTEM.BYTE; start, n: LONGINT)
    Reads n bytes from the file r.base at the reading position associated with r and places them in x, beginning at index start. The reading position is moved forward by n bytes on success, otherwise r.res is changed to indicate the error cause. Calling this procedure with the reader r positioned less than n bytes before the end of the file will will set r.res to readAfterEnd. r.bytesRead will hold the number of bytes that were actually read (being equal to n on success). Calls to this procedure while r.res # done will be ignored. Pre-condition: n and start are non-negative. Also, there is enough space in array x, starting at index start, to hold n bytes. Example:
    VAR byteArr: ARRAY 256 OF SHORTINT;
    
    r.ReadBytes(byteArr, 0, 16);
       => reads the next 16 bytes from r.base into byteArr[0..15]
    
    r.ReadBytes(byteArr, 16, 100);
       => reads the next 100 bytes from r.base into 
            byteArr[16..115]
    
    Method: (r: Reader) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations (SetPos, ReadByte, or ReadBytes) failed. The string starts with a capital letter and does not include any termination punctuation. descr should be large enough to hold a multi-line message (256 characters should suffice). If r.res = done, then descr is assigned the empty string. Example:
    r.SetPos(-1);
       => r.res = outOfRange
    r.ErrorDescr(str);
       => str = "Trying to set invalid position"
    
    Method: (r: Reader) ClearError
    Sets the result flag r.res to done, re-enabling further read operations on r. Example:
    r.ClearError
       => r.res = done
    

    Class Writer

    Class Writer provides primitive write operations on Files; that is, writing of bytes to a file. Most programmers would not use this class directly; a mapper class like BinaryRider.Writer or TextRider.Writer would be used instead (see section Module BinaryRider and see section Module TextRider)

    Class: Writer = POINTER TO WriterDesc
    This is a concrete rider type for writing bytes to files. Writer inherits the following fields from the base writer type:

    Field: base-: Channel.Channel
    This field refers to the file the Writer is connected to.
    Field: res-: INTEGER
    res is a result (error) flag that signals failure of a call to WriteByte, WriteBytes, or SetPos. It is initialized to done when creating a writer or by calling ClearError. The first failed writing (or SetPos) operation changes res to indicate the error, all further calls to WriteByte, WriteBytes, or SetPos will be ignored until ClearError resets this flag. This means that the successful completion of an arbitrary complex sequence of write operations can be ensured by asserting that res equals done beforehand and also after the last operation. Use ErrorDescr to get a plain text error description of this error code. See section Summary of File Constants for a list of applicable error codes. Please note: due to buffering, a write error may occur when flushing or closing the underlying file; you have to check the file's res field after any Flush() or the final Close().
    Field: bytesWritten-: LONGINT
    Set by WriteByte and WriteBytes to indicate the number of bytes that were successfully written.
    Field: positionable-: BOOLEAN
    TRUE if, and only if, the writer can be moved to another position with SetPos; for files that can only be written sequentially, this is FALSE.

    Writer inherits the following methods from the abstract writer class:

    Method: (w: Writer) Pos (): LONGINT
    Returns the current writing position associated with the writer w in file w.base, i.e., the index of the first byte that is written by the next call to WriteByte or WriteBytes. This procedure returns a non-negative result.
    Method: (w: Writer) SetPos (newPos: LONGINT)
    Sets the writing position to newPos. A negative value of newPos, or calling this procedure for a writer that doesn't allow positioning, will set w.res to outOfRange. A value larger than the file's length is legal, however, the next write operation zero fills the intervening space. That is, the gap from the previous end of the file to newPos are filled with 0X bytes. Calls to this procedure while w.res # done are ignored. Example:
    (* For file,
     -r--r--r--   1 nikitin     12265 Jun  9 11:16 test.dat
    *)
    
    VAR pos, LONGINT;
        w: Channel.Writer;
        f: Files.File;
    
    f := Files.Old("test.dat", {Files.write}, res);
    w := f. NewWriter();
    
    pos := w.Pos();
       => pos = 0
    
    w.SetPos(6000);
    
    pos := w.Pos();
       => pos = 6000
    
    Method: (w: Writer) WriteByte (x: SYSTEM.BYTE)
    Writes a single byte x to the file w.base at the writing position associated with w. The writing position is moved forward by one byte on success, otherwise w.res is set to indicate the error cause. w.bytesWritten will be 1 on success and 0 on failure. Calls to this procedure while w.res # done are ignored. Example:
    (* OOC assumes that SIZE(SYSTEM.BYTE) = SIZE(SHORTINT) *)
    VAR byte: SHORTINT;
    
    byte = ODH;
    w.WriteByte(byte);
    w.WriteByte("A");
    
    Method: (w: Writer) WriteBytes (VAR x: ARRAY OF SYSTEM.BYTE; start, n: LONGINT)
    Writes n bytes from x, starting at index start in x, to the file w.base at the writing position associated with w. The writing position is moved forward by n bytes on success, otherwise w.res is set to indicate the error cause. w.bytesWritten will hold the number of bytes that were actually written (being equal to n on success). Calls to this procedure while w.res # done are ignored. Pre-condition: n and start are non-negative. Also, this method requires that accessing n bytes in array x, starting from index start, will not go past the end of the array. Example:
    (* OOC assumes that SIZE(SYSTEM.BYTE) = SIZE(CHAR). *)
    VAR charArr: ARRAY 256 OF CHAR;
    
    charArr := "abcdefghijklmnopqrstuvwxyz";  
            (* Note charArr[26] = 0X *)
    
    w.WriteBytes(charArr, 0, 16);
       => writes exactly 16 values 
          (i.e., 0X is not automatically written) 
       => abcdefghijklmnop
    
    w.WriteBytes(charArr, 16, 11);
       => writes exactly 11 values 
          (i.e., 0X is written from charArr[26]) 
       => qrstuvwxyz0X
    
    Method: (w: Writer) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations (SetPos, WriteByte, or WriteBytes) failed. The string starts with a capital letter and does not include any termination punctuation. descr should be large enough to hold a multi-line message (256 characters should suffice). If w.res = done, then descr is assigned the empty string. Example:
    f.Close;
    w.WriteByte("A");
       => w.res = channelClosed
    w.ErrorDescr(str);
       => str = "File has been closed"
    
    Method: (w: Writer) ClearError
    Sets the result flag w.res to done, re-enabling further write operations on w. Example:
    w.ClearError
       => w.res = done
    

    Besides its inherited methods, Writer has the following additional methods:

    Method: (VAR w: Writer) Truncate (VAR newLength: LONGINT)
    Causes the file associated with w to have the specified length. If the file was previously larger than newLength, the extra data is lost. If it was previously shorter, bytes between the old and new lengths are read as null bytes (i.e., 0X bytes). The writer's position is not modified in either case. Please note: On systems that do not support shortening files directly it is implemented as a partial file copy.

    File Locators

    The following locator procedures are provided for opening files. Possible values for the flags parameter are read, write, tryRead, tryWrite (see section Summary of File Constants).

    Function: New (VAR file: ARRAY OF CHAR; VAR flags: SET; VAR res: INTEGER): File
    Creates a new file under the name file. On success, the new file object is returned, and res is set to done. Otherwise, it returns NIL and res and will indicate the problem.

    Use procedure ErrorDescr to get a plain text error description of this error code. See section Summary of File Constants for a list of applicable error codes.

    Please note: that in terms of the Oberon System this procedure combines the procedures New and Register.

    Function: Old (VAR file: ARRAY OF CHAR; VAR flags: SET; VAR res: INTEGER): File
    Opens an existing file. On success the new file object is returned and res is set to done. Otherwise, it returns NIL and res will indicate the problem.

    Use procedure ErrorDescr to get a plain text error description of this error code. See section Summary of File Constants for a list of applicable error codes.

    Function: Tmp (VAR file: ARRAY OF CHAR; VAR flags: SET; VAR res: INTEGER): File
    Creates a temporary file that can be registered later on. On success the new file object is returned and res is set to done. Otherwise, it returns NIL and res will indicate the problem.

    Use ErrorDescr to get a plain text error description of this error code. See section Summary of File Constants for a list of applicable error codes.

    Temporary files are created with an empty permission list, the permissions are extended upon registration. The files are deleted if they haven't been registered and are closed, or the program terminates.

    An unique temporary file name is created if the given file name is the empty string. Such a file can't be registered later. Note that some systems may have a low limit for the number of temporary file names. The limit is never less than 25. To be safe, you should never have more than 25 anonymous temporary files open simultaneously, or check that the TMP_MAX macro in /usr/include/stdio.h is large enough for your purposes.

    With oo2c if file isn't empty, the new name is derived from the old one by appending "^", "^1", "^2", etc. in turn, until a file name is found that doesn't exist already. If such call to Tmp returns nameTooLong, then this refers to the constructed temporary name, not the one in file.

    This function corresponds to Oberon System's New.

    Other File Operations

    It isn't always desirable to have to open a file before performing certain operations on it. You may not be interested in a file's contents; but rather some property of the file itself (for instance, does the named file even exist). As such, module Files provides some free-standing procedures:

    Procedure: SetModTime (VAR file: ARRAY OF CHAR; VAR mtime: Time.TimeStamp; VAR res: INTEGER)
    Sets the modification time of the given file to mtime. On success res will contain done, otherwise an error code that'll indicate the problem.

    Please note: under Unix this procedure will also change the access time to the value of mtime.

    Procedure: GetModTime (VAR file: ARRAY OF CHAR; VAR mtime: Time.TimeStamp; VAR res: INTEGER)
    Gets the modification time of the given file to mtime. On success res will contain done, otherwise an error code indicating the problem.

    Function: Exists (VAR file: ARRAY OF CHAR): BOOLEAN
    Returns TRUE if file file exists, FALSE otherwise. This procedure may be changed in future revisions to give more useful information on failure.

    Procedure: ErrorDescr (VAR res: INTEGER; VAR descr: ARRAY OF CHAR)
    Translates this module's error codes into strings. The string starts with a capital letter and does not include any termination punctuation. descr should be large enough to hold a multi-line message (256 characters should suffice). If res=done, then descr is assigned the empty string.

    Please note: This procedure should only be used to determine the result code of a failed attempt to create a new instance of a file (i.e., whenever one of the functions New(), Old(), or Tmp() returned NIL). You should use the type-bound ErrorDescr procedures for all other situations.

    Example:

    (* Attempting to open a "read-only" file for writing *)
    
    f := Files.Old ("example.dat", {Files.write}, res);
       => res = accessDenied
    Files.ErrorDescr (res, str);
       => str = "Failed to open file with requested access rights"
    

    Summary of File Constants

    For constant values that are common to all channel types (see section Summary of Channel Constants), local names have been provided:

    Constant: noLength
    A result value for File.Length.

    Constant: noPosition
    A possible return value for Reader.Pos() or Writer.Pos() meaning that the reader or writer has no concept of a position.

    The following values may appear in the res field of File, Reader, or Writer:

    Constant: done
    This indicates successful completion of the last operation.

    Constant: invalidChannel
    The channel (i.e., file) isn't valid. For example, because it wasn't opened in the first place or was somehow corrupted.

    Constant: writeError
    A write error occured; usually this error happens with a writer, but for buffered files this may also occur during a Flush or a Close.

    Constant: noRoom
    A write operation failed because there isn't any space left on the device. For example, the disk is full or you exeeded your quota; usually this error happens with a writer, but for buffered files this may also occur during a Flush or a Close.

    The following constants only apply to Reader.res and Writer.res:

    Constant: outOfRange
    SetPos has been called with a negative argument or it has been called on a rider that doesn't support positioning.

    Constant: readAfterEnd
    A call to ReadByte or ReadBytes has tried to access a byte beyond the end of the file. This means that there weren't enough bytes left or the read operation started at (or after) the end.

    Constant: channelClosed
    The rider's channel (i.e., file) has been closed, preventing any further read or write operations. This means there was a call to File.Close() (in which case, you probably made a programming error), or the channel has been otherwise closed.

    Constant: readError
    An unspecified read error.

    Constant: invalidFormat
    Set by a mapper (e.g., TextRiders.Reader) if the byte stream at the current reading position doesn't represent an object of the requested type.

    The following constants only apply to File.res:

    Constant: noReadAccess
    NewReader was called to create a reader on a file that doesn't allow read access.

    Constant: noWriteAccess
    NewWriter was called to create a writer on a file that doesn't allow write access.

    Constant: closeError
    An attempt to close the file failed.

    Constant: noModTime
    No modification time is available for the given file.

    Constant: noTmpName
    Creation of a temporary file failed because the system was unable to assign an unique name to it (closing or registering an existing temporary file beforehand might help in this case).

    The following values report problems when opening or modifying a file:

    Constant: accessDenied
    Access to the file was denied, e.g., because a file's permissions don't permit the requested access method, or because the given URL isn't publically readable.

    Constant: isDirectory
    The flags argument specified write access, and the file is a directory.

    Constant: tooManyFiles
    The process or the entire system has too many files open.

    Constant: noSuchFile
    The named file in a call to Old() does not exist. Or the directory part of a file name passed to New() or Tmp() does not exist.

    Constant: directoryFull
    The directory or the file system that would contain the new file cannot be extended, either because there is no space left or the directory has a fixed upper limit.

    Constant: readOnlyFileSystem
    The file resides on a read-only file system and it is attempted to create a new file or to gain write access for an existing one.

    Constant: invalidTime
    The time passed to procedure SetModTime is not a valid time stamp; either the millisecond part isn't valid, or the time value is too large or too small to be mapped to the time value of the underlying OS.

    Constant: notOwner
    Only the owner of a file can change its modification time.

    Constant: anonymousFile
    A file can only be registered if a file name was passed to the initial call to Tmp().

    Constant: dirWriteDenied
    You need to have write permission for the directory you want to add a new file to.

    Constant: fileError
    Unspecified error when opening/creating a file; this usually means that this module doesn't know how to interpret the error code delivered by the OS.

    Constant: nameTooLong
    Either the total length of the file name or of an individual file name component is too large; the operating system can impose such limits (see PATH_MAX and NAME_MAX in /usr/include/limits.h), or the file system itself restricts the format of names on it.

    Constant: notDirectory
    A file that is referenced as a directory component of the file name exists, but is not a directory.

    Constant: linkLoop
    Too many symbolic links were resolved while trying to look up the file name; the operating system has an arbitrary limit on the number of symbolic links that may be resolved in looking up a single file name, as a primitive way to detect loops.

    The following are possible elements for the flags parameter of New, Old, or Tmp.

    Please note: at least one of the following flags has to be set; otherwise you will get an "access denied" error:

    Constant: read
    If the file cannot be opened for reading access, then it isn't opened at all; in this case the error code is set to noReadAccess.

    Constant: write
    If the file cannot be opened for writing access, then it isn't opened at all; in this case the error code is set to noWriteAccess.

    Constant: tryRead
    Try to open this file for reading access; if the file permissions don't permit reading, the file is opened nevertheless, but the file descriptor's attribute readable is set to FALSE.

    Constant: tryWrite
    Try to open this file for writing access; if the file permissions don't permit writing, the file is opened nevertheless, but the file descriptor's attribute writable is set to FALSE.

    Module StdChannels

    Module StdChannels defines the standard I/O channels, which are predefined channels for input (typically the keyboard) and output (typically the computer screen).

    Standard channels do not have to be opened by a client program because they are already open and ready for use. Their attributes and operations are described by the class Channel.Channel.

    The standard channels (stdin, stdout, and stderr) should never be closed. You can close the standard channels (e.g., to detach a program from its terminal), but StdChannels does not provide a way to reopen them. Notice that the modules In, Out, Err, OakIn, and OakOut are all affected by such operations on standard channels. If, for example, you call stdout.Close, then the procedures in module Out will no longer function (unless you use Out.SetWriter to set another channel).

    A fourth standard channel, null, is also provided.

    Mappers may be attached to any of these channels to provide read/ write operations for them. Mappers from module TextRider are most often used.

    Also, be aware that modules In, Out, and Err provide simple interfaces to the standard channels (see section Standard I/O) So that, in many cases, you may not have to use module StdChannels directly.

    Read-only Variable: stdin
    The standard input channel, which is a predefined source of input for the program. The referenced channel is read-only.

    Example:

    VAR stringVar: ARRAY 256 OF CHAR; 
        rdr:       TextRider.Reader;
    
    rdr := TextRider.ConnectReader(StdChannels.stdin);
    rdr.ReadLine(stringVar);
    

    Read-only Variable: stdout
    The standard output channel, which is a predefined destination for output from the program. The referenced channel is write-only.

    Example:

    VAR wrtr: TextRider.Writer;
    
    wrtr := TextRider.ConnectWriter(StdChannels.stdout);
    wrtr.WriteString("A string to write"); wrtr.WriteLn;
    

    Read-only Variable: stderr
    The standard error channel, which can be used for error messages and diagnostics issued by the program. The referenced channel is write-only.

    Example:

    VAR wrtr: TextRider.Writer;
    
    wrtr := TextRider.ConnectWriter(StdChannels.stderr);
    wrtr.WriteString("An error has occured"); wrtr.WriteLn;
    

    Read-only Variable: null
    The null channel, which can be used as a destination for output that is to be discarded. The referenced channel is write-only.

    Module ProgramArgs

    This module provides access to the command line arguments passed to the program's invocation. They are mapped onto a standard channel args, with each argument transformed into a single line of text. Interpreting the list of arguments is usually done by applying an instance of TextRider.Reader or TextRider.Scanner to the argument channel.

    The number of arguments is determined by calling args.ArgNumber(). If the invocation were, for example, foo bar 42, where foo is the name of the program itself, then the channel's contents would look like this:

    foo
    bar
    42
    

    For the above example, args.ArgNumber() would return 2; that is, the program name is not counted by ArgNumber even though it is present in args.

    Note that command line arguments should not contain any end-of-line characters, otherwise, a single argument would be mapped onto multiple lines.

    Also, be careful with settings for TextRider.Reader and especially TextRider.Scanner: end-of-line characters are treated as whitespace by many of the read operations, which means, for a program foo, the reader or scanner has no way of distinguishing between

    foo 123 bar
    for "123 bar"
    

    You would normally consider the first invocation as having two arguments, and the second as having one; which is also how ProgramArgs would interpret them. For foo 123 bar, args would contain

    foo
    123
    bar
    

    whereas, for foo "123 bar", args would contain

    foo
    123 bar
    

    But a text reader or scanner, if set to treat end-of-line as whitespace, would treat both of these invocations as equivalent.

    Please note: In cases where separate arguments need to be considered as a whole, the reader method ReadLine should be used. Unlike other read operations, such asReadInt or ReadIdentifier, leading whitespace is not skipped and, after completion, the reading position is just behind the end-of-line character.

    So ReadLine should be used to read, for example, file name arguments because operating systems like Unix typically allow arbitrary characters in file names, including blanks and control codes.

    Module ProgramArgs provides local equivalents for the following constants from module Channels: done, outOfRange, readAfterEnd, channelClosed, noWriteAccess, and noModTime.

    Class: Channel = POINTER TO ChannelDesc
    This class is derived from the abstract base channel class. In addition to its inherited fields and methods (see section Abstract Class Channel), the class provides the following method:

    Method: (VAR ch: Channel) ArgNumber (): LONGINT
    Returns the number of command line arguments (excluding the program name itself) passed to the program.

    Read-only Variable: args
    The predefined program arguments channel. The referenced channel is read-only.

    As a further example, suppose a program foo required exactly two (positional) command line arguments. The first is an integer value and the second is an identifier. Also, suppose that all of the following invocations are to be considered equivalent:

    foo 123 bar
    foo +123 bar
    foo "  +123" " bar"
    

    Note that, the following module would not consider `foo 123 " bar "' or `foo 123+ bar' to be equivalent to the above invocations.

    Example:

    VAR r: TextRider.Reader;
        str: ARRAY 256 OF CHAR;
        int: LONGINT;
    
      r := TextRider.ConnectReader(ProgramArgs.args);
      IF r = NIL THEN 
         (* Error processing: failed to connect to `args' *)
      END;
    
      IF ProgramArgs.args.ArgNumber() # 2 THEN
         (* Error processing: wrong number of arguments *)
      END;
    
      (* skip past the line containing the program name `foo' *)
      r.ReadLn;
    
      r.ReadLInt(int);
      IF r.Res() # TextRider.done THEN
         (* Error processing: can't read an integer *)
      ELSIF ~r.Eol() THEN
         (* Error processing: this argument has other stuff after
            the integer just read *)
      END;
    
      r.ReadLn; (* skip to the next line *)
    
      r.ReadIdentifier(str);
      IF r.Res() # TextRider.done THEN
         (* Error processing: can't read an identifier *)
      ELSIF ~r.Eol() THEN
         (* Error processing: extra stuff after the identifier *)
      END;
    

    Standard Mappers

    Mappers are high-level riders, which are used to translate between a sequence of data items and an uninterpreted sequence of bytes (see section Riders and Mappers). Thus, the reader and writer types in BinaryRider and TextRider are considered mappers.

    The standard mappers, defined in this section, use the basic riders associated with a particular channel type for reading and writing bytes. You'll notice that there are very few error code constants defined within either of these modules; error codes are dependant on the channel being read, and so you'll have to use the constant values for readers and writers that are declared within each particular channel module.

    Because OOC has both CHAR and LONGCHAR character types, mappers for textual data have been set up as a class hierarchy, with base classes in module `Rider' from which all other text mappers derive.

    Text Mappers

    The text mapper modules (`Rider', `LongRider', `TextRider', and `UnicodeRider') provide facilities for reading and writing values in text format. Text format is delimited, or otherwise formatted, sequences of character values that can be interpreted as words, numbers, symbols, and so forth. This corresponds to the way human beings read text, or perhaps how an Oberon-2 source file is parsed by a compiler. Data in text format are generally refered to simply as text.

    Text can usually be interpreted in a limited number of ways. For example, the number 2 can be read as an INTEGER value or as a REAL. It could be an element of a SET, or perhaps even be part of an identifier such as oo2c. The interpretation is based on context and the format of the characters rather than as a fixed number of bytes.

    Because the corresponding classes from the text mapper modules provide related facilities, they form a class hierarchy as follows:

                Rider [ABSTRACT]
                /    \
              /        \
            /            \
       TextRider        LongRider [ABSTRACT]
                             |
                             |
                             |
                        UnicodeRider
    

    Module Rider

    Module `Rider' encapsulates the base classes for all other text mapper classes. These base classes (Reader, Writer, and Scanner) are abstract classes that define the interface elements required for concrete classes derived from them.

    See the concrete text mapper classes for more detail and examples of usage (section Module TextRider and section Module UnicodeRider).

    Class Reader (Rider)

    Constant: maxLengthEol
    The maximum number of characters allowed in Reader.eol.

    Abstract Class: Reader = POINTER TO ReaderDesc
    This class provides facilities for reading various kinds of text. Note that this type does not inherit properties from any basic reader type; rather it uses the basic reader type associated with the channel it is attached to.

    Also note that, after any failed read operation, all further attempts to read will be ignored until the error is cleared using ClearError.

    See section Class Reader (TextRider) for examples of usage.

    Field: opt-: SET
    The current read options setting for the reader.
    Field: base-: Channel.Channel
    This field refers to the channel the reader is connected to.

    The following fields determine how the reader interprets end-of-line markers. Note that the end-of-line marker may contain the character `0X', which means its length must be stored in a separate field. The eol marker cannot be empty, and all characters must be an ASCII code in the range 00X..1FX.

    Field: eol-: ARRAY maxLengthEol OF CHAR
    The character sequence that represents an end-of-line marker. Note that this is a character array, not a string (i.e., it may contain the character `0X').
    Field: eolLen-: INTEGER
    The number of characters in eol. The default value for this is `-1', which means that end-of-line is auto detected (see SetEol below). Otherwise, this value is in the range 1 <= eolLen <= maxLengthEol.

    The following methods can be used to check the status of a reader or, in some cases, change its state. Some methods are fully described in the abstract reader section (see section Abstract Class Reader), so only brief descriptions of those are given here.

    Method: (r: Reader) Available () : LONGINT
    Returns the number of bytes available for the next read operation.
    Method: (r: Reader) ClearError
    Clears error conditions on the reader r, re-enabling further read operations.
    Method: (r: Reader) Eol (): BOOLEAN
    This method returns TRUE if the reader is currently positioned at an end-of-line marker (see SetEol below). This will also return TRUE if r.Res() # done. Otherwise, FALSE is returned.
    Method: (r: Reader) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations failed.
    Method: (r: Reader) Pos (): LONGINT
    Returns the current reading position associated with the reader r in channel r.base.
    Method: (r: Reader) Res (): INTEGER
    This method returns the status of the last read operation (e.g., ReadLine, ReadInt, SetPos, etc.). Note that unlike some other reader types, Res() is a method rather than a field; but otherwise, it performs equivalently. Error codes are highly dependent on the channel being read, and therefore on the basic riders provided by that channel, so you must look at the result codes for a particular channel's reader type (e.g., Files.Reader error codes). See the various channel types for details of these error codes (i.e., section Module Files, section Module StdChannels, or section Module ProgramArgs). Use method ErrorDescr to get a plain text error description of this error code.
    Method: (r: Reader) SetEol (marker: ARRAY OF CHAR; markerLen: INTEGER)
    This method sets the end-of-line marker; that is, what character(s) is used to mark the end of a line. If the passed string marker does not fit into the field eol, or if it contains a character >= ` ', then r.Res() is set to invalidFormat. A marker length markerLen=-1 enables auto detection of the end-of-line convention used by the channel. For auto detection to work, the channel is required to use one of the following eol markers:
    `LF'
    used by Unix
    `CR'
    used by MacOS
    `CR/LF'
    used by MS-DOS and Windows
    Please note: ReadChar is unaffected by the current eol setting. That is, if the end-of-line marker consists of more than one character (like `CR/LF'), each character is read separately. All other read operations view an end-of-line marker at an atomic entity when the channel is read sequentially. If auto detection is enabled, and the eol convention of the file is `CR/LF', then the first end-of-line marker is not skipped completely when reached by the reader (r.Pos() is at the `LF'). This is transparent to all reading procedures except ReadChar and Pos; the `LF' will be skipped automatically on the next read. This positioning inconsistency only applies for the very first eol encountered. Pre-condition: All of the following apply:
    1. r.Res() = done, and
    2. (markerLen = -1) OR (1 <= markerLen < LEN (marker)), and
    3. markerLen <= maxLengthEol, and
    4. for all i: marker[i] < 20X
    Method: (r: Reader) SetOpts (opts: SET)
    This method is used to set the reader options r.opt.
    Method: (r: Reader) SetPos (newPos: LONGINT)
    Sets the reading position to newPos.

    The following methods read a value of the given type from the current position of the reader. Most read operations skip leading whitespace before reading a token; there are only three methods that do not skip whitespace: ReadChar, ReadLn, and ReadLine.

    When attempting to read, and if the value is not properly formatted for its type, r.Res() returns invalidFormat. The reader remains positioned at the character which caused the invalidFormat error, but further reading can not take place until the error is cleared.

    If a number, or potential set element, is properly formatted, but has a value that is out of range of the target type, then a valueOutOfRange error occurs. In this case, the reader is positioned after the last character that was read. Again, further reading can not take place until the error is cleared.

    A valueOutOfRange error also occurs for methods reading into an ARRAY OF CHAR (i.e., ReadLine, ReadIdentifier, and ReadString) if the character array is not large enough to hold the entire input.

    Otherwise, for any operation attempting to read when there are no characters left to be read, a read-after-end error occurs and Reader.Res() returns readAfterEnd.

    In any case, whenever an error occurs, it is safest to assume that no value has been read. That is, the variable being read into is left with an undefined value.

    All further calls of these read methods will be ignored if r.Res()#done. That is, no new characters will be read if an error has occurred previously.

    Method: (r: Reader) ReadBool (VAR bool: BOOLEAN)
    Reads in an identifier (see ReadIdentifier below), and if it is either of the tokens TRUE or FALSE, it is converted to a BOOLEAN value. If this method encounters any other token, an invalidFormat error occurs and the value of bool is undefined.
    Method: (r: Reader) ReadChar (VAR ch: CHAR)
    Reads in a single character value and places it in ch.
    Method: (r: Reader) ReadHex (VAR lint: LONGINT)
    Reads in characters in the form of an unsigned hexadecimal number and converts them to a LONGINT value. The first character must be a decimal digit (i.e., `0..9') and subsequent characters must be valid hexadecimal digits (i.e., `0..9' or `A..F'). If the first non-whitespace character is not a digit, then an invalidFormat error occurs. If the input is properly formatted as an unsigned hex number, but the value is out of range for a LONGINT, then a valueOutOfRange error occurs. Upon encountering an error, the value of lint is undefined. Please note: Because LONGINT values are signed, hex numbers in the range `80000000H..FFFFFFFFH' are interpreted as negative LONGINT values.
    Method: (r: Reader) ReadIdentifier (VAR s: ARRAY OF CHAR)
    Reads an Oberon-2 style identifier into s. An identifier is a sequence of letters and digits, which must begin with a letter. Sequences not beginning with a letter produce an invalidFormat error. If s is not large enough to hold the entire input, a valueOutOfRange error occurs. Upon encountering an error, the value of s is undefined.
    Method: (r: Reader) ReadInt (VAR int: INTEGER)
    Reads in characters in the form of a signed whole number and converts them to an INTEGER value. If the first character is not a digit, a "+" sign, or a "-" sign, then an invalidFormat error occurs. If the input is properly formatted as a signed whole number, but the value is out of range for an INTEGER, then a valueOutOfRange error occurs. Upon encountering an error, the value of int is undefined.
    Method: (r: Reader) ReadLInt (VAR lint: LONGINT)
    This method provides the same facility as ReadInt, except that it deals with LONGINT values.
    Method: (r: Reader) ReadSInt (VAR sint: SHORTINT)
    This method provides the same facility as ReadInt, except that it deals with SHORTINT values.
    Method: (r: Reader) ReadLine (VAR s: ARRAY OF CHAR)
    Reads a sequence of characters into s; reading continues until an end-of-line character is encountered, the array s is full, or r reaches the end of the channel. The end-of-line character is discarded and s is always terminated with 0X. If r is already positioned at an end-of-line character, s returns as an empty string. If s is not large enough to hold the entire input, a valueOutOfRange error occurs; s returns with the sequence of characters that have been read so far (terminated by 0X). If r has already reached the end of the channel (i.e., there are no more characters left to read), a readAfterEnd error occurs and s returns as an empty string.
    Method: (r: Reader) ReadLn
    This method reads and discards all characters up to and including the next end-of-line character. If the end of the channel is reached before encountering an end-of-line character, a readAfterEnd error occurs.
    Method: (r: Reader) ReadString (VAR s: ARRAY OF CHAR)
    Reads in a sequence of characters enclosed in single (') or double (") quote marks. The opening quote must be the same as the closing quote and must not occur within the string. Characters will be read until the terminating quote mark is encountered, an invalid character is read (end-of-line is always considered invalid), there are no more characters available in the channel, or the string s is full. s is always terminated with 0X. Unquoted strings produce an invalidFormat error. Strings with no terminating quote mark also result in an invalidFormat error. If s is not large enough to hold the entire input, a valueOutOfRange error occurs. Upon encountering an error, the value of s is undefined.
    Method: (r: Reader) ReadReal (VAR real: REAL)
    Reads in characters in the form of a signed fixed or floating-point number and converts them to a REAL value. If the first character is not a digit, a "+" sign, or a "-" sign, then an invalidFormat error occurs. If the input is properly formatted as a signed fixed or floating-point number, but the value is out of range for a REAL, then a valueOutOfRange error occurs. Upon encountering an error, the value of real is undefined.
    Method: (r: Reader) ReadLReal (VAR lreal: LONGREAL)
    This method provides the same facility as ReadReal, except that it deals with LONGREAL values.
    Method: (r: Reader) ReadSet (VAR s: SET)
    Reads in characters in the form of a set constructor and converts them to a SET. If the sequence of characters does not form a valid set constructor, then an invalidFormat error occurs. If the input is properly formatted as a set constructor, but a set element has a value out of the range 0..MAX(SET), then a valueOutOfRange error occurs. Upon encountering an error, the value of s is undefined.

    Class Writer (Rider)

    Abstract Class: Writer = POINTER TO WriterDesc
    This class provides facilities for writing various types of text. Note that this type does not inherit properties from any basic writer type; rather it uses the basic writer type associated with the channel it is attached to.

    See section Class Writer (TextRider) for examples of usage.

    Field: opt-: SET
    The current write options setting for the writer. See section Summary of TextRider Constants for possible option values.
    Field: base-: Channel.Channel
    This field refers to the channel the writer is connected to.

    The following methods can be used to check the status of a writer or, in some cases, change its state. Some methods are fully described in the abstract writer section (see section Abstract Class Writer), so only brief descriptions of those are given here.

    Method: (w: Writer) ClearError
    Clears error conditions on the writer w, re-enabling further write operations.
    Method: (w: Writer) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations failed.
    Method: (w: Writer) Pos () : LONGINT
    Returns the current writing position associated with the writer w in channel w.base.
    Method: (w: Writer) Res () : INTEGER
    This method returns the status of the last write operation (e.g., WriteBytes, WriteInt, SetPos, etc.) Note that unlike some other writer types, Res() is a method rather than a field; but otherwise, it performs equivalently. Error codes are highly dependent on the channel being written to (and therefore on the basic riders provided for that channel), so you must look at the result codes for the basic writer that is associated with that particular channel (e.g., Files.Writer error codes). See the various channel types for details of these error codes (i.e., section Module Files, section Module StdChannels, section Module ProgramArgs) Use ErrorDescr to get a plain text error description of this error code.
    Method: (w: Writer) SetEol (marker: ARRAY OF CHAR; markerLen: INTEGER)
    This method sets the end-of-line marker; that is, what character(s) is used to mark the end of a line. If the passed string marker does not fit into the field eol, then w.Res() is set to invalidFormat. The empty marker is permitted. The default value for a newly created writer is CharClass.systemEol. Pre-condition: All of the following apply:
    1. w.Res() = done, and
    2. 0 <= markerLen < LEN (marker), and
    3. markerLen <= maxLengthEol.
    Method: (w: Writer) SetOpts (opts: SET)
    This method is used to set the writer options w.opt.
    Method: (w: Writer) SetPos (newPos: LONGINT)
    Sets the writing position to newPos.

    The following writer methods are used to write values in text format to the underlying channel. In some situations, it is possible for only part of the value to be actually written.

    Method: (w: Writer) WriteBool (bool: BOOLEAN)
    Writes the value of bool as text. That is, either TRUE or FALSE.
    Method: (w: Writer) WriteChar (ch: CHAR)
    Writes a single character value ch.
    Method: (w: Writer) WriteHex (lint: LONGINT; d: LONGINT)
    Writes the value of lint as an unsigned hexadecimal number with a minimum field width of d. Leading zeros are written if the value of lint requires less than d places. If d is less than or equal to zero, field width is 8.
    Method: (w: Writer) WriteInt (int: INTEGER; n: LONGINT)
    Writes the value of int as a decimal number with a minimum field width of n. Leading spaces are written if the value of int requires less than n places. A sign is written only for negative values.
    Method: (w: Writer) WriteLInt (lint: LONGINT; n: LONGINT)
    This method provides the same facility as WriteInt, except that it deals with LONGINT values.
    Method: (w: Writer) WriteSInt (sint: SHORTINT; n: LONGINT)
    This method provides the same facility as WriteInt, except that it deals with SHORTINT values.
    Method: (w: Writer) WriteReal (real: REAL; n, k: LONGINT)
    Writes the value of real as a floating-point number with a minimum field width of n. If the value of k is greater than 0, that number of significant digits is included. Otherwise, an implementation-defined number of significant digits is included. The decimal point is not included if there are no significant digits in the fractional part. The number is scaled with one digit in the whole number part. A sign is included only for negative values.
    Method: (w: Writer) WriteLReal (lreal: LONGREAL; n, k: LONGINT)
    This method provides the same facility as WriteReal, except that it deals with LONGREAL values.
    Method: (w: Writer) WriteRealEng (real: REAL; n, k: LONGINT)
    Writes the value of real as a floating-point number with a minimum field width of n. If the value of k is greater than 0, that number of significant digits is included. Otherwise, an implementation-defined number of significant digits is included. The decimal point is not included if there are no significant digits in the fractional part. The number is scaled with one to three digits in the whole number part and with an exponent that is a multiple of three. A sign is included only for negative values.
    Method: (w: Writer) WriteLRealEng (lreal: LONGREAL; n, k: LONGINT)
    This method provides the same facility as WriteRealEng, except that it deals with LONGREAL values.
    Method: (w: Writer) WriteRealFix (real: REAL; n, k: LONGINT)
    Writes the value of real as a fixed-point number with a minimum field width of n. The value is rounded to the given value of k relative to the decimal point. The decimal point is suppressed if k is less than 0. The number will have at least one digit in the whole number part. A sign is included only for negative values.
    Method: (w: Writer) WriteLRealFix (lreal: LONGREAL; n, k: LONGINT)
    This method provides the same facility as WriteRealFix, except that it deals with LONGREAL values.
    Method: (w: Writer) WriteSet (s: SET)
    Writes the value of s as an Oberon-2 set constructor, including curly braces, commas, and range indicators ("..") where appropriate.
    Method: (w: Writer) WriteString (s: ARRAY OF CHAR)
    Writes a string value up to, but not including, the terminating 0X character. The behaviour of this method is undefined if s is an unterminated character array. Please note: ReadString and WriteString are not symmetric. That is, WriteString does not enclose the written string in quote marks; only the actual character values contained in s are written.
    Method: (w: Writer) WriteLn
    Writes an end-of-line marker (i.e., a "newline"). The default value for a newly created writer is CharClass.systemEol (see SetEol above).

    Class Scanner (Rider)

    A text scanner is a special type of reader, which is used to parse text for different kinds of tokens. Integers, reals, strings, identifiers, set constructors, the boolean tokens TRUE and FALSE, and other special symbols are all tokens recognized by this kind of scanner.

    These tokens are scanned sequentially, converted to an appropriate type, and then returned in one of the scanner's fields. The scanner's type field is then used to determine the type of token which has been scanned.

    Along with some typical reader methods, such as SetPos, the primary method of a scanner is Scan, which simply scans the next token based on the scanner's current options setting.

    See section Class Scanner (TextRider) for examples of usage.

    Data type: String
    A string type of pre-defined length for use within a scanner. Note that because this type is of finite length, a scanner is limited in the length of string it can scan.

    Please note: LEN() can be used on a variable of type String to determine the maximum size that can be held by a scanner string.

    Abstract Class: Scanner = POINTER TO ScannerDesc
    This class provides facilities for scanning sequences of characters from a channel and parsing those characters into various tokens. The tokens a scanner can recognize are defined by the constants provided for its type field (section Summary of TextRider Constants).

    Note that a scanner will not continue to read (via calls to Scan) if it has scanned an invalid token or an error occurs; ClearError must be called explicitly before scanning can continue. The difference is that invalid means that the token could not be interpreted; a sequence of characters was read, but could not be interpreted as a valid token. An error occurs when there is a problem with the underlying Reader; so, error is used to determine when you have reached end-of-text.

    Field: base-: Channel.Channel
    This field refers to the channel the scanner is connected to.
    Field: lines-: LONGINT
    Total number of lines (i.e., end-of-line characters) that have been scanned. This number is updated by Scan.
    Field: opt-: SET
    The current read options setting for the scanner. See section Summary of TextRider Constants for possible option values.
    Field: pos-: LONGINT
    Starting position of the most recently scanned token. Note that this is not the same as the value returned by the Pos() method. This value may be useful when an invalid token is scanned, as it will point to the start of the invalid token (whereas Pos() would be positioned after the invalid token). You could, for example, reset the scanner options and re-position the scanner back at the invalid token to attempt a re-scan.
    Field: type-: INTEGER
    The type of the token that has been most recently scanned. The constants bool, char, error, int, invalid, line, ident, real, set, string, tab, and undefined are possible values for type. See also the related output fields listed below.

    The following are the output fields within a scanner. Before the first call to the Scan method, the values of these fields are undefined. After each successive call to Scan, type is set and the matching output field contains the value of the scanned token. The value of output fields not corresponding to type are undefined.

    Field: bool-: BOOLEAN
    This field will contain a valid value only if the interpretBools option is set and one of the tokens TRUE or FALSE is scanned.
    Field: char-: CHAR
    Contains a value if type is char, line, or tab.
    Field: int-: LONGINT
    Contains a value if type is int. Please note: Valid integers are in either signed decimal or unsigned hexadecimal formats (hexadecimal tokens must be terminated with an "H" character).
    Field: real-: LONGREAL
    Contains a value if type is real.
    Field: set-: SET;
    Contains a value if type is set.
    Field: string-: String;
    Contains a value if type is string or ident.

    The following scanner methods are equivalent to the corresponding reader methods described in section Class Reader (TextRider), so only brief descriptions are given here.

    Method: (s: Scanner) Available () : LONGINT
    Returns the number of bytes available for the next scanning operation.
    Method: (s: Scanner) ClearError
    Clears error conditions on the scanner s, re-enabling further operations on s.
    Method: (s: Scanner) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations failed.
    Method: (s: Scanner) Pos (): LONGINT
    Returns the current reading position associated with the scanner s in channel s.base. Note that the value returned by this method is different from the position indicated by the scanner's pos field.
    Method: (s: Scanner) Res (): INTEGER
    This method returns the status of the last read operation (e.g., Scan, SetPos, etc.). Note that Res() is a method rather than a field; but otherwise, it performs equivalently. Use method ErrorDescr to get a plain text error description of this error code.
    Method: (s: Scanner) SetEol (marker: ARRAY OF CHAR; markerLen: INTEGER)
    This method sets the end-of-line marker; it provides the same facility as Reader.SetEol. A marker length markerLen=-1 enables auto detection of the end-of-line convention used by the channel.
    Method: (s: Scanner) SetOpts (opts: SET)
    This method is used to set the scanner options s.opt. See section Summary of TextRider Constants for possible option values.
    Method: (s: Scanner) SetPos (newPos: LONGINT)
    Sets the current scanning position to newPos.
    Method: (s: Scanner) Scan
    This method skips whitespace, and then scans for the next token as specified by the scanning options. Based on the type of token scanned, s.type is set and the matching output field is assigned a value. If the end of the valid text is reached, s.type is set to error. (Note that error is set when the last available valid token is read, not necessarily by a readAfterEnd condition.) Valid tokens are described as follows:
    bool
    If interpretBools is set as a scanner option, the text tokens TRUE or FALSE are read as bool. (Otherwise, these tokens are read as type ident.)
    char
    Normally, any printable characters other than a letter or number and any non-printable control character. However, scanner options will affect what a scanner interprets to be a char:
    • If interpretSets is not set, elements of a set constructor, "{", "}", ",", are read as char (and the associated integer constants are read as separate tokens).
    • If interpretStrings is not set, quote characters are read as char (and string contents are then read as separate tokens).
    • If useSignedNumbers is not set, "+" and "-" are read as char. (Otherwise, they are always considered part of a number.)
    int
    Any Oberon-2 integer constant. (Note that hexadecimal numbers must be unsigned and be terminated with an "H". Also, lower-case letters, `a..f', are not valid hex digits.)
    line
    If returnCtrlChars is set, an end-of-line character is read as s.type = line. Otherwise, it is counted as whitespace.
    ident
    Any Oberon-2 identifier. (Note that "_" is not considered as part of an identifier, nor is a selector ".".)
    real
    Any Oberon-2 real number constant.
    set
    Any Oberon-2 set constructor.
    string
    Any Oberon-2 string constant.
    tab
    If returnCtrlChars is set, a tab character is read as s.type = tab. Otherwise, it is counted as whitespace.

    Module LongRider

    Module `LongRider' extends the classes of `Rider' to provide support for types LONGCHAR and LongString. The classes of `LongRider' (Reader, Writer, and Scanner) are also abstract, and only extensions are described in this section; see section Module Rider for descriptions of other facilities.

    Also, see the concrete text mapper classes for more detail and examples of usage (see section Module TextRider and section Module UnicodeRider).

    Please note: Care should be taken when using the method SetPos for classes based on `LongRider'. Recall that SetPos operates just like the corresponding method from class Channel; that is, position is set directly within the byte stream. Setting the position is based on byte position rather than character position.

    Because `LongRider' based classes deal with multi-byte character encodings, which may be of variable width, and because SetPos positions a reader on a byte level, a user cannot necessarily set a rider to an arbitrary character position within a channel. For practical purposes, variable width encodings may limit usage to saving the position of a reader based on a call like pos := reader.Pos(), which can later be restored via reader.SetPos(pos).

    However, even in such a case, moving to a previously saved position might fail for encodings that use different states during decoding. For example, if the encoding uses special byte sequences to switch between different mappings while decoding, the actual mapping in use at file position `x' will not be reinstated correctly when calling `SetPos(x)'.

    Class Reader (LongRider)

    Abstract Class: Reader = POINTER TO ReaderDesc
    This is an abstract subclass of Rider.Reader that provides support for LONGCHAR and LongString.

    The specification for ReadChar is changed for LongRider.Reader in that it actually reads a LONGCHAR value (2 bytes) from the channel and then attempts to map it to a CHAR value (ISO-Latin-1). If the value cannot be mapped, a valueOutOfRange error occurs. Consequently for `LongRider', ReadLine, ReadIdentifier, and ReadString produce the same error in similar situations.

    Also note that a valueOutOfRange error occurs for methods reading into an ARRAY OF LONGCHAR (i.e., ReadLLine, ReadLIdentifier, and ReadLString) if the (long) character array is not large enough to hold the entire input.

    Reader adds the following methods:

    Method: (r: Reader) ReadLChar (VAR ch: LONGCHAR)
    Reads in a single (LONGCHAR) character value and places it in ch.
    Method: (r: Reader) ReadLIdentifier (VAR s: ARRAY OF LONGCHAR)
    Reads an Oberon-2 style identifier into s. An identifier is a sequence of letters and digits, which must begin with a letter. Sequences not beginning with a letter produce an invalidFormat error. If s is not large enough to hold the entire input, a valueOutOfRange error occurs. Upon encountering an error, the value of s is undefined.
    Method: (r: Reader) ReadLLine (VAR s: ARRAY OF LONGCHAR)
    Reads a sequence of (LONGCHAR) characters into s; reading continues until an end-of-line character is encountered, the array s is full, or r reaches the end of the channel. The end-of-line character is discarded and s is always terminated with 0X. If r is already positioned at an end-of-line character, s returns as an empty string. If s is not large enough to hold the entire input, a valueOutOfRange error occurs; s returns with the sequence of characters that have been read so far (terminated by 0X). If r has already reached the end of the channel (i.e., there are no more characters left to read), a readAfterEnd error occurs and s returns as an empty string.
    Method: (r: Reader) ReadLString (VAR s: ARRAY OF CHAR)
    Reads in a sequence of (LONGCHAR) characters enclosed in single (') or double (") quote marks. The opening quote must be the same as the closing quote and must not occur within the string. Characters will be read until the terminating quote mark is encountered, an invalid character is read (end-of-line is always considered invalid), there are no more characters available in the channel, or the string s is full. s is always terminated with 0X. Unquoted strings produce an invalidFormat error. Strings with no terminating quote mark also result in an invalidFormat error. If s is not large enough to hold the entire input, a valueOutOfRange error occurs. Upon encountering an error, the value of s is undefined.

    Class Writer (LongRider)

    Abstract Class: Writer = POINTER TO WriterDesc
    This is an abstract subclass of Rider.Writer that provides support for LONGCHAR and LongString.

    Note that the specification for WriteChar is changed for LongRider.Writer in that it actually writes 2 bytes at a time to the channel (i.e., CHAR values are actually written as Unicode values). ReadLine, ReadIdentifier, and ReadString behave similarly for `LongRider'.

    LongRider.Writer adds the following methods:

    Method: (w: Writer) WriteLChar (ch: LONGCHAR)
    Writes a single (LONGCHAR) character value ch.
    Method: (w: Writer) WriteLString (s: ARRAY OF LONGCHAR)
    Writes a long string value up to, but not including, the terminating 0X character. The behaviour of this method is undefined if s is an unterminated (LONGCHAR) character array. Please note: ReadLString and WriteLString are not symmetric. That is, WriteLString does not enclose the written string in quote marks; only the actual (LONGCHAR) character values contained in s are written.

    Class Scanner (LongRider)

    Abstract Class: Scanner = POINTER TO ScannerDesc
    This is an abstract subclass of Rider.Scanner that provides support for LONGCHAR and LongString.

    Data type: LongString
    A (long) string type of pre-defined length for use within a scanner. Note that because this type is of finite length, a scanner is limited in the length of string it can scan.

    Please note: LEN() can be used on a variable of type LongString to determine the maximum size that can be held by a scanner string.

    Field: type-: INTEGER
    This is an inherited field, however, it now has the additional possible values: lchar, lident, lline, lstring, ltab.
    Field: lchar-: LONGCHAR
    Contains a value if type is lchar, lline, or ltab.
    Field: lstring-: LongString;
    Contains a value if type is lstring or lident.

    Module TextRider

    Module `TextRider' provides concrete classes derived from the abstract base classes of module `Rider'. `TextRider' is used for reading and writing data as character type CHAR (i.e., interpreting byte streams as ISO-Latin-1 characters). The descriptions below include details of the `TextRider' facilities (much of which is repeated from the section on module `Rider') as well as many examples of use.

    The following program fragment gives an example of how you could use `TextRider' facilities to read the entire contents of a file, one line at a time, and echo each line to the screen (note that no error checking is done):

    VAR r: TextRider.Reader;
        f: Files.File;
        str: ARRAY 256 OF CHAR;
        res: INTEGER;
        
      f := Files.Old("Sample.txt", {Files.read}, res);
      r := TextRider.ConnectReader(f); 
    
      r.ReadLine(str);	
      WHILE r.Res()=Files.done DO
         Out.String(str); Out.Ln;
         r.ReadLine(str);	
      END;
    

    Class Reader (TextRider)

    Constant: maxLengthEol
    The maximum number of characters allowed in Reader.eol.

    Class: Reader = POINTER TO ReaderDesc
    This is the concrete subclass of Rider.Reader that provides facilities for reading various kinds of text. Note that this type does not inherit properties from any basic reader type; rather it uses the basic reader type associated with the channel it is attached to.

    Also note that, after any failed read operation, all further attempts to read will be ignored until the error is cleared using ClearError.

    Field: opt-: SET
    The current read options setting for the reader. See section Summary of TextRider Constants for possible option values.
    Field: base-: Channel.Channel
    This field refers to the channel the reader is connected to.

    The following fields determine how the reader interprets end-of-line markers. Note that the end-of-line marker may contain the character `0X', which means its length must be stored in a separate field. The eol marker cannot be empty, and all characters must be an ASCII code in the range 00X..1FX.

    Field: eol-: ARRAY maxLengthEol OF CHAR
    The character sequence that represents an end-of-line marker. Note that this is a character array, not a string (i.e., it may contain the character `0X').
    Field: eolLen-: INTEGER
    The number of characters in eol. The default value for this is `-1', which means that end-of-line is auto detected (see SetEol below). Otherwise, this value is in the range 1 <= eolLen <= maxLengthEol.

    The following methods can be used to check the status of a reader or, in some cases, change its state. Some methods are fully described in the abstract reader section (see section Abstract Class Reader), so only brief descriptions of those are given here.

    Method: (r: Reader) Available () : LONGINT
    Returns the number of bytes available for the next read operation.
    Method: (r: Reader) ClearError
    Clears error conditions on the reader r, re-enabling further read operations.
    Method: (r: Reader) Eol (): BOOLEAN
    This method returns TRUE if the reader is currently positioned at an end-of-line marker (see SetEol below). This will also return TRUE if r.Res() # done. Otherwise, FALSE is returned.
    Method: (r: Reader) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations failed.
    Method: (r: Reader) Pos (): LONGINT
    Returns the current reading position associated with the reader r in channel r.base.
    Method: (r: Reader) Res (): INTEGER
    This method returns the status of the last read operation (e.g., ReadLine, ReadInt, SetPos, etc.). Note that unlike some other reader types, Res() is a method rather than a field; but otherwise, it performs equivalently. Error codes are highly dependent on the channel being read, and therefore on the basic riders provided by that channel, so you must look at the result codes for a particular channel's reader type (e.g., Files.Reader error codes). See the various channel types for details of these error codes (i.e., section Module Files, section Module StdChannels, or section Module ProgramArgs). Use method ErrorDescr to get a plain text error description of this error code.
    Method: (r: Reader) SetEol (marker: ARRAY OF CHAR; markerLen: INTEGER)
    This method sets the end-of-line marker; that is, what character(s) is used to mark the end of a line. If the passed string marker does not fit into the field eol, or if it contains a character >= ` ', then r.Res() is set to invalidFormat. A marker length markerLen=-1 enables auto detection of the end-of-line convention used by the channel. For auto detection to work, the channel is required to use one of the following eol markers:
    `LF'
    used by Unix
    `CR'
    used by MacOS
    `CR/LF'
    used by MS-DOS and Windows
    Please note: ReadChar is unaffected by the current eol setting. That is, if the end-of-line marker consists of more than one character (like `CR/LF'), each character is read separately. All other read operations view an end-of-line marker at an atomic entity when the channel is read sequentially. If auto detection is enabled, and the eol convention of the file is `CR/LF', then the first end-of-line marker is not skipped completely when reached by the reader (r.Pos() is at the `LF'). This is transparent to all reading procedures except ReadChar and Pos; the `LF' will be skipped automatically on the next read. This positioning inconsistency only applies for the very first eol encountered. Pre-condition: All of the following apply:
    1. r.Res() = done, and
    2. (markerLen = -1) OR (1 <= markerLen < LEN (marker)), and
    3. markerLen <= maxLengthEol, and
    4. for all i: marker[i] < 20X
    Method: (r: Reader) SetOpts (opts: SET)
    This method is used to set the reader options r.opt. See section Summary of TextRider Constants for possible option values. Example:
    r.SetOpts({TextRider.returnCtrlChars});
       => read operations using r do not treat EOL and TAB 
            characters as whitespace.  
    r.SetOpts(TextRider.defReaderOptions);
       => reader options set to default values.
    
    Method: (r: Reader) SetPos (newPos: LONGINT)
    Sets the reading position to newPos.

    The following methods read a value of the given type from the current position of the reader. Most read operations skip leading whitespace before reading a token; there are only three methods that do not skip whitespace: ReadChar, ReadLn, and ReadLine.

    When attempting to read, and if the value is not properly formatted for its type, r.Res() returns invalidFormat. The reader remains positioned at the character which caused the invalidFormat error, but further reading can not take place until the error is cleared.

    If a number, or potential set element, is properly formatted, but has a value that is out of range of the target type, then a valueOutOfRange error occurs. In this case, the reader is positioned after the last character that was read. Again, further reading can not take place until the error is cleared.

    A valueOutOfRange error also occurs for methods reading into an ARRAY OF CHAR (i.e., ReadLine, ReadIdentifier, and ReadString) if the character array is not large enough to hold the entire input.

    Otherwise, for any operation attempting to read when there are no characters left to be read, a read-after-end error occurs and Reader.Res() returns readAfterEnd.

    In any case, whenever an error occurs, it is safest to assume that no value has been read. That is, the variable being read into is left with an undefined value.

    All further calls of these read methods will be ignored if r.Res()#done. That is, no new characters will be read if an error has occurred previously.

    Method: (r: Reader) ReadBool (VAR bool: BOOLEAN)
    Reads in an identifier (see ReadIdentifier below), and if it is either of the tokens TRUE or FALSE, it is converted to a BOOLEAN value. If this method encounters any other token, an invalidFormat error occurs and the value of bool is undefined.
    Method: (r: Reader) ReadChar (VAR ch: CHAR)
    Reads in a single character value and places it in ch.
    Method: (r: Reader) ReadHex (VAR lint: LONGINT)
    Reads in characters in the form of an unsigned hexadecimal number and converts them to a LONGINT value. The first character must be a decimal digit (i.e., `0..9') and subsequent characters must be valid hexadecimal digits (i.e., `0..9' or `A..F'). If the first non-whitespace character is not a digit, then an invalidFormat error occurs. If the input is properly formatted as an unsigned hex number, but the value is out of range for a LONGINT, then a valueOutOfRange error occurs. Upon encountering an error, the value of lint is undefined. Please note: Because LONGINT values are signed, hex numbers in the range `80000000H..FFFFFFFFH' are interpreted as negative LONGINT values.
    Method: (r: Reader) ReadIdentifier (VAR s: ARRAY OF CHAR)
    Reads an Oberon-2 style identifier into s. An identifier is a sequence of letters and digits, which must begin with a letter. Sequences not beginning with a letter produce an invalidFormat error. If s is not large enough to hold the entire input, a valueOutOfRange error occurs. Upon encountering an error, the value of s is undefined. Example:
    (* Input is as follows:  
    myIdentifier x y2 3z 
    *)
    
    VAR str: ARRAY 256 OF CHAR;
    
    r.ReadIdentifier(str)
       => str = "myIdentifier"
    r.ReadIdentifier(str)
       => str = "x"
    r.ReadIdentifier(str)
       => str = "y2"
    r.ReadIdentifier(str)
       => r.Res() = invalidFormat, str = undefined
    
    Method: (r: Reader) ReadInt (VAR int: INTEGER)
    Reads in characters in the form of a signed whole number and converts them to an INTEGER value. If the first character is not a digit, a "+" sign, or a "-" sign, then an invalidFormat error occurs. If the input is properly formatted as a signed whole number, but the value is out of range for an INTEGER, then a valueOutOfRange error occurs. Upon encountering an error, the value of int is undefined. Example:
    (* Input is as follows:
    12345
    999999999999999
    forty-two
    *)
    
    VAR intVar: INTEGER;
    
    r.ReadInt(intVar);
       => intVar = 12345
    r.ReadInt(intVar);
       => r.Res() = valueOutOfRange, intVar = undefined
    r.ClearError;
    r.ReadInt(intVar); (* attempting to read `forty-two' *)
       => r.Res() = invalidFormat, intVar = undefined
            (* r.Pos() is still at the `f' in `forty-two' *)
    
    Method: (r: Reader) ReadLInt (VAR lint: LONGINT)
    This method provides the same facility as ReadInt, except that it deals with LONGINT values.
    Method: (r: Reader) ReadSInt (VAR sint: SHORTINT)
    This method provides the same facility as ReadInt, except that it deals with SHORTINT values.
    Method: (r: Reader) ReadLine (VAR s: ARRAY OF CHAR)
    Reads a sequence of characters into s; reading continues until an end-of-line character is encountered, the array s is full, or r reaches the end of the channel. The end-of-line character is discarded and s is always terminated with 0X. If r is already positioned at an end-of-line character, s returns as an empty string. If s is not large enough to hold the entire input, a valueOutOfRange error occurs; s returns with the sequence of characters that have been read so far (terminated by 0X). If r has already reached the end of the channel (i.e., there are no more characters left to read), a readAfterEnd error occurs and s returns as an empty string.
    Method: (r: Reader) ReadLn
    This method reads and discards all characters up to and including the next end-of-line character. If the end of the channel is reached before encountering an end-of-line character, a readAfterEnd error occurs.
    Method: (r: Reader) ReadString (VAR s: ARRAY OF CHAR)
    Reads in a sequence of characters enclosed in single (') or double (") quote marks. The opening quote must be the same as the closing quote and must not occur within the string. Characters will be read until the terminating quote mark is encountered, an invalid character is read (end-of-line is always considered invalid), there are no more characters available in the channel, or the string s is full. s is always terminated with 0X. Unquoted strings produce an invalidFormat error. Strings with no terminating quote mark also result in an invalidFormat error. If s is not large enough to hold the entire input, a valueOutOfRange error occurs. Upon encountering an error, the value of s is undefined. Example:
    (* Input is as follows:
    "A well-formed string"
    'This is well-formed too'
    "Not well-formed
    because of line break"
    *)
    
    VAR str: ARRAY 256 OF CHAR;
    
    r.ReadString(str);
       => str = "A well-formed string"
    r.ReadString(str);
       => str = "This is well-formed too"
    r.ReadString(str);
       => r.Res() = invalidFormat, str = undefined
            (* r.Pos() is now at the end of this line *)
    r.ClearError;
    r.ReadString(str);  
       (* attempting to read `because of line break"' *)
       => r.Res() = invalidFormat, str = undefined
    
    Method: (r: Reader) ReadReal (VAR real: REAL)
    Reads in characters in the form of a signed fixed or floating-point number and converts them to a REAL value. If the first character is not a digit, a "+" sign, or a "-" sign, then an invalidFormat error occurs. If the input is properly formatted as a signed fixed or floating-point number, but the value is out of range for a REAL, then a valueOutOfRange error occurs. Upon encountering an error, the value of real is undefined. Example:
    (* Input is as follows:
    -42
    3.1415
    +54321E+30
    2.34E+56
    +A
    _34.56
    *)
    
    VAR realVar: REAL;
    
    r.ReadReal(realVar);
       => realVar = -4.200000E+1
    r.ReadReal(realVar);
       => realVar = 3.141500
    r.ReadReal(realVar);
       => realVar = 5.432100E+34
    r.ReadReal(realVar);
       => r.Res() = valueOutOfRange, realVar = undefined
    r.ReadReal(realVar);
       => r.Res() = done, realVar = 0.000000
            (* r.Pos() is now at `A' *)
    r.ClearError; r.ReadLn; 
       => Clear error and skip to the beginning of the next line 
    r.ReadReal(realVar);
       => r.Res() = invalidFormat, realVar = undefined
            (* r.Pos() is still at the `_' in `_34.56' *)
    
    Method: (r: Reader) ReadLReal (VAR lreal: LONGREAL)
    This method provides the same facility as ReadReal, except that it deals with LONGREAL values.
    Method: (r: Reader) ReadSet (VAR s: SET)
    Reads in characters in the form of a set constructor and converts them to a SET. If the sequence of characters does not form a valid set constructor, then an invalidFormat error occurs. If the input is properly formatted as a set constructor, but a set element has a value out of the range 0..MAX(SET), then a valueOutOfRange error occurs. Upon encountering an error, the value of s is undefined. Example:
    (* Input is as follows:
    {0, 1, 2, 3, 4, 5}
    { 0..5 }
    {6, 7, 1024}
    {6, 7, W}
    9..11
    {13..12}
    *)
    
    VAR setVar: SET;
    
    r.ReadSet(setVar);
       => setVar = {0..5}
    r.ReadSet(setVar);
       => setVar = {0..5}
    r.ReadSet(setVar);
       => r.Res() = valueOutOfRange, setVar = undefined
            (* r.Pos() is now at the `}' after the `1024' *)
    r.ClearError; r.ReadLn; 
       => Clear error and skip to the beginning of the next line 
    
    r.ReadSet(setVar);  (* attempt to read `{6, 7, W}' *)
       => r.Res() = invalidFormat, setVar = undefined
            (* r.Pos() is now at `W' *)
    r.ClearError; r.ReadLn; 
       => Clear error and skip to the beginning of the next line 
    
    r.ReadSet(setVar);  (* attempt to read `9..11' *)
       => r.Res() = invalidFormat, setVar = undefined
            (* r.Pos() is now at `9' *)
    r.ClearError; r.ReadLn; 
       => Clear error and skip to the beginning of the next line 
    
    r.ReadSet(setVar);  (* attempt to read `{13..12}' *)
       => r.Res() = invalidFormat, setVar = undefined
            (* r.Pos() is now at the `}' after the `12' *)
    

    Class Writer (TextRider)

    Class: Writer = POINTER TO WriterDesc
    This class provides facilities for writing various types of text. Note that this type does not inherit properties from any basic writer type; rather it uses the basic writer type associated with the channel it is attached to.

    Field: opt-: SET
    The current write options setting for the writer. See section Summary of TextRider Constants for possible option values.
    Field: base-: Channel.Channel
    This field refers to the channel the writer is connected to.

    The following methods can be used to check the status of a writer or, in some cases, change its state. Some methods are fully described in the abstract writer section (see section Abstract Class Writer), so only brief descriptions of those are given here.

    Method: (w: Writer) ClearError
    Clears error conditions on the writer w, re-enabling further write operations.
    Method: (w: Writer) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations failed.
    Method: (w: Writer) Pos () : LONGINT
    Returns the current writing position associated with the writer w in channel w.base.
    Method: (w: Writer) Res () : INTEGER
    This method returns the status of the last write operation (e.g., WriteBytes, WriteInt, SetPos, etc.) Note that unlike some other writer types, Res() is a method rather than a field; but otherwise, it performs equivalently. Error codes are highly dependent on the channel being written to (and therefore on the basic riders provided for that channel), so you must look at the result codes for the basic writer that is associated with that particular channel (e.g., Files.Writer error codes). See the various channel types for details of these error codes (i.e., section Module Files, section Module StdChannels, section Module ProgramArgs) Use ErrorDescr to get a plain text error description of this error code.
    Method: (w: Writer) SetEol (marker: ARRAY OF CHAR; markerLen: INTEGER)
    This method sets the end-of-line marker; that is, what character(s) is used to mark the end of a line. If the passed string marker does not fit into the field eol, then w.Res() is set to invalidFormat. The empty marker is permitted. The default value for a newly created writer is CharClass.systemEol. Pre-condition: All of the following apply:
    1. w.Res() = done, and
    2. 0 <= markerLen < LEN (marker), and
    3. markerLen <= maxLengthEol.
    Method: (w: Writer) SetOpts (opts: SET)
    This method is used to set the writer options w.opt. See section Summary of TextRider Constants for possible option values. Example:
    w.SetOpts({TextRider.noBuffering});
       => output is not buffered.
    w.SetOpts(TextRider.defWriterOptions);
       => writer options set to default values.
    
    Method: (w: Writer) SetPos (newPos: LONGINT)
    Sets the writing position to newPos.

    The following writer methods are used to write values in text format to the underlying channel. In some situations, it is possible for only part of the value to be actually written.

    Method: (w: Writer) WriteBool (bool: BOOLEAN)
    Writes the value of bool as text. That is, either TRUE or FALSE.
    Method: (w: Writer) WriteChar (ch: CHAR)
    Writes a single character value ch. Example:
    w.WriteChar("A");
       => writes one character = "A"
    
    Method: (w: Writer) WriteHex (lint: LONGINT; d: LONGINT)
    Writes the value of lint as an unsigned hexadecimal number with a minimum field width of d. Leading zeros are written if the value of lint requires less than d places. If d is less than or equal to zero, field width is 8. Example:
    w.WriteHex(127, 3);
       => writes "07F"  
    w.WriteHex(127, 0);
       => writes "0000007F"  
    w.WriteHex(-128, 0);
       => writes "FFFFFF80"
    
    Method: (w: Writer) WriteInt (int: INTEGER; n: LONGINT)
    Writes the value of int as a decimal number with a minimum field width of n. Leading spaces are written if the value of int requires less than n places. A sign is written only for negative values. Example:
    w.WriteInt(54321, 0);
       => writes "54321"
    w.WriteInt(54321, 10);
       => writes "     54321"
    
    Method: (w: Writer) WriteLInt (lint: LONGINT; n: LONGINT)
    This method provides the same facility as WriteInt, except that it deals with LONGINT values.
    Method: (w: Writer) WriteSInt (sint: SHORTINT; n: LONGINT)
    This method provides the same facility as WriteInt, except that it deals with SHORTINT values.
    Method: (w: Writer) WriteReal (real: REAL; n, k: LONGINT)
    Writes the value of real as a floating-point number with a minimum field width of n. If the value of k is greater than 0, that number of significant digits is included. Otherwise, an implementation-defined number of significant digits is included. The decimal point is not included if there are no significant digits in the fractional part. The number is scaled with one digit in the whole number part. A sign is included only for negative values. Example:
    w.WriteReal(3923009, 0, 0);
       => writes "3.923009E+6"
    w.WriteReal(3923009, 0, 1);
       => writes "4E+6"
    w.WriteReal(3923009, 0, 4);
       => writes "3.923E+6"
    w.WriteReal(3923009, 10, 1);
       => writes "      4E+6"
    
    w.WriteReal(-39.23009, 12, 2);
       => writes "     -3.9E+1"
    w.WriteReal(-39.23009, 1, 5);
       => writes "-3.9230E+1"
    
    w.WriteReal(0.0003923009, 6, 1);
       => writes "  4E-4"
    
    Method: (w: Writer) WriteLReal (lreal: LONGREAL; n, k: LONGINT)
    This method provides the same facility as WriteReal, except that it deals with LONGREAL values.
    Method: (w: Writer) WriteRealEng (real: REAL; n, k: LONGINT)
    Writes the value of real as a floating-point number with a minimum field width of n. If the value of k is greater than 0, that number of significant digits is included. Otherwise, an implementation-defined number of significant digits is included. The decimal point is not included if there are no significant digits in the fractional part. The number is scaled with one to three digits in the whole number part and with an exponent that is a multiple of three. A sign is included only for negative values. Example:
    w.WriteRealEng(39.23009, 0, 1);
       => writes "40"
    w.WriteRealEng(39.23009, 5, 2);
       => writes "   39"
    w.WriteRealEng(39.23009, 10, 5);
       => writes "    39.230"
    
    w.WriteRealEng(-3923009, 13, 1);
       => writes "        -4E+6"
    w.WriteRealEng(-3923009, 7, 3);
       => writes " -3.92E+6"
    w.WriteRealEng(-3923009, 0, 6);
       => writes "-3.92301E+6"
    
    w.WriteRealEng(0.0003923009, 1, 1);
       => writes "400E-6"
    w.WriteRealEng(0.0003923009, 4, 2);
       => writes "  390E-6"
    w.WriteRealEng(0.0003923009, 16, 5);
       => writes "       392.30E-6"
    
    Method: (w: Writer) WriteLRealEng (lreal: LONGREAL; n, k: LONGINT)
    This method provides the same facility as WriteRealEng, except that it deals with LONGREAL values.
    Method: (w: Writer) WriteRealFix (real: REAL; n, k: LONGINT)
    Writes the value of real as a fixed-point number with a minimum field width of n. The value is rounded to the given value of k relative to the decimal point. The decimal point is suppressed if k is less than 0. The number will have at least one digit in the whole number part. A sign is included only for negative values. Example:
    w.WriteRealFix(3923009, 0, -5);
       => writes "3920000"  (* rounded to the 
                            ten-thousands place *)
    w.WriteRealFix(3923009, 0, 4);
       => writes "3923009.0000"
    
    w.WriteRealFix(3923.5, 0, -1);
       => writes "3924" (* rounded to the "ones" place *)
    w.WriteRealFix(3923.5, 0, 0);
       => writes "3924." (* same as above, 
                            but writes a decimal point *)
    
    w.WriteRealFix(-39.23009, 10, 1);
       => writes "     -39.2"
    w.WriteRealFix(-39.23009, 20, 4);
       => writes "            -39.2301"
    
    w.WriteRealFix(0.0003923009, 5, 1);
       => writes "  0.0"
    w.WriteRealFix(0.0003923009, 11, 4);
       => writes "     0.0004"
    
    Method: (w: Writer) WriteLRealFix (lreal: LONGREAL; n, k: LONGINT)
    This method provides the same facility as WriteRealFix, except that it deals with LONGREAL values.
    Method: (w: Writer) WriteSet (s: SET)
    Writes the value of s as an Oberon-2 set constructor, including curly braces, commas, and range indicators ("..") where appropriate. Example:
    w.WriteSet({});
       => writes "{}"
    w.WriteSet({1,6,10});
       => writes "{1, 6, 10}"
    w.WriteSet({0, 1, 2, 3, 4, 5});
       => writes "{0..5}"
    w.WriteSet({0, 2, 3, 4, 8});
       => writes "{0, 2..4, 8}"
    w.WriteSet({0, 2..7, 8});
       => writes "{0, 2..8}"
    w.WriteSet({0, 2, 4, 6} + {1, 3, 5, 7});
       => writes "{0..7}"
    
    Method: (w: Writer) WriteString (s: ARRAY OF CHAR)
    Writes a string value up to, but not including, the terminating 0X character. The behaviour of this method is undefined if s is an unterminated character array. Please note: ReadString and WriteString are not symmetric. That is, WriteString does not enclose the written string in quote marks; only the actual character values contained in s are written.
    Method: (w: Writer) WriteLn
    Writes an end-of-line marker (i.e., a "newline"). The default value for a newly created writer is CharClass.systemEol (see SetEol above).

    Class Scanner (TextRider)

    A text scanner is a special type of reader, which is used to parse text for different kinds of tokens. Integers, reals, strings, identifiers, set constructors, the boolean tokens TRUE and FALSE, and other special symbols are all tokens recognized by this kind of scanner.

    These tokens are scanned sequentially, converted to an appropriate type, and then returned in one of the scanner's fields. The scanner's type field is then used to determine the type of token which has been scanned.

    Along with some typical reader methods, such as SetPos, the primary method of a scanner is Scan, which simply scans the next token based on the scanner's current options setting. A typical use of a scanner might look similar the following program fragment:

    Example:

    VAR s: TextRider.Scanner;
        f: Files.File;
        res: INTEGER;
        
      f := Files.Old("Sample.txt", {Files.read}, res);
      s := TextRider.ConnectScanner(f); 
    
      s.Scan;
      WHILE s.type # TextRider.error DO
         IF s.type = TextRider.string THEN
            ... (* Process string tokens *)
         ELSIF s.type = TextRider.ident THEN
            ... (* Process identifier tokens *)
         ELSIF s.type = TextRider.int THEN   
            ... (* Process integer tokens *)
         ELSIF ...
            ... (* Process other token types *)
         END; 
         s.Scan;
      END;
    
      Out.String("Total lines scanned="); 
      Out.LongInt(s.lines, 0); Out.Ln;
    

    Data type: String
    A string type of pre-defined length for use within a scanner. Note that because this type is of finite length, a scanner is limited in the length of string it can scan.

    Please note: LEN() can be used on a variable of type String to determine the maximum size that can be held by a scanner string.

    Class: Scanner = POINTER TO ScannerDesc
    This class provides facilities for scanning sequences of characters from a channel and parsing those characters into various tokens. The tokens a scanner can recognize are defined by the constants provided for its type field (section Summary of TextRider Constants).

    Note that a scanner will not continue to read (via calls to Scan) if it has scanned an invalid token or an error occurs; ClearError must be called explicitly before scanning can continue. The difference is that invalid means that the token could not be interpreted; a sequence of characters was read, but could not be interpreted as a valid token. An error occurs when there is a problem with the underlying Reader; so, error is used to determine when you have reached end-of-text.

    Field: base-: Channel.Channel
    This field refers to the channel the scanner is connected to.
    Field: lines-: LONGINT
    Total number of lines (i.e., end-of-line characters) that have been scanned. This number is updated by Scan.
    Field: opt-: SET
    The current read options setting for the scanner. See section Summary of TextRider Constants for possible option values.
    Field: pos-: LONGINT
    Starting position of the most recently scanned token. Note that this is not the same as the value returned by the Pos() method. This value may be useful when an invalid token is scanned, as it will point to the start of the invalid token (whereas Pos() would be positioned after the invalid token). You could, for example, reset the scanner options and re-position the scanner back at the invalid token to attempt a re-scan.
    Field: type-: INTEGER
    The type of the token that has been most recently scanned. The constants bool, char, error, int, invalid, line, ident, real, set, string, tab, and undefined are possible values for type. See also the related output fields listed below.

    The following are the output fields within a scanner. Before the first call to the Scan method, the values of these fields are undefined. After each successive call to Scan, type is set and the matching output field contains the value of the scanned token. The value of output fields not corresponding to type are undefined.

    Field: bool-: BOOLEAN
    This field will contain a valid value only if the interpretBools option is set and one of the tokens TRUE or FALSE is scanned.
    Field: char-: CHAR
    Contains a value if type is char, line, or tab.
    Field: int-: LONGINT
    Contains a value if type is int. Please note: Valid integers are in either signed decimal or unsigned hexadecimal formats (hexadecimal tokens must be terminated with an "H" character).
    Field: real-: LONGREAL
    Contains a value if type is real.
    Field: set-: SET;
    Contains a value if type is set.
    Field: string-: String;
    Contains a value if type is string or ident.

    The following scanner methods are equivalent to the corresponding reader methods described in section Class Reader (TextRider), so only brief descriptions are given here.

    Please note: Normally when scanning text, a program will monitor a scanner's type field and check for invalid tokens and the occurance of error. The Res() or ErrorDescr methods need to be checked only to find out error details (and then, possibly, the ClearError method can be used to clear the error).

    Example:

    VAR s: TextRider.Scanner;
        f: Files.File;
        res: INTEGER;
        str: ARRAY 256 OF CHAR;
        
    f := Files.Old("Sample.txt", {Files.read}, res);
    s := TextRider.ConnectScanner(f); 
    
    f.Close;
    s.Scan;
       => s.type = error
    s.ErrorDescr(str);
       => str = "File has been closed"
    
    Method: (s: Scanner) Available () : LONGINT
    Returns the number of bytes available for the next scanning operation.
    Method: (s: Scanner) ClearError
    Clears error conditions on the scanner s, re-enabling further operations on s.
    Method: (s: Scanner) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations failed.
    Method: (s: Scanner) Pos (): LONGINT
    Returns the current reading position associated with the scanner s in channel s.base. Note that the value returned by this method is different from the position indicated by the scanner's pos field.
    Method: (s: Scanner) Res (): INTEGER
    This method returns the status of the last read operation (e.g., Scan, SetPos, etc.). Note that Res() is a method rather than a field; but otherwise, it performs equivalently. Use method ErrorDescr to get a plain text error description of this error code.
    Method: (s: Scanner) SetEol (marker: ARRAY OF CHAR; markerLen: INTEGER)
    This method sets the end-of-line marker; it provides the same facility as Reader.SetEol. A marker length markerLen=-1 enables auto detection of the end-of-line convention used by the channel.
    Method: (s: Scanner) SetOpts (opts: SET)
    This method is used to set the scanner options s.opt. See section Summary of TextRider Constants for possible option values. Example:
    s.SetOpts({TextRider.returnCtrlChars, 
            TextRider.useSignedNumbers});
       => s.opt = {returnCtrlChars, useSignedNumbers}
    s.SetOpts(s.opt + {TextRider.interpretBools});
       => s.opt = {interpretBools, returnCtrlChars, 
            useSignedNumbers}
    s.SetOpts(TextRider.defScannerOptions);
       => scanner options set to default values.
    
    Method: (s: Scanner) SetPos (newPos: LONGINT)
    Sets the current scanning position to newPos.
    Method: (s: Scanner) Scan
    This method skips whitespace, and then scans for the next token as specified by the scanning options. Based on the type of token scanned, s.type is set and the matching output field is assigned a value. If the end of the valid text is reached, s.type is set to error. (Note that error is set when the last available valid token is read, not necessarily by a readAfterEnd condition.) Valid tokens are described as follows:
    bool
    If interpretBools is set as a scanner option, the text tokens TRUE or FALSE are read as bool. (Otherwise, these tokens are read as type ident.)
    char
    Normally, any printable characters other than a letter or number and any non-printable control character. However, scanner options will affect what a scanner interprets to be a char:
    • If interpretSets is not set, elements of a set constructor, "{", "}", ",", are read as char (and the associated integer constants are read as separate tokens).
    • If interpretStrings is not set, quote characters are read as char (and string contents are then read as separate tokens).
    • If useSignedNumbers is not set, "+" and "-" are read as char. (Otherwise, they are always considered part of a number.)
    int
    Any Oberon-2 integer constant. (Note that hexadecimal numbers must be unsigned and be terminated with an "H". Also, lower-case letters, `a..f', are not valid hex digits.)
    line
    If returnCtrlChars is set, an end-of-line character is read as s.type = line. Otherwise, it is counted as whitespace.
    ident
    Any Oberon-2 identifier. (Note that "_" is not considered as part of an identifier, nor is a selector ".".)
    real
    Any Oberon-2 real number constant.
    set
    Any Oberon-2 set constructor.
    string
    Any Oberon-2 string constant.
    tab
    If returnCtrlChars is set, a tab character is read as s.type = tab. Otherwise, it is counted as whitespace.

    Connecting TextRiders to Channels

    The following procedures are provided for creating instances of `TextRider' objects and connecting them to a channel. If the channel being passed as an argument to any of these functions has a value of NIL, behavior is undefined.

    Also, for any of these functions, the returned rider is positioned at the beginning of the channel for positionable channels and at the current position for non-positionable channels.

    Function: ConnectReader (ch: Channel.Channel): Reader
    This function creates a new reader and attaches it to the channel ch. ch.res is set to done on success and the new reader is returned. Otherwise, it returns NIL and ch.res is set to indicate the error cause.

    Function: ConnectWriter (ch: Channel.Channel): Writer
    This function creates a new writer and attaches it to the channel ch. ch.res is set to done on success and the new writer is returned. Otherwise, it returns NIL and ch.res is set to indicate the error cause.

    Function: ConnectScanner (ch: Channel.Channel): Scanner
    This function creates a new scanner and attaches it to the channel ch. ch.res is set to done on success and the new scanner is returned. Otherwise, it returns NIL and ch.res is set to indicate the error cause.

    Example:

    VAR
      r: TextRider.Reader;
      f: Files.File;
      res: INTEGER;
      
      f := Files.Old("test.dat", {Files.read}, res);
      IF (res # Files.done) THEN (* error processing *) END;
      
      r := TextRider.ConnectReader(f);
      IF (r = NIL) THEN (* error processing *) END;
    

    Summary of TextRider Constants

    Constant: maxLengthEol
    The maximum number of characters allowed in Reader.eol.

    For other constant values that may be applicable when using module `TextRider', see the specific channel implementation that you are reading to or writing from, such as section Module Files, section Module StdChannels, or section Module ProgramArgs.

    The following are possible return values for Res() methods:

    Constant: done
    This indicates successful completion of the last operation.

    Constant: invalidFormat
    Indicates that the text at the current reading (or scanning) position is not properly formatted as the requested type.

    Constant: valueOutOfRange
    Indicates that a number, or potential set element, is in the proper format, but has a value that is out of range of the target type.

    The following are all possible values for a scanner's type field:

    Constant: bool
    The scanner has read a valid boolean value. This can only be set when the scanner's options include interpretBools.

    Constant: char
    The scanner has read a valid character value.

    Constant: error
    Indicates that an error has occured while scanning. This could be an error condition resulting from one of the scanner's own operations (for example, an attempt to Scan when the scanner has reached the end of available text), or a result of a lower level error (say, an error occured in the underlying channel).

    Constant: ident
    The scanner has read a valid (Oberon-2) identifier.

    Constant: int
    The scanner has read a valid integer value.

    Constant: invalid
    The scanner has read an invalid value. Note that when type = invalid, the contents of all of the scanner's output fields are undefined.

    Constant: line
    The scanner has read a valid end-of-line character. This can only be set when the scanner's options include returnCtrlChars.

    Constant: real
    The scanner has read a valid real number value.

    Constant: set
    The scanner has read a valid set constructor value. This can only be set when the scanner's options include interpretSets.

    Constant: string
    The scanner has read a valid (Oberon-2) string value. This can only be set when the scanner's options include interpretStrings.

    Constant: tab
    The scanner has read a valid tab character. This can only be set when the scanner's options include returnCtrlChars.

    Constant: undefined
    This is the initial value of Scanner.type after ConnectScanner or ClearError (before any calls to Scan).

    The following is a possible writer option (i.e., a valid setting for the writer's opt field):

    Constant: noBuffering
    When this option is set for a writer, output is not buffered. This allows, for example, for interactive output prompts to appear as soon as they are written.

    The following is a possible reader or scanner option (i.e., a valid setting for the opt field):

    Constant: returnCtrlChars
    When this option is set, end-of-line and tab characters are not counted as whitespace.
    Scanners also permit the following additional options:

    Constant: interpretBools
    When this option is set, the text tokens TRUE or FALSE are read as boolean values (i.e., scanner.type = bool). Otherwise, these tokens are read as identifiers (i.e., scanner.type = ident.)

    Constant: interpretSets
    When set, text in the form a set constructor (with "{", "}", ",", and associated integer constants) are read as SET values. Otherwise, these are read as separate tokens.

    Constant: interpretStrings
    When set, quoted character sequences are read as string values. Otherwise, quote characters and string contents are read as separate tokens.

    Constant: useSignedNumbers
    When set, "+" and "-" characters are always considered part of a number. Otherwise, they are read as separate characters.

    Constant: defReaderOptions
    The default reader options setting, which is equivalent to having no options set (i.e., {}).

    Constant: defWriterOptions
    The default writer options setting, which is equivalent to having no options set (i.e., {}).

    Constant: defScannerOptions
    The default scanner options setting, which is equivalent to setting the options interpretBools, interpretSets, interpretStrings, and
    useSignedNumbers.

    Module UnicodeRider

    Module `UnicodeRider' provides concrete classes derived from the abstract base classes of module `LongRider'. `UnicodeRider' is used for reading and writing data as (long) character type LONGCHAR (i.e., interpreting byte streams as Unicode characters). The following sections describe only `UnicodeRider' specific facilities; see section Module TextRider for examples of usage and descriptions of facilities inherited from section Module Rider.

    Class Reader (UnicodeRider)

    Class: Reader = POINTER TO ReaderDesc
    This is the concrete subclass of LongRider.Reader that provides facilities for reading various kinds of unicode text.

    Note that, in UnicodeRider.Reader, ReadChar actually reads a LONGCHAR value (2 bytes) from the channel and then attempts to map it to a CHAR value (ISO-Latin-1). If the value cannot be mapped, a valueOutOfRange error occurs. Consequently for `UnicodeRider', ReadLine, ReadIdentifier, and ReadString produce the same error in similar situations.

    Also note that a valueOutOfRange error occurs for methods reading into an ARRAY OF LONGCHAR (i.e., ReadLLine, ReadLIdentifier, and ReadLString) if the (long) character array is not large enough to hold the entire input.

    UnicodeRider.Reader adds the following methods:

    Method: (r: Reader) ReadLChar (VAR ch: LONGCHAR)
    Reads in a single (LONGCHAR) character value and places it in ch.
    Method: (r: Reader) ReadLIdentifier (VAR s: ARRAY OF LONGCHAR)
    Reads an Oberon-2 style identifier into s. An identifier is a sequence of letters and digits, which must begin with a letter. Sequences not beginning with a letter produce an invalidFormat error. If s is not large enough to hold the entire input, a valueOutOfRange error occurs. Upon encountering an error, the value of s is undefined.
    Method: (r: Reader) ReadLLine (VAR s: ARRAY OF LONGCHAR)
    Reads a sequence of (LONGCHAR) characters into s; reading continues until an end-of-line character is encountered, the array s is full, or r reaches the end of the channel. The end-of-line character is discarded and s is always terminated with 0X. If r is already positioned at an end-of-line character, s returns as an empty string. If s is not large enough to hold the entire input, a valueOutOfRange error occurs; s returns with the sequence of characters that have been read so far (terminated by 0X). If r has already reached the end of the channel (i.e., there are no more characters left to read), a readAfterEnd error occurs and s returns as an empty string.
    Method: (r: Reader) ReadLString (VAR s: ARRAY OF CHAR)
    Reads in a sequence of (LONGCHAR) characters enclosed in single (') or double (") quote marks. The opening quote must be the same as the closing quote and must not occur within the string. Characters will be read until the terminating quote mark is encountered, an invalid character is read (end-of-line is always considered invalid), there are no more characters available in the channel, or the string s is full. s is always terminated with 0X. Unquoted strings produce an invalidFormat error. Strings with no terminating quote mark also result in an invalidFormat error. If s is not large enough to hold the entire input, a valueOutOfRange error occurs. Upon encountering an error, the value of s is undefined.

    Class Writer (UnicodeRider)

    Class: Writer = POINTER TO WriterDesc
    This is the concrete subclass of LongRider.Writer that provides facilities for writing various kinds of unicode text.

    For UnicodeRider.Writer, note that WriteChar actually writes 2 bytes at a time to the channel (i.e., CHAR values are actually written as Unicode values). ReadLine, ReadIdentifier, and ReadString behave similarly for `LongRider'.

    UnicodeRider.Writer adds the following methods:

    Method: (w: Writer) WriteLChar (ch: LONGCHAR)
    Writes a single (LONGCHAR) character value ch.
    Method: (w: Writer) WriteLString (s: ARRAY OF LONGCHAR)
    Writes a long string value up to, but not including, the terminating 0X character. The behaviour of this method is undefined if s is an unterminated (LONGCHAR) character array. Please note: ReadLString and WriteLString are not symmetric. That is, WriteLString does not enclose the written string in quote marks; only the actual (LONGCHAR) character values contained in s are written.

    Class Scanner (UnicodeRider)

    Class: Scanner = POINTER TO ScannerDesc
    This is the concrete subclass of LongRider.Scanner that provides facilities for scanning sequences of (long) characters from a channel and parsing those characters into various tokens. The tokens a scanner can recognize are defined by the constants provided for its type field (section Summary of UnicodeRider Constants).

    Data type: LongString
    A (long) string type of pre-defined length for use within a scanner. Note that because this type is of finite length, a scanner is limited in the length of string it can scan.

    Please note: LEN() can be used on a variable of type LongString to determine the maximum size that can be held by a scanner string.

    Field: type-: INTEGER
    This is an inherited field, however, it now has the additional possible values: lchar, lident, lline, lstring, ltab.
    Field: lchar-: LONGCHAR
    Contains a value if type is lchar, lline, or ltab.
    Field: lstring-: LongString;
    Contains a value if type is lstring or lident.

    Please note: After a call to Scan, the type field of UnicodeRider.Scanner is never expected to contain any of the following values: char, ident, line, string, tab. But rather, the "long" versions of these type values are set as appropriate.

    Connecting UnicodeRiders to Channels

    The following procedures are provided for creating instances of `UnicodeRider' objects and connecting them to a channel. If the channel being passed as an argument to any of these functions has a value of NIL, behavior is undefined.

    Also, for any of these functions, the returned rider is positioned at the beginning of the channel for positionable channels and at the current position for non-positionable channels.

    Function: ConnectReader (ch: Channel.Channel): Reader
    This function creates a new reader and attaches it to the channel ch. ch.res is set to done on success and the new reader is returned. Otherwise, it returns NIL and ch.res is set to indicate the error cause.

    Function: ConnectWriter (ch: Channel.Channel): Writer
    This function creates a new writer and attaches it to the channel ch. ch.res is set to done on success and the new writer is returned. Otherwise, it returns NIL and ch.res is set to indicate the error cause.

    Function: ConnectScanner (ch: Channel.Channel): Scanner
    This function creates a new scanner and attaches it to the channel ch. ch.res is set to done on success and the new scanner is returned. Otherwise, it returns NIL and ch.res is set to indicate the error cause.

    Summary of UnicodeRider Constants

    Constant: maxLengthEol
    The maximum number of characters allowed in Reader.eol.

    For other constant values that may be applicable when using module `UnicodeRider', see the specific channel implementation that you are reading to or writing from, such as section Module Files, section Module StdChannels, or section Module ProgramArgs.

    The following are possible return values for Res() methods:

    Constant: done
    This indicates successful completion of the last operation.

    Constant: invalidFormat
    Indicates that the text at the current reading (or scanning) position is not properly formatted as the requested type.

    Constant: valueOutOfRange
    Indicates that a number, or potential set element, is in the proper format, but has a value that is out of range of the target type.

    The following are all possible values for a scanner's type field:

    Constant: bool
    The scanner has read a valid boolean value. This can only be set when the scanner's options include interpretBools.

    Constant: char
    The scanner has read a valid character value.

    (For `UnicodeRider', type is never expected to contain this value. But rather, the "long" version is set when appropriate.)

    Constant: lchar
    The scanner has read a valid (long) character value.

    Constant: error
    Indicates that an error has occured while scanning. This could be an error condition resulting from one of the scanner's own operations (for example, an attempt to Scan when the scanner has reached the end of available text), or a result of a lower level error (say, an error occured in the underlying channel).

    Constant: ident
    The scanner has read a valid (Oberon-2) identifier.

    (For `UnicodeRider', type is never expected to contain this value. But rather, the "long" version is set when appropriate.)

    Constant: lident
    The scanner has read a valid (Oberon-2) identifier (as a LongString).

    Constant: int
    The scanner has read a valid integer value.

    Constant: invalid
    The scanner has read an invalid value. Note that when type = invalid, the contents of all of the scanner's output fields are undefined.

    Constant: line
    The scanner has read a valid end-of-line character. This can only be set when the scanner's options include returnCtrlChars.

    (For `UnicodeRider', type is never expected to contain this value. But rather, the "long" version is set when appropriate.)

    Constant: lline
    The scanner has read a valid (long) end-of-line character. This can only be set when the scanner's options include returnCtrlChars.

    Constant: real
    The scanner has read a valid real number value.

    Constant: set
    The scanner has read a valid set constructor value. This can only be set when the scanner's options include interpretSets.

    Constant: string
    The scanner has read a valid (Oberon-2) string value. This can only be set when the scanner's options include interpretStrings.

    (For `UnicodeRider', type is never expected to contain this value. But rather, the "long" version is set when appropriate.)

    Constant: lstring
    The scanner has read a valid (Oberon-2) (long) string value. This can only be set when the scanner's options include interpretStrings.

    Constant: tab
    The scanner has read a valid (long) tab character. This can only be set when the scanner's options include returnCtrlChars.

    (For `UnicodeRider', type is never expected to contain this value. But rather, the "long" version is set when appropriate.)

    Constant: ltab
    The scanner has read a valid tab character. This can only be set when the scanner's options include returnCtrlChars.

    Constant: undefined
    This is the initial value of Scanner.type after ConnectScanner or ClearError (before any calls to Scan).

    The following is a possible writer option (i.e., a valid setting for the writer's opt field):

    Constant: noBuffering
    When this option is set for a writer, output is not buffered. This allows, for example, for interactive output prompts to appear as soon as they are written.

    The following is a possible reader or scanner option (i.e., a valid setting for the opt field):

    Constant: returnCtrlChars
    When this option is set, end-of-line and tab characters are not counted as whitespace.
    Scanners also permit the following additional options:

    Constant: interpretBools
    When this option is set, the text tokens TRUE or FALSE are read as boolean values (i.e., scanner.type = bool). Otherwise, these tokens are read as identifiers (i.e., scanner.type = ident.)

    Constant: interpretSets
    When set, text in the form a set constructor (with "{", "}", ",", and associated integer constants) are read as SET values. Otherwise, these are read as separate tokens.

    Constant: interpretStrings
    When set, quoted character sequences are read as string values. Otherwise, quote characters and string contents are read as separate tokens.

    Constant: useSignedNumbers
    When set, "+" and "-" characters are always considered part of a number. Otherwise, they are read as separate characters.

    Constant: defReaderOptions
    The default reader options setting, which is equivalent to having no options set (i.e., {}).

    Constant: defWriterOptions
    The default writer options setting, which is equivalent to having no options set (i.e., {}).

    Constant: defScannerOptions
    The default scanner options setting, which is equivalent to setting the options interpretBools, interpretSets, interpretStrings, and
    useSignedNumbers.

    Module BinaryRider

    Module BinaryRider provides facilities for reading and writing binary data. Binary data are simple sequences of byte values that may be interpreted in any number of ways. This corresponds closely to the way information is stored within a running program. Values are stored as a fixed number of bytes rather than as a delimited sequence of characters. For example, if SIZE(INTEGER) = 2, then an INTEGER value is always stored as 2 bytes. If SIZE(LONGINT) = 4, then a LONGINT is stored as 4 bytes.

    The following program fragment gives an example of how you could read the entire contents of a file and echo each character to the screen (note that no error checking is done):

    VAR r: BinaryRider.Reader;
        f: Files.File;
        ch: CHAR;
        res: INTEGER;
        
      f := Files.Old("Sample.txt", {Files.read}, res);
      r := BinaryRider.ConnectReader(f); 
    
      r.ReadChar(ch);	
      WHILE r.Res()=Files.done DO
         Out.Char(ch);
         r.ReadChar(ch);	
      END;
    

    Please note: Different kinds of computers use different conventions for the ordering of bytes within a word. Some computers put the most significant byte within a word first (this is called big-endian order), and others put it last (little-endian order). A small number of systems use different byte order schemes; they aren't supported by this module (yet). Operations provided by BinaryRider default to the little-endian byte order. However, byte order can be specified using the SetByteOrder methods provided by classes Reader and Writer.

    Thus, programs can be written that produce files that are portable to machines with different byte orderings. It should be noted, however, that file I/O using the native byte order provides better speed efficiency.

    Class Reader (BinaryRider)

    Class: Reader = POINTER TO ReaderDesc
    This class provides facilities for reading various types of data in binary format. Note that this type does not inherit properties from any basic reader type; rather it uses the basic reader type associated with the channel it is attached to.

    Please note: Many of the methods for BinaryRider.Reader perform typical Reader operations. Rather than duplicate descriptions of those methods here, a reference to the abstract reader type is provided instead.

    Field: byteOrder-: SHORTINT
    The current endian (byte order) setting for the reader.
    Field: base-: Channel.Channel
    This field refers to the channel the reader is connected to.

    The following methods are all fully described in the section on abstract readers (see section Abstract Class Reader), so only brief descriptions are given here.

    Method: (r: Reader) Available () : LONGINT
    Returns the number of bytes available for the next reading operation.
    Method: (r: Reader) ClearError
    Clears error conditions on the reader r, re-enabling further read operations.
    Method: (r: Reader) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations failed.
    Method: (r: Reader) Pos () : LONGINT
    Returns the current reading position associated with the reader r in channel r.base.
    Method: (r: Reader) Res () : INTEGER
    This method returns the status of the last read operation. Note that unlike some other reader types, Res() is a method rather than a field; but otherwise, it performs equivalently. Error codes are highly dependent on the channel being read, and therefore on the basic riders provided by that channel, so you must look at the result codes for a particular channel's reader type. Use method ErrorDescr to get a plain text error description of this error code.
    Method: (r: Reader) SetByteOrder (order: SHORTINT)
    Sets byteOrder in reader r to order. This affects the interpretation of byte values for applicable read operations. Pre-condition: order is one of nativeEndian, littleEndian, or bigEndian. Example:
    VAR rBig, rLittle, r: BinaryRider.Reader;
        f: Files.File;
        
    f := Files.Old("test.dat", {Files.read}, res);
    
    r := BinaryRider.ConnectReader(f);
       => r reads from f using the default byte order 
            (i.e., little endian)
    
    rBig := BinaryRider.ConnectReader(f);
    rBig.SetByteOrder(BinaryRider.bigEndian);
       => rBig reads from f using big endian byte order
    
    rLittle := BinaryRider.ConnectReader(f);
    rLittle.SetByteOrder(BinaryRider.littleEndian);
       => rLittle reads from f using little endian byte order
    
    Method: (r: Reader) SetPos (newPos: LONGINT)
    Sets the reading position to newPos.

    The following methods read a value of the given type from the current position of the Reader. If the value is invalid for its type, Reader.Res() returns invalidFormat.

    Otherwise, if there aren't enough bytes to satisfy the request, Reader.Res() returns readAfterEnd.

    Method: (r: Reader) ReadBool (VAR bool: BOOLEAN)
    Reads in a single byte and interprets it as a BOOLEAN value. Zero values are read as FALSE and non-zero values are read as TRUE. Example:
    VAR bool: BOOLEAN;
    
    r.ReadBool(bool);
       => if byte read = 0, then bool = FALSE; 
            otherwise, bool = TRUE
    
    Method: (r: Reader) ReadBytes (VAR x: ARRAY OF SYSTEM.BYTE; start, n: LONGINT)
    Read n bytes from the channel r.base according to the native machine byte order. That is, ReadBytes is not affected by calls to SetByteOrder. Thus this method is equivalent to any basic rider Reader.ReadBytes method (see section Abstract Class Reader) Example:
    VAR byteArr: ARRAY 256 OF CHAR;
    
    r.ReadBytes(byteArr, 0, 16);
       => reads the next 16 bytes from r.base 
            into byteArr[0..15]  
    
    r.ReadBytes(byteArr, 16, 100);
       => reads the next 100 bytes from r.base 
            into byteArr[16..115]  
    
    Method: (r: Reader) ReadChar (VAR ch: CHAR)
    Reads in a single character value and places it in ch. Please note: OOC assumes that SIZE(SYSTEM.BYTE) = SIZE(CHAR). Example:
    VAR ch: CHAR;
    
    r.ReadChar(ch);
       => reads one byte and assigns it to ch
    
    Method: (r: Reader) ReadLChar (VAR ch: LONGCHAR)
    Reads in a single (long) character value and places it in ch. SIZE(LONGCHAR) bytes are read and interpreted based on the current byte order setting for reader r (see SetByteOrder).
    Method: (r: Reader) ReadInt (VAR int: INTEGER)
    Reads in an INTEGER value. SIZE(INTEGER) bytes are read and interpreted based on the current byte order setting for reader r (see SetByteOrder).
    Method: (r: Reader) ReadLInt (VAR lint: LONGINT)
    Reads in a LONGINT value. SIZE(LONGINT) bytes are read and interpreted based on the current byte order setting for reader r.
    Method: (r: Reader) ReadLReal (VAR lreal: LONGREAL)
    Reads in a LONGREAL value. SIZE(LONGREAL) bytes are read and interpreted based on the current byte order setting for reader r.
    Method: (r: Reader) ReadNum (VAR num: LONGINT)
    Reads an integer value in a compressed and portable format. This format is the same no matter what the byteOrder setting. Therefore, ReadNum is not affected by calls to SetByteOrder.
    Method: (r: Reader) ReadReal (VAR real: REAL)
    Reads in a REAL value. SIZE(REAL) bytes are read and interpreted based on the current byte order setting for reader r.
    Method: (r: Reader) ReadSet (VAR s: SET)
    Reads in a SET value. SIZE(SET) bytes are read and interpreted based on the current byte order setting for reader r.
    Method: (r: Reader) ReadSInt (VAR sint: SHORTINT)
    Reads in a SHORTINT value. Please note: OOC assumes that SIZE(SYSTEM.BYTE) = SIZE(SHORTINT) so that the current byte order setting for reader r (see SetByteOrder) does not matter for calls to ReadSInt.
    Method: (r: Reader) ReadString (VAR s: ARRAY OF CHAR)
    Reads in a sequence of characters until either the string terminator 0X is encountered, there are no more characters available in the channel, or the string s is full. s is always terminated with 0X. Example:
    VAR str: ARRAY 256 OF CHAR;
    
    r.ReadString(str);
       => reads up to 256 characters, stops when encounters 0X
    
    Method: (r: Reader) ReadLString (VAR s: ARRAY OF LONGCHAR)
    Reads in a sequence of (long) characters until either the string terminator 0X is encountered, there are no more characters available in the channel, or the string s is full. s is always terminated with 0X. For each character, SIZE(LONGCHAR) bytes are read and interpreted based on the current byte order setting for reader r (see SetByteOrder).

    Class Writer (BinaryRider)

    Class: Writer = POINTER TO WriterDesc
    This class provides facilities for writing various types of data in binary format. Note that this type does not inherit properties from any basic writer type; rather it uses the basic writer type associated with the channel it is attached to.

    Please note: Many of the methods for BinaryRider.Writer perform typical Writer operations. Rather than duplicate descriptions of those methods here, a reference to the abstract writer type is provided instead.

    Field: base-: Channel.Channel
    This field refers to the channel the writer is connected to.
    Field: byteOrder-: SHORTINT
    The current endian (byte order) setting for the writer.

    The following methods are all fully described in the section on abstract writers (see section Abstract Class Writer), so only brief descriptions are given here.

    Method: (w: Writer) ClearError
    Clears error conditions on the writer w, re-enabling further write operations.
    Method: (w: Writer) ErrorDescr (VAR descr: ARRAY OF CHAR)
    Retrieves a descriptive error message string stating the reason why one of the previous operations failed.
    Method: (w: Writer) Pos () : LONGINT
    Returns the current writing position associated with the writer w in channel w.base.
    Method: (w: Writer) Res () : INTEGER
    This method returns the status of the last write operation. Note that unlike some other writer types, Res() is a method rather than a field; but otherwise, it performs equivalently. Error codes are highly dependent on the channel being written to (and therefore on the basic riders provided for that channel), so you must look at the result codes for the basic writer that is associated with that particular channel. Use ErrorDescr to get a plain text error description of this error code.
    Method: (w: Writer) SetPos (newPos: LONGINT)
    Sets the writing position to newPos.

    The following writer methods are used to write values to the underlying channel. In some situations, it is possible for only part of the value to be written.

    Method: (w: Writer) WriteBytes (VAR x: ARRAY OF SYSTEM.BYTE; start, n: LONGINT)
    Write n bytes to the channel w.base according to the native machine byte order (i.e., WriteBytes is not affected by calls to SetByteOrder). Thus this method is equivalent to any basic rider Writer.WriteBytes method (see section Abstract Class Writer) Example:
    VAR byteArr: ARRAY 256 OF CHAR;
    
    w.WriteBytes(byteArr, 0, 16);
       => writes the values of byteArr[0..15] 
            to the current writing position of w
    
    w.WriteBytes(byteArr, 16, 100);
       => writes the values of byteArr[16..115] 
            to the current writing position of w
    
    Method: (w: Writer) WriteBool (bool: BOOLEAN)
    Writes a BOOLEAN value as a single byte. FALSE is written as 0 and TRUE is written as 1. Example:
    w.WriteBool(TRUE);
       => writes one byte = 01H
    
    w.WriteBool(FALSE);
       => writes one byte = 00H
    
    Method: (w: Writer) WriteChar (ch: CHAR)
    Writes the character value ch as a single byte. Please note: OOC assumes that SIZE(SYSTEM.BYTE) = SIZE(CHAR). Example:
    VAR ch: CHAR:
    
    w.WriteChar("A");
       => writes one byte = "A"
    
    ch := 41X;
    w.WriteChar(ch);
       => writes one byte = 41X (i.e., "A" in ASCII)
    
    Method: (w: Writer) WriteLChar (ch: LONGCHAR)
    Writes the (long) character value ch as SIZE(LONGCHAR) bytes based on the current byte order setting for writer w (see SetByteOrder).
    Method: (w: Writer) WriteString (s: ARRAY OF CHAR)
    Writes the string value of s (recall that a string is a character array containing 0X as an embedded terminator). The terminating 0X is also written. Example:
    VAR str: ARRAY 256 OF CHAR;
    
    w.WriteString("abcdefg");
       => writes a total of 8 characters including 0X
    
    str := "hijkl";
    w.WriteString(str);
       => writes a total of 6 characters including 0X
    
    Method: (w: Writer) WriteLString (s: ARRAY OF LONGCHAR)
    Writes the string value of s including the terminating 0X character. Each character is written as SIZE(LONGCHAR) bytes based on the current byte order setting for writer w (see SetByteOrder).
    Method: (w: Writer) WriteSInt (sint: SHORTINT)
    Writes a SHORTINT value. Please note: OOC assumes that SIZE(SYSTEM.BYTE) = SIZE(SHORTINT) so that the current byte order setting for writer w (see SetByteOrder) does not matter for calls to WriteSInt.
    Method: (w: Writer) WriteInt (int: INTEGER)
    Writes an INTEGER value. SIZE(INTEGER) bytes are written based on the current byte order setting for writer w (see SetByteOrder).
    Method: (w: Writer) WriteLInt (lint: LONGINT)
    Writes a LONGINT value. SIZE(LONGINT) bytes are written based on the current byte order setting for writer w.
    Method: (w: Writer) WriteNum (lint: LONGINT)
    Write an integer value in a compressed and portable format. This format is the same no matter what the byteOrder setting. Therefore, WriteNum is not affected by calls to SetByteOrder.
    Method: (w: Writer) WriteReal (real: REAL)
    Writes a REAL value. SIZE(REAL) bytes are written based on the current byte order setting for writer w.
    Method: (VAR w: Writer) WriteLReal (VAR lreal: LONGREAL)
    Writes a LONGREAL value. SIZE(LONGREAL) bytes are written based on the current byte order setting for writer w.
    Method: (VAR w: Writer) WriteSet (VAR s: SET)
    Writes a SET value. SIZE(SET) bytes are written based on the current byte order setting for writer w.
    Method: (VAR w: Writer) SetByteOrder (VAR order: SHORTINT)
    Sets byteOrder in writer w to order. This affects the interpretation of byte values for applicable write operations. Pre-condition: order is one of nativeEndian, littleEndian, or bigEndian. Example:
    VAR wBig, wLittle, w: BinaryRider.Writer;
        f: Files.File;
        
    f := Files.Old("test.dat", {Files.write}, res);
    
    w := BinaryRider.ConnectWriter(f);
       => w writes to f using native byte order
    
    wBig := BinaryRider.ConnectWriter(f);
    wBig.SetByteOrder(BinaryRider.bigEndian);
       => wBig writes to f using big endian byte order
    
    wLittle := BinaryRider.ConnectWriter(f);
    wLittle.SetByteOrder(BinaryRider.littleEndian);
       => wLittle writes to f using little endian byte order
    

    Connecting BinaryRiders to Channels

    Functions are provided by module BinaryRider to connect readers and writers to open channels. If the channel being passed as an argument to either of these functions has a value of NIL, behavior is undefined.

    Also, for either of these functions, the returned rider is positioned at the beginning of the channel for positionable channels and at the current position for non-positionable channels.

    Function: ConnectReader (VAR ch: Channel.Channel): Reader
    This function creates a new reader and attaches it to the channel ch. ch.res is set to done on success and the new reader is returned. Otherwise, it returns NIL and ch.res is set to indicate the error cause.

    Function: ConnectWriter (VAR ch: Channel.Channel): Writer
    This function creates a new writer and attaches it to the channel ch. ch.res is set to done on success and the new writer is returned. Otherwise, it returns NIL and ch.res is set to indicate the error cause.

    Example:

    VAR
      f: Files.File;
      r: BinaryRider.Reader;
      res: INTEGER;
      
      f := Files.Old("test.dat", {Files.read, Files.write}, res);
      IF (res # Files.done) THEN (* error processing *) END;
      
      r := BinaryRider.ConnectReader(f);
      IF (r = NIL) THEN (* error processing *) END;
    

    Summary of BinaryRider Constants

    For other constant values that may be applicable when using module BinaryRider, see the specific channel implementation that you are reading to or writing from.

    The following are possible return values for Res() methods:

    Constant: done
    This indicates successful completion of the last operation.

    Constant: invalidFormat
    Indicates that the data at the current reading position is not properly formatted as the requested type.

    Constant: readAfterEnd
    A read operation has tried to access a byte beyond the end of the channel. This means that there weren't enough bytes available or the read operation started at (or after) the end.

    The following are possible endian (byte order) settings:

    Constant: nativeEndian
    Use the host machine's byte order.

    Constant: littleEndian
    Read/write least significant byte first.

    Constant: bigEndian
    Read/write most significant byte first.

    Standard I/O

    Modules In, Out, and Err provide simple interfaces to the standard channels (see section Module StdChannels) These modules can be used to read from predefined input (typically the keyboard) and write to predefined output (typically the computer screen) locations.

    Historically, the various Oberon systems/ compilers have furnished modules called In and Out, which were intended primarily as aids for learning the Oberon(-2) programming language. These modules were often over-simplified to such a degree that they were of limited use beyond the initial learning stage. The intention was that, after learning the language, a programmer would learn other, more sophisticated methods for I/O.

    Although the modules In, Out, and Err in the OOC library are simple enough to be used by novices, they are not nearly as limited as the corresponding modules from the original Oberon system. Hence, they are still useful to programmers well beyond the beginning stages.

    These modules give simplified facilities similar to module TextRider applied to the standard channels; they allow reading and writing of data as text. If these prove to be insufficient for your needs, then modules TextRider or BinaryRider may be used instead (see section Standard Mappers)

    Module In

    Module In provides a set of basic read operations for text. It is initially set to read from the standard input channel StdChannels.stdin (see section Module StdChannels), but this may be changed with the SetReader procedure.

    Each of the procedures in this module is designed to interpret a specific type of text token. That is, Char will read in a single CHAR value, Int will read in an INTEGER value, and so forth. For exact syntax of each of these tokens see section Syntax of Text Tokens.

    The following program fragment gives an example of how you could read input a single line at a time (input stops after reading a blank line):

    VAR str: ARRAY 256 OF CHAR;
        
      In.Line(str);	
      WHILE In.Done() & (str # "") DO
         (* process each line *)
         In.Line(str);	
      END;
    

    Read-only Variable: reader
    The reader used for all read operations in module In. The type of reader is TextRider.Reader, and it is initialized to refer to a text reader connected to the channel StdChannels.stdin.

    The SetReader procedure may be used to change this to refer to another TextRider.Reader.

    Function: Done (): BOOLEAN
    This function returns FALSE after an unsuccessful read operation. This may be caused by attempting to read improperly formatted text (e.g., attempting to read non-numeric text using Int), or if the underlying reader has encountered an error. Further reading is not possible until the error is cleared using the ClearError procedure.

    Procedure: ClearError
    Clears error conditions, re-enabling further read operations.

    Procedure: SetReader (r: TextRider.Reader)
    This procedure is used to change the reader used by all read operations in module In. Refer to section Module TextRider for details on how to open other readers. If r=NIL, the reader is set to read from StdChannels.stdin.

    All of the following read operations require that Done() => TRUE; that is, they will not read anything else after an unsuccessful read operation has occured. Further reading cannot take place until the error is cleared using ClearError.

    Most of these read operations skip leading whitespace (i.e., spaces, tabs, end-of-line characters, etc.) before reading a token; the only procedures that do not skip whitespace are Char and Line.

    A read error will occur, not only for improperly formatted text, but for numbers (i.e., reading using Int, Real, and so forth) and set elements that have values out of range of the target type. For example, attempting to read `999999999999999999' using Int will give Done() => FALSE.

    An error will also occur for procedures that read into an ARRAY OF CHAR, when the array is not large enough to hold the entire input.

    Procedure: Bool (VAR bool: BOOLEAN)
    Reads in the text `TRUE' or `FALSE'; any other text results in an error. When an error occurs, the value of bool is undefined.

    Procedure: Char (VAR ch: CHAR)
    Reads in a single character.

    Procedure: Hex (VAR lint: LONGINT)
    Reads in text in the form of an unsigned hexadecimal number. The first character must be a decimal digit (i.e., `0..9') and subsequent characters must be valid hexadecimal digits (i.e., `0..9' or `A..F'). The value read must be in the valid range for a LONGINT.

    Upon encountering an error, the value of lint is undefined.

    Please note: Because LONGINT values are signed, hex numbers in the range `80000000H..FFFFFFFFH' are interpreted as negative LONGINT values.

    Procedure: Identifier (VAR s: ARRAY OF CHAR)
    Reads an Oberon-2 style identifier. The first character must be a letter, which is followed by any sequence of letters and digits. An error will occur if s is not large enough to hold the entire input.

    Upon encountering an error, the value of s is undefined. Example:

    (* Input is as follows:  
    myIdentifier 3isBad 
    *)
    
    VAR str: ARRAY 256 OF CHAR;
    
    In.Identifier(str)
       => Done() = TRUE, str = "myIdentifier"
    In.Identifier(str)
       => Done() = FALSE, str = undefined
    

    Procedure: Int (VAR int: INTEGER)
    Reads in text in the form of a signed whole number. The first character must be a digit, a "+" sign, or a "-" sign. The value read must be in the valid range for an INTEGER.

    Upon encountering an error, the value of int is undefined.

    Example:

    (* Input is as follows:
    12345
    999999999999999
    forty-two
    *)
    
    VAR intVar: INTEGER;
    
    In.Int(intVar);
       => Done() = TRUE, intVar = 12345
    In.Int(intVar);
       => Done() = FALSE, intVar = undefined
    In.ClearError;
    In.Int(intVar); (* attempting to read `forty-two' *)
       => Done() = FALSE, intVar = undefined
            (* reading position is still at the `f' in
               `forty-two' *)
    

    Procedure: LongInt (VAR lint: LONGINT)
    This procedure provides the same facility as Int, except that it deals with LONGINT values.

    Procedure: ShortInt (VAR int: SHORTINT)
    This procedure provides the same facility as Int, except that it deals with SHORTINT values.

    Procedure: Line (VAR s: ARRAY OF CHAR)
    Reads text until an end-of-line character is encountered. The end-of-line character is discarded and s is always terminated with 0X. An error will occur if s is not large enough to hold the entire input.

    Upon encountering an error, the value of s is undefined.

    Please note: This procedure returns an empty string if already at at the end-of-line.

    Procedure: String (VAR s: ARRAY OF CHAR)
    Reads in any text enclosed in single (') or double (") quote marks. The opening quote must be the same as the closing quote and must not occur within the string. Reading will continue until the terminating quote mark is encountered, an invalid character is read (end-of-line is always considered invalid), or there are no more characters available to be read. s is always terminated with 0X.

    Unquoted strings or strings with no terminating quote mark result in an error. An error will also occur if s is not large enough to hold the entire input.

    Upon encountering an error, the value of s is undefined.

    Example:

    (* Input is as follows:
    "A well-formed string"
    "No end quote
    *)
    
    VAR str: ARRAY 256 OF CHAR;
    
    In.String(str);
       => Done() = TRUE, str = "A well-formed string"
    In.String(str);
       => Done() = FALSE, str = undefined
            (* reading position is now at the end of this line *)
    

    Procedure: Real (VAR real: REAL)
    Reads in text in the form of a signed fixed or floating-point number. The first character must be a digit, a "+" sign, or a "-" sign. The value read must be in the valid range for a REAL.

    Upon encountering an error, the value of real is undefined.

    Example:

    (* Input is as follows:
    3.1415
    +54321E+30
    2.34E+56
    *)
    
    VAR realVar: REAL;
    
    In.Real(realVar);
       => Done() = TRUE, realVar = 3.141500
    In.Real(realVar);
       => Done() = TRUE, realVar = 5.432100E+34
    In.Real(realVar);
       => Done() = FALSE, realVar = undefined
            (* value is out of range for REAL *)
    

    Procedure: LongReal (VAR lreal: LONGREAL)
    This procedure provides the same facility as Real, except that it deals with LONGREAL values.

    Procedure: Set (VAR s: SET)
    Reads in text in the form of a set constructor. The values of set elements must be in the range `0..MAX(SET)'.

    Upon encountering an error, the value of s is undefined.

    Example:

    (* Input is as follows:
    {0, 1, 2, 3, 4, 5}
    {6, 7, 1024}
    *)
    
    VAR setVar: SET;
    
    In.Set(setVar);
       => Done() = TRUE, setVar = {0..5}
    In.Set(setVar);
       => Done() = FALSE, setVar = undefined
            (* reading position is now at the `}' after 
               the `1024' *)
    

    Module Out

    Module Out provides a set of basic write operations for text. It is initially set to write to the standard output channel StdChannels.stdout (see section Module StdChannels), but this may be changed with the SetWriter procedure.

    Read-only Variable: writer
    The writer used for all write operations in module Out. The type of writer is TextRider.Writer, and it is initialized to refer to a text reader connected to the channel StdChannels.stdout.

    The SetWriter procedure may be used to change this to refer to another TextRider.Writer.

    Function: Done (): BOOLEAN
    This function returns FALSE after an unsuccessful write operation. This may happen when underlying writer has encountered an error. Further writing is not possible until the error is cleared using the ClearError procedure.

    Procedure: ClearError
    Clears error conditions, re-enabling further read operations.

    Procedure: SetWriter (w: TextRider.Writer)
    This procedure is used to change the writer used by all write operations in module Out. Refer to section Module TextRider for details on how to open other writers. If w=NIL, the writer is set to write to StdChannels.stdout.

    Procedure: Flush
    Flushes all buffers associated with Out.writer. Any pending write operations are passed to the underlying system. If a writing error occurs while flushing buffers, Out.Done() will subsequently return FALSE. Otherwise, Out.Done() will return TRUE.

    Procedure: Bool (bool: BOOLEAN)
    Writes the value of bool as text. That is, either `TRUE' or `FALSE'.
    Procedure: Char (ch: CHAR)
    Writes a single character value ch.

    Example:

    Out.Char("A");
       => writes one character = "A"
    

    Procedure: Hex (lint: LONGINT; n: LONGINT)
    Writes the value of lint as an unsigned hexadecimal number with a minimum field width of n. Leading zeros are written if the value of lint requires less than n places. If n is less than or equal to zero, field width is 8.

    Example:

    Out.Hex(127, 4);
       => writes "007F"  
    Out.Hex(-128, 0);
       => writes "FFFFFF80"
    

    Procedure: Int (int: INTEGER; n: LONGINT)
    Writes the value of int as a decimal number with a minimum field width of n. Leading spaces are written if the value of int requires less than n places. A sign is written only for negative values.

    Example:

    Out.Int(54321, 0);
       => writes "54321"
    Out.Int(54321, 10);
       => writes "     54321"
    

    Procedure: LongInt (lint: LONGINT; n: LONGINT)
    This procedure provides the same facility as Int, except that it deals with LONGINT values.

    Procedure: ShortInt (sint: SHORTINT; n: LONGINT)
    This procedure provides the same facility as Int, except that it deals with SHORTINT values.

    Procedure: Real (real: REAL; n, k: LONGINT)
    Writes the value of real as a floating-point number with a minimum field width of n.

    If the value of k is greater than 0, that number of significant digits is included. Otherwise, an implementation-defined number of significant digits is included. The decimal point is not included if there are no significant digits in the fractional part.

    The number is scaled with one digit in the whole number part. A sign is included only for negative values.

    Example:

    Out.Real(3923009, 0, 0);
       => writes "3.923009E+6"
    Out.Real(3923009, 10, 1);
       => writes "      4E+6"
    
    Out.Real(-39.23009, 12, 2);
       => writes "     -3.9E+1"
    
    Out.Real(0.0003923009, 6, 1);
       => writes "  4E-4"
    

    Procedure: LongReal (lreal: LONGREAL; n, k: LONGINT)
    This procedure provides the same facility as Real, except that it deals with LONGREAL values.

    Procedure: RealEng (real: REAL; n, k: LONGINT)
    This procedure provides the same facility as Real, except that the number is scaled with one to three digits in the whole number part and has an exponent that is a multiple of three.

    Example:

    Out.RealEng(39.23009, 10, 5);
       => writes "    39.230"
    
    Out.RealEng(-3923009, 7, 3);
       => writes " -3.92E+6"
    
    Out.RealEng(0.0003923009, 1, 1);
       => writes "400E-6"
    Out.RealEng(0.0003923009, 4, 2);
       => writes "  390E-6"
    

    Procedure: LongRealEng (lreal: LONGREAL; n, k: LONGINT)
    This procedure provides the same facility as RealEng, except that it deals with LONGREAL values.

    Procedure: RealFix (real: REAL; n, k: LONGINT)
    Writes the value of real as a fixed-point number with a minimum field width of n.

    The value is rounded to the given value of k relative to the decimal point. The decimal point is suppressed if k is less than 0.

    The number will have at least one digit in the whole number part. A sign is included only for negative values.

    Example:

    Out.RealFix(3923009, 0, -5);
       => writes "3920000"  (* rounded to the 
                            ten-thousands place *)
    
    Out.RealFix(3923.5, 0, -1);
       => writes "3924" (* rounded to the "ones" place *)
    
    Out.RealFix(-39.23009, 10, 1);
       => writes "     -39.2"
    
    Out.RealFix(0.0003923009, 11, 4);
       => writes "     0.0004"
    

    Procedure: LongRealFix (lreal: LONGREAL; n, k: LONGINT)
    This procedure provides the same facility as RealFix, except that it deals with LONGREAL values.

    Procedure: Set (s: SET)
    Writes the value of s as an Oberon-2 set constructor, including curly braces, commas, and range indicators (`..') where appropriate.

    Example:

    Out.Set({1,6,10});
       => writes "{1, 6, 10}"
    Out.Set({0, 1, 2, 3, 4, 5});
       => writes "{0..5}"
    Out.Set({0, 2, 4, 6} + {1, 3, 5, 7});
       => writes "{0..7}"
    

    Procedure: String (s: ARRAY OF CHAR)
    Writes a string value up to, but not including, the terminating 0X character. The behaviour of this procedure is undefined if s is an unterminated character array.

    Please note: In.String and Out.String are not symmetric. That is,
    Out.String does not enclose the written string in quote marks; only the actual character values contained in s are written.

    Procedure: Ln
    Writes an end-of-line marker (i.e., a "newline").

    Module Err

    Module Err provides a set of basic write operations for text, which exactly mirror those in module Out. The difference is that Err is initially set to write to the standard error channel StdChannels.stderr (see section Module StdChannels). Also note that the call Err.SetWriter(NIL) will reset the writer for Err to StdChannels.stderr.

    Because the interfaces of Out and Err are identical, decriptions of facilities are not duplicated here.


    Go to the first, previous, next, last section, table of contents. OOCref_8.html100664 1750 1750 151107 6753666001 11217 0ustar sagsag The OOC Reference Manual - Mathematics

    Go to the first, previous, next, last section, table of contents.


    Mathematics

    The mathematics modules described in this chapter serve several purposes. They provide access to the underlying representation of REAL and LONGREAL values, as well as facilities for common mathematical functions and constants.

    The REAL and LONGREAL types, collectively referred to as the real numeric types, are used to represent floating-point numbers, which may be stored in various ways on a computer. The actual values are approximations of real numbers and may not be wholely accurate. Hence, precise details of the floating-point representation are often required when creating operations that involve real numeric types in order to minimize errors and calculate error bounds.

    A full discourse on floating-point numbers, as well as more complete descriptions of algorithms used for manipulating floating-point data, is beyond the scope of this manual. For further information, consult the following references:

    IEEE Standard for Binary Floating-Point Arithmetic
    (ANSI/IEEE STD 754-1985) (R1990) 
    Institute of Electrical and Electronics Engineers, Inc. (IEEE)
    
    IEEE Standard for Radix-Independent Floating-Point Arithmetic
    (ANSI/IEEE STD 854-1987) (R1994)
    Institute of Electrical and Electronics Engineers, Inc. (IEEE)
    
    Information technology -- Language independent arithmetic -- 
    Part 1: Integer and floating point arithmetic
    (ISO/IEC 10967-1:1994(E))
    International Organization for Standardization (ISO)
    
    What Every Computer Scientist Should Know About Floating-Point Arithmetic
    David Goldberg
    ACM Computing Surveys, Vol. 23, No. 1, March 1991, pp. 5-48
    
    Software Manual for the Elementary Functions
    William James Cody
    Prentice Hall, July 1980
    
    Computer Approximations
    John F. Hart
    Krieger Publishing Company, June 1978
    

    Low-level Numeric Properties

    The modules LowReal and LowLReal give access to the underlying properties of the types REAL and LONGREAL.

    Default properties of the real numeric types are defined by the constants in these modules. (An implementation may provide facilities for dynamically changing properties from these defaults.)

    Please note:

    Constant: radix
    The whole number value of the radix (base number system) used to represent the corresponding real number values. (Most modern computers use IEEE 754, which defines the radix to be 2.)

    Constant: places
    A whole number value representing of the number of radix places used to store values of the corresponding real numeric type.

    Constant: expoMax
    A whole number value representing the largest possible exponent of the corresponding real numeric type.

    Constant: expoMin
    A whole number value representing the smallest possible exponent of the corresponding real numeric type.

    Please note: It is possible that expoMin = expoMax, which is likely for the case of fixed point representation.

    Constant: large
    The largest possible value of the corresponding real numeric type.

    Please note: On some systems, large may be a machine representation of infinity.

    Constant: small
    The smallest possible positive value of the corresponding real numeric type, represented to maximal precision.

    Please note: If an implementation has stored values strictly between `0.0' and small, then presumbly the implementation supports gradual underflow.

    Constant: IEC559
    A boolean value that is TRUE if, and only if, the implementation of the corresponding real numeric type conforms to IEC 559:1989 (IEEE 754:1987) in all regards.

    Please note:

    Constant: LIA1
    A boolean value that is TRUE if, and only if, the implementation of the corresponding real numeric type conforms to ISO/IEC 10967-1:199x (LIA-1) in all regards: parameters, arithmetic, exceptions, and notification.

    Constant: rounds
    A boolean value that is TRUE if, and only if, each operation produces a result that is one of the values of the corresponding real numeric type nearest to the mathematical result.

    Please note: If rounds is TRUE, and the mathematical result lies mid-way between two values of the corresponding real numeric type, then the selection from the two possible values is implementation-dependent.

    Constant: gUnderflow
    A boolean value that is TRUE if, and only if, there are values of the corresponding real numeric type between `0.0' and small.

    Constant: exception
    A boolean value that is TRUE if, and only if, every operation that attempts to produce a real value out of range raises an exception.

    Constant: extend
    A boolean value that is TRUE if, and only if, expressions of the corresponding real numeric type are computed to higher precision than the stored values.

    Please note: If extend is TRUE, then values greater than large can be computed in expressions, but cannot be stored in variables.

    Constant: nModes
    A whole number value giving the number of bit positions needed for the status flags for mode control.

    Data type: Modes = SET
    This type is used to represent the status flags that apply to the underlying implementation of the corresponding real numeric type. This type is used for the setMode and currentMode() procedures.

    The following functions are provided in either LowReal (for REAL) or LowLReal (for LONGREAL):

    Function: exponent (x: REAL): INTEGER
    Function: exponent (x: LONGREAL): INTEGER
    This function returns the exponent value of x, which must lie between expoMin and expoMax. If x=0.0, an exception occurs and may be raised.

    Function: fraction (x: REAL): REAL
    Function: fraction (x: LONGREAL): LONGREAL
    This function returns the significand (or significant) part of x. Hence, the following relationship holds:

    x = scale(fraction(x), exponent(x))
    

    Function: IsInfinity (real: REAL): BOOLEAN
    Function: IsInfinity (real: LONGREAL): BOOLEAN
    This function returns TRUE if, and only if, real is a representation of Infinity (either positive or negative).

    Function: IsNaN (real: REAL): BOOLEAN
    Function: IsNaN (real: LONGREAL): BOOLEAN
    This function returns TRUE if, and only if, real is a NaN ("Not a Number") representation.

    Please note: The routines IsInfinity and IsNaN allow, for example, for string formatting routines to have a reasonably portable way to check whether they are dealing with out of range or illegal numbers.

    Function: sign (x: REAL): REAL
    Function: sign (x: LONGREAL): LONGREAL
    This function returns the sign of x as follows:

      If x > 0.0, return 1.0
      If x = 0.0, return either 1.0 or -1.0
      If x < 0.0, return -1.0
    

    Please note: The uncertainty about the handling of 0.0 is to allow for systems that distinguish between +0.0 and -0.0 (such as IEEE 754 systems).

    Function: succ (x: REAL): REAL
    Function: succ (x: LONGREAL): LONGREAL
    This function returns the next value of the corresponding real numeric type greater than x, if such a value exists; otherwise, an exception occurs and may be raised.

    Function: ulp (x: REAL): REAL
    Function: ulp (x: LONGREAL): LONGREAL
    This function returns the value of the corresponding real numeric type equal to a unit in the last place of x, if such a value exists; otherwise, an exception occurs and may be raised.

    Please note: When this value exists, one, or both, of the following is true: ulp(x) = succ(x)-x or ulp(x) = x-pred(x).

    Function: pred (x: REAL): REAL
    Function: pred (x: LONGREAL): LONGREAL
    This function returns the next value of the corresponding real numeric type less than x, if such a value exists; otherwise, an exception occurs and may be raised.

    Function: intpart (x: REAL): REAL
    Function: intpart (x: LONGREAL): LONGREAL
    This function returns the integral part of x. For negative values, this is -intpart(abs(x)).

    Function: fractpart (x: REAL): REAL
    Function: fractpart (x: LONGREAL): LONGREAL
    This function returns the fractional part of x. This satisfies the relationship fractpart(x) + intpart(x) = x.
    Function: scale (x: REAL; n: INTEGER): REAL
    Function: scale (x: LONGREAL; n: INTEGER): LONGREAL
    This function returns x*radix^n, if such a value exists; otherwise, an exception occurs and may be raised.

    Function: trunc (x: REAL; n: INTEGER): REAL
    Function: trunc (x: LONGREAL; n: INTEGER): LONGREAL
    This function returns the value of the most significant n places of x. If n is less than or equal to zero, an exception occurs and may be raised.

    Function: round (x: REAL; n: INTEGER): REAL
    Function: round (x: LONGREAL; n: INTEGER): LONGREAL
    This function returns the value of x rounded to the most significant n places. If such a value does not exist, or if n is less than or equal to zero, an exception occurs and may be raised.

    Function: synthesize (expart: INTEGER; frapart: REAL): REAL
    Function: synthesize (expart: INTEGER; frapart: LONGREAL): LONGREAL
    This function returns a value of the corresponding real numeric type contructed from the value of expart and frapart. This value satisfies the relationship

    synthesize(exponent(x), fraction(x)) = x.
    

    Procedure: setMode (m: Modes)
    This procedure sets status flags from the value of m, appropriate to the underlying implementation of the corresponding real numeric type.

    Please note:

    Function: currentMode (): Modes
    This function returns the current status flags (in the form set by setMode), or the default status flags (if setMode is not used).

    Please note: The returned value is not necessarily the value set by setMode, because a call of setMode might attempt to set flags that cannot be set by the program.

    Function: IsLowException (): BOOLEAN
    This function returns TRUE if the current process is in the exceptional execution state because of the raising of the corresponding LowReal or LowLReal exception; otherwise, it returns FALSE.

    Mathematical Functions

    The modules RealMath and LRealMath provide facilities for common mathematical functions and constants for REAL and LONGREAL numeric types.

    Please note: The angle in all trigonometric functions is measured in radians.

    The following useful mathematical constants are provided:

    Constant: pi
    An implementation-defined approximation to the mathematical constant pi.

    Constant: exp1
    An implementation-defined approximation to the mathematical constant e.

    Please note: Due to the approximations involved, sin(pi) might not exactly equal zero. Similarly, exp1 might not exactly equal exp(1).

    The following are mathematical functions provided in either RealMath (for REAL) or LRealMath (for LONGREAL):

    Function: sqrt (x: REAL): REAL
    Function: sqrt (x: LONGREAL): LONGREAL
    This function returns an approximation to the positive square root of x. If x is negative, an exception is raised.

    Function: exp (x: REAL): REAL
    Function: exp (x: LONGREAL): LONGREAL
    This function returns an approximation to the mathematical constant e raised to the power of x.

    Function: ln (x: REAL): REAL
    Function: ln (x: LONGREAL): LONGREAL
    This function returns an approximation to the natural logarithm of x. If x is zero or negative, an exception is raised.

    Function: sin (x: REAL): REAL
    Function: sin (x: LONGREAL): LONGREAL
    This function returns an approximation to the sine of x for all values of x.
    Function: cos (x: REAL): REAL
    Function: cos (x: LONGREAL): LONGREAL
    This function returns an approximation to the cosine of x for all values of x.
    Function: tan (x: REAL): REAL
    Function: tan (x: LONGREAL): LONGREAL
    This function returns an approximation to the tangent of x. If x is an odd multiple of pi/2, an exception is raised.

    Function: arcsin (x: REAL): REAL
    Function: arcsin (x: LONGREAL): LONGREAL
    This function returns an approximation to the arcsine of x. The result will be in the range [-pi/2, pi/2]. If the absolute value of x is greater than one, an exception is raised.
    Function: arccos (x: REAL): REAL
    Function: arccos (x: LONGREAL): LONGREAL
    This function returns an approximation to the arccosine of x. The result will be in the range [0, pi]. If the absolute value of x is greater than one, an exception is raised.

    Function: arctan (x: REAL): REAL
    Function: arctan (x: LONGREAL): LONGREAL
    This function returns an approximation to the arctangent of x for all values of x. The result will be in the range [-pi/2, pi/2].
    Function: power (base, exponent: REAL): REAL
    Function: power (base, exponent: LONGREAL): LONGREAL
    This function returns an approximation to the value of base raised to the power exponent. If base is zero or negative, an exception is raised.

    Please note: This function is mathematically equivalent to
    exp(exponent * ln(base)), but may be computed differently.

    Function: round (x: REAL): LONGINT
    Function: round (x: LONGREAL): LONGINT
    This function returns the nearest integer to the value of x. If the mathematical result is not within the range of the type LONGINT, an exception occurs and may be raised.

    Please note: If the value of x is midway between two integer values, the result is an implementation-defined selection of one of the two possible values.

    Function: IsRMathException (): BOOLEAN
    This function returns TRUE if the current process is in the exceptional execution state because of the raising of the corresponding RealMath or LRealMath exception; otherwise, it returns FALSE.

    Arbitrary Precision Integers

    Very often, a program requires numbers with a greater range or accuracy than exists with the built-in Oberon-2 integer types. Hence, the module Integers provides facilities for arbitrary precision integer operations.

    For further information on how these kinds of facilites may be implemented, consult the following reference:

    The Art Of Computer Programming:
    Volume 2, Seminumerical Algorithms, Second Edition
    Donald E. Knuth
    Addison-Wesley Publishing Co., January 1981
    

    Data type: Integer = POINTER TO IntegerDesc
    Instances of this type are used to represent arbitrary precision integers.

    The following operations are used to create initial instances of Integer and convert Integers to standard numeric types.

    Function: Entier (x: LONGREAL): Integer
    This function returns an instance of Integer whose value is the largest integer not greater than x.

    Example:

    VAR n: Integers.Integer;
    
    n:=Integers.Entier(1.0D20); 
       => n = 100000000000000000000
    
    n:=Integers.Entier(1111111111.5D0); 
       => n = 1111111111
    
    n:=Integers.Entier(0.0); 
       => n = 0
    

    Function: Float (x: Integer): LONGREAL
    This function returns an approximation to the value of x converted to a LONGREAL. If the result cannot be represented as a LONGREAL because the value of x is either too large or too small, this function returns either MIN(LONGREAL) or MAX(LONGREAL).
    Function: Long (x: LONGINT): Integer
    This function returns an instance of Integer whose value is x.
    Function: Short (x: Integer): LONGINT
    This function returns the value of x converted to a LONGINT. If the result cannot be represented as a LONGINT because the value of x is either too large or too small, this function returns either MIN(LONGINT) or MAX(LONGINT).

    Example:

    VAR n: Integers.Integer;
        s: LONGINT;
        f: LONGREAL; 
    
    n:=Integers.Long(1234);
    s:=Integers.Short(n); 
       => s = 1234
    f:=Integers.Float(n);
       => f = 1.23400000000000E+3
    
    n:=Integers.Long(80000000H); 
    s:=Integers.Short(n); 
       => s = -2147483648
    f:=Integers.Float(n);
       => f = -2.14748364800000E+9
    
    n:=Integers.Long(7FFFFFFFH);
    s:=Integers.Short(n); 
       => s = 2147483647
    f:=Integers.Float(n);
       => f = 2.14748364700000E+9
    

    The following are common mathematical operations, which operate on Integers:

    Function: Abs (x: Integer): Integer
    This function returns the absolute value of x.

    Function: Odd (x: Integer): BOOLEAN
    This function returns TRUE if x is an odd number, and FALSE if it is even.

    Function: Compare (x, y: Integer): LONGINT
    This function compares the values of x and y and gives the following result:

      If x > y, return 1
      If x = y, return 0
      If x < y, return -1
    

    Function: Difference (x, y: Integer): Integer
    This function returns the difference of x and y (i.e., x-y).

    Example:

    VAR n: Integers.Integer;
    
    n:=Integers.Difference(Integers.Long(2000000), Integers.Long(999));
       => n = 1999001
    
    n:=Integers.Difference(Integers.Long(999), Integers.Long(-2000000)); 
       => n = -2000999
    
    n:=Integers.Difference(Integers.Long(-999), Integers.Long(999)); 
       => n = -1998
    
    n:=Integers.Difference(Integers.Long(-2000000), Integers.Long(-999)); 
       => n = -1999001
    

    Function: Sum (x, y: Integer): Integer
    This function returns the sum of x and y (i.e., x+y).

    Example:

    VAR n: Integers.Integer;
    
    n:=Integers.Sum(Integers.Long(999), Integers.Long(2000000));
       => n = 2000999
    
    n:=Integers.Sum(Integers.Long(999), Integers.Long(-2000000)); 
       => n = -1999001
    
    n:=Integers.Sum(Integers.Long(-999), Integers.Long(999)); 
       => n = 0
    
    n:=Integers.Sum(Integers.Long(-2000000), Integers.Long(-999)); 
       => n = -2000999
    

    Function: Product (x, y: Integer): Integer
    This function returns the product of x and y (i.e., x*y).

    Example:

    VAR n: Integers.Integer;
    
    n:=Integers.Product(Integers.Long(100000000), Integers.Long(100000000)); 
       => n = 10000000000000000
    
    n:=Integers.Product(Integers.Long(71234), Integers.Long(66000)); 
       => n = 4701444000
    

    Function: Quotient (x, y: Integer): Integer
    This function returns the quotient of x divided by y (i.e., x DIV y).

    Pre-condition: y is not zero.

    Function: Remainder (x, y: Integer): Integer
    This function returns the remainder of x divided by y (i.e., x MOD y).

    Pre-condition: y is not zero.

    Example:

    VAR m, n: Integers.Integer;
    
    n:=Integers.Quotient(Integers.Long(2000000000), Integers.Long(1234)); 
    m:=Integers.Remainder(Integers.Long(2000000000), Integers.Long(1234)); 
       => n = 1620745, m = 670
    
    n:=Integers.Quotient(Integers.Long(2000000000), Integers.Long(123456)); 
    m:=Integers.Remainder(Integers.Long(2000000000), Integers.Long(123456)); 
       => n = 16200, m = 12800
    

    Procedure: QuoRem (x, y: Integer; VAR quo, rem: Integer)
    This procedure calculates both the quotient and remainder of x divided by y.

    Pre-condition: y is not zero.

    Example:

    VAR m, n: Integers.Integer;
    
    Integers.QuoRem(Integers.Long(2000000000), Integers.Long(1234), n, m); 
       => n = 1620745, m = 670
    
    Integers.QuoRem(Integers.Long(2000000000), Integers.Long(123456), n, m); 
       => n = 16200, m = 12800
    

    Function: GCD (x, y: Integer): Integer
    This function returns the greatest common divisor of x and y.

    Example:

    VAR n: Integers.Integer; 
    
    n:=Integers.GCD(Integers.Long(40902), Integers.Long(24140));
       => n = 34
    
    n:=Integers.GCD(Integers.Long(27182818), Integers.Long(10000000));
       => n = 2
    
    n:=Integers.GCD(Integers.Long(2940), Integers.Long(238));
       => n = 14
    

    Function: Power (x: Integer; exp: LONGINT): Integer
    This function returns the value of x raised to the power exp.

    Pre-condition: exp is greater than zero.

    Example:

    VAR n: Integers.Integer; 
    
    n:=Integers.Power(Integers.Long(2940), 2);
       => n = 8643600
    
    n:=Integers.Power(Integers.Long(2), 33);
       => n = 8589934592
    
    n:=Integers.Power(Integers.Long(10), 9);
       => n = 1000000000
    
    n:=Integers.Power(Integers.Long(2), 100);
       => n = 1267650600228229401496703205376
    

    Function: Sign (x: Integer): SHORTINT
    This function returns the sign of x as follows:

      If x > 0, return 1
      If x = 0, return 0
      If x < 0, return -1
    

    Function: Factorial (x: LONGINT): Integer
    This function returns x factorial (i.e., x!=x(x-1)(x-2)...(2)(1)).

    Pre-condition: x is not negative.

    Example:

    VAR n: Integers.Integer; 
    
    n:=Integers.Factorial(13);
       => n = 6227020800
    
    n:=Integers.Factorial(20);
       => n = 2432902008176640000
    

    The following operations are used to extract pieces of Integers:

    Function: ThisDigit10 (x: Integer; exp10: LONGINT): CHAR
    This function returns a single character, which represents the digit in x located at position exp10. Note that the right most digit (i.e., the "ones" place) has position zero.

    Pre-condition: exp10 is not negative.

    Example:

    VAR n: Integers.Integer; 
        c: CHAR;
    
    Integers.ConvertFromString("1267650600228229401496703205376", n);
    
    c:=Integers.ThisDigit10(n, 0);
       => c = "6"
    
    c:=Integers.ThisDigit10(n, 10);
       => c = "9"
    
    c:=Integers.ThisDigit10(n, 30);
       => c = "1"
    

    Function: Digits10Of (x: Integer): LONGINT
    This function returns the value of the last ten digits of x (i.e., it returns x MOD 1000000000).

    Example:

    VAR n: Integers.Integer; 
        s: LONGINT;
    
    Integers.ConvertFromString("1267650600228229401496703205376", n);
    
    s:=Integers.Digits10Of(n);
       => s = 703205376
    

    The following operations are used to convert between strings and Integers:

    Procedure: ConvertFromString (s: ARRAY OF CHAR; VAR x: Integer)
    This procedure converts s to an Integer value, which is assigned to x. Leading spaces and tab characters in s are skipped.

    Pre-condition: s is in the form of a signed whole number (see section Syntax of Text Tokens)

    Procedure: ConvertToString (x: Integer; VAR s: ARRAY OF CHAR)
    This procedure converts x to a string value, which is assigned to s.

    Example:

    VAR n: Integers.Integer; 
        str: ARRAY 1024 OF CHAR;
    
    Integers.ConvertFromString("1234567890", n);
       => n = 1234567890
    Integers.ConvertToString(n, str); 
       => str = "1234567890"
    
    Integers.ConvertFromString("  -9999999999", n); 
       => n = -9999999999
    Integers.ConvertToString(n, str);
       => str = "-9999999999"
    
    Integers.ConvertFromString(" 12345678901234567890123456789", n);
       => n = 12345678901234567890123456789
    Integers.ConvertToString(n, str); 
       => str = "12345678901234567890123456789"
    

    The following operations can be used to internalize and externalize Integers (i.e., read from and write to channels):

    Procedure: Externalize (VAR w: BinaryRider.Writer; x: Integer)
    Writes the value of x to a channel using writer w.
    Procedure: Internalize (VAR r: BinaryRider.Reader; VAR x: Integer)
    Retrieves a stored Integer value from a channel using reader r, and assigns it to x.

    Complex Numbers

    The modules ComplexMath and LComplexMath provide facilities for complex numbers, which includes common mathematical functions for types COMPLEX and LONGCOMPLEX.

    Instances of the following two classes are used to represent complex numbers:

    Data type: COMPLEX = POINTER TO COMPLEXDesc
    The real and imaginary parts of this type are represented as type REAL

    Data type: LONGCOMPLEX = POINTER TO LONGCOMPLEXDesc
    The real and imaginary parts of this type are represented as type LONGREAL

    Please note: To create initial instances of COMPLEX and LONGCOMPLEX, you must use the corresponding CMPLX() function.

    The following are instances of the corresponding complex number type. They are provided for convenience and have values that represent the specified complex number:

    Read-only Variable: i
    The value of i is initialized to CMPLX (0.0, 1.0).

    Read-only Variable: one
    The value of one is initialized to CMPLX (1.0, 0.0).

    Read-only Variable: zero
    The value of zero is initialized to CMPLX (0.0, 0.0).

    The following functions are provided in either ComplexMath (for COMPLEX) or
    LComplexMath (for LONGCOMPLEX):

    Function: CMPLX (r, i: REAL): COMPLEX
    Function: CMPLX (r, i: LONGREAL): LONGCOMPLEX
    This function returns an instance of the corresponding complex number type whose real part has a value of r and imaginary part has a value of i.

    Function: Copy (z: COMPLEX): COMPLEX
    Function: Copy (z: LONGCOMPLEX): LONGCOMPLEX
    This function returns a copy of z.

    Please note: This function provides the only reliable way to assign complex number values. If a and b are complex numbers, do not use a := b.

    Function: RealPart (z: COMPLEX): REAL
    Function: RealPart (z: LONGCOMPLEX): LONGREAL
    This function returns the real part of the complex number z.

    Function: ImagPart (z: COMPLEX): REAL
    Function: ImagPart (z: LONGCOMPLEX): LONGREAL
    This function returns the imaginary part of the complex number z.

    Function: add (z1, z2: COMPLEX): COMPLEX
    Function: add (z1, z2: LONGCOMPLEX): LONGCOMPLEX
    This function returns the value of z1 added to z2.

    Function: sub (z1, z2: COMPLEX): COMPLEX
    Function: sub (z1, z2: LONGCOMPLEX): LONGCOMPLEX
    This function returns the value of z2 subtracted from z1.

    Function: mul (z1, z2: COMPLEX): COMPLEX
    Function: mul (z1, z2: LONGCOMPLEX): LONGCOMPLEX
    This function returns the value of z1 multiplied by z2.

    Function: div (z1, z2: COMPLEX): COMPLEX
    Function: div (z1, z2: LONGCOMPLEX): LONGCOMPLEX
    This function returns the value of z1 divided by z2.

    Function: abs (z: COMPLEX): REAL
    Function: abs (z: LONGCOMPLEX): LONGREAL
    This function returns an approximation to the length (also known as the absolute value, or modulus) of z.

    Please note: An overflow exception may be raised in this computation, even when the complex number itself is well defined.

    Function: arg (z: COMPLEX): REAL
    Function: arg (z: LONGCOMPLEX): LONGREAL
    This function returns an approximation to the angle that z subtends to the positive real axis in the complex plane. The result will be in radians in the range [-pi, pi]. If the modulus (abs(x)) of z is zero, an exception is raised.

    Function: conj (z: COMPLEX): COMPLEX
    Function: conj (z: LONGCOMPLEX): LONGCOMPLEX
    This function returns an approximation to the complex conjugate of z.

    Function: power (base: COMPLEX; exponent: REAL): COMPLEX
    Function: power (base: LONGCOMPLEX; exponent: LONGREAL): LONGCOMPLEX
    This function returns an approximation to the value of the number base raised to the power exponent.

    Function: sqrt (z: COMPLEX): COMPLEX
    Function: sqrt (z: LONGCOMPLEX): LONGCOMPLEX
    This function returns an approximation to the principal square root of z.

    Please note: The result is the complex number with an arg() of half the value of the arg() of z, and whose abs() is the positive square root of the abs() of z.

    Function: exp (z: COMPLEX): COMPLEX
    Function: exp (z: LONGCOMPLEX): LONGCOMPLEX
    This function returns an approximation to the mathematical constant e raised to the power of z.

    Function: ln (z: COMPLEX): COMPLEX
    Function: ln (z: LONGCOMPLEX): LONGCOMPLEX
    This function returns an approximation to the principal value of the natural logarithm of z.

    Function: sin (z: COMPLEX): COMPLEX
    Function: sin (z: LONGCOMPLEX): LONGCOMPLEX
    This function returns an approximation to the complex sine of z.

    Function: cos (z: COMPLEX): COMPLEX
    Function: cos (z: LONGCOMPLEX): LONGCOMPLEX
    This function returns an approximation to the complex cosine of z.

    Function: tan (z: COMPLEX): COMPLEX
    Function: tan (z: LONGCOMPLEX): LONGCOMPLEX
    This function returns an approximation to the complex tangent of z. If z is an odd multiple of pi/2, an exception is raised.

    Function: arcsin (z: COMPLEX): COMPLEX
    Function: arcsin (z: LONGCOMPLEX): LONGCOMPLEX
    This function returns an approximation to the principal value of the complex arcsine of z.

    Function: arccos (z: COMPLEX): COMPLEX
    Function: arccos (z: LONGCOMPLEX): LONGCOMPLEX
    This function returns an approximation to the complex arccosine of z.

    Function: arctan (z: COMPLEX): COMPLEX
    Function: arctan (z: LONGCOMPLEX): LONGCOMPLEX
    This function returns an approximation to the complex arctangent of z.
    Function: polarToComplex (abs, arg: REAL): COMPLEX
    Function: polarToComplex (abs, arg: LONGREAL): LONGCOMPLEX
    This function returns an approximation to the complex number with the specified polar coordinates. The result will have a length of abs and angle of arg).

    Function: scalarMult (scalar: REAL; z: COMPLEX): COMPLEX
    Function: scalarMult (scalar: LONGREAL; z: LONGCOMPLEX): LONGCOMPLEX
    This function returns an approximation to the scalar product of scalar with z.

    Function: IsCMathException (): BOOLEAN
    This function returns TRUE if the current process is in the exceptional execution state because of the raising of the corresponding ComplexMath or LComplexMath exception; otherwise, it returns FALSE.

    Random Numbers

    "Random number" generating routines, like those provided in module `RandomNumbers', are more correctly called pseudo-random number generators because they have only the appearance of randomness, and actually exhibit a specific, repeatable pattern. However, the generated sequence of numbers should pass certain statistical tests as if it were a truly random sequence.

    The algorithm implemented by `RandomNumbers' is "good" in the sense that it passes many of these statistical tests, but it is not necessarily useful in all cases. A different algorithm might be better suited to a particular application simply because the inherent structure of the generated number sequence better satisfies the application's required properties.

    Because of the deterministic quality of random number generators, the user is required to specify an initial value, or seed. Sequences generated using the same seed (and the same algorithm) will always produce the same results. To get a different sequence, simply use a different seed. A common way to generate different seeds is to initialize using the system's clock time. (This is not done directly within `RandomNumbers' because then it is not possible to reproduce results, which could cause difficulties during, say, testing and debugging.)

    Also note that sequences will repeat themselves eventually. In this case, a sequence will start to repeat after, at most, modulo-1 elements, and possibly much sooner than that.

    A complete discussion of random number generating algorithms is beyond the scope of this manual. For more information about the algorithm used in this module, and other random number generators, consult the following references:

    Random number generators: good ones are hard to find
    S.K. Park and K.W. Miller
    Communications of the ACM, Vol. 31, No. 10, October 1988, pp. 1192-1201
    
    The Art Of Computer Programming:
    Volume 2, Seminumerical Algorithms, Second Edition
    Donald E. Knuth
    Addison-Wesley Publishing Co., January 1981
    

    Constant: modulo
    The determing parameter of the linear congruential generator being used by `RandomNumbers'.

    Procedure: GetSeed (VAR seed: LONGINT)
    This procedure gets the seed value currently in use by routines in module `RandomNumbers'.

    Procedure: PutSeed (seed: LONGINT)
    This procedure sets seed as the new seed value for routines in `RandomNumbers'. Any value for seed is allowed, but all values will be mapped into the range [1..modulo-1].

    Function: RND (range: LONGINT): LONGINT
    This function calculates a new "random" number. range has to be in the range [1..modulo-1], and the result is a number in the interval [0, range-1].

    Function: Random (): REAL
    This function calculates a new "random" number. The result is a number in the interval [0, 1).

    Example:

    VAR l: LONGINT;
        r: REAL;
    
    RandomNumbers.PutSeed(314159);
    
    l := RandomNumbers.RND(100);
       => l = 19
    l := RandomNumbers.RND(10000);
       => l = 5610
    l := RandomNumbers.RND(9999999);
       => l = 6158792
    l := RandomNumbers.RND(365);
       => l = 54
    
    RandomNumbers.GetSeed(l);
       => l = 143441039
    
    r := RandomNumbers.Random();
       => r = 0.6225381
    r := RandomNumbers.Random();
       => r = 0.9990177
    r := RandomNumbers.Random();
       => r = 0.4895853
    r := RandomNumbers.Random();
       => r = 0.4605866
    
    RandomNumbers.GetSeed(l);
       => l = 989102265
    


    Go to the first, previous, next, last section, table of contents. OOCref_9.html100664 1750 1750 121025 6753666031 11217 0ustar sagsag The OOC Reference Manual - Date and Time

    Go to the first, previous, next, last section, table of contents.


    Date and Time

    This chapter describes the facilities for manipulating dates and times, including getting and setting the date and time, and conversions between formats.

    Module Time

    Module Time provides facilites for time stamp and time interval manipulation.

    A time stamp represents a particular instant in time.

    A time interval is the duration between two instants read on the same time scale.

    Another way to view time stamps and intervals is to consider them in the context of a one-dimensional vector space: A time stamp is a point, a time interval a vector. Seen in this way, some functions perform vector arithmetic on time intervals.

    Please note: Date and time modules refer to UTC, which is Coordinated Universal Time (or Universal Time Coordinated). UTC replaces Greenwich Mean Time (GMT) and is recommended for all general timekeeping applications. UTC and GMT are effectively equivalent; the difference being that UTC is adjusted by an integral number of seconds called leap seconds (see http://www.boulder.nist.gov/timefreq/glossary.htm for more precise definitions).

    No provision is made for leap seconds in the date and time modules.

    The following constants are defined:

    Constant: msecPerSec
    The number of milliseconds per second.

    Constant: msecPerMin
    The number of milliseconds per minute.

    Constant: msecPerHour
    The number of milliseconds per hour.
    Constant: msecPerDay
    The number of milliseconds per day.

    Module Time declares the following types for time intervals and time stamps:

    Class: Interval = RECORD
    This type is used to represent a delta time measure, which can be used to increment a time or find the time difference between two times.

    The maximum number of milliseconds in an interval is the value msecPerDay.

    The fields are defined as follows:

    Field: dayInt-: LONGINT
    The number of days in this interval.
    Field: msecInt-: LONGINT
    The number of milliseconds in this interval.

    The following are operations on Interval:

    Procedure: InitInterval (VAR int: Interval; days, msecs: LONGINT)
    This procedure is used to initialize an Interval int with days days and msecs milliseconds.

    Pre-condition: msecs is not negative.

    Method: (VAR a: Interval) Add (b: Interval)
    This method computes the value of a added to b. The result is assigned to a.
    Method: (VAR a: Interval) Sub (b: Interval)
    This method computes the value of b subtracted from a. The result is assigned to a.

    Example:

    VAR int1, int2: Time.Interval;
    
    Time.InitInterval(int1, 10, 0);
    
    Time.InitInterval(int2, 5, 0);
       => int2.dayInt = 5, int2.msecInt = 0
     
    int1.Add(int2);  (* == int1 = int1 + int2 *)
       => int1.dayInt = 15, int1.msecInt = 0
    
    int1.Add(int1);  (* == int1 = int1 + int1 *)
       => int1.dayInt = 30, int1.msecInt = 0
    
    int1.Sub(int2);  (* == int1 = int1 - int2 *)
       => int1.dayInt = 25, int1.msecInt = 0
    
    Time.InitInterval(int1, 0, 43200000);  (* == 12 hours *)
       => int1.dayInt = 0, int1.msecInt = 43200000
    
    int1.Add(int1);  (* 12 hrs + 12 hrs = 24 hrs == 1 day *)
       => int1.dayInt = 1, int1.msecInt = 0
    
    Time.InitInterval(int2, 0, 1800000);  (* == 30 minutes *)
       => int2.dayInt = 0, int2.msecInt = 1800000
    
    int2.Add(int2);  (* 30 mins + 30 mins = 60 mins == 1 hr *)
       => int2.dayInt = 0, int2.msecInt = 3600000
    
    int1.Sub(int2);  (* 24 hrs - 1 hr = 23 hrs == 82800000 *)
       => int1.dayInt = 0, int1.msecInt = 82800000
    
    Method: (VAR a: Interval) Cmp (b: Interval): SHORTINT
    This method compares the values of a and b and returns the following result:
      If a > b, return 1
      If a = b, return 0
      If a < b, return -1
    
    Method: (VAR a: Interval) Scale (b: LONGREAL)
    This method scales the value of a by b (i.e., a multiplied by b). The result is assigned to a. Pre-condition: b is not negative.
    Method: (VAR a: Interval) Fraction (b: Interval): LONGREAL
    This method computes the fraction b of the interval a (i.e, a divided by b). Pre-condition: b is not zero.

    Example:

    VAR int1, int2: Time.Interval;
        result: SHORTINT;
        frac: LONGREAL;
    
    Time.InitInterval(int1, 0, 82800000);  (* == 23 hours *)
       => int1.dayInt = 0, int1.msecInt = 82800000
    
    Time.InitInterval(int2, 0, 3600000);  (* == 1 hr *)
       => int2.dayInt = 0, int2.msecInt = 3600000
    
    result := int1.Cmp(int2);
       => result = 1  (* == int1 > int2 *)
    
    result := int2.Cmp(int1);
       => result = -1  (* == int2 < int1 *)
    
    result := int1.Cmp(int1);
       => result = 0  (* == int1 = int1 *)
    
    int2.Scale(23);  (* 1 hr * 23 = 23 hrs *)
       => int2.dayInt = 0, int2.msecInt = 82800002
            (* approximately equal to 23 hrs. *)
    
    int2.Scale(2);  (* 23 hrs * 2 = 46 hours *)
       => int2.dayInt = 1, int2.msecInt = 79199997
            (* approximately == 1 day and 22 hours *)
    
    frac := int2.Fraction(int1); (* 46 hrs / 23 hrs = 2 *)
       => frac = 2.00000006219615  (* approx. 2 *)
    
    frac := int1.Fraction(int2); (* 23 hrs / 46 hrs = 0.5 *)
       => frac = 4.99999984450962E-1  (* approx. 0.5 *)
    

    Class: TimeStamp = RECORD
    This type represents an instant in time using a compressed date/time format.

    Please note: TimeStamp is in Coordinated Universal Time (UTC) on systems that support time zones. Without such support, it is assumed that they refer to the local time zone with an unspecified time zone offset.

    The fields are defined as follows:

    Field: days-: LONGINT
    Modified Julian days since midnight 17 Nov 1858. This quantity can be negative to represent dates occuring before day zero.
    Field: msecs-: LONGINT
    Milliseconds since 00:00.

    The following are operations on TimeStamp:

    Procedure: InitTimeStamp (VAR t: TimeStamp; days, msecs: LONGINT)
    This procedure is used to initialize a TimeStamp t with days days and msecs milliseconds.

    Pre-condition: msecs is not negative.

    Method: (VAR a: TimeStamp) Add (b: Interval)
    This method adds the interval b to the time stamp a.
    Method: (VAR a: TimeStamp) Sub (b: Interval)
    This method subtracts the interval b from the time stamp a.
    Method: (VAR a: TimeStamp) Delta (b: TimeStamp; VAR c: Interval)
    This method subtracts the value of time stamp b from the time stamp a. The result is assigned to the interval c.
    Method: (VAR a: TimeStamp) Cmp (b: TimeStamp): SHORTINT
    This method compares the values of a and b and returns the following result:
      If a > b, return 1
      If a = b, return 0
      If a < b, return -1
    

    Example:

    VAR ts1, ts2: Time.TimeStamp;
        int1  : Time.Interval;
        result: SHORTINT;
    
    Time.InitTimeStamp(ts1, 40000, 0);
       => ts1.days = 40000, ts1.msecs = 0
            (* == midnight 24 May 1968 *)
    
    Time.InitInterval(int1, 10, 3600000);
    ts1.Add(int1);
       => ts1.days = 40010, ts1.msecs = 3600000
            (* == 1:00 3 Jun 1968 *)
    
    Time.InitInterval(int1, 5000, 21600000);  
            (* == 5000 days, 6 hours *)
    ts1.Sub(int1);
       => ts1.days = 35009, ts1.msecs = 68400000
            (* == 19:00 24 Sep 1954 *)
    
    Time.InitTimeStamp(ts2, 50000, 43200000); 
       => ts1.days = 50000, ts1.msecs = 43200000
            (* == noon 10 October 1995 *)
    
    ts2.Delta(ts1, int1);
       => int1.dayInt = 14990, int1.msecInt = 61200000
    
    result := ts2.Cmp(ts1);
       => result = 1  
            (* == ts2 > ts1  i.e., ts2 occurs after ts1 *)
    

    Module JulianDay

    The module JulianDay provides facilities for convertion between day/ month/ year and various forms of Julian Days. Julian Days are a standard convention used for describing dates with the least possible ambiguity.

    The Julian Day Number (JDN) is a whole number representing the number of consecutive days since noon 1 January 4713 B.C. (this is Julian Day 0).

    The Julian Date (JD) is an extension of Julian Day Number, which includes a fractional part representing the elapsed fraction of a day since the preceding noon.

    The Modified Julian Day (MJD) begins instead at midnight (in keeping with more standard conventions) 17 November 1858. This allows the first two digits of the Julian Day to be removed; that is, this date is Julian Day 2400000. So,

    MJD = JD - 2400000.5
    

    The Modified Julian Date is the Julian Date minus 2400000.5.

    The Truncated Julian Day (TJD) is the Modified Julian Day truncated to four digits. When TJD first came into use, its origin date (i.e., "epoch") was at midnight 24 May 1968 (i.e., JDN 2440000). However, it "recycled" at midnight 10 October 1995 (i.e., JDN 2450000), so currently

    TJD = MJD - 50000
    

    Please note: The various Julian Days are integer values and are distinct from Julian Dates, which are real number values. You should keep this in mind when using the facilities in module JulianDay.

    Several constants are provided for use in Julian Day and Date calculations:

    Constant: startMJD
    Zero basis (i.e, "epoch") for modified Julian Day expressed as a Julian Date. (This number will be 2400000.5D0.)

    Constant: startTJD
    Zero basis (i.e, "epoch") for Truncated Julian Day.

    The following is provided to test for use of the Gregorian calendar:

    The Gregorian Calendar is the calendar system now in general use throughout the world. It was adopted because the Julian Calendar (used in the Roman empire and then by the Roman Catholic Church) accumulated an error of one day every 128 years (thus it is currently 13 days behind the Gregorian Calendar).

    The Gregorian Calendar (first prescribed in 1582 by Pope Gregory XIII) adjusts the Julian year to the astronomical year by dropping three leap years every 400 years. That is, at the end of each century, there is no leap year, except in the years 1600, 2000, 2400, and so forth.

    Read-only Variable: UseGregorian
    A boolean value that is TRUE when the Gregorian Calendar is being used by module JulianDay. See also the procedure SetGregorianStart.

    Conversion facilities are provided as follows:

    Function: DateToJD (day, month: SHORTINT; year: INTEGER): LONGREAL
    This function returns the Julian Date for the given day, month, and year at 0000 UTC (midnight). Any date with a positive year is valid. The returned value is the number of days since noon 1 January 4713 B.C. (Note that the result will always have a fractional part equal to `.5'.)

    Procedure: JDToDate (jd: LONGREAL; VAR day, month: SHORTINT; VAR year: INTEGER)
    This procedure converts a Julian Date jd to a date given by the day, month, and year.

    Algorithms for DateToJD and JDToDate by William H. Jefferys (with some modifications) at

    http://quasar.as.utexas.edu/BillInfo/JulianDatesG.html

    Example:

    VAR date: LONGREAL;
        day, month: SHORTINT;
        year: INTEGER;
        
    date := JulianDay.DateToJD(10, 10, 1995);
       => date = 2450000.5
    JulianDay.JDToDate(date, day, month, year);
       => day = 10, month = 10, year = 1995
    
    date := JulianDay.DateToJD(17, 11, 1858);
       => date = 2400000.5
    JulianDay.JDToDate(date, day, month, year);
       => day = 17, month = 11, year = 1858
    

    Function: DateToDays (day, month: SHORTINT; year: INTEGER): LONGINT
    This function returns the Modified Julian Day for the given day, month, and year at 0000 UTC (midnight). Any date with a positive year is valid. The returned value is the number of days since midnight 17 November 1858.

    Procedure: DaysToDate (jd: LONGINT; VAR day, month: SHORTINT; VAR year: INTEGER)
    This procedure converts a Modified Julian Day jd to a date given by the day, month, and year.

    Example:

    VAR days: LONGINT;
        day, month: SHORTINT;
        year: INTEGER;
    
    days := JulianDay.DateToDays(10, 10, 1995);
       => days = 50000
    JulianDay.DaysToDate(days, day, month, year);
       => day = 10, month = 10, year = 1995
    
    days := JulianDay.DateToDays(17, 11, 1858);
       => days = 0
    JulianDay.DaysToDate(days, day, month, year);
       => day = 17, month = 11, year = 1858
    
    days := JulianDay.DateToDays(8, 4, 1513);
       => days = -126222
    JulianDay.DaysToDate(days, day, month, year);
       => day = 8, month = 4, year = 1513
    

    Function: DateToTJD (day, month: SHORTINT; year: INTEGER): LONGINT
    This function returns the Truncated Julian Day for the given day, month, and year at 0000 UTC (midnight). Any date with a positive year is valid. The returned value is the number of days since midnight 10 October 1995.

    Procedure: TJDToDate (jd: LONGINT; VAR day, month: SHORTINT; VAR year: INTEGER)
    This procedure converts a Truncated Julian Day jd to a date given by the day, month, and year.

    Example:

    VAR days: LONGINT;
        day, month: SHORTINT;
        year: INTEGER;
    
    days := JulianDay.DateToTJD(10, 10, 1995);
       => days = 0
    JulianDay.TJDToDate(days, day, month, year);
       => day = 10, month = 10, year = 1995
    
    days := JulianDay.DateToTJD(25, 12, 1997);
       => days = 807
    JulianDay.TJDToDate(days, day, month, year);
       => day = 25, month = 12, year = 1997
    
    days := JulianDay.DateToTJD(17, 11, 1858);
       => days = -50000
    JulianDay.TJDToDate(days, day, month, year);
       => day = 17, month = 11, year = 1858
    

    Procedure: SetGregorianStart (day, month: SHORTINT; year: INTEGER)
    Sets the start date when the Gregorian Calendar was first used where the date in day, month, and year according to the Julian Calendar.

    The default date used is `3 Sep 1752' (when the Gregorian Calendar was adopted in England). (At that time, the Julian Calendar was 11 days behind the Gregorian Calendar. And so, `3 Sep 1752' according to the Julian Calendar is `14 Sep 1752' according the the Gregorian Calendar.)

    Example:

    VAR date: LONGREAL;
        day, month: SHORTINT;
        year: INTEGER;
    
    date := JulianDay.DateToJD(2, 9, 1752);
       => date = 2361220.5
    
    JulianDay.SetGregorianStart(15, 10, 1582);
       (* move start date to before `3 Sep 1752' *)
    
    JulianDay.JDToDate(date, day, month, year);
       => day = 13, month = 9, year = 1752
       (* When Gregorian start date occurs at an earlier date,
          Julian Calendar date `2 Sep 1752' is corrected to 
          the Gregorian date `13 Sep 1752'.
       *)   
    

    Module SysClock

    Module SysClock provides facilities for accessing a system clock that records the date and time of day. This includes a DateTime type, which represents a system-independent time format. Note that the module Calendar provides additional operations for DateTime. Please note:

    The following constants are defined:

    Constant: maxSecondParts
    Accuracy of measure for "parts of a second" (`fractions') (Most systems have just millisecond accuracy: `maxSecondParts = 999'.)
    Constant: zoneMin
    Used as a minimum range limit for time zone (`zone') in minutes.

    Constant: zoneMax
    Used as a maximum range limit for time zone (`zone') in minutes.

    The following constants are used as possible time zone values for zone:

    Constant: localTime
    Indicates that time zone is inactive and time is local.

    Constant: unknownZone
    Indicates that time zone is unknown.

    The following constants are used as possible daylight savings mode values for
    summerTimeFlag:

    Constant: unknown
    Indicates that current daylight savings status is unknown.

    Constant: inactive
    Indicates that daylight savings adjustments are not in effect.

    Constant: active
    Indicates that daylight savings adjustments are being used.
    Record: DateTime
    This type represents an instant in time using a combination of fields for date and time information. The fields are defined as follows:

    Field: year: INTEGER
    A positive value representing a four digit year.
    Field: month: SHORTINT
    A value in the range `1..12'.
    Field: day: SHORTINT
    A value in the range `1..31'.
    Field: hour: SHORTINT
    A value in the range `0..23'.
    Field: minute: SHORTINT
    A value in the range `0..59'.
    Field: second: SHORTINT
    A value in the range `0..59'.
    Field: fractions: INTEGER
    A value in the range `0..maxSecondParts' representing parts of a second in milliseconds.
    Field: zone: INTEGER
    A value in the range `zoneMin..zoneMax'. This represents a time zone differential factor, which is the number of minutes to add to local time to obtain UTC or is set to localTime when time zones are inactive. Please note: `-780..720' is the typical range for zone.
    Field: summerTimeFlag: SHORTINT
    This value represents the current status of daylight savings mode. Interpretation of this flag depends on local usage. However, the constants unknown, active, and inactive are provided as possible values.

    The following procedures are provided in module SysClock:

    Function: CanGetClock (): BOOLEAN
    This function returns TRUE if there is a system clock, which the program is permitted to read. Otherwise, it returns FALSE.
    Function: CanSetClock (): BOOLEAN
    This function returns TRUE if there is a system clock, which the program is permitted to set. Otherwise, it returns FALSE.

    Function: IsValidDateTime (d: DateTime): BOOLEAN
    This function returns TRUE if the value of d represents a valid date and time. Otherwise, it returns FALSE.

    Procedure: GetClock (VAR userData: DateTime)
    This procedure assigns the system date and time to the fields of userData (i.e., userData is set to local time).

    If an error occurs, userData is set to `1 Jan 1970'.

    Procedure: SetClock (userData: DateTime)
    This procedure sets the system clock to the date and time specified by userData. If the program cannot set the system clock, a call of SetClock has no effect.

    The behavior of SetClock is undefined if userData represents a invalid date and time.

    Procedure: MakeLocalTime (VAR c: DateTime)
    This procedure sets the daylight savings mode summerTimeFlag and time zone zone for calendar date c. This assumes that c describes a valid local time. The previous values of summerTimeFlag and zone are ignored and are overwritten by a call to MakeLocalTime.

    Please note:

    1. On most Unix systems the time zone information is only available for dates falling approximately within 1 Jan 1902 to 31 Dec 2037. Outside this range the field zone will be set to the unspecified localTime value , and summerTimeFlag will be set to unknown.
    2. The time zone information might not be fully accurate for past (and future) years that apply different Daylight Savings Time (DST) rules than the current year. Usually, the current set of rules is used for all years between 1902 and 2037.
    3. With DST there is one hour in the year that happens twice: the hour after which the clock is turned back for a full hour. It is undefined which time zone will be selected for dates refering to this hour; that is, whether DST or normal time zone will be chosen.

    Module Calendar

    Module Calendar provides facilities for manipulation of dates and times. These facilities include procedures to convert between SysClock.DateTime and Time.TimeStamp, as well as conversions between DateTime and various string formats.

    The following constants are defined for the days of the week:

    Constant: sunday
    Constant: monday
    Constant: tuesday
    Constant: wednesday
    Constant: thursday
    Constant: friday
    Constant: saturday
    And the following constants are defined for the months of the year:

    Constant: january
    Constant: february
    Constant: march
    Constant: april
    Constant: may
    Constant: june
    Constant: july
    Constant: august
    Constant: september
    Constant: october
    Constant: november
    Constant: december

    The following procedures are used to initialize instances of DateTime:

    Procedure: SetLocalTime (VAR c: SysClock.DateTime; d, m: SHORTINT; y: INTEGER; h, min, s: SHORTINT)
    This procedure initializes the calendar c with the local date from d days, m months, y years; and the local time from h hours, min minutes, and s seconds. These values must be in the valid ranges for each field:

    year
    y > 0.
    month
    m in the range `1..12'.
    day
    d in the range `1..31'.
    hour
    h in the range `0..23'.
    minute
    min in the range `0..59'.
    second
    s in the range `0..59'.

    The other fields of c are set as follows:

    Please note: SetLocalTime utilizes SysClock.MakeLocalTime to obtain time zone and daylight savings mode information. All restrictions on MakeLocalTime also apply to SetLocalTime.

    Example:

    VAR
      c: SysClock.DateTime;
    
    Calendar.SetLocalTime(c, 31, 12, 1997, 15, 30, 00);
       => c = Wednesday, 31 Dec 1997, 15:30:00.0 
    

    Procedure: SetUTC (VAR c: SysClock.DateTime; d, m: SHORTINT; y: INTEGER; h, min, s: SHORTINT)
    This procedure initializes the calendar c exactly like SetLocalTime except for the following differences:

    The following procedures are used to convert between
    SysClock.DateTime and Time.TimeStamp:

    Procedure: GetTimeStamp (VAR c: SysClock.DateTime; s: Time.TimeStamp)
    This procedure sets the calendar c from the time stamp s based on local time (i.e., c.zone and c.summerTimeFlag are set as in SetLocalTime).

    Example:

    VAR
      c: SysClock.DateTime;
      ts: Time.TimeStamp;
    
    Time.InitTimeStamp(ts, 50000, 43200000); 
            (* == noon 10 October 1995 UTC *)
    Calendar.GetTimeStamp(c, ts);
       => c = Tuesday, 10 Oct 1995, 08:00:00
       => c.zone = 240  
            (* i.e., local time is 4 hours behind UTC *)
    

    Procedure: SetTimeStamp (c: SysClock.DateTime; VAR t: T.TimeStamp)
    This procedure converts the calendar date c to a time stamp t.

    The following functions provide useful information about a particular DateTime value:

    Function: DayOfWeek (c: SysClock.DateTime): SHORTINT
    This function returns the day of the week of c as one of the constant values
    `sunday..saturday'.

    Function: IsLeapYear (c: SysClock.DateTime): BOOLEAN
    This function returns TRUE if c occurs within a leap year. Otherwise, it returns FALSE.

    Function: DaysPerMonth (c: SysClock.DateTime): SHORTINT
    This function returns the total number of days in the month of c (i.e., one of `28', `29', `30', or `31'). Leap years are taken into account.

    Function: WeekNumber (c: SysClock.DateTime; startday: SHORTINT): INTEGER
    This function returns the week number of c based on each week beginning on startday. The value of startday is one of the constant values
    `sunday..saturday'. The first week of a month is recognized as having 4 or more days in that month where each week begins on startday.

    Function: DayOfYear (c: SysClock.DateTime): INTEGER
    This function returns the day of the year of c in the range `1..366'. For instance, January first for any year returns `1'.

    Example:

    VAR
      c: SysClock.DateTime;
      day, week, dayOfYear, daysInMon: INTEGER;
    
    Calendar.SetLocalTime(c, 31, 12, 1996, 12, 00, 00);
       => c = Tuesday, 31 Dec 1996, 12:00:00
    day := Calendar.DayOfWeek(c);
       => day = Calendar.tuesday 
    week := Calendar.WeekNumber(c, Calendar.sunday);
       => week = 1
    dayOfYear := Calendar.DayOfYear(c);
       => dayOfYear = 366
    IF Calendar.IsLeapYear(c) THEN ...
       => TRUE
    
    Calendar.SetLocalTime(c, 31, 12, 1997, 15, 30, 00);
       => c = Wednesday, 31 Dec 1997, 15:30:00
    day := Calendar.DayOfWeek(c);
       => day = Calendar.wednesday
    week := Calendar.WeekNumber(c, Calendar.sunday);
       => week = 53
    dayOfYear := Calendar.DayOfYear(c);
       => dayOfYear = 365
    IF Calendar.IsLeapYear(c) THEN ...
       => FALSE
    
    Calendar.SetLocalTime(c, 1, 2, 1996, 00, 00, 00);
       => c = Thursday, 1 Feb 1996, 00:00:00
    IF Calendar.IsLeapYear(c) THEN ...
       => TRUE
    daysInMon := Calendar.DaysPerMonth(c);
       => daysInMon = 29
    
    Calendar.SetLocalTime(c, 1, 2, 1997, 00, 00, 00);
       => c = Saturday, 1 Feb 1997, 00:00:00
    IF Calendar.IsLeapYear(c) THEN ...
       => FALSE
    daysInMon := Calendar.DaysPerMonth(c);
       => daysInMon = 28
    

    The following procedures are used to convert between SysClock.DateTime and time-formatted strings:

    Procedure: TimeToStr (VAR c: SysClock.DateTime; pattern: ARRAY OF CHAR; VAR dateStr: ARRAY OF CHAR)
    This procedure converts c to a string dateStr using the format template pattern. Allowable conversion specifiers for pattern are specialized for printing the date and time components of c according to the locale currently specified for time conversion (see section Module Locales).

    Normal characters appearing in pattern are copied verbatim to the output string dateStr; this can include multibyte character sequences. Conversion specifiers are introduced by a `%' character, and are replaced in the output string as follows:

    `%a'
    The abbreviated weekday name according to the current locale.
    `%A'
    The full weekday name according to the current locale.
    `%b'
    The abbreviated month name according to the current locale.
    `%B'
    The full month name according to the current locale.
    `%c'
    The preferred date and time representation for the current locale.
    `%d'
    The day of the month as a decimal number (in the range `01' to `31').
    `%D'
    The day of the month as above, but with no leading zero.
    `%H'
    The hour as a decimal number, using a 24-hour clock (in the range `00' to `23').
    `%I'
    The hour as a decimal number, using a 12-hour clock (in the range `01' to `12').
    `%i'
    The hour as a decimal number, using a 12-hour clock, but with no leading zero.
    `%j'
    The day of the year as a decimal number (in the range `001' to `366').
    `%m'
    The month as a decimal number (in the range `01' to `12').
    `%M'
    The minute as a decimal number.
    `%p'
    One of `AM' or `PM', according to the given time value; or the corresponding strings for the current locale.
    `%S'
    The second as a decimal number.
    `%U'
    The week number of the current year as a decimal number, starting with the first Sunday as the first day of the first week.
    `%W'
    The week number of the current year as a decimal number, starting with the first Monday as the first day of the first week.
    `%w'
    The day of the week as a decimal number, Sunday being `0'.
    `%x'
    The preferred date representation for the current locale, but without the time.
    `%X'
    The preferred time representation for the current locale, but with no date.
    `%y'
    The year as a decimal number, but without a century (in the range `00' to `99').
    `%Y'
    The year as a decimal number, including the century.
    `%Z'
    The time zone or name or abbreviation (empty if the time zone cannot be determined).
    `%%'
    A literal `%' character.

    Example:

    VAR
      c: SysClock.DateTime;
      str: ARRAY 256 OF CHAR;
    
    (* c initialized to Wednesday, 25 Dec 1996, 15:30:00 *)
    
    Calendar.TimeToStr(c, "%A, %D %b %Y, %H:%M:%S", str); 
       => str = "Wednesday, 25 Dec 1996, 15:30:00"
    Calendar.TimeToStr(c, "%a, %d/%m/%y, %H:%M:%S %Z", str); 
       => str = "Wed, 25/12/96, 15:30:00 UTC-0500"
    Calendar.TimeToStr(c, "%A, %D %B %Y, %I:%M:%S %p", str); 
       => str = "Wednesday, 25 December 1996, 03:30:00 PM"
    Calendar.TimeToStr(c, "%b %D, %Y is %A and the %jth day.", str); 
       => str = "Dec 25, 1996 is Wednesday and the 360th day."
    

    Function: StrToTime (VAR c: SysClock.DateTime; dateStr: ARRAY OF CHAR; pattern: ARRAY OF CHAR): BOOLEAN
    This function converts the string dateStr into a calendar c using the format template pattern. Allowable conversion specifiers for pattern the same as in the TimeToStr procedure. However, only date and time components are used in the conversion; any other information, such as the day of the week and the week number, are ignored.

    For names appearing in dateStr, upper and lower-case distinctions are ignored.

    Unspecified time or date components are set to the lower-bound value for that component (after adjustment for the current time zone): For example, incomplete times will assume the zero time for missing time elements; and missing date elements will assume the corresponding date element from the reference date `1 Jan 1970'.

    If dateStr is successfully parsed into a valid calendar date according to the pattern, StrToTime returns TRUE. Otherwise, it returns FALSE.

    Example:

    VAR
      c: SysClock.DateTime;
    
    IF Calendar.StrToTime(c, "Sunday, Oct 12, 1995", "%A, %b %D, %Y") THEN 
       => TRUE, c = Thursday, 12 Oct 1995, 00:00:00
            (* Note that day of week is ignored, 
               and correct value assigned to c *)
    
    IF Calendar.StrToTime(c, "jul 4, 1776", "%b %D, %Y") THEN
       => TRUE, c = Thursday, 4 Jul 1776, 00:00:00
    
    IF Calendar.StrToTime(c, "3:30 pm, 25 December 96", 
                          "%i:%M %p, %D %B %y") THEN
       => TRUE, c = Wednesday, 25 Dec 1996, 15:30:00
    
    IF Calendar.StrToTime(c, "1963 14:15:30", "%Y %H:%M:%S") THEN
       => TRUE, c = Tuesday, 1 Jan 1963, 14:15:30
    
    IF Calendar.StrToTime(c, "05/30/97", "%m/%d/%y") THEN
       => TRUE, c = Friday, 30 May 1997, 00:00:00
    
    IF Calendar.StrToTime(c, "31 Feb 1997", "%D %b %Y") THEN
       => FALSE, c = undefined
    


    Go to the first, previous, next, last section, table of contents. OOCref_toc.html100664 1750 1750 31544 6753666561 11632 0ustar sagsag The OOC Reference Manual - Table of Contents

    The OOC Reference Manual


    This is Edition 0.09 DRAFT, last updated 9 July 1999, of @cite{The OOC Reference Manual}, for Version 1.4.5 or later of oo2c.


    This document was generated on 9 July 1999 using the texi2html translator version 1.51a.