gcc/libgomp/testsuite/libgomp.fortran/crayptr2.f90
Jack Howarth ae8d887945 re PR target/32765 (Testsuite failures due to undefined symbol ___emutls_get_address)
2007-12-17  Jack Howarth  <howarth@bromo.med.uc.edu>

	PR target/32765
	* testsuite/libgomp.fortran/crayptr2.f90: Move dg-options for darwin.

From-SVN: r131012
2007-12-17 19:30:08 +00:00

32 lines
680 B
Fortran

! { dg-do run }
! { dg-options "-fopenmp -fcray-pointer" }
! { dg-options "-fopenmp -fcray-pointer -static-libgcc" { target *-*-darwin* } }
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)
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