2018-06-09 Steven G. Kargl <kargl@gcc.gnu.org>
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / pr27916-2.f90
blob7973726cb5793a6d4cb63c0f151c6fbc7d740a86
1 ! PR fortran/27916
2 ! Test whether allocatable privatized arrays has "not currently allocated"
3 ! status at the start of OpenMP constructs.
4 ! { dg-do run }
6 program pr27916
7 integer :: n, i
8 logical :: r
9 integer, dimension(:), allocatable :: a
11 r = .false.
12 !$omp parallel do num_threads (4) default (private) &
13 !$omp & reduction (.or.: r) schedule (static)
14 do n = 1, 16
15 r = r .or. allocated (a)
16 allocate (a (16))
17 r = r .or. .not. allocated (a)
18 do i = 1, 16
19 a (i) = i
20 end do
21 deallocate (a)
22 r = r .or. allocated (a)
23 end do
24 !$omp end parallel do
25 if (r) STOP 1
26 end program pr27916