Skip to content

Commit 88bc622

Browse files
PeixinQiaojeanPerier
authored andcommitted
[flang][OpenMP] Add semantic check for teams nesting
This patch implements the following check for TEAMS construct: ``` OpenMP Version 5.0 Teams construct restriction: A teams region can only be strictly nested within the implicit parallel region or a target region. If a teams construct is nested within a target construct, that target construct must contain no statements, declarations or directives outside of the teams construct. ``` Also add one test case for the check. Reviewed By: kiranchandramohan, clementval Differential Revision: https://reviews.llvm.org/D106335
1 parent 14cfb57 commit 88bc622

File tree

7 files changed

+180
-34
lines changed

7 files changed

+180
-34
lines changed

flang/lib/Semantics/check-directive-structure.h

Lines changed: 0 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -203,12 +203,6 @@ class DirectiveStructureChecker : public virtual BaseChecker {
203203
GetContext().actualClauses.push_back(type);
204204
}
205205

206-
void EnterSIMDNest() { simdNest_++; }
207-
208-
void ExitSIMDNest() { simdNest_--; }
209-
210-
int GetSIMDNest() { return simdNest_; }
211-
212206
// Check if the given clause is present in the current context
213207
const PC *FindClause(C type) {
214208
auto it{GetContext().clauseInfo.find(type)};
@@ -320,7 +314,6 @@ class DirectiveStructureChecker : public virtual BaseChecker {
320314
directiveClausesMap_;
321315

322316
std::string ClauseSetToString(const common::EnumSet<C, ClauseEnumSize> set);
323-
int simdNest_{0};
324317
};
325318

326319
template <typename D, typename C, typename PC, std::size_t ClauseEnumSize>

flang/lib/Semantics/check-omp-structure.cpp

Lines changed: 54 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -285,7 +285,7 @@ void OmpStructureChecker::Enter(const parser::OpenMPConstruct &x) {
285285
// called individually for each construct. Therefore a
286286
// dirContext_ size `1` means the current construct is nested
287287
if (dirContext_.size() >= 1) {
288-
if (GetSIMDNest() > 0) {
288+
if (GetDirectiveNest(SIMDNest) > 0) {
289289
CheckSIMDNest(x);
290290
}
291291
}
@@ -306,7 +306,7 @@ void OmpStructureChecker::Enter(const parser::OpenMPLoopConstruct &x) {
306306

307307
PushContextAndClauseSets(beginDir.source, beginDir.v);
308308
if (llvm::omp::simdSet.test(GetContext().directive)) {
309-
EnterSIMDNest();
309+
EnterDirectiveNest(SIMDNest);
310310
}
311311

312312
if (beginDir.v == llvm::omp::Directive::OMPD_do) {
@@ -585,7 +585,7 @@ void OmpStructureChecker::CheckDistLinear(
585585

586586
void OmpStructureChecker::Leave(const parser::OpenMPLoopConstruct &) {
587587
if (llvm::omp::simdSet.test(GetContext().directive)) {
588-
ExitSIMDNest();
588+
ExitDirectiveNest(SIMDNest);
589589
}
590590
dirContext_.pop_back();
591591
}
@@ -625,11 +625,35 @@ void OmpStructureChecker::Enter(const parser::OpenMPBlockConstruct &x) {
625625
if (GetContext().directive == llvm::omp::Directive::OMPD_master) {
626626
CheckMasterNesting(x);
627627
}
628+
// A teams region can only be strictly nested within the implicit parallel
629+
// region or a target region.
630+
if (GetContext().directive == llvm::omp::Directive::OMPD_teams &&
631+
GetContextParent().directive != llvm::omp::Directive::OMPD_target) {
632+
context_.Say(parser::FindSourceLocation(x),
633+
"%s region can only be strictly nested within the implicit parallel "
634+
"region or TARGET region"_err_en_US,
635+
ContextDirectiveAsFortran());
636+
}
637+
// If a teams construct is nested within a target construct, that target
638+
// construct must contain no statements, declarations or directives outside
639+
// of the teams construct.
640+
if (GetContext().directive == llvm::omp::Directive::OMPD_teams &&
641+
GetContextParent().directive == llvm::omp::Directive::OMPD_target &&
642+
!GetDirectiveNest(TargetBlockOnlyTeams)) {
643+
context_.Say(GetContextParent().directiveSource,
644+
"TARGET construct with nested TEAMS region contains statements or "
645+
"directives outside of the TEAMS construct"_err_en_US);
646+
}
628647
}
629648

630649
CheckNoBranching(block, beginDir.v, beginDir.source);
631650

632651
switch (beginDir.v) {
652+
case llvm::omp::Directive::OMPD_target:
653+
if (CheckTargetBlockOnlyTeams(block)) {
654+
EnterDirectiveNest(TargetBlockOnlyTeams);
655+
}
656+
break;
633657
case llvm::omp::OMPD_workshare:
634658
case llvm::omp::OMPD_parallel_workshare:
635659
CheckWorkshareBlockStmts(block, beginDir.source);
@@ -683,6 +707,9 @@ void OmpStructureChecker::CheckIfDoOrderedClause(
683707
}
684708

685709
void OmpStructureChecker::Leave(const parser::OpenMPBlockConstruct &) {
710+
if (GetDirectiveNest(TargetBlockOnlyTeams)) {
711+
ExitDirectiveNest(TargetBlockOnlyTeams);
712+
}
686713
dirContext_.pop_back();
687714
}
688715

@@ -1919,6 +1946,30 @@ void OmpStructureChecker::CheckPrivateSymbolsInOuterCxt(
19191946
}
19201947
}
19211948

1949+
bool OmpStructureChecker::CheckTargetBlockOnlyTeams(
1950+
const parser::Block &block) {
1951+
bool nestedTeams{false};
1952+
auto it{block.begin()};
1953+
1954+
if (const auto *ompConstruct{parser::Unwrap<parser::OpenMPConstruct>(*it)}) {
1955+
if (const auto *ompBlockConstruct{
1956+
std::get_if<parser::OpenMPBlockConstruct>(&ompConstruct->u)}) {
1957+
const auto &beginBlockDir{
1958+
std::get<parser::OmpBeginBlockDirective>(ompBlockConstruct->t)};
1959+
const auto &beginDir{
1960+
std::get<parser::OmpBlockDirective>(beginBlockDir.t)};
1961+
if (beginDir.v == llvm::omp::Directive::OMPD_teams) {
1962+
nestedTeams = true;
1963+
}
1964+
}
1965+
}
1966+
1967+
if (nestedTeams && ++it == block.end()) {
1968+
return true;
1969+
}
1970+
return false;
1971+
}
1972+
19221973
void OmpStructureChecker::CheckWorkshareBlockStmts(
19231974
const parser::Block &block, parser::CharBlock source) {
19241975
OmpWorkshareBlockChecker ompWorkshareBlockChecker{context_, source};

flang/lib/Semantics/check-omp-structure.h

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -218,6 +218,7 @@ class OmpStructureChecker
218218
void SetLoopInfo(const parser::OpenMPLoopConstruct &x);
219219
void CheckIsLoopIvPartOfClause(
220220
llvmOmpClause clause, const parser::OmpObjectList &ompObjectList);
221+
bool CheckTargetBlockOnlyTeams(const parser::Block &);
221222
void CheckWorkshareBlockStmts(const parser::Block &, parser::CharBlock);
222223

223224
void CheckLoopItrVariableIsInt(const parser::OpenMPLoopConstruct &x);
@@ -248,6 +249,12 @@ class OmpStructureChecker
248249
void CheckPredefinedAllocatorRestriction(
249250
const parser::CharBlock &source, const parser::Name &name);
250251
bool isPredefinedAllocator{false};
252+
void EnterDirectiveNest(const int index) { directiveNest_[index]++; }
253+
void ExitDirectiveNest(const int index) { directiveNest_[index]--; }
254+
int GetDirectiveNest(const int index) { return directiveNest_[index]; }
255+
256+
enum directiveNestType { SIMDNest, TargetBlockOnlyTeams, LastType };
257+
int directiveNest_[LastType + 1] = {0};
251258
};
252259
} // namespace Fortran::semantics
253260
#endif // FORTRAN_SEMANTICS_CHECK_OMP_STRUCTURE_H_

flang/test/Semantics/omp-firstprivate01.f90

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ program omp_firstprivate
1212
a = 10
1313
b = 20
1414

15+
!ERROR: TARGET construct with nested TEAMS region contains statements or directives outside of the TEAMS construct
1516
!$omp target
1617
!$omp teams private(a, b)
1718
!ERROR: FIRSTPRIVATE variable 'a' is PRIVATE in outer context

flang/test/Semantics/omp-nested-master.f90

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -87,6 +87,7 @@ program omp_nest_master
8787

8888
!$omp ordered
8989
do i = 1, 10
90+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
9091
!$omp teams
9192
!$omp distribute
9293
do k =1, 10
@@ -102,6 +103,7 @@ program omp_nest_master
102103

103104
!$omp critical
104105
do i = 1, 10
106+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
105107
!$omp teams
106108
!$omp distribute
107109
do k =1, 10
@@ -117,6 +119,7 @@ program omp_nest_master
117119

118120
!$omp taskloop
119121
do i = 1, 10
122+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
120123
!$omp teams
121124
!$omp distribute
122125
do k =1, 10
@@ -133,6 +136,7 @@ program omp_nest_master
133136

134137
!$omp task
135138
do i = 1, 10
139+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
136140
!$omp teams
137141
!$omp distribute
138142
do k =1, 10

flang/test/Semantics/omp-nested-simd.f90

Lines changed: 1 addition & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ SUBROUTINE NESTED_BAD(N)
4242
DO J = 1,N
4343
print *, "Hi"
4444
!ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
45+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
4546
!$omp teams
4647
DO K = 1,N
4748
print *, 'Hello'
@@ -65,12 +66,6 @@ SUBROUTINE NESTED_BAD(N)
6566
end do
6667
!$omp end task
6768
!ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
68-
!$omp teams
69-
do J = 1, N
70-
K = 2
71-
end do
72-
!$omp end teams
73-
!ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
7469
!$omp target
7570
do J = 1, N
7671
K = 2
@@ -104,12 +99,6 @@ SUBROUTINE NESTED_BAD(N)
10499
end do
105100
!$omp end task
106101
!ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
107-
!$omp teams
108-
do J = 1, N
109-
K = 2
110-
end do
111-
!$omp end teams
112-
!ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
113102
!$omp target
114103
do J = 1, N
115104
K = 2
@@ -144,12 +133,6 @@ SUBROUTINE NESTED_BAD(N)
144133
end do
145134
!$omp end task
146135
!ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
147-
!$omp teams
148-
do J = 1, N
149-
K = 2
150-
end do
151-
!$omp end teams
152-
!ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
153136
!$omp target
154137
do J = 1, N
155138
K = 2
@@ -184,12 +167,6 @@ SUBROUTINE NESTED_BAD(N)
184167
end do
185168
!$omp end task
186169
!ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
187-
!$omp teams
188-
do J = 1, N
189-
K = 2
190-
end do
191-
!$omp end teams
192-
!ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
193170
!$omp target
194171
do J = 1, N
195172
K = 2
Lines changed: 113 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,113 @@
1+
! RUN: %S/test_errors.sh %s %t %flang -fopenmp
2+
! REQUIRES: shell
3+
4+
! OpenMP Version 5.0
5+
! Check OpenMP construct validity for the following directives:
6+
! 2.7 Teams Construct
7+
8+
program main
9+
integer :: i, j, N = 10
10+
real :: a, b, c
11+
12+
!$omp teams
13+
a = 3.14
14+
!$omp end teams
15+
16+
!$omp target
17+
!$omp teams
18+
a = 3.14
19+
!$omp end teams
20+
!$omp end target
21+
22+
!$omp target
23+
!$omp parallel
24+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
25+
!$omp teams
26+
a = 3.14
27+
!$omp end teams
28+
!$omp end parallel
29+
!$omp end target
30+
31+
!$omp parallel
32+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
33+
!$omp teams
34+
a = 3.14
35+
!$omp end teams
36+
!$omp end parallel
37+
38+
!$omp do
39+
do i = 1, N
40+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
41+
!$omp teams
42+
a = 3.14
43+
!$omp end teams
44+
end do
45+
46+
!$omp master
47+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
48+
!$omp teams
49+
a = 3.14
50+
!$omp end teams
51+
!$omp end master
52+
53+
!$omp target parallel
54+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
55+
!$omp teams
56+
a = 3.14
57+
!$omp end teams
58+
!$omp end target parallel
59+
60+
!$omp target
61+
!$omp teams
62+
!ERROR: Only `DISTRIBUTE` or `PARALLEL` regions are allowed to be strictly nested inside `TEAMS` region.
63+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
64+
!$omp teams
65+
a = 3.14
66+
!$omp end teams
67+
!$omp end teams
68+
!$omp end target
69+
70+
!$omp target teams
71+
!ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
72+
!$omp teams
73+
a = 3.14
74+
!$omp end teams
75+
!$omp end target teams
76+
77+
!ERROR: TARGET construct with nested TEAMS region contains statements or directives outside of the TEAMS construct
78+
!$omp target
79+
do i = 1, N
80+
!$omp teams
81+
a = 3.14
82+
!$omp end teams
83+
enddo
84+
!$omp end target
85+
86+
!ERROR: TARGET construct with nested TEAMS region contains statements or directives outside of the TEAMS construct
87+
!$omp target
88+
if (i .GT. 1) then
89+
if (j .GT. 1) then
90+
!$omp teams
91+
a = 3.14
92+
!$omp end teams
93+
end if
94+
end if
95+
!$omp end target
96+
97+
!ERROR: TARGET construct with nested TEAMS region contains statements or directives outside of the TEAMS construct
98+
!$omp target
99+
b = 3.14
100+
!$omp teams
101+
a = 3.14
102+
!$omp end teams
103+
!$omp end target
104+
105+
!ERROR: TARGET construct with nested TEAMS region contains statements or directives outside of the TEAMS construct
106+
!$omp target
107+
!$omp teams
108+
a = 3.14
109+
!$omp end teams
110+
c = 3.14
111+
!$omp end target
112+
113+
end program main

0 commit comments

Comments
 (0)