gcc/libgomp/testsuite/libgomp.fortran/use_device_ptr-optional-1.f90
Tobias Burnus 01509e2f04 libgomp/testsuite – use 'stop' and 'dg-do run'
libgomp/
        * testsuite/libgomp.fortran/target-simd.f90: Use stop not abort.
        * testsuite/libgomp.fortran/use_device_ptr-optional-1.f90:
        Ditto; add 'dg-do run' for torture testing.
        * testsuite/libgomp.fortran/lastprivate1.f90:  Add 'dg-do run'.
        * testsuite/libgomp.fortran/lastprivate2.f90: Ditto.
        * testsuite/libgomp.fortran/nestedfn4.f90: Ditto.
        * testsuite/libgomp.fortran/pr25219.f90: Ditto.
        * testsuite/libgomp.fortran/pr28390.f: Ditto.
        * testsuite/libgomp.fortran/pr35130.f90: Ditto.
        * testsuite/libgomp.fortran/pr90779.f90: Ditto.
        * testsuite/libgomp.fortran/task2.f90: Ditto.
        * testsuite/libgomp.fortran/taskgroup1.f90: Ditto.
        * testsuite/libgomp.fortran/taskloop1.f90: Ditto.
        * testsuite/libgomp.fortran/use_device_addr-1.f90: Ditto.
        * testsuite/libgomp.fortran/use_device_addr-2.f90: Ditto.
        * testsuite/libgomp.fortran/workshare1.f90: Ditto.
        * testsuite/libgomp.fortran/workshare2.f90: Ditto.

From-SVN: r277606
2019-10-30 11:33:58 +01:00

38 lines
999 B
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)
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
end program test_it