From 3f82421f9c460408f21dc8a68079957aada10c0e Mon Sep 17 00:00:00 2001
From: Pat Haugen <pthaugen@us.ibm.com>
Date: Fri, 11 Feb 2011 20:52:55 +0000
Subject: [PATCH] re PR rtl-optimization/47614 (cpu2000 benchmark 301.apsi
 fails with revision 169782)

	PR rtl-optimization/47614
	* rtl.h (check_for_inc_dec): Declare.
	* dse.c (check_for_inc_dec): Externalize...
	* postreload.c (reload_cse_simplify): ...use it before deleting stmt.
	(reload_cse_simplify_operands): Don't simplify opnds with side effects.

	* testsuite/gfortran.dg/pr47614.f: New.

From-SVN: r170059
---
 gcc/ChangeLog                       |  8 +++++++
 gcc/dse.c                           |  2 +-
 gcc/postreload.c                    |  4 ++++
 gcc/rtl.h                           |  3 +++
 gcc/testsuite/ChangeLog             |  5 ++++
 gcc/testsuite/gfortran.dg/pr47614.f | 37 +++++++++++++++++++++++++++++
 6 files changed, 58 insertions(+), 1 deletion(-)
 create mode 100644 gcc/testsuite/gfortran.dg/pr47614.f

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 0b859c56d6a2..92f3ddb9dfd1 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,11 @@
+2011-02-11  Pat Haugen <pthaugen@us.ibm.com>
+
+	PR rtl-optimization/47614
+	* rtl.h (check_for_inc_dec): Declare.
+	* dse.c (check_for_inc_dec): Externalize...
+	* postreload.c (reload_cse_simplify): ...use it before deleting stmt.
+	(reload_cse_simplify_operands): Don't simplify opnds with side effects.
+
 2011-02-11  Joseph Myers  <joseph@codesourcery.com>
 
 	PR driver/47678
diff --git a/gcc/dse.c b/gcc/dse.c
index 11639816bca7..8e9b6454e390 100644
--- a/gcc/dse.c
+++ b/gcc/dse.c
@@ -830,7 +830,7 @@ emit_inc_dec_insn_before (rtx mem ATTRIBUTE_UNUSED,
 /* Before we delete INSN, make sure that the auto inc/dec, if it is
    there, is split into a separate insn.  */
 
-static void
+void
 check_for_inc_dec (rtx insn)
 {
   rtx note = find_reg_note (insn, REG_INC, NULL_RTX);
diff --git a/gcc/postreload.c b/gcc/postreload.c
index 5cd26a79ddf1..a42341023014 100644
--- a/gcc/postreload.c
+++ b/gcc/postreload.c
@@ -112,6 +112,7 @@ reload_cse_simplify (rtx insn, rtx testreg)
 	  if (REG_P (value)
 	      && ! REG_FUNCTION_VALUE_P (value))
 	    value = 0;
+	  check_for_inc_dec (insn);
 	  delete_insn_and_edges (insn);
 	  return;
 	}
@@ -163,6 +164,7 @@ reload_cse_simplify (rtx insn, rtx testreg)
 
       if (i < 0)
 	{
+	  check_for_inc_dec (insn);
 	  delete_insn_and_edges (insn);
 	  /* We're done with this insn.  */
 	  return;
@@ -476,6 +478,8 @@ reload_cse_simplify_operands (rtx insn, rtx testreg)
 	    continue;
 	}
 #endif /* LOAD_EXTEND_OP */
+      if (side_effects_p (op))
+	continue;
       v = cselib_lookup (op, recog_data.operand_mode[i], 0, VOIDmode);
       if (! v)
 	continue;
diff --git a/gcc/rtl.h b/gcc/rtl.h
index 268613b6f1ce..e5c6e3830205 100644
--- a/gcc/rtl.h
+++ b/gcc/rtl.h
@@ -2302,6 +2302,9 @@ extern int cse_main (rtx, int);
 extern int exp_equiv_p (const_rtx, const_rtx, int, bool);
 extern unsigned hash_rtx (const_rtx x, enum machine_mode, int *, int *, bool);
 
+/* In dse.c */
+extern void check_for_inc_dec (rtx insn);
+
 /* In jump.c */
 extern int comparison_dominates_p (enum rtx_code, enum rtx_code);
 extern int condjump_p (const_rtx);
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index b9406bab86db..d680a16d3097 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2011-02-11  Pat Haugen <pthaugen@us.ibm.com>
+
+	PR rtl-optimization/47614
+	* gfortran.dg/pr47614.f: New.
+
 2011-02-11  Joseph Myers  <joseph@codesourcery.com>
 
 	PR driver/47678
diff --git a/gcc/testsuite/gfortran.dg/pr47614.f b/gcc/testsuite/gfortran.dg/pr47614.f
new file mode 100644
index 000000000000..52f14c0c17b0
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr47614.f
@@ -0,0 +1,37 @@
+! { dg-do run { target { powerpc*-*-* } } }
+! { dg-skip-if "" { powerpc*-*-darwin* } { "*" } { "" } }
+! { dg-options "-O3 -funroll-loops -ffast-math -mcpu=power4" }
+
+
+      SUBROUTINE SFCPAR(ZET,NZ,ZMH,TSL,TMES)
+      IMPLICIT REAL*8 (A-H, O-Z)
+      REAL*8 ZET(*)
+
+      ZS=MAX(TSL*ZMH,ZET(2))
+
+      DO 10 K=2,NZ
+         KLEV=K-1
+         IF(ZS.LE.ZET(K)) GO TO 20
+ 10   CONTINUE
+
+ 20   CONTINUE
+      TMES=ZET(KLEV+1)
+      
+      RETURN
+      END
+
+      program pr47614
+	real*8 ar1(10),d1,d2,d3
+	integer i
+
+	d1 = 2.0
+	d2 = 3.0
+	d3 = 3.0
+	do 50 i=1,10
+	  ar1(i) = d1
+	  d1 = d1 + 2.0
+ 50	continue
+
+	call sfcpar(ar1,10,d2,d3,d1)
+	if (d1.ne.10.0) call abort()
+      end
-- 
GitLab