gcc/libgomp/testsuite/libgomp.oacc-fortran/routine-10.f90
Tobias Burnus 12df77ab6d OpenACC/Fortran: permit 'routine' inside PURE
gcc/fortran/ChangeLog

	* parse.c (decode_oacc_directive): Permit 'acc routine' also
	inside pure procedures.
	* openmp.c (gfc_match_oacc_routine): Inside pure procedures
	do not permit gang, worker or vector clauses.

libgomp/ChangeLog:

	* testsuite/libgomp.oacc-fortran/routine-10.f90: New test.

gcc/testsuite/ChangeLog:

	* gfortran.dg/goacc/pure-elemental-procedures-2.f90: New test.

Reviewed-by: Thomas Schwinge <thomas@codesourcery.com>
2020-06-16 20:23:58 +02:00

53 lines
1.0 KiB
Fortran

! { dg-do run }
!
module m
implicit none
contains
pure subroutine add_ps_routine(a, b, c)
implicit none
!$acc routine seq
integer, intent(in) :: a, b
integer, intent(out) :: c
integer, parameter :: n = 10
integer :: i
do i = 1, n
if (i .eq. 5) then
c = a + b
end if
end do
end subroutine add_ps_routine
elemental impure function add_ef(a, b) result(c)
implicit none
!$acc routine
integer, intent(in) :: a, b
integer :: c
call add_ps_routine(a, b, c)
end function add_ef
end module m
program main
use m
implicit none
integer, parameter :: n = 10
integer, dimension(n) :: a_a
integer, dimension(n) :: b_a
integer, dimension(n) :: c_a
integer :: i
a_a = [(3 * i, i = 1, n)]
b_a = [(-2 * i, i = 1, n)]
!$acc parallel copyin(a_a, b_a) copyout(c_a)
!$acc loop gang
do i = 1, n
if (i .eq. 4) then
c_a = add_ef(a_a, b_a)
end if
end do
!$acc end parallel
if (any (c_a /= [(i, i=1, 10)])) stop 1
!print *, a
end program main