db941d7ef7
gcc/ * tree-nested.c (convert_nonlocal_omp_clauses): Add support for OMP_CLAUSE_{NUM_GANGS,NUM_VECTORS,VECTOR_LENGTH,SEQ}. (convert_local_omp_clauses): Likewise. gcc/fortran/ * f95-lang.c (gfc_attribute_table): Add an "oacc function" attribute. * gfortran.h (symbol_attribute): Add an oacc_function bit-field. (gfc_oacc_routine_name): New struct; (gfc_get_oacc_routine_name): New macro. (gfc_namespace): Add oacc_routine_clauses, oacc_routine_names and oacc_routine fields. (gfc_exec_op): Add EXEC_OACC_ROUTINE. * openmp.c (OACC_ROUTINE_CLAUSES): New mask. (gfc_oacc_routine_dims): New function. (gfc_match_oacc_routine): Add support for named routines and the gang, worker vector and seq clauses. * parse.c (is_oacc): Add EXEC_OACC_ROUTINE. * resolve.c (gfc_resolve_blocks): Likewise. * st.c (gfc_free_statement): Likewise. * trans-decl.c (add_attributes_to_decl): Attach an 'oacc function' attribute and shape geometry for acc routine. gcc/testsuite/ * gfortran.dg/goacc/routine-3.f90: New test. * gfortran.dg/goacc/routine-4.f90: New test. * gfortran.dg/goacc/routine-5.f90: New test. * gfortran.dg/goacc/routine-6.f90: New test. * gfortran.dg/goacc/subroutines: New test. libgomp/ * libgomp.oacc-fortran/routine-5.f90: New test. * libgomp.oacc-fortran/routine-7.f90: New test. * libgomp.oacc-fortran/routine-9.f90: New test. From-SVN: r231081
32 lines
571 B
Fortran
32 lines
571 B
Fortran
! { dg-do run }
|
|
! { dg-options "-fno-inline" }
|
|
|
|
program main
|
|
implicit none
|
|
integer, parameter :: n = 10
|
|
integer :: a(n), i
|
|
integer, external :: fact
|
|
!$acc routine (fact)
|
|
!$acc parallel
|
|
!$acc loop
|
|
do i = 1, n
|
|
a(i) = fact (i)
|
|
end do
|
|
!$acc end parallel
|
|
do i = 1, n
|
|
if (a(i) .ne. fact(i)) call abort
|
|
end do
|
|
end program main
|
|
|
|
recursive function fact (x) result (res)
|
|
implicit none
|
|
!$acc routine (fact)
|
|
integer, intent(in) :: x
|
|
integer :: res
|
|
if (x < 1) then
|
|
res = 1
|
|
else
|
|
res = x * fact(x - 1)
|
|
end if
|
|
end function fact
|