
The teams construct only permits omp_get_num_teams and omp_get_team_num as API call in strictly nested regions - check for it. Additionally, for Fortran, using DECL_NAME does not show the mangled name, hence, DECL_ASSEMBLER_NAME had to be used to. Finally, 'target device(ancestor:1)' wrongly rejected non-API calls as well. PR middle-end/102972 gcc/ChangeLog: * omp-low.c (omp_runtime_api_call): Use DECL_ASSEMBLER_NAME to get internal Fortran name; new permit_num_teams arg to permit omp_get_num_teams and omp_get_team_num. (scan_omp_1_stmt): Update call to it, add missing call for reverse offload, and check for strictly nested API calls in teams. gcc/testsuite/ChangeLog: * c-c++-common/gomp/target-device-ancestor-3.c: Add non-API routine test. * gfortran.dg/gomp/order-6.f90: Add missing bind(C). * c-c++-common/gomp/teams-3.c: New test. * gfortran.dg/gomp/teams-3.f90: New test. * gfortran.dg/gomp/teams-4.f90: New test. libgomp/ChangeLog: * testsuite/libgomp.c-c++-common/icv-3.c: Nest API calls inside parallel construct. * testsuite/libgomp.c-c++-common/icv-4.c: Likewise. * testsuite/libgomp.c/target-3.c: Likewise. * testsuite/libgomp.c/target-5.c: Likewise. * testsuite/libgomp.c/target-6.c: Likewise. * testsuite/libgomp.c/target-teams-1.c: Likewise. * testsuite/libgomp.c/teams-1.c: Likewise. * testsuite/libgomp.c/thread-limit-2.c: Likewise. * testsuite/libgomp.c/thread-limit-3.c: Likewise. * testsuite/libgomp.c/thread-limit-4.c: Likewise. * testsuite/libgomp.c/thread-limit-5.c: Likewise. * testsuite/libgomp.fortran/icv-3.f90: Likewise. * testsuite/libgomp.fortran/icv-4.f90: Likewise. * testsuite/libgomp.fortran/teams1.f90: Likewise.
66 lines
2.1 KiB
Fortran
66 lines
2.1 KiB
Fortran
use omp_lib
|
|
implicit none (type, external)
|
|
if (.not. env_exists ("OMP_NUM_TEAMS") &
|
|
.and. omp_get_max_teams () /= 0) &
|
|
error stop 1
|
|
call omp_set_num_teams (7)
|
|
if (omp_get_max_teams () /= 7) &
|
|
error stop 2
|
|
if (.not. env_exists ("OMP_TEAMS_THREAD_LIMIT") &
|
|
.and. omp_get_teams_thread_limit () /= 0) &
|
|
error stop 3
|
|
call omp_set_teams_thread_limit (15)
|
|
if (omp_get_teams_thread_limit () /= 15) &
|
|
error stop 4
|
|
!$omp teams
|
|
!$omp parallel if(.false.)
|
|
if (omp_get_max_teams () /= 7 &
|
|
.or. omp_get_teams_thread_limit () /= 15 &
|
|
.or. omp_get_num_teams () < 1 &
|
|
.or. omp_get_num_teams () > 7 &
|
|
.or. omp_get_team_num () < 0 &
|
|
.or. omp_get_team_num () >= omp_get_num_teams () &
|
|
.or. omp_get_thread_limit () < 1 &
|
|
.or. omp_get_thread_limit () > 15) &
|
|
error stop 5
|
|
!$omp end parallel
|
|
!$omp end teams
|
|
!$omp teams num_teams(5) thread_limit (13)
|
|
!$omp parallel if(.false.)
|
|
if (omp_get_max_teams () /= 7 &
|
|
.or. omp_get_teams_thread_limit () /= 15 &
|
|
.or. omp_get_num_teams () /= 5 &
|
|
.or. omp_get_team_num () < 0 &
|
|
.or. omp_get_team_num () >= omp_get_num_teams () &
|
|
.or. omp_get_thread_limit () < 1 &
|
|
.or. omp_get_thread_limit () > 13) &
|
|
error stop 6
|
|
!$omp end parallel
|
|
!$omp end teams
|
|
!$omp teams num_teams(8) thread_limit (16)
|
|
!$omp parallel if(.false.)
|
|
if (omp_get_max_teams () /= 7 &
|
|
.or. omp_get_teams_thread_limit () /= 15 &
|
|
.or. omp_get_num_teams () /= 8 &
|
|
.or. omp_get_team_num () < 0 &
|
|
.or. omp_get_team_num () >= omp_get_num_teams () &
|
|
.or. omp_get_thread_limit () < 1 &
|
|
.or. omp_get_thread_limit () > 16) &
|
|
error stop 7
|
|
!$omp end parallel
|
|
!$omp end teams
|
|
contains
|
|
logical function env_exists (name)
|
|
character(len=*) :: name
|
|
character(len=40) :: val
|
|
integer :: stat
|
|
call get_environment_variable (name, val, status=stat)
|
|
if (stat == 0) then
|
|
env_exists = .true.
|
|
else if (stat == 1) then
|
|
env_exists = .false.
|
|
else
|
|
error stop 10
|
|
endif
|
|
end
|
|
end
|