6e4d01d61f
2019-12-06 Tobias Burnus <tobias@codesourcery.com> Kwok Cheung Yeung <kcy@codesourcery.com> gcc/fortran/ * trans-openmp.c (gfc_build_conditional_assign, gfc_build_conditional_assign_expr): New static functions. (gfc_omp_finish_clause, gfc_trans_omp_clauses): Handle mapping of absent optional arguments and fix mapping of present optional args. gcc/ * omp-low.c (lower_omp_target): For optional arguments, deref once more to obtain the type. libgomp/ * oacc-mem.c (update_dev_host, gomp_acc_insert_pointer): Just return if input it a NULL pointer. * testsuite/libgomp.oacc-c-c++-common/lib-43.c: Remove; dependent on diagnostic of NULL pointer. * testsuite/libgomp.oacc-c-c++-common/lib-47.c: Ditto. * testsuite/libgomp.fortran/optional-map.f90: New. * testsuite/libgomp.fortran/use_device_addr-1.f90 (test_dummy_opt_callee_1_absent): New. (test_dummy_opt_call_1): Call it. * testsuite/libgomp.fortran/use_device_addr-2.f90: Likewise. * testsuite/libgomp.fortran/use_device_addr-3.f90: Likewise. * testsuite/libgomp.fortran/use_device_addr-4.f90: Likewise. * testsuite/libgomp.oacc-fortran/optional-cache.f95: New. * testsuite/libgomp.oacc-fortran/optional-data-copyin-by-value.f90: New. * testsuite/libgomp.oacc-fortran/optional-data-copyin.f90: New. * testsuite/libgomp.oacc-fortran/optional-data-copyout.f90: New. * testsuite/libgomp.oacc-fortran/optional-data-enter-exit.f90: New. * testsuite/libgomp.oacc-fortran/optional-declare.f90: New. * testsuite/libgomp.oacc-fortran/optional-firstprivate.f90: New. * testsuite/libgomp.oacc-fortran/optional-host_data.f90: New. * testsuite/libgomp.oacc-fortran/optional-nested-calls.f90: New. * testsuite/libgomp.oacc-fortran/optional-private.f90: New. * testsuite/libgomp.oacc-fortran/optional-reduction.f90: New. * testsuite/libgomp.oacc-fortran/optional-update-device.f90: New. * testsuite/libgomp.oacc-fortran/optional-update-host.f90: New. Co-Authored-By: Kwok Cheung Yeung <kcy@codesourcery.com> From-SVN: r279043
40 lines
767 B
Fortran
40 lines
767 B
Fortran
! Test the host_data construct with optional arguments.
|
|
! Based on host_data-1.f90.
|
|
|
|
! { dg-do run }
|
|
! { dg-additional-options "-cpp" }
|
|
|
|
program test
|
|
implicit none
|
|
|
|
integer, target :: i
|
|
integer, pointer :: ip, iph
|
|
|
|
! Assign the same targets
|
|
ip => i
|
|
iph => i
|
|
|
|
call foo(iph)
|
|
call foo(iph, ip)
|
|
contains
|
|
subroutine foo(iph, ip)
|
|
integer, pointer :: iph
|
|
integer, pointer, optional :: ip
|
|
|
|
!$acc data copyin(i)
|
|
!$acc host_data use_device(ip)
|
|
|
|
! Test how the pointers compare inside a host_data construct
|
|
if (present(ip)) then
|
|
#if ACC_MEM_SHARED
|
|
if (.not. associated(ip, iph)) STOP 1
|
|
#else
|
|
if (associated(ip, iph)) STOP 2
|
|
#endif
|
|
end if
|
|
|
|
!$acc end host_data
|
|
!$acc end data
|
|
end subroutine foo
|
|
end program test
|