[gcc-7] 320/354: * Update to SVN 20171017 (r253807) from the gcc-7-branch.

Ximin Luo infinity0 at debian.org
Thu Nov 23 15:51:33 UTC 2017


This is an automated email from the git hooks/post-receive script.

infinity0 pushed a commit to branch master
in repository gcc-7.

commit be7f9a78ecb78f7a529577c30b8812830da3eea5
Author: doko <doko at 6ca36cf4-e1d1-0310-8c6f-e303bb2178ca>
Date:   Tue Oct 17 10:54:24 2017 +0000

      * Update to SVN 20171017 (r253807) from the gcc-7-branch.
    
    
    git-svn-id: svn+ssh://svn.debian.org/svn/gcccvs/branches/sid/gcc-7@9749 6ca36cf4-e1d1-0310-8c6f-e303bb2178ca
---
 debian/changelog                |   4 +
 debian/patches/svn-updates.diff | 664 ++++++++++++++++++++++++++++++++++++++--
 2 files changed, 642 insertions(+), 26 deletions(-)

diff --git a/debian/changelog b/debian/changelog
index ca38b2f..4361031 100644
--- a/debian/changelog
+++ b/debian/changelog
@@ -1,5 +1,9 @@
 gcc-7 (7.2.0-11) UNRELEASED; urgency=medium
 
+  * Update to SVN 20171017 (r253807) from the gcc-7-branch.
+    - Fix PR fortran/52832, PR fortran/80120, PR fortran/81903,
+      PR fortran/82121, PR fortran/67543, PR fortran/78152, PR fortran/81048.
+    - Fix libgo bootstrap on s390x and alpha, introduced by the mips backport.
   * Mask __float128 from CUDA compilers. LP: #1717257.
 
  -- Matthias Klose <doko at debian.org>  Mon, 16 Oct 2017 19:01:11 +0200
diff --git a/debian/patches/svn-updates.diff b/debian/patches/svn-updates.diff
index b260ae6..05479f6 100644
--- a/debian/patches/svn-updates.diff
+++ b/debian/patches/svn-updates.diff
@@ -1,10 +1,10 @@
-# DP: updates from the 7 branch upto 20171014 (r253748).
+# DP: updates from the 7 branch upto 20171017 (r253807).
 
 last_update()
 {
 	cat > ${dir}LAST_UPDATED <EOF
-Sat Oct 14 07:09:31 CEST 2017
-Sat Oct 14 05:09:31 UTC 2017 (revision 253748)
+Tue Oct 17 12:44:50 CEST 2017
+Tue Oct 17 10:44:50 UTC 2017 (revision 253807)
 EOF
 }
 
@@ -6786,7 +6786,7 @@ Index: gcc/DATESTAMP
 +++ b/src/gcc/DATESTAMP	(.../branches/gcc-7-branch)
 @@ -1 +1 @@
 -20170814
-+20171014
++20171017
 Index: gcc/tree.c
 ===================================================================
 --- a/src/gcc/tree.c	(.../tags/gcc_7_2_0_release)
@@ -7260,7 +7260,7 @@ Index: gcc/ChangeLog
 ===================================================================
 --- a/src/gcc/ChangeLog	(.../tags/gcc_7_2_0_release)
 +++ b/src/gcc/ChangeLog	(.../branches/gcc-7-branch)
-@@ -1,3 +1,647 @@
+@@ -1,3 +1,643 @@
 +2017-10-13  Jakub Jelinek  <jakub at redhat.com>
 +
 +	PR target/82274
@@ -7901,10 +7901,6 @@ Index: gcc/ChangeLog
 +	* config/sh/sh-mem.cc (sh_expand_cmpnstr): Only unroll for
 +	constant count if that count is less than 32.
 +
-+2017-08-14  Richard Biener  <rguenther at suse.de>
-+
-+	* BASE-VER: Set to 7.2.1.
-+
  2017-08-14  Release Manager
  
  	* GCC 7.2.0 released.
@@ -9048,6 +9044,26 @@ Index: gcc/testsuite/gfortran.dg/dtio_12.f90
 +  if (trim (msg) .ne. "77") call abort
    close(10)
  end
+Index: gcc/testsuite/gfortran.dg/associate_26.f90
+===================================================================
+--- a/src/gcc/testsuite/gfortran.dg/associate_26.f90	(.../tags/gcc_7_2_0_release)
++++ b/src/gcc/testsuite/gfortran.dg/associate_26.f90	(.../branches/gcc-7-branch)
+@@ -0,0 +1,15 @@
++! { dg-do compile }
++! { dg-options "-fcoarray=single" }
++!
++! Test the fix for PR78152
++!
++! Contributed by <physiker at toast2.net>
++!
++program co_assoc
++  implicit none
++  integer, parameter :: p = 5
++  real, allocatable :: a(:,:)[:,:]
++  allocate (a(p,p)[2,*])
++    associate (i => a(1:p, 1:p))
++  end associate
++end program co_assoc
 Index: gcc/testsuite/gfortran.dg/warn_target_lifetime_3.f90
 ===================================================================
 --- a/src/gcc/testsuite/gfortran.dg/warn_target_lifetime_3.f90	(.../tags/gcc_7_2_0_release)
@@ -9061,6 +9077,41 @@ Index: gcc/testsuite/gfortran.dg/warn_target_lifetime_3.f90
  !
  subroutine test
    integer, pointer :: p
+Index: gcc/testsuite/gfortran.dg/associate_29.f90
+===================================================================
+--- a/src/gcc/testsuite/gfortran.dg/associate_29.f90	(.../tags/gcc_7_2_0_release)
++++ b/src/gcc/testsuite/gfortran.dg/associate_29.f90	(.../branches/gcc-7-branch)
+@@ -0,0 +1,30 @@
++! { dg-do compile }
++!
++! Test the fix for PR82121
++!
++! Contributed by Iain Miller  <iain.miller at ecmwf.int>
++!
++MODULE YOMCDDH
++  IMPLICIT NONE
++  SAVE
++  TYPE :: TCDDH
++    CHARACTER(len=12),ALLOCATABLE :: CADHTLS(:)
++  END TYPE TCDDH
++  CHARACTER(len=12),ALLOCATABLE :: CADHTTS(:)
++  TYPE(TCDDH), POINTER :: YRCDDH => NULL()
++END MODULE YOMCDDH
++
++
++SUBROUTINE SUCDDH()
++  USE YOMCDDH  , ONLY : YRCDDH,CADHTTS
++  IMPLICIT NONE
++  ALLOCATE (YRCDDH%CADHTLS(20))
++  ALLOCATE (CADHTTS(20))
++  ASSOCIATE(CADHTLS=>YRCDDH%CADHTLS, NORMCHAR=>CADHTTS)
++! Direct reference to character array compiled correctly
++!    YRCDDH%CADHTLS(1)='SVGTLF'
++! Reference to associated variable name failed to compile
++    CADHTLS(2)='SVGTLT'
++    NORMCHAR(1)='SVLTTC'
++  END ASSOCIATE
++END SUBROUTINE SUCDDH
 Index: gcc/testsuite/gfortran.dg/array_temporaries_4.f90
 ===================================================================
 --- a/src/gcc/testsuite/gfortran.dg/array_temporaries_4.f90	(.../tags/gcc_7_2_0_release)
@@ -9125,6 +9176,94 @@ Index: gcc/testsuite/gfortran.dg/array_temporaries_4.f90
 +  x = (/a (0, "one"),a (0, "two"),a (0, "three"),a (0, "four")/) ! { dg-warning "Creating array temporary" }
 +  y = x
 +end program test 
+Index: gcc/testsuite/gfortran.dg/associate_9.f03
+===================================================================
+--- a/src/gcc/testsuite/gfortran.dg/associate_9.f03	(.../tags/gcc_7_2_0_release)
++++ b/src/gcc/testsuite/gfortran.dg/associate_9.f03	(.../branches/gcc-7-branch)
+@@ -1,8 +1,6 @@
+ ! { dg-do compile }
+ ! { dg-options "-std=f2003 -fall-intrinsics" }
+ 
+-! FIXME: Change into run test and remove excess error expectation.
+-
+ ! PR fortran/38936
+ ! Association to derived-type, where the target type is not know
+ ! during parsing (only resolution).
+@@ -46,5 +44,3 @@
+     IF (x%comp /= 10) CALL abort ()
+   END ASSOCIATE
+ END PROGRAM main
+-
+-! { dg-excess-errors "Syntex error in IF" }
+Index: gcc/testsuite/gfortran.dg/associate_28.f90
+===================================================================
+--- a/src/gcc/testsuite/gfortran.dg/associate_28.f90	(.../tags/gcc_7_2_0_release)
++++ b/src/gcc/testsuite/gfortran.dg/associate_28.f90	(.../branches/gcc-7-branch)
+@@ -0,0 +1,64 @@
++! { dg-do run }
++!
++! Test the fix for PR81903
++!
++! Contributed by Karl May  <karl.may0 at freenet.de>
++!
++Module TestMod_A
++  Type :: TestType_A
++    Real, Allocatable :: a(:,:)
++  End type TestType_A
++End Module TestMod_A
++Module TestMod_B
++  Type :: TestType_B
++   Real, Pointer, contiguous :: a(:,:)
++  End type TestType_B
++End Module TestMod_B
++Module TestMod_C
++  use TestMod_A
++  use TestMod_B
++  Implicit None
++  Type :: TestType_C
++    Class(TestType_A), Pointer :: TT_A(:)
++    Type(TestType_B), Allocatable :: TT_B(:)
++  contains
++    Procedure, Pass :: SetPt => SubSetPt
++  End type TestType_C
++  Interface
++    Module Subroutine SubSetPt(this)
++      class(TestType_C), Intent(InOut), Target :: this
++    End Subroutine
++  End Interface
++End Module TestMod_C
++Submodule(TestMod_C) SetPt
++contains
++  Module Procedure SubSetPt
++    Implicit None
++    integer :: i
++    integer :: sum_a = 0
++    outer:block
++      associate(x=>this%TT_B,y=>this%TT_A)
++        Do i=1,size(x)
++          x(i)%a=>y(i)%a
++          sum_a = sum_a + sum (int (x(i)%a))
++        End Do
++      end associate
++    End block outer
++    if (sum_a .ne. 30) call abort
++  End Procedure
++End Submodule SetPt
++Program Test
++  use TestMod_C
++  use TestMod_A
++  Implicit None
++  Type(TestType_C) :: tb
++  Type(TestType_A), allocatable, Target :: ta(:)
++  integer :: i
++  real :: src(2,2) = reshape ([(real(i), i = 1,4)],[2,2])
++  allocate(ta(2),tb%tt_b(2))
++  do i=1,size(ta)
++    allocate(ta(i)%a(2,2), source = src*real(i))
++  End do
++  tb%TT_A=>ta
++  call tb%setpt()
++End Program Test
 Index: gcc/testsuite/gfortran.dg/zero_sized_7.f90
 ===================================================================
 --- a/src/gcc/testsuite/gfortran.dg/zero_sized_7.f90	(.../tags/gcc_7_2_0_release)
@@ -9209,6 +9348,118 @@ Index: gcc/testsuite/gfortran.dg/pr81723.f
 +
 +      RETURN
 +      END
+Index: gcc/testsuite/gfortran.dg/associate_30.f90
+===================================================================
+--- a/src/gcc/testsuite/gfortran.dg/associate_30.f90	(.../tags/gcc_7_2_0_release)
++++ b/src/gcc/testsuite/gfortran.dg/associate_30.f90	(.../branches/gcc-7-branch)
+@@ -0,0 +1,15 @@
++! { dg-do compile }
++!
++! Test the fix for PR67543
++!
++! Contributed by Gerhard Steinmetz  <gerhard.steinmetz.fortran at t-online.de>
++!
++   subroutine s1
++      associate (x => null())   ! { dg-error "cannot be NULL()" }
++      end associate
++   end subroutine
++
++   subroutine s2
++      associate (x => [null()]) ! { dg-error "has no type" }
++      end associate
++   end subroutine
+Index: gcc/testsuite/gfortran.dg/derived_init_4.f90
+===================================================================
+--- a/src/gcc/testsuite/gfortran.dg/derived_init_4.f90	(.../tags/gcc_7_2_0_release)
++++ b/src/gcc/testsuite/gfortran.dg/derived_init_4.f90	(.../branches/gcc-7-branch)
+@@ -0,0 +1,59 @@
++! { dg-do run }
++!
++! Test the fix for PR81048, where in the second call to 'g2' the
++! default initialization was "forgotten". 'g1', 'g1a' and 'g3' check
++! that this does not occur for scalars and explicit results.
++!
++! Contributed by David Smith  <dm577216smith at gmail.com>
++!
++program test
++   type f
++       integer :: f = -1
++   end type
++   type(f) :: a, b(3)
++   type(f), allocatable :: ans
++   b = g2(a)
++   b = g2(a)
++   ans = g1(a)
++   if (ans%f .ne. -1) call abort
++   ans = g1(a)
++   if (ans%f .ne. -1) call abort
++   ans = g1a(a)
++   if (ans%f .ne. -1) call abort
++   ans = g1a(a)
++   if (ans%f .ne. -1) call abort
++   b = g3(a)
++   b = g3(a)
++contains
++   function g3(a) result(res)
++      type(f) :: a, res(3)
++      do j = 1, 3
++         if (res(j)%f == -1) then
++             res(j)%f = a%f - 1
++         else
++             call abort
++         endif
++      enddo
++   end function g3
++
++   function g2(a)
++      type(f) :: a, g2(3)
++      do j = 1, 3
++         if (g2(j)%f == -1) then
++             g2(j)%f = a%f - 1
++         else
++             call abort
++         endif
++      enddo
++   end function g2
++
++   function g1(a)
++     type(f) :: g1, a
++     if (g1%f .ne. -1 ) call abort
++   end function
++
++   function g1a(a) result(res)
++     type(f) :: res, a
++     if (res%f .ne. -1 ) call abort
++   end function
++end program test
+Index: gcc/testsuite/gfortran.dg/associate_27.f90
+===================================================================
+--- a/src/gcc/testsuite/gfortran.dg/associate_27.f90	(.../tags/gcc_7_2_0_release)
++++ b/src/gcc/testsuite/gfortran.dg/associate_27.f90	(.../branches/gcc-7-branch)
+@@ -0,0 +1,23 @@
++! { dg-do run }
++!
++! Test the fix for PR80120
++!
++! Contributed by Marco Restelli  <mrestelli at gmail.com>
++!
++program p
++ implicit none
++
++ type :: t
++  character(len=25) :: text(2)
++ end type t
++ type(t) :: x
++
++ x%text(1) = "ABC"
++ x%text(2) = "defgh"
++
++ associate( c => x%text )
++   if (c(1)(:maxval(len_trim(c))) .ne. trim (x%text(1))) call abort
++   if (c(2)(:maxval(len_trim(c))) .ne. trim (x%text(2))) call abort
++ end associate
++
++end program p
 Index: gcc/testsuite/gfortran.dg/warn_target_lifetime_4.f90
 ===================================================================
 --- a/src/gcc/testsuite/gfortran.dg/warn_target_lifetime_4.f90	(.../tags/gcc_7_2_0_release)
@@ -10414,7 +10665,31 @@ Index: gcc/testsuite/ChangeLog
 ===================================================================
 --- a/src/gcc/testsuite/ChangeLog	(.../tags/gcc_7_2_0_release)
 +++ b/src/gcc/testsuite/ChangeLog	(.../branches/gcc-7-branch)
-@@ -1,3 +1,468 @@
+@@ -1,3 +1,492 @@
++2017-10-16  Paul Thomas  <pault at gcc.gnu.org>
++
++	PR fortran/78512
++	* gfortran.dg/associate_9.f03 : Remove XFAIL.
++	* gfortran.dg/associate_26.f90 : New test.
++
++	PR fortran/80120
++	* gfortran.dg/associate_27.f90 : New test.
++
++	PR fortran/81903
++	* gfortran.dg/associate_28.f90 : New test.
++
++	PR fortran/82121
++	* gfortran.dg/associate_29.f90 : New test.
++
++	PR fortran/67543
++	* gfortran.dg/associate_30.f90 : New test.
++
++2017-10-16  Paul Thomas  <pault at gcc.gnu.org>
++
++	Backport from trunk
++	PR fortran/81048
++	* gfortran.dg/derived_init_4.f90 : New test.
++
 +2017-10-13  Jakub Jelinek  <jakub at redhat.com>
 +
 +	PR target/82274
@@ -10543,7 +10818,7 @@ Index: gcc/testsuite/ChangeLog
 +
 +	Backported from mainline
 +	2017-09-14  Jakub Jelinek  <jakub at redhat.com>
-+ 
++
 +	PR target/81325
 +	* g++.dg/cpp0x/pr81325.C: New test.
 +
@@ -10883,6 +11158,24 @@ Index: gcc/testsuite/ChangeLog
  2017-08-14  Release Manager
  
  	* GCC 7.2.0 released.
+@@ -150,7 +639,7 @@
+ 	* gfortran.dg/pr81175.f: New testcase.
+ 
+ 	2017-06-21  Marc Glisse  <marc.glisse at inria.fr>
+- 
++
+  	* gcc.dg/tree-ssa/addadd.c: Un-XFAIL.
+  	* gcc.dg/tree-ssa/addadd-2.c: New file.
+ 
+@@ -358,7 +847,7 @@
+ 	* c-c++-common/ubsan/sanitize-recover-7.c (dg-options): Add -w.
+ 
+ 2017-06-24  Marek Polacek  <polacek at redhat.com>
+-	
++
+ 	Backport from mainline
+ 	2017-05-04  Marek Polacek  <polacek at redhat.com>
+ 
 Index: gcc/testsuite/g++.dg/opt/pr82159.C
 ===================================================================
 --- a/src/gcc/testsuite/g++.dg/opt/pr82159.C	(.../tags/gcc_7_2_0_release)
@@ -13749,7 +14042,40 @@ Index: gcc/fortran/ChangeLog
 ===================================================================
 --- a/src/gcc/fortran/ChangeLog	(.../tags/gcc_7_2_0_release)
 +++ b/src/gcc/fortran/ChangeLog	(.../branches/gcc-7-branch)
-@@ -1,3 +1,32 @@
+@@ -1,3 +1,65 @@
++2017-10-16  Paul Thomas  <pault at gcc.gnu.org>
++
++	PR fortran/52832
++	* match.c (gfc_match_associate): Before failing the association
++	try again, allowing a proc pointer selector.
++
++	PR fortran/80120
++	PR fortran/81903
++	PR fortran/82121
++	* primary.c (gfc_match_varspec): Introduce 'tgt_expr', which
++	points to the associate selector, if any. Go through selector
++	references, after resolution for variables, to catch any full
++	or section array references. If a class associate name does
++	not have the same declared type as the selector, resolve the
++	selector and copy the declared type to the associate name.
++	Before throwing a no implicit type error, resolve all allowed
++	selector expressions, and copy the resulting typespec.
++
++	PR fortran/67543
++	* resolve.c (resolve_assoc_var): Selector must cannot be the
++	NULL expression and it must have a type.
++
++	PR fortran/78152
++	* resolve.c (resolve_symbol): Allow associate names to be
++	coarrays.
++
++2017-10-16  Paul Thomas  <pault at gcc.gnu.org>
++
++	Backport from trunk
++	PR fortran/81048
++	* resolve.c (resolve_symbol): Ensure that derived type array
++	results get default initialization.
++
 +2017-10-03  Thomas Koenig  <tkoenig at gcc.gnu.org>
 +	    Steven G. Kargl  <kargl at gcc.gnu.org>
 +
@@ -13825,6 +14151,86 @@ Index: gcc/fortran/expr.c
        for (ref = expr->ref; ref; ref = ref->next)
  	{
  	  switch (ref->type)
+Index: gcc/fortran/resolve.c
+===================================================================
+--- a/src/gcc/fortran/resolve.c	(.../tags/gcc_7_2_0_release)
++++ b/src/gcc/fortran/resolve.c	(.../branches/gcc-7-branch)
+@@ -8294,11 +8294,23 @@
+ 	sym->attr.subref_array_pointer = 1;
+     }
+ 
++  if (target->expr_type == EXPR_NULL)
++    {
++      gfc_error ("Selector at %L cannot be NULL()", &target->where);
++      return;
++    }
++  else if (target->ts.type == BT_UNKNOWN)
++    {
++      gfc_error ("Selector at %L has no type", &target->where);
++      return;
++    }
++
+   /* Get type if this was not already set.  Note that it can be
+      some other type than the target in case this is a SELECT TYPE
+      selector!  So we must not update when the type is already there.  */
+   if (sym->ts.type == BT_UNKNOWN)
+     sym->ts = target->ts;
++
+   gcc_assert (sym->ts.type != BT_UNKNOWN);
+ 
+   /* See if this is a valid association-to-variable.  */
+@@ -11824,6 +11836,7 @@
+   if (sym->ts.deferred
+       && !(sym->attr.pointer
+ 	   || sym->attr.allocatable
++	   || sym->attr.associate_var
+ 	   || sym->attr.omp_udr_artificial_var))
+     {
+       gfc_error ("Entity %qs at %L has a deferred type parameter and "
+@@ -14609,6 +14622,7 @@
+   if (class_attr.codimension
+       && !(class_attr.allocatable || sym->attr.dummy || sym->attr.save
+ 	   || sym->attr.select_type_temporary
++	   || sym->attr.associate_var
+ 	   || (sym->ns->save_all && !sym->attr.automatic)
+ 	   || sym->ns->proc_name->attr.flavor == FL_MODULE
+ 	   || sym->ns->proc_name->attr.is_main_program
+@@ -14793,7 +14807,12 @@
+ 
+       if ((!a->save && !a->dummy && !a->pointer
+ 	   && !a->in_common && !a->use_assoc
+-	   && !a->result && !a->function)
++	   && a->referenced
++	   && !((a->function || a->result)
++		&& (!a->dimension
++		    || sym->ts.u.derived->attr.alloc_comp
++		    || sym->ts.u.derived->attr.pointer_comp))
++	   && !(a->function && sym != sym->result))
+ 	  || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
+ 	apply_default_init (sym);
+       else if (a->function && sym->result && a->access != ACCESS_PRIVATE
+Index: gcc/fortran/match.c
+===================================================================
+--- a/src/gcc/fortran/match.c	(.../tags/gcc_7_2_0_release)
++++ b/src/gcc/fortran/match.c	(.../branches/gcc-7-branch)
+@@ -1882,8 +1882,15 @@
+       if (gfc_match (" %n => %e", newAssoc->name, &newAssoc->target)
+ 	    != MATCH_YES)
+ 	{
+-	  gfc_error ("Expected association at %C");
+-	  goto assocListError;
++	  /* Have another go, allowing for procedure pointer selectors.  */
++	  gfc_matching_procptr_assignment = 1;
++	  if (gfc_match (" %n => %e", newAssoc->name, &newAssoc->target)
++ 	      != MATCH_YES)
++ 	    {
++ 	      gfc_error ("Expected association at %C");
++ 	      goto assocListError;
++ 	    }
++	  gfc_matching_procptr_assignment = 0;
+ 	}
+       newAssoc->where = gfc_current_locus;
+ 
 Index: gcc/fortran/trans-io.c
 ===================================================================
 --- a/src/gcc/fortran/trans-io.c	(.../tags/gcc_7_2_0_release)
@@ -13865,13 +14271,138 @@ Index: gcc/fortran/trans-io.c
  
    if (ts->type == BT_CLASS)
      derived = ts->u.derived->components->ts.u.derived;
-Index: gcc/BASE-VER
+Index: gcc/fortran/primary.c
 ===================================================================
---- a/src/gcc/BASE-VER	(.../tags/gcc_7_2_0_release)
-+++ b/src/gcc/BASE-VER	(.../branches/gcc-7-branch)
-@@ -1 +1 @@
--7.2.0
-+7.2.1
+--- a/src/gcc/fortran/primary.c	(.../tags/gcc_7_2_0_release)
++++ b/src/gcc/fortran/primary.c	(.../branches/gcc-7-branch)
+@@ -1890,6 +1890,7 @@
+   gfc_ref *substring, *tail, *tmp;
+   gfc_component *component;
+   gfc_symbol *sym = primary->symtree->n.sym;
++  gfc_expr *tgt_expr = NULL;
+   match m;
+   bool unknown;
+   char sep;
+@@ -1918,6 +1919,9 @@
+ 	}
+     }
+ 
++  if (sym->assoc && sym->assoc->target)
++    tgt_expr = sym->assoc->target;
++
+   /* For associate names, we may not yet know whether they are arrays or not.
+      If the selector expression is unambiguously an array; eg. a full array
+      or an array section, then the associate name must be an array and we can
+@@ -1929,20 +1933,28 @@
+       && sym->ts.type != BT_CLASS
+       && !sym->attr.dimension)
+     {
+-      if ((!sym->assoc->dangling
+-	   && sym->assoc->target
+-	   && sym->assoc->target->ref
+-	   && sym->assoc->target->ref->type == REF_ARRAY
+-	   && (sym->assoc->target->ref->u.ar.type == AR_FULL
+-	       || sym->assoc->target->ref->u.ar.type == AR_SECTION))
+-	  ||
+-	   (!(sym->assoc->dangling || sym->ts.type == BT_CHARACTER)
+-	    && sym->assoc->st
+-	   && sym->assoc->st->n.sym
+-	    && sym->assoc->st->n.sym->attr.dimension == 0))
++      gfc_ref *ref = NULL;
++
++      if (!sym->assoc->dangling && tgt_expr)
+ 	{
+-    sym->attr.dimension = 1;
+-	  if (sym->as == NULL && sym->assoc
++	   if (tgt_expr->expr_type == EXPR_VARIABLE)
++	     gfc_resolve_expr (tgt_expr);
++
++	   ref = tgt_expr->ref;
++	   for (; ref; ref = ref->next)
++	      if (ref->type == REF_ARRAY
++		  && (ref->u.ar.type == AR_FULL
++		      || ref->u.ar.type == AR_SECTION))
++		break;
++	}
++
++      if (ref || (!(sym->assoc->dangling || sym->ts.type == BT_CHARACTER)
++		  && sym->assoc->st
++		  && sym->assoc->st->n.sym
++		  && sym->assoc->st->n.sym->attr.dimension == 0))
++	{
++	  sym->attr.dimension = 1;
++	  if (sym->as == NULL
+ 	      && sym->assoc->st
+ 	      && sym->assoc->st->n.sym
+ 	      && sym->assoc->st->n.sym->as)
+@@ -1949,6 +1961,15 @@
+ 	    sym->as = gfc_copy_array_spec (sym->assoc->st->n.sym->as);
+ 	}
+     }
++  else if (sym->ts.type == BT_CLASS
++	   && tgt_expr
++	   && tgt_expr->expr_type == EXPR_VARIABLE
++	   && sym->ts.u.derived != tgt_expr->ts.u.derived)
++    {
++      gfc_resolve_expr (tgt_expr);
++      if (tgt_expr->rank)
++	sym->ts.u.derived = tgt_expr->ts.u.derived;
++    }
+ 
+   if ((equiv_flag && gfc_peek_ascii_char () == '(')
+       || gfc_peek_ascii_char () == '[' || sym->attr.codimension
+@@ -2008,10 +2029,31 @@
+       && gfc_get_default_type (sym->name, sym->ns)->type == BT_DERIVED)
+     gfc_set_default_type (sym, 0, sym->ns);
+ 
++  /* See if there is a usable typespec in the "no IMPLICIT type" error.  */
+   if (sym->ts.type == BT_UNKNOWN && m == MATCH_YES)
+     {
+-      gfc_error ("Symbol %qs at %C has no IMPLICIT type", sym->name);
+-      return MATCH_ERROR;
++      bool permissible;
++
++      /* These target expressions can ge resolved at any time.  */
++      permissible = tgt_expr && tgt_expr->symtree && tgt_expr->symtree->n.sym
++		    && (tgt_expr->symtree->n.sym->attr.use_assoc
++			|| tgt_expr->symtree->n.sym->attr.host_assoc
++			|| tgt_expr->symtree->n.sym->attr.if_source
++								== IFSRC_DECL);
++      permissible = permissible
++		    || (tgt_expr && tgt_expr->expr_type == EXPR_OP);
++
++      if (permissible)
++	{
++	  gfc_resolve_expr (tgt_expr);
++	  sym->ts = tgt_expr->ts;
++	}
++
++      if (sym->ts.type == BT_UNKNOWN)
++	{
++	  gfc_error ("Symbol %qs at %C has no IMPLICIT type", sym->name);
++	  return MATCH_ERROR;
++	}
+     }
+   else if ((sym->ts.type != BT_DERIVED && sym->ts.type != BT_CLASS)
+            && m == MATCH_YES)
+@@ -2948,7 +2990,7 @@
+      expression here.  */
+   if (gfc_in_match_data ())
+     gfc_reduce_init_expr (e);
+- 
++
+   *result = e;
+   return MATCH_YES;
+ }
+@@ -3662,7 +3704,7 @@
+ 	implicit_ns = gfc_current_ns;
+       else
+ 	implicit_ns = sym->ns;
+-	
++
+       old_loc = gfc_current_locus;
+       if (gfc_match_member_sep (sym) == MATCH_YES
+ 	  && sym->ts.type == BT_UNKNOWN
 Index: gcc/langhooks.h
 ===================================================================
 --- a/src/gcc/langhooks.h	(.../tags/gcc_7_2_0_release)
@@ -318363,14 +318894,20 @@ Index: libgo/mksysinfo.sh
 ===================================================================
 --- a/src/libgo/mksysinfo.sh	(.../tags/gcc_7_2_0_release)
 +++ b/src/libgo/mksysinfo.sh	(.../branches/gcc-7-branch)
-@@ -302,9 +302,13 @@
-     upcase_fields "__user_psw_struct" "PtracePsw" >> ${OUT} || true
-     upcase_fields "__user_fpregs_struct" "PtraceFpregs" >> ${OUT} || true
-     upcase_fields "__user_per_struct" "PtracePer" >> ${OUT} || true
-+  else
-+    # mips*
-+    regs=`grep '^type _pt_regs struct' gen-sysinfo.go || true`
-   fi
+@@ -295,16 +295,11 @@
+ # _user_regs_struct.
+ regs=`grep '^type _user_regs_struct struct' gen-sysinfo.go || true`
+ if test "$regs" = ""; then
+-  # s390
+-  regs=`grep '^type __user_regs_struct struct' gen-sysinfo.go || true`
+-  if test "$regs" != ""; then
+-    # Substructures of __user_regs_struct on s390
+-    upcase_fields "__user_psw_struct" "PtracePsw" >> ${OUT} || true
+-    upcase_fields "__user_fpregs_struct" "PtraceFpregs" >> ${OUT} || true
+-    upcase_fields "__user_per_struct" "PtracePer" >> ${OUT} || true
+-  fi
++  # mips*
++  regs=`grep '^type _pt_regs struct' gen-sysinfo.go || true`
  fi
  if test "$regs" != ""; then
 +  regs=`echo $regs | sed -e 's/type _pt_regs struct//'`
@@ -318906,6 +319443,49 @@ Index: libgo/go/syscall/endian_big.go
  
  package syscall
  
+Index: libgo/go/syscall/syscall_linux_alpha.go
+===================================================================
+--- a/src/libgo/go/syscall/syscall_linux_alpha.go	(.../tags/gcc_7_2_0_release)
++++ b/src/libgo/go/syscall/syscall_linux_alpha.go	(.../branches/gcc-7-branch)
+@@ -8,38 +8,6 @@
+ 
+ import "unsafe"
+ 
+-type PtraceRegs struct {
+-	R0      uint64
+-	R1      uint64
+-	R2      uint64
+-	R3      uint64
+-	R4      uint64
+-	R5      uint64
+-	R6      uint64
+-	R7      uint64
+-	R8      uint64
+-	R19     uint64
+-	R20     uint64
+-	R21     uint64
+-	R22     uint64
+-	R23     uint64
+-	R24     uint64
+-	R25     uint64
+-	R26     uint64
+-	R27     uint64
+-	R28     uint64
+-	Hae     uint64
+-	Trap_a0 uint64
+-	Trap_a1 uint64
+-	Trap_a2 uint64
+-	Ps      uint64
+-	Pc      uint64
+-	Gp      uint64
+-	R16     uint64
+-	R17     uint64
+-	R18     uint64
+-}
+-
+ func (r *PtraceRegs) PC() uint64 {
+ 	return r.Pc
+ }
 Index: libgo/go/syscall/syscall_linux_mipsx.go
 ===================================================================
 --- a/src/libgo/go/syscall/syscall_linux_mipsx.go	(.../tags/gcc_7_2_0_release)
@@ -318938,6 +319518,38 @@ Index: libgo/go/syscall/syscall_linux_mipsx.go
 +func PtraceSetRegs(pid int, regs *PtraceRegs) (err error) {
 +	return ptrace(PTRACE_SETREGS, pid, 0, uintptr(unsafe.Pointer(regs)))
 +}
+Index: libgo/go/syscall/syscall_linux_s390x.go
+===================================================================
+--- a/src/libgo/go/syscall/syscall_linux_s390x.go	(.../tags/gcc_7_2_0_release)
++++ b/src/libgo/go/syscall/syscall_linux_s390x.go	(.../branches/gcc-7-branch)
+@@ -8,9 +8,9 @@
+ 
+ import "unsafe"
+ 
+-func (r *PtraceRegs) PC() uint64 { return r.Psw.Addr }
++func (r *PtraceRegs) PC() uint64 { return r.Psw.addr }
+ 
+-func (r *PtraceRegs) SetPC(pc uint64) { r.Psw.Addr = pc }
++func (r *PtraceRegs) SetPC(pc uint64) { r.Psw.addr = pc }
+ 
+ const syscall_PTRACE_PEEKUSR_AREA = 0x5000
+ const syscall_PTRACE_POKEUSR_AREA = 0x5001
+Index: libgo/go/syscall/syscall_linux_s390.go
+===================================================================
+--- a/src/libgo/go/syscall/syscall_linux_s390.go	(.../tags/gcc_7_2_0_release)
++++ b/src/libgo/go/syscall/syscall_linux_s390.go	(.../branches/gcc-7-branch)
+@@ -8,9 +8,9 @@
+ 
+ import "unsafe"
+ 
+-func (r *PtraceRegs) PC() uint64 { return uint64(r.Psw.Addr) }
++func (r *PtraceRegs) PC() uint64 { return uint64(r.Psw.addr) }
+ 
+-func (r *PtraceRegs) SetPC(pc uint64) { r.Psw.Addr = uint32(pc) }
++func (r *PtraceRegs) SetPC(pc uint64) { r.Psw.addr = uint32(pc) }
+ 
+ const syscall_PTRACE_PEEKUSR_AREA = 0x5000
+ const syscall_PTRACE_POKEUSR_AREA = 0x5001
 Index: libgo/match.sh
 ===================================================================
 --- a/src/libgo/match.sh	(.../tags/gcc_7_2_0_release)

-- 
Alioth's /usr/local/bin/git-commit-notice on /srv/git.debian.org/git/reproducible/gcc-7.git



More information about the Reproducible-commits mailing list