gcc/libgomp/testsuite/libgomp.oacc-fortran/privatized-ref-1.f95
Thomas Schwinge 7a5e036b61 [OpenACC privatization] Analyze 'lookup_decl'-translated DECL [PR90115, PR102330, PR104774]
... so that it matches what we analyze and what we action on.
Fix-up for commit 29a2f51806 "openacc:
Add support for gang local storage allocation in shared memory [PR90115]".

	PR middle-end/90115
	PR middle-end/102330
	PR middle-end/104774
	gcc/
	* omp-low.cc (oacc_privatization_candidate_p)
	(oacc_privatization_scan_clause_chain)
	(oacc_privatization_scan_decl_chain, lower_oacc_private_marker):
	Analyze 'lookup_decl'-translated DECL.
	gcc/testsuite/
	* c-c++-common/goacc/kernels-decompose-pr104061-1-3.c: Adjust.
	* c-c++-common/goacc/kernels-decompose-pr104061-1-4.c: Likewise.
	* c-c++-common/goacc/kernels-decompose-pr104132-1.c: Likewise.
	* c-c++-common/goacc/kernels-decompose-pr104133-1.c: Likewise.
	* c-c++-common/goacc/kernels-decompose-pr104774-1.c: Likewise.
	* c-c++-common/goacc/privatization-1-compute-loop.c: Likewise.
	* c-c++-common/goacc/privatization-1-compute.c: Likewise.
	* c-c++-common/goacc/privatization-1-routine_gang-loop.c:
	Likewise.
	* c-c++-common/goacc/privatization-1-routine_gang.c: Likewise.
	* gfortran.dg/goacc-gomp/pr102330-1.f90: Likewise, and subsume...
	* gfortran.dg/goacc-gomp/pr102330-2.f90: ... this file, and...
	* gfortran.dg/goacc-gomp/pr102330-3.f90: ... this file.
	* gfortran.dg/goacc/privatization-1-compute-loop.f90: Adjust.
	* gfortran.dg/goacc/privatization-1-compute.f90: Likewise.
	* gfortran.dg/goacc/privatization-1-routine_gang-loop.f90:
	Likewise.
	* gfortran.dg/goacc/privatization-1-routine_gang.f90: Likewise.
	libgomp/
	* testsuite/libgomp.oacc-c-c++-common/kernels-decompose-1.c:
	Enhance.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-local-worker-1.c:
	Adjust.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-local-worker-2.c:
	Likewise.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-local-worker-3.c:
	Likewise.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-local-worker-4.c:
	Likewise.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-local-worker-5.c:
	Likewise.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-loop-vector-1.c:
	Likewise.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-loop-vector-2.c:
	Likewise.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-loop-worker-2.c:
	Likewise.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-loop-worker-3.c:
	Likewise.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-loop-worker-4.c:
	Likewise.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-loop-worker-5.c:
	Likewise.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-loop-worker-6.c:
	Likewise.
	* testsuite/libgomp.oacc-c-c++-common/kernels-private-vars-loop-worker-7.c:
	Likewise.
	* testsuite/libgomp.oacc-fortran/optional-private.f90: Likewise.
	* testsuite/libgomp.oacc-fortran/privatized-ref-1.f95: Likewise.
	* testsuite/libgomp.oacc-fortran/privatized-ref-2.f90: Likewise.
2022-03-10 12:06:28 +01:00

163 lines
5.5 KiB
Fortran

! { dg-do run }
! { dg-additional-options "-fopt-info-note-omp" }
! { dg-additional-options "-foffload=-fopt-info-note-omp" }
! { dg-additional-options "--param=openacc-privatization=noisy" }
! { dg-additional-options "-foffload=--param=openacc-privatization=noisy" }
! { dg-additional-options "-Wuninitialized" }
!TODO
! { dg-xfail-run-if TODO { openacc_radeon_accel_selected && { ! __OPTIMIZE__ } } }
! It's only with Tcl 8.5 (released in 2007) that "the variable 'varName'
! passed to 'incr' may be unset, and in that case, it will be set to [...]",
! so to maintain compatibility with earlier Tcl releases, we manually
! initialize counter variables:
! { dg-line l_dummy[variable c_loop 0] }
! { dg-message "dummy" "" { target iN-VAl-Id } l_dummy } to avoid
! "WARNING: dg-line var l_dummy defined, but not used". */
program main
implicit none
integer :: myint
integer :: i
real :: res(65536), tmp
res(:) = 0.0
myint = 3
call gangs(myint, res)
do i=1,65536
tmp = i * 97
if (res(i) .ne. tmp) stop 1
end do
res(:) = 0.0
myint = 5
call workers(myint, res)
do i=1,65536
tmp = i * 99
if (res(i) .ne. tmp) stop 2
end do
res(:) = 0.0
myint = 7
call vectors(myint, res)
do i=1,65536
tmp = i * 101
if (res(i) .ne. tmp) stop 3
end do
res(:) = 0.0
myint = 9
call gangs_workers_vectors(myint, res)
do i=1,65536
tmp = i * 103
if (res(i) .ne. tmp) stop 4
end do
contains
subroutine gangs(t1, res)
implicit none
integer :: t1
integer :: i, j
real, intent(out) :: res(:)
!$acc parallel copyout(res) num_gangs(64)
!$acc loop collapse(2) gang private(t1) ! { dg-line l_loop[incr c_loop] }
! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
! { dg-note {variable 't1' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
do i=0,255
do j=1,256
t1 = (i * 256 + j) * 97
res(i * 256 + j) = t1
end do
end do
!$acc end parallel
end subroutine gangs
subroutine workers(t1, res)
implicit none
integer :: t1
integer :: i, j
real, intent(out) :: res(:)
!$acc parallel copyout(res) num_gangs(64) num_workers(64)
! { dg-warning "using .num_workers \\(32\\)., ignoring 64" "" { target openacc_nvidia_accel_selected } .-1 }
!$acc loop gang ! { dg-line l_loop[incr c_loop] }
! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
do i=0,255
!$acc loop worker private(t1) ! { dg-line l_loop[incr c_loop] }
! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
! { dg-note {variable 't1' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
do j=1,256
t1 = (i * 256 + j) * 99
res(i * 256 + j) = t1
end do
end do
!$acc end parallel
end subroutine workers
subroutine vectors(t1, res)
implicit none
integer :: t1
integer :: i, j
real, intent(out) :: res(:)
!$acc parallel copyout(res) num_gangs(64) num_workers(64)
! { dg-warning "using .num_workers \\(32\\)., ignoring 64" "" { target openacc_nvidia_accel_selected } .-1 }
!$acc loop gang worker ! { dg-line l_loop[incr c_loop] }
! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
do i=0,255
!$acc loop vector private(t1) ! { dg-line l_loop[incr c_loop] }
! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
! { dg-note {variable 't1' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
do j=1,256
t1 = (i * 256 + j) * 101
res(i * 256 + j) = t1
end do
end do
!$acc end parallel
end subroutine vectors
subroutine gangs_workers_vectors(t1, res)
implicit none
integer :: t1
integer :: i, j
real, intent(out) :: res(:)
!$acc parallel copyout(res) num_gangs(64) num_workers(64)
! { dg-warning "using .num_workers \\(32\\)., ignoring 64" "" { target openacc_nvidia_accel_selected } .-1 }
!$acc loop collapse(2) gang worker vector private(t1) ! { dg-line l_loop[incr c_loop] }
! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
! { dg-note {variable 't1' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } l_loop$c_loop }
do i=0,255
do j=1,256
t1 = (i * 256 + j) * 103
res(i * 256 + j) = t1
end do
end do
!$acc end parallel
end subroutine gangs_workers_vectors
end program main