From bedee914ca77688f4c2d9138216b3a3b84fbb619 Mon Sep 17 00:00:00 2001
From: Paul Thomas <pault@gcc.gnu.org>
Date: Tue, 16 May 2017 20:09:02 +0000
Subject: [PATCH] re PR fortran/80554 ([f08] variable redefinition in
 submodule)

2017-05-16  Paul Thomas  <pault@gcc.gnu.org>

	PR fortran/80554
	* decl.c (build_sym): In a submodule allow overriding of host
	associated symbols from the ancestor module with a new
	declaration.

2017-05-16  Paul Thomas  <pault@gcc.gnu.org>

	PR fortran/80554
	* gfortran.dg/submodule_29.f08: New test.

From-SVN: r248129
---
 gcc/fortran/ChangeLog                      | 11 ++++-
 gcc/fortran/decl.c                         | 22 ++++++++-
 gcc/testsuite/ChangeLog                    |  7 ++-
 gcc/testsuite/gfortran.dg/submodule_29.f08 | 56 ++++++++++++++++++++++
 4 files changed, 92 insertions(+), 4 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/submodule_29.f08

diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 542ee730b9b7..a364e4460f91 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,10 @@
+2017-05-16  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/80554
+	* decl.c (build_sym): In a submodule allow overriding of host
+	associated symbols from the ancestor module with a new
+	declaration.
+
 2017-05-15  Steven G. Kargl  <kargl@gcc.gnu.org>
 
 	PR fortran/80674
@@ -18,7 +25,7 @@
 	end and stride expressions
 	(gfc_advance_section): Simplify start and end
 	expressions
-	(gfc_get_section_index): Simplify start expression 
+	(gfc_get_section_index): Simplify start expression
 
 2017-05-13  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
 
@@ -35,7 +42,7 @@
 	Fortran 95 restriction on namelist objects.
 
 2017-05-11  Nathan Sidwell  <nathan@acm.org>
-	
+
 	* trans-decl.c: Include dumpfile.h not tree-dump.h,
 
 2017-05-09  Janus Weil  <janus@gcc.gnu.org>
diff --git a/gcc/fortran/decl.c b/gcc/fortran/decl.c
index 5ca664e57a57..1cbf23819a94 100644
--- a/gcc/fortran/decl.c
+++ b/gcc/fortran/decl.c
@@ -1383,8 +1383,28 @@ build_sym (const char *name, gfc_charlen *cl, bool cl_deferred,
   symbol_attribute attr;
   gfc_symbol *sym;
   int upper;
+  gfc_symtree *st;
 
-  if (gfc_get_symbol (name, NULL, &sym))
+  /* Symbols in a submodule are host associated from the parent module or
+     submodules. Therefore, they can be overridden by declarations in the
+     submodule scope. Deal with this by attaching the existing symbol to
+     a new symtree and recycling the old symtree with a new symbol...  */
+  st = gfc_find_symtree (gfc_current_ns->sym_root, name);
+  if (st != NULL && gfc_state_stack->state == COMP_SUBMODULE
+      && st->n.sym != NULL
+      && st->n.sym->attr.host_assoc && st->n.sym->attr.used_in_submodule)
+    {
+      gfc_symtree *s = gfc_get_unique_symtree (gfc_current_ns);
+      s->n.sym = st->n.sym;
+      sym = gfc_new_symbol (name, gfc_current_ns);
+
+
+      st->n.sym = sym;
+      sym->refs++;
+      gfc_set_sym_referenced (sym);
+    }
+  /* ...Otherwise generate a new symtree and new symbol.  */
+  else if (gfc_get_symbol (name, NULL, &sym))
     return false;
 
   /* Check if the name has already been defined as a type.  The
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index b3dd772e7da1..b8ea07b10f67 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2017-05-16  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/80554
+	* gfortran.dg/submodule_29.f08: New test.
+
 2017-05-16  David Malcolm  <dmalcolm@redhat.com>
 
 	* g++.dg/other/accessor-fixits-1.C: New test case.
@@ -1279,7 +1284,7 @@
 	* gcc.dg/tree-ssa/vrp35.c: Disable EVRP.
 	* gcc.dg/tree-ssa/vrp36.c: Likewise.
 	* gcc.dg/tree-ssa/pr49039.c: Likewise.
- 
+
 2017-04-27  Marek Polacek  <polacek@redhat.com>
 
 	PR sanitizer/80349
diff --git a/gcc/testsuite/gfortran.dg/submodule_29.f08 b/gcc/testsuite/gfortran.dg/submodule_29.f08
new file mode 100644
index 000000000000..98141cc700ce
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/submodule_29.f08
@@ -0,0 +1,56 @@
+! { dg-do run }
+!
+! Test the fix for PR80554 in which it was not recognised that the symbol 'i'
+! is host associated in the submodule 's' so that the new declaration in the
+! submodule was rejected.
+!
+! Contributed by Tamas Bela Feher  <tamas.bela.feher@ipp.mpg.de>
+!
+module M
+  implicit none
+  integer :: i = 0
+  character (100) :: buffer
+  interface
+    module subroutine write_i()
+    end subroutine
+  end interface
+  interface
+    module subroutine write_i_2()
+    end subroutine
+  end interface
+contains
+  subroutine foo
+    integer :: i
+  end
+end module
+
+submodule (M) S
+    integer :: i = 137
+  contains
+    module subroutine write_i()
+       write (buffer,*) i
+    end subroutine
+end submodule
+
+submodule (M:S) S2
+    integer :: i = 1037
+  contains
+    module subroutine write_i_2()
+       write (buffer,*) i
+    end subroutine
+end submodule
+
+program test_submod_variable
+  use M
+  implicit none
+  integer :: j
+  i = 42
+  call write_i
+  read (buffer, *) j
+  if (i .ne. 42) call abort
+  if (j .ne. 137) call abort
+  call write_i_2
+  read (buffer, *) j
+  if (i .ne. 42) call abort
+  if (j .ne. 1037) call abort
+end program
-- 
GitLab