
The clause makes any device code use the local memory address for each of the variables specified unless the given variable is already present on the current device. 2019-12-19 Julian Brown <julian@codesourcery.com> Maciej W. Rozycki <macro@codesourcery.com> Tobias Burnus <tobias@codesourcery.com> Thomas Schwinge <thomas@codesourcery.com> gcc/ * omp-low.c (lower_omp_target): Support GOMP_MAP_NO_ALLOC. * tree-pretty-print.c (dump_omp_clause): Likewise. gcc/c-family/ * c-pragma.h (pragma_omp_clause): Add PRAGMA_OACC_CLAUSE_NO_CREATE. gcc/c/ * c-parser.c (c_parser_omp_clause_name): Support no_create. (c_parser_oacc_data_clause): Likewise. (c_parser_oacc_all_clauses): Likewise. (OACC_DATA_CLAUSE_MASK, OACC_KERNELS_CLAUSE_MASK) (OACC_PARALLEL_CLAUSE_MASK, OACC_SERIAL_CLAUSE_MASK): Add PRAGMA_OACC_CLAUSE_NO_CREATE. * c-typeck.c (handle_omp_array_sections): Support GOMP_MAP_NO_ALLOC. gcc/cp/ * parser.c (cp_parser_omp_clause_name): Support no_create. (cp_parser_oacc_data_clause): Likewise. (cp_parser_oacc_all_clauses): Likewise. (OACC_DATA_CLAUSE_MASK, OACC_KERNELS_CLAUSE_MASK) (OACC_PARALLEL_CLAUSE_MASK): Add PRAGMA_OACC_CLAUSE_NO_CREATE. * semantics.c (handle_omp_array_sections): Support no_create. gcc/fortran/ * gfortran.h (gfc_omp_map_op): Add OMP_MAP_NO_ALLOC. * openmp.c (omp_mask2): Add OMP_CLAUSE_NO_CREATE. (gfc_match_omp_clauses): Support no_create. (OACC_PARALLEL_CLAUSES, OACC_KERNELS_CLAUSES) (OACC_DATA_CLAUSES): Add OMP_CLAUSE_NO_CREATE. * trans-openmp.c (gfc_trans_omp_clauses_1): Support OMP_MAP_NO_ALLOC. gcc/testsuite/ * gfortran.dg/goacc/common-block-1.f90: Add no_create-clause tests. * gfortran.dg/goacc/common-block-1.f90: Likewise. * gfortran.dg/goacc/data-clauses.f95: Likewise. * gfortran.dg/goacc/data-tree.f95: Likewise. * gfortran.dg/goacc/kernels-tree.f95: Likewise. * gfortran.dg/goacc/parallel-tree.f95: Likewise. include/ * gomp-constants.h (gomp_map_kind): Support GOMP_MAP_NO_ALLOC. libgomp/ * target.c (gomp_map_vars_async): Support GOMP_MAP_NO_ALLOC. * testsuite/libgomp.oacc-c-c++-common/no_create-1.c: New test. * testsuite/libgomp.oacc-c-c++-common/no_create-2.c: New test. * testsuite/libgomp.oacc-c-c++-common/no_create-3.c: New test. * testsuite/libgomp.oacc-c-c++-common/no_create-4.c: New test. * testsuite/libgomp.oacc-c-c++-common/no_create-5.c: New test. * testsuite/libgomp.oacc-fortran/no_create-1.f90: New test. * testsuite/libgomp.oacc-fortran/no_create-2.f90: New test. * testsuite/libgomp.oacc-fortran/no_create-3.F90: New test. Reviewed-by: Thomas Schwinge <thomas@codesourcery.com> Co-Authored-By: Maciej W. Rozycki <macro@codesourcery.com> Co-Authored-By: Thomas Schwinge <thomas@codesourcery.com> Co-Authored-By: Tobias Burnus <tobias@codesourcery.com> From-SVN: r279551
90 lines
1.9 KiB
Fortran
90 lines
1.9 KiB
Fortran
! { dg-do run }
|
|
|
|
! Test no_create clause with data/parallel constructs.
|
|
|
|
program no_create
|
|
use openacc
|
|
implicit none
|
|
logical :: shared_memory
|
|
integer, parameter :: n = 512
|
|
integer :: myvar, myarr(n)
|
|
integer i
|
|
|
|
shared_memory = .false.
|
|
!$acc kernels copyin (shared_memory)
|
|
shared_memory = .true.
|
|
!$acc end kernels
|
|
|
|
myvar = 55
|
|
do i = 1, n
|
|
myarr(i) = 0
|
|
end do
|
|
|
|
call do_on_target(myvar, n, myarr)
|
|
|
|
if (shared_memory) then
|
|
if (myvar .ne. 44) stop 10
|
|
else
|
|
if (myvar .ne. 33) stop 11
|
|
end if
|
|
do i = 1, n
|
|
if (shared_memory) then
|
|
if (myarr(i) .ne. i * 2) stop 20
|
|
else
|
|
if (myarr(i) .ne. i) stop 21
|
|
end if
|
|
end do
|
|
|
|
myvar = 55
|
|
do i = 1, n
|
|
myarr(i) = 0
|
|
end do
|
|
|
|
!$acc enter data copyin(myvar, myarr)
|
|
call do_on_target(myvar, n, myarr)
|
|
!$acc exit data copyout(myvar, myarr)
|
|
|
|
if (myvar .ne. 44) stop 30
|
|
do i = 1, n
|
|
if (myarr(i) .ne. i * 2) stop 31
|
|
end do
|
|
end program no_create
|
|
|
|
subroutine do_on_target (var, n, arr)
|
|
use openacc
|
|
implicit none
|
|
integer :: var, n, arr(n)
|
|
integer :: i
|
|
|
|
!$acc data no_create (var, arr)
|
|
|
|
if (acc_is_present(var)) then
|
|
! The no_create clause is meant for partially shared-memory machines. This
|
|
! test is written to work on non-shared-memory machines, though this is not
|
|
! necessarily a useful way to use the no_create clause in practice.
|
|
|
|
!$acc parallel !no_create (var)
|
|
var = 44
|
|
!$acc end parallel
|
|
else
|
|
var = 33
|
|
end if
|
|
if (acc_is_present(arr)) then
|
|
! The no_create clause is meant for partially shared-memory machines. This
|
|
! test is written to work on non-shared-memory machines, though this is not
|
|
! necessarily a useful way to use the no_create clause in practice.
|
|
|
|
!$acc parallel loop !no_create (arr)
|
|
do i = 1, n
|
|
arr(i) = i * 2
|
|
end do
|
|
!$acc end parallel loop
|
|
else
|
|
do i = 1, n
|
|
arr(i) = i
|
|
end do
|
|
end if
|
|
|
|
!$acc end data
|
|
|
|
end subroutine do_on_target
|