From 693d710f2ad03341b24d45d1b2ab75533d67687e Mon Sep 17 00:00:00 2001
From: Jakub Jelinek <jakub@redhat.com>
Date: Wed, 3 May 2006 14:51:33 +0200
Subject: [PATCH] re PR fortran/27395 (Problem with arrays in the OpenMP
 REDUCTION clause in Fortran)

	PR fortran/27395
	* gimplify.c (gimplify_scan_omp_clauses): Compare OMP_CLAUSE_CODE
	rather than TREE_CODE to OMP_CLAUSE_REDUCTION.  Set also GOVD_SEEN
	bit for OMP_CLAUSE_REDUCTION_PLACEHOLDER.

	* testsuite/libgomp.fortran/pr27395-1.f90: New test.
	* testsuite/libgomp.fortran/pr27395-2.f90: New test.

From-SVN: r113494
---
 gcc/ChangeLog                                 |  7 +++++
 gcc/gimplify.c                                |  4 +--
 libgomp/ChangeLog                             |  6 ++++
 .../testsuite/libgomp.fortran/pr27395-1.f90   | 31 +++++++++++++++++++
 .../testsuite/libgomp.fortran/pr27395-2.f90   | 30 ++++++++++++++++++
 5 files changed, 76 insertions(+), 2 deletions(-)
 create mode 100644 libgomp/testsuite/libgomp.fortran/pr27395-1.f90
 create mode 100644 libgomp/testsuite/libgomp.fortran/pr27395-2.f90

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 6e73c304f345..902857b933f9 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,10 @@
+2006-05-03  Jakub Jelinek  <jakub@redhat.com>
+
+	PR fortran/27395
+	* gimplify.c (gimplify_scan_omp_clauses): Compare OMP_CLAUSE_CODE
+	rather than TREE_CODE to OMP_CLAUSE_REDUCTION.  Set also GOVD_SEEN
+	bit for OMP_CLAUSE_REDUCTION_PLACEHOLDER.
+
 2006-05-02  Daniel Berlin  <dberlin@dberlin.org>
 
 	Fix PR tree-optimization/26626
diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index af3d92431284..91b88810f38e 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -4510,11 +4510,11 @@ gimplify_scan_omp_clauses (tree *list_p, tree *pre_p, bool in_parallel)
 	      && DECL_BY_REFERENCE (TREE_OPERAND (decl, 0)))
 	    OMP_CLAUSE_DECL (c) = decl = TREE_OPERAND (decl, 0);
 	  omp_add_variable (ctx, decl, flags);
-	  if (TREE_CODE (c) == OMP_CLAUSE_REDUCTION
+	  if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_REDUCTION
 	      && OMP_CLAUSE_REDUCTION_PLACEHOLDER (c))
 	    {
 	      omp_add_variable (ctx, OMP_CLAUSE_REDUCTION_PLACEHOLDER (c),
-				GOVD_LOCAL);
+				GOVD_LOCAL | GOVD_SEEN);
 	      gimplify_omp_ctxp = ctx;
 	      push_gimplify_context ();
 	      gimplify_stmt (&OMP_CLAUSE_REDUCTION_INIT (c));
diff --git a/libgomp/ChangeLog b/libgomp/ChangeLog
index 76d5631106fb..d04194cd4a65 100644
--- a/libgomp/ChangeLog
+++ b/libgomp/ChangeLog
@@ -1,3 +1,9 @@
+2006-05-03  Jakub Jelinek  <jakub@redhat.com>
+
+	PR fortran/27395
+	* testsuite/libgomp.fortran/pr27395-1.f90: New test.
+	* testsuite/libgomp.fortran/pr27395-2.f90: New test.
+
 2006-05-02  Jakub Jelinek  <jakub@redhat.com>
 
 	PR c++/26943
diff --git a/libgomp/testsuite/libgomp.fortran/pr27395-1.f90 b/libgomp/testsuite/libgomp.fortran/pr27395-1.f90
new file mode 100644
index 000000000000..380a107760bc
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/pr27395-1.f90
@@ -0,0 +1,31 @@
+! PR fortran/27395
+! { dg-do run }
+
+program pr27395_1
+  implicit none
+  integer, parameter :: n=10,m=1001
+  integer :: i
+  integer, dimension(n) :: sumarray
+  call foo(n,m,sumarray)
+  do i=1,n
+    if (sumarray(i).ne.m*i) call abort
+  end do
+end program pr27395_1
+
+subroutine foo(n,m,sumarray)
+  use omp_lib, only : omp_get_thread_num
+  implicit none
+  integer, intent(in) :: n,m
+  integer, dimension(n), intent(out) :: sumarray
+  integer :: i,j
+  sumarray(:)=0
+!$OMP PARALLEL DEFAULT(shared) NUM_THREADS(4)
+!$OMP DO PRIVATE(j,i), REDUCTION(+:sumarray)
+  do j=1,m
+    do i=1,n
+      sumarray(i)=sumarray(i)+i
+    end do
+  end do
+!$OMP END DO
+!$OMP END PARALLEL
+end subroutine foo
diff --git a/libgomp/testsuite/libgomp.fortran/pr27395-2.f90 b/libgomp/testsuite/libgomp.fortran/pr27395-2.f90
new file mode 100644
index 000000000000..b3cb255f6dd7
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/pr27395-2.f90
@@ -0,0 +1,30 @@
+! PR fortran/27395
+! { dg-do run }
+
+program pr27395_2
+  implicit none
+  integer, parameter :: n=10,m=1001
+  integer :: i
+  call foo(n,m)
+end program pr27395_2
+
+subroutine foo(n,m)
+  use omp_lib, only : omp_get_thread_num
+  implicit none
+  integer, intent(in) :: n,m
+  integer :: i,j
+  integer, dimension(n) :: sumarray
+  sumarray(:)=0
+!$OMP PARALLEL DEFAULT(shared) NUM_THREADS(4)
+!$OMP DO PRIVATE(j,i), REDUCTION(+:sumarray)
+  do j=1,m
+    do i=1,n
+      sumarray(i)=sumarray(i)+i
+    end do
+  end do
+!$OMP END DO
+!$OMP END PARALLEL
+  do i=1,n
+    if (sumarray(i).ne.m*i) call abort
+  end do
+end subroutine foo
-- 
GitLab