Retro68/gcc/libgomp/testsuite/libgomp.fortran/associate3.f90
2017-04-10 13:32:00 +02:00

21 lines
341 B
Fortran

! PR fortran/71717
! { dg-do run }
type t
real, allocatable :: f(:)
end type
type (t) :: v
integer :: i, j
allocate (v%f(4))
v%f = 19.
i = 5
associate (u => v, k => i)
!$omp parallel do
do j = 1, 4
u%f(j) = 21.
if (j.eq.1) k = 7
end do
end associate
if (any (v%f(:).ne.21.) .or. i.ne.7) call abort
end