From cab37c89d1d443c24ad189bb8b62f5665ba829ad Mon Sep 17 00:00:00 2001
From: Jakub Jelinek <jakub@redhat.com>
Date: Thu, 12 Dec 2013 09:52:06 +0100
Subject: [PATCH] re PR libgomp/59467 (copyprivate in the fortran testsuite)

	PR libgomp/59467
	* gimplify.c (omp_check_private): Add copyprivate argument, if it
	is true, don't check omp_privatize_by_reference.
	(gimplify_scan_omp_clauses): For OMP_CLAUSE_COPYPRIVATE verify
	decl is private in outer context.  Adjust omp_check_private caller.

	* gfortran.dg/gomp/pr59467.f90: New test.
	* c-c++-common/gomp/pr59467.c: New test.

	* testsuite/libgomp.fortran/crayptr2.f90: Add private (d) clause to
	!$omp parallel.

From-SVN: r205922
---
 gcc/ChangeLog                                 |  8 +++
 gcc/gimplify.c                                | 35 ++++++++--
 gcc/testsuite/ChangeLog                       |  6 ++
 gcc/testsuite/c-c++-common/gomp/pr59467.c     | 68 +++++++++++++++++++
 gcc/testsuite/gfortran.dg/gomp/pr59467.f90    | 24 +++++++
 libgomp/ChangeLog                             |  6 ++
 .../testsuite/libgomp.fortran/crayptr2.f90    |  2 +-
 7 files changed, 144 insertions(+), 5 deletions(-)
 create mode 100644 gcc/testsuite/c-c++-common/gomp/pr59467.c
 create mode 100644 gcc/testsuite/gfortran.dg/gomp/pr59467.f90

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index d580c4d41b7b..26266a1f35a1 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,11 @@
+2013-12-12  Jakub Jelinek  <jakub@redhat.com>
+
+	PR libgomp/59467
+	* gimplify.c (omp_check_private): Add copyprivate argument, if it
+	is true, don't check omp_privatize_by_reference.
+	(gimplify_scan_omp_clauses): For OMP_CLAUSE_COPYPRIVATE verify
+	decl is private in outer context.  Adjust omp_check_private caller.
+
 2013-12-11  Jeff Law  <law@redhat.com>
 
 	PR rtl-optimization/59446
diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index 8bcce22a9385..1ca847ac7597 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -5817,7 +5817,7 @@ omp_is_private (struct gimplify_omp_ctx *ctx, tree decl, bool simd)
    region's REDUCTION clause.  */
 
 static bool
-omp_check_private (struct gimplify_omp_ctx *ctx, tree decl)
+omp_check_private (struct gimplify_omp_ctx *ctx, tree decl, bool copyprivate)
 {
   splay_tree_node n;
 
@@ -5826,8 +5826,11 @@ omp_check_private (struct gimplify_omp_ctx *ctx, tree decl)
       ctx = ctx->outer_context;
       if (ctx == NULL)
 	return !(is_global_var (decl)
-		 /* References might be private, but might be shared too.  */
-		 || lang_hooks.decls.omp_privatize_by_reference (decl));
+		 /* References might be private, but might be shared too,
+		    when checking for copyprivate, assume they might be
+		    private, otherwise assume they might be shared.  */
+		 || (!copyprivate
+		     && lang_hooks.decls.omp_privatize_by_reference (decl)));
 
       if ((ctx->region_type & (ORT_TARGET | ORT_TARGET_DATA)) != 0)
 	continue;
@@ -6037,12 +6040,36 @@ gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
 	      remove = true;
 	      break;
 	    }
+	  if (OMP_CLAUSE_CODE (c) == OMP_CLAUSE_COPYPRIVATE
+	      && !remove
+	      && !omp_check_private (ctx, decl, true))
+	    {
+	      remove = true;
+	      if (is_global_var (decl))
+		{
+		  if (DECL_THREAD_LOCAL_P (decl))
+		    remove = false;
+		  else if (DECL_HAS_VALUE_EXPR_P (decl))
+		    {
+		      tree value = get_base_address (DECL_VALUE_EXPR (decl));
+
+		      if (value
+			  && DECL_P (value)
+			  && DECL_THREAD_LOCAL_P (value))
+			remove = false;
+		    }
+		}
+	      if (remove)
+		error_at (OMP_CLAUSE_LOCATION (c),
+			  "copyprivate variable %qE is not threadprivate"
+			  " or private in outer context", DECL_NAME (decl));
+	    }
 	do_notice:
 	  if (outer_ctx)
 	    omp_notice_variable (outer_ctx, decl, true);
 	  if (check_non_private
 	      && region_type == ORT_WORKSHARE
-	      && omp_check_private (ctx, decl))
+	      && omp_check_private (ctx, decl, false))
 	    {
 	      error ("%s variable %qE is private in outer context",
 		     check_non_private, DECL_NAME (decl));
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 6022e3f38eb5..b91e83f48bc0 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,9 @@
+2013-12-12  Jakub Jelinek  <jakub@redhat.com>
+
+	PR libgomp/59467
+	* gfortran.dg/gomp/pr59467.f90: New test.
+	* c-c++-common/gomp/pr59467.c: New test.
+
 2013-12-12  Ryan Mansfield  <rmansfield@qnx.com>
 
 	PR testsuite/59442
diff --git a/gcc/testsuite/c-c++-common/gomp/pr59467.c b/gcc/testsuite/c-c++-common/gomp/pr59467.c
new file mode 100644
index 000000000000..475182a6236d
--- /dev/null
+++ b/gcc/testsuite/c-c++-common/gomp/pr59467.c
@@ -0,0 +1,68 @@
+/* PR libgomp/59467 */
+
+int v;
+
+void
+foo (void)
+{
+  int x = 0, y = 0;
+  #pragma omp parallel
+  {
+    int z;
+    #pragma omp single copyprivate (x)	/* { dg-error "is not threadprivate or private in outer context" } */
+    {
+      #pragma omp atomic write
+	x = 6;
+    }
+    #pragma omp atomic read
+    z = x;
+    #pragma omp atomic
+    y += z;
+  }
+  #pragma omp parallel
+  {
+    int z;
+    #pragma omp single copyprivate (v)	/* { dg-error "is not threadprivate or private in outer context" } */
+    {
+      #pragma omp atomic write
+	v = 6;
+    }
+    #pragma omp atomic read
+    z = v;
+    #pragma omp atomic
+    y += z;
+  }
+  #pragma omp parallel private (x)
+  {
+    int z;
+    #pragma omp single copyprivate (x)
+    {
+      #pragma omp atomic write
+	x = 6;
+    }
+    #pragma omp atomic read
+    z = x;
+    #pragma omp atomic
+    y += z;
+  }
+  x = 0;
+  #pragma omp parallel reduction (+:x)
+  {
+    #pragma omp single copyprivate (x)
+    {
+      #pragma omp atomic write
+	x = 6;
+    }
+    #pragma omp atomic
+    y += x;
+  }
+  #pragma omp single copyprivate (x)
+  {
+    x = 7;
+  }
+  #pragma omp single copyprivate (v)	/* { dg-error "is not threadprivate or private in outer context" } */
+  {
+    #pragma omp atomic write
+      v = 6;
+  }
+}
diff --git a/gcc/testsuite/gfortran.dg/gomp/pr59467.f90 b/gcc/testsuite/gfortran.dg/gomp/pr59467.f90
new file mode 100644
index 000000000000..e69c9eb49a02
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/gomp/pr59467.f90
@@ -0,0 +1,24 @@
+! PR libgomp/59467
+! { dg-do compile }
+! { dg-options "-fopenmp" }
+  FUNCTION t()
+    INTEGER :: a, b, t
+    a = 0
+    b = 0
+    !$OMP PARALLEL REDUCTION(+:b)
+      !$OMP SINGLE	! { dg-error "is not threadprivate or private in outer context" }
+        !$OMP ATOMIC WRITE
+        a = 6
+      !$OMP END SINGLE COPYPRIVATE (a)
+      b = a
+    !$OMP END PARALLEL
+    t = b
+    b = 0
+    !$OMP PARALLEL REDUCTION(+:b)
+      !$OMP SINGLE
+        !$OMP ATOMIC WRITE
+        b = 6
+      !$OMP END SINGLE COPYPRIVATE (b)
+    !$OMP END PARALLEL
+    t = t + b
+  END FUNCTION
diff --git a/libgomp/ChangeLog b/libgomp/ChangeLog
index 00b4ce1ba899..bdcc930d97bd 100644
--- a/libgomp/ChangeLog
+++ b/libgomp/ChangeLog
@@ -1,3 +1,9 @@
+2013-12-12  Jakub Jelinek  <jakub@redhat.com>
+
+	PR libgomp/59467
+	* testsuite/libgomp.fortran/crayptr2.f90: Add private (d) clause to
+	!$omp parallel.
+
 2013-11-07  Thomas Schwinge  <thomas@codesourcery.com>
 
 	* testsuite/lib/libgomp.exp (libgomp_init): Don't add -fopenmp to
diff --git a/libgomp/testsuite/libgomp.fortran/crayptr2.f90 b/libgomp/testsuite/libgomp.fortran/crayptr2.f90
index 4ad7cf228b65..c88cc7ab884a 100644
--- a/libgomp/testsuite/libgomp.fortran/crayptr2.f90
+++ b/libgomp/testsuite/libgomp.fortran/crayptr2.f90
@@ -12,7 +12,7 @@
   b = 2
   c = 3
   l = .false.
-!$omp parallel num_threads (3) reduction (.or.:l)
+!$omp parallel num_threads (3) reduction (.or.:l) private (d)
   if (omp_get_thread_num () .eq. 0) then
     ip = loc (a)
   elseif (omp_get_thread_num () .eq. 1) then
-- 
GitLab