diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index fc4951222352702faa87812f478516149865a1f8..caed89593bca19e196c3a6d2832152f7ec00600e 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,29 @@
+2002-07-23	Paul Koning	<pkoning@equallogic.com>
+
+	* real.c (REAL_WORDS_BIG_ENDIAN): Make 1 for DEC.
+	(LARGEST_EXPONENT_IS_NORMAL): Ditto.
+	(VAX_HALFWORD_ORDER): Define (1 for DEC VAX, 0 otherwise).
+	(TARGET_G_FLOAT): Default to 0 if not defined.
+	(ieeetoe): New, common routine to convert target format floats 
+	to internal form.
+	(e24toe, e53toe): Change to use ieeetoe, distinguish DEC
+	vs. others.
+	(e113toe): Change to use ieeetoe.
+
+2002-07-23  Roman Lechtchinsky  <rl@cs.tu-berlin.de>
+
+	* real.c (REAL_WORDS_BIG_ENDIAN): Make sure it is 0 for DEC and 1 for
+	IBM.
+	(e53toe): Assume IEEE if non of DEC, IBM and C4X is defined.
+	(e64toe): Remove special cases for DEC and IBM. Remove support for
+	ARM_EXTENDED_IEEE_FORMAT.
+	(e24toe): Remove special cases for DEC.
+	(significand_size): Simplify. Indent.
+	(ieee_format, ieee_24, ieee_53, ieee_64, ieee_113): New.
+	(etoieee, toieee): New.
+	(etoe113, toe113, etoe64, toe64, etoe53, toe53, etoe24, toe24): Use
+	etoieee and toieee for IEEE arithmetic.
+
 2002-07-23  Gabriel Dos Reis  <gdr@nerim.net>
 
 	* doc/extend.texi: Say ISO C90, not ISO C89.
diff --git a/gcc/real.c b/gcc/real.c
index 456108eb742c3d4097be6277ac41bcba367af7f7..4dcd0363534278f96a78b3ce3546d73b3dd41be9 100644
--- a/gcc/real.c
+++ b/gcc/real.c
@@ -129,6 +129,31 @@ unknown arithmetic type
 
 #define REAL_WORDS_BIG_ENDIAN FLOAT_WORDS_BIG_ENDIAN
 
+/* Make sure that the endianness is correct for IBM and DEC. */
+#if defined(DEC)
+#undef LARGEST_EXPONENT_IS_NORMAL
+#define LARGEST_EXPONENT_IS_NORMAL(x) 1
+#undef REAL_WORDS_BIG_ENDIAN
+/* Strangely enough, DEC float most closely resembles big endian IEEE */
+#define REAL_WORDS_BIG_ENDIAN 1
+/* ... but the halfwords are reversed from IEEE big endian. */
+#ifndef VAX_HALFWORD_ORDER
+#define VAX_HALFWORD_ORDER 1
+#endif
+#else
+#if defined(IBM) && !REAL_WORDS_BIG_ENDIAN
+  #error "Little-endian representations are not supported for IBM."
+#endif
+#endif
+
+#if defined(DEC) && !defined (TARGET_G_FLOAT)
+#define TARGET_G_FLOAT 0
+#endif
+
+#ifndef VAX_HALFWORD_ORDER
+#define VAX_HALFWORD_ORDER 0
+#endif
+
 /* Define INFINITY for support of infinity.
    Define NANS for support of Not-a-Number's (NaN's).  */
 #if !defined(DEC) && !defined(IBM) && !defined(C4X)
@@ -276,6 +301,106 @@ struct compile_test_dummy {
 #define CHARMASK 0x7f
 #endif
 
+/* Information about the various IEEE precisions. At the moment, we only
+   support exponents of 15 bits or less.  */
+struct ieee_format
+{
+  /* Precision.  */
+  int precision;
+
+  /* Size of the exponent in bits.  */
+  int expbits;
+
+  /* Overall size of the value in bits.  */
+  int bits;
+
+  /* Mode used for representing the value.  */
+  enum machine_mode mode;
+
+  /* Exponent adjustment for offsets.  */
+  EMULONG adjustment;
+};
+
+/* IEEE float (24 bits).  */
+static const struct ieee_format ieee_24 =
+{
+  24,
+  8,
+  32,
+  SFmode,
+  EXONE - 0x7f
+};
+
+/* IEEE double (53 bits).  */
+static const struct ieee_format ieee_53 =
+{
+  53,
+  11,
+  64,
+  DFmode,
+  EXONE - 0x3ff
+};
+
+/* IEEE extended double (64 bits).  */
+static const struct ieee_format ieee_64 =
+{
+  64,
+  15,
+  80,
+  XFmode,
+  0
+};
+
+/* IEEE long double (113 bits).  */
+static const struct ieee_format ieee_113 =
+{
+  113,
+  15,
+  128,
+  TFmode,
+  0
+};
+
+/* DEC F float (24 bits).  */
+static const struct ieee_format dec_f =
+{
+  24,
+  8,
+  32,
+  SFmode,
+  EXONE - 0201
+};
+
+/* DEC D float (56 bits).  */
+static const struct ieee_format dec_d =
+{
+  56,
+  8,
+  64,
+  DFmode,
+  EXONE - 0201
+};
+
+/* DEC G float (53 bits).  */
+static const struct ieee_format dec_g =
+{
+  53,
+  11,
+  64,
+  DFmode,
+  EXONE - 1025
+};
+
+/* DEC H float (113 bits).  (not yet used) */
+static const struct ieee_format dec_h =
+{
+  113,
+  15,
+  128,
+  TFmode,
+  EXONE - 16385
+};
+
 extern int extra_warnings;
 extern const UEMUSHORT ezero[NE], ehalf[NE], eone[NE], etwo[NE];
 extern const UEMUSHORT elog2[NE], esqrt2[NE];
@@ -350,6 +475,12 @@ static void etoe53	PARAMS ((const UEMUSHORT *, UEMUSHORT *));
 static void toe53	PARAMS ((UEMUSHORT *, UEMUSHORT *));
 static void etoe24	PARAMS ((const UEMUSHORT *, UEMUSHORT *));
 static void toe24	PARAMS ((UEMUSHORT *, UEMUSHORT *));
+static void ieeetoe	PARAMS ((const UEMUSHORT *, UEMUSHORT *,
+				 const struct ieee_format *));
+static void etoieee	PARAMS ((const UEMUSHORT *, UEMUSHORT *,
+				 const struct ieee_format *));
+static void toieee	PARAMS ((UEMUSHORT *, UEMUSHORT *,
+				 const struct ieee_format *));
 static int ecmp		PARAMS ((const UEMUSHORT *, const UEMUSHORT *));
 #if 0
 static void eround	PARAMS ((const UEMUSHORT *, UEMUSHORT *));
@@ -430,7 +561,7 @@ endian (e, x, mode)
 {
   unsigned long th, t;
 
-  if (REAL_WORDS_BIG_ENDIAN)
+  if (REAL_WORDS_BIG_ENDIAN && !VAX_HALFWORD_ORDER)
     {
       switch (mode)
 	{
@@ -3072,90 +3203,9 @@ e53toe (pe, y)
   c4xtoe (pe, y, HFmode);
 
 #else
-  UEMUSHORT r;
-  const UEMUSHORT *e;
-  UEMUSHORT *p;
-  UEMUSHORT yy[NI];
-  int denorm, k;
-
-  e = pe;
-  denorm = 0;			/* flag if denormalized number */
-  ecleaz (yy);
-  if (! REAL_WORDS_BIG_ENDIAN)
-    e += 3;
-  r = *e;
-  yy[0] = 0;
-  if (r & 0x8000)
-    yy[0] = 0xffff;
-  yy[M] = (r & 0x0f) | 0x10;
-  r &= ~0x800f;			/* strip sign and 4 significand bits */
-#ifdef INFINITY
-  if (r == 0x7ff0)
-    {
-#ifdef NANS
-      if (! REAL_WORDS_BIG_ENDIAN)
-	{
-	  if (((pe[3] & 0xf) != 0) || (pe[2] != 0)
-	      || (pe[1] != 0) || (pe[0] != 0))
-	    {
-	      enan (y, yy[0] != 0);
-	      return;
-	    }
-	}
-      else
-	{
-	  if (((pe[0] & 0xf) != 0) || (pe[1] != 0)
-	      || (pe[2] != 0) || (pe[3] != 0))
-	    {
-	      enan (y, yy[0] != 0);
-	      return;
-	    }
-	}
-#endif  /* NANS */
-      eclear (y);
-      einfin (y);
-      if (yy[0])
-	eneg (y);
-      return;
-    }
-#endif  /* INFINITY */
-  r >>= 4;
-  /* If zero exponent, then the significand is denormalized.
-     So take back the understood high significand bit.  */
 
-  if (r == 0)
-    {
-      denorm = 1;
-      yy[M] &= ~0x10;
-    }
-  r += EXONE - 01777;
-  yy[E] = r;
-  p = &yy[M + 1];
-#ifdef IEEE
-  if (! REAL_WORDS_BIG_ENDIAN)
-    {
-      *p++ = *(--e);
-      *p++ = *(--e);
-      *p++ = *(--e);
-    }
-  else
-    {
-      ++e;
-      *p++ = *e++;
-      *p++ = *e++;
-      *p++ = *e++;
-    }
-#endif
-  eshift (yy, -5);
-  if (denorm)
-    {
-	/* If zero exponent, then normalize the significand.  */
-      if ((k = enormlz (yy)) > NBITS)
-	ecleazs (yy);
-      else
-	yy[E] -= (UEMUSHORT) (k - 1);
-    }
-  emovo (yy, y);
+  ieeetoe (pe, y, &ieee_53);
+  
 #endif /* not C4X */
 #endif /* not IBM */
 #endif /* not DEC */
@@ -3177,24 +3227,15 @@ e64toe (pe, y)
   p = yy;
   for (i = 0; i < NE - 5; i++)
     *p++ = 0;
-/* This precision is not ordinarily supported on DEC or IBM.  */
-#ifdef DEC
-  for (i = 0; i < 5; i++)
-    *p++ = *e++;
-#endif
-#ifdef IBM
-  p = &yy[0] + (NE - 1);
-  *p-- = *e++;
-  ++e;
-  for (i = 0; i < 5; i++)
-    *p-- = *e++;
-#endif
-#ifdef IEEE
+#ifndef C4X
+  /* REAL_WORDS_BIG_ENDIAN is always 0 for DEC and 1 for IBM.
+     This precision is not ordinarily supported on DEC or IBM.  */
   if (! REAL_WORDS_BIG_ENDIAN)
     {
       for (i = 0; i < 5; i++)
 	*p++ = *e++;
 
+#ifdef IEEE
       /* For denormal long double Intel format, shift significand up one
 	 -- but only if the top significand bit is zero.  A top bit of 1
 	 is "pseudodenormal" when the exponent is zero.  */
@@ -3207,22 +3248,17 @@ e64toe (pe, y)
 	  emovo (temp,y);
 	  return;
 	}
+#endif /* IEEE */
     }
   else
     {
       p = &yy[0] + (NE - 1);
-#ifdef ARM_EXTENDED_IEEE_FORMAT
-      /* For ARMs, the exponent is in the lowest 15 bits of the word.  */
-      *p-- = (e[0] & 0x8000) | (e[1] & 0x7ffff);
-      e += 2;
-#else
       *p-- = *e++;
       ++e;
-#endif
       for (i = 0; i < 4; i++)
 	*p-- = *e++;
     }
-#endif
+#endif  /* not C4X */
 #ifdef INFINITY
   /* Point to the exponent field and check max exponent cases.  */
   p = &yy[NE - 1];
@@ -3244,16 +3280,6 @@ e64toe (pe, y)
 	}
       else
 	{
-#ifdef ARM_EXTENDED_IEEE_FORMAT
-	  for (i = 2; i <= 5; i++)
-	    {
-	      if (pe[i] != 0)
-		{
-		  enan (y, (*p & 0x8000) != 0);
-		  return;
-		}
-	    }
-#else /* not ARM */
 	  /* In Motorola extended precision format, the most significant
 	     bit of an infinity mantissa could be either 1 or 0.  It is
 	     the lower order bits that tell whether the value is a NaN.  */
@@ -3269,7 +3295,6 @@ bigend_nan:
 		  return;
 		}
 	    }
-#endif /* not ARM */
 	}
 #endif /* NANS */
       eclear (y);
@@ -3293,86 +3318,9 @@ e113toe (pe, y)
      const UEMUSHORT *pe;
      UEMUSHORT *y;
 {
-  UEMUSHORT r;
-  const UEMUSHORT *e;
-  UEMUSHORT *p;
-  UEMUSHORT yy[NI];
-  int denorm, i;
-
-  e = pe;
-  denorm = 0;
-  ecleaz (yy);
-#ifdef IEEE
-  if (! REAL_WORDS_BIG_ENDIAN)
-    e += 7;
-#endif
-  r = *e;
-  yy[0] = 0;
-  if (r & 0x8000)
-    yy[0] = 0xffff;
-  r &= 0x7fff;
-#ifdef INFINITY
-  if (r == 0x7fff)
-    {
-#ifdef NANS
-      if (! REAL_WORDS_BIG_ENDIAN)
-	{
-	  for (i = 0; i < 7; i++)
-	    {
-	      if (pe[i] != 0)
-		{
-		  enan (y, yy[0] != 0);
-		  return;
-		}
-	    }
-	}
-      else
-	{
-	  for (i = 1; i < 8; i++)
-	    {
-	      if (pe[i] != 0)
-		{
-		  enan (y, yy[0] != 0);
-		  return;
-		}
-	    }
-	}
-#endif /* NANS */
-      eclear (y);
-      einfin (y);
-      if (yy[0])
-	eneg (y);
-      return;
-    }
-#endif  /* INFINITY */
-  yy[E] = r;
-  p = &yy[M + 1];
-#ifdef IEEE
-  if (! REAL_WORDS_BIG_ENDIAN)
-    {
-      for (i = 0; i < 7; i++)
-	*p++ = *(--e);
-    }
-  else
-    {
-      ++e;
-      for (i = 0; i < 7; i++)
-	*p++ = *e++;
-    }
-#endif
-/* If denormal, remove the implied bit; else shift down 1.  */
-  if (r == 0)
-    {
-      yy[M] = 0;
-    }
-  else
-    {
-      yy[M] = 1;
-      eshift (yy, -1);
-    }
-  emovo (yy, y);
+  ieeetoe (pe, y, &ieee_113);
 }
-#endif
+#endif  /* INTEL_EXTENDED_IEEE_FORMAT == 0 */
 
 /* Convert single precision float PE to e type Y.  */
 
@@ -3392,50 +3340,83 @@ e24toe (pe, y)
   c4xtoe (pe, y, QFmode);
 
 #else
+#ifdef DEC
+
+  ieeetoe (pe, y, &dec_f);
+  
+#else
+
+  ieeetoe (pe, y, &ieee_24);
+
+#endif /* not DEC */
+#endif /* not C4X */
+#endif /* not IBM */
+}
+
+/* Convert machine format float of specified format PE to e type Y.  */
 
+static void
+ieeetoe (pe, y, fmt)
+     const UEMUSHORT *pe;
+     UEMUSHORT *y;
+     const struct ieee_format *fmt;
+{
   UEMUSHORT r;
   const UEMUSHORT *e;
   UEMUSHORT *p;
   UEMUSHORT yy[NI];
-  int denorm, k;
-
+  int denorm, i, k;
+  int shortsm1 = fmt->bits / 16 - 1;
+#ifdef INFINITY
+  int expmask = (1 << fmt->expbits) - 1;
+#endif
+int expshift = (fmt->precision - 1) & 0x0f;
+  int highbit = 1 << expshift;
+  
   e = pe;
-  denorm = 0;			/* flag if denormalized number */
+  denorm = 0;
   ecleaz (yy);
-#ifdef IEEE
   if (! REAL_WORDS_BIG_ENDIAN)
-    e += 1;
-#endif
-#ifdef DEC
-  e += 1;
-#endif
+    e += shortsm1;
   r = *e;
   yy[0] = 0;
   if (r & 0x8000)
     yy[0] = 0xffff;
-  yy[M] = (r & 0x7f) | 0200;
-  r &= ~0x807f;			/* strip sign and 7 significand bits */
+  yy[M] = (r & (highbit - 1)) | highbit;
+  r = (r & 0x7fff) >> expshift;
 #ifdef INFINITY
-  if (!LARGEST_EXPONENT_IS_NORMAL (32) && r == 0x7f80)
+  if (!LARGEST_EXPONENT_IS_NORMAL (fmt->precision) && r == expmask)
     {
 #ifdef NANS
-      if (REAL_WORDS_BIG_ENDIAN)
+      /* First check the word where high order mantissa and exponent live */
+      if ((*e & (highbit - 1)) != 0)
+	{
+	  enan (y, yy[0] != 0);
+	  return;
+	}
+      if (! REAL_WORDS_BIG_ENDIAN)
 	{
-	  if (((pe[0] & 0x7f) != 0) || (pe[1] != 0))
+	  for (i = 0; i < shortsm1; i++)
 	    {
-	      enan (y, yy[0] != 0);
-	      return;
+	      if (pe[i] != 0)
+		{
+		  enan (y, yy[0] != 0);
+		  return;
+		}
 	    }
 	}
       else
 	{
-	  if (((pe[1] & 0x7f) != 0) || (pe[0] != 0))
+	  for (i = 1; i < shortsm1 + 1; i++)
 	    {
-	      enan (y, yy[0] != 0);
-	      return;
+	      if (pe[i] != 0)
+		{
+		  enan (y, yy[0] != 0);
+		  return;
+		}
 	    }
 	}
-#endif  /* NANS */
+#endif /* NANS */
       eclear (y);
       einfin (y);
       if (yy[0])
@@ -3443,40 +3424,45 @@ e24toe (pe, y)
       return;
     }
 #endif  /* INFINITY */
-  r >>= 7;
   /* If zero exponent, then the significand is denormalized.
      So take back the understood high significand bit.  */
   if (r == 0)
     {
       denorm = 1;
-      yy[M] &= ~0200;
+      yy[M] &= ~highbit;
     }
-  r += EXONE - 0177;
+  r += fmt->adjustment;
   yy[E] = r;
   p = &yy[M + 1];
-#ifdef DEC
-  *p++ = *(--e);
-#endif
-#ifdef IEEE
   if (! REAL_WORDS_BIG_ENDIAN)
-    *p++ = *(--e);
+    {
+      for (i = 0; i < shortsm1; i++)
+	*p++ = *(--e);
+    }
   else
     {
       ++e;
-      *p++ = *e++;
+      for (i = 0; i < shortsm1; i++)
+	*p++ = *e++;
     }
-#endif
-  eshift (yy, -8);
-  if (denorm)
-    {				/* if zero exponent, then normalize the significand */
-      if ((k = enormlz (yy)) > NBITS)
-	ecleazs (yy);
-      else
-	yy[E] -= (UEMUSHORT) (k - 1);
+  if (fmt->precision == 113)
+    {
+      /* denorm is left alone in 113 bit format */
+      if (!denorm)
+	eshift (yy, -1);
+    }
+  else
+    {
+      eshift (yy, -(expshift + 1));
+      if (denorm)
+	{ /* if zero exponent, then normalize the significand */
+	  if ((k = enormlz (yy)) > NBITS)
+	    ecleazs (yy);
+	  else
+	    yy[E] -= (UEMUSHORT) (k - 1);
+	}
     }
   emovo (yy, y);
-#endif /* not C4X */
-#endif /* not IBM */
 }
 
 #if (INTEL_EXTENDED_IEEE_FORMAT == 0)
@@ -3487,93 +3473,20 @@ etoe113 (x, e)
      const UEMUSHORT *x;
      UEMUSHORT *e;
 {
-  UEMUSHORT xi[NI];
-  EMULONG exp;
-  int rndsav;
-
-#ifdef NANS
-  if (eisnan (x))
-    {
-      make_nan (e, eisneg (x), TFmode);
-      return;
-    }
-#endif
-  emovi (x, xi);
-  exp = (EMULONG) xi[E];
-#ifdef INFINITY
-  if (eisinf (x))
-    goto nonorm;
-#endif
-  /* round off to nearest or even */
-  rndsav = rndprc;
-  rndprc = 113;
-  emdnorm (xi, 0, 0, exp, !ROUND_TOWARDS_ZERO);
-  rndprc = rndsav;
-#ifdef INFINITY
- nonorm:
-#endif
-  toe113 (xi, e);
-}
+  etoieee (x, e, &ieee_113);
+}
 
 /* Convert exploded e-type X, that has already been rounded to
    113-bit precision, to IEEE 128-bit long double format Y.  */
 
 static void
-toe113 (a, b)
-     UEMUSHORT *a, *b;
+toe113 (x, y)
+     UEMUSHORT *x, *y;
 {
-  UEMUSHORT *p, *q;
-  UEMUSHORT i;
-
-#ifdef NANS
-  if (eiisnan (a))
-    {
-      make_nan (b, eiisneg (a), TFmode);
-      return;
-    }
-#endif
-  p = a;
-  if (REAL_WORDS_BIG_ENDIAN)
-    q = b;
-  else
-    q = b + 7;			/* point to output exponent */
-
-  /* If not denormal, delete the implied bit.  */
-  if (a[E] != 0)
-    {
-      eshup1 (a);
-    }
-  /* combine sign and exponent */
-  i = *p++;
-  if (REAL_WORDS_BIG_ENDIAN)
-    {
-      if (i)
-	*q++ = *p++ | 0x8000;
-      else
-	*q++ = *p++;
-    }
-  else
-    {
-      if (i)
-	*q-- = *p++ | 0x8000;
-      else
-	*q-- = *p++;
-    }
-  /* skip over guard word */
-  ++p;
-  /* move the significand */
-  if (REAL_WORDS_BIG_ENDIAN)
-    {
-      for (i = 0; i < 7; i++)
-	*q++ = *p++;
-    }
-  else
-    {
-      for (i = 0; i < 7; i++)
-	*q-- = *p++;
-    }
+  toieee (x, y, &ieee_113);
 }
-#endif
+
+#endif  /* INTEL_EXTENDED_IEEE_FORMAT == 0 */
 
 /* Convert e-type X to IEEE double extended format E.  */
 
@@ -3582,148 +3495,17 @@ etoe64 (x, e)
      const UEMUSHORT *x;
      UEMUSHORT *e;
 {
-  UEMUSHORT xi[NI];
-  EMULONG exp;
-  int rndsav;
-
-#ifdef NANS
-  if (eisnan (x))
-    {
-      make_nan (e, eisneg (x), XFmode);
-      return;
-    }
-#endif
-  emovi (x, xi);
-  /* adjust exponent for offset */
-  exp = (EMULONG) xi[E];
-#ifdef INFINITY
-  if (eisinf (x))
-    goto nonorm;
-#endif
-  /* round off to nearest or even */
-  rndsav = rndprc;
-  rndprc = 64;
-  emdnorm (xi, 0, 0, exp, !ROUND_TOWARDS_ZERO);
-  rndprc = rndsav;
-#ifdef INFINITY
- nonorm:
-#endif
-  toe64 (xi, e);
+  etoieee (x, e, &ieee_64);
 }
 
 /* Convert exploded e-type X, that has already been rounded to
    64-bit precision, to IEEE double extended format Y.  */
 
 static void
-toe64 (a, b)
-     UEMUSHORT *a, *b;
+toe64 (x, y)
+     UEMUSHORT *x, *y;
 {
-  UEMUSHORT *p, *q;
-  UEMUSHORT i;
-
-#ifdef NANS
-  if (eiisnan (a))
-    {
-      make_nan (b, eiisneg (a), XFmode);
-      return;
-    }
-#endif
-  /* Shift denormal long double Intel format significand down one bit.  */
-  if ((a[E] == 0) && ! REAL_WORDS_BIG_ENDIAN)
-    eshdn1 (a);
-  p = a;
-#ifdef IBM
-  q = b;
-#endif
-#ifdef DEC
-  q = b + 4;
-#endif
-#ifdef IEEE
-  if (REAL_WORDS_BIG_ENDIAN)
-    q = b;
-  else
-    {
-      q = b + 4;			/* point to output exponent */
-      /* Clear the last two bytes of 12-byte Intel format.  q is pointing
-	 into an array of size 6 (e.g. x[NE]), so the last two bytes are
-	 always there, and there are never more bytes, even when we are using
-	 INTEL_EXTENDED_IEEE_FORMAT.  */
-      *(q+1) = 0;
-    }
-#endif
-
-  /* combine sign and exponent */
-  i = *p++;
-#ifdef IBM
-  if (i)
-    *q++ = *p++ | 0x8000;
-  else
-    *q++ = *p++;
-  *q++ = 0;
-#endif
-#ifdef DEC
-  if (i)
-    *q-- = *p++ | 0x8000;
-  else
-    *q-- = *p++;
-#endif
-#ifdef IEEE
-  if (REAL_WORDS_BIG_ENDIAN)
-    {
-#ifdef ARM_EXTENDED_IEEE_FORMAT
-      /* The exponent is in the lowest 15 bits of the first word.  */
-      *q++ = i ? 0x8000 : 0;
-      *q++ = *p++;
-#else
-      if (i)
-	*q++ = *p++ | 0x8000;
-      else
-	*q++ = *p++;
-      *q++ = 0;
-#endif
-    }
-  else
-    {
-      if (i)
-	*q-- = *p++ | 0x8000;
-      else
-	*q-- = *p++;
-    }
-#endif
-  /* skip over guard word */
-  ++p;
-  /* move the significand */
-#ifdef IBM
-  for (i = 0; i < 4; i++)
-    *q++ = *p++;
-#endif
-#ifdef DEC
-  for (i = 0; i < 4; i++)
-    *q-- = *p++;
-#endif
-#ifdef IEEE
-  if (REAL_WORDS_BIG_ENDIAN)
-    {
-      for (i = 0; i < 4; i++)
-	*q++ = *p++;
-    }
-  else
-    {
-#ifdef INFINITY
-      if (eiisinf (a))
-	{
-	  /* Intel long double infinity significand.  */
-	  *q-- = 0x8000;
-	  *q-- = 0;
-	  *q-- = 0;
-	  *q = 0;
-	  return;
-	}
-#endif
-      for (i = 0; i < 4; i++)
-	*q-- = *p++;
-    }
-#endif
+  toieee (x, y, &ieee_64);
 }
 
 /* e type to double precision.  */
@@ -3736,7 +3518,7 @@ etoe53 (x, e)
      const UEMUSHORT *x;
      UEMUSHORT *e;
 {
-  etodec (x, e);		/* see etodec.c */
+  etodec (x, e);
 }
 
 /* Convert exploded e-type X, that has already been rounded to
@@ -3799,36 +3581,10 @@ toe53 (x, y)
 
 static void
 etoe53 (x, e)
-     const UEMUSHORT *x;
-     UEMUSHORT *e;
+      const UEMUSHORT *x;
+      UEMUSHORT *e;
 {
-  UEMUSHORT xi[NI];
-  EMULONG exp;
-  int rndsav;
-
-#ifdef NANS
-  if (eisnan (x))
-    {
-      make_nan (e, eisneg (x), DFmode);
-      return;
-    }
-#endif
-  emovi (x, xi);
-  /* adjust exponent for offsets */
-  exp = (EMULONG) xi[E] - (EXONE - 0x3ff);
-#ifdef INFINITY
-  if (eisinf (x))
-    goto nonorm;
-#endif
-  /* round off to nearest or even */
-  rndsav = rndprc;
-  rndprc = 53;
-  emdnorm (xi, 0, 0, exp, !ROUND_TOWARDS_ZERO);
-  rndprc = rndsav;
-#ifdef INFINITY
- nonorm:
-#endif
-  toe53 (xi, e);
+  etoieee (x, e, &ieee_53);
 }
 
 /* Convert exploded e-type X, that has already been rounded to
@@ -3838,91 +3594,7 @@ static void
 toe53 (x, y)
      UEMUSHORT *x, *y;
 {
-  UEMUSHORT i;
-  UEMUSHORT *p;
-
-#ifdef NANS
-  if (eiisnan (x))
-    {
-      make_nan (y, eiisneg (x), DFmode);
-      return;
-    }
-#endif
-  if (LARGEST_EXPONENT_IS_NORMAL (64) && x[1] > 2047)
-    {
-      saturate (y, eiisneg (x), 64, 1);
-      return;
-    }
-  p = &x[0];
-#ifdef IEEE
-  if (! REAL_WORDS_BIG_ENDIAN)
-    y += 3;
-#endif
-  *y = 0;			/* output high order */
-  if (*p++)
-    *y = 0x8000;		/* output sign bit */
-
-  i = *p++;
-  if (i >= (unsigned int) 2047)
-    {
-      /* Saturate at largest number less than infinity.  */
-#ifdef INFINITY
-      *y |= 0x7ff0;
-      if (! REAL_WORDS_BIG_ENDIAN)
-	{
-	  *(--y) = 0;
-	  *(--y) = 0;
-	  *(--y) = 0;
-	}
-      else
-	{
-	  ++y;
-	  *y++ = 0;
-	  *y++ = 0;
-	  *y++ = 0;
-	}
-#else
-      *y |= (UEMUSHORT) 0x7fef;
-      if (! REAL_WORDS_BIG_ENDIAN)
-	{
-	  *(--y) = 0xffff;
-	  *(--y) = 0xffff;
-	  *(--y) = 0xffff;
-	}
-      else
-	{
-	  ++y;
-	  *y++ = 0xffff;
-	  *y++ = 0xffff;
-	  *y++ = 0xffff;
-	}
-#endif
-      return;
-    }
-  if (i == 0)
-    {
-      eshift (x, 4);
-    }
-  else
-    {
-      i <<= 4;
-      eshift (x, 5);
-    }
-  i |= *p++ & (UEMUSHORT) 0x0f;	/* *p = xi[M] */
-  *y |= (UEMUSHORT) i;	/* high order output already has sign bit set */
-  if (! REAL_WORDS_BIG_ENDIAN)
-    {
-      *(--y) = *p++;
-      *(--y) = *p++;
-      *(--y) = *p;
-    }
-  else
-    {
-      ++y;
-      *y++ = *p++;
-      *y++ = *p++;
-      *y++ = *p++;
-    }
+  toieee (x, y, &ieee_53);
 }
 
 #endif /* not C4X */
@@ -3954,7 +3626,7 @@ toe24 (x, y)
   toibm (x, y, SFmode);
 }
 
-#else
+#else /* it's not IBM */
 
 #ifdef C4X
 /* Convert e-type X to C4X float E.  */
@@ -3977,143 +3649,242 @@ toe24 (x, y)
   toc4x (x, y, QFmode);
 }
 
+#else /* it's neither IBM nor C4X */
+
+#ifdef DEC
+
+/* Convert e-type X to DEC F-float E.  */
+
+static void
+etoe24 (x, e)
+      const UEMUSHORT *x;
+      UEMUSHORT *e;
+{
+  etoieee (x, e, &dec_f);
+}
+
+/* Convert exploded e-type X, that has already been rounded to
+   float precision, to DEC F-float Y.  */
+
+static void
+toe24 (x, y)
+      UEMUSHORT *x, *y;
+{
+  toieee (x, y, &dec_f);
+}
+
 #else
 
-/* Convert e-type X to IEEE float E.  DEC float is the same as IEEE float.  */
+/* Convert e-type X to IEEE float E.  */
 
 static void
 etoe24 (x, e)
-     const UEMUSHORT *x;
-     UEMUSHORT *e;
+      const UEMUSHORT *x;
+      UEMUSHORT *e;
+{
+  etoieee (x, e, &ieee_24);
+}
+
+/* Convert exploded e-type X, that has already been rounded to
+   float precision, to IEEE float Y.  */
+
+static void
+toe24 (x, y)
+      UEMUSHORT *x, *y;
+{
+  toieee (x, y, &ieee_24);
+}
+
+#endif  /* not DEC */
+#endif  /* not C4X */
+#endif  /* not IBM */
+
+
+/* Convert e-type X to the IEEE format described by FMT.  */
+
+static void
+etoieee (x, e, fmt)
+      const UEMUSHORT *x;
+      UEMUSHORT *e;
+      const struct ieee_format *fmt;
 {
-  EMULONG exp;
   UEMUSHORT xi[NI];
+  EMULONG exp;
   int rndsav;
 
 #ifdef NANS
   if (eisnan (x))
     {
-      make_nan (e, eisneg (x), SFmode);
+      make_nan (e, eisneg (x), fmt->mode);
       return;
     }
 #endif
+
   emovi (x, xi);
-  /* adjust exponent for offsets */
-  exp = (EMULONG) xi[E] - (EXONE - 0177);
+
 #ifdef INFINITY
   if (eisinf (x))
     goto nonorm;
 #endif
-  /* round off to nearest or even */
+  /* Adjust exponent for offset.  */
+  exp = (EMULONG) xi[E] - fmt->adjustment;
+  
+  /* Round off to nearest or even.  */
   rndsav = rndprc;
-  rndprc = 24;
+  rndprc = fmt->precision;
   emdnorm (xi, 0, 0, exp, !ROUND_TOWARDS_ZERO);
   rndprc = rndsav;
 #ifdef INFINITY
  nonorm:
 #endif
-  toe24 (xi, e);
+  toieee (xi, e, fmt);
 }
 
 /* Convert exploded e-type X, that has already been rounded to
-   float precision, to IEEE float Y.  */
+   the necessary precision, to the IEEE format described by FMT.  */
 
 static void
-toe24 (x, y)
-     UEMUSHORT *x, *y;
+toieee (x, y, fmt)
+      UEMUSHORT *x, *y;
+      const struct ieee_format *fmt;
 {
-  UEMUSHORT i;
-  UEMUSHORT *p;
+  UEMUSHORT maxexp;
+  UEMUSHORT *q;
+  int words;
+  int i;
 
+  maxexp = (1 << fmt->expbits) - 1;
+  words = (fmt->bits - fmt->expbits) / EMUSHORT_SIZE;
+  
 #ifdef NANS
   if (eiisnan (x))
     {
-      make_nan (y, eiisneg (x), SFmode);
+      make_nan (y, eiisneg (x), fmt->mode);
       return;
     }
 #endif
-  if (LARGEST_EXPONENT_IS_NORMAL (32) && x[1] > 255)
+
+  if (fmt->expbits < 15
+      && LARGEST_EXPONENT_IS_NORMAL (fmt->bits)
+      && x[E] > maxexp)
     {
-      saturate (y, eiisneg (x), 32, 1);
+      saturate (y, eiisneg (x), fmt->bits, 1);
       return;
     }
-  p = &x[0];
-#ifdef IEEE
-  if (! REAL_WORDS_BIG_ENDIAN)
-    y += 1;
-#endif
-#ifdef DEC
-  y += 1;
-#endif
-  *y = 0;			/* output high order */
-  if (*p++)
-    *y = 0x8000;		/* output sign bit */
 
-  i = *p++;
-/* Handle overflow cases.  */
-  if (!LARGEST_EXPONENT_IS_NORMAL (32) && i >= 255)
+  /* Point to the exponent.  */
+  if (REAL_WORDS_BIG_ENDIAN)
+    q = y;
+  else
+    q = y + words;
+
+  /* Copy the sign.  */
+  if (x[0])
+    *q = 0x8000;
+  else
+    *q = 0;
+
+  if (fmt->expbits < 15
+      && !LARGEST_EXPONENT_IS_NORMAL (fmt->bits)
+      && x[E] >= maxexp)
     {
+      /* Saturate at largest number less that infinity.  */
+      UEMUSHORT fill;
 #ifdef INFINITY
-      *y |= (UEMUSHORT) 0x7f80;
-#ifdef DEC
-      *(--y) = 0;
+      *q |= maxexp << (15 - fmt->expbits);
+      fill = 0;
+#else
+      *q |= (maxexp << (15 - fmt->expbits)) - 1;
+      fill = 0xffff;
 #endif
-#ifdef IEEE
-      if (! REAL_WORDS_BIG_ENDIAN)
-	*(--y) = 0;
-      else
+
+      if (!REAL_WORDS_BIG_ENDIAN)
 	{
-	  ++y;
-	  *y = 0;
+	  for (i = 0; i < words; i++)
+	    *(--q) = fill;
 	}
-#endif
-#else  /* no INFINITY */
-      *y |= (UEMUSHORT) 0x7f7f;
-#ifdef DEC
-      *(--y) = 0xffff;
-#endif
-#ifdef IEEE
-      if (! REAL_WORDS_BIG_ENDIAN)
-	*(--y) = 0xffff;
       else
 	{
-	  ++y;
-	  *y = 0xffff;
+	  for (i = 0; i < words; i++)
+	    *(++q) = fill;
 	}
-#endif
-#ifdef ERANGE
+#if defined(INFINITY) && defined(ERANGE)
       errno = ERANGE;
 #endif
-#endif  /* no INFINITY */
       return;
     }
-  if (i == 0)
+
+  /* If denormal and DEC float, return zero (DEC has no denormals) */
+#ifdef DEC
+  if (x[E] == 0)
+    {
+      for (i = 0; i < fmt->bits / EMUSHORT_SIZE ; i++)
+	q[i] = 0;
+      return;
+    }
+#endif /* DEC */
+
+  /* Delete the implied bit unless denormal, except for
+     64-bit precision.  */
+  if (fmt->precision != 64 && x[E] != 0)
     {
-      eshift (x, 7);
+      eshup1 (x);
+    }
+
+  /* Shift denormal double extended Intel format significand down
+     one bit. */
+  if (fmt->precision == 64 && x[E] == 0 && ! REAL_WORDS_BIG_ENDIAN)
+    eshdn1 (x);
+
+  if (fmt->expbits < 15)
+    {
+      /* Shift the significand.  */
+      eshift (x, 15 - fmt->expbits);
+
+      /* Combine the exponent and upper bits of the significand.  */
+      *q |= x[E] << (15 - fmt->expbits);
+      *q |= x[M] & (UEMUSHORT) ~((maxexp << (15 - fmt->expbits)) | 0x8000);
     }
   else
     {
-      i <<= 7;
-      eshift (x, 8);
+      /* Copy the exponent.  */
+      *q |= x[E];
+    }
+
+  /* Add padding after the exponent. At the moment, this is only necessary for
+     64-bit precision; in this case, the padding is 16 bits.  */
+  if (fmt->precision == 64)
+    {
+      *(q + 1) = 0;
+
+      /* Skip padding.  */
+      if (REAL_WORDS_BIG_ENDIAN)
+	++q;
+    }
+
+  /* Copy the significand.  */
+  if (REAL_WORDS_BIG_ENDIAN)
+    {
+      for (i = 0; i < words; i++)
+	*(++q) = x[i + M + 1];
+    }
+#ifdef INFINITY
+  else if (fmt->precision == 64 && eiisinf (x))
+    {
+      /* Intel double extended infinity significand.  */
+      *(--q) = 0x8000;
+      *(--q) = 0;
+      *(--q) = 0;
+      *(--q) = 0;
     }
-  i |= *p++ & (UEMUSHORT) 0x7f;	/* *p = xi[M] */
-  /* High order output already has sign bit set.  */
-  *y |= i;
-#ifdef DEC
-  *(--y) = *p;
 #endif
-#ifdef IEEE
-  if (! REAL_WORDS_BIG_ENDIAN)
-    *(--y) = *p;
   else
     {
-      ++y;
-      *y = *p;
+      for (i = 0; i < words; i++)
+	*(--q) = x[i + M + 1];
     }
-#endif
 }
-#endif  /* not C4X */
-#endif  /* not IBM */
+
 
 /* Compare two e type numbers.
    Return +1 if a > b
@@ -5436,14 +5207,22 @@ read_expnt:
   else if (oprec == 24 || oprec == 56)
     lexp -= EXONE - (0x41 << 2);
 #else
+#ifdef DEC
   else if (oprec == 24)
+    lexp -= dec_f.adjustment;
+  else if (oprec == 56)
+    {
+      if (TARGET_G_FLOAT)
+	lexp -= dec_g.adjustment;
+      else
+	lexp -= dec_d.adjustment;
+    }
+#else
+else if (oprec == 24)
     lexp -= EXONE - 0177;
+#endif /* DEC */
 #endif /* IBM */
 #endif /* C4X */
-#ifdef DEC
-  else if (oprec == 56)
-    lexp -= EXONE - 0201;
-#endif
   rndprc = oprec;
   emdnorm (yy, lost, 0, lexp, 64);
 
@@ -5455,7 +5234,7 @@ read_expnt:
     {
 #ifdef DEC
     case 56:
-      todec (yy, y);		/* see etodec.c */
+      todec (yy, y);
       break;
 #endif
 #ifdef IBM
@@ -5754,37 +5533,10 @@ dectoe (d, e)
      const UEMUSHORT *d;
      UEMUSHORT *e;
 {
-  UEMUSHORT y[NI];
-  UEMUSHORT r, *p;
-
-  ecleaz (y);			/* start with a zero */
-  p = y;			/* point to our number */
-  r = *d;			/* get DEC exponent word */
-  if (*d & (unsigned int) 0x8000)
-    *p = 0xffff;		/* fill in our sign */
-  ++p;				/* bump pointer to our exponent word */
-  r &= 0x7fff;			/* strip the sign bit */
-  if (r == 0)			/* answer = 0 if high order DEC word = 0 */
-    goto done;
-
-
-  r >>= 7;			/* shift exponent word down 7 bits */
-  r += EXONE - 0201;		/* subtract DEC exponent offset */
-  /* add our e type exponent offset */
-  *p++ = r;			/* to form our exponent */
-
-  r = *d++;			/* now do the high order mantissa */
-  r &= 0177;			/* strip off the DEC exponent and sign bits */
-  r |= 0200;			/* the DEC understood high order mantissa bit */
-  *p++ = r;			/* put result in our high guard word */
-
-  *p++ = *d++;			/* fill in the rest of our mantissa */
-  *p++ = *d++;
-  *p = *d;
-
-  eshdn8 (y);			/* shift our mantissa down 8 bits */
- done:
-  emovo (y, e);
+  if (TARGET_G_FLOAT)
+    ieeetoe (d, e, &dec_g);
+  else
+    ieeetoe (d, e, &dec_d);
 }
 
 /* Convert e type X to DEC double precision D.  */
@@ -5797,13 +5549,19 @@ etodec (x, d)
   UEMUSHORT xi[NI];
   EMULONG exp;
   int rndsav;
+  const struct ieee_format *fmt;
+
+  if (TARGET_G_FLOAT)
+    fmt = &dec_g;
+  else
+    fmt = &dec_d;
 
   emovi (x, xi);
   /* Adjust exponent for offsets.  */
-  exp = (EMULONG) xi[E] - (EXONE - 0201);
+  exp = (EMULONG) xi[E] - fmt->adjustment;
   /* Round off to nearest or even.  */
   rndsav = rndprc;
-  rndprc = 56;
+  rndprc = fmt->precision;
   emdnorm (xi, 0, 0, exp, !ROUND_TOWARDS_ZERO);
   rndprc = rndsav;
   todec (xi, d);
@@ -5816,42 +5574,10 @@ static void
 todec (x, y)
      UEMUSHORT *x, *y;
 {
-  UEMUSHORT i;
-  UEMUSHORT *p;
-
-  p = x;
-  *y = 0;
-  if (*p++)
-    *y = 0100000;
-  i = *p++;
-  if (i == 0)
-    {
-      *y++ = 0;
-      *y++ = 0;
-      *y++ = 0;
-      *y++ = 0;
-      return;
-    }
-  if (i > 0377)
-    {
-      *y++ |= 077777;
-      *y++ = 0xffff;
-      *y++ = 0xffff;
-      *y++ = 0xffff;
-#ifdef ERANGE
-      errno = ERANGE;
-#endif
-      return;
-    }
-  i &= 0377;
-  i <<= 7;
-  eshup8 (x);
-  x[M] &= 0177;
-  i |= x[M];
-  *y++ |= i;
-  *y++ = x[M + 1];
-  *y++ = x[M + 2];
-  *y++ = x[M + 3];
+  if (TARGET_G_FLOAT)
+    toieee (x, y, &dec_g);
+  else
+    toieee (x, y, &dec_d);
 }
 #endif /* DEC */
 
@@ -6904,49 +6630,37 @@ significand_size (mode)
      enum machine_mode mode;
 {
 
-/* Don't test the modes, but their sizes, lest this
-   code won't work for BITS_PER_UNIT != 8 .  */
+  /* Don't test the modes, but their sizes, lest this
+     code won't work for BITS_PER_UNIT != 8 .  */
 
-switch (GET_MODE_BITSIZE (mode))
-  {
-  case 32:
+  switch (GET_MODE_BITSIZE (mode))
+    {
+     case 32:
 
-#if TARGET_FLOAT_FORMAT == C4X_FLOAT_FORMAT
-    return 56;
+#ifdef C4X
+       return 56;
+#else
+       return 24;
 #endif
 
-    return 24;
-
-  case 64:
-#if TARGET_FLOAT_FORMAT == IEEE_FLOAT_FORMAT
-    return 53;
-#else
-#if TARGET_FLOAT_FORMAT == IBM_FLOAT_FORMAT
-    return 56;
-#else
-#if TARGET_FLOAT_FORMAT == VAX_FLOAT_FORMAT
-    return 56;
-#else
-#if TARGET_FLOAT_FORMAT == C4X_FLOAT_FORMAT
-    return 56;
+     case 64:
+#ifdef IEEE
+       return 53;
 #else
-    abort ();
-#endif
-#endif
-#endif
+       return 56;
 #endif
 
-  case 96:
-    return 64;
+     case 96:
+       return 64;
 
-  case 128:
+     case 128:
 #if (INTEL_EXTENDED_IEEE_FORMAT == 0)
-    return 113;
+       return 113;
 #else
-    return 64;
+       return 64;
 #endif
 
-  default:
-    abort ();
-  }
+     default:
+       abort ();
+    }
 }