From e1c8221962aa8dfba5b2462449bccfe10c2d561e Mon Sep 17 00:00:00 2001
From: Jakub Jelinek <jakub@redhat.com>
Date: Thu, 12 Jul 2007 14:16:54 +0200
Subject: [PATCH] re PR fortran/32550 (openmp: COPYPRIVATE of pointer variables
 fails)

	PR fortran/32550
	* trans.h (GFC_POINTER_TYPE_P): Define.
	* trans-types.c (gfc_sym_type): Set it for types on attr->sym.pointer.
	* trans-openmp.c (gfc_omp_privatize_by_reference): Return false
	if GFC_POINTER_TYPE_P is set on the type.

	* testsuite/libgomp.fortran/pr32550.f90: New test.
	* testsuite/libgomp.fortran/crayptr2.f90: New test.

From-SVN: r126583
---
 gcc/fortran/ChangeLog                         |  8 +++++
 gcc/fortran/trans-openmp.c                    |  9 ++++--
 gcc/fortran/trans-types.c                     |  2 ++
 gcc/fortran/trans.h                           |  2 ++
 libgomp/ChangeLog                             |  6 ++++
 .../testsuite/libgomp.fortran/crayptr2.f90    | 30 +++++++++++++++++++
 libgomp/testsuite/libgomp.fortran/pr32550.f90 | 20 +++++++++++++
 7 files changed, 74 insertions(+), 3 deletions(-)
 create mode 100644 libgomp/testsuite/libgomp.fortran/crayptr2.f90
 create mode 100644 libgomp/testsuite/libgomp.fortran/pr32550.f90

diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 20bf60b8d128..ef75186ae030 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,11 @@
+2007-07-12  Jakub Jelinek  <jakub@redhat.com>
+
+	PR fortran/32550
+	* trans.h (GFC_POINTER_TYPE_P): Define.
+	* trans-types.c (gfc_sym_type): Set it for types on attr->sym.pointer.
+	* trans-openmp.c (gfc_omp_privatize_by_reference): Return false
+	if GFC_POINTER_TYPE_P is set on the type.
+
 2007-07-12  Richard Guenther  <rguenther@suse.de>
 
 	* trans-intrinsic.c (gfc_conv_intrinsic_repeat): Convert
diff --git a/gcc/fortran/trans-openmp.c b/gcc/fortran/trans-openmp.c
index 7c381db4f6e5..b0683308f755 100644
--- a/gcc/fortran/trans-openmp.c
+++ b/gcc/fortran/trans-openmp.c
@@ -50,9 +50,12 @@ gfc_omp_privatize_by_reference (tree decl)
 
   if (TREE_CODE (type) == POINTER_TYPE)
     {
-      /* POINTER/ALLOCATABLE have aggregate types, all user variables
-	 that have POINTER_TYPE type are supposed to be privatized
-	 by reference.  */
+      /* Array POINTER/ALLOCATABLE have aggregate types, all user variables
+	 that have POINTER_TYPE type and don't have GFC_POINTER_TYPE_P
+	 set are supposed to be privatized by reference.  */
+      if (GFC_POINTER_TYPE_P (type))
+	return false;
+
       if (!DECL_ARTIFICIAL (decl))
 	return true;
 
diff --git a/gcc/fortran/trans-types.c b/gcc/fortran/trans-types.c
index dace23a5bdee..5af85f194c7b 100644
--- a/gcc/fortran/trans-types.c
+++ b/gcc/fortran/trans-types.c
@@ -1538,6 +1538,8 @@ gfc_sym_type (gfc_symbol * sym)
     {
       if (sym->attr.allocatable || sym->attr.pointer)
 	type = gfc_build_pointer_type (sym, type);
+      if (sym->attr.pointer)
+	GFC_POINTER_TYPE_P (type) = 1;
     }
 
   /* We currently pass all parameters by reference.
diff --git a/gcc/fortran/trans.h b/gcc/fortran/trans.h
index a57deca97f3d..02fe413be036 100644
--- a/gcc/fortran/trans.h
+++ b/gcc/fortran/trans.h
@@ -600,6 +600,8 @@ struct lang_decl		GTY(())
 #define GFC_DESCRIPTOR_TYPE_P(node) TYPE_LANG_FLAG_1(node)
 /* An array without a descriptor.  */
 #define GFC_ARRAY_TYPE_P(node) TYPE_LANG_FLAG_2(node)
+/* Fortran POINTER type.  */
+#define GFC_POINTER_TYPE_P(node) TYPE_LANG_FLAG_3(node)
 /* The GFC_TYPE_ARRAY_* members are present in both descriptor and
    descriptorless array types.  */
 #define GFC_TYPE_ARRAY_LBOUND(node, dim) \
diff --git a/libgomp/ChangeLog b/libgomp/ChangeLog
index 5836fff354b9..20be557df947 100644
--- a/libgomp/ChangeLog
+++ b/libgomp/ChangeLog
@@ -1,3 +1,9 @@
+2007-07-12  Jakub Jelinek  <jakub@redhat.com>
+
+	PR fortran/32550
+	* testsuite/libgomp.fortran/pr32550.f90: New test.
+	* testsuite/libgomp.fortran/crayptr2.f90: New test.
+
 2007-07-05  H.J. Lu  <hongjiu.lu@intel.com>
 
 	* aclocal.m4: Regenerated.
diff --git a/libgomp/testsuite/libgomp.fortran/crayptr2.f90 b/libgomp/testsuite/libgomp.fortran/crayptr2.f90
new file mode 100644
index 000000000000..f8fce6b47605
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/crayptr2.f90
@@ -0,0 +1,30 @@
+! { dg-do run }
+! { dg-options "-fopenmp -fcray-pointer" }
+
+  use omp_lib
+  integer :: a, b, c, d, p
+  logical :: l
+  pointer (ip, p)
+  save ip
+!$omp threadprivate (ip)
+  a = 1
+  b = 2
+  c = 3
+  l = .false.
+!$omp parallel num_threads (3) reduction (.or.:l)
+  if (omp_get_thread_num () .eq. 0) then
+    ip = loc (a)
+  elseif (omp_get_thread_num () .eq. 1) then
+    ip = loc (b)
+  else
+    ip = loc (c)
+  end if
+  l = p .ne. omp_get_thread_num () + 1
+!$omp single
+  d = omp_get_thread_num ()
+!$omp end single copyprivate (d, ip)
+  l = l .or. (p .ne. d + 1)
+!$omp end parallel
+
+  if (l) call abort
+end
diff --git a/libgomp/testsuite/libgomp.fortran/pr32550.f90 b/libgomp/testsuite/libgomp.fortran/pr32550.f90
new file mode 100644
index 000000000000..907a768e6d56
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/pr32550.f90
@@ -0,0 +1,20 @@
+! PR fortran/32550
+! { dg-do run }
+
+      integer, pointer, save :: ptr
+      integer, target :: targ
+      integer :: e
+!$omp threadprivate(ptr)
+      e = 0
+      targ = 42
+!$omp parallel shared(targ)
+!$omp single
+      ptr => targ
+!$omp end single copyprivate(ptr)
+      if (ptr.ne.42) then
+!$omp atomic
+	e = e + 1
+      end if
+!$omp end parallel
+      if (e.ne.0) call abort
+      end
-- 
GitLab