
The ptx insn atom doesn't support local memory. In case of doing an atomic operation on local memory, we run into: ... operation not supported on global/shared address space ... This is the cuGetErrorString message for CUDA_ERROR_INVALID_ADDRESS_SPACE. The message is somewhat confusing given that actually the operation is not supported on local address space. Fix this by falling back on a non-atomic version when detecting a frame-related memory operand. This only solves some cases that are detected at compile-time. It does however fix the openacc private-atomic-* test-cases. Tested on x86_64 with nvptx accelerator. gcc/ChangeLog: 2022-01-27 Tom de Vries <tdevries@suse.de> * config/nvptx/nvptx.md (define_insn "atomic_compare_and_swap<mode>_1") (define_insn "atomic_exchange<mode>") (define_insn "atomic_fetch_add<mode>") (define_insn "atomic_fetch_addsf") (define_insn "atomic_fetch_<logic><mode>"): Output non-atomic version if memory operands is frame-relative. gcc/testsuite/ChangeLog: 2022-01-31 Tom de Vries <tdevries@suse.de> * gcc.target/nvptx/stack-atomics-run.c: New test. libgomp/ChangeLog: 2022-01-27 Tom de Vries <tdevries@suse.de> * testsuite/libgomp.oacc-c-c++-common/private-atomic-1.c: Remove PR83812 workaround. * testsuite/libgomp.oacc-fortran/private-atomic-1-vector.f90: Same. * testsuite/libgomp.oacc-fortran/private-atomic-1-worker.f90: Same.
35 lines
1.4 KiB
Fortran
35 lines
1.4 KiB
Fortran
! 'atomic' access of worker-private variable
|
|
|
|
! { 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.
|
|
|
|
|
|
program main
|
|
integer :: w, arr(0:31)
|
|
|
|
!$acc parallel num_gangs(32) num_workers(32) copyout(arr)
|
|
!$acc loop gang worker private(w)
|
|
! { dg-note {variable 'j' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
! { dg-note {variable 'w' in 'private' clause is candidate for adjusting OpenACC privatization level} "" { target *-*-* } .-2 }
|
|
! { dg-note {variable 'w' ought to be adjusted for OpenACC privatization level: 'worker'} "" { target *-*-* } .-3 }
|
|
! { dg-note {variable 'w' adjusted for OpenACC privatization level: 'worker'} "TODO" { target { ! openacc_host_selected } xfail *-*-* } .-4 }
|
|
do j = 0, 31
|
|
w = 0
|
|
!$acc loop seq
|
|
! { dg-note {variable 'i' in 'private' clause isn't candidate for adjusting OpenACC privatization level: not addressable} "" { target *-*-* } .-1 }
|
|
do i = 0, 31
|
|
!$acc atomic update
|
|
w = w + 1
|
|
!$acc end atomic
|
|
end do
|
|
arr(j) = w
|
|
end do
|
|
!$acc end parallel
|
|
|
|
if (any (arr .ne. 32)) stop 1
|
|
end program main
|