Commit 51a025fb by Paul Thomas

2018-11-24 Paul Thomas <pault@gcc.gnu.org>

	PR fortran/888143
	* resolve.c (resolve_variable): Check for associate names with
	NULL target.

2018-11-24  Paul Thomas  <pault@gcc.gnu.org>

	PR fortran/888143
	* gfortran.dg/associate_46.f90: New test.

From-SVN: r266427
parent eabec4d3
2018-11-24 Paul Thomas <pault@gcc.gnu.org>
PR fortran/888143
* resolve.c (resolve_variable): Check for associate names with
NULL target.
2018-11-23 Jakub Jelinek <jakub@redhat.com>
* lang.opt (fpad-source): New option.
......
......@@ -5410,7 +5410,7 @@ resolve_variable (gfc_expr *e)
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>
PR fortran/888143
* gfortran.dg/associate_46.f90: New test.
2018-11-23 Jeff Law <law@redhat.com>
PR rtl-optimization/84768
......@@ -585,7 +590,7 @@
Likewise.
* gcc.target/s390/global-array-even-element.c: Likewise.
2018-11-14 Wilco Dijkstra <wdijkstr@arm.com>
2018-11-14 Wilco Dijkstra <wdijkstr@arm.com>
Jackson Woodruff <jackson.woodruff@arm.com>
PR 71026/tree-optimization
......@@ -600,7 +605,7 @@
PR rtl-optimization/87817
* gcc.target/i386/bmi2-bzhi-3.c (main): Add a couple of new tests.
2018-11-14 Wilco Dijkstra <wdijkstr@arm.com>
2018-11-14 Wilco Dijkstra <wdijkstr@arm.com>
* gcc.target/aarch64/pr62178.c: Relax scan-assembler checks.
......
! { 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
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment