a2c26c5031
2019-11-11 Tobias Burnus <tobias@codesourcery.com> Kwok Cheung Yeung <kcy@codesourcery.com> gcc/ * langhooks-def.h (LANG_HOOKS_OMP_CHECK_OPTIONAL_ARGUMENT): Renamed from LANG_HOOKS_OMP_IS_OPTIONAL_ARGUMENT; update define. (LANG_HOOKS_DECLS): Rename also here. * langhooks.h (lang_hooks_for_decls): Rename omp_is_optional_argument to omp_check_optional_argument; take additional bool argument. * omp-general.h (omp_check_optional_argument): Likewise. * omp-general.h (omp_check_optional_argument): Likewise. * omp-low.c (lower_omp_target): Update calls; handle absent Fortran optional arguments with USE_DEVICE_ADDR/USE_DEVICE_PTR. gcc/fortran/ * trans-expr.c (gfc_conv_expr_present): Check for DECL_ARTIFICIAL for the VALUE hidden argument avoiding -fallow-underscore issues. * trans-decl.c (create_function_arglist): Also set GFC_DECL_OPTIONAL_ARGUMENT for per-value arguments. * f95-lang.c (LANG_HOOKS_OMP_CHECK_OPTIONAL_ARGUMENT): Renamed from LANG_HOOKS_OMP_IS_OPTIONAL_ARGUMENT; point to gfc_omp_check_optional_argument. * trans.h (gfc_omp_check_optional_argument): Subsitutes gfc_omp_is_optional_argument declaration. * trans-openmp.c (gfc_omp_is_optional_argument): Make static. (gfc_omp_check_optional_argument): New function. libgomp/ * testsuite/libgomp.fortran/use_device_ptr-optional-1.f90: Extend. * testsuite/libgomp.fortran/use_device_ptr-optional-2.f90: New. Co-Authored-By: Kwok Cheung Yeung <kcy@codesourcery.com> From-SVN: r278046
60 lines
1.5 KiB
Fortran
60 lines
1.5 KiB
Fortran
! { dg-do run }
|
|
! Test whether use_device_ptr properly handles OPTIONAL arguments
|
|
! (Only case of present arguments is tested)
|
|
program test_it
|
|
implicit none
|
|
integer, target :: ixx
|
|
integer, pointer :: ptr_i, ptr_null
|
|
|
|
ptr_i => ixx
|
|
call foo(ptr_i)
|
|
|
|
ptr_null => null()
|
|
call bar(ptr_null)
|
|
|
|
call foo_absent()
|
|
call bar_absent()
|
|
contains
|
|
subroutine foo(ii)
|
|
integer, pointer, optional :: ii
|
|
|
|
if (.not.present(ii)) stop 1
|
|
if (.not.associated(ii, ixx)) stop 2
|
|
!$omp target data map(to:ixx) use_device_ptr(ii)
|
|
if (.not.present(ii)) stop 3
|
|
if (.not.associated(ii)) stop 4
|
|
!$omp end target data
|
|
end subroutine foo
|
|
|
|
! For bar, it is assumed that a NULL ptr on the host maps to NULL on the device
|
|
subroutine bar(jj)
|
|
integer, pointer, optional :: jj
|
|
|
|
if (.not.present(jj)) stop 5
|
|
if (associated(jj)) stop 6
|
|
!$omp target data map(to:ixx) use_device_ptr(jj)
|
|
if (.not.present(jj)) stop 7
|
|
if (associated(jj)) stop 8
|
|
!$omp end target data
|
|
end subroutine bar
|
|
|
|
subroutine foo_absent(ii)
|
|
integer, pointer, optional :: ii
|
|
|
|
if (present(ii)) STOP 31
|
|
!$omp target data map(to:ixx) use_device_ptr(ii)
|
|
if (present(ii)) STOP 32
|
|
!$omp end target data
|
|
end subroutine foo_absent
|
|
|
|
! For bar, it is assumed that a NULL ptr on the host maps to NULL on the device
|
|
subroutine bar_absent(jj)
|
|
integer, pointer, optional :: jj
|
|
|
|
if (present(jj)) STOP 41
|
|
!$omp target data map(to:ixx) use_device_ptr(jj)
|
|
if (present(jj)) STOP 42
|
|
!$omp end target data
|
|
end subroutine bar_absent
|
|
end program test_it
|