gcc/libgomp/testsuite/libgomp.fortran/crayptr2.f90
Jakub Jelinek cab37c89d1 re PR libgomp/59467 (copyprivate in the fortran testsuite)
PR libgomp/59467
	* gimplify.c (omp_check_private): Add copyprivate argument, if it
	is true, don't check omp_privatize_by_reference.
	(gimplify_scan_omp_clauses): For OMP_CLAUSE_COPYPRIVATE verify
	decl is private in outer context.  Adjust omp_check_private caller.

	* gfortran.dg/gomp/pr59467.f90: New test.
	* c-c++-common/gomp/pr59467.c: New test.

	* testsuite/libgomp.fortran/crayptr2.f90: Add private (d) clause to
	!$omp parallel.

From-SVN: r205922
2013-12-12 09:52:06 +01:00

32 lines
657 B
Fortran

! { dg-do run }
! { dg-options "-fopenmp -fcray-pointer" }
! { dg-require-effective-target tls_runtime }
use omp_lib
integer :: a, b, c, d, p
logical :: l
pointer (ip, p)
save ip
!$omp threadprivate (ip)
a = 1
b = 2
c = 3
l = .false.
!$omp parallel num_threads (3) reduction (.or.:l) private (d)
if (omp_get_thread_num () .eq. 0) then
ip = loc (a)
elseif (omp_get_thread_num () .eq. 1) then
ip = loc (b)
else
ip = loc (c)
end if
l = p .ne. omp_get_thread_num () + 1
!$omp single
d = omp_get_thread_num ()
!$omp end single copyprivate (d, ip)
l = l .or. (p .ne. d + 1)
!$omp end parallel
if (l) call abort
end