+2009-12-15 Aldy Hernandez <aldyh@redhat.com>
+
+ PR graphite/42185
+ * graphite-sese-to-poly.c (is_reduction_operation_p): Assert that
+ we are a GIMPLE_ASSIGN. Do not calculate rhs code twice.
+ (follow_ssa_with_commutative_ops): Return NULL on non assignment.
+
2009-12-15 Eric Botcazou <ebotcazou@adacore.com>
* config/rs6000/rs6000.md (probe_stack): Use an enclosing SET.
static inline bool
is_reduction_operation_p (gimple stmt)
{
+ enum tree_code code;
+
+ gcc_assert (is_gimple_assign (stmt));
+ code = gimple_assign_rhs_code (stmt);
+
return flag_associative_math
- && commutative_tree_code (gimple_assign_rhs_code (stmt))
- && associative_tree_code (gimple_assign_rhs_code (stmt));
+ && commutative_tree_code (code)
+ && associative_tree_code (code);
}
/* Returns true when PHI contains an argument ARG. */
return NULL;
}
+ if (!is_gimple_assign (stmt))
+ return NULL;
+
if (gimple_num_ops (stmt) == 2)
return follow_ssa_with_commutative_ops (gimple_assign_rhs1 (stmt), lhs);
--- /dev/null
+! { dg-compile }
+! { dg-options "-fgraphite -O -ffast-math" }
+
+MODULE powell
+ INTEGER, PARAMETER :: dp=8
+CONTAINS
+ SUBROUTINE trsapp (n,npt,xopt,xpt,gq,hq,pq,delta,step,d,g,hd,hs,crvmin)
+ REAL(dp), DIMENSION(*), INTENT(INOUT) :: step, d, g, hd, hs
+ LOGICAL :: jump1, jump2
+ REAL(dp) :: alpha, angle, angtest, bstep, cf, cth, dd, delsq, dg, dhd, &
+ reduc, sg, sgk, shs, ss, sth, temp, tempa, tempb
+ DO i=1,n
+ dd=dd+d(i)**2
+ END DO
+ mainloop : DO
+ IF ( .NOT. jump2 ) THEN
+ IF ( .NOT. jump1 ) THEN
+ bstep=temp/(ds+SQRT(ds*ds+dd*temp))
+ IF (alpha < bstep) THEN
+ IF (ss < delsq) CYCLE mainloop
+ END IF
+ IF (gg <= 1.0e-4_dp*ggbeg) EXIT mainloop
+ END IF
+ END IF
+ END DO mainloop
+ END SUBROUTINE trsapp
+END MODULE powell