Cygwin: mmap: allow remapping part of an existing anonymous mapping
[newlib-cygwin.git] / newlib / libc / stdlib / gdtoa-ldtoa.c
blobd5db270a67ad01171c6b3cd4f174e401a318f052
1 /* $OpenBSD: ldtoa.c,v 1.4 2016/03/09 16:28:47 deraadt Exp $ */
2 /*-
3 * Copyright (c) 2003 David Schultz <das@FreeBSD.ORG>
4 * All rights reserved.
6 * Redistribution and use in source and binary forms, with or without
7 * modification, are permitted provided that the following conditions
8 * are met:
9 * 1. Redistributions of source code must retain the above copyright
10 * notice, this list of conditions and the following disclaimer.
11 * 2. Redistributions in binary form must reproduce the above copyright
12 * notice, this list of conditions and the following disclaimer in the
13 * documentation and/or other materials provided with the distribution.
15 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
16 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
17 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
18 * ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
19 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
20 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
21 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
22 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
23 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
24 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
25 * SUCH DAMAGE.
28 #include <newlib.h>
29 #include <sys/config.h>
31 #ifdef _USE_GDTOA
32 #include <sys/types.h>
33 #include <machine/ieee.h>
34 #include <float.h>
35 #include <stdint.h>
36 #include <limits.h>
37 #include <math.h>
38 #include <stdlib.h>
39 #include "gdtoaimp.h"
41 #if (LDBL_MANT_DIG > DBL_MANT_DIG)
44 * ldtoa() is a wrapper for gdtoa() that makes it smell like dtoa(),
45 * except that the floating point argument is passed by reference.
46 * When dtoa() is passed a NaN or infinity, it sets expt to 9999.
47 * However, a long double could have a valid exponent of 9999, so we
48 * use INT_MAX in ldtoa() instead.
50 char *
51 _ldtoa_r(struct _reent *ptr,
52 long double ld, int mode, int ndigits, int *decpt, int *sign, char **rve)
54 FPI fpi = {
55 LDBL_MANT_DIG, /* nbits */
56 LDBL_MIN_EXP - LDBL_MANT_DIG, /* emin */
57 LDBL_MAX_EXP - LDBL_MANT_DIG, /* emax */
58 FLT_ROUNDS, /* rounding */
59 #ifdef Sudden_Underflow /* unused, but correct anyway */
61 #else
63 #endif
65 int be, kind;
66 char *ret;
67 struct ieee_ext *p = (struct ieee_ext *)&ld;
68 uint32_t bits[(LDBL_MANT_DIG + 31) / 32];
69 void *vbits = bits;
71 _REENT_CHECK_MP (ptr);
73 /* reentrancy addition to use mprec storage pool */
74 if (_REENT_MP_RESULT (ptr)) {
75 freedtoa (ptr, (char *) _REENT_MP_RESULT (ptr));
76 _REENT_MP_RESULT (ptr) = 0;
80 * gdtoa doesn't know anything about the sign of the number, so
81 * if the number is negative, we need to swap rounding modes of
82 * 2 (upwards) and 3 (downwards).
84 *sign = p->ext_sign;
85 fpi.rounding ^= (fpi.rounding >> 1) & p->ext_sign;
87 be = p->ext_exp - (LDBL_MAX_EXP - 1) - (LDBL_MANT_DIG - 1);
88 EXT_TO_ARRAY32(p, bits);
90 switch (fpclassify(ld)) {
91 case FP_NORMAL:
92 kind = STRTOG_Normal;
93 #ifdef EXT_IMPLICIT_NBIT
94 bits[LDBL_MANT_DIG / 32] |= 1 << ((LDBL_MANT_DIG - 1) % 32);
95 #endif /* EXT_IMPLICIT_NBIT */
96 break;
97 case FP_ZERO:
98 kind = STRTOG_Zero;
99 break;
100 case FP_SUBNORMAL:
101 kind = STRTOG_Denormal;
102 be++;
103 break;
104 case FP_INFINITE:
105 kind = STRTOG_Infinite;
106 break;
107 case FP_NAN:
108 kind = STRTOG_NaN;
109 break;
110 default:
111 abort();
114 ret = gdtoa(ptr, &fpi, be, vbits, &kind, mode, ndigits, decpt, rve);
115 if (*decpt == -32768)
116 *decpt = INT_MAX;
117 return ret;
119 DEF_STRONG(_ldtoa_r);
121 #else /* (LDBL_MANT_DIG == DBL_MANT_DIG) */
123 char *
124 _ldtoa_r(struct _reent *ptr,
125 long double ld, int mode, int ndigits, int *decpt, int *sign,
126 char **rve)
128 char *ret;
130 ret = _dtoa_r(ptr, (double)ld, mode, ndigits, decpt, sign, rve);
131 if (*decpt == 9999)
132 *decpt = INT_MAX;
133 return ret;
135 DEF_STRONG(_ldtoa_r);
137 #endif /* (LDBL_MANT_DIG == DBL_MANT_DIG) */
139 /* Routine used to tell if long double is NaN or Infinity or regular number.
140 Returns: 0 = regular number
141 1 = Nan
142 2 = Infinity
145 _ldcheck (long double *d)
147 switch (fpclassify(*d)) {
148 case FP_NAN:
149 return 1;
150 case FP_INFINITE:
151 return 2;
152 default:
153 return 0;
157 #endif /* _USE_GDTOA */