about summary refs log tree commit diff
path: root/stdlib/strtod.c
diff options
context:
space:
mode:
authorUlrich Drepper <drepper@redhat.com>1997-03-04 05:53:28 +0000
committerUlrich Drepper <drepper@redhat.com>1997-03-04 05:53:28 +0000
commit377a515b4ce100dc119db09a7bc1d7628136993a (patch)
tree92bcdcc43bde79c11ac56b74f05ad4a4dcf3dd96 /stdlib/strtod.c
parentd1a2b102df91d6e478d1fa25d8a3e38f0b98e374 (diff)
downloadglibc-377a515b4ce100dc119db09a7bc1d7628136993a.tar.gz
glibc-377a515b4ce100dc119db09a7bc1d7628136993a.tar.xz
glibc-377a515b4ce100dc119db09a7bc1d7628136993a.zip
1997-03-04 04:31  Ulrich Drepper  <drepper@cygnus.com>

	* Makerules: Add rules to handle versioning.
	* config.h.in (DO_VERSIONING): New macro.
	* config.make.in (versioning): New variable.
	* configure.in: Add checks for .symver directive in gas and
	--version-script option to ld.  Define DO_VERSIONING and
	versioning if appropriate.

	* math/Makefile (routines): Add s_signbit, s_fpclassify, s_fmax,
	s_fmin, and s_fdim.
	* math/math.h: Define ISO C 9X constants, macros and functions.
	* math/mathcalls.h: Likewise.
	* sysdeps/libm-ieee754/s_fdim.c: New file.
	* sysdeps/libm-ieee754/s_fdimf.c: New file.
	* sysdeps/libm-ieee754/s_fdiml.c: New file.
	* sysdeps/libm-ieee754/s_fmax.c: New file.
	* sysdeps/libm-ieee754/s_fmaxf.c: New file.
	* sysdeps/libm-ieee754/s_fmaxl.c: New file.
	* sysdeps/libm-ieee754/s_fmin.c: New file.
	* sysdeps/libm-ieee754/s_fminf.c: New file.
	* sysdeps/libm-ieee754/s_fminl.c: New file.
	* sysdeps/libm-ieee754/s_fpclassify.c: New file.
	* sysdeps/libm-ieee754/s_fpclassifyf.c: New file.
	* sysdeps/libm-ieee754/s_fpclassifyl.c: New file.
	* sysdeps/libm-ieee754/s_signbit.c: New file.
	* sysdeps/libm-ieee754/s_signbitf.c: New file.
	* sysdeps/libm-ieee754/s_signbitl.c: New file.

	* stdio-common/printf_fphex.c: Correct printing of decimal point
	character.
	Simplify conversion of mantissa to string.
	* stdio-common/vfscanf.c: Handle %A format.
	Optimize termination of floating-point scanning.
	* stdio-common/tstscanf.c (main): Add new test to scanf to test
	scanning float values with given width.
	* stdlib/strtod.c: Add handling of floating-point numbers in
	hexadecimal notation.

	* stdlib/stdlib.h: Use __USE_ISOC9X feature macro for new long long
	functions.
	Pretty print #if directives.
	* string/string.h: Pretty print #if directives.

	* sysdeps/ieee754/dbl2mpn.c: Update copyright.
	* sysdeps/ieee754/ldbl2mpn.c: Likewise.
	* sysdeps/ieee754/mpn2dbl.c: Likewise.
	* sysdeps/ieee754/mpn2flt.c: Likewise.
	* sysdeps/ieee754/mpn2ldbl.c: Likewise.

	* sysdeps/unix/sysv/linux/poll.c: Implement poll function by
	falling back to select-based implementation if syscall isn't
	available.
	* sysdeps/unix/sysv/linux/syscalls.list: Add s_poll.

	* time/leapseconds: Update from tzdata1997b.
	* time/zic.c: Update from tzcode1997b.

1997-03-01 15:08  Andreas Schwab  <schwab@issan.informatik.uni-dortmund.de>

	* time/Makefile $(tzfiles:%=$(objpfx)z.%): Remove unneeded
	depedencies between installed $(tzlinks) and $(tzbases) files.

1997-03-01 14:27  Andreas Schwab  <schwab@issan.informatik.uni-dortmund.de>

	* math/math.h: Make compatible with traditional preprocessor;
	requires carefull placement of whitespace in macro arguments.
	Use __CONCAT instead of ##.
	Declare long double functions only if __STDC__ or __GNUC__.
	* math/mathcall.h: Avoid whitespace before argument of macro call
	that is used as function name.

	* sysdeps/m68k/fpu/__math.h: Use __CONCAT instead of ##.
	(__m81_u, __m81_inline): Depend on __LIBC_M81_MATH_INLINES instead
	of __NO_M81_MATH_INLINES.
	[!__LIBC_M81_MATH_INLINES]: Don't define internal functions
	starting with __ieee754.
	[!__NO_MATH_INLINES && __OPTIMIZE__]: Define user visible
	functions as inlines.
	(__m81_defun): Put __attribute__ between return type and function
	name.
	* math/math.h: Include <__math.h> also if __LIBC_M81_MATH_INLINES
	is defined.
	* sysdeps/m68k/fpu/e_acos.c: Define __LIBC_M81_MATH_INLINES
	instead of __NO_M81_MATH_INLINES.
	* sysdeps/m68k/fpu/e_fmod.c: Likewise.
	* sysdeps/m68k/fpu/k_cos.c: Likewise.
	* sysdeps/m68k/fpu/k_sin.c: Likewise.
	* sysdeps/m68k/fpu/k_tan.c: Likewise.
	* sysdeps/m68k/fpu/s_atan.c: Likewise. De-ANSI-declify.
	* sysdeps/m68k/fpu/s_frexp.c: Likewise.
	* sysdeps/m68k/fpu/s_ilogb.c: Likewise.
	* sysdeps/m68k/fpu/s_isinf.c: Likewise.
	* sysdeps/m68k/fpu/s_modf.c: Likewise.
	* sysdeps/m68k/fpu/s_scalbn.c: Likewise.

1997-02-27 21:51  Andreas Schwab  <schwab@issan.informatik.uni-dortmund.de>

	* Makefile (tests): Cope with $PATH not including the current
	directory.

1997-02-27 18:04  Andreas Schwab  <schwab@issan.informatik.uni-dortmund.de>

	* sysdeps/unix/Makefile ($(common-objpfx)mk-local_lim): Use
	$(common-objdir-compile).
	($(common-objpfx)make-ioctls): Likewise.
	(mk-local_lim-CFLAGS): Set this instead of local_lim-CFLAGS.
	($(common-objpfx)sys/param.h): Use $(make-target-directory).
	($(addprefix $(common-objpfx),$(sys/param.h-includes))):
	Likewise.
	($(common-objpfx)sys/syscall.h): Likewise.
	($(common-objpfx)local_lim.h): Let make deal with command
	failure.
	($(common-objpfx)param.h.dep): Use temporary file and update
	target atomically.
	($(common-objpfx)errnos): Avoid the Useless Use of cat Award.
	(include $(common-objpfx)param.h.dep): Ignore error.

	* sysdeps/posix/Makefile ($(common-objpfx)mk-stdiolim): Use
	$(common-objdir-compile).
	(mk-stdiolim-CFLAGS): Renamed from cded-objdir-includes, use
	$(shell pwd) instead of $$cwd.

	* sysdeps/generic/Makefile ($(common-objpfx)det_endian): Use
	$(common-objdir-compile).
	($(objpfx)make_siglist): Use $(native-compile).
	(make_siglist-CFLAGS): New variable.

	* Makerules (ALL_BUILD_CFLAGS): Renamed from BUILD_CFLAGS, leaving
	the old name for the user to pass additional flags to the host
	compiler.  Fix reference to config header.
	(native-compile, common-objdir-compile): Rewritten to make more
	generally usable.
	* sysdeps/unix/sysv/sysv4/solaris2/Makefile: Set ALL_BUILD_CFLAGS
	instead of BUILD_CFLAGS.

	* sysvips/sys/ipc.h: Warn if needed feature select macro are not
	defined.

1997-02-27 17:11  Andreas Schwab  <schwab@issan.informatik.uni-dortmund.de>

	* sunrpc/Makefile ($(objpfx)rpc-proto.d, $(objpfx)rpc-proto.c):
	New rules to generate dependencies for the RPC service objects.

1997-02-27 16:26  Andreas Schwab  <schwab@issan.informatik.uni-dortmund.de>

	* argp/argp-parse.c (parser_finalize): Always set *END_INDEX if
	supplied.

1997-02-28 03:27  Ulrich Drepper  <drepper@cygnus.com>

	* stdlib/strtod.c (STRTOF): Make sure return value is large enough
	so that clearing second word is necessary.

	* sysdeps/unix/sysv/linux/netinet/in_systm.h: Don't use kernel
	header since it is wrong for 64 bit systems.
	Patch by a sun <asun@zoology.washington.edu>.

1997-02-27 10:34:11  Richard Henderson  <rth@tamu.edu>

	* sysdeps/unix/sysv/linux/alpha/brk.S: Support both the Linux/i386
	and OSF/1 style brk syscalls.  We may want to change Linux/Alpha
	for the benefit of running foreign binaries.

1997-03-01 20:21  Miles Bader  <miles@gnu.ai.mit.edu>
1997-02-25 19:42  Miles Bader  <miles@gnu.ai.mit.edu>
Diffstat (limited to 'stdlib/strtod.c')
-rw-r--r--stdlib/strtod.c163
1 files changed, 135 insertions, 28 deletions
diff --git a/stdlib/strtod.c b/stdlib/strtod.c
index ed24c08f2b..316adec5ff 100644
--- a/stdlib/strtod.c
+++ b/stdlib/strtod.c
@@ -40,6 +40,8 @@
 # define CHAR_TYPE wint_t
 # define L_(Ch) L##Ch
 # define ISSPACE(Ch) iswspace (Ch)
+# define ISDIGIT(Ch) iswdigit (Ch)
+# define ISXDIGIT(Ch) iswxdigit (Ch)
 # define TOLOWER(Ch) towlower (Ch)
 # define STRNCASECMP(S1, S2, N) __wcsncasecmp ((S1), (S2), (N))
 #else
@@ -47,6 +49,8 @@
 # define CHAR_TYPE char
 # define L_(Ch) Ch
 # define ISSPACE(Ch) isspace (Ch)
+# define ISDIGIT(Ch) isdigit (Ch)
+# define ISXDIGIT(Ch) isxdigit (Ch)
 # define TOLOWER(Ch) tolower (Ch)
 # define STRNCASECMP(S1, S2, N) __strncasecmp ((S1), (S2), (N))
 #endif
@@ -125,6 +129,7 @@ static const mp_limb_t _tens_in_limb[MAX_DIG_PER_LIMB + 1] =
 #define SWAP(x, y)		({ typeof(x) _tmp = x; x = y; y = _tmp; })
 
 #define NDIG			(MAX_10_EXP - MIN_10_EXP + 2 * MANT_DIG)
+#define HEXNDIG			((MAX_EXP - MIN_EXP + 7) / 8 + 2 * MANT_DIG)
 #define	RETURN_LIMB_SIZE		howmany (MANT_DIG, BITS_PER_MP_LIMB)
 
 #define RETURN(val,end)							      \
@@ -239,7 +244,7 @@ str_to_mpn (const STRING_TYPE *str, int digcnt, mp_limb_t *n, mp_size_t *nsize,
   /* Number of digits for actual limb.  */
   int cnt = 0;
   mp_limb_t low = 0;
-  mp_limb_t base;
+  mp_limb_t start;
 
   *nsize = 0;
   assert (digcnt > 0);
@@ -262,9 +267,10 @@ str_to_mpn (const STRING_TYPE *str, int digcnt, mp_limb_t *n, mp_size_t *nsize,
 	  low = 0;
 	}
 
-      /* There might be thousands separators or radix characters in the string.
-	 But these all can be ignored because we know the format of the number
-	 is correct and we have an exact number of characters to read.  */
+      /* There might be thousands separators or radix characters in
+	 the string.  But these all can be ignored because we know the
+	 format of the number is correct and we have an exact number
+	 of characters to read.  */
       while (*str < L_('0') || *str > L_('9'))
 	++str;
       low = low * 10 + *str++ - L_('0');
@@ -275,11 +281,11 @@ str_to_mpn (const STRING_TYPE *str, int digcnt, mp_limb_t *n, mp_size_t *nsize,
   if (*exponent > 0 && cnt + *exponent <= MAX_DIG_PER_LIMB)
     {
       low *= _tens_in_limb[*exponent];
-      base = _tens_in_limb[cnt + *exponent];
+      start = _tens_in_limb[cnt + *exponent];
       *exponent = 0;
     }
   else
-    base = _tens_in_limb[cnt];
+    start = _tens_in_limb[cnt];
 
   if (*nsize == 0)
     {
@@ -289,11 +295,12 @@ str_to_mpn (const STRING_TYPE *str, int digcnt, mp_limb_t *n, mp_size_t *nsize,
   else
     {
       mp_limb_t cy;
-      cy = __mpn_mul_1 (n, n, *nsize, base);
+      cy = __mpn_mul_1 (n, n, *nsize, start);
       cy += __mpn_add_1 (n, n, *nsize, low);
       if (cy != 0)
 	n[(*nsize)++] = cy;
     }
+
   return str;
 }
 
@@ -346,6 +353,9 @@ INTERNAL (STRTOF) (nptr, endptr, group)
   MPN_VAR (num);		/* MP representation of the number.  */
   int exponent;			/* Exponent of the number.  */
 
+  /* Numbers starting `0X' or `0x' have to be processed with base 16.  */
+  int base = 10;
+
   /* When we have to compute fractional digits we form a fraction with a
      second multi-precision number (and we sometimes need a second for
      temporary results).  */
@@ -485,6 +495,18 @@ INTERNAL (STRTOF) (nptr, endptr, group)
       RETURN (0.0, nptr);
     }
 
+  /* First look whether we are faced with a hexadecimal number.  */
+  if (c == L_('0') && TOLOWER (cp[1]) == L_('x'))
+    {
+      /* Okay, it is a hexa-decimal number.  Remember this and skip
+	 the characters.  BTW: hexadecimal numbers must not be
+	 grouped.  */
+      base = 16;
+      cp += 2;
+      c = *cp;
+      grouping = NULL;
+    }
+
   /* Record the start of the digits, in case we will check their grouping.  */
   start_of_digits = startp = cp;
 
@@ -494,25 +516,29 @@ INTERNAL (STRTOF) (nptr, endptr, group)
 
   /* If no other digit but a '0' is found the result is 0.0.
      Return current read pointer.  */
-  if ((c < L_('0') || c > L_('9')) && (wint_t) c != decimal
-      && TOLOWER (c) != L_('e'))
+  if ((c < L_('0') || c > L_('9')) &&
+      (base == 16 && (c < TOLOWER (L_('a')) || c > TOLOWER (L_('f')))) &&
+      (wint_t) c != decimal &&
+      (base == 16 && (cp == start_of_digits || TOLOWER (c) != L_('p'))) &&
+      (base != 16 && TOLOWER (c) != L_('e')))
     {
       tp = correctly_grouped_prefix (start_of_digits, cp, thousands, grouping);
       /* If TP is at the start of the digits, there was no correctly
 	 grouped prefix of the string; so no number found.  */
-      RETURN (0.0, tp == start_of_digits ? nptr : tp);
+      RETURN (0.0, tp == start_of_digits ? (base == 16 ? cp - 1 : nptr) : tp);
     }
 
   /* Remember first significant digit and read following characters until the
      decimal point, exponent character or any non-FP number character.  */
   startp = cp;
   dig_no = 0;
-  while (dig_no < NDIG ||
+  while (dig_no < (base == 16 ? HEXNDIG : NDIG) ||
 	 /* If parsing grouping info, keep going past useful digits
 	    so we can check all the grouping separators.  */
 	 grouping)
     {
-      if (c >= L_('0') && c <= L_('9'))
+      if ((c >= L_('0') && c <= L_('9'))
+	  || (base == 16 && TOLOWER (c) >= L_('a') && TOLOWER (c) <= L_('f')))
 	++dig_no;
       else if (thousands == L'\0' || (wint_t) c != thousands)
 	/* Not a digit or separator: end of the integer part.  */
@@ -552,7 +578,7 @@ INTERNAL (STRTOF) (nptr, endptr, group)
 	}
     }
 
-  if (dig_no >= NDIG)
+  if (dig_no >= (base == 16 ? HEXNDIG : NDIG))
     /* Too many digits to be representable.  Assigning this to EXPONENT
        allows us to read the full number but return HUGE_VAL after parsing.  */
     exponent = MAX_10_EXP;
@@ -567,7 +593,8 @@ INTERNAL (STRTOF) (nptr, endptr, group)
   if ((wint_t) c == decimal)
     {
       c = *++cp;
-      while (c >= L_('0') && c <= L_('9'))
+      while (c >= L_('0') && c <= L_('9') ||
+	     (base == 16 && TOLOWER (c) >= L_('a') && TOLOWER (c) <= L_('f')))
 	{
 	  if (c != L_('0') && lead_zero == -1)
 	    lead_zero = dig_no - int_no;
@@ -580,7 +607,7 @@ INTERNAL (STRTOF) (nptr, endptr, group)
   expp = cp;
 
   /* Read exponent.  */
-  if (TOLOWER (c) == L_('e'))
+  if (TOLOWER (c) == (base == 16 ? L_('p') : L_('e')))
     {
       int exp_negative = 0;
 
@@ -598,9 +625,14 @@ INTERNAL (STRTOF) (nptr, endptr, group)
 	  int exp_limit;
 
 	  /* Get the exponent limit. */
-	  exp_limit = exp_negative ?
-		-MIN_10_EXP + MANT_DIG - int_no :
-		MAX_10_EXP - int_no + lead_zero;
+	  if (base == 16)
+	    exp_limit = (exp_negative ?
+			 -MIN_EXP + MANT_DIG - 4 * int_no :
+			 MAX_EXP - 4 * int_no + lead_zero);
+	  else
+	    exp_limit = (exp_negative ?
+			 -MIN_10_EXP + MANT_DIG - int_no :
+			 MAX_10_EXP - int_no + lead_zero);
 
 	  do
 	    {
@@ -610,11 +642,11 @@ INTERNAL (STRTOF) (nptr, endptr, group)
 		/* The exponent is too large/small to represent a valid
 		   number.  */
 		{
-	 	  FLOAT retval;
+	 	  FLOAT result;
 
 		  /* Overflow or underflow.  */
 		  __set_errno (ERANGE);
-		  retval = (exp_negative ? 0.0 :
+		  result = (exp_negative ? 0.0 :
 			    negative ? -FLOAT_HUGE_VAL : FLOAT_HUGE_VAL);
 
 		  /* Accept all following digits as part of the exponent.  */
@@ -622,7 +654,7 @@ INTERNAL (STRTOF) (nptr, endptr, group)
 		    ++cp;
 		  while (*cp >= L_('0') && *cp <= L_('9'));
 
-		  RETURN (retval, cp);
+		  RETURN (result, cp);
 		  /* NOTREACHED */
 		}
 
@@ -664,17 +696,89 @@ INTERNAL (STRTOF) (nptr, endptr, group)
       while ((wint_t) *startp != decimal)
 	++startp;
       startp += lead_zero + 1;
-      exponent -= lead_zero;
+      exponent -= base == 16 ? 4 * lead_zero : lead_zero;
       dig_no -= lead_zero;
     }
 
+  /* If the BASE is 16 we can use a simpler algorithm.  */
+  if (base == 16)
+    {
+      static const int nbits[16] = { 0, 1, 2, 2, 3, 3, 3, 3,
+				     4, 4, 4, 4, 4, 4, 4, 4 };
+      int idx = (MANT_DIG - 1) / BITS_PER_MP_LIMB;
+      int pos = (MANT_DIG - 1) % BITS_PER_MP_LIMB;
+      mp_limb_t val;
+
+      while (!ISXDIGIT (*startp))
+	++startp;
+      if (ISDIGIT (*startp))
+	val = *startp++ - L_('0');
+      else
+	val = 10 + TOLOWER (*startp++) - L_('a');
+      bits = nbits[val];
+
+      if (pos + 1 >= 4)
+	{
+	  /* We don't have to care for wrapping.  This is the normal
+	     case so we add this optimization.  */
+	  retval[idx] = val << (pos - bits + 1);
+	  pos -= bits;
+	}
+      else
+	{
+	  if (pos + 1 >= bits)
+	    {
+	      retval[idx] = val << (pos - bits + 1);
+	      pos -= bits;
+	    }
+	  else
+	    {
+	      retval[idx--] = val >> (bits - pos - 1);
+	      retval[idx] = val << (BITS_PER_MP_LIMB - (bits - pos - 1));
+	      pos = BITS_PER_MP_LIMB - 1 - (bits - pos - 1);
+	    }
+	}
+
+      while (--dig_no > 0 && idx >= 0)
+	{
+	  while (!ISXDIGIT (*startp))
+	    ++startp;
+	  if (ISDIGIT (*startp))
+	    val = *startp++ - L_('0');
+	  else
+	    val = 10 + TOLOWER (*startp++) - L_('a');
+
+	  if (pos + 1 >= 4)
+	    {
+	      retval[idx] |= val << (pos - 4 + 1);
+	      pos -= 4;
+	    }
+	  else
+	    {
+	      retval[idx--] |= val >> (4 - pos - 1);
+	      val <<= BITS_PER_MP_LIMB - (4 - pos - 1);
+	      if (idx < 0)
+		return round_and_return (retval, exponent, negative, val,
+					 BITS_PER_MP_LIMB - 1, dig_no > 0);
+
+	      retval[idx] = val;
+	      pos = BITS_PER_MP_LIMB - 1 - (4 - pos - 1);
+	    }
+	}
+
+      /* We ran out of digits.  */
+      MPN_ZERO (retval, idx);
+
+      return round_and_return (retval, exponent, negative, 0, 0, 0);
+    }
+
   /* Now we have the number of digits in total and the integer digits as well
      as the exponent and its sign.  We can decide whether the read digits are
      really integer digits or belong to the fractional part; i.e. we normalize
      123e-2 to 1.23.  */
   {
-    register int incr = exponent < 0 ? MAX (-int_no, exponent)
-				     : MIN (dig_no - int_no, exponent);
+    register int incr = (exponent < 0 ? MAX (-int_no, exponent)
+			 : MIN (dig_no - int_no, exponent));
     int_no += incr;
     exponent -= incr;
   }
@@ -711,9 +815,10 @@ INTERNAL (STRTOF) (nptr, endptr, group)
 		  mp_limb_t cy;
 		  exponent ^= expbit;
 
-		  /* FIXME: not the whole multiplication has to be done.
-		     If we have the needed number of bits we only need the
-		     information whether more non-zero bits follow.  */
+		  /* FIXME: not the whole multiplication has to be
+		     done.  If we have the needed number of bits we
+		     only need the information whether more non-zero
+		     bits follow.  */
 		  if (numsize >= ttab->arraysize - _FPIO_CONST_OFFSET)
 		    cy = __mpn_mul (pdest, psrc, numsize,
 				    &ttab->array[_FPIO_CONST_OFFSET],
@@ -848,7 +953,7 @@ INTERNAL (STRTOF) (nptr, endptr, group)
     assert (dig_no > int_no && exponent <= 0);
 
 
-    /* For the fractional part we need not process too much digits.  One
+    /* For the fractional part we need not process too many digits.  One
        decimal digits gives us log_2(10) ~ 3.32 bits.  If we now compute
                         ceil(BITS / 3) =: N
        digits we should have enough bits for the result.  The remaining
@@ -1126,7 +1231,9 @@ INTERNAL (STRTOF) (nptr, endptr, group)
 		      for (i = RETURN_LIMB_SIZE; i > empty; --i)
 			retval[i] = retval[i - empty];
 #endif
+#if RETURN_LIMB_SIZE > 1
 		      retval[1] = 0;
+#endif
 		      for (i = numsize; i > 0; --i)
 			num[i + empty] = num[i - 1];
 		      MPN_ZERO (num, empty + 1);