3f9e8f13a3
PR fortran/63938 * trans-openmp.c (gfc_trans_omp_atomic): Make sure lhsaddr is simple enough for goa_lhs_expr_p. * libgomp.fortran/pr63938-1.f90: New test. * libgomp.fortran/pr63938-2.f90: New test. From-SVN: r218031
19 lines
286 B
Fortran
19 lines
286 B
Fortran
! PR fortran/63938
|
|
! { dg-do run }
|
|
|
|
program pr63938_2
|
|
type t
|
|
integer :: x
|
|
end type
|
|
integer :: i
|
|
type(t) :: x
|
|
x%x = 0
|
|
!$omp parallel do
|
|
do i = 1, 1000
|
|
!$omp atomic
|
|
x%x = x%x + 1
|
|
end do
|
|
!$omp end parallel do
|
|
if (x%x .ne. 1000) call abort
|
|
end program pr63938_2
|