
... 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.
137 lines
4.8 KiB
Fortran
137 lines
4.8 KiB
Fortran
! Test that optional arguments work in private clauses. The effect of
|
|
! non-present arguments in private clauses is undefined, and is not tested
|
|
! for. The tests are based on those in private-variables.f90.
|
|
|
|
! { dg-do run }
|
|
|
|
! { dg-additional-options "-fopt-info-note-omp" }
|
|
! { dg-additional-options "--param=openacc-privatization=noisy" }
|
|
! { dg-additional-options "-foffload=-fopt-info-note-omp" }
|
|
! { dg-additional-options "-foffload=--param=openacc-privatization=noisy" }
|
|
! for testing/documenting aspects of that functionality.
|
|
|
|
! { dg-additional-options "-Wopenacc-parallelism" } for testing/documenting
|
|
! aspects of that functionality.
|
|
|
|
|
|
program main
|
|
implicit none
|
|
|
|
type vec3
|
|
integer x, y, z, attr(13)
|
|
end type vec3
|
|
integer :: x
|
|
type(vec3) :: pt
|
|
integer :: arr(2)
|
|
|
|
call t1(x)
|
|
call t2(pt)
|
|
call t3(arr)
|
|
contains
|
|
|
|
! Test of gang-private variables declared on loop directive.
|
|
|
|
subroutine t1(x)
|
|
integer, optional :: x
|
|
integer :: i, arr(32)
|
|
|
|
do i = 1, 32
|
|
arr(i) = i
|
|
end do
|
|
|
|
!$acc parallel copy(arr) num_gangs(32) num_workers(8) vector_length(32)
|
|
! { dg-warning "region is worker partitioned but does not contain worker partitioned code" "" { target *-*-* } .-1 }
|
|
! { dg-warning "region is vector partitioned but does not contain vector partitioned code" "" { target *-*-* } .-2 }
|
|
!$acc loop gang private(x)
|
|
! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
! { dg-note {variable 'x' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
|
|
do i = 1, 32
|
|
x = i * 2;
|
|
arr(i) = arr(i) + x
|
|
end do
|
|
!$acc end parallel
|
|
|
|
do i = 1, 32
|
|
if (arr(i) .ne. i * 3) STOP 1
|
|
end do
|
|
end subroutine t1
|
|
|
|
|
|
! Test of gang-private addressable variable declared on loop directive, with
|
|
! broadcasting to partitioned workers.
|
|
|
|
subroutine t2(pt)
|
|
integer i, j, arr(0:32*32)
|
|
type(vec3), optional :: pt
|
|
|
|
do i = 0, 32*32-1
|
|
arr(i) = i
|
|
end do
|
|
|
|
!$acc parallel copy(arr) num_gangs(32) num_workers(8) vector_length(32)
|
|
! { dg-warning "region is worker partitioned but does not contain worker partitioned code" "" { target *-*-* } .-1 }
|
|
!$acc loop gang private(pt)
|
|
! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
! { dg-note {variable 'pt' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
|
|
do i = 0, 31
|
|
pt%x = i
|
|
pt%y = i * 2
|
|
pt%z = i * 4
|
|
pt%attr(5) = i * 6
|
|
|
|
!$acc loop vector
|
|
! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
do j = 0, 31
|
|
arr(i * 32 + j) = arr(i * 32 + j) + pt%x + pt%y + pt%z + pt%attr(5);
|
|
end do
|
|
end do
|
|
!$acc end parallel
|
|
|
|
do i = 0, 32 * 32 - 1
|
|
if (arr(i) .ne. i + (i / 32) * 13) STOP 2
|
|
end do
|
|
end subroutine t2
|
|
|
|
! Test of vector-private variables declared on loop directive. Array type.
|
|
|
|
subroutine t3(pt)
|
|
integer, optional :: pt(2)
|
|
integer :: i, j, k, idx, arr(0:32*32*32)
|
|
|
|
do i = 0, 32*32*32-1
|
|
arr(i) = i
|
|
end do
|
|
|
|
!$acc parallel copy(arr) num_gangs(32) num_workers(8) vector_length(32)
|
|
!$acc loop gang
|
|
! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
do i = 0, 31
|
|
!$acc loop worker
|
|
! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
do j = 0, 31
|
|
!$acc loop vector private(pt)
|
|
! { dg-note {variable 'k' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
! { dg-note {variable 'pt' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
|
|
do k = 0, 31
|
|
pt(1) = ieor(i, j * 3)
|
|
pt(2) = ior(i, j * 5)
|
|
arr(i * 1024 + j * 32 + k) = arr(i * 1024 + j * 32 + k) + pt(1) * k
|
|
arr(i * 1024 + j * 32 + k) = arr(i * 1024 + j * 32 + k) + pt(2) * k
|
|
end do
|
|
end do
|
|
end do
|
|
!$acc end parallel
|
|
|
|
do i = 0, 32 - 1
|
|
do j = 0, 32 -1
|
|
do k = 0, 32 - 1
|
|
idx = i * 1024 + j * 32 + k
|
|
if (arr(idx) .ne. idx + ieor(i, j * 3) * k + ior(i, j * 5) * k) then
|
|
STOP 3
|
|
end if
|
|
end do
|
|
end do
|
|
end do
|
|
end subroutine t3
|
|
|
|
end program main
|