1 /****************************************************************
3 * The author of this software is David M. Gay.
5 * Copyright (c) 1991 by AT&T.
7 * Permission to use, copy, modify, and distribute this software for any
8 * purpose without fee is hereby granted, provided that this entire notice
9 * is included in all copies of any software which is or includes a copy
10 * or modification of this software and in all copies of the supporting
11 * documentation for such software.
13 * THIS SOFTWARE IS BEING PROVIDED "AS IS", WITHOUT ANY EXPRESS OR IMPLIED
14 * WARRANTY. IN PARTICULAR, NEITHER THE AUTHOR NOR AT&T MAKES ANY
15 * REPRESENTATION OR WARRANTY OF ANY KIND CONCERNING THE MERCHANTABILITY
16 * OF THIS SOFTWARE OR ITS FITNESS FOR ANY PARTICULAR PURPOSE.
18 ***************************************************************/
20 /* Please send bug reports to
22 AT&T Bell Laboratories, Room 2C-463
24 Murray Hill, NJ 07974-2070
26 dmg@research.att.com or research!dmg
35 #ifdef _REENT_THREAD_LOCAL
36 _Thread_local
struct _Bigint
*_tls_mp_result
;
37 _Thread_local
int _tls_mp_result_k
;
41 quorem (_Bigint
* b
, _Bigint
* S
)
46 __ULong
*bx
, *bxe
, *sx
, *sxe
;
54 /*debug*/ if (b
->_wds
> n
)
55 /*debug*/ Bug ("oversize b in quorem");
63 q
= *bxe
/ (*sxe
+ 1); /* ensure q <= true quotient */
66 /*debug*/ Bug ("oversized quotient in quorem");
76 ys
= (si
& 0xffff) * q
+ carry
;
77 zs
= (si
>> 16) * q
+ (ys
>> 16);
79 y
= (*bx
& 0xffff) - (ys
& 0xffff) + borrow
;
81 Sign_Extend (borrow
, y
);
82 z
= (*bx
>> 16) - (zs
& 0xffff) + borrow
;
84 Sign_Extend (borrow
, z
);
87 ys
= *sx
++ * q
+ carry
;
89 y
= *bx
- (ys
& 0xffff) + borrow
;
91 Sign_Extend (borrow
, y
);
99 while (--bxe
> bx
&& !*bxe
)
115 ys
= (si
& 0xffff) + carry
;
116 zs
= (si
>> 16) + (ys
>> 16);
118 y
= (*bx
& 0xffff) - (ys
& 0xffff) + borrow
;
120 Sign_Extend (borrow
, y
);
121 z
= (*bx
>> 16) - (zs
& 0xffff) + borrow
;
123 Sign_Extend (borrow
, z
);
128 y
= *bx
- (ys
& 0xffff) + borrow
;
130 Sign_Extend (borrow
, y
);
139 while (--bxe
> bx
&& !*bxe
)
147 /* dtoa for IEEE arithmetic (dmg): convert double to ASCII string.
149 * Inspired by "How to Print Floating-Point Numbers Accurately" by
150 * Guy L. Steele, Jr. and Jon L. White [Proc. ACM SIGPLAN '90, pp. 92-101].
153 * 1. Rather than iterating, we use a simple numeric overestimate
154 * to determine k = floor(log10(d)). We scale relevant
155 * quantities using O(log2(k)) rather than O(k) multiplications.
156 * 2. For some modes > 2 (corresponding to ecvt and fcvt), we don't
157 * try to generate digits strictly left to right. Instead, we
158 * compute with fewer bits and propagate the carry if necessary
159 * when rounding the final digit up. This is often faster.
160 * 3. Under the assumption that input will be rounded nearest,
161 * mode 0 renders 1e23 as 1e23 rather than 9.999999999999999e22.
162 * That is, we allow equality in stopping tests when the
163 * round-nearest rule will give the same floating-point value
164 * as would satisfaction of the stopping test with strict
166 * 4. We remove common factors of powers of 2 from relevant
168 * 5. When converting floating-point integers less than 1e16,
169 * we use floating-point arithmetic rather than resorting
170 * to multiple-precision integers.
171 * 6. When asked to produce fewer than 15 digits, we first try
172 * to get by with floating-point arithmetic; we resort to
173 * multiple-precision integer arithmetic only if we cannot
174 * guarantee that the floating-point calculation has given
175 * the correctly rounded result. For k requested digits and
176 * "uniformly" distributed input, the probability is
177 * something like 10^(k-15) that we must resort to the long
183 _dtoa_r (struct _reent
*ptr
,
191 /* Arguments ndigits, decpt, sign are similar to those
192 of ecvt and fcvt; trailing zeros are suppressed from
193 the returned string. If not null, *rve is set to point
194 to the end of the return value. If d is +-Infinity or NaN,
195 then *decpt is set to 9999.
198 0 ==> shortest string that yields d when read in
199 and rounded to nearest.
200 1 ==> like 0, but with Steele & White stopping rule;
201 e.g. with IEEE P754 arithmetic , mode 0 gives
202 1e23 whereas mode 1 gives 9.999999999999999e22.
203 2 ==> max(1,ndigits) significant digits. This gives a
204 return value similar to that of ecvt, except
205 that trailing zeros are suppressed.
206 3 ==> through ndigits past the decimal point. This
207 gives a return value similar to that from fcvt,
208 except that trailing zeros are suppressed, and
209 ndigits can be negative.
210 4-9 should give the same return values as 2-3, i.e.,
211 4 <= mode <= 9 ==> same return as mode
212 2 + (mode & 1). These modes are mainly for
213 debugging; often they run slower but sometimes
214 faster than modes 2-3.
215 4,5,8,9 ==> left-to-right digit generation.
216 6-9 ==> don't try fast floating-point estimate
219 Values of mode other than 0-9 are treated as mode 0.
221 Sufficient space is allocated to the return value
222 to hold the suppressed trailing zeros.
225 int bbits
, b2
, b5
, be
, dig
, i
, ieps
, ilim
, ilim0
, ilim1
, j
, j1
, k
, k0
,
226 k_check
, leftright
, m2
, m5
, s2
, s5
, spec_case
, try_quick
;
227 union double_union d
, d2
, eps
;
229 #ifndef Sudden_Underflow
233 _Bigint
*b
, *b1
, *delta
, *mlo
= NULL
, *mhi
, *S
;
239 _REENT_CHECK_MP(ptr
);
240 if (_REENT_MP_RESULT(ptr
))
242 _REENT_MP_RESULT(ptr
)->_k
= _REENT_MP_RESULT_K(ptr
);
243 _REENT_MP_RESULT(ptr
)->_maxwds
= 1 << _REENT_MP_RESULT_K(ptr
);
244 Bfree (ptr
, _REENT_MP_RESULT(ptr
));
245 _REENT_MP_RESULT(ptr
) = 0;
248 if (word0 (d
) & Sign_bit
)
250 /* set sign for everything, including 0's and NaNs */
252 word0 (d
) &= ~Sign_bit
; /* clear sign bit */
257 #if defined(IEEE_Arith) + defined(VAX)
259 if ((word0 (d
) & Exp_mask
) == Exp_mask
)
261 if (word0 (d
) == 0x8000)
264 /* Infinity or NaN */
268 !word1 (d
) && !(word0 (d
) & 0xfffff) ? "Infinity" :
281 d
.d
+= 0; /* normalize */
292 b
= d2b (ptr
, d
.d
, &be
, &bbits
);
293 #ifdef Sudden_Underflow
294 i
= (int) (word0 (d
) >> Exp_shift1
& (Exp_mask
>> Exp_shift1
));
296 if ((i
= (int) (word0 (d
) >> Exp_shift1
& (Exp_mask
>> Exp_shift1
))) != 0)
300 word0 (d2
) &= Frac_mask1
;
301 word0 (d2
) |= Exp_11
;
303 if (j
= 11 - hi0bits (word0 (d2
) & Frac_mask
))
307 /* log(x) ~=~ log(1.5) + (x-1.5)/1.5
308 * log10(x) = log(x) / log(10)
309 * ~=~ log(1.5)/log(10) + (x-1.5)/(1.5*log(10))
310 * log10(d) = (i-Bias)*log(2)/log(10) + log10(d2)
312 * This suggests computing an approximation k to log10(d) by
314 * k = (i - Bias)*0.301029995663981
315 * + ( (d2-1.5)*0.289529654602168 + 0.176091259055681 );
317 * We want k to be too large rather than too small.
318 * The error in the first-order Taylor series approximation
319 * is in our favor, so we just round up the constant enough
320 * to compensate for any error in the multiplication of
321 * (i - Bias) by 0.301029995663981; since |i - Bias| <= 1077,
322 * and 1077 * 0.30103 * 2^-52 ~=~ 7.2e-14,
323 * adding 1e-13 to the constant term more than suffices.
324 * Hence we adjust the constant term to 0.1760912590558.
325 * (We could get a more accurate k by invoking log10,
326 * but this is probably not worthwhile.)
334 #ifndef Sudden_Underflow
339 /* d is denormalized */
341 i
= bbits
+ be
+ (Bias
+ (P
- 1) - 1);
342 #if defined (_DOUBLE_IS_32BITS)
343 x
= word0 (d
) << (32 - i
);
345 x
= (i
> 32) ? (word0 (d
) << (64 - i
)) | (word1 (d
) >> (i
- 32))
346 : (word1 (d
) << (32 - i
));
349 word0 (d2
) -= 31 * Exp_msk1
; /* adjust exponent */
350 i
-= (Bias
+ (P
- 1) - 1) + 1;
354 #if defined (_DOUBLE_IS_32BITS)
355 ds
= (d2
.d
- 1.5) * 0.289529651 + 0.176091269 + i
* 0.30103001;
357 ds
= (d2
.d
- 1.5) * 0.289529654602168 + 0.1760912590558 + i
* 0.301029995663981;
360 if (ds
< 0. && ds
!= k
)
361 k
--; /* want k = floor(ds) */
363 if (k
>= 0 && k
<= Ten_pmax
)
392 if (mode
< 0 || mode
> 9)
415 ilim
= ilim1
= i
= ndigits
;
427 j
= sizeof (__ULong
);
428 for (_REENT_MP_RESULT_K(ptr
) = 0; sizeof (_Bigint
) - sizeof (__ULong
) + j
<= i
;
430 _REENT_MP_RESULT_K(ptr
)++;
431 _REENT_MP_RESULT(ptr
) = eBalloc (ptr
, _REENT_MP_RESULT_K(ptr
));
432 s
= s0
= (char *) _REENT_MP_RESULT(ptr
);
434 if (ilim
>= 0 && ilim
<= Quick_max
&& try_quick
)
436 /* Try to get by with floating-point arithmetic. */
442 ieps
= 2; /* conservative */
449 /* prevent overflows */
451 d
.d
/= bigtens
[n_bigtens
- 1];
454 for (; j
; j
>>= 1, i
++)
462 else if ((j1
= -k
) != 0)
464 d
.d
*= tens
[j1
& 0xf];
465 for (j
= j1
>> 4; j
; j
>>= 1, i
++)
472 if (k_check
&& d
.d
< 1. && ilim
> 0)
481 eps
.d
= ieps
* d
.d
+ 7.;
482 word0 (eps
) -= (P
- 1) * Exp_msk1
;
496 /* Use Steele & White method of only
497 * generating digits needed.
499 eps
.d
= 0.5 / tens
[ilim
- 1] - eps
.d
;
504 *s
++ = '0' + (int) L
;
507 if (1. - d
.d
< eps
.d
)
518 /* Generate ilim digits, then fix them up. */
519 eps
.d
*= tens
[ilim
- 1];
520 for (i
= 1;; i
++, d
.d
*= 10.)
524 *s
++ = '0' + (int) L
;
527 if (d
.d
> 0.5 + eps
.d
)
529 else if (d
.d
< 0.5 - eps
.d
)
548 /* Do we have a "small" integer? */
550 if (be
>= 0 && k
<= Int_max
)
554 if (ndigits
< 0 && ilim
<= 0)
557 if (ilim
< 0 || d
.d
<= 5 * ds
)
565 #ifdef Check_FLT_ROUNDS
566 /* If FLT_ROUNDS == 2, L will usually be high by 1 */
573 *s
++ = '0' + (int) L
;
577 if ((d
.d
> ds
) || ((d
.d
== ds
) && (L
& 1)))
605 #ifndef Sudden_Underflow
606 denorm
? be
+ (Bias
+ (P
- 1) - 1 + 1) :
609 1 + 4 * P
- 3 - bbits
+ ((bbits
+ be
- 1) & 3);
635 if (m2
> 0 && s2
> 0)
637 i
= m2
< s2
? m2
: s2
;
648 mhi
= pow5mult (ptr
, mhi
, m5
);
649 b1
= mult (ptr
, mhi
, b
);
653 if ((j
= b5
- m5
) != 0)
654 b
= pow5mult (ptr
, b
, j
);
657 b
= pow5mult (ptr
, b
, b5
);
661 S
= pow5mult (ptr
, S
, s5
);
663 /* Check for special case that d is a normalized power of 2. */
668 if (!word1 (d
) && !(word0 (d
) & Bndry_mask
)
669 #ifndef Sudden_Underflow
670 && word0 (d
) & Exp_mask
674 /* The special case */
681 /* Arrange for convenient computation of quotients:
682 * shift left if necessary so divisor has 4 leading 0 bits.
684 * Perhaps we should just compute leading 28 bits of S once
685 * and for all and pass them and a shift to quorem, so it
686 * can do shifts and ors to compute the numerator for q.
690 if ((i
= ((s5
? 32 - hi0bits (S
->_x
[S
->_wds
- 1]) : 1) + s2
) & 0x1f) != 0)
693 if ((i
= ((s5
? 32 - hi0bits (S
->_x
[S
->_wds
- 1]) : 1) + s2
) & 0xf) != 0)
711 b
= lshift (ptr
, b
, b2
);
713 S
= lshift (ptr
, S
, s2
);
719 b
= multadd (ptr
, b
, 10, 0); /* we botched the k estimate */
721 mhi
= multadd (ptr
, mhi
, 10, 0);
725 if (ilim
<= 0 && mode
> 2)
727 if (ilim
< 0 || cmp (b
, S
= multadd (ptr
, S
, 5, 0)) <= 0)
729 /* no digits, fcvt style */
742 mhi
= lshift (ptr
, mhi
, m2
);
744 /* Compute mlo -- check for special case
745 * that d is a normalized power of 2.
751 mhi
= eBalloc (ptr
, mhi
->_k
);
753 mhi
= lshift (ptr
, mhi
, Log2P
);
758 dig
= quorem (b
, S
) + '0';
759 /* Do we yet have the shortest decimal string
760 * that will round to d?
763 delta
= diff (ptr
, S
, mhi
);
764 j1
= delta
->_sign
? 1 : cmp (b
, delta
);
767 if (j1
== 0 && !mode
&& !(word1 (d
) & 1))
777 if ((j
< 0) || ((j
== 0) && !mode
785 b
= lshift (ptr
, b
, 1);
787 if (((j1
> 0) || ((j1
== 0) && (dig
& 1)))
797 { /* possible if i == 1 */
808 b
= multadd (ptr
, b
, 10, 0);
810 mlo
= mhi
= multadd (ptr
, mhi
, 10, 0);
813 mlo
= multadd (ptr
, mlo
, 10, 0);
814 mhi
= multadd (ptr
, mhi
, 10, 0);
821 *s
++ = dig
= quorem (b
, S
) + '0';
824 b
= multadd (ptr
, b
, 10, 0);
827 /* Round off last digit */
829 b
= lshift (ptr
, b
, 1);
831 if ((j
> 0) || ((j
== 0) && (dig
& 1)))
852 if (mlo
&& mlo
!= mhi
)