1(*	$Id: LRealStr.Mod,v 1.8 2001/07/15 14:59:29 ooc-devel Exp $	*)
2MODULE oocLRealStr;
3
4 (*
5    LRealStr -  LONGREAL/string conversions.
6    Copyright (C) 1996, 2001 Michael Griebling
7
8    This module is free software; you can redistribute it and/or modify
9    it under the terms of the GNU Lesser General Public License as
10    published by the Free Software Foundation; either version 2 of the
11    License, or (at your option) any later version.
12
13    This module is distributed in the hope that it will be useful,
14    but WITHOUT ANY WARRANTY; without even the implied warranty of
15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16    GNU Lesser General Public License for more details.
17
18    You should have received a copy of the GNU Lesser General Public
19    License along with this program; if not, write to the Free Software
20    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
21
22*)
23
24IMPORT
25  Low := oocLowLReal, Conv := oocConvTypes, RC := oocLRealConv, Str := oocStrings,
26  LInt := oocLongInts;
27
28CONST
29  ZERO=0.0D0; B=8000H;
30
31TYPE
32  ConvResults*= Conv.ConvResults; (* strAllRight, strOutOfRange, strWrongFormat, strEmpty *)
33
34CONST
35  strAllRight*=Conv.strAllRight;       (* the string format is correct for the corresponding conversion *)
36  strOutOfRange*=Conv.strOutOfRange;   (* the string is well-formed but the value cannot be represented *)
37  strWrongFormat*=Conv.strWrongFormat; (* the string is in the wrong format for the conversion *)
38  strEmpty*=Conv.strEmpty;             (* the given string is empty *)
39
40
41(* the string form of a signed fixed-point real number is
42     ["+" | "-"], decimal digit, {decimal digit}, [".", {decimal digit}]
43*)
44
45(* the string form of a signed floating-point real number is
46     signed fixed-point real number, "E"|"e", ["+" | "-"], decimal digit, {decimal digit}
47*)
48
49PROCEDURE StrToReal*(str: ARRAY OF CHAR; VAR real: LONGREAL; VAR res: ConvResults);
50 (*
51    Ignores any leading spaces in str. If the subsequent characters in str
52    are in the format of a signed real number, and shall assign values to
53    `res' and `real' as follows:
54
55    strAllRight
56      if the remainder of `str' represents a complete signed real number
57      in the range of the type of `real' -- the value of this number shall
58      be assigned to `real';
59
60    strOutOfRange
61      if the remainder of `str' represents a complete signed real number
62      but its value is out of the range of the type of `real' -- the
63      maximum or minimum value of the type of `real' shall be assigned to
64      `real' according to the sign of the number;
65
66    strWrongFormat
67      if there are remaining characters in `str' but these are not in the
68      form of a complete signed real number -- the value of `real' is not
69      defined;
70
71    strEmpty
72      if there are no remaining characters in `str' -- the value of `real'
73      is not defined.
74  *)
75BEGIN
76  res:=RC.FormatReal(str);
77  IF res IN {strAllRight, strOutOfRange} THEN real:=RC.ValueReal(str) END
78END StrToReal;
79
80PROCEDURE AppendChar(ch: CHAR; VAR str: ARRAY OF CHAR);
81VAR ds: ARRAY 2 OF CHAR;
82BEGIN
83  ds[0]:=ch; ds[1]:=0X; Str.Append(ds, str)
84END AppendChar;
85
86PROCEDURE AppendDigit(dig: LONGINT; VAR str: ARRAY OF CHAR);
87BEGIN
88  AppendChar(CHR(dig+ORD("0")), str)
89END AppendDigit;
90
91PROCEDURE AppendExponent(exp: INTEGER; VAR str: ARRAY OF CHAR);
92BEGIN
93  Str.Append("E", str);
94  IF exp<0 THEN exp:=-exp; Str.Append("-", str)
95  ELSE Str.Append("+", str)
96  END;
97  IF exp>=100 THEN AppendDigit(exp DIV 100, str) END;
98  IF exp>=10 THEN AppendDigit((exp DIV 10) MOD 10, str) END;
99  AppendDigit(exp MOD 10, str)
100END AppendExponent;
101
102PROCEDURE AppendFraction(VAR n: LInt.LongInt; sigFigs, place: INTEGER; VAR str: ARRAY OF CHAR);
103VAR digs, end: INTEGER; d: LONGINT; lstr: ARRAY 64 OF CHAR;
104BEGIN
105  (* write significant digits *)
106  lstr:="";
107  FOR digs:=1 TO sigFigs DO
108    LInt.DivDigit(n, 10, d); AppendDigit(d, lstr);
109  END;
110
111  (* reverse the real digits and append to str *)
112  end:=sigFigs-1;
113  FOR digs:=0 TO sigFigs-1 DO
114    IF digs=place THEN Str.Append(".", str) END;
115    AppendChar(lstr[end], str); DEC(end)
116  END;
117
118  (* pad out digits to the decimal position *)
119  FOR digs:=sigFigs TO place-1 DO Str.Append("0", str) END
120END AppendFraction;
121
122PROCEDURE RemoveLeadingZeros(VAR str: ARRAY OF CHAR);
123VAR len: LONGINT;
124BEGIN
125  len:=Str.Length(str);
126  WHILE (len>1)&(str[0]="0")&(str[1]#".") DO Str.Delete(str, 0, 1); DEC(len) END
127END RemoveLeadingZeros;
128
129
130
131PROCEDURE MaxDigit (VAR n: LInt.LongInt) : LONGINT;
132
133VAR
134
135	i, max : LONGINT;
136
137BEGIN
138
139	(* return the maximum digit in the specified LongInt number *)
140
141  FOR i:=0 TO LEN(n)-1 DO
142
143  	 IF n[i] # 0 THEN
144
145		max := n[i];
146
147		WHILE max>=10 DO max:=max DIV 10 END;
148
149      	RETURN max;
150
151    END;
152  END;
153
154  RETURN 0;
155
156END MaxDigit;
157
158PROCEDURE Scale (x: LONGREAL; VAR n: LInt.LongInt; sigFigs: INTEGER; exp: INTEGER; VAR overflow : BOOLEAN);
159CONST
160  MaxDigits=4; LOG2B=15;
161VAR
162  i, m, ln, d: LONGINT; e1, e2: INTEGER;
163
164  max: LONGINT;
165BEGIN
166  (* extract fraction & exponent *)
167  m:=0; overflow := FALSE;
168  WHILE Low.exponent(x)=Low.expoMin DO        (* scale up subnormal numbers *)
169    x:=x*2.0D0; DEC(m)
170  END;
171  m:=m+Low.exponent(x); x:=Low.fraction(x);
172  x:=Low.scale(x, SHORT(m MOD LOG2B));        (* scale up the number *)
173  m:=m DIV LOG2B;                             (* base B exponent *)
174
175
176  (* convert to an extended integer MOD B *)
177  ln:=LEN(n)-1;
178  FOR i:=ln-MaxDigits TO ln DO
179    n[i]:=SHORT(ENTIER(x));                   (* convert/store the number *)
180    x:=(x-n[i])*B
181  END;
182  FOR i:=0 TO ln-MaxDigits-1 DO n[i]:=0 END;  (* zero the other digits *)
183
184  (* scale to get the number of significant digits *)
185  e1:=SHORT(m)-MaxDigits; e2:= sigFigs-exp-1;
186  IF e1>=0 THEN
187    LInt.BPower(n, e1+1); LInt.TenPower(n, e2);
188
189  	max := MaxDigit(n);    (* remember the original digit so we can check for round-up *)
190    LInt.AddDigit(n, B DIV 2); LInt.DivDigit(n, B, d) (* round *)
191  ELSIF e2>0 THEN
192    LInt.TenPower(n, e2);
193    IF e1>0 THEN LInt.BPower(n, e1-1) ELSE LInt.BPower(n, e1+1) END;
194
195  	max := MaxDigit(n);    (* remember the original digit so we can check for round-up *)
196    LInt.AddDigit(n, B DIV 2); LInt.DivDigit(n, B, d) (* round *)
197  ELSE (* e1<=0, e2<=0 *)
198    LInt.TenPower(n, e2); LInt.BPower(n, e1+1);
199
200  	max := MaxDigit(n);    (* remember the original digit so we can check for round-up *)
201    LInt.AddDigit(n, B DIV 2); LInt.DivDigit(n, B, d) (* round *)
202  END;
203
204
205
206  (* check if the upper digit was changed by rounding up *)
207
208  IF (max = 9) & (max # MaxDigit(n)) THEN
209
210	 overflow := TRUE;
211
212  END
213END Scale;
214
215PROCEDURE RealToFloat*(real: LONGREAL; sigFigs: INTEGER; VAR str: ARRAY OF CHAR);
216 (*
217    The call RealToFloat(real,sigFigs,str) shall assign to `str' the
218    possibly truncated string corresponding to the value of `real' in
219    floating-point form.  A sign shall be included only for negative
220    values.  One significant digit shall be included in the whole number
221    part.  The signed exponent part shall be included only if the exponent
222    value is not 0.  If the value of `sigFigs' is greater than 0, that
223    number of significant digits shall be included, otherwise an
224    implementation-defined number of significant digits shall be
225    included.  The decimal point shall not be included if there are no
226    significant digits in the fractional part.
227
228    For example:
229
230    value:     3923009     39.23009     0.0003923009
231    sigFigs
232      1        4E+6        4E+1         4E-4
233      2        3.9E+6      3.9E+1       3.9E-4
234      5        3.9230E+6   3.9230E+1    3.9230E-4
235 *)
236VAR
237  exp: INTEGER; in: LInt.LongInt;
238
239  lstr: ARRAY 64 OF CHAR;
240
241  overflow: BOOLEAN;
242
243  d: LONGINT;
244BEGIN
245  (* set significant digits, extract sign & exponent *)
246  lstr:="";
247  IF sigFigs<=0 THEN sigFigs:=RC.SigFigs END;
248
249  (* check for illegal numbers *)
250  IF Low.IsNaN(real) THEN COPY("NaN", str); RETURN END;
251  IF real<ZERO THEN Str.Append("-", lstr); real:=-real END;
252  IF Low.IsInfinity(real) THEN Str.Append("Infinity", lstr); COPY(lstr, str); RETURN END;
253  exp:=Low.exponent10(real);
254
255  (* round the number and extract exponent again *)
256  Scale(real, in, sigFigs, exp, overflow);
257
258  IF overflow THEN
259
260  	 IF exp>=0 THEN INC(exp) ELSE DEC(exp) END;
261
262  	 LInt.DivDigit(in, 10, d)
263
264  END;
265
266  (* output number like x[.{x}][E+n[n]] *)
267  AppendFraction(in, sigFigs, 1, lstr);
268  IF exp#0 THEN AppendExponent(exp, lstr) END;
269
270  (* possibly truncate the result *)
271  COPY(lstr, str)
272END RealToFloat;
273
274PROCEDURE RealToEng*(real: LONGREAL; sigFigs: INTEGER; VAR str: ARRAY OF CHAR);
275 (*
276    Converts the value of real to floating-point string form, with
277    sigFigs significant figures, and copies the possibly truncated
278    result to str. The number is scaled with one to three digits in
279    the whole number part and with an exponent that is a multiple of
280    three.
281
282    For example:
283
284    value:     3923009     39.23009   0.0003923009
285    sigFigs
286      1        4E+6        40         400E-6
287      2        3.9E+6      39         390E-6
288      5        3.9230E+6   39.230     392.30E-6
289  *)
290VAR
291  in: LInt.LongInt; exp, offset: INTEGER;
292
293  lstr: ARRAY 64 OF CHAR;
294
295  d: LONGINT;
296
297  overflow: BOOLEAN;
298BEGIN
299  (* set significant digits, extract sign & exponent *)
300  lstr:="";
301  IF sigFigs<=0 THEN sigFigs:=RC.SigFigs END;
302
303  (* check for illegal numbers *)
304  IF Low.IsNaN(real) THEN COPY("NaN", str); RETURN END;
305  IF real<ZERO THEN Str.Append("-", lstr); real:=-real END;
306  IF Low.IsInfinity(real) THEN Str.Append("Infinity", lstr); COPY(lstr, str); RETURN END;
307  exp:=Low.exponent10(real);
308
309  (* round the number and extract exponent again (ie. 9.9 => 10.0) *)
310  Scale(real, in, sigFigs, exp, overflow);
311  IF overflow THEN
312
313  	 IF exp>=0 THEN INC(exp) ELSE DEC(exp) END;
314
315  	 LInt.DivDigit(in, 10, d)
316
317  END;
318
319
320  (* find the offset to make the exponent a multiple of three *)
321  offset:=exp MOD 3;
322
323  (* output number like x[x][x][.{x}][E+n[n]] *)
324  AppendFraction(in, sigFigs, offset+1, lstr);
325  exp:=exp-offset;
326  IF exp#0 THEN AppendExponent(exp, lstr) END;
327
328  (* possibly truncate the result *)
329  COPY(lstr, str)
330END RealToEng;
331
332PROCEDURE RealToFixed*(real: LONGREAL; place: INTEGER; VAR str: ARRAY OF CHAR);
333 (*
334    The call RealToFixed(real,place,str) shall assign to `str' the
335    possibly truncated string corresponding to the value of `real' in
336    fixed-point form.  A sign shall be included only for negative values.
337    At least one digit shall be included in the whole number part.  The
338    value shall be rounded to the given value of `place' relative to the
339    decimal point.  The decimal point shall be suppressed if `place' is
340    less than 0.
341
342    For example:
343
344    value:     3923009         3.923009   0.0003923009
345    sigFigs
346     -5        3920000         0          0
347     -2        3923010         0          0
348     -1        3923009         4          0
349      0        3923009.        4.         0.
350      1        3923009.0       3.9        0.0
351      4        3923009.0000    3.9230     0.0004
352 *)
353VAR
354  in: LInt.LongInt; exp, digs: INTEGER;
355
356  overflow, addDecPt: BOOLEAN;
357
358  lstr: ARRAY 256 OF CHAR;
359BEGIN
360  (* set significant digits, extract sign & exponent *)
361  lstr:=""; addDecPt:=place=0;
362
363  (* check for illegal numbers *)
364  IF Low.IsNaN(real) THEN COPY("NaN", str); RETURN END;
365  IF real<ZERO THEN Str.Append("-", lstr); real:=-real END;
366  IF Low.IsInfinity(real) THEN Str.Append("Infinity", lstr); COPY(lstr, str); RETURN END;
367  exp:=Low.exponent10(real);
368  IF place<0 THEN digs:=place+exp+2 ELSE digs:=place+exp+1 END;
369
370
371  (* round the number and extract exponent again (ie. 9.9 => 10.0) *)
372  Scale(real, in, digs, exp, overflow);
373
374  IF overflow THEN
375
376	 INC(digs); INC(exp);
377
378	 addDecPt := place=0;
379
380  END;
381
382  (* output number like x[{x}][.{x}] *)
383  IF exp<0 THEN
384    IF place<0 THEN AppendFraction(in, 1, 1, lstr)
385    ELSE AppendFraction(in, place+1, 1, lstr)
386    END
387  ELSE AppendFraction(in, digs, exp+1, lstr);
388    RemoveLeadingZeros(lstr)
389  END;
390
391  (* special formatting *)
392  IF addDecPt THEN Str.Append(".", lstr) END;
393
394  (* possibly truncate the result *)
395  COPY(lstr, str)
396END RealToFixed;
397
398PROCEDURE RealToStr*(real: LONGREAL; VAR str: ARRAY OF CHAR);
399 (*
400    If the sign and magnitude of `real' can be shown within the capacity
401    of `str', the call RealToStr(real,str) shall behave as the call
402    RealToFixed(real,place,str), with a value of `place' chosen to fill
403    exactly the remainder of `str'.  Otherwise, the call shall behave as
404    the call RealToFloat(real,sigFigs,str), with a value of `sigFigs' of
405    at least one, but otherwise limited to the number of significant
406    digits that can be included together with the sign and exponent part
407    in `str'.
408 *)
409VAR
410  cap, exp, fp, len, pos: INTEGER;
411  found: BOOLEAN;
412BEGIN
413  cap:=SHORT(LEN(str))-1;  (* determine the capacity of the string with space for trailing 0X *)
414
415  (* check for illegal numbers *)
416  IF Low.IsNaN(real) THEN COPY("NaN", str); RETURN END;
417  IF real<ZERO THEN COPY("-", str); fp:=-1 ELSE COPY("", str); fp:=0 END;
418  IF Low.IsInfinity(ABS(real)) THEN Str.Append("Infinity", str); RETURN END;
419
420  (* extract exponent *)
421  exp:=Low.exponent10(real);
422
423  (* format number *)
424  INC(fp, RC.SigFigs-exp-2);
425  len:=RC.LengthFixedReal(real, fp);
426  IF cap>=len THEN
427    RealToFixed(real, fp, str);
428
429    (* pad with remaining zeros *)
430    IF fp<0 THEN Str.Append(".", str); INC(len) END; (* add decimal point *)
431    WHILE len<cap DO Str.Append("0", str); INC(len) END
432  ELSE
433    fp:=RC.LengthFloatReal(real, RC.SigFigs); (* check actual length *)
434    IF fp<=cap THEN
435      RealToFloat(real, RC.SigFigs, str);
436
437      (* pad with remaining zeros *)
438      Str.FindNext("E", str, 2, found, pos);
439      WHILE fp<cap DO Str.Insert("0", pos, str); INC(fp) END
440    ELSE fp:=RC.SigFigs-fp+cap;
441      IF fp<1 THEN fp:=1 END;
442      RealToFloat(real, fp, str)
443    END
444  END
445END RealToStr;
446
447END oocLRealStr.
448
449
450
451
452