17.9 A Closer Look at Whole Number I/O

To date, this text has been concerned with ISO standard I/O only on the top level. For instance, the modules SWholeIO (and WholeIO) have been freely used, but little attention has been paid to the layer below these high level modules. The purpose of this section is to examine more closely what goes on in the process of reading and writing numeric data.

For instance, in order to output a CARDINAL value, the internal representation must first be changed into a string of characters. Once this is complete, the string may simply be passed to TextIO for output to the screen.

Likewise, for a CARDINAL to be read into memory, characters must be read and processed, interpreting the string of characters as a number and then constructing the numeric value in memory.

In ISO Modula-2 these conversions are handled in two levels of modules. The module WholeConv (and others like it for real and longreal types) scan input strings to determine if they can legitimately be regarded as CARDINALs, INTEGERs, REALs, or LONGREALs (as the case may be.) The module WholeStr (and others like it for Real and Long types) handles the actual conversions from numeric to string and vice-versa.

In addition, there are some modules that provide common information to the conversion routines in the form of constants they all use, and in the form of routines designed to classify characters as numeric, alphabetic, control, or white space.

To illustrate this activity, and a technique employed by the standard library that has not as yet been used in this text, the following subsections detail the modules WholeConv and WholeStr. The corresponding modules for the real types are similar though somewhat more complicated because there are several output forms in use (fixed, floating, and engineering.) These will not be detailed here.

17.9.1 Common Conversion Information Modules

The first of these provides two enumeration types and one procedure type that all the xxConv modules use when they scan input to check its validity.

DEFINITION MODULE ConvTypes;

  (* Common types used in the string conversion modules *)

TYPE
  ConvResults =     (* Values of this type are used to express the format of a string *)
  ( strAllRight,    (* the string format is correct for the corresponding conversion *)
    strOutOfRange,  (* the string is well-formed but the value cannot be represented *)
    strWrongFormat, (* the string is in the wrong format for the conversion *)
    strEmpty        (* the given string is empty *) );

  ScanClass =  (* Values of this type are used to classify input to finite state scanners *)
  ( padding,   (* a leading or padding character at this point in the scan - ignore it *)
    valid,     (* a valid character at this point in the scan - accept it *)
    invalid,   (* an invalid character at this point in the scan - reject it *)
    terminator (* a terminating character at this point in the scan (not part of token) *) );
	
  ScanState =  (* The type of lexical scanning control procedures *)
  PROCEDURE (CHAR, VAR ScanClass, VAR ScanState); 

END ConvTypes.

Because only types are defined here, the implementation part of this module is empty. The values of the type ConvResults are for reporting the results of the scan of a string. If, for example the maximum CARDINAL value that can be stored were 10000, and the string "100000" were passed to the scanner checking for cardinal values, it should report the value strOutOfRange. If the string "-M123" were passed to a scanner expecting an integer, it would correctly parse the sign at the beginning, but would then expect a digit. Not finding one, it would return the value strWrongFormat.

The values of the type ScanClass are for the purpose of classifying characters in the string being scanned. For instance, spaces at the beginning are padding and can be ignored. After the padding has all been scanned, subsequent characters are either valid or invalid, depending on what was expected at that point in the scan. A determination that the scan of the string is finished is eventually made, and the character scanned to decide this is called the terminating character. In many cases, this is a space. However, when scanning a numeric string, it could be a letter.

The procedure type ScanState provides a standard type for scanning procedures. Each one will take a character to scan and produce a classification of the character. Moreover, the correct procedure to scan the next character will be returned.

At any given point in the string, the scanner is in a particular state. If one is scanning for integer values for instance and presents the string " -234" the scanner will first be in a starting state where it expects padding (skip and stay in the same state) or a sign or digit (read, store and go to a digit reading state). Once a sign or a digit has been read, the scanner is in a digit reading state where it expects either a digit or a terminating character. There is a different procedure for each state, but one procedure variable can be used for the current one, and the procedure can set the next state through the variable parameter before exiting each time. The entire scanning machine (including all its procedures) has only a few states, and this idea is captured in the definition below. For more specific details on the operation of such a machine, study the WholeConv module below.

A routine that operates at any given time in one of finitely many states, at least one of which is a terminal state, is called a finite state machine.

Much more can be said about finite state machines, but such remarks are beyond the scope of this course. The reader is encouraged to further study of the theory of such computing machines as Turing machines and finite state machines.

The second module that is used in common by all the conversion modules is CharClass. This provides a general classification of characters that can be useful in a variety of contexts, not just the one here. Its definition is:

DEFINITION MODULE CharClass;

  (* Classification of values of the type CHAR *)

PROCEDURE IsNumeric (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch is classified as a numeric character *)

PROCEDURE IsLetter (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch is classified as a letter *)

PROCEDURE IsUpper (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch is classified as an upper case letter *)

PROCEDURE IsLower (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch is classified as a lower case letter *)

PROCEDURE IsControl (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch represents a control function *)

PROCEDURE IsWhiteSpace (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch represents a space character or a format effector *)

END CharClass.

If the ISO/IEEE character set for the Latin alphabet is employed, an implementation could be done as follows:

IMPLEMENTATION MODULE CharClass;

(* =========================================
            Definition Module from
                  ISO Modula-2
Draft Standard CD10515 by JTC1/SC22/WG13
    Language and Module designs © 1992 by
BSI, D.J. Andrews, B.J. Cornelius, R. B. Henry
R. Sutcliffe, D.P. Ward, and M. Woodman

          Implementation © 1993
                by R. Sutcliffe
       (Portions coded by G. Tischer)
        Trinity Western University
7600 Glover Rd., Langley, BC Canada V3A 6H4
         e-mail: rsutc@twu.ca
    Last modification date 1993 10 20
=========================================== *)

  (* Classification of values of the type CHAR *)

PROCEDURE IsNumeric (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch is classified as a numeric character *)
BEGIN
  RETURN (ch > 57C) AND (ch < 72C);
END IsNumeric;

PROCEDURE IsLetter (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch is classified as a letter *)
BEGIN
  RETURN ((ch > 100C) AND (ch < 133C)) OR ((ch > 140C) AND (ch < 173C));
END IsLetter;

PROCEDURE IsUpper (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch is classified as an upper case letter *)
BEGIN
  RETURN (ch > 100C) AND (ch < 133C);
END IsUpper;

PROCEDURE IsLower (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch is classified as a lower case letter *)
BEGIN
  RETURN (ch > 140C) AND (ch < 173C);
END IsLower;

PROCEDURE IsControl (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch represents a control function *)
BEGIN
  RETURN (ch > 0C) AND (ch < 40C);
END IsControl;

PROCEDURE IsWhiteSpace (ch: CHAR): BOOLEAN;
  (* Returns TRUE if and only if ch represents a space character or a format
effector *)
BEGIN
  RETURN (ch = 11C) OR (ch = 15C) OR (ch = 40C);
END IsWhiteSpace;

END CharClass.

17.9.2 Scanning For Whole Number Input

The module WholeConv (and corresponding ones for real and longreal types) is employed for this purpose. Its definition is as follows:

DEFINITION MODULE WholeConv;

  (* Low-level whole-number/string conversions *)

IMPORT
  ConvTypes;

TYPE
  ConvResults = ConvTypes.ConvResults; (* strAllRight, strOutOfRange,
strWrongFormat, strEmpty *)

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. *)

PROCEDURE FormatInt (str: ARRAY OF CHAR): ConvResults;
  (* Returns the format of the string value for conversion to INTEGER. *)

PROCEDURE ValueInt (str: ARRAY OF CHAR): INTEGER;
(* Returns the value corresponding to the signed whole number string value str if str is well-formed; otherwise raises the WholeConv exception. *)

PROCEDURE LengthInt (int: INTEGER): CARDINAL;
 (* Returns the number of characters in the string representation of int. *)

PROCEDURE ScanCard (inputCh: CHAR; VAR chClass: ConvTypes.ScanClass;
                    VAR nextState: ConvTypes.ScanState);
  (* Represents the start state of a finite state scanner for unsigned whole numbers -  assigns class of inputCh to chClass and a procedure representing the next state to nextState. *)

PROCEDURE FormatCard (str: ARRAY OF CHAR): ConvResults;
  (* Returns the format of the string value for conversion to CARDINAL. *)

PROCEDURE ValueCard (str: ARRAY OF CHAR): CARDINAL;
  (* Returns the value corresponding to the unsigned whole number string value str if str is well-formed; otherwise raises the WholeConv exception *)

PROCEDURE LengthCard (card: CARDINAL): CARDINAL;
  (* Returns the number of characters in the string representation of card. *)

PROCEDURE IsWholeConvException (): BOOLEAN;
  (* Returns TRUE if the current coroutine is in the exceptional execution state because of the raising of an exception in a routine from this module; otherwise returns FALSE. *)

END WholeConv.

In a manner similar to the way in which device modules import and re-export the channel constants, these modules import and re-export the type ConvResults. Notice that there is a starting state (procedure) for scanning for an integer, and another one for starting the scan of a cardinal. Subsequent scanners are hidden away in the implementation module. Observe too that one must know the results of a call to FormatCard before attempting to do the actual conversion to a cardinal with ValueCard because if the string turns out to be invalid, ValueCard will raise an exception. Here is an implementation of this module:

IMPLEMENTATION MODULE WholeConv;

(* =========================================
            Definition Module from
                  ISO Modula-2
Draft Standard CD10515 by JTC1/SC22/WG13
    Language and Module designs © 1992 by
BSI, D.J. Andrews, B.J. Cornelius, R. B. Henry
R. Sutcliffe, D.P. Ward, and M. Woodman

          Implementation © 1994
                by R. Sutcliffe
       (Portions coded by G. Tischer)
        Trinity Western University
7600 Glover Rd., Langley, BC Canada V3A 6H4
         e-mail: rsutc@twu.ca
    Last modification date 1996 12 03
=========================================== *)

  (* Low-level whole-number/string conversions *)

(*1994 06 14 First version by R. Sutcliffe
   1996 11 12 revised by R. Sutcliffe not to use scanClass inputs. 
   ideas considered include those of Norm Black and Keith Hopper *)

IMPORT
  ConvTypes;
FROM ConvTypes IMPORT
  ScanClass;
FROM EXCEPTIONS IMPORT
  ExceptionSource, AllocateSource, RAISE, IsExceptionalExecution, IsCurrentSource;

FROM CharClass IMPORT
  IsWhiteSpace, IsNumeric;

(* two globals to hold last wholes checked by format; use if OK in value *)
VAR  
  theCard : CARDINAL;
  theInt : INTEGER;

CONST
    zeroAsc = ORD ("0");
    maxCardDiv10  = MAX (CARDINAL) / 10;
    lastMaxCardDigitChar = CHR( (MAX (CARDINAL) REM 10) + zeroAsc );
    maxIntDiv10  = MAX (INTEGER) / 10;
    lastMaxIntDigitChar = CHR( (MAX (INTEGER) REM 10) + zeroAsc );
    minIntDiv10  = MIN (INTEGER) / 10;
    lastMinIntDigitChar = CHR( ABS ((MIN (INTEGER) REM 10)) + VAL (INTEGER, zeroAsc) );
VAR
    WholeConvExSource : ExceptionSource;

(* local procs representing scan states after the initial one. These are named after the last input classified *)

PROCEDURE Sign (inputCh : CHAR; VAR chClass : ConvTypes.ScanClass; VAR nextState : ConvTypes.ScanState);
(* after sign must get digit *)
BEGIN
    IF IsNumeric (inputCh)
      THEN
        chClass := ConvTypes.valid;
        nextState := WDigit;
      ELSE
        chClass := ConvTypes.invalid;
        nextState := Sign;
      END;
END Sign;

PROCEDURE WDigit (inputCh : CHAR; VAR chClass : ConvTypes.ScanClass; VAR nextState : ConvTypes.ScanState);
(* after digit can have another digit; anything else terminates *)
BEGIN
    IF IsNumeric (inputCh)
      THEN
        chClass := ConvTypes.valid;
        nextState := WDigit;
      ELSE
        chClass := ConvTypes.terminator;
        (* no point in changing states *)
     END;
END WDigit;

(* exported procs *)   
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. *)

BEGIN
    IF IsWhiteSpace (inputCh)
       THEN
         (* say got padding *)
         chClass := ConvTypes.padding;
         (* and next state is same as this one *)
         nextState := ScanInt;
      ELSIF IsNumeric (inputCh) THEN (* got digit *)
         chClass := ConvTypes.valid;
         (* switch to digit state *)
         nextState := WDigit;
      ELSIF (inputCh = '-') OR (inputCh = '+') THEN
         chClass := ConvTypes.valid;
         (* switch to sign state *)
          nextState := Sign;
      ELSE (* anything else is no good *)
         chClass := ConvTypes.invalid;
         nextState := ScanInt;
      END;
END ScanInt;

PROCEDURE FormatInt (str: ARRAY OF CHAR) : ConvResults;
  (* Returns the format of the string value for conversion to INTEGER. *)

VAR
  count, len : CARDINAL;
  class : ConvTypes.ScanClass;
  Scan : ConvTypes.ScanState;
  pos : BOOLEAN;
  ch : CHAR;

BEGIN
  pos := TRUE;
  len := LENGTH (str);
  IF len = 0
    THEN
      RETURN ConvTypes.strEmpty
    ELSE
      theInt := 0;
      Scan := ScanInt;
      count := 0;
      LOOP
        ch := str [count];
        Scan (ch, class, Scan);
        CASE class OF
          padding:
            (* leave it *) |
          valid:
            IF ch = "-" (* negative sign *)
              THEN
                pos := FALSE;
              ELSIF pos AND (theInt <= maxIntDiv10) THEN
                theInt := theInt * 10; (* shift number over *)
                IF (theInt < maxIntDiv10) OR (ch <= lastMaxIntDigitChar)
                  THEN
                    INC (theInt, VAL (INTEGER, (ORD (ch) - zeroAsc))) ; (* add digit *)
                   ELSE
                     RETURN ConvTypes.strOutOfRange
                   END 
                       (* consider the case when the last digit might cause an overflow. *)
              ELSIF (NOT pos) AND (theInt >= minIntDiv10) THEN
                theInt := theInt * 10; (* shift *)
                IF  ((theInt > minIntDiv10) OR (ch <= lastMinIntDigitChar))
                  THEN
                    DEC (theInt, VAL (INTEGER, (ORD (ch) - zeroAsc))); (* add digit *)
                  ELSE
                    RETURN ConvTypes.strOutOfRange
                  END;
              ELSE
                  RETURN ConvTypes.strOutOfRange
              END; |
          invalid:
             RETURN ConvTypes.strWrongFormat |
          terminator: (* if get here, all OK so far *)
             RETURN ConvTypes.strAllRight;
         END; (* case *)
      INC (count);
     IF count = len (* end of string and still all ok -- haven't returned *)
        THEN
           RETURN ConvTypes.strAllRight;
        END;
     END; (* loop *)
 END; (* if *)
 
END FormatInt;

PROCEDURE ValueInt (str: ARRAY OF CHAR): INTEGER;
(* Returns the value corresponding to the signed whole number string value str if str is well-formed; otherwise raises the WholeConv exception. *)
 
BEGIN
  IF FormatInt (str) # ConvTypes.strAllRight
    THEN
      RAISE (WholeConvExSource, 0, "Can't convert badly formatted string to integer.");
    ELSE
      RETURN theInt
    END;
END ValueInt;

PROCEDURE LengthInt (int: INTEGER): CARDINAL;
 (* Returns the number of characters in the string representation of int. *)

VAR
  count : CARDINAL;
  neg : BOOLEAN;
  
BEGIN
  IF int < 0
    THEN
      neg := TRUE;
    ELSIF int > 0 THEN
      neg := FALSE;
    ELSE (* equals zero *)
      RETURN 1;
    END;
  count := 0;
  WHILE int # 0
    DO
      int := int / 10;
      INC (count);
    END;
  IF neg 
    THEN
      INC (count)  (* need room for sign *)
    END;
  RETURN count;
END LengthInt ;

PROCEDURE ScanCard (inputCh: CHAR; VAR chClass: ConvTypes.ScanClass; VAR nextState: ConvTypes.ScanState);
  (* Represents the start state of a finite state scanner for unsigned whole numbers -  assigns class of inputCh to chClass and a procedure representing the next state to nextState. *)

BEGIN
  IF IsWhiteSpace (inputCh)
    THEN
      (* say got padding *)
      chClass := ConvTypes.padding;
       (* and next state is same as this one *)
       nextState := ScanInt;
    ELSIF IsNumeric (inputCh) THEN (* got digit *)
       chClass := ConvTypes.valid;
       (* switch to digit state *)
       nextState := WDigit;
    ELSE (* anything else is no good *)
       chClass := ConvTypes.invalid;
       (* No point in setting next state  *)
    END;
END ScanCard;

PROCEDURE FormatCard (str: ARRAY OF CHAR): ConvResults;
  (* Returns the format of the string value for conversion to CARDINAL. *)
VAR
  count, len : CARDINAL;
  class : ConvTypes.ScanClass;
  Scan : ConvTypes.ScanState;

BEGIN
  len := LENGTH (str);
  IF len = 0
    THEN
      RETURN ConvTypes.strEmpty
    ELSE
      theCard := 0;
      Scan := ScanCard;
      count := 0;
      LOOP
        Scan (str [count], class, Scan);
        CASE class OF
          padding:
            (* leave it *) |
          valid:
            IF theCard <= maxCardDiv10 
              THEN
                theCard := theCard * 10; (* shift *)
                IF (theCard < maxCardDiv10) OR (str [count] <= lastMaxCardDigitChar)
                  THEN (* add digit *)
                    theCard := theCard + (ORD(str [count]) - zeroAsc);
                  ELSE
                    RETURN ConvTypes.strOutOfRange
                  END;
                ELSE
                  RETURN ConvTypes.strOutOfRange
               END; |
          invalid:
             RETURN ConvTypes.strWrongFormat |
          terminator: (* if get here, all OK so far *)
             RETURN ConvTypes.strAllRight;
         END; (* case *)
      INC (count);
      IF count = len (* end of string and still all ok -- haven't returned *)
        THEN
          RETURN ConvTypes.strAllRight;
        END;
    END; (* loop *)
  END; (* if *)
 
END FormatCard;

PROCEDURE ValueCard (str: ARRAY OF CHAR): CARDINAL;
  (* Returns the value corresponding to the unsigned whole number string value str if str is well-formed; otherwise raises the WholeConv exception    *)

BEGIN
 IF FormatCard (str) # ConvTypes.strAllRight
    THEN
       RAISE (WholeConvExSource, 0, "Can't convert badly formatted string to cardinal.");
    ELSE
       RETURN theCard; (* stashed globally for us *)
    END;
END ValueCard;

PROCEDURE LengthCard (card: CARDINAL): CARDINAL;
  (* Returns the number of characters in the string representation of card. *)
VAR
  count : CARDINAL;
  
BEGIN
  IF card = 0
    THEN
      RETURN 1;
    END;
  count := 0;
  WHILE card # 0
    DO
      card := card DIV 10;
      INC (count);
    END;
  RETURN count;
END LengthCard;

PROCEDURE IsWholeConvException (): BOOLEAN;
  (* Returns TRUE if the current coroutine is in the exceptional execution state because of the raising of an exception in a routine from this module; otherwise returns FALSE. *)

BEGIN
   RETURN (IsExceptionalExecution() ) AND (IsCurrentSource (WholeConvExSource) )
END IsWholeConvException ;

BEGIN (* initialization of main module *)

  AllocateSource (WholeConvExSource);

END WholeConv.

There are a few interesting things worth noting about this implementation. Since the Format and Value procedure pairs are closely related, in this implementation a choice has been made to store the value constructed by Format in a global variable. When Value calls Format it can then pick up the result at once. There is a design problem here, however, and that is that an outside client must call Format and then Value and so do all the work twice. If the outside routine has access to the source code of WholeConv some of it can be copied there to improve the speed. Other clients will just have to suffer a performance hit when using both routines.

Another thing that a careful implementor has to worry about is the handling of values of type INTEGER. Usually signed numbers are implemented in such a way that the expression ABS (MIN( INTEGER)) causes an overflow because the result is too big. Thus, it is necessary in conversion code to handle the case of MIN(INTEGER) separately. Note also that when one gets close to the MAX and MIN values of INTEGER and the MAX value of CARDINAL, it is necessary to look carefully at the last digit so as to ensure that an overflow does not take place. For instance, if the largest cardinal that could be stored were 65535, then maxCardDiv10 is 6553 and LastMaxCardDigitChan is 5. If the scan thus far had 6553 as it added digits on the right and shifted left, the next digit must be looked at carefully to see if an overflow would take place if it were used.

17.9.3 High Level String Conversion Routines

At the next higher level (the one that I/O modules will call to do conversions) the ISO library has such modules as WholeStr. Here is the definition:

DEFINITION MODULE WholeStr;

  (* Whole-number/string conversions *)

IMPORT
  ConvTypes;

TYPE
  ConvResults = ConvTypes.ConvResults; (* strAllRight, strOutOfRange, strWrongFormat, strEmpty *)

(* the string form of a signed whole number is
     ["+" | "-"], decimal digit, {decimal digit}
*)

PROCEDURE StrToInt (str: ARRAY OF CHAR; VAR int: INTEGER; VAR res: ConvResults);
  (* Ignores any leading spaces in str. If the subsequent characters in str are in the format of a signed whole number, assigns a corresponding value to int. Assigns a value indicating the format of str to res.  *)

PROCEDURE IntToStr (int: INTEGER; VAR str: ARRAY OF CHAR);
  (* Converts the value of int to string form and copies the possibly truncated result to str. *)

(* the string form of an unsigned whole number is decimal digit, {decimal digit} *)

PROCEDURE StrToCard (str: ARRAY OF CHAR; VAR card: CARDINAL; VAR res:
ConvResults);
  (* Ignores any leading spaces in str. If the subsequent characters in str are in the format of an unsigned whole number, assigns a corresponding value to card. Assigns a value indicating the format of str to res.  *)

PROCEDURE CardToStr (card: CARDINAL; VAR str: ARRAY OF CHAR);
  (* Converts the value of card to string form and copies the possibly truncated result to str. *)

END WholeStr.

Notice that if the string to which a whole number is to be converted is not long enough, then the result is supposed to be simply truncated. In the implementation that follows, this is done by dividing the whole number by 10 until it will fit.

IMPLEMENTATION MODULE WholeStr;

(* omit copyright notice from above to save space *)
(* omit long version history *)
(* Whole-number/string conversions *)

FROM WholeConv IMPORT
  ScanCard, ScanInt, LengthInt, LengthCard;
IMPORT
  ConvTypes;
FROM ConvTypes IMPORT
  ScanClass;
  (* debug *)

(* It makes no sense to call FormatInt and ValueInt from WholeConv because then the work is done twice.  So, we dump a copy of FormatInt and FormatCard here *)
(* two globals to hold last wholes checked by format; use if OK in value *)
VAR  
  theCard : CARDINAL;
  theInt : INTEGER;
CONST
  zeroAsc = ORD ("0");
  maxCardDiv10  = MAX (CARDINAL) / 10;
  lastMaxCardDigitChar = CHR( (MAX (CARDINAL) REM 10) + zeroAsc);
  maxIntDiv10  = MAX (INTEGER) / 10;
  lastMaxIntDigitChar = CHR( (MAX (INTEGER) REM 10) + zeroAsc);
  minIntDiv10  = MIN (INTEGER) / 10;
  lastMinIntDigitChar = CHR ((ABS (MIN (INTEGER) + 10)) REM 10 + VAL (INTEGER, zeroAsc));

(* omit copies of FormatInt and FormatCard from above *)
(* end copies of stuff from WholeConv *)

PROCEDURE StrToInt (str: ARRAY OF CHAR; VAR int: INTEGER; VAR res: ConvResults);
  (* Ignores any leading spaces in str. If the subsequent characters in str are in the format of a signed whole number, assigns a corresponding value to int. Assigns a value indicating the format of str to res.  *)
BEGIN
  res := FormatInt (str);
  IF res = ConvTypes.strAllRight
     THEN
      int := theInt; (* pick up the global *)
    END;
END StrToInt;

PROCEDURE IntToStr (int: INTEGER; VAR str: ARRAY OF CHAR);
  (* Converts the value of int to string form and copies the possibly truncated result to str. *)

(* the string form of an unsigned whole number is
     decimal digit, {decimal digit} *)
VAR
  maxs, maxi, count, digit, stop : CARDINAL;
  neg : BOOLEAN;

BEGIN
  neg := (int < 0);
  maxs := HIGH (str) + 1;
  maxi := LengthInt (int); (* includes any neg *)
  IF maxs > maxi
     THEN
      count := maxi;
      str [count] := "";
    ELSE
      count := maxs;
      (* if string is too short, throw away some digits *)
      WHILE maxi > count
         DO
          int := int / 10;
          DEC (maxi);
        END;
    END;
  IF neg   
    THEN
      IF int = MIN (INTEGER) (* special case this one, cant do abs else *)
        THEN
          str [count - 1] := lastMinIntDigitChar;
          DEC (count);
          int := int / 10;
        END;
      stop := 1;
      str [0] := "-";
      int := ABS (int);
    ELSE
      stop := 0;
    END;
  WHILE count > stop
    DO
      digit := int REM 10;
      str [count - 1] := CHR (digit + zeroAsc);
      int := int / 10;
      DEC (count);
    END;
END IntToStr;

PROCEDURE StrToCard (str: ARRAY OF CHAR; VAR card: CARDINAL; VAR res:
ConvResults);
  (* Ignores any leading spaces in str. If the subsequent characters in str are in the format of an unsigned whole number, assigns a corresponding value to card. Assigns a value indicating the format of str to res.  *)
BEGIN
  res := FormatCard (str);
  IF res = ConvTypes.strAllRight
    THEN
      card := theCard; (* pick up the global *)
    END;

END StrToCard;

PROCEDURE CardToStr (card: CARDINAL; VAR str: ARRAY OF CHAR);
  (* Converts the value of card to string form and copies the possibly truncated result to str. *)
VAR
  maxs, maxi, count, digit : CARDINAL;

BEGIN
  maxs := HIGH (str) + 1;
  maxi := LengthCard (card);
  IF maxs > maxi
    THEN
      count := maxi;
      str [count] := "";
    ELSE
      count := maxs;
      (* if string is too short, throw away some digits *)
      WHILE maxi > count
        DO
          card := card / 10;
          DEC (maxi);
        END;
    END;
  WHILE count > 0
    DO
      digit := card REM 10;
      str [count - 1] := CHR (digit + zeroAsc);
      card := card / 10;
      DEC (count);
    END;
END CardToStr;

END WholeStr.

There are similar modules for the conversion of reals and longreals, but the code is somewhat more complex because of the need to consider the exponent and the mantissa. There is also a lower level module for working with reals called LoReal, but that is beyond the scope of this section.

17.9.4 High Level Whole Number I/O

The reader is familiar of course with the use of WholeIO and SWholeIO from long use throughout the text. With the materials already developed here , it is now possible to produce implementations for both. Rather than reproduce the entire contents of both, only a single procedure is given here to illustrate the calls to the conversion routines above.

PROCEDURE WriteInt (cid: IOChan.ChanId; int: INTEGER; width: CARDINAL);
  (* Writes the value of int to cid in text form, in a field of the given
minimum width. *)

VAR
  temp : String;
  count, len    : CARDINAL;

BEGIN
  IntToStr (int, temp);        (* convert the integer to a string *)
  len := LENGTH (temp);
  IF len < width               (* write spaces *)
    THEN
       WriteString (cid, PadString (width-len));
    ELSIF width = 0 THEN
      WriteChar (cid, GetPadChar());
    END;
  WriteString (cid,temp);          (* write the string *)
END WriteInt;

Contents