gcc/libgomp/testsuite/libgomp.oacc-fortran/optional-nested-calls.f90
Tobias Burnus 6e4d01d61f [OpenMP/OpenACC/Fortran] Fix mapping of optional (present|absent) arguments
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
2019-12-06 14:06:53 +01:00

136 lines
3.1 KiB
Fortran

! Test propagation of optional arguments from within an OpenACC parallel region.
! { dg-do run }
program test
implicit none
integer, parameter :: n = 64
integer :: i
integer :: res_int
integer :: a_arr(n), b_arr(n), res_arr(n)
integer, allocatable :: a_alloc(:), b_alloc(:), res_alloc(:)
call test_int_caller(res_int, 5)
if (res_int .ne. 10) stop 1
call test_int_caller(res_int, 2, 3)
if (res_int .ne. 11) stop 2
do i = 1, n
a_arr(i) = i
b_arr(i) = n - i + 1
end do
call test_array_caller(res_arr, a_arr)
do i = 1, n
if (res_arr(i) .ne. 2 * a_arr(i)) stop 3
end do
call test_array_caller(res_arr, a_arr, b_arr)
do i = 1, n
if (res_arr(i) .ne. a_arr(i) * b_arr(i) + a_arr(i) + b_arr(i)) stop 4
end do
allocate(a_alloc(n))
allocate(b_alloc(n))
allocate(res_alloc(n))
do i = 1, n
a_alloc(i) = i
b_alloc(i) = n - i + 1
end do
call test_array_caller(res_arr, a_arr)
do i = 1, n
if (res_arr(i) .ne. 2 * a_alloc(i)) stop 5
end do
call test_array_caller(res_arr, a_arr, b_arr)
do i = 1, n
if (res_arr(i) .ne. a_arr(i) * b_alloc(i) + a_alloc(i) + b_alloc(i)) stop 6
end do
deallocate(a_alloc)
deallocate(b_alloc)
deallocate(res_alloc)
contains
subroutine test_int_caller(res, a, b)
integer :: res, a
integer, optional :: b
!$acc data copyin(a, b) copyout (res)
!$acc parallel
res = a
if (present(b)) res = res * b
call test_int_callee(res, a, b)
!$acc end parallel
!$acc end data
end subroutine test_int_caller
subroutine test_int_callee(res, a, b)
!$acc routine seq
integer :: res, a
integer, optional :: b
res = res + a
if (present(b)) res = res + b
end subroutine test_int_callee
subroutine test_array_caller(res, a, b)
integer :: res(n), a(n), i
integer, optional :: b(n)
!$acc data copyin(a, b) copyout(res)
!$acc parallel
!$acc loop seq
do i = 1, n
res(i) = a(i)
if (present(b)) res(i) = res(i) * b(i)
end do
call test_array_callee(res, a, b)
!$acc end parallel
!$acc end data
end subroutine test_array_caller
subroutine test_array_callee(res, a, b)
!$acc routine seq
integer :: res(n), a(n), i
integer, optional :: b(n)
do i = 1, n
res(i) = res(i) + a(i)
if (present(b)) res(i) = res(i) + b(i)
end do
end subroutine test_array_callee
subroutine test_allocatable_caller(res, a, b)
integer :: i
integer, allocatable :: res(:), a(:)
integer, allocatable, optional :: b(:)
!$acc data copyin(a, b) copyout(res)
!$acc parallel
!$acc loop seq
do i = 1, n
res(i) = a(i)
if (present(b)) res(i) = res(i) * b(i)
end do
call test_array_callee(res, a, b)
!$acc end parallel
!$acc end data
end subroutine test_allocatable_caller
subroutine test_allocatable_callee(res, a, b)
!$acc routine seq
integer :: i
integer, allocatable :: res(:), a(:)
integer, allocatable, optional :: b(:)
do i = 1, n
res(i) = res(i) + a(i)
if (present(b)) res(i) = res(i) + b(i)
end do
end subroutine test_allocatable_callee
end program test