+2018-11-24 Paul Thomas <pault@gcc.gnu.org>
+
+ Backport from mainline
+ PR fortran/88143
+ * resolve.c (resolve_variable): Check for associate names with
+ NULL target.
+
2019-11-03 Tobias Burnus <burnus@net-b.de>
Thomas Koenig <tkoenig@gcc.gnu.org>
the ts' type of the component refs is still array valued, which
can't be translated that way. */
if (sym->assoc && e->rank == 0 && e->ref && sym->ts.type == BT_CLASS
- && sym->assoc->target->ts.type == BT_CLASS
+ && sym->assoc->target && sym->assoc->target->ts.type == BT_CLASS
&& CLASS_DATA (sym->assoc->target)->as)
{
gfc_ref *ref = e->ref;
+2018-11-24 Paul Thomas <pault@gcc.gnu.org>
+
+ Backport from mainline
+ PR fortran/88143
+ * gfortran.dg/associate_46.f90: New test.
+
2018-11-22 Eric Botcazou <ebotcazou@adacore.com>
Backport from mainline
--- /dev/null
+! { dg-do run }
+!
+! Check the fix for PR88143, in which the associate name caused
+! a segfault in resolve.c. Make sure that the associate construct
+! does its job correctly, as well as compiles.
+!
+! Contributed by Andrew Wood <andrew@fluidgravity.co.uk>
+!
+MODULE m
+ IMPLICIT NONE
+ TYPE t
+ INTEGER, DIMENSION(:), ALLOCATABLE :: i
+ END TYPE
+ CONTAINS
+ SUBROUTINE s(x, idx1, idx2, k)
+ CLASS(*), DIMENSION(:), INTENT(IN), OPTIONAL :: x
+ INTEGER :: idx1, idx2, k
+ SELECT TYPE ( x )
+ CLASS IS ( t )
+ ASSOCIATE ( j => x(idx1)%i )
+ k = j(idx2)
+ END ASSOCIATE
+ END SELECT
+ END
+END
+
+ use m
+ class (t), allocatable :: c(:)
+ integer :: k
+ allocate (c(2))
+ allocate (c(1)%i, source = [3,2,1])
+ allocate (c(2)%i, source = [6,5,4])
+ call s(c, 1, 3, k)
+ if (k .ne. 1) stop 1
+ call s(c, 2, 1, k)
+ if (k .ne. 6) stop 2
+end