cd75853e1d
PR fortran/27916 * trans-openmp.c (gfc_omp_clause_default_ctor): New function. * trans.h (gfc_omp_clause_default_ctor): New prototype. * f95-lang.c (LANG_HOOKS_OMP_CLAUSE_DEFAULT_CTOR): Define. * testsuite/libgomp.fortran/pr27916-1.f90: New test. * testsuite/libgomp.fortran/pr27916-2.f90: New test. From-SVN: r114520
27 lines
626 B
Fortran
27 lines
626 B
Fortran
! PR fortran/27916
|
|
! Test whether allocatable privatized arrays has "not currently allocated"
|
|
! status at the start of OpenMP constructs.
|
|
! { dg-do run }
|
|
|
|
program pr27916
|
|
integer :: n, i
|
|
logical :: r
|
|
integer, dimension(:), allocatable :: a
|
|
|
|
r = .false.
|
|
!$omp parallel do num_threads (4) default (private) &
|
|
!$omp & reduction (.or.: r) schedule (static)
|
|
do n = 1, 16
|
|
r = r .or. allocated (a)
|
|
allocate (a (16))
|
|
r = r .or. .not. allocated (a)
|
|
do i = 1, 16
|
|
a (i) = i
|
|
end do
|
|
deallocate (a)
|
|
r = r .or. allocated (a)
|
|
end do
|
|
!$omp end parallel do
|
|
if (r) call abort
|
|
end program pr27916
|