re PR fortran/83064 (DO CONCURRENT and auto-parallelization)
authorThomas Koenig <tkoenig@gcc.gnu.org>
Mon, 9 Apr 2018 21:52:05 +0000 (21:52 +0000)
committerThomas Koenig <tkoenig@gcc.gnu.org>
Mon, 9 Apr 2018 21:52:05 +0000 (21:52 +0000)
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/83064
* gfortran.dg/do_concurrent_5.f90: New test.
* gfortran.dg/vect/vect-do-concurrent-1.f90: Adjust dg-bogus
message.

From-SVN: r259258

gcc/fortran/ChangeLog
gcc/fortran/trans-stmt.c
gcc/testsuite/ChangeLog
gcc/testsuite/gfortran.dg/do_concurrent_5.f90 [new file with mode: 0644]
gcc/testsuite/gfortran.dg/vect/vect-do-concurrent-1.f90

index 324fbf3f0bbf541ea2aa1ff2fa410d4a04ec9c45..53792eb25d8013aa49f4fdda9d5d2302b60f3b5a 100644 (file)
@@ -1,3 +1,10 @@
+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
index 25d5d3cc8cb5564b472d240c07f348c4aef045b3..c44450e6aa587d3a85df2087184688721720dfcc 100644 (file)
@@ -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),
index d2fefd33de610ce308abe5700c2308a6b664f4c5..9bfd5915ed10cc1411d92086cf88e5a7889aeaea 100644 (file)
@@ -1,3 +1,10 @@
+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
diff --git a/gcc/testsuite/gfortran.dg/do_concurrent_5.f90 b/gcc/testsuite/gfortran.dg/do_concurrent_5.f90
new file mode 100644 (file)
index 0000000..feee4c9
--- /dev/null
@@ -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
index 3e6ad21764fa63637e893ebe1d14f3a385d810ad..6aece5a26590cc3b0d170e153bbc259aa3ab1be1 100644 (file)
@@ -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 }