gcc/libgomp/testsuite/libgomp.fortran/icv-4.f90
Tobias Burnus 948d461954 OpenMP: Add strictly nested API call check [PR102972]
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.
2021-10-30 23:45:32 +02:00

47 lines
1.3 KiB
Fortran

! { dg-set-target-env-var OMP_NUM_TEAMS "6" }
! { dg-set-target-env-var OMP_TEAMS_THREAD_LIMIT "12" }
use omp_lib
implicit none (type, external)
if (env_is_set ("OMP_NUM_TEAMS", "6")) then
if (omp_get_max_teams () /= 6) &
error stop 1
else
call omp_set_num_teams (6)
end if
if (env_is_set ("OMP_TEAMS_THREAD_LIMIT", "12")) then
if (omp_get_teams_thread_limit () /= 12) &
error stop 2
else
call omp_set_teams_thread_limit (12)
end if
!$omp teams
!$omp parallel if(.false.)
if (omp_get_max_teams () /= 6 &
.or. omp_get_teams_thread_limit () /= 12 &
.or. omp_get_num_teams () < 1 &
.or. omp_get_num_teams () > 6 &
.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 () > 12) &
error stop 3
!$omp end parallel
!$omp end teams
contains
logical function env_is_set (name, val)
character(len=*) :: name, val
character(len=40) :: val2
integer :: stat
call get_environment_variable (name, val2, status=stat)
if (stat == 0) then
if (val == val2) then
env_is_set = .true.
return
end if
else if (stat /= 1) then
error stop 10
endif
env_is_set = .false.
end
end