c26dffff5c
PR fortran/49792 * trans-expr.c (gfc_trans_assignment_1): Set OMPWS_SCALARIZER_WS bit in ompws_flags only if loop.temp_ss is NULL, and clear it if lhs needs reallocation. * trans-openmp.c (gfc_trans_omp_workshare): Don't return early if code is NULL, emit a barrier if workshare emitted no code at all and NOWAIT clause isn't present. * testsuite/libgomp.fortran/pr49792-1.f90: New test. * testsuite/libgomp.fortran/pr49792-2.f90: New test. From-SVN: r177898
23 lines
471 B
Fortran
23 lines
471 B
Fortran
! PR fortran/49792
|
|
! { dg-do run }
|
|
! { dg-options "-std=f2003 -fall-intrinsics" }
|
|
|
|
subroutine reverse(n, a)
|
|
integer :: n
|
|
real(kind=8) :: a(n)
|
|
!$omp parallel workshare
|
|
a(:) = a(n:1:-1)
|
|
!$omp end parallel workshare
|
|
end subroutine reverse
|
|
|
|
program pr49792
|
|
integer :: b(16)
|
|
integer, allocatable :: a(:)
|
|
b = 1
|
|
!$omp parallel workshare
|
|
a = b
|
|
!$omp end parallel workshare
|
|
if (size(a).ne.size(b)) call abort()
|
|
if (any (a.ne.b)) call abort()
|
|
end program pr49792
|