public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)
@ 2019-06-25  8:31 Tamar Christina
  2019-06-25  8:33 ` Tamar Christina
  0 siblings, 1 reply; 16+ messages in thread
From: Tamar Christina @ 2019-06-25  8:31 UTC (permalink / raw)
  To: gcc-patches; +Cc: nd

[-- Attachment #1: Type: text/plain, Size: 1823 bytes --]

Hi All,

This is an updated version of my GCC-9 patch which moves part of the type conversion code
from convert.c to match.pd because match.pd is able to apply this transformation in the
presence of intermediate temporary variables.

The previous patch was only regtested on aarch64-none-linux-gnu and I hadn't done a
regression on x86_64-pc-linux-gnu only a bootstrap.  The previous patch was approved

here https://gcc.gnu.org/ml/gcc-patches/2018-12/msg00116.html
but before committing I ran a x86_64-pc-linux-gnu regtest to be sure and this
showed an issue with a DFP test. I Have fixed this by removing the offending convert.
The convert was just saying "keep the type as is" but match.pd looped here as it thinks
the match did something and would try other patterns, causing it to match itself again.

Instead when there's nothing to update, I just don't do anything.

The second change was to merge this with the existing pattern for integer conversion
in order to silence a warning from match.pd which though that the two patterns overlaps
because their match conditions are similar (they have different conditions inside the ifs
but match.pd doesn't check those of course.).

Regtested and bootstrapped on aarch64-none-linux-gnu and x86_64-pc-linux-gnu and no issues.

Ok for trunk?

Thanks,
Tamar

Concretely it makes both these cases behave the same

  float e = (float)a * (float)b;
  *c = (_Float16)e;

and 

  *c = (_Float16)((float)a * (float)b);

Thanks,
Tamar

gcc/ChangeLog:

2019-06-25  Tamar Christina  <tamar.christina@arm.com>

	* convert.c (convert_to_real_1): Move part of conversion code...
	* match.pd: ...To here.

gcc/testsuite/ChangeLog:

2019-06-25  Tamar Christina  <tamar.christina@arm.com>

	* gcc.dg/type-convert-var.c: New test.

-- 

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #2: rb10277.patch --]
[-- Type: text/x-diff; name="rb10277.patch", Size: 11518 bytes --]

diff --git a/gcc/convert.c b/gcc/convert.c
index d5aa07b510e0e7831e8d121b383e42e5c6e89321..923eb70366e6c05141fb1580ba6f85e354aa3f76 100644
--- a/gcc/convert.c
+++ b/gcc/convert.c
@@ -298,92 +298,6 @@ convert_to_real_1 (tree type, tree expr, bool fold_p)
 	      return build1 (TREE_CODE (expr), type, arg);
 	    }
 	  break;
-	/* Convert (outertype)((innertype0)a+(innertype1)b)
-	   into ((newtype)a+(newtype)b) where newtype
-	   is the widest mode from all of these.  */
-	case PLUS_EXPR:
-	case MINUS_EXPR:
-	case MULT_EXPR:
-	case RDIV_EXPR:
-	   {
-	     tree arg0 = strip_float_extensions (TREE_OPERAND (expr, 0));
-	     tree arg1 = strip_float_extensions (TREE_OPERAND (expr, 1));
-
-	     if (FLOAT_TYPE_P (TREE_TYPE (arg0))
-		 && FLOAT_TYPE_P (TREE_TYPE (arg1))
-		 && DECIMAL_FLOAT_TYPE_P (itype) == DECIMAL_FLOAT_TYPE_P (type))
-	       {
-		  tree newtype = type;
-
-		  if (TYPE_MODE (TREE_TYPE (arg0)) == SDmode
-		      || TYPE_MODE (TREE_TYPE (arg1)) == SDmode
-		      || TYPE_MODE (type) == SDmode)
-		    newtype = dfloat32_type_node;
-		  if (TYPE_MODE (TREE_TYPE (arg0)) == DDmode
-		      || TYPE_MODE (TREE_TYPE (arg1)) == DDmode
-		      || TYPE_MODE (type) == DDmode)
-		    newtype = dfloat64_type_node;
-		  if (TYPE_MODE (TREE_TYPE (arg0)) == TDmode
-		      || TYPE_MODE (TREE_TYPE (arg1)) == TDmode
-		      || TYPE_MODE (type) == TDmode)
-                    newtype = dfloat128_type_node;
-		  if (newtype == dfloat32_type_node
-		      || newtype == dfloat64_type_node
-		      || newtype == dfloat128_type_node)
-		    {
-		      expr = build2 (TREE_CODE (expr), newtype,
-				     convert_to_real_1 (newtype, arg0,
-							fold_p),
-				     convert_to_real_1 (newtype, arg1,
-							fold_p));
-		      if (newtype == type)
-			return expr;
-		      break;
-		    }
-
-		  if (TYPE_PRECISION (TREE_TYPE (arg0)) > TYPE_PRECISION (newtype))
-		    newtype = TREE_TYPE (arg0);
-		  if (TYPE_PRECISION (TREE_TYPE (arg1)) > TYPE_PRECISION (newtype))
-		    newtype = TREE_TYPE (arg1);
-		  /* Sometimes this transformation is safe (cannot
-		     change results through affecting double rounding
-		     cases) and sometimes it is not.  If NEWTYPE is
-		     wider than TYPE, e.g. (float)((long double)double
-		     + (long double)double) converted to
-		     (float)(double + double), the transformation is
-		     unsafe regardless of the details of the types
-		     involved; double rounding can arise if the result
-		     of NEWTYPE arithmetic is a NEWTYPE value half way
-		     between two representable TYPE values but the
-		     exact value is sufficiently different (in the
-		     right direction) for this difference to be
-		     visible in ITYPE arithmetic.  If NEWTYPE is the
-		     same as TYPE, however, the transformation may be
-		     safe depending on the types involved: it is safe
-		     if the ITYPE has strictly more than twice as many
-		     mantissa bits as TYPE, can represent infinities
-		     and NaNs if the TYPE can, and has sufficient
-		     exponent range for the product or ratio of two
-		     values representable in the TYPE to be within the
-		     range of normal values of ITYPE.  */
-		  if (TYPE_PRECISION (newtype) < TYPE_PRECISION (itype)
-		      && (flag_unsafe_math_optimizations
-			  || (TYPE_PRECISION (newtype) == TYPE_PRECISION (type)
-			      && real_can_shorten_arithmetic (TYPE_MODE (itype),
-							      TYPE_MODE (type))
-			      && !excess_precision_type (newtype))))
-		    {
-		      expr = build2 (TREE_CODE (expr), newtype,
-				     convert_to_real_1 (newtype, arg0,
-							fold_p),
-				     convert_to_real_1 (newtype, arg1,
-							fold_p));
-		      if (newtype == type)
-			return expr;
-		    }
-	       }
-	   }
-	  break;
 	default:
 	  break;
       }
diff --git a/gcc/match.pd b/gcc/match.pd
index f9bc097c49122bf1b4bcf0b12b09840daf7b8fbc..228a69f99ae0318f034b2f713e522acd9e0995ae 100644
--- a/gcc/match.pd
+++ b/gcc/match.pd
@@ -4870,37 +4870,116 @@ DEFINE_INT_AND_FLOAT_ROUND_FN (RINT)
    the C/C++ front-ends by shorten_binary_op and shorten_compare.  Long
    term we want to move all that code out of the front-ends into here.  */
 
-/* If we have a narrowing conversion of an arithmetic operation where
-   both operands are widening conversions from the same type as the outer
-   narrowing conversion.  Then convert the innermost operands to a suitable
-   unsigned type (to avoid introducing undefined behavior), perform the
-   operation and convert the result to the desired type.  */
-(for op (plus minus)
-  (simplify
-    (convert (op:s (convert@2 @0) (convert?@3 @1)))
-    (if (INTEGRAL_TYPE_P (type)
-	 /* We check for type compatibility between @0 and @1 below,
-	    so there's no need to check that @1/@3 are integral types.  */
-	 && INTEGRAL_TYPE_P (TREE_TYPE (@0))
-	 && INTEGRAL_TYPE_P (TREE_TYPE (@2))
-	 /* The precision of the type of each operand must match the
-	    precision of the mode of each operand, similarly for the
-	    result.  */
-	 && type_has_mode_precision_p (TREE_TYPE (@0))
-	 && type_has_mode_precision_p (TREE_TYPE (@1))
-	 && type_has_mode_precision_p (type)
-	 /* The inner conversion must be a widening conversion.  */
-	 && TYPE_PRECISION (TREE_TYPE (@2)) > TYPE_PRECISION (TREE_TYPE (@0))
-	 && types_match (@0, type)
-	 && (types_match (@0, @1)
-	     /* Or the second operand is const integer or converted const
-		integer from valueize.  */
-	     || TREE_CODE (@1) == INTEGER_CST))
-      (if (TYPE_OVERFLOW_WRAPS (TREE_TYPE (@0)))
-	(op @0 (convert @1))
-	(with { tree utype = unsigned_type_for (TREE_TYPE (@0)); }
-	 (convert (op (convert:utype @0)
-		      (convert:utype @1))))))))
+/* Convert (outertype)((innertype0)a+(innertype1)b)
+   into ((newtype)a+(newtype)b) where newtype
+   is the widest mode from all of these.  */
+(for op (plus minus mult rdiv)
+ (simplify
+   (convert (op:s@0 (convert1?@3 @1) (convert2?@4 @2)))
+   (with { tree arg0 = strip_float_extensions (@1);
+	   tree arg1 = strip_float_extensions (@2);
+	   tree itype = TREE_TYPE (@0);
+	   tree ty1 = TREE_TYPE (arg0);
+	   tree ty2 = TREE_TYPE (arg1);
+	   enum tree_code code = TREE_CODE (itype); }
+    (switch
+      (if (FLOAT_TYPE_P (ty1)
+	   && FLOAT_TYPE_P (ty2)
+	   && FLOAT_TYPE_P (type)
+	   && DECIMAL_FLOAT_TYPE_P (itype) == DECIMAL_FLOAT_TYPE_P (type))
+	 (with { tree newtype = type;
+		 if (TYPE_MODE (ty1) == SDmode
+		     || TYPE_MODE (ty2) == SDmode
+		     || TYPE_MODE (type) == SDmode)
+		   newtype = dfloat32_type_node;
+		 if (TYPE_MODE (ty1) == DDmode
+		     || TYPE_MODE (ty2) == DDmode
+		     || TYPE_MODE (type) == DDmode)
+		   newtype = dfloat64_type_node;
+		 if (TYPE_MODE (ty1) == TDmode
+		     || TYPE_MODE (ty2) == TDmode
+		     || TYPE_MODE (type) == TDmode)
+		   newtype = dfloat128_type_node; }
+	  (if ((newtype == dfloat32_type_node
+		|| newtype == dfloat64_type_node
+		|| newtype == dfloat128_type_node)
+	       && newtype == type)
+	     (convert:newtype (op (convert:newtype @1) (convert:newtype @2)))
+	     (with { if (TYPE_PRECISION (ty1) > TYPE_PRECISION (newtype))
+		       newtype = ty1;
+		     if (TYPE_PRECISION (ty2) > TYPE_PRECISION (newtype))
+		       newtype = ty2; }
+		/* Sometimes this transformation is safe (cannot
+		   change results through affecting double rounding
+		   cases) and sometimes it is not.  If NEWTYPE is
+		   wider than TYPE, e.g. (float)((long double)double
+		   + (long double)double) converted to
+		   (float)(double + double), the transformation is
+		   unsafe regardless of the details of the types
+		   involved; double rounding can arise if the result
+		   of NEWTYPE arithmetic is a NEWTYPE value half way
+		   between two representable TYPE values but the
+		   exact value is sufficiently different (in the
+		   right direction) for this difference to be
+		   visible in ITYPE arithmetic.  If NEWTYPE is the
+		   same as TYPE, however, the transformation may be
+		   safe depending on the types involved: it is safe
+		   if the ITYPE has strictly more than twice as many
+		   mantissa bits as TYPE, can represent infinities
+		   and NaNs if the TYPE can, and has sufficient
+		   exponent range for the product or ratio of two
+		   values representable in the TYPE to be within the
+		   range of normal values of ITYPE.  */
+	       (if (TYPE_PRECISION (newtype) < TYPE_PRECISION (itype)
+		    && (flag_unsafe_math_optimizations
+		        || (TYPE_PRECISION (newtype) == TYPE_PRECISION (type)
+			    && real_can_shorten_arithmetic (TYPE_MODE (itype),
+							    TYPE_MODE (type))
+			    && !excess_precision_type (newtype))))
+		  (convert:newtype (op (convert:newtype @1) (convert:newtype @2)))
+	  )))) )
+
+      (if (code == REAL_TYPE)
+	/* Ignore the conversion if we don't need to store intermediate
+	   results and neither type is a decimal float.  */
+	  (if (!(flag_float_store
+	       || DECIMAL_FLOAT_TYPE_P (type)
+	       || DECIMAL_FLOAT_TYPE_P (itype))
+	      && types_match (ty1, ty2))
+	    (convert (op (convert:ty1 @1) (convert:ty2 @2)))))
+
+      /* If we have a narrowing conversion of an arithmetic operation where
+	 both operands are widening conversions from the same type as the outer
+	 narrowing conversion.  Then convert the innermost operands to a
+	 suitable unsigned type (to avoid introducing undefined behavior),
+	 perform the operation and convert the result to the desired type.  */
+      (if (INTEGRAL_TYPE_P (type)
+	   && op != MULT_EXPR
+	   && op != RDIV_EXPR
+	   /* We check for type compatibility between @0 and @1 below,
+	      so there's no need to check that @2/@4 are integral types.  */
+	   && INTEGRAL_TYPE_P (TREE_TYPE (@1))
+	   && INTEGRAL_TYPE_P (TREE_TYPE (@3))
+	   /* The precision of the type of each operand must match the
+	      precision of the mode of each operand, similarly for the
+	      result.  */
+	   && type_has_mode_precision_p (TREE_TYPE (@1))
+	   && type_has_mode_precision_p (TREE_TYPE (@2))
+	   && type_has_mode_precision_p (type)
+	   /* The inner conversion must be a widening conversion.  */
+	   && TYPE_PRECISION (TREE_TYPE (@3)) > TYPE_PRECISION (TREE_TYPE (@1))
+	   && types_match (@1, type)
+	   && (types_match (@1, @2)
+	       /* Or the second operand is const integer or converted const
+		  integer from valueize.  */
+	       || TREE_CODE (@2) == INTEGER_CST))
+        (if (TYPE_OVERFLOW_WRAPS (TREE_TYPE (@1)))
+	  (op @1 (convert @2))
+	  (with { tree utype = unsigned_type_for (TREE_TYPE (@1)); }
+	   (convert (op (convert:utype @1)
+		        (convert:utype @2))))))
+    )
+)))
 
 /* This is another case of narrowing, specifically when there's an outer
    BIT_AND_EXPR which masks off bits outside the type of the innermost
diff --git a/gcc/testsuite/gcc.dg/type-convert-var.c b/gcc/testsuite/gcc.dg/type-convert-var.c
new file mode 100644
index 0000000000000000000000000000000000000000..88d74e2a49d7123515b87ff64a18bd9b306d57e9
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/type-convert-var.c
@@ -0,0 +1,9 @@
+/* { dg-do compile } */
+/* { dg-additional-options "-O1 -fdump-tree-optimized" } */
+void foo (float a, float b, float *c)
+{
+  double e = (double)a * (double)b;
+  *c = (float)e;
+}
+
+/* { dg-final { scan-tree-dump-not {double} "optimized" } } */


^ permalink raw reply	[flat|nested] 16+ messages in thread

* RE: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)
  2019-06-25  8:31 [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch) Tamar Christina
@ 2019-06-25  8:33 ` Tamar Christina
  2019-06-25  9:02   ` Richard Biener
  0 siblings, 1 reply; 16+ messages in thread
From: Tamar Christina @ 2019-06-25  8:33 UTC (permalink / raw)
  To: Tamar Christina, gcc-patches; +Cc: nd, Jeff Law, ian, Joseph Myers, rguenther

Adding some maintainers

> -----Original Message-----
> From: gcc-patches-owner@gcc.gnu.org <gcc-patches-owner@gcc.gnu.org> On 
> Behalf Of Tamar Christina
> Sent: Tuesday, June 25, 2019 09:31
> To: gcc-patches@gcc.gnu.org
> Cc: nd <nd@arm.com>
> Subject: [GCC][middle-end] Add rules to strip away unneeded type casts 
> in expressions (2nd patch)
> 
> Hi All,
> 
> This is an updated version of my GCC-9 patch which moves part of the 
> type conversion code from convert.c to match.pd because match.pd is 
> able to apply this transformation in the presence of intermediate 
> temporary variables.
> 
> The previous patch was only regtested on aarch64-none-linux-gnu and I 
> hadn't done a regression on x86_64-pc-linux-gnu only a bootstrap.  The 
> previous patch was approved
> 
> here https://gcc.gnu.org/ml/gcc-patches/2018-12/msg00116.html
> but before committing I ran a x86_64-pc-linux-gnu regtest to be sure 
> and this showed an issue with a DFP test. I Have fixed this by 
> removing the offending convert.
> The convert was just saying "keep the type as is" but match.pd looped 
> here as it thinks the match did something and would try other 
> patterns, causing it to match itself again.
> 
> Instead when there's nothing to update, I just don't do anything.
> 
> The second change was to merge this with the existing pattern for 
> integer conversion in order to silence a warning from match.pd which 
> though that the two patterns overlaps because their match conditions 
> are similar (they have different conditions inside the ifs but 
> match.pd doesn't check those of course.).
> 
> Regtested and bootstrapped on aarch64-none-linux-gnu and x86_64-pc- 
> linux-gnu and no issues.
> 
> Ok for trunk?
> 
> Thanks,
> Tamar
> 
> Concretely it makes both these cases behave the same
> 
>   float e = (float)a * (float)b;
>   *c = (_Float16)e;
> 
> and
> 
>   *c = (_Float16)((float)a * (float)b);
> 
> Thanks,
> Tamar
> 
> gcc/ChangeLog:
> 
> 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> 
> 	* convert.c (convert_to_real_1): Move part of conversion code...
> 	* match.pd: ...To here.
> 
> gcc/testsuite/ChangeLog:
> 
> 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> 
> 	* gcc.dg/type-convert-var.c: New test.
> 
> --

^ permalink raw reply	[flat|nested] 16+ messages in thread

* RE: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)
  2019-06-25  8:33 ` Tamar Christina
@ 2019-06-25  9:02   ` Richard Biener
  2019-07-02  9:41     ` Tamar Christina
  0 siblings, 1 reply; 16+ messages in thread
From: Richard Biener @ 2019-06-25  9:02 UTC (permalink / raw)
  To: Tamar Christina; +Cc: gcc-patches, nd, Jeff Law, ian, Joseph Myers

[-- Attachment #1: Type: text/plain, Size: 5024 bytes --]

On Tue, 25 Jun 2019, Tamar Christina wrote:

> Adding some maintainers
> 
> > -----Original Message-----
> > From: gcc-patches-owner@gcc.gnu.org <gcc-patches-owner@gcc.gnu.org> On 
> > Behalf Of Tamar Christina
> > Sent: Tuesday, June 25, 2019 09:31
> > To: gcc-patches@gcc.gnu.org
> > Cc: nd <nd@arm.com>
> > Subject: [GCC][middle-end] Add rules to strip away unneeded type casts 
> > in expressions (2nd patch)
> > 
> > Hi All,
> > 
> > This is an updated version of my GCC-9 patch which moves part of the 
> > type conversion code from convert.c to match.pd because match.pd is 
> > able to apply this transformation in the presence of intermediate 
> > temporary variables.
> > 
> > The previous patch was only regtested on aarch64-none-linux-gnu and I 
> > hadn't done a regression on x86_64-pc-linux-gnu only a bootstrap.  The 
> > previous patch was approved
> > 
> > here https://gcc.gnu.org/ml/gcc-patches/2018-12/msg00116.html
> > but before committing I ran a x86_64-pc-linux-gnu regtest to be sure 
> > and this showed an issue with a DFP test. I Have fixed this by 
> > removing the offending convert.
> > The convert was just saying "keep the type as is" but match.pd looped 
> > here as it thinks the match did something and would try other 
> > patterns, causing it to match itself again.
> > 
> > Instead when there's nothing to update, I just don't do anything.
> > 
> > The second change was to merge this with the existing pattern for 
> > integer conversion in order to silence a warning from match.pd which 
> > though that the two patterns overlaps because their match conditions 
> > are similar (they have different conditions inside the ifs but 
> > match.pd doesn't check those of course.).
> > 
> > Regtested and bootstrapped on aarch64-none-linux-gnu and x86_64-pc- 
> > linux-gnu and no issues.
> > 
> > Ok for trunk?

This looks like a literal 1:1 translation plus merging with the
existing pattern around integers.  You changed
(op:s@0 (convert@3 @1) (convert?@4 @2)) to
(op:s@0 (convert1?@3 @1) (convert2?@4 @2)) where this now also
matches if there are no inner conversions at all - was that a
desired change or did you merely want to catch when the first
operand is not a conversion but the second is, possibly only
for the RDIV_EXPR case?

+(for op (plus minus mult rdiv)
+ (simplify
+   (convert (op:s@0 (convert1?@3 @1) (convert2?@4 @2)))
+   (with { tree arg0 = strip_float_extensions (@1);
+          tree arg1 = strip_float_extensions (@2);
+          tree itype = TREE_TYPE (@0);

you now unconditionally call strip_float_extensions on each operand
even for the integer case, please sink stuff only used in one
case arm.  I guess keeping the integer case first via

  (if (INTEGRAL_TYPE_P (type)
...
   (with { tree arg0 = strip_float_extensions (@1);
...

should work (with the 'with' being in the ifs else position).

+      (if (code == REAL_TYPE)
+       /* Ignore the conversion if we don't need to store intermediate
+          results and neither type is a decimal float.  */
+         (if (!(flag_float_store
+              || DECIMAL_FLOAT_TYPE_P (type)
+              || DECIMAL_FLOAT_TYPE_P (itype))
+             && types_match (ty1, ty2))
+           (convert (op (convert:ty1 @1) (convert:ty2 @2)))))

this looks prone to the same recursion issue you described above.

'code' is used exactly once, using SCALAR_FLOAT_TYPE_P (itype)
in the above test would be clearer.  Also both ifs can be combined.
The snipped above also doesn't appear in the convert.c code you
remove and the original one is

  switch (TREE_CODE (TREE_TYPE (expr)))
    {
    case REAL_TYPE:
      /* Ignore the conversion if we don't need to store intermediate
         results and neither type is a decimal float.  */
      return build1_loc (loc,
                         (flag_float_store
                          || DECIMAL_FLOAT_TYPE_P (type)
                          || DECIMAL_FLOAT_TYPE_P (itype))
                         ? CONVERT_EXPR : NOP_EXPR, type, expr);

which as far as I can see doesn't do anything besides
exchanging CONVERT_EXPR for NOP_EXPR which is a noop to the IL.
So it appears this shouldn't be moved to match.pd at all?
It's also not a 1:1 move since you are changing 'expr'.

Thanks,
Richard.

> > Thanks,
> > Tamar
> > 
> > Concretely it makes both these cases behave the same
> > 
> >   float e = (float)a * (float)b;
> >   *c = (_Float16)e;
> > 
> > and
> > 
> >   *c = (_Float16)((float)a * (float)b);
> > 
> > Thanks,
> > Tamar
> > 
> > gcc/ChangeLog:
> > 
> > 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> > 
> > 	* convert.c (convert_to_real_1): Move part of conversion code...
> > 	* match.pd: ...To here.
> > 
> > gcc/testsuite/ChangeLog:
> > 
> > 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> > 
> > 	* gcc.dg/type-convert-var.c: New test.
> > 
> > --
> 

-- 
Richard Biener <rguenther@suse.de>
SUSE Linux GmbH, Maxfeldstrasse 5, 90409 Nuernberg, Germany;
GF: Felix Imendörffer, Mary Higgins, Sri Rasiah; HRB 21284 (AG Nürnberg)

^ permalink raw reply	[flat|nested] 16+ messages in thread

* Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)
  2019-06-25  9:02   ` Richard Biener
@ 2019-07-02  9:41     ` Tamar Christina
  2019-07-02 10:20       ` Richard Biener
  0 siblings, 1 reply; 16+ messages in thread
From: Tamar Christina @ 2019-07-02  9:41 UTC (permalink / raw)
  To: Richard Biener; +Cc: gcc-patches, nd, Jeff Law, ian, Joseph Myers

Hi Richi,

The 06/25/2019 10:02, Richard Biener wrote:
> 
> This looks like a literal 1:1 translation plus merging with the
> existing pattern around integers.  You changed
> (op:s@0 (convert@3 @1) (convert?@4 @2)) to
> (op:s@0 (convert1?@3 @1) (convert2?@4 @2)) where this now also
> matches if there are no inner conversions at all - was that a
> desired change or did you merely want to catch when the first
> operand is not a conversion but the second is, possibly only
> for the RDIV_EXPR case?
>

Yes, the ? ? is for the RDIV case, I really only want (c a) `op` (c b),
a `op` (c b) and (c a) `op` b.  But didn't find a way to do this.

The only thing I can think of that gets this is without overmatching is
to either duplicate the code or move this back to a C helper function and
call that from match.pd.  But I was hoping to have it all in match.pd
instead of hiding it away in a C call.

Do you have a better way of doing it or a preference to an approach?
 
> +(for op (plus minus mult rdiv)
> + (simplify
> +   (convert (op:s@0 (convert1?@3 @1) (convert2?@4 @2)))
> +   (with { tree arg0 = strip_float_extensions (@1);
> +          tree arg1 = strip_float_extensions (@2);
> +          tree itype = TREE_TYPE (@0);
> 
> you now unconditionally call strip_float_extensions on each operand
> even for the integer case, please sink stuff only used in one
> case arm.  I guess keeping the integer case first via
> 

Done, Initially didn't think it would be an issue since I don't use the value it
creates in the integer case. But I re-ordered it.
 
> should work (with the 'with' being in the ifs else position).
> 
> +      (if (code == REAL_TYPE)
> +       /* Ignore the conversion if we don't need to store intermediate
> +          results and neither type is a decimal float.  */
> +         (if (!(flag_float_store
> +              || DECIMAL_FLOAT_TYPE_P (type)
> +              || DECIMAL_FLOAT_TYPE_P (itype))
> +             && types_match (ty1, ty2))
> +           (convert (op (convert:ty1 @1) (convert:ty2 @2)))))
> 
> this looks prone to the same recursion issue you described above.

It's to break the recursion when you don't match anything. Indeed don't need it if
I change the match condition above.

Thanks,
Tamar
> 
> 'code' is used exactly once, using SCALAR_FLOAT_TYPE_P (itype)
> in the above test would be clearer.  Also both ifs can be combined.
> The snipped above also doesn't appear in the convert.c code you
> remove and the original one is
> 
>   switch (TREE_CODE (TREE_TYPE (expr)))
>     {
>     case REAL_TYPE:
>       /* Ignore the conversion if we don't need to store intermediate
>          results and neither type is a decimal float.  */
>       return build1_loc (loc,
>                          (flag_float_store
>                           || DECIMAL_FLOAT_TYPE_P (type)
>                           || DECIMAL_FLOAT_TYPE_P (itype))
>                          ? CONVERT_EXPR : NOP_EXPR, type, expr);
> 
> which as far as I can see doesn't do anything besides
> exchanging CONVERT_EXPR for NOP_EXPR which is a noop to the IL.
> So it appears this shouldn't be moved to match.pd at all?
> It's also not a 1:1 move since you are changing 'expr'.
> 
> Thanks,
> Richard.
> 
> > > Thanks,
> > > Tamar
> > > 
> > > Concretely it makes both these cases behave the same
> > > 
> > >   float e = (float)a * (float)b;
> > >   *c = (_Float16)e;
> > > 
> > > and
> > > 
> > >   *c = (_Float16)((float)a * (float)b);
> > > 
> > > Thanks,
> > > Tamar
> > > 
> > > gcc/ChangeLog:
> > > 
> > > 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> > > 
> > > 	* convert.c (convert_to_real_1): Move part of conversion code...
> > > 	* match.pd: ...To here.
> > > 
> > > gcc/testsuite/ChangeLog:
> > > 
> > > 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> > > 
> > > 	* gcc.dg/type-convert-var.c: New test.
> > > 
> > > --
> > 
> 
> -- 
> Richard Biener <rguenther@suse.de>
> SUSE Linux GmbH, Maxfeldstrasse 5, 90409 Nuernberg, Germany;
> GF: Felix Imendörffer, Mary Higgins, Sri Rasiah; HRB 21284 (AG Nürnberg)

-- 

^ permalink raw reply	[flat|nested] 16+ messages in thread

* Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)
  2019-07-02  9:41     ` Tamar Christina
@ 2019-07-02 10:20       ` Richard Biener
  2019-07-02 16:44         ` Tamar Christina
  0 siblings, 1 reply; 16+ messages in thread
From: Richard Biener @ 2019-07-02 10:20 UTC (permalink / raw)
  To: Tamar Christina; +Cc: gcc-patches, nd, Jeff Law, ian, Joseph Myers

[-- Attachment #1: Type: text/plain, Size: 4897 bytes --]

On Tue, 2 Jul 2019, Tamar Christina wrote:

> Hi Richi,
> 
> The 06/25/2019 10:02, Richard Biener wrote:
> > 
> > This looks like a literal 1:1 translation plus merging with the
> > existing pattern around integers.  You changed
> > (op:s@0 (convert@3 @1) (convert?@4 @2)) to
> > (op:s@0 (convert1?@3 @1) (convert2?@4 @2)) where this now also
> > matches if there are no inner conversions at all - was that a
> > desired change or did you merely want to catch when the first
> > operand is not a conversion but the second is, possibly only
> > for the RDIV_EXPR case?
> >
> 
> Yes, the ? ? is for the RDIV case, I really only want (c a) `op` (c b),
> a `op` (c b) and (c a) `op` b.  But didn't find a way to do this.

One way would be to do

 (simplify
  (convert (op:sc@0 (convert @1) (convert? @2)))

but that doesn't work for RDIV.  Using :C is tempting but you
do not get to know the original operand order which you of
course need.  So I guess the way you do it is fine - you
could guard all of the code with a few types_match () checks
but I'm not sure it is worth the trouble.

Richard.

> The only thing I can think of that gets this is without overmatching is
> to either duplicate the code or move this back to a C helper function and
> call that from match.pd.  But I was hoping to have it all in match.pd
> instead of hiding it away in a C call.
> 
> Do you have a better way of doing it or a preference to an approach?
>  
> > +(for op (plus minus mult rdiv)
> > + (simplify
> > +   (convert (op:s@0 (convert1?@3 @1) (convert2?@4 @2)))
> > +   (with { tree arg0 = strip_float_extensions (@1);
> > +          tree arg1 = strip_float_extensions (@2);
> > +          tree itype = TREE_TYPE (@0);
> > 
> > you now unconditionally call strip_float_extensions on each operand
> > even for the integer case, please sink stuff only used in one
> > case arm.  I guess keeping the integer case first via
> > 
> 
> Done, Initially didn't think it would be an issue since I don't use the value it
> creates in the integer case. But I re-ordered it.
>  
> > should work (with the 'with' being in the ifs else position).
> > 
> > +      (if (code == REAL_TYPE)
> > +       /* Ignore the conversion if we don't need to store intermediate
> > +          results and neither type is a decimal float.  */
> > +         (if (!(flag_float_store
> > +              || DECIMAL_FLOAT_TYPE_P (type)
> > +              || DECIMAL_FLOAT_TYPE_P (itype))
> > +             && types_match (ty1, ty2))
> > +           (convert (op (convert:ty1 @1) (convert:ty2 @2)))))
> > 
> > this looks prone to the same recursion issue you described above.
> 
> It's to break the recursion when you don't match anything. Indeed don't need it if
> I change the match condition above.
> Thanks,
> Tamar
> > 
> > 'code' is used exactly once, using SCALAR_FLOAT_TYPE_P (itype)
> > in the above test would be clearer.  Also both ifs can be combined.
> > The snipped above also doesn't appear in the convert.c code you
> > remove and the original one is
> > 
> >   switch (TREE_CODE (TREE_TYPE (expr)))
> >     {
> >     case REAL_TYPE:
> >       /* Ignore the conversion if we don't need to store intermediate
> >          results and neither type is a decimal float.  */
> >       return build1_loc (loc,
> >                          (flag_float_store
> >                           || DECIMAL_FLOAT_TYPE_P (type)
> >                           || DECIMAL_FLOAT_TYPE_P (itype))
> >                          ? CONVERT_EXPR : NOP_EXPR, type, expr);
> > 
> > which as far as I can see doesn't do anything besides
> > exchanging CONVERT_EXPR for NOP_EXPR which is a noop to the IL.
> > So it appears this shouldn't be moved to match.pd at all?
> > It's also not a 1:1 move since you are changing 'expr'.
> > 
> > Thanks,
> > Richard.
> > 
> > > > Thanks,
> > > > Tamar
> > > > 
> > > > Concretely it makes both these cases behave the same
> > > > 
> > > >   float e = (float)a * (float)b;
> > > >   *c = (_Float16)e;
> > > > 
> > > > and
> > > > 
> > > >   *c = (_Float16)((float)a * (float)b);
> > > > 
> > > > Thanks,
> > > > Tamar
> > > > 
> > > > gcc/ChangeLog:
> > > > 
> > > > 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> > > > 
> > > > 	* convert.c (convert_to_real_1): Move part of conversion code...
> > > > 	* match.pd: ...To here.
> > > > 
> > > > gcc/testsuite/ChangeLog:
> > > > 
> > > > 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> > > > 
> > > > 	* gcc.dg/type-convert-var.c: New test.
> > > > 
> > > > --
> > > 
> > 
> > -- 
> > Richard Biener <rguenther@suse.de>
> > SUSE Linux GmbH, Maxfeldstrasse 5, 90409 Nuernberg, Germany;
> > GF: Felix Imendörffer, Mary Higgins, Sri Rasiah; HRB 21284 (AG Nürnberg)
> 
> 

-- 
Richard Biener <rguenther@suse.de>
SUSE Linux GmbH, Maxfeldstrasse 5, 90409 Nuernberg, Germany;
GF: Felix Imendörffer, Mary Higgins, Sri Rasiah; HRB 21284 (AG Nürnberg)

^ permalink raw reply	[flat|nested] 16+ messages in thread

* Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)
  2019-07-02 10:20       ` Richard Biener
@ 2019-07-02 16:44         ` Tamar Christina
  2019-07-03  9:06           ` Richard Biener
                             ` (2 more replies)
  0 siblings, 3 replies; 16+ messages in thread
From: Tamar Christina @ 2019-07-02 16:44 UTC (permalink / raw)
  To: Richard Biener; +Cc: gcc-patches, nd, Jeff Law, ian, Joseph Myers

[-- Attachment #1: Type: text/plain, Size: 5584 bytes --]


Hi All,

Here's an updated patch with the changes processed from the previous review.

I've bootstrapped and regtested on aarch64-none-linux-gnu and x86_64-pc-linux-gnu and no issues.

Ok for trunk?

Thanks,
Tamar

The 07/02/2019 11:20, Richard Biener wrote:
> On Tue, 2 Jul 2019, Tamar Christina wrote:
> 
> > Hi Richi,
> > 
> > The 06/25/2019 10:02, Richard Biener wrote:
> > > 
> > > This looks like a literal 1:1 translation plus merging with the
> > > existing pattern around integers.  You changed
> > > (op:s@0 (convert@3 @1) (convert?@4 @2)) to
> > > (op:s@0 (convert1?@3 @1) (convert2?@4 @2)) where this now also
> > > matches if there are no inner conversions at all - was that a
> > > desired change or did you merely want to catch when the first
> > > operand is not a conversion but the second is, possibly only
> > > for the RDIV_EXPR case?
> > >
> > 
> > Yes, the ? ? is for the RDIV case, I really only want (c a) `op` (c b),
> > a `op` (c b) and (c a) `op` b.  But didn't find a way to do this.
> 
> One way would be to do
> 
>  (simplify
>   (convert (op:sc@0 (convert @1) (convert? @2)))
> 
> but that doesn't work for RDIV.  Using :C is tempting but you
> do not get to know the original operand order which you of
> course need.  So I guess the way you do it is fine - you
> could guard all of the code with a few types_match () checks
> but I'm not sure it is worth the trouble.
> 
> Richard.
> 
> > The only thing I can think of that gets this is without overmatching is
> > to either duplicate the code or move this back to a C helper function and
> > call that from match.pd.  But I was hoping to have it all in match.pd
> > instead of hiding it away in a C call.
> > 
> > Do you have a better way of doing it or a preference to an approach?
> >  
> > > +(for op (plus minus mult rdiv)
> > > + (simplify
> > > +   (convert (op:s@0 (convert1?@3 @1) (convert2?@4 @2)))
> > > +   (with { tree arg0 = strip_float_extensions (@1);
> > > +          tree arg1 = strip_float_extensions (@2);
> > > +          tree itype = TREE_TYPE (@0);
> > > 
> > > you now unconditionally call strip_float_extensions on each operand
> > > even for the integer case, please sink stuff only used in one
> > > case arm.  I guess keeping the integer case first via
> > > 
> > 
> > Done, Initially didn't think it would be an issue since I don't use the value it
> > creates in the integer case. But I re-ordered it.
> >  
> > > should work (with the 'with' being in the ifs else position).
> > > 
> > > +      (if (code == REAL_TYPE)
> > > +       /* Ignore the conversion if we don't need to store intermediate
> > > +          results and neither type is a decimal float.  */
> > > +         (if (!(flag_float_store
> > > +              || DECIMAL_FLOAT_TYPE_P (type)
> > > +              || DECIMAL_FLOAT_TYPE_P (itype))
> > > +             && types_match (ty1, ty2))
> > > +           (convert (op (convert:ty1 @1) (convert:ty2 @2)))))
> > > 
> > > this looks prone to the same recursion issue you described above.
> > 
> > It's to break the recursion when you don't match anything. Indeed don't need it if
> > I change the match condition above.
> > Thanks,
> > Tamar
> > > 
> > > 'code' is used exactly once, using SCALAR_FLOAT_TYPE_P (itype)
> > > in the above test would be clearer.  Also both ifs can be combined.
> > > The snipped above also doesn't appear in the convert.c code you
> > > remove and the original one is
> > > 
> > >   switch (TREE_CODE (TREE_TYPE (expr)))
> > >     {
> > >     case REAL_TYPE:
> > >       /* Ignore the conversion if we don't need to store intermediate
> > >          results and neither type is a decimal float.  */
> > >       return build1_loc (loc,
> > >                          (flag_float_store
> > >                           || DECIMAL_FLOAT_TYPE_P (type)
> > >                           || DECIMAL_FLOAT_TYPE_P (itype))
> > >                          ? CONVERT_EXPR : NOP_EXPR, type, expr);
> > > 
> > > which as far as I can see doesn't do anything besides
> > > exchanging CONVERT_EXPR for NOP_EXPR which is a noop to the IL.
> > > So it appears this shouldn't be moved to match.pd at all?
> > > It's also not a 1:1 move since you are changing 'expr'.
> > > 
> > > Thanks,
> > > Richard.
> > > 
> > > > > Thanks,
> > > > > Tamar
> > > > > 
> > > > > Concretely it makes both these cases behave the same
> > > > > 
> > > > >   float e = (float)a * (float)b;
> > > > >   *c = (_Float16)e;
> > > > > 
> > > > > and
> > > > > 
> > > > >   *c = (_Float16)((float)a * (float)b);
> > > > > 
> > > > > Thanks,
> > > > > Tamar
> > > > > 
> > > > > gcc/ChangeLog:
> > > > > 
> > > > > 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> > > > > 
> > > > > 	* convert.c (convert_to_real_1): Move part of conversion code...
> > > > > 	* match.pd: ...To here.
> > > > > 
> > > > > gcc/testsuite/ChangeLog:
> > > > > 
> > > > > 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> > > > > 
> > > > > 	* gcc.dg/type-convert-var.c: New test.
> > > > > 
> > > > > --
> > > > 
> > > 
> > > -- 
> > > Richard Biener <rguenther@suse.de>
> > > SUSE Linux GmbH, Maxfeldstrasse 5, 90409 Nuernberg, Germany;
> > > GF: Felix Imendörffer, Mary Higgins, Sri Rasiah; HRB 21284 (AG Nürnberg)
> > 
> > 
> 
> -- 
> Richard Biener <rguenther@suse.de>
> SUSE Linux GmbH, Maxfeldstrasse 5, 90409 Nuernberg, Germany;
> GF: Felix Imendörffer, Mary Higgins, Sri Rasiah; HRB 21284 (AG Nürnberg)

-- 

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #2: rb10277.patch --]
[-- Type: text/x-diff; name="rb10277.patch", Size: 11102 bytes --]

diff --git a/gcc/convert.c b/gcc/convert.c
index a8f2bd049ba0cd83865ba0a5f7d74f9cdbad0d09..7f0d933f4d9e29719acb27eb1b32a9e540d93073 100644
--- a/gcc/convert.c
+++ b/gcc/convert.c
@@ -298,92 +298,6 @@ convert_to_real_1 (tree type, tree expr, bool fold_p)
 	      return build1 (TREE_CODE (expr), type, arg);
 	    }
 	  break;
-	/* Convert (outertype)((innertype0)a+(innertype1)b)
-	   into ((newtype)a+(newtype)b) where newtype
-	   is the widest mode from all of these.  */
-	case PLUS_EXPR:
-	case MINUS_EXPR:
-	case MULT_EXPR:
-	case RDIV_EXPR:
-	   {
-	     tree arg0 = strip_float_extensions (TREE_OPERAND (expr, 0));
-	     tree arg1 = strip_float_extensions (TREE_OPERAND (expr, 1));
-
-	     if (FLOAT_TYPE_P (TREE_TYPE (arg0))
-		 && FLOAT_TYPE_P (TREE_TYPE (arg1))
-		 && DECIMAL_FLOAT_TYPE_P (itype) == DECIMAL_FLOAT_TYPE_P (type))
-	       {
-		  tree newtype = type;
-
-		  if (TYPE_MODE (TREE_TYPE (arg0)) == SDmode
-		      || TYPE_MODE (TREE_TYPE (arg1)) == SDmode
-		      || TYPE_MODE (type) == SDmode)
-		    newtype = dfloat32_type_node;
-		  if (TYPE_MODE (TREE_TYPE (arg0)) == DDmode
-		      || TYPE_MODE (TREE_TYPE (arg1)) == DDmode
-		      || TYPE_MODE (type) == DDmode)
-		    newtype = dfloat64_type_node;
-		  if (TYPE_MODE (TREE_TYPE (arg0)) == TDmode
-		      || TYPE_MODE (TREE_TYPE (arg1)) == TDmode
-		      || TYPE_MODE (type) == TDmode)
-                    newtype = dfloat128_type_node;
-		  if (newtype == dfloat32_type_node
-		      || newtype == dfloat64_type_node
-		      || newtype == dfloat128_type_node)
-		    {
-		      expr = build2 (TREE_CODE (expr), newtype,
-				     convert_to_real_1 (newtype, arg0,
-							fold_p),
-				     convert_to_real_1 (newtype, arg1,
-							fold_p));
-		      if (newtype == type)
-			return expr;
-		      break;
-		    }
-
-		  if (TYPE_PRECISION (TREE_TYPE (arg0)) > TYPE_PRECISION (newtype))
-		    newtype = TREE_TYPE (arg0);
-		  if (TYPE_PRECISION (TREE_TYPE (arg1)) > TYPE_PRECISION (newtype))
-		    newtype = TREE_TYPE (arg1);
-		  /* Sometimes this transformation is safe (cannot
-		     change results through affecting double rounding
-		     cases) and sometimes it is not.  If NEWTYPE is
-		     wider than TYPE, e.g. (float)((long double)double
-		     + (long double)double) converted to
-		     (float)(double + double), the transformation is
-		     unsafe regardless of the details of the types
-		     involved; double rounding can arise if the result
-		     of NEWTYPE arithmetic is a NEWTYPE value half way
-		     between two representable TYPE values but the
-		     exact value is sufficiently different (in the
-		     right direction) for this difference to be
-		     visible in ITYPE arithmetic.  If NEWTYPE is the
-		     same as TYPE, however, the transformation may be
-		     safe depending on the types involved: it is safe
-		     if the ITYPE has strictly more than twice as many
-		     mantissa bits as TYPE, can represent infinities
-		     and NaNs if the TYPE can, and has sufficient
-		     exponent range for the product or ratio of two
-		     values representable in the TYPE to be within the
-		     range of normal values of ITYPE.  */
-		  if (TYPE_PRECISION (newtype) < TYPE_PRECISION (itype)
-		      && (flag_unsafe_math_optimizations
-			  || (TYPE_PRECISION (newtype) == TYPE_PRECISION (type)
-			      && real_can_shorten_arithmetic (TYPE_MODE (itype),
-							      TYPE_MODE (type))
-			      && !excess_precision_type (newtype))))
-		    {
-		      expr = build2 (TREE_CODE (expr), newtype,
-				     convert_to_real_1 (newtype, arg0,
-							fold_p),
-				     convert_to_real_1 (newtype, arg1,
-							fold_p));
-		      if (newtype == type)
-			return expr;
-		    }
-	       }
-	   }
-	  break;
 	default:
 	  break;
       }
diff --git a/gcc/match.pd b/gcc/match.pd
index f8e35e96d22036bb0b96fbdbe2c7a346f4695067..66a1ad385ffff4456c87a8891ab78c437fefc64f 100644
--- a/gcc/match.pd
+++ b/gcc/match.pd
@@ -4937,37 +4937,106 @@ DEFINE_INT_AND_FLOAT_ROUND_FN (RINT)
    the C/C++ front-ends by shorten_binary_op and shorten_compare.  Long
    term we want to move all that code out of the front-ends into here.  */
 
-/* If we have a narrowing conversion of an arithmetic operation where
-   both operands are widening conversions from the same type as the outer
-   narrowing conversion.  Then convert the innermost operands to a suitable
-   unsigned type (to avoid introducing undefined behavior), perform the
-   operation and convert the result to the desired type.  */
-(for op (plus minus)
-  (simplify
-    (convert (op:s (convert@2 @0) (convert?@3 @1)))
-    (if (INTEGRAL_TYPE_P (type)
-	 /* We check for type compatibility between @0 and @1 below,
-	    so there's no need to check that @1/@3 are integral types.  */
-	 && INTEGRAL_TYPE_P (TREE_TYPE (@0))
-	 && INTEGRAL_TYPE_P (TREE_TYPE (@2))
-	 /* The precision of the type of each operand must match the
-	    precision of the mode of each operand, similarly for the
-	    result.  */
-	 && type_has_mode_precision_p (TREE_TYPE (@0))
-	 && type_has_mode_precision_p (TREE_TYPE (@1))
-	 && type_has_mode_precision_p (type)
-	 /* The inner conversion must be a widening conversion.  */
-	 && TYPE_PRECISION (TREE_TYPE (@2)) > TYPE_PRECISION (TREE_TYPE (@0))
-	 && types_match (@0, type)
-	 && (types_match (@0, @1)
-	     /* Or the second operand is const integer or converted const
-		integer from valueize.  */
-	     || TREE_CODE (@1) == INTEGER_CST))
-      (if (TYPE_OVERFLOW_WRAPS (TREE_TYPE (@0)))
-	(op @0 (convert @1))
-	(with { tree utype = unsigned_type_for (TREE_TYPE (@0)); }
-	 (convert (op (convert:utype @0)
-		      (convert:utype @1))))))))
+/* Convert (outertype)((innertype0)a+(innertype1)b)
+   into ((newtype)a+(newtype)b) where newtype
+   is the widest mode from all of these.  */
+(for op (plus minus mult rdiv)
+ (simplify
+   (convert (op:s@0 (convert1?@3 @1) (convert2?@4 @2)))
+   /* If we have a narrowing conversion of an arithmetic operation where
+      both operands are widening conversions from the same type as the outer
+      narrowing conversion.  Then convert the innermost operands to a
+      suitable unsigned type (to avoid introducing undefined behavior),
+      perform the operation and convert the result to the desired type.  */
+   (if (INTEGRAL_TYPE_P (type)
+	&& op != MULT_EXPR
+	&& op != RDIV_EXPR
+	/* We check for type compatibility between @0 and @1 below,
+	   so there's no need to check that @2/@4 are integral types.  */
+	&& INTEGRAL_TYPE_P (TREE_TYPE (@1))
+	&& INTEGRAL_TYPE_P (TREE_TYPE (@3))
+	/* The precision of the type of each operand must match the
+	   precision of the mode of each operand, similarly for the
+	   result.  */
+	&& type_has_mode_precision_p (TREE_TYPE (@1))
+	&& type_has_mode_precision_p (TREE_TYPE (@2))
+	&& type_has_mode_precision_p (type)
+	/* The inner conversion must be a widening conversion.  */
+	&& TYPE_PRECISION (TREE_TYPE (@3)) > TYPE_PRECISION (TREE_TYPE (@1))
+	&& types_match (@1, type)
+	&& (types_match (@1, @2)
+	    /* Or the second operand is const integer or converted const
+	       integer from valueize.  */
+	    || TREE_CODE (@2) == INTEGER_CST))
+     (if (TYPE_OVERFLOW_WRAPS (TREE_TYPE (@1)))
+       (op @1 (convert @2))
+       (with { tree utype = unsigned_type_for (TREE_TYPE (@1)); }
+       (convert (op (convert:utype @1)
+		    (convert:utype @2)))))
+      (with { tree arg0 = strip_float_extensions (@1);
+	      tree arg1 = strip_float_extensions (@2);
+	      tree itype = TREE_TYPE (@0);
+	      tree ty1 = TREE_TYPE (arg0);
+	      tree ty2 = TREE_TYPE (arg1);
+	      enum tree_code code = TREE_CODE (itype); }
+	(if (FLOAT_TYPE_P (ty1)
+	     && FLOAT_TYPE_P (ty2)
+	     && FLOAT_TYPE_P (type)
+	     && DECIMAL_FLOAT_TYPE_P (itype) == DECIMAL_FLOAT_TYPE_P (type))
+	 (with { tree newtype = type;
+		 if (TYPE_MODE (ty1) == SDmode
+		     || TYPE_MODE (ty2) == SDmode
+		     || TYPE_MODE (type) == SDmode)
+		   newtype = dfloat32_type_node;
+		 if (TYPE_MODE (ty1) == DDmode
+		     || TYPE_MODE (ty2) == DDmode
+		     || TYPE_MODE (type) == DDmode)
+		   newtype = dfloat64_type_node;
+		 if (TYPE_MODE (ty1) == TDmode
+		     || TYPE_MODE (ty2) == TDmode
+		     || TYPE_MODE (type) == TDmode)
+		   newtype = dfloat128_type_node; }
+	  (if ((newtype == dfloat32_type_node
+		|| newtype == dfloat64_type_node
+		|| newtype == dfloat128_type_node)
+	      && newtype == type)
+	    (convert:newtype (op (convert:newtype @1) (convert:newtype @2)))
+	    (with { if (TYPE_PRECISION (ty1) > TYPE_PRECISION (newtype))
+		      newtype = ty1;
+		    if (TYPE_PRECISION (ty2) > TYPE_PRECISION (newtype))
+		      newtype = ty2; }
+	       /* Sometimes this transformation is safe (cannot
+		  change results through affecting double rounding
+		  cases) and sometimes it is not.  If NEWTYPE is
+		  wider than TYPE, e.g. (float)((long double)double
+		  + (long double)double) converted to
+		  (float)(double + double), the transformation is
+		  unsafe regardless of the details of the types
+		  involved; double rounding can arise if the result
+		  of NEWTYPE arithmetic is a NEWTYPE value half way
+		  between two representable TYPE values but the
+		  exact value is sufficiently different (in the
+		  right direction) for this difference to be
+		  visible in ITYPE arithmetic.  If NEWTYPE is the
+		  same as TYPE, however, the transformation may be
+		  safe depending on the types involved: it is safe
+		  if the ITYPE has strictly more than twice as many
+		  mantissa bits as TYPE, can represent infinities
+		  and NaNs if the TYPE can, and has sufficient
+		  exponent range for the product or ratio of two
+		  values representable in the TYPE to be within the
+		  range of normal values of ITYPE.  */
+	      (if (TYPE_PRECISION (newtype) < TYPE_PRECISION (itype)
+		   && (flag_unsafe_math_optimizations
+		       || (TYPE_PRECISION (newtype) == TYPE_PRECISION (type)
+			   && real_can_shorten_arithmetic (TYPE_MODE (itype),
+							   TYPE_MODE (type))
+			   && !excess_precision_type (newtype))))
+		 (convert:newtype (op (convert:newtype @1)
+				      (convert:newtype @2)))
+	 )))) )
+   )
+)))
 
 /* This is another case of narrowing, specifically when there's an outer
    BIT_AND_EXPR which masks off bits outside the type of the innermost
diff --git a/gcc/testsuite/gcc.dg/type-convert-var.c b/gcc/testsuite/gcc.dg/type-convert-var.c
new file mode 100644
index 0000000000000000000000000000000000000000..88d74e2a49d7123515b87ff64a18bd9b306d57e9
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/type-convert-var.c
@@ -0,0 +1,9 @@
+/* { dg-do compile } */
+/* { dg-additional-options "-O1 -fdump-tree-optimized" } */
+void foo (float a, float b, float *c)
+{
+  double e = (double)a * (double)b;
+  *c = (float)e;
+}
+
+/* { dg-final { scan-tree-dump-not {double} "optimized" } } */


^ permalink raw reply	[flat|nested] 16+ messages in thread

* Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)
  2019-07-02 16:44         ` Tamar Christina
@ 2019-07-03  9:06           ` Richard Biener
  2019-07-30  7:05           ` [PATCH] Fix up gcc.dg/type-convert-var.c testcase (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)) Jakub Jelinek
  2019-07-30  7:11           ` Fix up -fexcess-precision handling in LTO " Jakub Jelinek
  2 siblings, 0 replies; 16+ messages in thread
From: Richard Biener @ 2019-07-03  9:06 UTC (permalink / raw)
  To: Tamar Christina; +Cc: gcc-patches, nd, Jeff Law, ian, Joseph Myers

[-- Attachment #1: Type: text/plain, Size: 8067 bytes --]

On Tue, 2 Jul 2019, Tamar Christina wrote:

> 
> Hi All,
> 
> Here's an updated patch with the changes processed from the previous review.
> 
> I've bootstrapped and regtested on aarch64-none-linux-gnu and x86_64-pc-linux-gnu and no issues.
> 
> Ok for trunk?

+     (if (TYPE_OVERFLOW_WRAPS (TREE_TYPE (@1)))
+       (op @1 (convert @2))
+       (with { tree utype = unsigned_type_for (TREE_TYPE (@1)); }
+       (convert (op (convert:utype @1)

indenting is off, one space more for (convert (it's inside the with)

+                   (convert:utype @2)))))
+      (with { tree arg0 = strip_float_extensions (@1);

indenting is off here, one space less for the (with please.

you'll run into strip_float_extensions for integer types as well so
please move the FLOAT_TYPE_P (type) check before the with like

     (if (FLOAT_TYPE_P (type)
          && DECIMAL_FLOAT_TYPE_P (TREE_TPE (@0)) == DECIMAL_FLOAT_TYPE_P 
(type))
      (with { tree arg0 = strip_float_extensions (@1);

+         (if ((newtype == dfloat32_type_node
+               || newtype == dfloat64_type_node
+               || newtype == dfloat128_type_node)
+             && newtype == type)
+           (convert:newtype (op (convert:newtype @1) (convert:newtype 
@2)))

I think you want to elide the outermost convert:newtype here and use

            (op (convert:newtype @1) (convert:newtype @2))

newtype == type check you also want to write types_match_p (newtype, type)

+             (if (TYPE_PRECISION (newtype) < TYPE_PRECISION (itype)
+                  && (flag_unsafe_math_optimizations
+                      || (TYPE_PRECISION (newtype) == TYPE_PRECISION 
(type)
+                          && real_can_shorten_arithmetic (TYPE_MODE 
(itype),
+                                                          TYPE_MODE 
(type))
+                          && !excess_precision_type (newtype))))
+                (convert:newtype (op (convert:newtype @1)
+                                     (convert:newtype @2)))

here the outermost convert looks bogus - you need to build an
expression of type 'type' thus

   (convert:type (op (convert:newtype @1) (convert:newtype @2)))

I think you also want to avoid endless recursion by adding a

             && !types_match_p (itype, newtype)

since in that case you've re-created the original expression.

OK with those changes.

Thanks,
Richard.

> Thanks,
> Tamar
> 
> The 07/02/2019 11:20, Richard Biener wrote:
> > On Tue, 2 Jul 2019, Tamar Christina wrote:
> > 
> > > Hi Richi,
> > > 
> > > The 06/25/2019 10:02, Richard Biener wrote:
> > > > 
> > > > This looks like a literal 1:1 translation plus merging with the
> > > > existing pattern around integers.  You changed
> > > > (op:s@0 (convert@3 @1) (convert?@4 @2)) to
> > > > (op:s@0 (convert1?@3 @1) (convert2?@4 @2)) where this now also
> > > > matches if there are no inner conversions at all - was that a
> > > > desired change or did you merely want to catch when the first
> > > > operand is not a conversion but the second is, possibly only
> > > > for the RDIV_EXPR case?
> > > >
> > > 
> > > Yes, the ? ? is for the RDIV case, I really only want (c a) `op` (c b),
> > > a `op` (c b) and (c a) `op` b.  But didn't find a way to do this.
> > 
> > One way would be to do
> > 
> >  (simplify
> >   (convert (op:sc@0 (convert @1) (convert? @2)))
> > 
> > but that doesn't work for RDIV.  Using :C is tempting but you
> > do not get to know the original operand order which you of
> > course need.  So I guess the way you do it is fine - you
> > could guard all of the code with a few types_match () checks
> > but I'm not sure it is worth the trouble.
> > 
> > Richard.
> > 
> > > The only thing I can think of that gets this is without overmatching is
> > > to either duplicate the code or move this back to a C helper function and
> > > call that from match.pd.  But I was hoping to have it all in match.pd
> > > instead of hiding it away in a C call.
> > > 
> > > Do you have a better way of doing it or a preference to an approach?
> > >  
> > > > +(for op (plus minus mult rdiv)
> > > > + (simplify
> > > > +   (convert (op:s@0 (convert1?@3 @1) (convert2?@4 @2)))
> > > > +   (with { tree arg0 = strip_float_extensions (@1);
> > > > +          tree arg1 = strip_float_extensions (@2);
> > > > +          tree itype = TREE_TYPE (@0);
> > > > 
> > > > you now unconditionally call strip_float_extensions on each operand
> > > > even for the integer case, please sink stuff only used in one
> > > > case arm.  I guess keeping the integer case first via
> > > > 
> > > 
> > > Done, Initially didn't think it would be an issue since I don't use the value it
> > > creates in the integer case. But I re-ordered it.
> > >  
> > > > should work (with the 'with' being in the ifs else position).
> > > > 
> > > > +      (if (code == REAL_TYPE)
> > > > +       /* Ignore the conversion if we don't need to store intermediate
> > > > +          results and neither type is a decimal float.  */
> > > > +         (if (!(flag_float_store
> > > > +              || DECIMAL_FLOAT_TYPE_P (type)
> > > > +              || DECIMAL_FLOAT_TYPE_P (itype))
> > > > +             && types_match (ty1, ty2))
> > > > +           (convert (op (convert:ty1 @1) (convert:ty2 @2)))))
> > > > 
> > > > this looks prone to the same recursion issue you described above.
> > > 
> > > It's to break the recursion when you don't match anything. Indeed don't need it if
> > > I change the match condition above.
> > > Thanks,
> > > Tamar
> > > > 
> > > > 'code' is used exactly once, using SCALAR_FLOAT_TYPE_P (itype)
> > > > in the above test would be clearer.  Also both ifs can be combined.
> > > > The snipped above also doesn't appear in the convert.c code you
> > > > remove and the original one is
> > > > 
> > > >   switch (TREE_CODE (TREE_TYPE (expr)))
> > > >     {
> > > >     case REAL_TYPE:
> > > >       /* Ignore the conversion if we don't need to store intermediate
> > > >          results and neither type is a decimal float.  */
> > > >       return build1_loc (loc,
> > > >                          (flag_float_store
> > > >                           || DECIMAL_FLOAT_TYPE_P (type)
> > > >                           || DECIMAL_FLOAT_TYPE_P (itype))
> > > >                          ? CONVERT_EXPR : NOP_EXPR, type, expr);
> > > > 
> > > > which as far as I can see doesn't do anything besides
> > > > exchanging CONVERT_EXPR for NOP_EXPR which is a noop to the IL.
> > > > So it appears this shouldn't be moved to match.pd at all?
> > > > It's also not a 1:1 move since you are changing 'expr'.
> > > > 
> > > > Thanks,
> > > > Richard.
> > > > 
> > > > > > Thanks,
> > > > > > Tamar
> > > > > > 
> > > > > > Concretely it makes both these cases behave the same
> > > > > > 
> > > > > >   float e = (float)a * (float)b;
> > > > > >   *c = (_Float16)e;
> > > > > > 
> > > > > > and
> > > > > > 
> > > > > >   *c = (_Float16)((float)a * (float)b);
> > > > > > 
> > > > > > Thanks,
> > > > > > Tamar
> > > > > > 
> > > > > > gcc/ChangeLog:
> > > > > > 
> > > > > > 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> > > > > > 
> > > > > > 	* convert.c (convert_to_real_1): Move part of conversion code...
> > > > > > 	* match.pd: ...To here.
> > > > > > 
> > > > > > gcc/testsuite/ChangeLog:
> > > > > > 
> > > > > > 2019-06-25  Tamar Christina  <tamar.christina@arm.com>
> > > > > > 
> > > > > > 	* gcc.dg/type-convert-var.c: New test.
> > > > > > 
> > > > > > --
> > > > > 
> > > > 
> > > > -- 
> > > > Richard Biener <rguenther@suse.de>
> > > > SUSE Linux GmbH, Maxfeldstrasse 5, 90409 Nuernberg, Germany;
> > > > GF: Felix Imendörffer, Mary Higgins, Sri Rasiah; HRB 21284 (AG Nürnberg)
> > > 
> > > 
> > 
> > -- 
> > Richard Biener <rguenther@suse.de>
> > SUSE Linux GmbH, Maxfeldstrasse 5, 90409 Nuernberg, Germany;
> > GF: Felix Imendörffer, Mary Higgins, Sri Rasiah; HRB 21284 (AG Nürnberg)
> 
> 

-- 
Richard Biener <rguenther@suse.de>
SUSE Linux GmbH, Maxfeldstrasse 5, 90409 Nuernberg, Germany;
GF: Felix Imendörffer, Mary Higgins, Sri Rasiah; HRB 21284 (AG Nürnberg)

^ permalink raw reply	[flat|nested] 16+ messages in thread

* [PATCH] Fix up gcc.dg/type-convert-var.c testcase (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch))
  2019-07-02 16:44         ` Tamar Christina
  2019-07-03  9:06           ` Richard Biener
@ 2019-07-30  7:05           ` Jakub Jelinek
  2019-07-30  7:09             ` Rainer Orth
  2019-07-30  7:11           ` Fix up -fexcess-precision handling in LTO " Jakub Jelinek
  2 siblings, 1 reply; 16+ messages in thread
From: Jakub Jelinek @ 2019-07-30  7:05 UTC (permalink / raw)
  To: Richard Biener, Rainer Orth, Mike Stump, Joseph S. Myers,
	Tamar Christina
  Cc: gcc-patches

On Tue, Jul 02, 2019 at 04:43:54PM +0000, Tamar Christina wrote:
> --- /dev/null
> +++ b/gcc/testsuite/gcc.dg/type-convert-var.c
> @@ -0,0 +1,9 @@
> +/* { dg-do compile } */
> +/* { dg-additional-options "-O1 -fdump-tree-optimized" } */
> +void foo (float a, float b, float *c)
> +{
> +  double e = (double)a * (double)b;
> +  *c = (float)e;
> +}
> +
> +/* { dg-final { scan-tree-dump-not {double} "optimized" } } */
> 

This new testcase FAILs e.g. on i686-linux.  The problem is that
with no dg-options, the testcase options default to -ansi, which
implies -fexcess-precision=standard.  On i686-linux, that is conversion to
long double which must (and does) survive until expansion.

Fixed by using -fexcess-precision=fast, tested on x86_64-linux and
i686-linux, ok for trunk?

2019-07-30  Jakub Jelinek  <jakub@redhat.com>

	* gcc.dg/type-convert-var.c: Add -0fexcess-precision=fast to
	dg-additional-options.

--- gcc/testsuite/gcc.dg/type-convert-var.c.jj	2019-07-28 17:29:27.156351325 +0200
+++ gcc/testsuite/gcc.dg/type-convert-var.c	2019-07-30 08:51:33.349558035 +0200
@@ -1,5 +1,5 @@
 /* { dg-do compile } */
-/* { dg-additional-options "-O1 -fdump-tree-optimized" } */
+/* { dg-additional-options "-fexcess-precision=fast -O1 -fdump-tree-optimized" } */
 void foo (float a, float b, float *c)
 {
   double e = (double)a * (double)b;


	Jakub

^ permalink raw reply	[flat|nested] 16+ messages in thread

* Re: [PATCH] Fix up gcc.dg/type-convert-var.c testcase (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch))
  2019-07-30  7:05           ` [PATCH] Fix up gcc.dg/type-convert-var.c testcase (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)) Jakub Jelinek
@ 2019-07-30  7:09             ` Rainer Orth
  2019-07-30  7:13               ` Jakub Jelinek
  0 siblings, 1 reply; 16+ messages in thread
From: Rainer Orth @ 2019-07-30  7:09 UTC (permalink / raw)
  To: Jakub Jelinek
  Cc: Richard Biener, Mike Stump, Joseph S. Myers, Tamar Christina,
	gcc-patches

Hi Jakub,

> On Tue, Jul 02, 2019 at 04:43:54PM +0000, Tamar Christina wrote:
>> --- /dev/null
>> +++ b/gcc/testsuite/gcc.dg/type-convert-var.c
>> @@ -0,0 +1,9 @@
>> +/* { dg-do compile } */
>> +/* { dg-additional-options "-O1 -fdump-tree-optimized" } */
>> +void foo (float a, float b, float *c)
>> +{
>> +  double e = (double)a * (double)b;
>> +  *c = (float)e;
>> +}
>> +
>> +/* { dg-final { scan-tree-dump-not {double} "optimized" } } */
>> 
>
> This new testcase FAILs e.g. on i686-linux.  The problem is that

this is PR middle-end/91282.

> with no dg-options, the testcase options default to -ansi, which
> implies -fexcess-precision=standard.  On i686-linux, that is conversion to
> long double which must (and does) survive until expansion.
>
> Fixed by using -fexcess-precision=fast, tested on x86_64-linux and
> i686-linux, ok for trunk?
>
> 2019-07-30  Jakub Jelinek  <jakub@redhat.com>
>
> 	* gcc.dg/type-convert-var.c: Add -0fexcess-precision=fast to
                                          ^ typo

	Rainer

-- 
-----------------------------------------------------------------------------
Rainer Orth, Center for Biotechnology, Bielefeld University

^ permalink raw reply	[flat|nested] 16+ messages in thread

* Fix up -fexcess-precision handling in LTO (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch))
  2019-07-02 16:44         ` Tamar Christina
  2019-07-03  9:06           ` Richard Biener
  2019-07-30  7:05           ` [PATCH] Fix up gcc.dg/type-convert-var.c testcase (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)) Jakub Jelinek
@ 2019-07-30  7:11           ` Jakub Jelinek
  2019-07-30  7:42             ` Richard Biener
                               ` (2 more replies)
  2 siblings, 3 replies; 16+ messages in thread
From: Jakub Jelinek @ 2019-07-30  7:11 UTC (permalink / raw)
  To: Richard Biener, Joseph S. Myers, Tamar Christina; +Cc: gcc-patches

On Tue, Jul 02, 2019 at 04:43:54PM +0000, Tamar Christina wrote:
> Here's an updated patch with the changes processed from the previous review.
> 
> I've bootstrapped and regtested on aarch64-none-linux-gnu and x86_64-pc-linux-gnu and no issues.

These changes also broke gcc.dg/torture/c99-contract-1.c with -flto
on i686-linux.

The problem is that after moving the folding from convert.c to match.pd,
it is now performed not only during FE folding, but also much later on,
including post-IPA optimizations in lto1.  The C FE arranges
flag_excess_precision_cmdline and flag_excess_precision to be
EXCESS_PRECISION_STANDARD and thus on i686-linux floating point arithmetics
is performed in long double, but the lto1 FE has both set to
EXCESS_PRECISION_FAST and undoes that widening.

There seems to be quite complicated distinction between
flag_excess_precision_cmdline and flag_excess_precision, but it seems
that these days it is unnecessary, flag_excess_precision is only ever set
from flag_excess_precision_cmdline, perhaps in the past targets used to
modify flag_excess_precision, but they don't do that anymore.

Furthermore, some comments claimed that the proper EXCESS_PRECISION_STANDARD
handling requires FE support, but that also doesn't seem to be the case
these days, some FEs even just use EXCESS_PRECISION_STANDARD by default
(go, D).

So, the following patch gets rid of flag_excess_precision and renames
flag_excess_precision_cmdline to flag_excess_precision, plus adds
Optimization flag to that command line option, so that we remember it during
compilation and e.g. during LTO can then have some functions with standard
excess precision and others with fast excess precision.

Bootstrapped/regtested on x86_64-linux and i686-linux, ok for trunk?

2019-07-30  Jakub Jelinek  <jakub@redhat.com>

	PR middle-end/91283
	* common.opt (fexcess-precision=): Add Optimization flag.  Use
	flag_excess_precision variable instead of
	flag_excess_precision_cmdline.
	* flags.h (class target_flag_state): Remove x_flag_excess_precision
	member.
	(flag_excess_precision): Don't define.
	* langhooks.c (lhd_post_options): Set flag_excess_precision instead of
	flag_excess_precision_cmdline.  Remove comment.
	* opts.c (set_fast_math_flags): Use frontend_set_flag_excess_precision
	and x_flag_excess_precision instead of
	frontend_set_flag_excess_precision_cmdline and
	x_flag_excess_precision_cmdline.
	(fast_math_flags_set_p): Use x_flag_excess_precision instead of
	x_flag_excess_precision_cmdline.
	* toplev.c (init_excess_precision): Remove.
	(lang_dependent_init_target): Don't call it.
ada/
	* gcc-interface/misc.c (gnat_post_options): Set flag_excess_precision
	instead of flag_excess_precision_cmdline.
brig/
	* brig-lang.c (brig_langhook_post_options): Set flag_excess_precision
	instead of flag_excess_precision_cmdline.
c-family/
	* c-common.c (c_ts18661_flt_eval_method): Use flag_excess_precision
	instead of flag_excess_precision_cmdline.
	* c-cppbuiltin.c (c_cpp_flt_eval_method_iec_559): Likewise.
	* c-opts.c (c_common_post_options): Likewise.
d/
	* d-lang.cc (d_post_options): Set flag_excess_precision instead of
	flag_excess_precision_cmdline.
fortran/
	* options.c (gfc_post_options): Set flag_excess_precision instead of
	flag_excess_precision_cmdline.  Remove comment.
go/
	* go-lang.c (go_langhook_post_options): Set flag_excess_precision
	instead of flag_excess_precision_cmdline.
lto/
	* lto-lang.c (lto_post_options): Set flag_excess_precision instead of
	flag_excess_precision_cmdline.  Remove comment.

--- gcc/common.opt.jj	2019-07-29 12:56:38.968248060 +0200
+++ gcc/common.opt	2019-07-29 13:01:24.067067583 +0200
@@ -1399,7 +1399,7 @@ Common Report Var(flag_expensive_optimiz
 Perform a number of minor, expensive optimizations.
 
 fexcess-precision=
-Common Joined RejectNegative Enum(excess_precision) Var(flag_excess_precision_cmdline) Init(EXCESS_PRECISION_DEFAULT) SetByCombined
+Common Joined RejectNegative Enum(excess_precision) Var(flag_excess_precision) Init(EXCESS_PRECISION_DEFAULT) Optimization SetByCombined
 -fexcess-precision=[fast|standard]	Specify handling of excess floating-point precision.
 
 Enum
--- gcc/flags.h.jj	2019-07-10 15:52:20.362155642 +0200
+++ gcc/flags.h	2019-07-29 13:02:05.488460207 +0200
@@ -51,9 +51,6 @@ public:
   align_flags x_align_jumps;
   align_flags x_align_labels;
   align_flags x_align_functions;
-
-  /* The excess precision currently in effect.  */
-  enum excess_precision x_flag_excess_precision;
 };
 
 extern class target_flag_state default_target_flag_state;
@@ -68,12 +65,6 @@ extern class target_flag_state *this_tar
 #define align_labels	 (this_target_flag_state->x_align_labels)
 #define align_functions	 (this_target_flag_state->x_align_functions)
 
-/* String representaions of the above options are available in
-   const char *str_align_foo.  NULL if not set.  */
-
-#define flag_excess_precision \
-  (this_target_flag_state->x_flag_excess_precision)
-
 /* Returns TRUE if generated code should match ABI version N or
    greater is in use.  */
 
--- gcc/langhooks.c.jj	2019-01-01 12:37:19.531936001 +0100
+++ gcc/langhooks.c	2019-07-29 13:10:35.053988315 +0200
@@ -95,9 +95,7 @@ lhd_return_null_const_tree (const_tree A
 bool
 lhd_post_options (const char ** ARG_UNUSED (pfilename))
 {
-  /* Excess precision other than "fast" requires front-end
-     support.  */
-  flag_excess_precision_cmdline = EXCESS_PRECISION_FAST;
+  flag_excess_precision = EXCESS_PRECISION_FAST;
   return false;
 }
 
--- gcc/opts.c.jj	2019-07-29 12:56:38.000000000 +0200
+++ gcc/opts.c	2019-07-29 13:02:40.522946490 +0200
@@ -2962,9 +2962,8 @@ set_fast_math_flags (struct gcc_options
     opts->x_flag_errno_math = !set;
   if (set)
     {
-      if (opts->frontend_set_flag_excess_precision_cmdline
-	  == EXCESS_PRECISION_DEFAULT)
-	opts->x_flag_excess_precision_cmdline
+      if (opts->frontend_set_flag_excess_precision == EXCESS_PRECISION_DEFAULT)
+	opts->x_flag_excess_precision
 	  = set ? EXCESS_PRECISION_FAST : EXCESS_PRECISION_DEFAULT;
       if (!opts->frontend_set_flag_signaling_nans)
 	opts->x_flag_signaling_nans = 0;
@@ -2999,8 +2998,7 @@ fast_math_flags_set_p (const struct gcc_
 	  && opts->x_flag_finite_math_only
 	  && !opts->x_flag_signed_zeros
 	  && !opts->x_flag_errno_math
-	  && opts->x_flag_excess_precision_cmdline
-	     == EXCESS_PRECISION_FAST);
+	  && opts->x_flag_excess_precision == EXCESS_PRECISION_FAST);
 }
 
 /* Return true iff flags are set as if -ffast-math but using the flags stored
--- gcc/toplev.c.jj	2019-07-28 17:29:31.246291937 +0200
+++ gcc/toplev.c	2019-07-29 13:08:49.601534597 +0200
@@ -1849,27 +1849,11 @@ backend_init (void)
   init_regs ();
 }
 
-/* Initialize excess precision settings.
-
-   We have no need to modify anything here, just keep track of what the
-   user requested.  We'll figure out any appropriate relaxations
-   later.  */
-
-static void
-init_excess_precision (void)
-{
-  gcc_assert (flag_excess_precision_cmdline != EXCESS_PRECISION_DEFAULT);
-  flag_excess_precision = flag_excess_precision_cmdline;
-}
-
 /* Initialize things that are both lang-dependent and target-dependent.
    This function can be called more than once if target parameters change.  */
 static void
 lang_dependent_init_target (void)
 {
-  /* This determines excess precision settings.  */
-  init_excess_precision ();
-
   /* This creates various _DECL nodes, so needs to be called after the
      front end is initialized.  It also depends on the HAVE_xxx macros
      generated from the target machine description.  */
--- gcc/c-family/c-common.c.jj	2019-07-04 00:18:32.052090626 +0200
+++ gcc/c-family/c-common.c	2019-07-29 13:12:05.762659524 +0200
@@ -8342,7 +8342,7 @@ c_ts18661_flt_eval_method (void)
     = targetm.c.excess_precision (EXCESS_PRECISION_TYPE_IMPLICIT);
 
   enum excess_precision_type flag_type
-    = (flag_excess_precision_cmdline == EXCESS_PRECISION_STANDARD
+    = (flag_excess_precision == EXCESS_PRECISION_STANDARD
        ? EXCESS_PRECISION_TYPE_STANDARD
        : EXCESS_PRECISION_TYPE_FAST);
 
--- gcc/c-family/c-cppbuiltin.c.jj	2019-01-16 09:35:04.563323106 +0100
+++ gcc/c-family/c-cppbuiltin.c	2019-07-29 13:11:06.124532722 +0200
@@ -746,7 +746,7 @@ static bool
 c_cpp_flt_eval_method_iec_559 (void)
 {
   enum excess_precision_type front_end_ept
-    = (flag_excess_precision_cmdline == EXCESS_PRECISION_STANDARD
+    = (flag_excess_precision == EXCESS_PRECISION_STANDARD
        ? EXCESS_PRECISION_TYPE_STANDARD
        : EXCESS_PRECISION_TYPE_FAST);
 
--- gcc/c-family/c-opts.c.jj	2019-07-10 15:52:20.364155611 +0200
+++ gcc/c-family/c-opts.c	2019-07-29 13:11:37.110078371 +0200
@@ -800,14 +800,13 @@ c_common_post_options (const char **pfil
      support.  */
   if (c_dialect_cxx ())
     {
-      if (flag_excess_precision_cmdline == EXCESS_PRECISION_STANDARD)
+      if (flag_excess_precision == EXCESS_PRECISION_STANDARD)
 	sorry ("%<-fexcess-precision=standard%> for C++");
-      flag_excess_precision_cmdline = EXCESS_PRECISION_FAST;
+      flag_excess_precision = EXCESS_PRECISION_FAST;
     }
-  else if (flag_excess_precision_cmdline == EXCESS_PRECISION_DEFAULT)
-    flag_excess_precision_cmdline = (flag_iso
-				     ? EXCESS_PRECISION_STANDARD
-				     : EXCESS_PRECISION_FAST);
+  else if (flag_excess_precision == EXCESS_PRECISION_DEFAULT)
+    flag_excess_precision = (flag_iso ? EXCESS_PRECISION_STANDARD
+				      : EXCESS_PRECISION_FAST);
 
   /* ISO C restricts floating-point expression contraction to within
      source-language expressions (-ffp-contract=on, currently an alias
--- gcc/ada/gcc-interface/misc.c.jj	2019-03-11 22:56:52.475722730 +0100
+++ gcc/ada/gcc-interface/misc.c	2019-07-29 13:08:05.768177333 +0200
@@ -255,9 +255,9 @@ static bool
 gnat_post_options (const char **pfilename ATTRIBUTE_UNUSED)
 {
   /* Excess precision other than "fast" requires front-end support.  */
-  if (flag_excess_precision_cmdline == EXCESS_PRECISION_STANDARD)
+  if (flag_excess_precision == EXCESS_PRECISION_STANDARD)
     sorry ("%<-fexcess-precision=standard%> for Ada");
-  flag_excess_precision_cmdline = EXCESS_PRECISION_FAST;
+  flag_excess_precision = EXCESS_PRECISION_FAST;
 
   /* No psABI change warnings for Ada.  */
   warn_psabi = 0;
--- gcc/brig/brig-lang.c.jj	2019-06-25 16:03:28.221358420 +0200
+++ gcc/brig/brig-lang.c	2019-07-29 13:09:20.341083849 +0200
@@ -166,8 +166,8 @@ brig_langhook_handle_option
 static bool
 brig_langhook_post_options (const char **pfilename ATTRIBUTE_UNUSED)
 {
-  if (flag_excess_precision_cmdline == EXCESS_PRECISION_DEFAULT)
-    flag_excess_precision_cmdline = EXCESS_PRECISION_STANDARD;
+  if (flag_excess_precision == EXCESS_PRECISION_DEFAULT)
+    flag_excess_precision = EXCESS_PRECISION_STANDARD;
 
   /* gccbrig casts pointers around like crazy, TBAA might produce broken
      code if not disabling it by default.  Some PRM conformance tests such
--- gcc/d/d-lang.cc.jj	2019-05-20 11:39:15.581117453 +0200
+++ gcc/d/d-lang.cc	2019-07-29 13:10:05.205425991 +0200
@@ -772,8 +772,8 @@ d_post_options (const char ** fn)
   if (global_options_set.x_flag_max_errors)
     global.errorLimit = flag_max_errors;
 
-  if (flag_excess_precision_cmdline == EXCESS_PRECISION_DEFAULT)
-    flag_excess_precision_cmdline = EXCESS_PRECISION_STANDARD;
+  if (flag_excess_precision == EXCESS_PRECISION_DEFAULT)
+    flag_excess_precision = EXCESS_PRECISION_STANDARD;
 
   if (global.params.useUnitTests)
     global.params.useAssert = true;
--- gcc/fortran/options.c.jj	2019-07-17 09:02:50.211382394 +0200
+++ gcc/fortran/options.c	2019-07-29 13:07:34.492635929 +0200
@@ -262,11 +262,9 @@ gfc_post_options (const char **pfilename
   /* Finalize DEC flags.  */
   post_dec_flags (flag_dec);
 
-  /* Excess precision other than "fast" requires front-end
-     support.  */
-  if (flag_excess_precision_cmdline == EXCESS_PRECISION_STANDARD)
+  if (flag_excess_precision == EXCESS_PRECISION_STANDARD)
     sorry ("%<-fexcess-precision=standard%> for Fortran");
-  flag_excess_precision_cmdline = EXCESS_PRECISION_FAST;
+  flag_excess_precision = EXCESS_PRECISION_FAST;
 
   /* Fortran allows associative math - but we cannot reassociate if
      we want traps or signed zeros. Cf. also flag_protect_parens.  */
--- gcc/go/go-lang.c.jj	2019-05-08 09:18:28.516742244 +0200
+++ gcc/go/go-lang.c	2019-07-29 13:09:41.755769840 +0200
@@ -293,8 +293,8 @@ go_langhook_post_options (const char **p
     go_add_search_path (dir);
   go_search_dirs.release ();
 
-  if (flag_excess_precision_cmdline == EXCESS_PRECISION_DEFAULT)
-    flag_excess_precision_cmdline = EXCESS_PRECISION_STANDARD;
+  if (flag_excess_precision == EXCESS_PRECISION_DEFAULT)
+    flag_excess_precision = EXCESS_PRECISION_STANDARD;
 
   /* Tail call optimizations can confuse uses of runtime.Callers.  */
   if (!global_options_set.x_flag_optimize_sibling_calls)
--- gcc/lto/lto-lang.c.jj	2019-06-25 16:03:29.794334463 +0200
+++ gcc/lto/lto-lang.c	2019-07-29 13:06:52.453252365 +0200
@@ -925,9 +925,8 @@ lto_post_options (const char **pfilename
       break;
     }
 
-  /* Excess precision other than "fast" requires front-end
-     support.  */
-  flag_excess_precision_cmdline = EXCESS_PRECISION_FAST;
+  if (flag_excess_precision == EXCESS_PRECISION_DEFAULT)
+    flag_excess_precision = EXCESS_PRECISION_FAST;
 
   /* When partitioning, we can tear appart STRING_CSTs uses from the same
      TU into multiple partitions.  Without constant merging the constants


	Jakub

^ permalink raw reply	[flat|nested] 16+ messages in thread

* Re: [PATCH] Fix up gcc.dg/type-convert-var.c testcase (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch))
  2019-07-30  7:09             ` Rainer Orth
@ 2019-07-30  7:13               ` Jakub Jelinek
  2019-07-30  7:34                 ` Richard Biener
  0 siblings, 1 reply; 16+ messages in thread
From: Jakub Jelinek @ 2019-07-30  7:13 UTC (permalink / raw)
  To: Rainer Orth
  Cc: Richard Biener, Mike Stump, Joseph S. Myers, Tamar Christina,
	gcc-patches

On Tue, Jul 30, 2019 at 09:05:35AM +0200, Rainer Orth wrote:
> > This new testcase FAILs e.g. on i686-linux.  The problem is that
> 
> this is PR middle-end/91282.

Indeed.

> > with no dg-options, the testcase options default to -ansi, which
> > implies -fexcess-precision=standard.  On i686-linux, that is conversion to
> > long double which must (and does) survive until expansion.
> >
> > Fixed by using -fexcess-precision=fast, tested on x86_64-linux and
> > i686-linux, ok for trunk?
> >
> > 2019-07-30  Jakub Jelinek  <jakub@redhat.com>
> >
> > 	* gcc.dg/type-convert-var.c: Add -0fexcess-precision=fast to
>                                           ^ typo

Oops, fixed:

2019-07-30  Jakub Jelinek  <jakub@redhat.com>

	PR middle-end/91282
	* gcc.dg/type-convert-var.c: Add -fexcess-precision=fast to
	dg-additional-options.

--- gcc/testsuite/gcc.dg/type-convert-var.c.jj	2019-07-28 17:29:27.156351325 +0200
+++ gcc/testsuite/gcc.dg/type-convert-var.c	2019-07-30 08:51:33.349558035 +0200
@@ -1,5 +1,5 @@
 /* { dg-do compile } */
-/* { dg-additional-options "-O1 -fdump-tree-optimized" } */
+/* { dg-additional-options "-fexcess-precision=fast -O1 -fdump-tree-optimized" } */
 void foo (float a, float b, float *c)
 {
   double e = (double)a * (double)b;


	Jakub

^ permalink raw reply	[flat|nested] 16+ messages in thread

* Re: [PATCH] Fix up gcc.dg/type-convert-var.c testcase (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch))
  2019-07-30  7:13               ` Jakub Jelinek
@ 2019-07-30  7:34                 ` Richard Biener
  0 siblings, 0 replies; 16+ messages in thread
From: Richard Biener @ 2019-07-30  7:34 UTC (permalink / raw)
  To: Jakub Jelinek
  Cc: Rainer Orth, Mike Stump, Joseph S. Myers, Tamar Christina, gcc-patches

[-- Attachment #1: Type: text/plain, Size: 1574 bytes --]

On Tue, 30 Jul 2019, Jakub Jelinek wrote:

> On Tue, Jul 30, 2019 at 09:05:35AM +0200, Rainer Orth wrote:
> > > This new testcase FAILs e.g. on i686-linux.  The problem is that
> > 
> > this is PR middle-end/91282.
> 
> Indeed.
> 
> > > with no dg-options, the testcase options default to -ansi, which
> > > implies -fexcess-precision=standard.  On i686-linux, that is conversion to
> > > long double which must (and does) survive until expansion.
> > >
> > > Fixed by using -fexcess-precision=fast, tested on x86_64-linux and
> > > i686-linux, ok for trunk?
> > >
> > > 2019-07-30  Jakub Jelinek  <jakub@redhat.com>
> > >
> > > 	* gcc.dg/type-convert-var.c: Add -0fexcess-precision=fast to
> >                                           ^ typo
> 
> Oops, fixed:

OK.

> 2019-07-30  Jakub Jelinek  <jakub@redhat.com>
> 
> 	PR middle-end/91282
> 	* gcc.dg/type-convert-var.c: Add -fexcess-precision=fast to
> 	dg-additional-options.
> 
> --- gcc/testsuite/gcc.dg/type-convert-var.c.jj	2019-07-28 17:29:27.156351325 +0200
> +++ gcc/testsuite/gcc.dg/type-convert-var.c	2019-07-30 08:51:33.349558035 +0200
> @@ -1,5 +1,5 @@
>  /* { dg-do compile } */
> -/* { dg-additional-options "-O1 -fdump-tree-optimized" } */
> +/* { dg-additional-options "-fexcess-precision=fast -O1 -fdump-tree-optimized" } */
>  void foo (float a, float b, float *c)
>  {
>    double e = (double)a * (double)b;
> 
> 
> 	Jakub
> 

-- 
Richard Biener <rguenther@suse.de>
SUSE Linux GmbH, Maxfeldstrasse 5, 90409 Nuernberg, Germany;
GF: Felix Imendörffer, Mary Higgins, Sri Rasiah; HRB 21284 (AG NÌrnberg)

^ permalink raw reply	[flat|nested] 16+ messages in thread

* Re: Fix up -fexcess-precision handling in LTO (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch))
  2019-07-30  7:11           ` Fix up -fexcess-precision handling in LTO " Jakub Jelinek
@ 2019-07-30  7:42             ` Richard Biener
  2019-07-30  7:46               ` Jakub Jelinek
  2019-08-06 15:02             ` Patch ping (Re: Fix up -fexcess-precision handling in LTO (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch))) Jakub Jelinek
  2019-08-19 22:27             ` Fix up -fexcess-precision handling in LTO (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)) Joseph Myers
  2 siblings, 1 reply; 16+ messages in thread
From: Richard Biener @ 2019-07-30  7:42 UTC (permalink / raw)
  To: Jakub Jelinek; +Cc: Joseph S. Myers, Tamar Christina, gcc-patches

[-- Attachment #1: Type: text/plain, Size: 14609 bytes --]

On Tue, 30 Jul 2019, Jakub Jelinek wrote:

> On Tue, Jul 02, 2019 at 04:43:54PM +0000, Tamar Christina wrote:
> > Here's an updated patch with the changes processed from the previous review.
> > 
> > I've bootstrapped and regtested on aarch64-none-linux-gnu and x86_64-pc-linux-gnu and no issues.
> 
> These changes also broke gcc.dg/torture/c99-contract-1.c with -flto
> on i686-linux.
> 
> The problem is that after moving the folding from convert.c to match.pd,
> it is now performed not only during FE folding, but also much later on,
> including post-IPA optimizations in lto1.  The C FE arranges
> flag_excess_precision_cmdline and flag_excess_precision to be
> EXCESS_PRECISION_STANDARD and thus on i686-linux floating point arithmetics
> is performed in long double, but the lto1 FE has both set to
> EXCESS_PRECISION_FAST and undoes that widening.
> 
> There seems to be quite complicated distinction between
> flag_excess_precision_cmdline and flag_excess_precision, but it seems
> that these days it is unnecessary, flag_excess_precision is only ever set
> from flag_excess_precision_cmdline, perhaps in the past targets used to
> modify flag_excess_precision, but they don't do that anymore.
> 
> Furthermore, some comments claimed that the proper EXCESS_PRECISION_STANDARD
> handling requires FE support, but that also doesn't seem to be the case
> these days, some FEs even just use EXCESS_PRECISION_STANDARD by default
> (go, D).
> 
> So, the following patch gets rid of flag_excess_precision and renames
> flag_excess_precision_cmdline to flag_excess_precision, plus adds
> Optimization flag to that command line option, so that we remember it during
> compilation and e.g. during LTO can then have some functions with standard
> excess precision and others with fast excess precision.
> 
> Bootstrapped/regtested on x86_64-linux and i686-linux, ok for trunk?

Looks OK to me but I'd like Joseph to chime in here.  I think for
FE support it means adding actual _widening_ casts to the effective
compute precision type (thus long double).  But once that's done
the rest should be indeed FE independent (but I doubt D and go get
it correct).

Thanks,
Richard.

> 2019-07-30  Jakub Jelinek  <jakub@redhat.com>
> 
> 	PR middle-end/91283
> 	* common.opt (fexcess-precision=): Add Optimization flag.  Use
> 	flag_excess_precision variable instead of
> 	flag_excess_precision_cmdline.
> 	* flags.h (class target_flag_state): Remove x_flag_excess_precision
> 	member.
> 	(flag_excess_precision): Don't define.
> 	* langhooks.c (lhd_post_options): Set flag_excess_precision instead of
> 	flag_excess_precision_cmdline.  Remove comment.
> 	* opts.c (set_fast_math_flags): Use frontend_set_flag_excess_precision
> 	and x_flag_excess_precision instead of
> 	frontend_set_flag_excess_precision_cmdline and
> 	x_flag_excess_precision_cmdline.
> 	(fast_math_flags_set_p): Use x_flag_excess_precision instead of
> 	x_flag_excess_precision_cmdline.
> 	* toplev.c (init_excess_precision): Remove.
> 	(lang_dependent_init_target): Don't call it.
> ada/
> 	* gcc-interface/misc.c (gnat_post_options): Set flag_excess_precision
> 	instead of flag_excess_precision_cmdline.
> brig/
> 	* brig-lang.c (brig_langhook_post_options): Set flag_excess_precision
> 	instead of flag_excess_precision_cmdline.
> c-family/
> 	* c-common.c (c_ts18661_flt_eval_method): Use flag_excess_precision
> 	instead of flag_excess_precision_cmdline.
> 	* c-cppbuiltin.c (c_cpp_flt_eval_method_iec_559): Likewise.
> 	* c-opts.c (c_common_post_options): Likewise.
> d/
> 	* d-lang.cc (d_post_options): Set flag_excess_precision instead of
> 	flag_excess_precision_cmdline.
> fortran/
> 	* options.c (gfc_post_options): Set flag_excess_precision instead of
> 	flag_excess_precision_cmdline.  Remove comment.
> go/
> 	* go-lang.c (go_langhook_post_options): Set flag_excess_precision
> 	instead of flag_excess_precision_cmdline.
> lto/
> 	* lto-lang.c (lto_post_options): Set flag_excess_precision instead of
> 	flag_excess_precision_cmdline.  Remove comment.
> 
> --- gcc/common.opt.jj	2019-07-29 12:56:38.968248060 +0200
> +++ gcc/common.opt	2019-07-29 13:01:24.067067583 +0200
> @@ -1399,7 +1399,7 @@ Common Report Var(flag_expensive_optimiz
>  Perform a number of minor, expensive optimizations.
>  
>  fexcess-precision=
> -Common Joined RejectNegative Enum(excess_precision) Var(flag_excess_precision_cmdline) Init(EXCESS_PRECISION_DEFAULT) SetByCombined
> +Common Joined RejectNegative Enum(excess_precision) Var(flag_excess_precision) Init(EXCESS_PRECISION_DEFAULT) Optimization SetByCombined
>  -fexcess-precision=[fast|standard]	Specify handling of excess floating-point precision.
>  
>  Enum
> --- gcc/flags.h.jj	2019-07-10 15:52:20.362155642 +0200
> +++ gcc/flags.h	2019-07-29 13:02:05.488460207 +0200
> @@ -51,9 +51,6 @@ public:
>    align_flags x_align_jumps;
>    align_flags x_align_labels;
>    align_flags x_align_functions;
> -
> -  /* The excess precision currently in effect.  */
> -  enum excess_precision x_flag_excess_precision;
>  };
>  
>  extern class target_flag_state default_target_flag_state;
> @@ -68,12 +65,6 @@ extern class target_flag_state *this_tar
>  #define align_labels	 (this_target_flag_state->x_align_labels)
>  #define align_functions	 (this_target_flag_state->x_align_functions)
>  
> -/* String representaions of the above options are available in
> -   const char *str_align_foo.  NULL if not set.  */
> -
> -#define flag_excess_precision \
> -  (this_target_flag_state->x_flag_excess_precision)
> -
>  /* Returns TRUE if generated code should match ABI version N or
>     greater is in use.  */
>  
> --- gcc/langhooks.c.jj	2019-01-01 12:37:19.531936001 +0100
> +++ gcc/langhooks.c	2019-07-29 13:10:35.053988315 +0200
> @@ -95,9 +95,7 @@ lhd_return_null_const_tree (const_tree A
>  bool
>  lhd_post_options (const char ** ARG_UNUSED (pfilename))
>  {
> -  /* Excess precision other than "fast" requires front-end
> -     support.  */
> -  flag_excess_precision_cmdline = EXCESS_PRECISION_FAST;
> +  flag_excess_precision = EXCESS_PRECISION_FAST;
>    return false;
>  }
>  
> --- gcc/opts.c.jj	2019-07-29 12:56:38.000000000 +0200
> +++ gcc/opts.c	2019-07-29 13:02:40.522946490 +0200
> @@ -2962,9 +2962,8 @@ set_fast_math_flags (struct gcc_options
>      opts->x_flag_errno_math = !set;
>    if (set)
>      {
> -      if (opts->frontend_set_flag_excess_precision_cmdline
> -	  == EXCESS_PRECISION_DEFAULT)
> -	opts->x_flag_excess_precision_cmdline
> +      if (opts->frontend_set_flag_excess_precision == EXCESS_PRECISION_DEFAULT)
> +	opts->x_flag_excess_precision
>  	  = set ? EXCESS_PRECISION_FAST : EXCESS_PRECISION_DEFAULT;
>        if (!opts->frontend_set_flag_signaling_nans)
>  	opts->x_flag_signaling_nans = 0;
> @@ -2999,8 +2998,7 @@ fast_math_flags_set_p (const struct gcc_
>  	  && opts->x_flag_finite_math_only
>  	  && !opts->x_flag_signed_zeros
>  	  && !opts->x_flag_errno_math
> -	  && opts->x_flag_excess_precision_cmdline
> -	     == EXCESS_PRECISION_FAST);
> +	  && opts->x_flag_excess_precision == EXCESS_PRECISION_FAST);
>  }
>  
>  /* Return true iff flags are set as if -ffast-math but using the flags stored
> --- gcc/toplev.c.jj	2019-07-28 17:29:31.246291937 +0200
> +++ gcc/toplev.c	2019-07-29 13:08:49.601534597 +0200
> @@ -1849,27 +1849,11 @@ backend_init (void)
>    init_regs ();
>  }
>  
> -/* Initialize excess precision settings.
> -
> -   We have no need to modify anything here, just keep track of what the
> -   user requested.  We'll figure out any appropriate relaxations
> -   later.  */
> -
> -static void
> -init_excess_precision (void)
> -{
> -  gcc_assert (flag_excess_precision_cmdline != EXCESS_PRECISION_DEFAULT);
> -  flag_excess_precision = flag_excess_precision_cmdline;
> -}
> -
>  /* Initialize things that are both lang-dependent and target-dependent.
>     This function can be called more than once if target parameters change.  */
>  static void
>  lang_dependent_init_target (void)
>  {
> -  /* This determines excess precision settings.  */
> -  init_excess_precision ();
> -
>    /* This creates various _DECL nodes, so needs to be called after the
>       front end is initialized.  It also depends on the HAVE_xxx macros
>       generated from the target machine description.  */
> --- gcc/c-family/c-common.c.jj	2019-07-04 00:18:32.052090626 +0200
> +++ gcc/c-family/c-common.c	2019-07-29 13:12:05.762659524 +0200
> @@ -8342,7 +8342,7 @@ c_ts18661_flt_eval_method (void)
>      = targetm.c.excess_precision (EXCESS_PRECISION_TYPE_IMPLICIT);
>  
>    enum excess_precision_type flag_type
> -    = (flag_excess_precision_cmdline == EXCESS_PRECISION_STANDARD
> +    = (flag_excess_precision == EXCESS_PRECISION_STANDARD
>         ? EXCESS_PRECISION_TYPE_STANDARD
>         : EXCESS_PRECISION_TYPE_FAST);
>  
> --- gcc/c-family/c-cppbuiltin.c.jj	2019-01-16 09:35:04.563323106 +0100
> +++ gcc/c-family/c-cppbuiltin.c	2019-07-29 13:11:06.124532722 +0200
> @@ -746,7 +746,7 @@ static bool
>  c_cpp_flt_eval_method_iec_559 (void)
>  {
>    enum excess_precision_type front_end_ept
> -    = (flag_excess_precision_cmdline == EXCESS_PRECISION_STANDARD
> +    = (flag_excess_precision == EXCESS_PRECISION_STANDARD
>         ? EXCESS_PRECISION_TYPE_STANDARD
>         : EXCESS_PRECISION_TYPE_FAST);
>  
> --- gcc/c-family/c-opts.c.jj	2019-07-10 15:52:20.364155611 +0200
> +++ gcc/c-family/c-opts.c	2019-07-29 13:11:37.110078371 +0200
> @@ -800,14 +800,13 @@ c_common_post_options (const char **pfil
>       support.  */
>    if (c_dialect_cxx ())
>      {
> -      if (flag_excess_precision_cmdline == EXCESS_PRECISION_STANDARD)
> +      if (flag_excess_precision == EXCESS_PRECISION_STANDARD)
>  	sorry ("%<-fexcess-precision=standard%> for C++");
> -      flag_excess_precision_cmdline = EXCESS_PRECISION_FAST;
> +      flag_excess_precision = EXCESS_PRECISION_FAST;
>      }
> -  else if (flag_excess_precision_cmdline == EXCESS_PRECISION_DEFAULT)
> -    flag_excess_precision_cmdline = (flag_iso
> -				     ? EXCESS_PRECISION_STANDARD
> -				     : EXCESS_PRECISION_FAST);
> +  else if (flag_excess_precision == EXCESS_PRECISION_DEFAULT)
> +    flag_excess_precision = (flag_iso ? EXCESS_PRECISION_STANDARD
> +				      : EXCESS_PRECISION_FAST);
>  
>    /* ISO C restricts floating-point expression contraction to within
>       source-language expressions (-ffp-contract=on, currently an alias
> --- gcc/ada/gcc-interface/misc.c.jj	2019-03-11 22:56:52.475722730 +0100
> +++ gcc/ada/gcc-interface/misc.c	2019-07-29 13:08:05.768177333 +0200
> @@ -255,9 +255,9 @@ static bool
>  gnat_post_options (const char **pfilename ATTRIBUTE_UNUSED)
>  {
>    /* Excess precision other than "fast" requires front-end support.  */
> -  if (flag_excess_precision_cmdline == EXCESS_PRECISION_STANDARD)
> +  if (flag_excess_precision == EXCESS_PRECISION_STANDARD)
>      sorry ("%<-fexcess-precision=standard%> for Ada");
> -  flag_excess_precision_cmdline = EXCESS_PRECISION_FAST;
> +  flag_excess_precision = EXCESS_PRECISION_FAST;
>  
>    /* No psABI change warnings for Ada.  */
>    warn_psabi = 0;
> --- gcc/brig/brig-lang.c.jj	2019-06-25 16:03:28.221358420 +0200
> +++ gcc/brig/brig-lang.c	2019-07-29 13:09:20.341083849 +0200
> @@ -166,8 +166,8 @@ brig_langhook_handle_option
>  static bool
>  brig_langhook_post_options (const char **pfilename ATTRIBUTE_UNUSED)
>  {
> -  if (flag_excess_precision_cmdline == EXCESS_PRECISION_DEFAULT)
> -    flag_excess_precision_cmdline = EXCESS_PRECISION_STANDARD;
> +  if (flag_excess_precision == EXCESS_PRECISION_DEFAULT)
> +    flag_excess_precision = EXCESS_PRECISION_STANDARD;
>  
>    /* gccbrig casts pointers around like crazy, TBAA might produce broken
>       code if not disabling it by default.  Some PRM conformance tests such
> --- gcc/d/d-lang.cc.jj	2019-05-20 11:39:15.581117453 +0200
> +++ gcc/d/d-lang.cc	2019-07-29 13:10:05.205425991 +0200
> @@ -772,8 +772,8 @@ d_post_options (const char ** fn)
>    if (global_options_set.x_flag_max_errors)
>      global.errorLimit = flag_max_errors;
>  
> -  if (flag_excess_precision_cmdline == EXCESS_PRECISION_DEFAULT)
> -    flag_excess_precision_cmdline = EXCESS_PRECISION_STANDARD;
> +  if (flag_excess_precision == EXCESS_PRECISION_DEFAULT)
> +    flag_excess_precision = EXCESS_PRECISION_STANDARD;
>  
>    if (global.params.useUnitTests)
>      global.params.useAssert = true;
> --- gcc/fortran/options.c.jj	2019-07-17 09:02:50.211382394 +0200
> +++ gcc/fortran/options.c	2019-07-29 13:07:34.492635929 +0200
> @@ -262,11 +262,9 @@ gfc_post_options (const char **pfilename
>    /* Finalize DEC flags.  */
>    post_dec_flags (flag_dec);
>  
> -  /* Excess precision other than "fast" requires front-end
> -     support.  */
> -  if (flag_excess_precision_cmdline == EXCESS_PRECISION_STANDARD)
> +  if (flag_excess_precision == EXCESS_PRECISION_STANDARD)
>      sorry ("%<-fexcess-precision=standard%> for Fortran");
> -  flag_excess_precision_cmdline = EXCESS_PRECISION_FAST;
> +  flag_excess_precision = EXCESS_PRECISION_FAST;
>  
>    /* Fortran allows associative math - but we cannot reassociate if
>       we want traps or signed zeros. Cf. also flag_protect_parens.  */
> --- gcc/go/go-lang.c.jj	2019-05-08 09:18:28.516742244 +0200
> +++ gcc/go/go-lang.c	2019-07-29 13:09:41.755769840 +0200
> @@ -293,8 +293,8 @@ go_langhook_post_options (const char **p
>      go_add_search_path (dir);
>    go_search_dirs.release ();
>  
> -  if (flag_excess_precision_cmdline == EXCESS_PRECISION_DEFAULT)
> -    flag_excess_precision_cmdline = EXCESS_PRECISION_STANDARD;
> +  if (flag_excess_precision == EXCESS_PRECISION_DEFAULT)
> +    flag_excess_precision = EXCESS_PRECISION_STANDARD;
>  
>    /* Tail call optimizations can confuse uses of runtime.Callers.  */
>    if (!global_options_set.x_flag_optimize_sibling_calls)
> --- gcc/lto/lto-lang.c.jj	2019-06-25 16:03:29.794334463 +0200
> +++ gcc/lto/lto-lang.c	2019-07-29 13:06:52.453252365 +0200
> @@ -925,9 +925,8 @@ lto_post_options (const char **pfilename
>        break;
>      }
>  
> -  /* Excess precision other than "fast" requires front-end
> -     support.  */
> -  flag_excess_precision_cmdline = EXCESS_PRECISION_FAST;
> +  if (flag_excess_precision == EXCESS_PRECISION_DEFAULT)
> +    flag_excess_precision = EXCESS_PRECISION_FAST;
>  
>    /* When partitioning, we can tear appart STRING_CSTs uses from the same
>       TU into multiple partitions.  Without constant merging the constants
> 
> 
> 	Jakub
> 

-- 
Richard Biener <rguenther@suse.de>
SUSE Linux GmbH, Maxfeldstrasse 5, 90409 Nuernberg, Germany;
GF: Felix Imendörffer, Mary Higgins, Sri Rasiah; HRB 21284 (AG NÌrnberg)

^ permalink raw reply	[flat|nested] 16+ messages in thread

* Re: Fix up -fexcess-precision handling in LTO (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch))
  2019-07-30  7:42             ` Richard Biener
@ 2019-07-30  7:46               ` Jakub Jelinek
  0 siblings, 0 replies; 16+ messages in thread
From: Jakub Jelinek @ 2019-07-30  7:46 UTC (permalink / raw)
  To: Richard Biener; +Cc: Joseph S. Myers, Tamar Christina, gcc-patches

On Tue, Jul 30, 2019 at 09:35:04AM +0200, Richard Biener wrote:
> Looks OK to me but I'd like Joseph to chime in here.  I think for

Ok, will wait for Joseph.

> FE support it means adding actual _widening_ casts to the effective
> compute precision type (thus long double).  But once that's done
> the rest should be indeed FE independent (but I doubt D and go get
> it correct).

The FE must add casts to whatever excess_precision_type returns (if
non-NULL).  Seems all of C, D and Go do something:
c/c-typeck.c:	      && (eptype = excess_precision_type (type2)) != NULL_TREE)
c/c-typeck.c:		   && (eptype = excess_precision_type (type1)) != NULL_TREE)
c/c-typeck.c:	   && (eptype = excess_precision_type (type0)) != NULL_TREE)
c/c-typeck.c:	   && (eptype = excess_precision_type (type1)) != NULL_TREE)
c-family/c-lex.c:  const_type = excess_precision_type (type);
d/expr.cc:	tree eptype = excess_precision_type (type);
d/expr.cc:    tree eptype = excess_precision_type (type);
go/go-gcc.cc:        tree computed_type = excess_precision_type(type_tree);
go/go-gcc.cc:  tree computed_type = excess_precision_type(type_tree);
go/go-gcc.cc:      excess_type = excess_precision_type(TREE_TYPE(args[0]));
match.pd:			   && !excess_precision_type (newtype)))
and in the middle-end (since Tamar's changes) we only care if it returns
NULL or not.

	Jakub

^ permalink raw reply	[flat|nested] 16+ messages in thread

* Patch ping (Re: Fix up -fexcess-precision handling in LTO (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)))
  2019-07-30  7:11           ` Fix up -fexcess-precision handling in LTO " Jakub Jelinek
  2019-07-30  7:42             ` Richard Biener
@ 2019-08-06 15:02             ` Jakub Jelinek
  2019-08-19 22:27             ` Fix up -fexcess-precision handling in LTO (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)) Joseph Myers
  2 siblings, 0 replies; 16+ messages in thread
From: Jakub Jelinek @ 2019-08-06 15:02 UTC (permalink / raw)
  To: Joseph S. Myers; +Cc: gcc-patches

Hi!

I'd like to ping the https://gcc.gnu.org/ml/gcc-patches/2019-07/msg01750.html
patch.

Thanks.

On Tue, Jul 30, 2019 at 09:09:11AM +0200, Jakub Jelinek wrote:
> Bootstrapped/regtested on x86_64-linux and i686-linux, ok for trunk?
> 
> 2019-07-30  Jakub Jelinek  <jakub@redhat.com>
> 
> 	PR middle-end/91283
> 	* common.opt (fexcess-precision=): Add Optimization flag.  Use
> 	flag_excess_precision variable instead of
> 	flag_excess_precision_cmdline.
> 	* flags.h (class target_flag_state): Remove x_flag_excess_precision
> 	member.
> 	(flag_excess_precision): Don't define.
> 	* langhooks.c (lhd_post_options): Set flag_excess_precision instead of
> 	flag_excess_precision_cmdline.  Remove comment.
> 	* opts.c (set_fast_math_flags): Use frontend_set_flag_excess_precision
> 	and x_flag_excess_precision instead of
> 	frontend_set_flag_excess_precision_cmdline and
> 	x_flag_excess_precision_cmdline.
> 	(fast_math_flags_set_p): Use x_flag_excess_precision instead of
> 	x_flag_excess_precision_cmdline.
> 	* toplev.c (init_excess_precision): Remove.
> 	(lang_dependent_init_target): Don't call it.
> ada/
> 	* gcc-interface/misc.c (gnat_post_options): Set flag_excess_precision
> 	instead of flag_excess_precision_cmdline.
> brig/
> 	* brig-lang.c (brig_langhook_post_options): Set flag_excess_precision
> 	instead of flag_excess_precision_cmdline.
> c-family/
> 	* c-common.c (c_ts18661_flt_eval_method): Use flag_excess_precision
> 	instead of flag_excess_precision_cmdline.
> 	* c-cppbuiltin.c (c_cpp_flt_eval_method_iec_559): Likewise.
> 	* c-opts.c (c_common_post_options): Likewise.
> d/
> 	* d-lang.cc (d_post_options): Set flag_excess_precision instead of
> 	flag_excess_precision_cmdline.
> fortran/
> 	* options.c (gfc_post_options): Set flag_excess_precision instead of
> 	flag_excess_precision_cmdline.  Remove comment.
> go/
> 	* go-lang.c (go_langhook_post_options): Set flag_excess_precision
> 	instead of flag_excess_precision_cmdline.
> lto/
> 	* lto-lang.c (lto_post_options): Set flag_excess_precision instead of
> 	flag_excess_precision_cmdline.  Remove comment.

	Jakub

^ permalink raw reply	[flat|nested] 16+ messages in thread

* Re: Fix up -fexcess-precision handling in LTO (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch))
  2019-07-30  7:11           ` Fix up -fexcess-precision handling in LTO " Jakub Jelinek
  2019-07-30  7:42             ` Richard Biener
  2019-08-06 15:02             ` Patch ping (Re: Fix up -fexcess-precision handling in LTO (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch))) Jakub Jelinek
@ 2019-08-19 22:27             ` Joseph Myers
  2 siblings, 0 replies; 16+ messages in thread
From: Joseph Myers @ 2019-08-19 22:27 UTC (permalink / raw)
  To: Jakub Jelinek; +Cc: Richard Biener, Tamar Christina, gcc-patches

On Tue, 30 Jul 2019, Jakub Jelinek wrote:

> Furthermore, some comments claimed that the proper EXCESS_PRECISION_STANDARD
> handling requires FE support, but that also doesn't seem to be the case
> these days, some FEs even just use EXCESS_PRECISION_STANDARD by default
> (go, D).
> 
> So, the following patch gets rid of flag_excess_precision and renames
> flag_excess_precision_cmdline to flag_excess_precision, plus adds
> Optimization flag to that command line option, so that we remember it during
> compilation and e.g. during LTO can then have some functions with standard
> excess precision and others with fast excess precision.
> 
> Bootstrapped/regtested on x86_64-linux and i686-linux, ok for trunk?

OK minus the removal of the comment in lhd_post_options.  Proper handling 
requires front-end support (to generate GIMPLE with the operations in the 
intended type).  Back-end support (to avoid having insn patterns claiming 
to operate on the types the processor in fact does not have direct support 
for arithmetic on), although not strictly required, is a very good idea, 
to make it more obvious if something is wrongly generating arithmetic on 
inappropriate types.  And then you need the middle-end support (to avoid 
transformations introducing operations in the types that aren't meant to 
have direct operations, even if in fact the semantics are equivalent) as 
well.

-- 
Joseph S. Myers
joseph@codesourcery.com

^ permalink raw reply	[flat|nested] 16+ messages in thread

end of thread, other threads:[~2019-08-19 22:04 UTC | newest]

Thread overview: 16+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2019-06-25  8:31 [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch) Tamar Christina
2019-06-25  8:33 ` Tamar Christina
2019-06-25  9:02   ` Richard Biener
2019-07-02  9:41     ` Tamar Christina
2019-07-02 10:20       ` Richard Biener
2019-07-02 16:44         ` Tamar Christina
2019-07-03  9:06           ` Richard Biener
2019-07-30  7:05           ` [PATCH] Fix up gcc.dg/type-convert-var.c testcase (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)) Jakub Jelinek
2019-07-30  7:09             ` Rainer Orth
2019-07-30  7:13               ` Jakub Jelinek
2019-07-30  7:34                 ` Richard Biener
2019-07-30  7:11           ` Fix up -fexcess-precision handling in LTO " Jakub Jelinek
2019-07-30  7:42             ` Richard Biener
2019-07-30  7:46               ` Jakub Jelinek
2019-08-06 15:02             ` Patch ping (Re: Fix up -fexcess-precision handling in LTO (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch))) Jakub Jelinek
2019-08-19 22:27             ` Fix up -fexcess-precision handling in LTO (was Re: [GCC][middle-end] Add rules to strip away unneeded type casts in expressions (2nd patch)) Joseph Myers

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).