
2024-02-15 Kwok Cheung Yeung <kcyeung@baylibre.com> gcc/fortran/ * dump-parse-tree.cc (show_attr): Handle omp_declare_target_indirect attribute. * f95-lang.cc (gfc_gnu_attributes): Add entry for 'omp declare target indirect'. * gfortran.h (symbol_attribute): Add omp_declare_target_indirect field. (struct gfc_omp_clauses): Add indirect field. * openmp.cc (omp_mask2): Add OMP_CLAUSE_INDIRECT. (gfc_match_omp_clauses): Match indirect clause. (OMP_DECLARE_TARGET_CLAUSES): Add OMP_CLAUSE_INDIRECT. (gfc_match_omp_declare_target): Check omp_device_type and apply omp_declare_target_indirect attribute to symbol if indirect clause active. Show warning if there are only device_type and/or indirect clauses on the directive. * trans-decl.cc (add_attributes_to_decl): Add 'omp declare target indirect' attribute if symbol has indirect attribute set. gcc/testsuite/ * gfortran.dg/gomp/declare-target-4.f90 (f1): Update expected warning. * gfortran.dg/gomp/declare-target-indirect-1.f90: New. * gfortran.dg/gomp/declare-target-indirect-2.f90: New. libgomp/ * testsuite/libgomp.fortran/declare-target-indirect-1.f90: New. * testsuite/libgomp.fortran/declare-target-indirect-2.f90: New. * testsuite/libgomp.fortran/declare-target-indirect-3.f90: New.
39 lines
711 B
Fortran
39 lines
711 B
Fortran
! { dg-do run }
|
|
|
|
module m
|
|
contains
|
|
integer function foo ()
|
|
!$omp declare target to (foo) indirect
|
|
foo = 5
|
|
end function
|
|
|
|
integer function bar ()
|
|
!$omp declare target to (bar) indirect
|
|
bar = 8
|
|
end function
|
|
|
|
integer function baz ()
|
|
!$omp declare target to (baz) indirect
|
|
baz = 11
|
|
end function
|
|
end module
|
|
|
|
program main
|
|
use m
|
|
implicit none
|
|
|
|
integer :: x, expected
|
|
procedure (foo), pointer :: foo_ptr, bar_ptr, baz_ptr
|
|
|
|
foo_ptr => foo
|
|
bar_ptr => bar
|
|
baz_ptr => baz
|
|
|
|
expected = foo () + bar () + baz ()
|
|
|
|
!$omp target map (to: foo_ptr, bar_ptr, baz_ptr) map (from: x)
|
|
x = foo_ptr () + bar_ptr () + baz_ptr ()
|
|
!$omp end target
|
|
|
|
stop x - expected
|
|
end program
|