+2018-04-12 Thomas Koenig <tkoenig@gcc.gnu.org>
+
+ PR fortran/83064
+ PR testsuite/85346
+ * trans-stmt.c (gfc_trans_forall_loop): Use annot_expr_ivdep_kind
+ for annotation and remove dependence on -ftree-parallelize-loops.
+
2018-04-10 Jakub Jelinek <jakub@redhat.com>
PR fortran/85313
cond = fold_build2_loc (input_location, LE_EXPR, logical_type_node,
count, build_int_cst (TREE_TYPE (count), 0));
- /* PR 83064 means that we cannot use the annotation if the
- autoparallelizer is active. */
- if (forall_tmp->do_concurrent && ! flag_tree_parallelize_loops)
+ /* PR 83064 means that we cannot use annot_expr_parallel_kind until
+ the autoparallelizer can hande this. */
+ if (forall_tmp->do_concurrent)
cond = build3 (ANNOTATE_EXPR, TREE_TYPE (cond), cond,
build_int_cst (integer_type_node,
- annot_expr_parallel_kind),
+ annot_expr_ivdep_kind),
integer_zero_node);
tmp = build1_v (GOTO_EXPR, exit_label);
+2018-04-12 Thomas Koenig <tkoenig@gcc.gnu.org>
+
+ PR fortran/83064
+ PR testsuite/85346
+ * gfortran.dg/do_concurrent_5.f90: Dynamically allocate main work
+ array and move test to libgomp/testsuite/libgomp.fortran.
+ * gfortran.dg/do_concurrent_6.f90: New test.
+
2018-04-12 Marek Polacek <polacek@redhat.com>
PR c++/85258
--- /dev/null
+! { dg-do compile }
+! { dg-additional-options "-fdump-tree-original" }
+
+program main
+ real, dimension(100) :: a,b
+ call random_number(a)
+ do concurrent (i=1:100)
+ b(i) = a(i)*a(i)
+ end do
+ print *,sum(a)
+end program main
+
+! { dg-final { scan-tree-dump-times "ivdep" 1 "original" } }
+2018-04-12 Thomas Koenig <tkoenig@gcc.gnu.org>
+
+ PR fortran/83064
+ PR testsuite/85346
+ * testsuite/libgomp.fortran/do_concurrent_5.f90: Move modified
+ test from gfortran.dg to here.
+
2018-04-05 Tom de Vries <tom@codesourcery.com>
PR target/85204
! { dg-do run }
! PR 83064 - this used to give wrong results.
-! { dg-options "-O3 -ftree-parallelize-loops=2" }
+! { dg-additional-options "-O1 -ftree-parallelize-loops=2" }
! Original test case by Christian Felter
program main
implicit none
integer, parameter :: nsplit = 4
- integer(int64), parameter :: ne = 20000000
- integer(int64) :: stride, low(nsplit), high(nsplit), edof(ne), i
+ integer(int64), parameter :: ne = 2**20
+ integer(int64) :: stride, low(nsplit), high(nsplit), i
real(real64), dimension(nsplit) :: pi
-
+ integer(int64), dimension(:), allocatable :: edof
+
+ allocate (edof(ne))
edof(1::4) = 1
edof(2::4) = 2
edof(3::4) = 3
do concurrent (i = 1:nsplit)
pi(i) = sum(compute( low(i), high(i) ))
end do
- if (abs (sum(pi) - atan(1.0d0)) > 1e-5) call abort
+ if (abs (sum(pi) - atan(1.0d0)) > 1e-5) STOP 1
contains