gcc/libgomp/testsuite/libgomp.oacc-fortran/declare-1.f90
Julian Brown 11e811d8e2 OpenACC: Don't gang-privatize artificial variables [PR90115]
This patch prevents compiler-generated artificial variables from being
treated as privatization candidates for OpenACC.

The rationale is that e.g. "gang-private" variables actually must be
shared by each worker and vector spawned within a particular gang, but
that sharing is not necessary for any compiler-generated variable (at
least at present, but no such need is anticipated either).  Variables on
the stack (and machine registers) are already private per-"thread"
(gang, worker and/or vector), and that's fine for artificial variables.

We're restricting this to blocks, as we still need to understand what it
means for a 'DECL_ARTIFICIAL' to appear in a 'private' clause.

Several tests need their scan output patterns adjusted to compensate.

2022-10-14  Julian Brown  <julian@codesourcery.com>

	PR middle-end/90115
gcc/
	* omp-low.cc (oacc_privatization_candidate_p): Artificial vars are not
	privatization candidates.

libgomp/
	* testsuite/libgomp.oacc-fortran/declare-1.f90: Adjust scan output.
	* testsuite/libgomp.oacc-fortran/host_data-5.F90: Likewise.
	* testsuite/libgomp.oacc-fortran/if-1.f90: Likewise.
	* testsuite/libgomp.oacc-fortran/print-1.f90: Likewise.
	* testsuite/libgomp.oacc-fortran/privatized-ref-2.f90: Likewise.

Co-authored-by: Thomas Schwinge <thomas@codesourcery.com>
2022-10-28 10:17:34 +02:00

250 lines
5.9 KiB
Fortran

! { dg-do run }
! { dg-skip-if "" { *-*-* } { "-DACC_MEM_SHARED=1" } }
! { dg-additional-options "-fopt-info-all-omp" }
! { dg-additional-options "--param=openacc-privatization=noisy" }
! { dg-additional-options "-foffload=-fopt-info-all-omp" }
! { dg-additional-options "-foffload=--param=openacc-privatization=noisy" }
! for testing/documenting aspects of that functionality.
! Tests to exercise the declare directive along with
! the clauses: copy
! copyin
! copyout
! create
! present
! present_or_copy
! present_or_copyin
! present_or_copyout
! present_or_create
module vars
implicit none
integer z
!$acc declare create (z)
end module vars
subroutine subr5 (a, b, c, d)
implicit none
integer, parameter :: N = 8
integer :: i
integer :: a(N)
!$acc declare present_or_copyin (a)
integer :: b(N)
!$acc declare present_or_create (b)
integer :: c(N)
!$acc declare present_or_copyout (c)
integer :: d(N)
!$acc declare present_or_copy (d)
i = 0
!$acc parallel
! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
do i = 1, N
b(i) = a(i)
c(i) = b(i)
d(i) = d(i) + b(i)
end do
!$acc end parallel
end subroutine
subroutine subr4 (a, b)
implicit none
integer, parameter :: N = 8
integer :: i
integer :: a(N)
!$acc declare present (a)
integer :: b(N)
!$acc declare copyout (b)
i = 0
!$acc parallel
! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
do i = 1, N
b(i) = a(i)
end do
!$acc end parallel
end subroutine
subroutine subr3 (a, c)
implicit none
integer, parameter :: N = 8
integer :: i
integer :: a(N)
!$acc declare present (a)
integer :: c(N)
!$acc declare copyin (c)
i = 0
!$acc parallel
! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
do i = 1, N
a(i) = c(i)
c(i) = 0
end do
!$acc end parallel
end subroutine
subroutine subr2 (a, b, c)
implicit none
integer, parameter :: N = 8
integer :: i
integer :: a(N)
!$acc declare present (a)
integer :: b(N)
!$acc declare create (b)
integer :: c(N)
!$acc declare copy (c)
i = 0
!$acc parallel
! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
do i = 1, N
b(i) = a(i)
c(i) = b(i) + c(i) + 1
end do
!$acc end parallel
end subroutine
subroutine subr1 (a)
implicit none
integer, parameter :: N = 8
integer :: i
integer :: a(N)
!$acc declare present (a)
i = 0
!$acc parallel
! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
do i = 1, N
a(i) = a(i) + 1
end do
!$acc end parallel
end subroutine
subroutine test (a, e)
use openacc
implicit none
logical :: e
integer, parameter :: N = 8
integer :: a(N)
if (acc_is_present (a) .neqv. e) STOP 1
end subroutine
subroutine subr0 (a, b, c, d)
! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } .-1 }
! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
! { dg-note {variable 'a\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-3 }
implicit none
integer, parameter :: N = 8
integer :: a(N)
!$acc declare copy (a)
integer :: b(N)
integer :: c(N)
integer :: d(N)
integer :: i
call test (a, .true.)
call test (b, .false.)
call test (c, .false.)
call subr1 (a)
call test (a, .true.)
call test (b, .false.)
call test (c, .false.)
call subr2 (a, b, c)
call test (a, .true.)
call test (b, .false.)
call test (c, .false.)
do i = 1, N
if (c(i) .ne. 8) STOP 2
end do
call subr3 (a, c)
call test (a, .true.)
call test (b, .false.)
call test (c, .false.)
do i = 1, N
if (a(i) .ne. 2) STOP 3
if (c(i) .ne. 8) STOP 4
end do
call subr4 (a, b)
call test (a, .true.)
call test (b, .false.)
call test (c, .false.)
do i = 1, N
if (b(i) .ne. 8) STOP 5
end do
call subr5 (a, b, c, d)
call test (a, .true.)
call test (b, .false.)
call test (c, .false.)
call test (d, .false.)
do i = 1, N
if (c(i) .ne. 8) STOP 6
if (d(i) .ne. 13) STOP 7
end do
end subroutine
program main
! { dg-note {variable 'C\.[0-9]+' declared in block potentially has improper OpenACC privatization level: 'const_decl'} "TODO" { target *-*-* } .-1 }
! { dg-note {variable 'D\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-2 }
! { dg-note {variable 'S\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-3 }
! { dg-note {variable 'desc\.[0-9]+' declared in block isn't candidate for adjusting OpenACC privatization level: artificial} "" { target *-*-* } .-4 }
use vars
use openacc
implicit none
integer, parameter :: N = 8
integer :: a(N)
integer :: b(N)
integer :: c(N)
integer :: d(N)
integer :: i
a(:) = 2
b(:) = 3
c(:) = 4
d(:) = 5
if (acc_is_present (z) .neqv. .true.) STOP 8
call subr0 (a, b, c, d)
call test (a, .false.)
call test (b, .false.)
call test (c, .false.)
call test (d, .false.)
do i = 1, N
if (a(i) .ne. 8) STOP 9
if (b(i) .ne. 8) STOP 10
if (c(i) .ne. 8) STOP 11
if (d(i) .ne. 13) STOP 12
end do
end program