1 /****************************************************************
3 The author of this software is David M. Gay.
5 Copyright (C) 1998-2001 by Lucent Technologies
8 Permission to use, copy, modify, and distribute this software and
9 its documentation for any purpose and without fee is hereby
10 granted, provided that the above copyright notice appear in all
11 copies and that both that the copyright notice and this
12 permission notice and warranty disclaimer appear in supporting
13 documentation, and that the name of Lucent or any of its entities
14 not be used in advertising or publicity pertaining to
15 distribution of the software without specific, written prior
18 LUCENT DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS SOFTWARE,
19 INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS.
20 IN NO EVENT SHALL LUCENT OR ANY OF ITS ENTITIES BE LIABLE FOR ANY
21 SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
22 WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER
23 IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION,
24 ARISING OUT OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OF
27 ****************************************************************/
29 /* Please send bug reports to David M. Gay (dmg at acm dot org,
30 * with " at " changed at "@" and " dot " changed to "."). */
41 #if defined (_HAVE_LONG_DOUBLE) && !defined (_LDBL_EQ_DBL)
46 fivesbits
[] = { 0, 3, 5, 7, 10, 12, 14, 17, 19, 21,
47 24, 26, 28, 31, 33, 35, 38, 40, 42, 45,
55 sum (struct _reent
*p
, _Bigint
*a
, _Bigint
*b
)
58 __ULong carry
, *xc
, *xa
, *xb
, *xe
, y
;
63 if (a
->_wds
< b
->_wds
) {
66 c
= eBalloc(p
, a
->_k
);
75 y
= (*xa
& 0xffff) + (*xb
& 0xffff) + carry
;
76 carry
= (y
& 0x10000) >> 16;
77 z
= (*xa
++ >> 16) + (*xb
++ >> 16) + carry
;
78 carry
= (z
& 0x10000) >> 16;
82 xe
+= a
->_wds
- b
->_wds
;
84 y
= (*xa
& 0xffff) + carry
;
85 carry
= (y
& 0x10000) >> 16;
86 z
= (*xa
++ >> 16) + carry
;
87 carry
= (z
& 0x10000) >> 16;
92 y
= *xa
++ + *xb
++ + carry
;
93 carry
= (y
& 0x10000) >> 16;
97 xe
+= a
->_wds
- b
->_wds
;
100 carry
= (y
& 0x10000) >> 16;
105 if (c
->_wds
== c
->_maxwds
) {
106 b
= eBalloc(p
, c
->_k
+ 1);
111 c
->_x
[c
->_wds
++] = 1;
117 rshift (_Bigint
*b
, int k
)
119 __ULong
*x
, *x1
, *xe
, y
;
131 *x1
++ = (y
| (*x
<< n
)) & ALL_ON
;
141 if ((b
->_wds
= x1
- b
->_x
) == 0)
153 for(n
= 0; x
< xe
&& !*x
; x
++)
163 increment (struct _reent
*p
, _Bigint
*b
)
168 __ULong carry
= 1, y
;
175 if (*x
< (__ULong
)0xffffffffL
) {
192 if (b
->_wds
>= b
->_maxwds
) {
193 b1
= eBalloc(p
,b
->_k
+1);
198 b
->_x
[b
->_wds
++] = 1;
204 decrement (_Bigint
*b
)
208 __ULong borrow
= 1, y
;
225 borrow
= (y
& 0x10000) >> 16;
227 } while(borrow
&& x
< xe
);
229 return STRTOG_Inexlo
;
233 all_on (_Bigint
*b
, int n
)
238 xe
= x
+ (n
>> kshift
);
240 if ((*x
++ & ALL_ON
) != ALL_ON
)
243 return ((*x
| (ALL_ON
<< n
)) & ALL_ON
) == ALL_ON
;
248 set_ones (struct _reent
*p
, _Bigint
*b
, int n
)
253 k
= (n
+ ((1 << kshift
) - 1)) >> kshift
;
267 x
[-1] >>= ULbits
- n
;
272 rvOK (struct _reent
*p
, double d
, FPI
*fpi
, Long
*exp
, __ULong
*bits
, int exact
,
276 __ULong carry
, inex
, lostbits
;
277 int bdif
, e
, j
, k
, k1
, nb
, rv
;
280 b
= d2b(p
, d
, &e
, &bdif
);
281 bdif
-= nb
= fpi
->nbits
;
290 #ifndef IMPRECISE_INEXACT
307 default: /* round near */
318 if (b
->_x
[k
>>kshift
] & ((__ULong
)1 << (k
& kmask
)))
322 /* "break" cases: round up 1 bit, then truncate; bdif > 0 */
327 if ( (lostbits
= any_on(b
, bdif
)) !=0)
328 inex
= STRTOG_Inexlo
;
331 inex
= STRTOG_Inexhi
;
333 if ( (j
= nb
& kmask
) !=0)
335 if (hi0bits(b
->_x
[b
->_wds
- 1]) != j
) {
337 lostbits
= b
->_x
[0] & 1;
344 b
= lshift(p
, b
, -bdif
);
348 if (k
> nb
|| fpi
->sudden_underflow
) {
350 *irv
= STRTOG_Underflow
| STRTOG_Inexlo
;
357 if (k1
> 0 && !lostbits
)
358 lostbits
= any_on(b
, k1
);
359 if (!lostbits
&& !exact
)
362 carry
= b
->_x
[k1
>>kshift
] & (1 << (k1
& kmask
));
364 *irv
= STRTOG_Denormal
;
367 inex
= STRTOG_Inexhi
| STRTOG_Underflow
;
373 inex
= STRTOG_Inexlo
| STRTOG_Underflow
;
379 else if (e
> fpi
->emax
) {
381 *irv
= STRTOG_Infinite
| STRTOG_Overflow
| STRTOG_Inexhi
;
388 copybits(bits
, nb
, b
);
401 L
= word1(d
) << 16 | word1(d
) >> 16;
404 if ( (L
= word1(d
)) !=0)
406 return P
- lo0bits(&L
);
408 L
= word0(d
) << 16 | word0(d
) >> 16 | Exp_msk11
;
410 L
= word0(d
) | Exp_msk1
;
412 return P
- 32 - lo0bits(&L
);
416 _strtodg_l (struct _reent
*p
, const char *s00
, char **se
, FPI
*fpi
, Long
*exp
,
417 __ULong
*bits
, locale_t loc
)
419 int abe
, abits
, asub
;
420 int bb0
, bb2
, bb5
, bbe
, bd2
, bd5
, bbbits
, bs2
, c
, decpt
, denorm
;
421 int dsign
, e
, e1
, e2
, emin
, esign
, finished
, i
, inex
, irv
;
422 int j
, k
, nbits
, nd
, nd0
, nf
, nz
, nz0
, rd
, rvbits
, rve
, rve1
, sign
;
423 int sudden_underflow
;
424 const char *s
, *s0
, *s1
;
425 //double adj, adj0, rv, tol;
430 _Bigint
*ab
, *bb
, *bb1
, *bd
, *bd0
, *bs
, *delta
, *rvb
, *rvb0
;
431 const char *decimal_point
= __get_numeric_locale(loc
)->decimal_point
;
432 int dec_len
= strlen (decimal_point
);
435 denorm
= sign
= nz0
= nz
= 0;
439 for(s
= s00
;;s
++) switch(*s
) {
449 irv
= STRTOG_NoNumber
;
468 irv
= gethex(p
, &s
, fpi
, exp
, &rvb
, sign
, loc
);
469 if (irv
== STRTOG_NoNumber
) {
481 sudden_underflow
= fpi
->sudden_underflow
;
484 for(decpt
= nd
= nf
= 0; (c
= *s
) >= '0' && c
<= '9'; nd
++, s
++)
491 if (strncmp (s
, decimal_point
, dec_len
) == 0)
503 for(; c
== '0'; c
= *++s
)
505 if (c
> '0' && c
<= '9') {
513 for(; c
>= '0' && c
<= '9'; c
= *++s
) {
518 for(i
= 1; i
< nz
; i
++)
521 else if (nd
<= DBL_DIG
+ 1)
525 else if (nd
<= DBL_DIG
+ 1)
533 if (c
== 'e' || c
== 'E') {
534 if (!nd
&& !nz
&& !nz0
) {
535 irv
= STRTOG_NoNumber
;
547 if (c
>= '0' && c
<= '9') {
550 if (c
> '0' && c
<= '9') {
553 while((c
= *++s
) >= '0' && c
<= '9')
555 if (s
- s1
> 8 || L
> 19999)
556 /* Avoid confusion from exponents
557 * so large that e might overflow.
559 e
= 19999; /* safe for 16 bit ints */
574 /* Check for Nan and Infinity */
579 if (match(&s
,"nf")) {
581 if (!match(&s
,"inity"))
583 irv
= STRTOG_Infinite
;
589 if (match(&s
, "an")) {
591 *exp
= fpi
->emax
+ 1;
594 irv
= hexnan(&s
, fpi
, bits
);
599 #endif /* INFNAN_CHECK */
600 irv
= STRTOG_NoNumber
;
609 switch(fpi
->rounding
& 3) {
620 /* Now we have nd0 digits, starting at s0, followed by a
621 * decimal point, followed by nd-nd0 digits. The number we're
622 * after is the integer represented by those digits times
627 k
= nd
< DBL_DIG
+ 1 ? nd
: DBL_DIG
+ 1;
630 dval(rv
) = tens
[k
- 9] * dval(rv
) + z
;
632 if (nbits
<= P
&& nd
<= DBL_DIG
) {
634 if (rvOK(p
, dval(rv
), fpi
, exp
, bits
, 1, rd
, &irv
))
642 i
= fivesbits
[e
] + mantbits(rv
) <= P
;
643 /* rv = */ rounded_product(dval(rv
), tens
[e
]);
644 if (rvOK(p
, dval(rv
), fpi
, exp
, bits
, i
, rd
, &irv
))
651 if (e
<= Ten_pmax
+ i
) {
652 /* A fancier test would sometimes let us do
653 * this for larger i values.
659 /* VAX exponent range is so narrow we must
660 * worry about overflow here...
663 dval(adj
) = dval(rv
);
664 word0(adj
) -= P
*Exp_msk1
;
665 /* adj = */ rounded_product(dval(adj
), tens
[e2
]);
666 if ((word0(adj
) & Exp_mask
)
667 > Exp_msk1
*(DBL_MAX_EXP
+Bias
-1-P
))
669 word0(adj
) += P
*Exp_msk1
;
670 dval(rv
) = dval(adj
);
672 /* rv = */ rounded_product(dval(rv
), tens
[e2
]);
674 if (rvOK(p
, dval(rv
), fpi
, exp
, bits
, 0, rd
, &irv
))
679 #ifndef Inaccurate_Divide
680 else if (e
>= -Ten_pmax
) {
681 /* rv = */ rounded_quotient(dval(rv
), tens
[-e
]);
682 if (rvOK(p
, dval(rv
), fpi
, exp
, bits
, 0, rd
, &irv
))
691 /* Get starting approximation = rv * 10**e1 */
695 if ( (i
= e1
& 15) !=0)
699 while(e1
>= (1 << (n_bigtens
-1))) {
700 e2
+= ((word0(rv
) & Exp_mask
)
701 >> Exp_shift1
) - Bias
;
702 word0(rv
) &= ~Exp_mask
;
703 word0(rv
) |= Bias
<< Exp_shift1
;
704 dval(rv
) *= bigtens
[n_bigtens
-1];
705 e1
-= 1 << (n_bigtens
-1);
707 e2
+= ((word0(rv
) & Exp_mask
) >> Exp_shift1
) - Bias
;
708 word0(rv
) &= ~Exp_mask
;
709 word0(rv
) |= Bias
<< Exp_shift1
;
710 for(j
= 0; e1
> 0; j
++, e1
>>= 1)
712 dval(rv
) *= bigtens
[j
];
717 if ( (i
= e1
& 15) !=0)
721 while(e1
>= (1 << (n_bigtens
-1))) {
722 e2
+= ((word0(rv
) & Exp_mask
)
723 >> Exp_shift1
) - Bias
;
724 word0(rv
) &= ~Exp_mask
;
725 word0(rv
) |= Bias
<< Exp_shift1
;
726 dval(rv
) *= tinytens
[n_bigtens
-1];
727 e1
-= 1 << (n_bigtens
-1);
729 e2
+= ((word0(rv
) & Exp_mask
) >> Exp_shift1
) - Bias
;
730 word0(rv
) &= ~Exp_mask
;
731 word0(rv
) |= Bias
<< Exp_shift1
;
732 for(j
= 0; e1
> 0; j
++, e1
>>= 1)
734 dval(rv
) *= tinytens
[j
];
738 /* e2 is a correction to the (base 2) exponent of the return
739 * value, reflecting adjustments above to avoid overflow in the
740 * native arithmetic. For native IBM (base 16) arithmetic, we
741 * must multiply e2 by 4 to change from base 16 to 2.
745 rvb
= d2b(p
, dval(rv
), &rve
, &rvbits
); /* rv = rvb * 2^rve */
747 if ((j
= rvbits
- nbits
) > 0) {
752 bb0
= 0; /* trailing zero bits in rvb */
753 e2
= rve
+ rvbits
- nbits
;
754 if (e2
> fpi
->emax
+ 1)
756 rve1
= rve
+ rvbits
- nbits
;
757 if (e2
< (emin
= fpi
->emin
)) {
761 rvb
= lshift(p
, rvb
, j
);
772 irv
= STRTOG_Underflow
| STRTOG_Inexlo
;
778 rvb
->_x
[0] = rvb
->_wds
= rvbits
= 1;
784 if (sudden_underflow
&& e2
+ 1 < emin
)
788 /* Now the hard part -- adjusting rv to the correct value.*/
790 /* Put digits into bd: true value = bd * 10^e */
792 bd0
= s2b(p
, s0
, nd0
, nd
, y
);
795 bd
= eBalloc(p
,bd0
->_k
);
797 bb
= eBalloc(p
,rvb
->_k
);
799 bbbits
= rvbits
- bb0
;
816 j
= nbits
+ 1 - bbbits
;
817 i
= bbe
+ bbbits
- nbits
;
818 if (i
< emin
) /* denormal */
822 i
= bb2
< bd2
? bb2
: bd2
;
831 bs
= pow5mult(p
, bs
, bb5
);
832 bb1
= mult(p
, bs
, bb
);
838 bb
= lshift(p
, bb
, bb2
);
842 bd
= pow5mult(p
, bd
, bd5
);
844 bd
= lshift(p
, bd
, bd2
);
846 bs
= lshift(p
, bs
, bs2
);
848 inex
= STRTOG_Inexhi
;
849 delta
= diff(p
, bb
, bd
);
850 if (delta
->_wds
<= 1 && !delta
->_x
[0])
852 dsign
= delta
->_sign
;
853 delta
->_sign
= finished
= 0;
858 if ( (finished
= dsign
^ (rd
&1)) !=0) {
860 irv
|= STRTOG_Inexhi
;
863 irv
|= STRTOG_Inexlo
;
866 for(i
= 0, j
= nbits
; j
>= ULbits
;
868 if (rvb
->_x
[i
] & ALL_ON
)
871 if (j
> 1 && lo0bits(rvb
->_x
+ i
) < j
- 1)
874 rvb
= set_ones(p
, rvb
, rvbits
= nbits
);
877 irv
|= dsign
? STRTOG_Inexlo
: STRTOG_Inexhi
;
881 /* Error is less than half an ulp -- check for
882 * special case of mantissa a power of two.
885 ? STRTOG_Normal
| STRTOG_Inexlo
886 : STRTOG_Normal
| STRTOG_Inexhi
;
887 if (dsign
|| bbbits
> 1 || denorm
|| rve1
== emin
)
889 delta
= lshift(p
, delta
,1);
890 if (cmp(delta
, bs
) > 0) {
891 irv
= STRTOG_Normal
| STRTOG_Inexlo
;
897 /* exactly half-way between */
899 if (denorm
&& all_on(rvb
, rvbits
)) {
900 /*boundary case -- increment exponent*/
903 rve
= emin
+ nbits
- (rvbits
= 1);
904 irv
= STRTOG_Normal
| STRTOG_Inexhi
;
908 irv
= STRTOG_Normal
| STRTOG_Inexlo
;
910 else if (bbbits
== 1) {
913 /* boundary case -- decrement exponent */
915 irv
= STRTOG_Normal
| STRTOG_Inexhi
;
916 if (rvb
->_wds
== 1 && rvb
->_x
[0] == 1)
917 sudden_underflow
= 1;
921 rvb
= set_ones(p
, rvb
, rvbits
= nbits
);
925 irv
= STRTOG_Normal
| STRTOG_Inexhi
;
926 if ((bbbits
< nbits
&& !denorm
) || !(rvb
->_x
[0] & 1))
929 rvb
= increment(p
, rvb
);
930 j
= kmask
& (ULbits
- (rvbits
& kmask
));
931 if (hi0bits(rvb
->_x
[rvb
->_wds
- 1]) != j
)
933 irv
= STRTOG_Normal
| STRTOG_Inexhi
;
939 irv
= STRTOG_Normal
| STRTOG_Inexlo
;
943 if ((dval(adj
) = ratio(delta
, bs
)) <= 2.) {
945 inex
= STRTOG_Inexlo
;
948 inex
= STRTOG_Inexhi
;
950 else if (denorm
&& bbbits
<= 1) {
954 irv
= STRTOG_Underflow
| STRTOG_Inexlo
;
960 adj0
= dval(adj
) = 1.;
963 adj0
= dval(adj
) *= 0.5;
966 inex
= STRTOG_Inexlo
;
968 if (dval(adj
) < 2147483647.) {
977 if (asub
&& adj0
> 0.)
981 if (!asub
&& adj0
> 0.) {
984 inex
= STRTOG_Inexact
- inex
;
992 /* adj *= ulp(dval(rv)); */
993 /* if (asub) rv -= adj; else rv += adj; */
995 if (!denorm
&& rvbits
< nbits
) {
996 rvb
= lshift(p
, rvb
, j
= nbits
- rvbits
);
1000 ab
= d2b(p
, dval(adj
), &abe
, &abits
);
1004 ab
= lshift(p
, ab
, abe
);
1008 j
= hi0bits(rvb
->_x
[rvb
->_wds
-1]);
1009 rvb
= diff(p
, rvb
, ab
);
1013 else if (rvb
->_wds
<= k
1014 || hi0bits( rvb
->_x
[k
]) >
1015 hi0bits(rvb0
->_x
[k
])) {
1016 /* unlikely; can only have lost 1 high bit */
1022 rvb
= lshift(p
, rvb
, 1);
1030 rvb
= sum(p
, rvb
, ab
);
1033 || hi0bits(rvb
->_x
[k
]) < hi0bits(rvb0
->_x
[k
])) {
1035 if (++rvbits
== nbits
)
1053 /* Can we stop now? */
1054 tol
= dval(adj
) * 5e-16; /* > max rel error */
1055 dval(adj
) = adj0
- .5;
1056 if (dval(adj
) < -tol
) {
1062 else if (dval(adj
) > tol
&& adj0
< 1. - tol
) {
1067 bb0
= denorm
? 0 : trailz(rvb
);
1073 if (!denorm
&& (j
= nbits
- rvbits
)) {
1075 rvb
= lshift(p
, rvb
, j
);
1086 if (rve
> fpi
->emax
) {
1089 irv
= STRTOG_Infinite
| STRTOG_Overflow
| STRTOG_Inexhi
;
1094 *exp
= fpi
->emax
+ 1;
1098 if (sudden_underflow
) {
1100 irv
= STRTOG_Underflow
| STRTOG_Inexlo
;
1106 irv
= (irv
& ~STRTOG_Retmask
) |
1107 (rvb
->_wds
> 0 ? STRTOG_Denormal
: STRTOG_Zero
);
1108 if (irv
& STRTOG_Inexact
)
1109 irv
|= STRTOG_Underflow
;
1120 copybits(bits
, nbits
, rvb
);
1126 #endif /* _HAVE_LONG_DOUBLE && !_LDBL_EQ_DBL */