Jelajahi Sumber

Documentation comments writtern to almost all library modules

Arthur Yefimov 2 tahun lalu
induk
melakukan
e99078018f
9 mengubah file dengan 404 tambahan dan 141 penghapusan
  1. 78 21
      src/In.Mod
  2. 12 2
      src/Int.Mod
  3. 45 0
      src/Out.Mod
  4. 11 5
      src/Random.Mod
  5. 13 4
      src/Reals.Mod
  6. 16 18
      src/Strings.Mod
  7. 116 65
      src/TermBox.Mod
  8. 95 25
      src/Texts.Mod
  9. 18 1
      src/Utf8.Mod

+ 78 - 21
src/In.Mod

@@ -1,4 +1,17 @@
 MODULE In;
+(** 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 (but may not always do so on Linux/Unix or Windows).
+
+    Module In as in Oakwood Guidlines for  Oberon-2 Compiler Developers, 1995.
+     With the following changes:
+     LongInt, Int, Int16 also read minus signs first.
+     Char reads a 2-byte character. On Linux it decodes input as UTF-8.
+    On Windows it uses ReadConsoleW WinAPI call if console is attached,
+    otherwise uses ReadFile and decodes input as UTF-8.
+     Open may not rewind.
+    Extra procedures: Line, HugeInt, Int16. *)
 
 (*!FIXME From the Oakwood guidlines:
   An unsuccessful input operation sets Done to FALSE;
@@ -11,20 +24,33 @@ CONST
   ready   = 1; (* readState when nextch is defined and contains next character on current line. *)
   eof     = 2; (* readState when at end of file. *)
 
-  (* Codepages, values of cp *)
+  (** Codepages, values of cp **)
   singleByte = 1;
   utf8       = 2; (*!TODO also add UTF16 *)
 
 TYPE
   SBYTE = BYTE;
-  BYTE* = UBYTE;
+  BYTE* = UBYTE; (** 8-bit unsigned integer, 0..255 *)
 
 VAR
+  (** TRUE after every Open, FALSE after the first error.
+       Done 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. *)
   Done-: BOOLEAN;
-  nextch: CHAR; (* Maintains 1 character read ahaead except at end of line. *)
+
+  nextch: CHAR; (** Maintains 1 character read ahaead except at end of line *)
   readState: INTEGER;
-  cp: INTEGER; (* Input Code Page *)
+  cp: INTEGER; (** Input Code Page *)
+
+(** Initialization **)
 
+(** Open (re)sets the current position to the beginning of the input stream.
+    Done indicates if the operation was successful.
+     Note that on Windows or Linux/Unix rewind may not be possible, also on
+    these OS Open is not strictly required before any other operation. *)
 PROCEDURE Open*;
 VAR error: Platform.ErrorCode;
 BEGIN
@@ -36,6 +62,12 @@ BEGIN
   Done := error = 0
 END Open;
 
+(** Input operations **)
+
+(** The following operations require Done = TRUE and guarantee (Done = TRUE
+    and the result is valid) or (Done = FALSE). All operations except Char
+    skip leading blanks, tabs or end-of-line characters. *)
+
 PROCEDURE GetByte(): INTEGER;
 VAR error: Platform.ErrorCode; x, n: INTEGER;
   m: ARRAY 1 OF SBYTE;
@@ -57,6 +89,7 @@ BEGIN
   END ;
 RETURN ok END GetChar;
 
+(** Puts in `x` the byte at the current position *)
 PROCEDURE Byte*(VAR x: BYTE);
 BEGIN x := SYSTEM.VAL(BYTE, SHORT(SHORT(GetByte())))
 END Byte;
@@ -94,6 +127,9 @@ BEGIN StartRead;
   WHILE (readState = ready) & (nextch <= ' ') DO ReadChar END
 END StartAndSkip;
 
+(** Puts in `ch` the character at the current position. May read 1 to 4 bytes
+    if decoding from UTF-8 (on Linux/Unix and on Windows if input
+    is redirected). *)
 PROCEDURE Char*(VAR ch: CHAR);
 BEGIN StartRead;
   IF readState = ready THEN ch := nextch;
@@ -102,6 +138,8 @@ BEGIN StartRead;
   END
 END Char;
 
+(** Returns 64-bit integer at the current position according to the format:
+     IntConst = [-] (digit {digit} | digit {hexDigit} "H"). *)
 PROCEDURE HugeInt*(VAR h: LONGINT);
 VAR ok, neg, hex, endofnum: BOOLEAN;
   decacc, hexacc, digit: LONGINT;
@@ -143,20 +181,24 @@ BEGIN StartAndSkip;
   IF ~ok THEN Done := FALSE END
 END HugeInt;
 
+(** Returns 16-bit integer in the same way as HugeInt does *)
 PROCEDURE Int16*(VAR i: SHORTINT);
 VAR h: LONGINT;
 BEGIN HugeInt(h); i := SHORT(SHORT(h)) (*!FIXME check range, update Done*)
 END Int16;
 
+(** Returns 32-bit integer in the same way as HugeInt does *)
 PROCEDURE Int*(VAR i: INTEGER); (*32-bit INTEGER alias*)
 VAR h: LONGINT;
 BEGIN HugeInt(h); i := SHORT(h) (*!FIXME check range, update Done*)
 END Int;
 
+(** Alias for Int. Does the same thing *)
 PROCEDURE LongInt*(VAR i: INTEGER);
 BEGIN Int(i)
 END LongInt;
 
+(** Read a line of UTF-8-encoded characters until CR, LF or end of file *)
 PROCEDURE Line*(VAR line: ARRAY OF CHAR);
 VAR i: INTEGER;
 BEGIN StartRead; i := 0;
@@ -170,49 +212,62 @@ BEGIN StartRead; i := 0;
   IF (readState = ready) & (nextch = 0AX) THEN readState := pending END
 END Line;
 
-(** Skip whitespaces, read characters until a whitespace, skip whitespaces
-    until a new line character. *)
+(** Read a word and put it in `s`.
+     Skip whitespaces, read UTF-8-encoded characters until the next whitespace
+    and put the read word in `s`, then skip whitespaces until the next
+    non-whitespace or a new line character. Skip the new line character *)
 PROCEDURE Word*(VAR s: ARRAY OF CHAR);
 VAR i: INTEGER;
 BEGIN StartRead; i := 0;
   IF readState # ready THEN Done := FALSE END;
-  WHILE (readState = ready) & (nextch > ' ') & (i < LEN(s) - 1) DO
-    s[i] := nextch; INC(i); ReadChar
+  WHILE (readState = ready) & (nextch > ' ') DO
+    IF i < LEN(s) - 1 THEN s[i] := nextch; INC(i) ELSE Done := FALSE END;
+    ReadChar
   END;
   s[i] := 0X;
   WHILE (readState = ready) & (nextch <= ' ') & (nextch # 0AX) DO ReadChar END;
   IF (readState = ready) & (nextch = 0AX) THEN readState := pending END
 END Word;
 
+(** Read a string literal and put it in `s`.
+     A string literal is a quoted sequence of characters that may include
+    spaces but not other whitespaces (tabs, new lines etc.). The quotes can
+    be single or double quotes. The string must begin and end with the same
+    quotation marks. *)
 PROCEDURE String*(VAR s: ARRAY OF CHAR);
 VAR i: INTEGER;
+  q: CHAR; (* ' or " *)
 BEGIN StartAndSkip; i := 0;
-  IF (readState = ready) & (nextch = '"') THEN
-    ReadChar;
-    WHILE (readState = ready) & (i < LEN(s) - 1) &
-        (nextch >= ' ') & (nextch # '"') DO
-      s[i] := nextch; ReadChar; INC(i)
+  IF (readState = ready) & ((nextch = '"') OR (nextch = "'")) THEN
+    q := nextch; ReadChar;
+    WHILE (readState = ready) & (nextch >= ' ') & (nextch # q) DO
+      IF i < LEN(s) - 1 THEN s[i] := nextch; INC(i) ELSE Done := FALSE END;
+      ReadChar
+    END;
+    IF (readState = ready) & (nextch = q) THEN ReadChar
+    ELSE Done := FALSE
     END
   END;
-  IF (readState = ready) & (i < LEN(s) - 1) & (nextch = '"') THEN
-    ReadChar; s[i] := 0X
-  ELSE s[0] := 0X; Done := FALSE
-  END
+  s[i] := 0X
 END String;
 
-(** Read a file name *)
-PROCEDURE Name*(VAR name: ARRAY OF CHAR);
+(** Reads the name `s` at the current position according to the file name
+    format of the operating system (e.g. "lib/My.Mod" under Unix).
+    Skips the 0AX in the end (if any). *)
+PROCEDURE Name*(VAR s: ARRAY OF CHAR);
 VAR c: CHAR;
   i: INTEGER;
 BEGIN i := 0; Char(c);
   WHILE c > ' ' DO
-    IF i < LEN(name) - 1 THEN name[i] := c; INC(i) ELSE Done := FALSE END;
+    IF i < LEN(s) - 1 THEN s[i] := c; INC(i) ELSE Done := FALSE END;
     Char(c)
   END;
-  name[i] := 0X;
+  s[i] := 0X;
   IF c = 0AX THEN Char(c) END
 END Name;
 
+(** Reads and puts in `x` a 32-bit real number (REAL) in format:
+      ["-"] digit {digit} [{digit} ["E" ("+" | "-") digit {digit}]]. *)
 PROCEDURE Real*(VAR x: SHORTREAL);
 VAR s: ARRAY 16 OF CHAR;
 BEGIN StartAndSkip; Word(s);
@@ -220,6 +275,8 @@ BEGIN StartAndSkip; Word(s);
   IF ~Reals.Done THEN Done := FALSE END
 END Real;
 
+(** Reads and puts in `x` a 64-bit real number (LONGREAL) in format:
+      ["-"] digit {digit} [{digit} ["E" ("+" | "-") digit {digit}]]. *)
 PROCEDURE LongReal*(VAR x: REAL);
 VAR s: ARRAY 16 OF CHAR;
 BEGIN StartAndSkip; Word(s);

+ 12 - 2
src/Int.Mod

@@ -1,6 +1,8 @@
 MODULE Int;
+(** Module for INTEGER conversion from and to a string *)
 IMPORT Strings;
 
+(** Converts integer `n` to string `s` *)
 PROCEDURE Str*(n: INTEGER; VAR s: ARRAY OF CHAR);
 VAR i, j: INTEGER; tmp: CHAR; neg: BOOLEAN;
 BEGIN
@@ -21,6 +23,9 @@ BEGIN
   END
 END Str;
 
+(** Returns the contents of string `s` converted to an integer. Sets `ok` to
+    TRUE if `s` contains a valid representation of an integer number,
+    otherwise sets `ok` to FALSE and returns 0 *)
 PROCEDURE ValEx*(IN s: ARRAY OF CHAR; VAR ok: BOOLEAN): INTEGER;
 VAR i, n: INTEGER;
   c: CHAR;
@@ -31,19 +36,24 @@ BEGIN n := 0; c := s[0]; ok := FALSE;
     n := n * 10 + ORD(c) - ORD('0');
     INC(i); c := s[i]
   END;
-  IF s[i] # 0X THEN ok := FALSE END;
-  IF neg THEN n := -n END ;
+  IF s[i] # 0X THEN ok := FALSE; n := 0 ELSIF neg THEN n := -n END ;
 RETURN n END ValEx;
 
+(** Returns the contents of string `s` converted to an integer. If `s`
+    does not contain a valid representation of an integer number, returns 0 *)
 PROCEDURE Val*(IN s: ARRAY OF CHAR): INTEGER;
 VAR ok: BOOLEAN;
 BEGIN RETURN ValEx(s, ok) END Val;
 
+(** Inserts a textual representation of integer `n` in position `pos` of
+    string `s` *)
 PROCEDURE Insert*(n: INTEGER; pos: INTEGER; VAR s: ARRAY OF CHAR);
 VAR sn: ARRAY 30 OF CHAR;
 BEGIN Str(n, sn); Strings.Insert(sn, pos, s)
 END Insert;
 
+(** Appends a textual representation of integer `n` to the end of
+    the string `s` *)
 PROCEDURE Append*(n: INTEGER; VAR s: ARRAY OF CHAR);
 VAR sn: ARRAY 30 OF CHAR;
 BEGIN Str(n, sn); Strings.Append(sn, s)

+ 45 - 0
src/Out.Mod

@@ -1,4 +1,9 @@
 MODULE Out;
+(** 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.
+     The output is buffered. The buffer is flushed when and overflow occurres
+    or when Flush or Ln are called. *)
 
 IMPORT SYSTEM, Platform, U := Utf8, Reals;
 
@@ -10,6 +15,7 @@ VAR
   buf: ARRAY 128 OF CHAR;
   in: INTEGER;
 
+(** Flushes the output buffer to the output device *)
 PROCEDURE Flush*;
 VAR error: Platform.ErrorCode;
 BEGIN
@@ -17,10 +23,13 @@ BEGIN
   in := 0
 END Flush;
 
+(** Initializes the output stream.
+     On Windows, Unix and Linux does nothing. *)
 PROCEDURE Open*;
 BEGIN
 END Open;
 
+(** Writes the character `ch` to the end of the output stream *)
 PROCEDURE Char*(ch: CHAR);
 BEGIN
   IF in >= LEN(buf) THEN Flush END;
@@ -33,6 +42,8 @@ VAR n: INTEGER;
 BEGIN n := 0; WHILE (n < LEN(s)) & (s[n] # 0X) DO INC(n) END; RETURN n
 END Length;
 
+(** Writes the null-terminated character sequence `s` to the end of the
+    output stream (without 0X). *)
 PROCEDURE String*(IN s: ARRAY OF CHAR);
 VAR l: INTEGER; error: Platform.ErrorCode;
 BEGIN
@@ -46,6 +57,8 @@ BEGIN
   END
 END String;
 
+(** Writes the null-terminated 1-byte-character sequence `s` encoded in UTF-8
+    to the end of the output stream (without 0X). *)
 PROCEDURE Utf8*(IN s: ARRAY OF SHORTCHAR);
 VAR q: ARRAY 4096 OF CHAR;
   p: POINTER TO ARRAY OF CHAR;
@@ -59,6 +72,10 @@ BEGIN
   END
 END Utf8;
 
+(** Writes the integer number `x` to the end of the output stream.
+     `n` is the minimum amount of characters that should be written. If the
+    textual representation of `x` takes less characters, then space characters
+    are written first. If `n` is 0 or 1, `n` does not do anything. *)
 PROCEDURE Int*(x, n: HUGEINT);
   CONST zero = ORD('0');
   VAR s: ARRAY 22 OF CHAR; i: INTEGER; negative: BOOLEAN;
@@ -80,6 +97,10 @@ BEGIN
   WHILE i > 0 DO DEC(i); Char(s[i]) END
 END Int;
 
+(** Writes `x` as hexadecimal integer to the end of the output stream.
+     `n` is the minimum amount of characters that should be written. If the
+    textual representation of `x` takes less characters, then space characters
+    are written first. If `n` is 0 or 1, `n` does not do anything. *)
 PROCEDURE Hex*(x, n: HUGEINT);
 BEGIN
   IF n < 1 THEN n := 1 ELSIF n > 16 THEN n := 16 END;
@@ -94,25 +115,49 @@ BEGIN
   END
 END Hex;
 
+(** Writes an end-of-line symbol to the end of the output stream.
+     On Linux/Unix it is 0AX. On Windows it is a pair: 0DX, 0AX. *)
 PROCEDURE Ln*;
 BEGIN String(Platform.NewLine); Flush
 END Ln;
 
+(** Writes the real number `x` to the end of the output stream using an
+    exponential form.
+     `n` is the minimum amount of characters that should be written. If the
+    textual representation of `x` takes less characters, then space characters
+    are written first. *)
 PROCEDURE Real*(x: REAL; n: INTEGER);
 VAR s: ARRAY 256 OF CHAR;
 BEGIN Reals.Str(x, n, s); String(s)
 END Real;
 
+(** Writes the long real number `x` to the end of the output stream using an
+    exponential form.
+     `n` is the minimum amount of characters that should be written. If the
+    textual representation of `x` takes less characters, then space characters
+    are written first. *)
 PROCEDURE LongReal*(x: LONGREAL; n: INTEGER);
 VAR s: ARRAY 256 OF CHAR;
 BEGIN Reals.LongStr(x, n, s); String(s)
 END LongReal;
 
+(** Writes the real number `x` to the end of the output stream using an
+    exponential form.
+     `n` is the minimum amount of characters that should be written. If the
+    textual representation of `x` takes less characters, then space characters
+    are written first.
+     `k` is the number of digits after a decimal point.  *)
 PROCEDURE RealFix*(x: REAL; n, k: INTEGER);
 VAR s: ARRAY 256 OF CHAR;
 BEGIN Reals.StrFix(x, n, k, s); String(s)
 END RealFix;
 
+(** Writes the long real number `x` to the end of the output stream using an
+    exponential form.
+     `n` is the minimum amount of characters that should be written. If the
+    textual representation of `x` takes less characters, then space characters
+    are written first.
+     `k` is the number of digits after a decimal point.  *)
 PROCEDURE LongRealFix*(x: LONGREAL; n, k: INTEGER);
 VAR s: ARRAY 256 OF CHAR;
 BEGIN Reals.LongStrFix(x, n, k, s); String(s)

+ 11 - 5
src/Random.Mod

@@ -1,4 +1,6 @@
 MODULE Random;
+(** A simple and fast pseudo-random number generator *)
+
 IMPORT Platform;
 CONST modulo* = 2147483647; (* =2^31-1 *)
 VAR seed*: INTEGER;
@@ -6,8 +8,9 @@ VAR seed*: INTEGER;
 PROCEDURE Time(): INTEGER;
 RETURN Platform.Time() END Time;
 
-(* Set random seed value. Any values are allowed, although
-   values not in [1..2^31-2] will be mapped into this range. *)
+(** Sets the value of the random seed. Any values are allowed, although
+    values that are not in [1..2^31 - 2] range will be mapped into this range.
+     The same random seed results in the same sequence of random numbers *)
 PROCEDURE PutSeed*(newSeed: INTEGER);
 BEGIN newSeed := newSeed MOD modulo;
   IF newSeed = 0 THEN seed := 1 ELSE seed := newSeed END
@@ -23,17 +26,20 @@ BEGIN hi := seed DIV q; lo := seed MOD q;
   IF test > 0 THEN seed := test ELSE seed := test + modulo END
 END NextRND;
 
-(* Calculates a new number. range has to be included in
-   [1..2^31-2]. Result is a number from 0, 1, ... , range-1. *)
+(** Returns a random integer number from 0 to (range - 1).
+     For example, Int(6) may return a number from 0 to 5.
+     `range` must be in range [1; 2^31 - 2]. *)
 PROCEDURE Int*(range: INTEGER): INTEGER;
 BEGIN NextRND
 RETURN seed MOD range END Int;
 
-(* Calculates a number x with 0.0 <= x < 1.0. *)
+(** Returns a random real number x, where 0 <= x < 1. *)
 PROCEDURE Uniform*(): REAL;
 BEGIN NextRND
 RETURN (seed - 1) * (1 / (modulo - 1)) END Uniform;
 
+(** Initializes the randomization process using current time.
+    This procedure is called automatically on module initialization *)
 PROCEDURE Randomize*;
 BEGIN PutSeed(Time())
 END Randomize;

+ 13 - 4
src/Reals.Mod

@@ -1,5 +1,5 @@
 MODULE Reals;
-
+(** Module for REAL and LONGREAL conversion from and to a string *)
 IMPORT SYSTEM;
 
 TYPE
@@ -23,6 +23,7 @@ BEGIN r := 1.0E0; power := 1.0E1;
   RETURN r
 END Ten;
 
+(** Returns a long real number converted from string `s` *)
 PROCEDURE LongVal*(IN s: ARRAY OF CHAR): LONGREAL;
 VAR p, e: INTEGER; y, g: LONGREAL; neg, negE: BOOLEAN;
 BEGIN Done := FALSE;
@@ -62,15 +63,13 @@ BEGIN Done := FALSE;
   END ;
 RETURN y END LongVal;
 
+(** Returns a real number converted from string `s` *)
 PROCEDURE Val*(IN s: ARRAY OF CHAR): REAL;
 VAR y: LONGREAL;
 BEGIN
   RETURN SHORT(LongVal(s))
 END Val;
 
-(****)
-
-
 PROCEDURE digit(n: HUGEINT; VAR s: ARRAY OF CHAR; VAR i: INTEGER);
 BEGIN
   DEC(i); s[i] := SHORT(CHR(n MOD 10 + 48));
@@ -192,10 +191,14 @@ BEGIN si := 0; Done := TRUE;
   s[si] := 0X
 END RealP;
 
+(** Converts real number `x` to string `s`.
+     `n` means the minimum number of charactes (`s` prepended with spaces). *)
 PROCEDURE Str*(x: REAL; n: INTEGER; VAR s: ARRAY OF CHAR);
 BEGIN RealP(x, n, FALSE, s)
 END Str;
 
+(** Converts long real number `x` to string `s`.
+     `n` means the minimum number of charactes (`s` prepended with spaces). *)
 PROCEDURE LongStr*(x: LONGREAL; n: INTEGER; VAR s: ARRAY OF CHAR);
 BEGIN RealP(x, n, TRUE, s)
 END LongStr;
@@ -242,6 +245,9 @@ BEGIN SYSTEM.GET(SYSTEM.ADR(x), i);
   RETURN SHORT(ASH(i, -52) MOD 800H)
 END LongExpo;
 
+(** Converts real number `x` to string `s`.
+     `n` means the minimum number of charactes (`s` prepended with spaces).
+     `k` means the number of digits after a decimal point *)
 PROCEDURE StrFix*(x: REAL; n, k: INTEGER; VAR s: ARRAY OF CHAR);
 CONST maxD = 9;
 VAR e, si, i, minus, p, N: INTEGER; x0: REAL;
@@ -301,6 +307,9 @@ BEGIN Done := TRUE; si := 0; e := Expo(x);
   s[si] := 0X
 END StrFix;
 
+(** Converts long real number `x` to string `s`.
+     `n` means the minimum number of charactes (`s` prepended with spaces).
+     `k` means the number of digits after a decimal point *)
 PROCEDURE LongStrFix*(x: LONGREAL; n, k: INTEGER; VAR s: ARRAY OF CHAR);
 CONST maxD = 20;
 VAR e, si, i, minus, p, N: INTEGER; x0: LONGREAL;

+ 16 - 18
src/Strings.Mod

@@ -2,22 +2,22 @@ MODULE Strings;
 (** 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. *)
+     All positions in strings start at 0. *)
 IMPORT Reals, SYSTEM;
 
 TYPE
   REAL = SYSTEM.REAL32;
   LONGREAL = SYSTEM.REAL64;
 
-(** Returns the number of characters in s up to and excluding the first 0X. *)
+(** Returns the number of characters in `s`
+    up to and excluding the first 0X *)
 PROCEDURE Length*(IN s: ARRAY OF CHAR): INTEGER;
 VAR i: INTEGER;
 BEGIN i := 0; WHILE (i < LEN(s)) & (s[i] # 0X) DO INC(i) END ;
 RETURN i END Length;
 
-(** Appends string s to the end of string dst.
-     Has the same effect as Insert(s, Length(s), dst). *)
+(** Appends string `s` to the end of string `dst`.
+     Has the same effect as Insert(s, Length(s), dst) *)
 PROCEDURE Append*(IN s: ARRAY OF CHAR; VAR dst: ARRAY OF CHAR);
 VAR n1, n2, i: INTEGER;
 BEGIN
@@ -28,13 +28,10 @@ BEGIN
   END
 END Append;
 
-(** Inserts the string src into the string dst at position pos
-    (0 <= pos <= Length(dst)).*)(**
-
+(** 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 Insert*(IN src: ARRAY OF CHAR; pos: INTEGER; VAR dst: ARRAY OF CHAR);
@@ -60,7 +57,7 @@ BEGIN
   IF j >= len THEN dst[len - 1] := 0X END
 END Insert;
 
-(** Deletes n characters from s starting at position pos
+(** 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 Delete*(VAR s: ARRAY OF CHAR; pos, n: INTEGER);
@@ -76,7 +73,7 @@ BEGIN
 END Delete;
 
 (** Has the same effect as Delete(dst, pos, Length(src)) followed by an
-    Insert(src, pos, dst). *)
+    Insert(src, pos, dst) *)
 PROCEDURE Replace*(IN src: ARRAY OF CHAR;
     pos: INTEGER; VAR dst: ARRAY OF CHAR);
 BEGIN
@@ -84,8 +81,8 @@ BEGIN
   Insert(src, pos, dst)
 END Replace;
 
-(** Extracts a substring dst with n characters from position pos
-    (0 <= pos < Length(src)) in src.
+(** 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
     Length(src) - 1.
      If the size of dst is not large enough to hold the result of the
@@ -106,7 +103,7 @@ BEGIN len := Length(src);
   END
 END Extract;
 
-(** Copies src to dst. If there is no space, truncates it with 0X.
+(** Copies `src` to `dst`. If there is no space, truncates it with 0X.
      Has the same effect as Extract(src, 0, LEN(dst), dst) *)
 PROCEDURE Copy*(IN src: ARRAY OF CHAR; VAR dst: ARRAY OF CHAR);
 VAR i, len: INTEGER;
@@ -119,8 +116,8 @@ BEGIN
   dst[i] := 0X
 END Copy;
 
-(** Returns the position of the first occurrence of pat in s after
-    position pos (inclusive).
+(** Returns the position of the first occurrence of `pat` in `s` after
+    position `pos` (inclusive).
      If pat is not found, -1 is returned. *)
 PROCEDURE Pos*(IN pattern, s: ARRAY OF CHAR; pos: INTEGER): INTEGER;
 VAR n1, n2, i, j: INTEGER;
@@ -138,7 +135,8 @@ BEGIN
   RETURN -1
 END Pos;
 
-(** Replaces each lower case latin letter in s by its upper case equivalent. *)
+(** Replaces each lower case latin letter
+    in `s` by its upper case equivalent. *)
 PROCEDURE Cap*(VAR s: ARRAY OF CHAR);
 VAR i: INTEGER;
 BEGIN

+ 116 - 65
src/TermBox.Mod

@@ -1,4 +1,5 @@
 MODULE TermBox;
+(** Termbox is a module for creating cross-platform text-based interfaces *)
 IMPORT G := Graph, Strings, Int, Out, Platform, Kernel;
 
 CONST
@@ -11,29 +12,30 @@ CONST
   stdW = 80;
   stdH = 25;
 
-  (* Settings set members *)
-  fullscreen*  = 1;
-  window*      = 2;
-  exact*       = 3;
-  sharp*       = 4;
-  software*    = 5;
-  noMouse*     = 6;
-  center*      = 7;
-  resizable*   = 8;
-  maximized*   = 9;
-  minimized*   = 10;
-  frameless*   = 11;
-
-  (* Event.type possible values *)
-  noEvent* = 0;
-  quit*    = 1;
-  key*     = 2;
-  mouse*   = 3;
-  resize*  = 11;
-  timer*   = 14;
-  error*   = 15;
-
-  (* Key Codes *)
+  (** Flags for procedure Settings **)
+  (** The flags only work if TermBox works via module Graph *)
+  fullscreen*  =  1; (** Run in fullscreen if possible *)
+  window*      =  2; (** Run in window if possible *)
+  exact*       =  3; (** Use the exact given pixel size *)
+  sharp*       =  4; (** Use integer multitudes of hardware pixels *)
+  software*    =  5; (** Render graphics in software *)
+  noMouse*     =  6; (** Hide mouse pointer *)
+  center*      =  7; (** Center the window *)
+  resizable*   =  8; (** Make window resizable *)
+  maximized*   =  9; (** Maximize window on startup *)
+  minimized*   = 10; (** Minimize window on startup *)
+  frameless*   = 11; (** Hide window frames *)
+
+  (** Event.type possible values **)
+  noEvent* =  0; (** No event occurred (used only internally) *)
+  quit*    =  1; (** User closed the window (works only if Graph is used) *)
+  key*     =  2; (** Key press *)
+  mouse*   =  3; (** Mouse button click, release or drag *)
+  resize*  = 11; (** Terminal window changed its size *)
+  timer*   = 14; (** Tick of the TermBox timer *)
+  error*   = 15; (** Error event *)
+
+  (** Key Codes **)
   kA*          = 1;
   kB*          = 2;
   kC*          = 3;
@@ -151,22 +153,24 @@ CONST
   kNumLock*    = 225;
   kCapsLock*   = 226;
 
-  kMax*        = 226;
-
-  (* Modifiers Set *)
-  mShift*      = 0;
-  mCtrl*       = 1;
-  mAlt*        = 2;
-  mLwin*       = 3;
-  mRwin*       = 4;
-  mMenu*       = 5;
-  mAltGr*      = 6;
-  mCommand*    = 7;
-  mScrolllock* = 8;
-  mNumlock*    = 9;
-  mCapslock*   = 10;
-
-  (* Characters *)
+  kMax*        = 226; (** Maximum key code *)
+
+  (** Key Modifiers Set - Event.mod **)
+  (** The set of modifier keys such as Alt or Ctrl *)
+  mShift*      =  0; (** SHIFT *)
+  mCtrl*       =  1; (** CTRL *)
+  mAlt*        =  2; (** ALT *)
+  mLwin*       =  3; (** Left Windows Key *)
+  mRwin*       =  4; (** Right Windows Key *)
+  mMenu*       =  5; (** Menu Key *)
+  mAltGr*      =  6; (** ALT-Graph (Right ALT) *)
+  mCommand*    =  7; (** Command key (on Mac) *)
+  mScrolllock* =  8; (** Scroll Lock *)
+  mNumlock*    =  9; (** Num Lock *)
+  mCapslock*   = 10; (** Caps Lock *)
+
+  (** Characters **)
+  (** Useful constants for pseudo-graphical box drawing *)
   lineHor*         = 2500X;
   lineVert*        = 2502X;
 
@@ -235,32 +239,32 @@ CONST
   rightHalfBlock* = 2590X;
 
 TYPE
-  Event* = RECORD
-    type*: INTEGER;
-    x*, y*: INTEGER;
-    w*, h*: INTEGER;  (* Size of screen in cells on resize *)
-    button*: INTEGER; (* Mouse button that is pressed, 0 means release *)
-    key*: INTEGER;    (* Physical key code *)
-    ch*: CHAR;        (* Typed character *)
-    mod*: SET         (* Key modifiers *)
+  Event* = RECORD (** Record that holds information on the event occurred *)
+    type*: INTEGER;   (** One of Event.type constants (see above) *)
+    x*, y*: INTEGER;  (** For mouse presses, releases and drags *)
+    w*, h*: INTEGER;  (** Size of screen in cells on resize *)
+    button*: INTEGER; (** Mouse button that is pressed, 0 means release *)
+    key*: INTEGER;    (** Physical key code of the key pressed or released *)
+    ch*: CHAR;        (** The typed character on key press *)
+    mod*: SET         (** Key modifiers set (see above) *)
   END;
 
   Cell = RECORD
     ch, oldCh: CHAR;
     fg, oldFg: INTEGER;
     bg, oldBg: INTEGER;
-    updated: INTEGER (* > 0 means need to redraw, 2 means redraw in any case *)
+    updated: INTEGER (** >0 means need to redraw, 2 means redraw in any case *)
   END;
 
-  Part* = POINTER TO PartDesc; (* Part of screen buffer *)
-  PartDesc* = RECORD
+  Part = POINTER TO PartDesc; (** Part of screen buffer *)
+  PartDesc = RECORD
     cells: ARRAY partH, partW OF Cell;
-    w, h: INTEGER; (* Actually used sizes of array *)
-    redraw: BOOLEAN; (* TRUE if any cell needs to be redrawn *)
+    w, h: INTEGER;   (** Actually used sizes of array *)
+    redraw: BOOLEAN; (** TRUE if any cell needs to be redrawn *)
     down, right: Part
   END;
 
-  Buffer = RECORD (* Screen buffer *)
+  Buffer = RECORD (** Screen buffer *)
     first: Part;
     w, h: INTEGER;
     redrawAll: BOOLEAN
@@ -269,7 +273,7 @@ TYPE
 VAR
   t0, t1: REAL;
 
-  wantTitle: ARRAY 256 OF CHAR; (* Assigned in procedure SetTitle *)
+  wantTitle: ARRAY 256 OF CHAR; (** Assigned in procedure SetTitle *)
   wantZoom: REAL;
   wantW, wantH: INTEGER;
   wantScaleX, wantScaleY: REAL;
@@ -278,22 +282,22 @@ VAR
   iconFile, fontFile: ARRAY 256 OF CHAR;
 
   processingEvent: BOOLEAN;
-  skipEnter: BOOLEAN; (* If TRUE, skip the G.char event with key = enter *)
+  skipEnter: BOOLEAN; (** If TRUE, skip the G.char event with key = enter *)
   mouseDown: BOOLEAN;
   mouseShown: BOOLEAN;
   mouseX, mouseY, mouseButton: INTEGER;
-  curX, curY: INTEGER; (* Text cursor position *)
-  cursorShown: BOOLEAN; (* TRUE if text cursor is show while it is blinking *)
-  cursorTimer: G.Timer; (* Text cursor tick timer *)
-  flipTimer: G.Timer; (* Frame change timer *)
-  userTimer: G.Timer; (* User timer set by StartTimer *)
+  curX, curY: INTEGER; (** Text cursor position *)
+  cursorShown: BOOLEAN; (** TRUE if text cursor is show while it is blinking *)
+  cursorTimer: G.Timer; (** Text cursor tick timer *)
+  flipTimer: G.Timer; (** Frame change timer *)
+  userTimer: G.Timer; (** User timer set by StartTimer *)
 
   needFlip: INTEGER;
   screen: G.Window;
   font: G.MonoFont;
   colors: ARRAY nofcolors OF G.Color;
 
-  Done*: BOOLEAN;
+  Done*: BOOLEAN; (** TRUE on successful initialization, FALSE on error *)
 
 PROCEDURE SetPartCellUpdated(p: Part; VAR cell: Cell);
 BEGIN
@@ -348,6 +352,7 @@ BEGIN
   END
 RETURN p END GetPart;
 
+(** Clears the internal back buffer with foreground `fg` and background `bg` *)
 PROCEDURE ClearTo*(fg, bg: INTEGER);
 VAR x, y: INTEGER;
   l, p: Part;
@@ -365,6 +370,8 @@ BEGIN l := buffer.first;
   END
 END ClearTo;
 
+(** Clears the internal back buffer with a grey foreground and a
+    black background *)
 PROCEDURE Clear*;
 BEGIN ClearTo(7, 0)
 END Clear;
@@ -408,6 +415,8 @@ BEGIN
   END
 END Flip;
 
+(** Synchronizes the internal back buffer with the terminal.
+     Nothing will change on the screen until Flush or Sync is called *)
 PROCEDURE Flush*;
 VAR x, y, X, Y: INTEGER;
   l, p: Part;
@@ -435,6 +444,10 @@ BEGIN
   END
 END Flush;
 
+(** Sync comes handy when something causes desync between TermBox's
+    understanding of a terminal buffer and the reality. Such as a third party
+    process. Sync forces a complete resync between TermBox and the terminal,
+    it may not be visually pretty though. *)
 PROCEDURE Sync*;
 BEGIN
   buffer.redrawAll := TRUE;
@@ -462,14 +475,17 @@ BEGIN
   Sync
 END ToggleFS;
 
+(** Returns TRUE if fullscreen mode is currently used *)
 PROCEDURE IsFS*(): BOOLEAN;
 RETURN ~(G.window IN G.GetWindowOptions(screen))
 END IsFS;
 
+(** Switch to window mode *)
 PROCEDURE SwitchToWindow*;
 BEGIN IF IsFS() THEN ToggleFS END
 END SwitchToWindow;
 
+(** Switch to fullscreen mode *)
 PROCEDURE SwitchToFS*;
 BEGIN IF ~IsFS() THEN ToggleFS END
 END SwitchToFS;
@@ -603,10 +619,14 @@ BEGIN
   END
 RETURN got END PeekAndParseEvent;
 
+(** Waits until the next event, copies it in `event`
+    and removes it from the queue *)
 PROCEDURE WaitEvent*(VAR event: Event);
 BEGIN REPEAT WaitAndParseEvent(event) UNTIL event.type # noEvent
 END WaitEvent;
 
+(** Copies the next event in the queue to `event` but does not remove
+    it from the queue. *)
 PROCEDURE PeekEvent*(VAR event: Event): BOOLEAN;
 VAR got: BOOLEAN;
 BEGIN
@@ -616,6 +636,7 @@ BEGIN
   END
 RETURN got END PeekEvent;
 
+(** Returns TRUE if there are events in the events queue *)
 PROCEDURE HasEvents*(): BOOLEAN;
 VAR e: Event;
   x: BOOLEAN;
@@ -623,6 +644,7 @@ BEGIN
   IF processingEvent THEN x := FALSE ELSE x := PeekEvent(e) END
 RETURN x END HasEvents;
 
+(** Moves the text input cursor to cell (x; y) *)
 PROCEDURE SetCursor*(x, y: INTEGER);
 BEGIN
   IF (x # curX) OR (y # curY) THEN
@@ -638,36 +660,46 @@ BEGIN
   END
 END SetCursor;
 
+(** Hides the text input cursor (moves it off the screen) *)
 PROCEDURE HideCursor*;
 BEGIN SetCursor(-1, -1)
 END HideCursor;
 
+(** Shows the mouse cursor *)
 PROCEDURE ShowMouse*;
 BEGIN IF ~mouseShown THEN mouseShown := TRUE; UpdateCell(mouseX, mouseY) END
 END ShowMouse;
 
+(** Hides the mouse cursor *)
 PROCEDURE HideMouse*;
 BEGIN IF mouseShown THEN mouseShown := FALSE; UpdateCell(mouseX, mouseY) END
 END HideMouse;
 
+(** Sets background color `bg` for the cell at position (x; y) *)
 PROCEDURE SetBg*(x, y, bg: INTEGER);
 VAR p: Part;
 BEGIN p := GetPart(buffer, x, y);
   IF p # NIL THEN SetPartBg(p, x, y, bg) END
 END SetBg;
 
+(** Sets foreground color `fg` for the cell at position (x; y) *)
 PROCEDURE SetFg*(x, y, fg: INTEGER);
 VAR p: Part;
 BEGIN p := GetPart(buffer, x, y);
   IF p # NIL THEN SetPartFg(p, x, y, fg) END
 END SetFg;
 
+(** Fills the cell at (x; y) with character `ch` and the given
+    foreground (fg) and background (bg) colors *)
 PROCEDURE SetCell*(x, y: INTEGER; ch: CHAR; fg, bg: INTEGER);
 VAR p: Part;
 BEGIN p := GetPart(buffer, x, y);
   IF p # NIL THEN SetPartCell(p, x, y, ch, fg, bg) END
 END SetCell;
 
+(** Fill a rectangular area of characters with `ch` using the foreground (fg)
+    and background (bg) colors. The top-left corner of the area is (x; y),
+    width is `w` and height is `h` *)
 PROCEDURE Fill*(x, y, w, h: INTEGER; ch: CHAR; fg, bg: INTEGER);
 VAR X, Y: INTEGER;
 BEGIN
@@ -678,6 +710,9 @@ BEGIN
   END
 END Fill;
 
+(** Writes at most `limit` characters of `s` in a line starting at position
+    (x; y) on to the terminal using the given foreground (fg) and
+    background (bg) colors *)
 PROCEDURE Print*(x, y, limit: INTEGER; s: ARRAY OF CHAR; fg, bg: INTEGER);
 VAR i, w, h: INTEGER;
 BEGIN i := 0;
@@ -686,16 +721,20 @@ BEGIN i := 0;
   END
 END Print;
 
+(** Sets the character of the cell at (x; y) *)
 PROCEDURE SetChar*(x, y: INTEGER; ch: CHAR);
 VAR p: Part;
 BEGIN p := GetPart(buffer, x, y);
   IF p # NIL THEN SetPartChar(p, x, y, ch) END
 END SetChar;
 
+(** Returns size of the terminal window in characters *)
 PROCEDURE Size*(VAR width, height: INTEGER);
 BEGIN width := buffer.w; height := buffer.h
 END Size;
 
+(** Given the (x; y) coordinate, returns data of the
+    corresponding terminal cell *)
 PROCEDURE GetCell*(x, y: INTEGER; VAR ch: CHAR; VAR fg, bg: INTEGER);
 VAR p: Part;
   cell: Cell;
@@ -706,10 +745,12 @@ BEGIN p := GetPart(buffer, x, y);
   END
 END GetCell;
 
+(** Delay for `ms` milliseconds *)
 PROCEDURE Delay*(ms: INTEGER);
 BEGIN G.Delay(ms)
 END Delay;
 
+(** Closes TermBox *)
 PROCEDURE Close*;
 BEGIN
   font := NIL;
@@ -760,18 +801,24 @@ BEGIN
   END;
 END InitColors;
 
+(** Sets the title of the window *)
 PROCEDURE SetTitle*(title: ARRAY OF CHAR);
 BEGIN wantTitle := title
 END SetTitle;
 
+(** Sets zoom as a real number. *)
 PROCEDURE SetZoomF*(zoom: REAL);
 BEGIN wantZoom := zoom; G.SetZoomF(zoom)
 END SetZoomF;
 
+(** Sets zoom as an integer.
+     SetZoom(2) will make virtual pixels two times bigger in size *)
 PROCEDURE SetZoom*(zoom: INTEGER);
 BEGIN wantZoom := FLT(zoom); G.SetZoom(zoom)
 END SetZoom;
 
+(** Sets horizontal (x) and vertical (y) scale factors.
+     Call SetScale(2.0, 1.0) to two make pixels times wider *)
 PROCEDURE SetScale*(x, y: REAL);
 BEGIN wantScaleX := x; wantScaleY := y; G.SetScale(x, y)
 END SetScale;
@@ -801,6 +848,7 @@ BEGIN
   IF b # NIL THEN G.SetWindowIcon(screen, b) END
 END InitIcon;
 
+(** Returns Graph.Window object of the terminal (only when Graph is used) *)
 PROCEDURE GetWindow*(): G.Window;
 RETURN screen END GetWindow;
 
@@ -823,6 +871,9 @@ BEGIN G.GetDesktopResolution(dw, dh);
   InitIcon
 END InitScreen;
 
+(** Start TermBox timer. The timer event will be created every `speed`
+    fraction of a second.
+     Call StartTimer(1/30) for 30 timer events every second *)
 PROCEDURE StartTimer*(speed: REAL);
 BEGIN
   userTimer := G.NewTimer(speed);
@@ -839,6 +890,7 @@ BEGIN
   G.StartTimer(flipTimer)
 END InitTimers;
 
+(** Initializes TermBox. Sets Done to TRUE on success, FALSE otherwise *)
 PROCEDURE Init*;
 VAR opt: SET;
 BEGIN Done := FALSE;
@@ -863,6 +915,7 @@ BEGIN Done := FALSE;
   END
 END Init;
 
+(** Sets width and height of graphical window and settings flags (for Graph) *)
 PROCEDURE Settings*(w, h: INTEGER; flags: SET);
 BEGIN
   IF w = 0 THEN wantW := stdW ELSE wantW := w END;
@@ -873,14 +926,12 @@ BEGIN
   settings := flags
 END Settings;
 
-PROCEDURE TESTCB*(VAR s: ARRAY OF CHAR);
-BEGIN G.GetClipboardText(screen, s)
-END TESTCB;
-
+(** Sets the terminal icon (if Graph is used) *)
 PROCEDURE SetIcon*(s: ARRAY OF CHAR);
 BEGIN iconFile := s
 END SetIcon;
 
+(** Sets the font file for the terminal (if Graph is used) *)
 PROCEDURE SetFontFile*(s: ARRAY OF CHAR);
 BEGIN fontFile := s
 END SetFontFile;

+ 95 - 25
src/Texts.Mod

@@ -1,17 +1,20 @@
 MODULE Texts; (*JG 21.11.90 / NW 11.7.90 / 24.12.95 / 22.11.10 / 18.11.2014 / 10.1.2019 / AE 05.02.2022*)
+(** Module for reading and writing text files *)
 IMPORT Files, IntToStr := Int, Platform, SYSTEM;
 
 CONST
-  (* Scanner class values *)
-  Inval*  = 0; (* Invalid symbol *)
-  Name*   = 1; (* Name (identifier) s (length len) *)
-  String* = 2; (* Literal string s (length len) *)
-  Int*    = 3; (* Integer i (decimal or hexadecimal) *)
-  Real*   = 4; (* Real number x *)
-  Char*   = 6; (* Special character c *)
-
-  replace* = 0; insert* = 1; delete* = 2; unmark* = 3; (* Op-codes *)
-
+  (** Scanner.class values **)
+  Inval*  = 0; (** Invalid symbol *)
+  Name*   = 1; (** Name (identifier) s (length len) *)
+  String* = 2; (** Literal string s (length len) *)
+  Int*    = 3; (** Integer i (decimal or hexadecimal) *)
+  Real*   = 4; (** Real number x *)
+  Char*   = 6; (** Special character c *)
+
+  (** Op-codes **)
+  replace* = 0; insert* = 1; delete* = 2; unmark* = 3;
+
+  (** - **)
   CR = 0DX; LF = 0AX;
   isWindows = Platform.Windows;
 
@@ -24,43 +27,54 @@ TYPE
     prev, next: Piece
   END;
 
+  (** Text object *)
   Text* = POINTER TO TextDesc;
   TextDesc* = RECORD
-    len*: INTEGER;
-    changed*: BOOLEAN;
+    len*: INTEGER; (** Length of the text file in bytes (not characters!)  *)
+    changed*: BOOLEAN; (** TRUE if the text has been changed *)
     trailer: Piece;
-    pce: Piece;  (* Cache *)
-    org: INTEGER (* Cache *)
+    pce: Piece;  (** Cache *)
+    org: INTEGER (** Cache *)
   END;
 
+  (** A rider on a text object to read it one character at a time *)
   Reader* = RECORD
-    eot*: BOOLEAN;
-    col*: INTEGER;
+    eot*: BOOLEAN; (** TRUE if end of text has been reached *)
+    col*: INTEGER; (** Color. Not used *)
     ref: Piece;
     org: INTEGER;
     off: INTEGER;
     rider: Files.Rider
   END;
 
+  (** A rider on a text object to read and parse (scan) it in small pieces *)
   Scanner* = RECORD(Reader)
-    nextCh*: CHAR;
-    line*, class*: INTEGER;
-    i*: INTEGER;
-    x*: REAL;
-    c*: CHAR;
-    len*: INTEGER;
-    s*: ARRAY 1900 OF CHAR
+    nextCh*: CHAR; (** A read-ahead character value *)
+    line*: INTEGER; (** Current line number *)
+    class*: INTEGER; (** One of the scanner class constants (see above) *)
+    i*: INTEGER; (** If class = Int, i = the value of the scanned integer *)
+    x*: REAL; (** If class = Real, x = the value of the scanned real number *)
+    c*: CHAR; (** If class = Char, c = the value of the scanned character *)
+    len*: INTEGER; (** If class = String, len holds the string length *)
+    s*: ARRAY 1900 OF CHAR (** If class = String, s holds the string *)
   END;
 
+  (** Buffer of a piece of text
+       The idea is to write a piece of text first into a Buffer, and
+      thereafter insert or append it to a Text. This is done for reasons of
+      efficiency, because the possibly needed rendering of the text, for
+      example on a display, can be done once upon insertion of the buffered
+      piece of text rather than after generating each character *)
   Buffer* = POINTER TO BufDesc;
   BufDesc* = RECORD
     len*: INTEGER;
     header, last: Piece
   END;
 
+  (** An obeject that is used to write a piece of text in a Buffer *)
   Writer* = RECORD
-    buf*: Buffer;
-    col: INTEGER; (* Color !FIXME CURRENTLY NOT USED *)
+    buf*: Buffer; (** The Writer's internal buffer *)
+    col*: INTEGER; (** Color. Not used *)
     rider: Files.Rider
   END;
 
@@ -73,6 +87,7 @@ VAR Q: Piece;
 BEGIN NEW(Q); Q.f := TrailerFile; Q.off := -1; Q.len := 1; Q.col := -1
 RETURN Q END Trailer;
 
+(** Loads text `T` from file via rider `r` attached to the file *)
 PROCEDURE Load*(VAR R: Files.Rider; T: Text);
 VAR Q, q: Piece;
   f: Files.File;
@@ -85,6 +100,9 @@ BEGIN f := Files.Base(R); Q := Trailer();
   T.trailer := Q; T.len := q.len
 END Load;
 
+(** Initialize Text `T`.
+     If `name` is non-empty, open file with name `name` and load it in `T`.
+     If `name` is an empty string, create a new empty Text *)
 PROCEDURE Open*(T: Text; name: ARRAY OF CHAR);
 VAR f: Files.File; R: Files.Rider; Q, q: Piece;
   len: INTEGER;
@@ -101,6 +119,7 @@ BEGIN f := Files.Old(name);
   T.changed := FALSE; T.org := -1; T.pce := T.trailer (* Init cache *)
 END Open;
 
+(** Write text `T` into a file via rider `r` attached to the file *)
 PROCEDURE Store*(VAR W: Files.Rider; T: Text);
 VAR p: Piece;
   R: Files.Rider;
@@ -115,6 +134,7 @@ BEGIN p := T.trailer.next;
   T.changed := FALSE
 END Store;
 
+(** Store text `T` on a storage medium as a file with the given `name` *)
 PROCEDURE Close*(T: Text; name: ARRAY OF CHAR);
 VAR f: Files.File; w: Files.Rider;
 BEGIN f := Files.New(name); Files.Set(w, f, 0);
@@ -123,6 +143,7 @@ END Close;
 
 (* -------------------- Editing ----------------------- *)
 
+(** Initialize buffer `B` as an empty buffer *)
 PROCEDURE OpenBuf*(B: Buffer);
 BEGIN NEW(B.header); (* Null piece *)
   B.last := B.header; B.len := 0
@@ -156,6 +177,8 @@ BEGIN
   END
 END SplitPiece;
 
+(** Saves piece of text `T` from `beg` (inclusive) to `end` (exclusive) to
+    buffer `B`. The previous content of `B` is deleted *)
 PROCEDURE Save*(T: Text; beg, end: INTEGER; B: Buffer);
 VAR p, q, qb, qe: Piece; org: INTEGER;
 BEGIN
@@ -174,6 +197,8 @@ BEGIN
   B.len := B.len + (end - beg)
 END Save;
 
+(** Copies the contents of the source buffer `SB` to the
+    destination buffer `DB` *)
 PROCEDURE Copy*(SB, DB: Buffer);
 VAR Q, q, p: Piece;
 BEGIN p := SB.header; Q := DB.last;
@@ -183,6 +208,7 @@ BEGIN p := SB.header; Q := DB.last;
   DB.last := Q; DB.len := DB.len + SB.len
 END Copy;
 
+(** Inserts the contents of buffer `B` into text `T` at position `pos` *)
 PROCEDURE Insert*(T: Text; pos: INTEGER; B: Buffer);
 VAR pl, pr, p, qb, qe: Piece; org, end: INTEGER;
 BEGIN
@@ -201,10 +227,14 @@ BEGIN
   T.changed := TRUE
 END Insert;
 
+(** Appends the contents of buffer `B` into the end of text `T` *)
 PROCEDURE Append*(T: Text; B: Buffer);
 BEGIN Insert(T, T.len, B)
 END Append;
 
+(** Copies a piece of text `T` from position `beg` (inclusive) to
+    position `end` (exclusive) to buffer `B` and deletes this piece
+    from text `T`. The previous content of `B` is deleted *)
 PROCEDURE Delete*(T: Text; beg, end: INTEGER; B: Buffer);
 VAR pb, pe, pbr, per: Piece; orgb, orge: INTEGER;
 BEGIN
@@ -222,6 +252,8 @@ BEGIN
   T.changed := TRUE
 END Delete;
 
+(** Changes the color of the piece of `T` at [bef; end) to `col`.
+     Does not work *)
 PROCEDURE ChangeColor*(T: Text; beg, end: INTEGER; col: INTEGER); (*!FIXME does nothing*)
 VAR pb, pe, p: Piece; org: INTEGER;
 BEGIN
@@ -232,6 +264,7 @@ BEGIN
   T.changed := TRUE
 END ChangeColor;
 
+(** Puts in `col` the color of a character in `T` at position `pos` *)
 PROCEDURE GetColor*(T: Text; pos: INTEGER; VAR col: INTEGER);
 VAR p: Piece; org: INTEGER;
 BEGIN FindPiece(T, pos, org, p); col := p.col
@@ -239,6 +272,7 @@ END GetColor;
 
 (* ------------------ Access: Readers ------------------------- *)
 
+(** Initializes Reader `R` by setting it to position `pos` of text `T` *)
 PROCEDURE OpenReader*(VAR R: Reader; T: Text; pos: INTEGER);
 VAR p: Piece; org: INTEGER;
 BEGIN FindPiece(T, pos, org, p);
@@ -246,6 +280,9 @@ BEGIN FindPiece(T, pos, org, p);
   Files.Set(R.rider, p.f, p.off + R.off); R.eot := FALSE
 END OpenReader;
 
+(** Reads a character fro the text attached the reader `R` and puts it in `ch`.
+    Reader `R` is advanced (moved forward) by 1-4 bytes, because the
+    encoding is UTF-8. *)
 PROCEDURE Read*(VAR R: Reader; VAR ch: CHAR);
 BEGIN Files.ReadChar(R.rider, ch);
   R.col := R.ref.col;
@@ -257,11 +294,13 @@ BEGIN Files.ReadChar(R.rider, ch);
   END
 END Read;
 
+(** Returns the current position of `R` in bytes (not characters!) *)
 PROCEDURE Pos*(VAR R: Reader): INTEGER;
 RETURN R.org + R.off END Pos;  
 
 (* ------------------ Access: Scanners (NW) ------------------------- *)
 
+(** Initializes Scanner `S` by setting it to position `pos` of text `T` *)
 PROCEDURE OpenScanner*(VAR S: Scanner; T: Text; pos: INTEGER);
 BEGIN OpenReader(S, T, pos); S.line := 0; S.nextCh := ' '
 END OpenScanner;
@@ -279,6 +318,18 @@ BEGIN t := 1.0; p := 10.0; (* Compute 10^n *)
   END
 RETURN t END Ten;
 
+(** Scans the text attached to `S` and reads whatever is in the text. Stores
+    the scanned value in `S`. S.class is set to one of the possbile constants
+    (see above).
+     The options are: an integer (Int), a real value (Real), a string in
+    quotes (String), a sequence of non-space characters (Name), a single
+    (otherwise unrecognized) character (Char) or an invalid value (Inval, also
+    means end of text).
+     The integer result is stored in S.i, real -- in S.x, character -- in S.c,
+    string -- in S.s (the string) and S.len (the length of the string).
+     The line number in S.line is the line number of the next character that
+    is always held in a S.nextCh.
+     Call OpenScanner, then Scan, then check the value of S.class *)
 PROCEDURE Scan*(VAR S: Scanner);
 CONST maxExp = 38; maxM = 16777216; (* 2^24 *)
 VAR ch, quot: CHAR;
@@ -357,15 +408,19 @@ END Scan;
 
 (* --------------- Access: Writers (NW) ------------------ *)
 
+(** Initializes Writer `W` by setting it to position `pos` of text `T` *)
 PROCEDURE OpenWriter*(VAR W: Writer);
 BEGIN NEW(W.buf); OpenBuf(W.buf); W.col := 0;
   Files.Set(W.rider, Files.New(''), 0)
 END OpenWriter;
 
+(** Sets the color of the Writer.
+     Does not work *)
 PROCEDURE SetColor*(VAR W: Writer; col: INTEGER);
 BEGIN W.col := col
 END SetColor;
 
+(** Writes character `ch` into the internal buffer of Writer `W` *)
 PROCEDURE Write*(VAR W: Writer; ch: CHAR);
 VAR p: Piece;
 BEGIN
@@ -380,16 +435,22 @@ BEGIN
   INC(W.buf.last.len); INC(W.buf.len)
 END Write;
 
+(** Writes next line character (or CRLF pair on Windows) into the internal
+    buffer of Writer `W` *)
 PROCEDURE WriteLn*(VAR W: Writer);
 BEGIN IF isWindows THEN Write(W, CR) END; Write(W, LF)
 END WriteLn;
 
+(** Writes string `s` into the internal buffer of Writer `W` *)
 PROCEDURE WriteString*(VAR W: Writer; s: ARRAY OF CHAR);
 VAR i: INTEGER;
 BEGIN i := 0;
   WHILE s[i] # 0X DO Write(W, s[i]); INC(i) END
 END WriteString;
 
+(** Writes integer `x` into the internal buffer of Writer `W`.
+     `n` means the minimum number of characters to write
+    (the number gets prefixed with spaces) *)
 PROCEDURE WriteInt*(VAR W: Writer; x, n: INTEGER);
 VAR i: INTEGER; x0: INTEGER;
   a: ARRAY 10 OF CHAR;
@@ -405,6 +466,8 @@ BEGIN
   END
 END WriteInt;
 
+(** Writes `x` as a hexadecimal integer into the internal
+    buffer of Writer `W`. *)
 PROCEDURE WriteHex*(VAR W: Writer; x: INTEGER);
 VAR i: INTEGER; y: INTEGER;
   a: ARRAY 10 OF CHAR;
@@ -416,6 +479,9 @@ BEGIN i := 0; Write(W, ' ');
   REPEAT DEC(i); Write(W, a[i]) UNTIL i = 0
 END WriteHex;
 
+(** Writes real number `x` into the internal buffer of Writer `W`.
+     `n` means the minimum number of characters to write
+    (the number gets prefixed with spaces) *)
 PROCEDURE WriteReal*(VAR W: Writer; x: REAL; n: INTEGER);
 VAR e, i, k, m: INTEGER;
   d: ARRAY 16 OF CHAR;
@@ -446,6 +512,10 @@ BEGIN e := ASR(SYSTEM.VAL(INTEGER, x), 23) MOD 100H; (* Binary exponent *)
   END
 END WriteReal;
 
+(** Writes real number `x` into the internal buffer of Writer `W`.
+     `n` means the minimum number of characters to write
+    (the number gets prefixed with spaces)
+     `k` means the number of digits after a decimal point *)
 PROCEDURE WriteRealFix*(VAR W: Writer; x: REAL; n, k: INTEGER);
 VAR i, m: INTEGER; neg: BOOLEAN;
   d: ARRAY 12 OF CHAR;

+ 18 - 1
src/Utf8.Mod

@@ -1,12 +1,14 @@
 MODULE Utf8;
+(** Module for UTF-8 manipulation, encoding and decoding *)
 
 TYPE
   CHAR8 = SHORTCHAR;
   SHORTCHAR* = CHAR8;
 
 VAR
-  Done-: BOOLEAN;
+  Done-: BOOLEAN; (** TRUE on successful operation, FALSE on error *)
 
+(** Convert UTF-8 string `in` to a UTF-16 string `out` *)
 PROCEDURE Decode*(IN in: ARRAY OF SHORTCHAR; OUT out: ARRAY OF CHAR);
 VAR i, j, val, lim: INTEGER; c: SHORTCHAR;
 BEGIN Done := TRUE; c := in[0]; i := 1; j := 0; lim := LEN(out) - 1;
@@ -31,6 +33,10 @@ BEGIN Done := TRUE; c := in[0]; i := 1; j := 0; lim := LEN(out) - 1;
   IF c # 0X THEN Done := FALSE END
 END Decode;
 
+(** Converts at most `inLen` first characters of UTF-16 string `in` to a
+    UTF-8 string `out` and sets `outLen` to the number of parsed UTF-16
+    characters.
+     Done is set to TRUE on success and FALSE in case of an error *)
 PROCEDURE EncodeEx*(IN in: ARRAY OF CHAR; inLen: INTEGER;
     OUT out: ARRAY OF SHORTCHAR; OUT outLen: INTEGER);
 VAR i, j, val, lim: INTEGER;
@@ -54,11 +60,15 @@ BEGIN Done := TRUE; i := 0; j := 0; lim := LEN(out) - 1;
   IF (i # inLen) & (in[i] # 0X) THEN Done := FALSE END
 END EncodeEx;
 
+(** Converts UTF-16A string `in` to a UTF-8 string `out`.
+     Done is set to TRUE on success and FALSE in case of an error *)
 PROCEDURE Encode*(IN in: ARRAY OF CHAR; OUT out: ARRAY OF SHORTCHAR);
 VAR n: INTEGER;
 BEGIN EncodeEx(in, -1, out, n)
 END Encode;
 
+(** Converts the first UTF-8-encoded character from `s` to an UTF-16
+    character and returns it *)
 PROCEDURE DecodeChar*(IN s: ARRAY OF (*!FIXME SHORT?*)CHAR): CHAR;
 VAR i, x, c: INTEGER;
 BEGIN c := ORD(s[0]);
@@ -74,17 +84,24 @@ BEGIN c := ORD(s[0]);
   END ;
 RETURN CHR(c) END DecodeChar;
 
+(** Converts a single UTF-16 character `c` to an UTF-8 string `s` and
+    puts in `len` the number of generated bytes *)
 PROCEDURE EncodeChar*(c: CHAR; OUT s: ARRAY OF SHORTCHAR; OUT len: INTEGER);
 VAR q: ARRAY 1 OF CHAR;
 BEGIN q[0] := c; EncodeEx(q, 1, s, len)
 END EncodeChar;
 
+(** Returns a SHORTCHAR character value with the given ordinal value.
+     This is essentially CHR(n) if it would return a SHORTCHAR *)
 PROCEDURE ShortChr*(n: INTEGER): SHORTCHAR;
 BEGIN RETURN SHORT(CHR(n)) END ShortChr;
 
+(** Converts a CHAR value `c` to a SHORTCHAR value (may truncate it)
+    and returns it *)
 PROCEDURE Short*(c: CHAR): SHORTCHAR;
 BEGIN RETURN SHORT(c) END Short;
 
+(** Converts a SHORTCHAR value `c` to a CHAR value and returns it *)
 PROCEDURE Long*(c: SHORTCHAR): CHAR;
 BEGIN RETURN LONG(c) END Long;