From 213ab0a6c49f10069615b98d38bb794f844cf433 Mon Sep 17 00:00:00 2001
From: Tobias Burnus <burnus@gcc.gnu.org>
Date: Fri, 2 Jan 2015 14:34:58 +0100
Subject: [PATCH] trans-decl.c (gfc_build_qualified_array): Fix coarray tokens
 for module coarrays with -fcoarray=lib.

2015-01-02  Tobias Burnus  <burnus@net-b.de>

        * trans-decl.c (gfc_build_qualified_array): Fix coarray tokens
        for module coarrays with -fcoarray=lib.

2015-01-02  Tobias Burnus  <burnus@net-b.de>

        * gfortran.dg/coarray/codimension_2.f90: New.
        * gfortran.dg/coarray/codimension_2a.f90: New.
        * gfortran.dg/coarray_35.f90: New.
        * gfortran.dg/coarray_35a.f90: New.

From-SVN: r219142
---
 gcc/fortran/ChangeLog                         |  7 ++++-
 gcc/fortran/trans-decl.c                      | 18 ++++++++++--
 gcc/testsuite/ChangeLog                       |  9 +++++-
 .../gfortran.dg/coarray/codimension_2.f90     | 14 ++++++++++
 .../gfortran.dg/coarray/codimension_2a.f90    | 26 +++++++++++++++++
 gcc/testsuite/gfortran.dg/coarray_35.f90      | 17 +++++++++++
 gcc/testsuite/gfortran.dg/coarray_35a.f90     | 28 +++++++++++++++++++
 7 files changed, 114 insertions(+), 5 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/coarray/codimension_2.f90
 create mode 100644 gcc/testsuite/gfortran.dg/coarray/codimension_2a.f90
 create mode 100644 gcc/testsuite/gfortran.dg/coarray_35.f90
 create mode 100644 gcc/testsuite/gfortran.dg/coarray_35a.f90

diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index e45269e0845d..ea72687383f6 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,8 @@
+2015-01-02  Tobias Burnus  <burnus@net-b.de>
+
+	* trans-decl.c (gfc_build_qualified_array): Fix coarray tokens
+	for module coarrays with -fcoarray=lib.
+
 2015-01-02  Janus Weil  <janus@gcc.gnu.org>
 
 	PR fortran/60507
@@ -5,7 +10,7 @@
 	expression is a procedure-pointer result.
 	(compare_actual_formal): Use it.
 
-Copyright (C) 2014 Free Software Foundation, Inc.
+Copyright (C) 2015 Free Software Foundation, Inc.
 
 Copying and distribution of this file, with or without modification,
 are permitted in any medium without royalty provided the copyright
diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c
index 75b84f1495bb..9ef6bfcda808 100644
--- a/gcc/fortran/trans-decl.c
+++ b/gcc/fortran/trans-decl.c
@@ -819,10 +819,22 @@ gfc_build_qualified_array (tree decl, gfc_symbol * sym)
       && GFC_TYPE_ARRAY_CAF_TOKEN (type) == NULL_TREE)
     {
       tree token;
+      tree token_type = build_qualified_type (pvoid_type_node,
+					      TYPE_QUAL_RESTRICT);
+
+      if (sym->module && (sym->attr.use_assoc
+			  || sym->ns->proc_name->attr.flavor == FL_MODULE))
+	{
+	  tree token_name
+		= get_identifier (gfc_get_string (GFC_PREFIX ("caf_token%s"),
+			IDENTIFIER_POINTER (gfc_sym_mangled_identifier (sym))));
+	  token = build_decl (DECL_SOURCE_LOCATION (decl), VAR_DECL, token_name,
+			      token_type);
+	  TREE_PUBLIC (token) = 1;
+	}
+      else
+	token = gfc_create_var_np (token_type, "caf_token");
 
-      token = gfc_create_var_np (build_qualified_type (pvoid_type_node,
-						       TYPE_QUAL_RESTRICT),
-				 "caf_token");
       GFC_TYPE_ARRAY_CAF_TOKEN (type) = token;
       DECL_ARTIFICIAL (token) = 1;
       TREE_STATIC (token) = 1;
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 44bc6f2dd3f1..543cec61e1a6 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,9 +1,16 @@
+2015-01-02  Tobias Burnus  <burnus@net-b.de>
+
+	* gfortran.dg/coarray/codimension_2.f90: New.
+	* gfortran.dg/coarray/codimension_2a.f90: New.
+	* gfortran.dg/coarray_35.f90: New.
+	* gfortran.dg/coarray_35a.f90: New.
+
 2015-01-02  Janus Weil  <janus@gcc.gnu.org>
 
 	PR fortran/60507
 	* gfortran.dg/dummy_procedure_11: New.
 
-Copyright (C) 2014 Free Software Foundation, Inc.
+Copyright (C) 2015 Free Software Foundation, Inc.
 
 Copying and distribution of this file, with or without modification,
 are permitted in any medium without royalty provided the copyright
diff --git a/gcc/testsuite/gfortran.dg/coarray/codimension_2.f90 b/gcc/testsuite/gfortran.dg/coarray/codimension_2.f90
new file mode 100644
index 000000000000..b211f9b24485
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/coarray/codimension_2.f90
@@ -0,0 +1,14 @@
+! { dg-do link }
+! { dg-additional-sources codimension_2a.f90 }
+!
+! To be used with codimension_2a.f90
+! Check that the coarray declared in the module is accessible
+! by doing a link test
+!
+! Contributed by Alessandro Fanfarillo.
+!
+module global_coarrays
+  implicit none
+  integer,parameter :: n=10
+  integer :: b(10)[*]
+end module global_coarrays
diff --git a/gcc/testsuite/gfortran.dg/coarray/codimension_2a.f90 b/gcc/testsuite/gfortran.dg/coarray/codimension_2a.f90
new file mode 100644
index 000000000000..8eb472c6358c
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/coarray/codimension_2a.f90
@@ -0,0 +1,26 @@
+! { dg-do compile { target { ! *-*-* } } }
+! SKIP THIS FILE
+!
+! Used by codimension_2.f90
+!
+! Check that the coarray declared in the module is accessible
+! by doing a link test
+!
+! Contributed by Alessandro Fanfarillo.
+!
+program testmod
+  use global_coarrays
+  implicit none
+  
+  integer :: me
+
+  me = this_image()
+
+  b = me
+
+  if(me==1) then
+     b(:) = b(:)[2]
+     write(*,*) b
+  end if
+
+end program testmod
diff --git a/gcc/testsuite/gfortran.dg/coarray_35.f90 b/gcc/testsuite/gfortran.dg/coarray_35.f90
new file mode 100644
index 000000000000..e65f8fec90fc
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/coarray_35.f90
@@ -0,0 +1,17 @@
+! { dg-do compile }
+! { dg-options "-fcoarray=lib" }
+!
+! To be used with coarray_35a.f90
+! Check that the coarray declared in the module is accessible
+! by checking the assembler name
+!
+! Contributed by Alessandro Fanfarillo.
+!
+module global_coarrays
+  implicit none
+  integer,parameter :: n=10
+  integer :: b(10)[*]
+end module global_coarrays
+
+! Check for the symbol of the coarray token (w/o system-dependend prefix)
+! { dg-final { scan-assembler "caf_token__global_coarrays_MOD_b" } }
diff --git a/gcc/testsuite/gfortran.dg/coarray_35a.f90 b/gcc/testsuite/gfortran.dg/coarray_35a.f90
new file mode 100644
index 000000000000..eeeb2891ca99
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/coarray_35a.f90
@@ -0,0 +1,28 @@
+! { dg-do compile }
+! { dg-options "-fcoarray=lib" }
+! { dg-compile-aux-modules "coarray_35.f90" }
+!
+! Check that the coarray declared in the module is accessible
+! by checking the assembler name
+!
+! Contributed by Alessandro Fanfarillo.
+!
+program testmod
+  use global_coarrays
+  implicit none
+  
+  integer :: me
+
+  me = this_image()
+
+  b = me
+
+  if(me==1) then
+     b(:) = b(:)[2]
+     write(*,*) b
+  end if
+
+end program testmod
+
+! Check for the symbol of the coarray token (w/o system-dependend prefix)
+! { dg-final { scan-assembler "caf_token__global_coarrays_MOD_b" } }
-- 
GitLab