aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/associate_16.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc-4.9/gcc/testsuite/gfortran.dg/associate_16.f90')
-rw-r--r--gcc-4.9/gcc/testsuite/gfortran.dg/associate_16.f9023
1 files changed, 23 insertions, 0 deletions
diff --git a/gcc-4.9/gcc/testsuite/gfortran.dg/associate_16.f90 b/gcc-4.9/gcc/testsuite/gfortran.dg/associate_16.f90
new file mode 100644
index 000000000..9129388b2
--- /dev/null
+++ b/gcc-4.9/gcc/testsuite/gfortran.dg/associate_16.f90
@@ -0,0 +1,23 @@
+! { dg-do compile }
+! PR 60834 - this used to ICE.
+
+module m
+ implicit none
+ type :: t
+ real :: diffusion=1.
+ end type
+contains
+ subroutine solve(this, x)
+ class(t), intent(in) :: this
+ real, intent(in) :: x(:)
+ integer :: i
+ integer, parameter :: n(1:5)=[(i,i=1, 5)]
+
+ associate( nu=>this%diffusion)
+ associate( exponential=>exp(-(x(i)-n) ))
+ do i = 1, size(x)
+ end do
+ end associate
+ end associate
+ end subroutine solve
+end module m