1! { dg-do compile }
2! PR 60834 - this used to ICE.
3
4module m
5  implicit none
6  type :: t
7    real :: diffusion=1.
8  end type
9contains
10  subroutine solve(this, x)
11    class(t), intent(in) :: this
12    real, intent(in) :: x(:)
13    integer :: i
14    integer, parameter :: n(1:5)=[(i,i=1, 5)]
15
16    associate( nu=>this%diffusion)
17      associate( exponential=>exp(-(x(i)-n) ))
18        do i = 1, size(x)
19        end do
20      end associate
21    end associate
22  end subroutine solve
23end module m
24