2 * This implementation is broken, as e.g. strtod("1.7E+064", ...) yields an
3 * incorrect (inaccurate) result.
4 * For libroot, we use the glibc version instead.
5 * This file is still used in the kernel, however, since I didn't dare
6 * introducing a glibc-based source into the kernel.
7 * So, currently we have to live with the fact that strtod() in our kernel
8 * gives somewhat inaccurate results.
13 * The Regents of the University of California. All rights reserved.
15 * Redistribution and use in source and binary forms, with or without
16 * modification, are permitted provided that the following conditions
18 * 1. Redistributions of source code must retain the above copyright
19 * notice, this list of conditions and the following disclaimer.
20 * 2. Redistributions in binary form must reproduce the above copyright
21 * notice, this list of conditions and the following disclaimer in the
22 * documentation and/or other materials provided with the distribution.
23 * 3. All advertising materials mentioning features or use of this software
24 * must display the following acknowledgement:
25 * This product includes software developed by the University of
26 * California, Berkeley and its contributors.
27 * 4. Neither the name of the University nor the names of its contributors
28 * may be used to endorse or promote products derived from this software
29 * without specific prior written permission.
31 * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
32 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
33 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
34 * ARE DISCLAIMED. IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
35 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
36 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
37 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
38 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
39 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
40 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
45 /****************************************************************
47 * The author of this software is David M. Gay.
49 * Copyright (c) 1991 by AT&T.
51 * Permission to use, copy, modify, and distribute this software for any
52 * purpose without fee is hereby granted, provided that this entire notice
53 * is included in all copies of any software which is or includes a copy
54 * or modification of this software and in all copies of the supporting
55 * documentation for such software.
57 * THIS SOFTWARE IS BEING PROVIDED "AS IS", WITHOUT ANY EXPRESS OR IMPLIED
58 * WARRANTY. IN PARTICULAR, NEITHER THE AUTHOR NOR AT&T MAKES ANY
59 * REPRESENTATION OR WARRANTY OF ANY KIND CONCERNING THE MERCHANTABILITY
60 * OF THIS SOFTWARE OR ITS FITNESS FOR ANY PARTICULAR PURPOSE.
62 ***************************************************************/
64 /* Please send bug reports to
66 AT&T Bell Laboratories, Room 2C-463
68 Murray Hill, NJ 07974-2070
70 dmg@research.att.com or research!dmg
73 /* strtod for IEEE-, VAX-, and IBM-arithmetic machines.
75 * This strtod returns a nearest machine number to the input decimal
76 * string (or sets errno to ERANGE). With IEEE arithmetic, ties are
77 * broken by the IEEE round-even rule. Otherwise ties are broken by
78 * biased rounding (add half and chop).
80 * Inspired loosely by William D. Clinger's paper "How to Read Floating
81 * Point Numbers Accurately" [Proc. ACM SIGPLAN '90, pp. 92-101].
85 * 1. We only require IEEE, IBM, or VAX double-precision
86 * arithmetic (not IEEE double-extended).
87 * 2. We get by with floating-point arithmetic in a case that
88 * Clinger missed -- when we're computing d * 10^n
89 * for a small integer d and the integer n is not too
90 * much larger than 22 (the maximum integer k for which
91 * we can represent 10^k exactly), we may be able to
92 * compute (d*10^k) * 10^(e-k) with just one roundoff.
93 * 3. Rather than a bit-at-a-time adjustment of the binary
94 * result in the hard case, we use floating-point
95 * arithmetic to determine the adjustment to within
96 * one bit; only in really hard cases do we need to
97 * compute a second residual.
98 * 4. Because of 3., we don't need a large table of powers of 10
99 * for ten-to-e (just some small tables, e.g. of 10^k
104 * #define Sudden_Underflow for IEEE-format machines without gradual
105 * underflow (i.e., that flush to zero on underflow).
106 * #define IBM for IBM mainframe-style floating-point arithmetic.
107 * #define VAX for VAX-style floating-point arithmetic.
108 * #define Unsigned_Shifts if >> does treats its left operand as unsigned.
109 * #define No_leftright to omit left-right logic in fast floating-point
110 * computation of dtoa.
111 * #define Check_FLT_ROUNDS if FLT_ROUNDS can assume the values 2 or 3.
112 * #define RND_PRODQUOT to use rnd_prod and rnd_quot (assembly routines
113 * that use extended-precision instructions to compute rounded
114 * products and quotients) with IBM.
115 * #define ROUND_BIASED for IEEE-format with biased rounding.
116 * #define Inaccurate_Divide for IEEE-format with correctly rounded
117 * products but inaccurate quotients, e.g., for Intel i860.
118 * #define Just_16 to store 16 bits per 32-bit Long when doing high-precision
119 * integer arithmetic. Whether this speeds things up or slows things
120 * down depends on the machine and the number being converted.
121 * #define Bad_float_h if your system lacks a float.h or if it does not
122 * define some or all of DBL_DIG, DBL_MAX_10_EXP, DBL_MAX_EXP,
123 * FLT_RADIX, FLT_ROUNDS, and DBL_MAX.
126 #if defined(__i386__) || defined(__ia64__) || defined(__alpha__) || \
127 defined(__sparc64__) || defined(__powerpc__) || defined(__POWERPC__) || \
128 defined(__m68k__) || defined(__M68K__) || defined(__arm__) || \
129 defined(__ARM__) || defined(__mipsel__) || defined(__MIPSEL__) || \
131 # include <sys/types.h>
132 # if BYTE_ORDER == BIG_ENDIAN
133 # define IEEE_BIG_ENDIAN
135 # define IEEE_LITTLE_ENDIAN
137 #endif /* defined(__i386__) ... */
139 #include <inttypes.h>
141 typedef int32_t Long
;
142 typedef u_int32_t ULong
;
146 # include <KernelExport.h>
147 # define Bug(x) {dprintf("%s\n", x);}
150 # define Bug(x) {fprintf(stderr, "%s\n", x); exit(1);}
161 #include <errno_private.h>
165 #ifdef IEEE_BIG_ENDIAN
166 # define IEEE_ARITHMETIC
168 #ifdef IEEE_LITTLE_ENDIAN
169 # define IEEE_ARITHMETIC
171 #ifdef IEEE_ARITHMETIC
173 # define DBL_MAX_10_EXP 308
174 # define DBL_MAX_EXP 1024
176 # define FLT_ROUNDS 1
177 # define DBL_MAX 1.7976931348623157e+308
182 # define DBL_MAX_10_EXP 75
183 # define DBL_MAX_EXP 63
184 # define FLT_RADIX 16
185 # define FLT_ROUNDS 0
186 # define DBL_MAX 7.2370055773322621e+75
191 # define DBL_MAX_10_EXP 38
192 # define DBL_MAX_EXP 127
194 # define FLT_ROUNDS 1
195 # define DBL_MAX 1.7014118346046923e+38
199 # define LONG_MAX 2147483647
212 #ifdef Unsigned_Shifts
213 # define Sign_Extend(a,b) if (b < 0) a |= 0xffff0000;
215 # define Sign_Extend(a,b) /*no-op*/
218 #if defined(IEEE_LITTLE_ENDIAN) + defined(IEEE_BIG_ENDIAN) + defined(VAX) + \
220 #error Only one of IEEE_LITTLE_ENDIAN, IEEE_BIG_ENDIAN, VAX, or IBM should be defined.
223 union doubleasulongs
{
228 #ifdef IEEE_LITTLE_ENDIAN
229 # define word0(x) (((union doubleasulongs *)&x)->w)[1]
230 # define word1(x) (((union doubleasulongs *)&x)->w)[0]
232 # define word0(x) (((union doubleasulongs *)&x)->w)[0]
233 # define word1(x) (((union doubleasulongs *)&x)->w)[1]
236 /* The following definition of Storeinc is appropriate for MIPS processors.
237 * An alternative that might be better on some machines is
238 * #define Storeinc(a,b,c) (*a++ = b << 16 | c & 0xffff)
240 #if defined(IEEE_LITTLE_ENDIAN) + defined(VAX)
241 # define Storeinc(a,b,c) (((unsigned short *)a)[1] = (unsigned short)b, \
242 ((unsigned short *)a)[0] = (unsigned short)c, a++)
244 # define Storeinc(a,b,c) (((unsigned short *)a)[0] = (unsigned short)b, \
245 ((unsigned short *)a)[1] = (unsigned short)c, a++)
248 /* #define P DBL_MANT_DIG */
249 /* Ten_pmax = floor(P*log(2)/log(5)) */
250 /* Bletch = (highest power of 2 < DBL_MAX_10_EXP) / 16 */
251 /* Quick_max = floor((P-1)*log(FLT_RADIX)/log(10) - 1) */
252 /* Int_max = floor(P*log(FLT_RADIX)/log(10) - 1) */
254 #if defined(IEEE_LITTLE_ENDIAN) + defined(IEEE_BIG_ENDIAN)
256 #define Exp_shift1 20
257 #define Exp_msk1 0x100000
258 #define Exp_msk11 0x100000
259 #define Exp_mask 0x7ff00000
264 #define Exp_1 0x3ff00000
265 #define Exp_11 0x3ff00000
267 #define Frac_mask 0xfffff
268 #define Frac_mask1 0xfffff
271 #define Bndry_mask 0xfffff
272 #define Bndry_mask1 0xfffff
274 #define Sign_bit 0x80000000
280 #define Infinite(x) (word0(x) == 0x7ff00000) /* sufficient test for here */
282 #undef Sudden_Underflow
283 #define Sudden_Underflow
286 #define Exp_shift1 24
287 #define Exp_msk1 0x1000000
288 #define Exp_msk11 0x1000000
289 #define Exp_mask 0x7f000000
292 #define Exp_1 0x41000000
293 #define Exp_11 0x41000000
294 #define Ebits 8 /* exponent has 7 bits, but 8 is the right value in b2d */
295 #define Frac_mask 0xffffff
296 #define Frac_mask1 0xffffff
299 #define Bndry_mask 0xefffff
300 #define Bndry_mask1 0xffffff
302 #define Sign_bit 0x80000000
304 #define Tiny0 0x100000
311 #define Exp_msk1 0x80
312 #define Exp_msk11 0x800000
313 #define Exp_mask 0x7f80
316 #define Exp_1 0x40800000
317 #define Exp_11 0x4080
319 #define Frac_mask 0x7fffff
320 #define Frac_mask1 0xffff007f
323 #define Bndry_mask 0xffff007f
324 #define Bndry_mask1 0xffff007f
326 #define Sign_bit 0x8000
340 #define rounded_product(a,b) a = rnd_prod(a, b)
341 #define rounded_quotient(a,b) a = rnd_quot(a, b)
342 extern double rnd_prod(double, double), rnd_quot(double, double);
344 #define rounded_product(a,b) a *= b
345 #define rounded_quotient(a,b) a /= b
348 #define Big0 (Frac_mask1 | Exp_msk1*(DBL_MAX_EXP+Bias-1))
349 #define Big1 0xffffffff
352 /* When Pack_32 is not defined, we store 16 bits per 32-bit Long.
353 * This makes some inner loops simpler and sometimes saves work
354 * during multiplications, but it often seems to make things slightly
355 * slower. Hence the default is now to store 32 bits per Long.
365 extern "C" double strtod(const char *s00
, char **se
);
366 extern "C" char *__dtoa(double d
, int mode
, int ndigits
,
367 int *decpt
, int *sign
, char **rve
, char **resultp
);
373 int k
, maxwds
, sign
, wds
;
377 typedef struct Bigint Bigint
;
386 rv
= (Bigint
*)malloc(sizeof(Bigint
) + (x
-1)*sizeof(Long
));
389 rv
->sign
= rv
->wds
= 0;
401 #define Bcopy(x,y) memcpy((char *)&x->sign, (char *)&y->sign, \
402 y->wds*sizeof(Long) + 2*sizeof(int))
406 multadd(Bigint
*b
, int m
, int a
) /* multiply by m and add a */
421 y
= (xi
& 0xffff) * m
+ a
;
422 z
= (xi
>> 16) * m
+ (y
>> 16);
424 *x
++ = (z
<< 16) + (y
& 0xffff);
432 if (wds
>= b
->maxwds
) {
446 s2b(const char *s
, int nd0
, int nd
, ULong y9
)
453 for (k
= 0, y
= 1; x
> y
; y
<<= 1, k
++) ;
460 b
->x
[0] = y9
& 0xffff;
461 b
->wds
= (b
->x
[1] = y9
>> 16) ? 2 : 1;
468 b
= multadd(b
, 10, *s
++ - '0');
474 b
= multadd(b
, 10, *s
++ - '0');
484 if (!(x
& 0xffff0000)) {
488 if (!(x
& 0xff000000)) {
492 if (!(x
& 0xf0000000)) {
496 if (!(x
& 0xc0000000)) {
500 if (!(x
& 0x80000000)) {
502 if (!(x
& 0x40000000))
566 mult(Bigint
*a
, Bigint
*b
)
571 ULong
*x
, *xa
, *xae
, *xb
, *xbe
, *xc
, *xc0
;
576 if (a
->wds
< b
->wds
) {
588 for (x
= c
->x
, xa
= x
+ wc
; x
< xa
; x
++)
596 for (; xb
< xbe
; xb
++, xc0
++) {
597 if ( (y
= *xb
& 0xffff) ) {
602 z
= (*x
& 0xffff) * y
+ (*xc
& 0xffff) + carry
;
604 z2
= (*x
++ >> 16) * y
+ (*xc
>> 16) + carry
;
610 if ( (y
= *xb
>> 16) ) {
616 z
= (*x
& 0xffff) * y
+ (*xc
>> 16) + carry
;
619 z2
= (*x
++ >> 16) * y
+ (*xc
& 0xffff) + carry
;
626 for (; xb
< xbe
; xc0
++) {
632 z
= *x
++ * y
+ *xc
+ carry
;
640 for (xc0
= c
->x
, xc
= xc0
+ wc
; wc
> 0 && !*--xc
; --wc
) ;
650 pow5mult(Bigint
*b
, int k
)
652 Bigint
*b1
, *p5
, *p51
;
654 static int p05
[3] = { 5, 25, 125 };
657 b
= multadd(b
, p05
[i
-1], 0);
674 if (!(p51
= p5
->next
)) {
675 p51
= p5
->next
= mult(p5
,p5
);
685 lshift(Bigint
*b
, int k
)
689 ULong
*x
, *x1
, *xe
, z
;
698 for (i
= b
->maxwds
; n1
> i
; i
<<= 1)
702 for (i
= 0; i
< n
; i
++)
722 *x1
++ = *x
<< k
& 0xffff | z
;
740 cmp(Bigint
*a
, Bigint
*b
)
742 ULong
*xa
, *xa0
, *xb
, *xb0
;
748 if (i
> 1 && !a
->x
[i
-1])
749 Bug("cmp called with a->x[a->wds-1] == 0");
750 if (j
> 1 && !b
->x
[j
-1])
751 Bug("cmp called with b->x[b->wds-1] == 0");
761 return *xa
< *xb
? -1 : 1;
770 diff(Bigint
*a
, Bigint
*b
)
774 Long borrow
, y
; /* We need signed shifts here. */
775 ULong
*xa
, *xae
, *xb
, *xbe
, *xc
;
806 y
= (*xa
& 0xffff) - (*xb
& 0xffff) + borrow
;
808 Sign_Extend(borrow
, y
);
809 z
= (*xa
++ >> 16) - (*xb
++ >> 16) + borrow
;
811 Sign_Extend(borrow
, z
);
815 y
= (*xa
& 0xffff) + borrow
;
817 Sign_Extend(borrow
, y
);
818 z
= (*xa
++ >> 16) + borrow
;
820 Sign_Extend(borrow
, z
);
825 y
= *xa
++ - *xb
++ + borrow
;
827 Sign_Extend(borrow
, y
);
833 Sign_Extend(borrow
, y
);
850 L
= (word0(x
) & Exp_mask
) - (P
-1)*Exp_msk1
;
851 #ifndef Sudden_Underflow
859 #ifndef Sudden_Underflow
863 word0(a
) = 0x80000 >> L
;
868 word1(a
) = L
>= 31 ? 1 : 1 << (31 - L
);
877 b2d(Bigint
*a
, int *e
)
879 ULong
*xa
, *xa0
, w
, y
, z
;
893 if (!y
) Bug("zero y in b2d");
899 d0
= Exp_1
| (y
>> (Ebits
- k
));
900 w
= xa
> xa0
? *--xa
: 0;
901 d1
= (y
<< ((32-Ebits
) + k
)) | (w
>> (Ebits
- k
));
904 z
= xa
> xa0
? *--xa
: 0;
906 d0
= Exp_1
| (y
<< k
) | (z
>> (32 - k
));
907 y
= xa
> xa0
? *--xa
: 0;
908 d1
= (z
<< k
) | (y
>> (32 - k
));
914 if (k
< Ebits
+ 16) {
915 z
= xa
> xa0
? *--xa
: 0;
916 d0
= Exp_1
| y
<< k
- Ebits
| z
>> Ebits
+ 16 - k
;
917 w
= xa
> xa0
? *--xa
: 0;
918 y
= xa
> xa0
? *--xa
: 0;
919 d1
= z
<< k
+ 16 - Ebits
| w
<< k
- Ebits
| y
>> 16 + Ebits
- k
;
922 z
= xa
> xa0
? *--xa
: 0;
923 w
= xa
> xa0
? *--xa
: 0;
925 d0
= Exp_1
| y
<< k
+ 16 | z
<< k
| w
>> 16 - k
;
926 y
= xa
> xa0
? *--xa
: 0;
927 d1
= w
<< k
+ 16 | y
<< k
;
931 word0(d
) = d0
>> 16 | d0
<< 16;
932 word1(d
) = d1
>> 16 | d1
<< 16;
942 d2b(double d
, int *e
, int *bits
)
949 d0
= word0(d
) >> 16 | word0(d
) << 16;
950 d1
= word1(d
) >> 16 | word1(d
) << 16;
964 d0
&= 0x7fffffff; /* clear sign bit, which we ignore */
965 #ifdef Sudden_Underflow
966 de
= (int)(d0
>> Exp_shift
);
971 if ( (de
= (int)(d0
>> Exp_shift
)) )
976 if ( (k
= lo0bits(&y
)) ) {
977 x
[0] = y
| (z
<< (32 - k
));
982 i
= b
->wds
= (x
[1] = z
) ? 2 : 1;
986 Bug("Zero passed to d2b");
997 x
[0] = y
| z
<< 32 - k
& 0xffff;
998 x
[1] = z
>> k
- 16 & 0xffff;
1003 x
[1] = y
>> 16 | z
<< 16 - k
& 0xffff;
1004 x
[2] = z
>> k
& 0xffff;
1018 Bug("Zero passed to d2b");
1035 #ifndef Sudden_Underflow
1039 *e
= (de
- Bias
- (P
-1) << 2) + k
;
1040 *bits
= 4*P
+ 8 - k
- hi0bits(word0(d
) & Frac_mask
);
1042 *e
= de
- Bias
- (P
-1) + k
;
1045 #ifndef Sudden_Underflow
1047 *e
= de
- Bias
- (P
-1) + 1 + k
;
1049 *bits
= 32*i
- hi0bits(x
[i
-1]);
1051 *bits
= (i
+2)*16 - hi0bits(x
[i
]);
1062 ratio(Bigint
*a
, Bigint
*b
)
1070 k
= ka
- kb
+ 32*(a
->wds
- b
->wds
);
1072 k
= ka
- kb
+ 16*(a
->wds
- b
->wds
);
1076 word0(da
) += (k
>> 2)*Exp_msk1
;
1081 word0(db
) += (k
>> 2)*Exp_msk1
;
1087 word0(da
) += k
*Exp_msk1
;
1090 word0(db
) += k
*Exp_msk1
;
1098 1e0
, 1e1
, 1e2
, 1e3
, 1e4
, 1e5
, 1e6
, 1e7
, 1e8
, 1e9
,
1099 1e10
, 1e11
, 1e12
, 1e13
, 1e14
, 1e15
, 1e16
, 1e17
, 1e18
, 1e19
,
1108 bigtens
[] = { 1e16
, 1e32
, 1e64
, 1e128
, 1e256
};
1109 static double tinytens
[] = { 1e-16, 1e-32, 1e-64, 1e-128, 1e-256 };
1113 bigtens
[] = { 1e16
, 1e32
, 1e64
};
1114 static double tinytens
[] = { 1e-16, 1e-32, 1e-64 };
1117 bigtens
[] = { 1e16
, 1e32
};
1118 static double tinytens
[] = { 1e-16, 1e-32 };
1125 strtod(const char * __restrict s00
, char ** __restrict se
)
1127 int bb2
, bb5
, bbe
, bd2
, bd5
, bbbits
, bs2
, c
, dsign
,
1128 e
, e1
, esign
, i
, j
, k
, nd
, nd0
, nf
, nz
, nz0
, sign
;
1129 const char *s
, *s0
, *s1
;
1130 double aadj
, aadj1
, adj
, rv
, rv0
;
1133 Bigint
*bb
, *bb1
, *bd
, *bd0
, *bs
, *delta
;
1134 char decimal_point
= localeconv()->decimal_point
[0];
1136 sign
= nz0
= nz
= 0;
1138 for (s
= s00
;;s
++) switch(*s
) {
1150 if (isspace((unsigned char)*s
))
1157 while (*++s
== '0') ;
1163 for (nd
= nf
= 0; (c
= *s
) >= '0' && c
<= '9'; nd
++, s
++)
1169 if ((char)c
== decimal_point
) {
1172 for (; c
== '0'; c
= *++s
)
1174 if (c
> '0' && c
<= '9') {
1182 for (; c
>= '0' && c
<= '9'; c
= *++s
) {
1187 for (i
= 1; i
< nz
; i
++)
1190 else if (nd
<= DBL_DIG
+ 1)
1194 else if (nd
<= DBL_DIG
+ 1)
1202 if (c
== 'e' || c
== 'E') {
1203 if (!nd
&& !nz
&& !nz0
) {
1215 if (c
>= '0' && c
<= '9') {
1218 if (c
> '0' && c
<= '9') {
1221 while ((c
= *++s
) >= '0' && c
<= '9')
1223 if (s
- s1
> 8 || L
> 19999)
1224 /* Avoid confusion from exponents
1225 * so large that e might overflow.
1227 e
= 19999; /* safe for 16 bit ints */
1244 /* Now we have nd0 digits, starting at s0, followed by a
1245 * decimal point, followed by nd-nd0 digits. The number we're
1246 * after is the integer represented by those digits times
1251 k
= nd
< DBL_DIG
+ 1 ? nd
: DBL_DIG
+ 1;
1254 rv
= tens
[k
- 9] * rv
+ z
;
1256 #ifndef RND_PRODQUOT
1263 if (e
<= Ten_pmax
) {
1265 goto vax_ovfl_check
;
1267 /* rv = */ rounded_product(rv
, tens
[e
]);
1272 if (e
<= Ten_pmax
+ i
) {
1273 /* A fancier test would sometimes let us do
1274 * this for larger i values.
1279 /* VAX exponent range is so narrow we must
1280 * worry about overflow here...
1283 word0(rv
) -= P
*Exp_msk1
;
1284 /* rv = */ rounded_product(rv
, tens
[e
]);
1285 if ((word0(rv
) & Exp_mask
)
1286 > Exp_msk1
*(DBL_MAX_EXP
+Bias
-1-P
))
1288 word0(rv
) += P
*Exp_msk1
;
1290 /* rv = */ rounded_product(rv
, tens
[e
]);
1295 #ifndef Inaccurate_Divide
1296 else if (e
>= -Ten_pmax
) {
1297 /* rv = */ rounded_quotient(rv
, tens
[-e
]);
1304 /* Get starting approximation = rv * 10**e1 */
1307 if ( (i
= e1
& 15) )
1309 if ( (e1
&= ~15) ) {
1310 if (e1
> DBL_MAX_10_EXP
) {
1312 __set_errno(ERANGE
);
1317 for (j
= 0; e1
> 1; j
++, e1
>>= 1)
1320 /* The last multiplication could overflow. */
1321 word0(rv
) -= P
*Exp_msk1
;
1323 if ((z
= word0(rv
) & Exp_mask
)
1324 > Exp_msk1
*(DBL_MAX_EXP
+Bias
-P
))
1326 if (z
> Exp_msk1
*(DBL_MAX_EXP
+Bias
-1-P
)) {
1327 /* set to largest number */
1328 /* (Can't trust DBL_MAX) */
1333 word0(rv
) += P
*Exp_msk1
;
1336 } else if (e1
< 0) {
1338 if ( (i
= e1
& 15) )
1340 if ( (e1
&= ~15) ) {
1342 for (j
= 0; e1
> 1; j
++, e1
>>= 1)
1345 /* The last multiplication could underflow. */
1354 __set_errno(ERANGE
);
1359 /* The refinement below will clean
1360 * this approximation up.
1366 /* Now the hard part -- adjusting rv to the correct value.*/
1368 /* Put digits into bd: true value = bd * 10^e */
1370 bd0
= s2b(s0
, nd0
, nd
, y
);
1373 bd
= Balloc(bd0
->k
);
1375 bb
= d2b(rv
, &bbe
, &bbbits
); /* rv = bb * 2^bbe */
1390 #ifdef Sudden_Underflow
1392 j
= 1 + 4*P
- 3 - bbbits
+ ((bbe
+ bbbits
- 1) & 3);
1397 i
= bbe
+ bbbits
- 1; /* logb(rv) */
1398 if (i
< Emin
) /* denormal */
1405 i
= bb2
< bd2
? bb2
: bd2
;
1414 bs
= pow5mult(bs
, bb5
);
1420 bb
= lshift(bb
, bb2
);
1422 bd
= pow5mult(bd
, bd5
);
1424 bd
= lshift(bd
, bd2
);
1426 bs
= lshift(bs
, bs2
);
1427 delta
= diff(bb
, bd
);
1428 dsign
= delta
->sign
;
1432 /* Error is less than half an ulp -- check for
1433 * special case of mantissa a power of two.
1435 if (dsign
|| word1(rv
) || word0(rv
) & Bndry_mask
)
1437 delta
= lshift(delta
,Log2P
);
1438 if (cmp(delta
, bs
) > 0)
1443 /* exactly half-way between */
1445 if ((word0(rv
) & Bndry_mask1
) == Bndry_mask1
1446 && word1(rv
) == 0xffffffff) {
1447 /*boundary case -- increment exponent*/
1448 word0(rv
) = (word0(rv
) & Exp_mask
)
1457 } else if (!(word0(rv
) & Bndry_mask
) && !word1(rv
)) {
1459 /* boundary case -- decrement exponent */
1460 #ifdef Sudden_Underflow
1461 L
= word0(rv
) & Exp_mask
;
1470 L
= (word0(rv
) & Exp_mask
) - Exp_msk1
;
1472 word0(rv
) = L
| Bndry_mask1
;
1473 word1(rv
) = 0xffffffff;
1480 #ifndef ROUND_BIASED
1481 if (!(word1(rv
) & LSB
))
1486 #ifndef ROUND_BIASED
1489 #ifndef Sudden_Underflow
1497 if ((aadj
= ratio(delta
, bs
)) <= 2.) {
1500 else if (word1(rv
) || word0(rv
) & Bndry_mask
) {
1501 #ifndef Sudden_Underflow
1502 if (word1(rv
) == Tiny1
&& !word0(rv
))
1508 /* special case -- power of FLT_RADIX to be */
1509 /* rounded down... */
1511 if (aadj
< 2./FLT_RADIX
)
1512 aadj
= 1./FLT_RADIX
;
1519 aadj1
= dsign
? aadj
: -aadj
;
1520 #ifdef Check_FLT_ROUNDS
1521 switch(FLT_ROUNDS
) {
1522 case 2: /* towards +infinity */
1525 case 0: /* towards 0 */
1526 case 3: /* towards -infinity */
1530 if (FLT_ROUNDS
== 0)
1534 y
= word0(rv
) & Exp_mask
;
1536 /* Check for overflow */
1538 if (y
== Exp_msk1
*(DBL_MAX_EXP
+Bias
-1)) {
1540 word0(rv
) -= P
*Exp_msk1
;
1541 adj
= aadj1
* ulp(rv
);
1543 if ((word0(rv
) & Exp_mask
) >=
1544 Exp_msk1
*(DBL_MAX_EXP
+Bias
-P
)) {
1545 if (word0(rv0
) == Big0
&& word1(rv0
) == Big1
)
1551 word0(rv
) += P
*Exp_msk1
;
1553 #ifdef Sudden_Underflow
1554 if ((word0(rv
) & Exp_mask
) <= P
*Exp_msk1
) {
1556 word0(rv
) += P
*Exp_msk1
;
1557 adj
= aadj1
* ulp(rv
);
1560 if ((word0(rv
) & Exp_mask
) < P
*Exp_msk1
)
1562 if ((word0(rv
) & Exp_mask
) <= P
*Exp_msk1
)
1565 if (word0(rv0
) == Tiny0
1566 && word1(rv0
) == Tiny1
)
1572 word0(rv
) -= P
*Exp_msk1
;
1574 adj
= aadj1
* ulp(rv
);
1578 /* Compute adj so that the IEEE rounding rules will
1579 * correctly round rv + adj in some half-way cases.
1580 * If rv * ulp(rv) is denormalized (i.e.,
1581 * y <= (P-1)*Exp_msk1), we must adjust aadj to avoid
1582 * trouble from bits lost to denormalization;
1583 * example: 1.2e-307 .
1585 if (y
<= (P
-1)*Exp_msk1
&& aadj
>= 1.) {
1586 aadj1
= (double)(int)(aadj
+ 0.5);
1590 adj
= aadj1
* ulp(rv
);
1594 z
= word0(rv
) & Exp_mask
;
1596 /* Can we stop now? */
1599 /* The tolerances below are conservative. */
1600 if (dsign
|| word1(rv
) || word0(rv
) & Bndry_mask
) {
1601 if (aadj
< .4999999 || aadj
> .5000001)
1603 } else if (aadj
< .4999999/FLT_RADIX
)
1620 return sign
? -rv
: rv
;
1624 double __strtod_internal(const char *number
, char **_end
, int group
);
1627 __strtod_internal(const char *number
, char **_end
, int group
)
1629 // ToDo: group is currently not supported!
1632 return strtod(number
, _end
);
1635 // XXX this is not correct
1637 long double __strtold_internal(const char *number
, char **_end
, int group
);
1640 __strtold_internal(const char *number
, char **_end
, int group
)
1642 return __strtod_internal(number
, _end
, group
);
1645 float __strtof_internal(const char *number
, char **_end
, int group
);
1648 __strtof_internal(const char *number
, char **_end
, int group
)
1650 return __strtod_internal(number
, _end
, group
);
1654 /* removed from the build, is only used by __dtoa() */
1657 quorem(Bigint
*b
, Bigint
*S
)
1662 ULong
*bx
, *bxe
, *sx
, *sxe
;
1670 /*debug*/ if (b
->wds
> n
)
1671 /*debug*/ Bug("oversize b in quorem");
1679 q
= *bxe
/ (*sxe
+ 1); /* ensure q <= true quotient */
1681 /*debug*/ if (q
> 9)
1682 /*debug*/ Bug("oversized quotient in quorem");
1690 ys
= (si
& 0xffff) * q
+ carry
;
1691 zs
= (si
>> 16) * q
+ (ys
>> 16);
1693 y
= (*bx
& 0xffff) - (ys
& 0xffff) + borrow
;
1695 Sign_Extend(borrow
, y
);
1696 z
= (*bx
>> 16) - (zs
& 0xffff) + borrow
;
1698 Sign_Extend(borrow
, z
);
1701 ys
= *sx
++ * q
+ carry
;
1703 y
= *bx
- (ys
& 0xffff) + borrow
;
1705 Sign_Extend(borrow
, y
);
1708 } while (sx
<= sxe
);
1711 while (--bxe
> bx
&& !*bxe
)
1716 if (cmp(b
, S
) >= 0) {
1725 ys
= (si
& 0xffff) + carry
;
1726 zs
= (si
>> 16) + (ys
>> 16);
1728 y
= (*bx
& 0xffff) - (ys
& 0xffff) + borrow
;
1730 Sign_Extend(borrow
, y
);
1731 z
= (*bx
>> 16) - (zs
& 0xffff) + borrow
;
1733 Sign_Extend(borrow
, z
);
1738 y
= *bx
- (ys
& 0xffff) + borrow
;
1740 Sign_Extend(borrow
, y
);
1743 } while (sx
<= sxe
);
1747 while (--bxe
> bx
&& !*bxe
)
1754 #endif /* removed from the build, is only used by __dtoa() */
1756 /* dtoa for IEEE arithmetic (dmg): convert double to ASCII string.
1758 * Inspired by "How to Print Floating-Point Numbers Accurately" by
1759 * Guy L. Steele, Jr. and Jon L. White [Proc. ACM SIGPLAN '90, pp. 92-101].
1762 * 1. Rather than iterating, we use a simple numeric overestimate
1763 * to determine k = floor(log10(d)). We scale relevant
1764 * quantities using O(log2(k)) rather than O(k) multiplications.
1765 * 2. For some modes > 2 (corresponding to ecvt and fcvt), we don't
1766 * try to generate digits strictly left to right. Instead, we
1767 * compute with fewer bits and propagate the carry if necessary
1768 * when rounding the final digit up. This is often faster.
1769 * 3. Under the assumption that input will be rounded nearest,
1770 * mode 0 renders 1e23 as 1e23 rather than 9.999999999999999e22.
1771 * That is, we allow equality in stopping tests when the
1772 * round-nearest rule will give the same floating-point value
1773 * as would satisfaction of the stopping test with strict
1775 * 4. We remove common factors of powers of 2 from relevant
1777 * 5. When converting floating-point integers less than 1e16,
1778 * we use floating-point arithmetic rather than resorting
1779 * to multiple-precision integers.
1780 * 6. When asked to produce fewer than 15 digits, we first try
1781 * to get by with floating-point arithmetic; we resort to
1782 * multiple-precision integer arithmetic only if we cannot
1783 * guarantee that the floating-point calculation has given
1784 * the correctly rounded result. For k requested digits and
1785 * "uniformly" distributed input, the probability is
1786 * something like 10^(k-15) that we must resort to the Long
1792 __dtoa(double d
, int mode
, int ndigits
, int *decpt
, int *sign
, char **rve
,
1795 /* Arguments ndigits, decpt, sign are similar to those
1796 of ecvt and fcvt; trailing zeros are suppressed from
1797 the returned string. If not null, *rve is set to point
1798 to the end of the return value. If d is +-Infinity or NaN,
1799 then *decpt is set to 9999.
1802 0 ==> shortest string that yields d when read in
1803 and rounded to nearest.
1804 1 ==> like 0, but with Steele & White stopping rule;
1805 e.g. with IEEE P754 arithmetic , mode 0 gives
1806 1e23 whereas mode 1 gives 9.999999999999999e22.
1807 2 ==> max(1,ndigits) significant digits. This gives a
1808 return value similar to that of ecvt, except
1809 that trailing zeros are suppressed.
1810 3 ==> through ndigits past the decimal point. This
1811 gives a return value similar to that from fcvt,
1812 except that trailing zeros are suppressed, and
1813 ndigits can be negative.
1814 4-9 should give the same return values as 2-3, i.e.,
1815 4 <= mode <= 9 ==> same return as mode
1816 2 + (mode & 1). These modes are mainly for
1817 debugging; often they run slower but sometimes
1818 faster than modes 2-3.
1819 4,5,8,9 ==> left-to-right digit generation.
1820 6-9 ==> don't try fast floating-point estimate
1823 Values of mode other than 0-9 are treated as mode 0.
1825 Sufficient space is allocated to the return value
1826 to hold the suppressed trailing zeros.
1829 int bbits
, b2
, b5
, be
, dig
, i
, ieps
, ilim
, ilim0
, ilim1
,
1830 j
, j1
, k
, k0
, k_check
, leftright
, m2
, m5
, s2
, s5
,
1831 spec_case
, try_quick
;
1833 #ifndef Sudden_Underflow
1837 Bigint
*b
, *b1
, *delta
, *mlo
, *mhi
, *S
;
1841 if (word0(d
) & Sign_bit
) {
1842 /* set sign for everything, including 0's and NaNs */
1844 word0(d
) &= ~Sign_bit
; /* clear sign bit */
1849 #if defined(IEEE_Arith) + defined(VAX)
1851 if ((word0(d
) & Exp_mask
) == Exp_mask
)
1853 if (word0(d
) == 0x8000)
1856 /* Infinity or NaN */
1860 !word1(d
) && !(word0(d
) & 0xfffff) ? "Infinity" :
1873 d
+= 0; /* normalize */
1883 b
= d2b(d
, &be
, &bbits
);
1884 #ifdef Sudden_Underflow
1885 i
= (int)(word0(d
) >> Exp_shift1
& (Exp_mask
>>Exp_shift1
));
1887 if ( (i
= (int)((word0(d
) >> Exp_shift1
) & (Exp_mask
>>Exp_shift1
))) ) {
1890 word0(d2
) &= Frac_mask1
;
1891 word0(d2
) |= Exp_11
;
1893 if ( (j
= 11 - hi0bits(word0(d2
) & Frac_mask
)) )
1897 /* log(x) ~=~ log(1.5) + (x-1.5)/1.5
1898 * log10(x) = log(x) / log(10)
1899 * ~=~ log(1.5)/log(10) + (x-1.5)/(1.5*log(10))
1900 * log10(d) = (i-Bias)*log(2)/log(10) + log10(d2)
1902 * This suggests computing an approximation k to log10(d) by
1904 * k = (i - Bias)*0.301029995663981
1905 * + ( (d2-1.5)*0.289529654602168 + 0.176091259055681 );
1907 * We want k to be too large rather than too small.
1908 * The error in the first-order Taylor series approximation
1909 * is in our favor, so we just round up the constant enough
1910 * to compensate for any error in the multiplication of
1911 * (i - Bias) by 0.301029995663981; since |i - Bias| <= 1077,
1912 * and 1077 * 0.30103 * 2^-52 ~=~ 7.2e-14,
1913 * adding 1e-13 to the constant term more than suffices.
1914 * Hence we adjust the constant term to 0.1760912590558.
1915 * (We could get a more accurate k by invoking log10,
1916 * but this is probably not worthwhile.)
1924 #ifndef Sudden_Underflow
1927 /* d is denormalized */
1929 i
= bbits
+ be
+ (Bias
+ (P
-1) - 1);
1930 x
= i
> 32 ? ((word0(d
) << (64 - i
)) | (word1(d
) >> (i
- 32)))
1931 : (word1(d
) << (32 - i
));
1933 word0(d2
) -= 31*Exp_msk1
; /* adjust exponent */
1934 i
-= (Bias
+ (P
-1) - 1) + 1;
1938 ds
= (d2
-1.5)*0.289529654602168 + 0.1760912590558 + i
*0.301029995663981;
1940 if (ds
< 0. && ds
!= k
)
1941 k
--; /* want k = floor(ds) */
1943 if (k
>= 0 && k
<= Ten_pmax
) {
1965 if (mode
< 0 || mode
> 9)
1986 ilim
= ilim1
= i
= ndigits
;
1992 i
= ndigits
+ k
+ 1;
1998 *resultp
= (char *) malloc(i
+ 1);
2001 if (ilim
>= 0 && ilim
<= Quick_max
&& try_quick
) {
2003 /* Try to get by with floating-point arithmetic. */
2009 ieps
= 2; /* conservative */
2014 /* prevent overflows */
2016 d
/= bigtens
[n_bigtens
-1];
2019 for (; j
; j
>>= 1, i
++)
2025 } else if ( (j1
= -k
) ) {
2026 d
*= tens
[j1
& 0xf];
2027 for (j
= j1
>> 4; j
; j
>>= 1, i
++)
2033 if (k_check
&& d
< 1. && ilim
> 0) {
2042 word0(eps
) -= (P
-1)*Exp_msk1
;
2052 #ifndef No_leftright
2054 /* Use Steele & White method of only
2055 * generating digits needed.
2057 eps
= 0.5/tens
[ilim
-1] - eps
;
2061 *s
++ = '0' + (int)L
;
2073 /* Generate ilim digits, then fix them up. */
2074 eps
*= tens
[ilim
-1];
2075 for (i
= 1;; i
++, d
*= 10.) {
2078 *s
++ = '0' + (int)L
;
2082 else if (d
< 0.5 - eps
) {
2083 while (*--s
== '0');
2090 #ifndef No_leftright
2100 /* Do we have a "small" integer? */
2102 if (be
>= 0 && k
<= Int_max
) {
2105 if (ndigits
< 0 && ilim
<= 0) {
2107 if (ilim
< 0 || d
<= 5*ds
)
2114 #ifdef Check_FLT_ROUNDS
2115 /* If FLT_ROUNDS == 2, L will usually be high by 1 */
2121 *s
++ = '0' + (int)L
;
2124 if (d
> ds
|| (d
== ds
&& L
& 1)) {
2148 #ifndef Sudden_Underflow
2149 denorm
? be
+ (Bias
+ (P
-1) - 1 + 1) :
2152 1 + 4*P
- 3 - bbits
+ ((bbits
+ be
- 1) & 3);
2165 if ((i
= ilim
) < 0) {
2174 if (m2
> 0 && s2
> 0) {
2175 i
= m2
< s2
? m2
: s2
;
2183 mhi
= pow5mult(mhi
, m5
);
2188 if ( (j
= b5
- m5
) )
2191 b
= pow5mult(b
, b5
);
2195 S
= pow5mult(S
, s5
);
2197 /* Check for special case that d is a normalized power of 2. */
2200 if (!word1(d
) && !(word0(d
) & Bndry_mask
)
2201 #ifndef Sudden_Underflow
2202 && word0(d
) & Exp_mask
2205 /* The special case */
2213 /* Arrange for convenient computation of quotients:
2214 * shift left if necessary so divisor has 4 leading 0 bits.
2216 * Perhaps we should just compute leading 28 bits of S once
2217 * and for all and pass them and a shift to quorem, so it
2218 * can do shifts and ors to compute the numerator for q.
2221 if ( (i
= ((s5
? 32 - hi0bits(S
->x
[S
->wds
-1]) : 1) + s2
) & 0x1f) )
2224 if ( (i
= ((s5
? 32 - hi0bits(S
->x
[S
->wds
-1]) : 1) + s2
) & 0xf) )
2245 b
= multadd(b
, 10, 0); /* we botched the k estimate */
2247 mhi
= multadd(mhi
, 10, 0);
2251 if (ilim
<= 0 && mode
> 2) {
2252 if (ilim
< 0 || cmp(b
,S
= multadd(S
,5,0)) <= 0) {
2253 /* no digits, fcvt style */
2265 mhi
= lshift(mhi
, m2
);
2267 /* Compute mlo -- check for special case
2268 * that d is a normalized power of 2.
2273 mhi
= Balloc(mhi
->k
);
2275 mhi
= lshift(mhi
, Log2P
);
2279 dig
= quorem(b
,S
) + '0';
2280 /* Do we yet have the shortest decimal string
2281 * that will round to d?
2284 delta
= diff(S
, mhi
);
2285 j1
= delta
->sign
? 1 : cmp(b
, delta
);
2287 #ifndef ROUND_BIASED
2288 if (j1
== 0 && !mode
&& !(word1(d
) & 1)) {
2297 if (j
< 0 || (j
== 0 && !mode
2298 #ifndef ROUND_BIASED
2305 if ((j1
> 0 || (j1
== 0 && dig
& 1))
2313 if (dig
== '9') { /* possible if i == 1 */
2324 b
= multadd(b
, 10, 0);
2326 mlo
= mhi
= multadd(mhi
, 10, 0);
2328 mlo
= multadd(mlo
, 10, 0);
2329 mhi
= multadd(mhi
, 10, 0);
2334 *s
++ = dig
= quorem(b
,S
) + '0';
2337 b
= multadd(b
, 10, 0);
2340 /* Round off last digit */
2344 if (j
> 0 || (j
== 0 && dig
& 1)) {
2354 while (*--s
== '0');
2360 if (mlo
&& mlo
!= mhi
)
2366 if (s
== s0
) { /* don't return empty string */
2376 #endif // 0 -> __dtoa() is removed from the build