
A splay-tree was previously used to lookup equivalent target addresses for a given host address on offload targets. However, as splay-trees can modify their structure on lookup, they are not suitable for concurrent access from separate teams/threads without some form of locking. This patch changes the lookup data structure to a hashtab instead, which does not have these issues. The call to build_indirect_map to initialize the data structure is now called from just the first thread of the first team to avoid redundant calls to this function. 2024-03-22 Kwok Cheung Yeung <kcyeung@baylibre.com> libgomp/ * config/accel/target-indirect.c: Include string.h and hashtab.h. Remove include of splay-tree.h. Update comments. (splay_tree_prefix, splay_tree_c): Delete. (struct indirect_map_t): New. (hash_entry_type, htab_alloc, htab_free, htab_hash, htab_eq): New. (GOMP_INDIRECT_ADD_MAP): Remove volatile qualifier. (USE_SPLAY_TREE_LOOKUP): Rename to... (USE_HASHTAB_LOOKUP): ..this. (indirect_map, indirect_array): Delete. (indirect_htab): New. (build_indirect_map): Remove locking. Build indirect map using hashtab. (GOMP_target_map_indirect_ptr): Use indirect_htab to lookup target address. (GOMP_target_map_indirect_ptr): Remove volatile qualifier. * config/gcn/team.c (gomp_gcn_enter_kernel): Call build_indirect_map from first thread of first team only. * config/nvptx/team.c (gomp_nvptx_main): Likewise. * testsuite/libgomp.c-c++-common/declare-target-indirect-2.c (main): Add missing break statements. * testsuite/libgomp.fortran/declare-target-indirect-2.f90: Remove xfail.
53 lines
1 KiB
Fortran
53 lines
1 KiB
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
|
|
|
|
type fp
|
|
procedure (foo), pointer, nopass :: f => null ()
|
|
end type
|
|
|
|
integer, parameter :: N = 256
|
|
integer :: i, x = 0, expected = 0;
|
|
type (fp) :: fn_ptr (N)
|
|
|
|
do i = 1, N
|
|
select case (mod (i, 3))
|
|
case (0)
|
|
fn_ptr (i)%f => foo
|
|
case (1)
|
|
fn_ptr (i)%f => bar
|
|
case (2)
|
|
fn_ptr (i)%f => baz
|
|
end select
|
|
expected = expected + fn_ptr (i)%f ()
|
|
end do
|
|
|
|
!$omp target teams distribute parallel do &
|
|
!$omp & reduction(+: x) map (to: fn_ptr) map (tofrom: x)
|
|
do i = 1, N
|
|
x = x + fn_ptr (i)%f ()
|
|
end do
|
|
!$omp end target teams distribute parallel do
|
|
|
|
stop x - expected
|
|
end program
|