aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--gcc/fortran/ChangeLog7
-rw-r--r--gcc/fortran/trans-stmt.c5
-rw-r--r--gcc/testsuite/ChangeLog7
-rw-r--r--gcc/testsuite/gfortran.dg/do_concurrent_5.f9070
-rw-r--r--gcc/testsuite/gfortran.dg/vect/vect-do-concurrent-1.f901
5 files changed, 88 insertions, 2 deletions
diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 324fbf3..53792eb 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,5 +1,12 @@
2018-04-09 Thomas Koenig <tkoenig@gcc.gnu.org>
+ PR fortran/83064
+ * trans-stmt.c (gfc_trans_forall_loop): Remove annotation for
+ parallell processing of DO CONCURRENT -ftree-parallelize-loops
+ is set.
+
+2018-04-09 Thomas Koenig <tkoenig@gcc.gnu.org>
+
PR fortran/51260
* resolve.c (resolve_variable): Simplify cases where access to a
parameter array results in a single constant.
diff --git a/gcc/fortran/trans-stmt.c b/gcc/fortran/trans-stmt.c
index 25d5d3c..c44450e 100644
--- a/gcc/fortran/trans-stmt.c
+++ b/gcc/fortran/trans-stmt.c
@@ -3642,7 +3642,10 @@ gfc_trans_forall_loop (forall_info *forall_tmp, tree body,
/* The exit condition. */
cond = fold_build2_loc (input_location, LE_EXPR, logical_type_node,
count, build_int_cst (TREE_TYPE (count), 0));
- if (forall_tmp->do_concurrent)
+
+ /* PR 83064 means that we cannot use the annotation if the
+ autoparallelizer is active. */
+ if (forall_tmp->do_concurrent && ! flag_tree_parallelize_loops)
cond = build3 (ANNOTATE_EXPR, TREE_TYPE (cond), cond,
build_int_cst (integer_type_node,
annot_expr_parallel_kind),
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index d2fefd3..9bfd591 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,5 +1,12 @@
2018-04-09 Thomas Koenig <tkoenig@gcc.gnu.org>
+ PR fortran/83064
+ * gfortran.dg/do_concurrent_5.f90: New test.
+ * gfortran.dg/vect/vect-do-concurrent-1.f90: Adjust dg-bogus
+ message.
+
+2018-04-09 Thomas Koenig <tkoenig@gcc.gnu.org>
+
PR fortran/51260
* gfortran.dg/parameter_array_element_3.f90: New test.
diff --git a/gcc/testsuite/gfortran.dg/do_concurrent_5.f90 b/gcc/testsuite/gfortran.dg/do_concurrent_5.f90
new file mode 100644
index 0000000..feee4c9
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/do_concurrent_5.f90
@@ -0,0 +1,70 @@
+! { dg-do run }
+! PR 83064 - this used to give wrong results.
+! { dg-options "-O3 -ftree-parallelize-loops=2" }
+! Original test case by Christian Felter
+
+program main
+ use, intrinsic :: iso_fortran_env
+ implicit none
+
+ integer, parameter :: nsplit = 4
+ integer(int64), parameter :: ne = 20000000
+ integer(int64) :: stride, low(nsplit), high(nsplit), edof(ne), i
+ real(real64), dimension(nsplit) :: pi
+
+ edof(1::4) = 1
+ edof(2::4) = 2
+ edof(3::4) = 3
+ edof(4::4) = 4
+
+ stride = ceiling(real(ne)/nsplit)
+ do i = 1, nsplit
+ high(i) = stride*i
+ end do
+ do i = 2, nsplit
+ low(i) = high(i-1) + 1
+ end do
+ low(1) = 1
+ high(nsplit) = ne
+
+ pi = 0
+ 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
+
+contains
+
+ pure function compute( low, high ) result( ttt )
+ integer(int64), intent(in) :: low, high
+ real(real64), dimension(nsplit) :: ttt
+ integer(int64) :: j, k
+
+ ttt = 0
+
+ ! Unrolled loop
+! do j = low, high, 4
+! k = 1
+! ttt(k) = ttt(k) + (-1)**(j+1) / real( 2*j-1 )
+! k = 2
+! ttt(k) = ttt(k) + (-1)**(j+2) / real( 2*j+1 )
+! k = 3
+! ttt(k) = ttt(k) + (-1)**(j+3) / real( 2*j+3 )
+! k = 4
+! ttt(k) = ttt(k) + (-1)**(j+4) / real( 2*j+5 )
+! end do
+
+ ! Loop with modulo operation
+! do j = low, high
+! k = mod( j, nsplit ) + 1
+! ttt(k) = ttt(k) + (-1)**(j+1) / real( 2*j-1 )
+! end do
+
+ ! Loop with subscripting via host association
+ do j = low, high
+ k = edof(j)
+ ttt(k) = ttt(k) + (-1.0_real64)**(j+1) / real( 2*j-1 )
+ end do
+ end function
+
+end program main
diff --git a/gcc/testsuite/gfortran.dg/vect/vect-do-concurrent-1.f90 b/gcc/testsuite/gfortran.dg/vect/vect-do-concurrent-1.f90
index 3e6ad21..6aece5a2 100644
--- a/gcc/testsuite/gfortran.dg/vect/vect-do-concurrent-1.f90
+++ b/gcc/testsuite/gfortran.dg/vect/vect-do-concurrent-1.f90
@@ -12,4 +12,3 @@ subroutine test(n, a, b, c)
end subroutine test
! { dg-message "loop vectorized" "" { target *-*-* } 0 }
-! { dg-bogus " version\[^\n\r]* alias" "" { target *-*-* } 0 }