+2015-12-02 Aditya Kumar <aditya.k7@samsung.com>
+ Sebastian Pop <s.pop@samsung.com>
+
+ PR tree-optimization/68550
+ * graphite-isl-ast-to-gimple.c (copy_loop_phi_nodes): Add dump.
+ (copy_bb_and_scalar_dependences): Do not code generate loop peeled
+ statements.
+
2015-12-02 Ulrich Weigand <Ulrich.Weigand@de.ibm.com>
* configure.ac: Check assembler support for R_PPC64_ENTRY relocation.
codegen_error = !copy_loop_phi_args (phi, ibp_old_bb, new_phi,
ibp_new_bb, true);
update_stmt (new_phi);
+
+ if (dump_file)
+ {
+ fprintf (dump_file, "[codegen] creating loop-phi node: ");
+ print_gimple_stmt (dump_file, new_phi, 0, 0);
+ }
}
return true;
return NULL;
}
+ /* In case ISL did some loop peeling, like this:
+
+ S_8(0);
+ for (int c1 = 1; c1 <= 5; c1 += 1) {
+ S_8(c1);
+ }
+ S_8(6);
+
+ there should be no loop-phi nodes in S_8(0).
+
+ FIXME: We need to reason about dynamic instances of S_8, i.e., the
+ values of all scalar variables: for the moment we instantiate only
+ SCEV analyzable expressions on the iteration domain, and we need to
+ extend that to reductions that cannot be analyzed by SCEV. */
+ if (!bb_in_sese_p (phi_bb, region->if_region->true_region->region))
+ {
+ codegen_error = true;
+ return NULL;
+ }
+
if (dump_file)
fprintf (dump_file, "[codegen] bb_%d contains loop phi nodes.\n",
bb->index);
+2015-12-02 Aditya Kumar <aditya.k7@samsung.com>
+ Sebastian Pop <s.pop@samsung.com>
+
+ PR tree-optimization/68550
+ * gfortran.dg/graphite/pr68550-1.f90: New.
+ * gfortran.dg/graphite/pr68550-2.f90: New.
+
2015-12-02 Marek Polacek <polacek@redhat.com>
PR c/68513
--- /dev/null
+! { dg-do compile }
+! { dg-options "-floop-nest-optimize -O2" }
+
+SUBROUTINE integrate_core_1(grid,coef_xyz,pol_x,pol_y,&
+ pol_z,map,sphere_bounds,cmax,gridbounds)
+ INTEGER, PARAMETER :: dp=8
+ INTEGER, INTENT(IN) :: sphere_bounds(*), cmax, &
+ map(-cmax:cmax,1:3), &
+ gridbounds(2,3)
+ REAL(dp), INTENT(IN) :: grid(gridbounds(1,1):gridbounds(2,1), &
+ gridbounds(1,2):gridbounds(2,2),&
+ gridbounds(1,3):gridbounds(2,3))
+ INTEGER, PARAMETER :: lp = 1
+ REAL(dp), INTENT(IN) :: pol_x(0:lp,-cmax:cmax), &
+ pol_y(1:2,0:lp,-cmax:0), &
+ pol_z(1:2,0:lp,-cmax:0)
+ REAL(dp), INTENT(OUT) :: coef_xyz(((lp+1)*(lp+2)*(lp+3))/6)
+ INTEGER :: i, ig, igmax, igmin, j, j2, &
+ jg, jg2, jgmin, k, k2, kg, &
+ kg2, kgmin, lxp, sci
+ REAL(dp) :: coef_x(4,0:lp), &
+ coef_xy(2,((lp+1)*(lp+2))/2), &
+ s(4)
+ DO kg=kgmin,0
+ DO jg=jgmin,0
+ coef_x=0.0_dp
+ DO ig=igmin,igmax
+ DO lxp=0,lp
+ coef_x(:,lxp)=coef_x(:,lxp)+s(:)*pol_x(lxp,ig)
+ ENDDO
+ END DO
+ coef_xy(:,3)=coef_xy(:,3)+coef_x(3:4,0)*pol_y(2,1,jg)
+ END DO
+ coef_xyz(3)=coef_xyz(3)+coef_xy(1,3)*pol_z(1,0,kg)
+ END DO
+ END SUBROUTINE integrate_core_1
--- /dev/null
+! { dg-do compile }
+! { dg-options "-floop-nest-optimize -fcheck=bounds -O1" }
+
+SUBROUTINE PD2VAL(RES,NDERIV,TG1,TG2,C0)
+ INTEGER, PARAMETER :: dp=8
+ REAL(KIND=dp), INTENT(OUT) :: res(*)
+ REAL(KIND=dp), INTENT(IN) :: TG1, TG2, C0(105,*)
+ REAL(KIND=dp) :: T1(0:13), T2(0:13)
+ DO K=1,NDERIV+1
+ RES(K)=RES(K)+DOT_PRODUCT(T1(0:7),C0(70:77,K))*T2(6)
+ RES(K)=RES(K)+DOT_PRODUCT(T1(0:4),C0(91:95,K))*T2(9)
+ RES(K)=RES(K)+DOT_PRODUCT(T1(0:3),C0(96:99,K))*T2(10)
+ ENDDO
+END SUBROUTINE PD2VAL