Skip to content

Commit 24efa31

Browse files
PeixinQiaoschweitzpgi
authored andcommitted
[flang] Fix processing ModuleLikeUnit evaluationList
Push the ModuleLikeUnit evalutionList when entering module unit. Pop it when exiting module unit if there is no module procedure. Otherwise, pop it when entering the first module procedure. Reviewed By: V Donaldson Differential Revision: https://reviews.llvm.org/D120460
1 parent 942f684 commit 24efa31

File tree

2 files changed

+52
-13
lines changed

2 files changed

+52
-13
lines changed

flang/lib/Lower/PFTBuilder.cpp

Lines changed: 10 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -167,8 +167,6 @@ class PFTBuilder {
167167
exitFunction();
168168
} else if constexpr (lower::pft::isConstruct<A> ||
169169
lower::pft::isDirective<A>) {
170-
if constexpr (lower::pft::isDeclConstruct<A>)
171-
return;
172170
exitConstructOrDirective();
173171
}
174172
}
@@ -252,11 +250,6 @@ class PFTBuilder {
252250
if (evaluationListStack.empty())
253251
return;
254252
auto evaluationList = evaluationListStack.back();
255-
if (evaluationList->empty() &&
256-
pftParentStack.back().getIf<lower::pft::ModuleLikeUnit>()) {
257-
popEvaluationList();
258-
return;
259-
}
260253
if (evaluationList->empty() || !evaluationList->back().isEndStmt()) {
261254
const auto &endStmt =
262255
pftParentStack.back().get<lower::pft::FunctionLikeUnit>().endStmt;
@@ -286,10 +279,20 @@ class PFTBuilder {
286279
lastLexicalEvaluation = nullptr;
287280
}
288281

282+
/// Pop the ModuleLikeUnit evaluationList when entering the first module
283+
/// procedure.
284+
void cleanModuleEvaluationList() {
285+
if (evaluationListStack.empty())
286+
return;
287+
if (pftParentStack.back().isA<lower::pft::ModuleLikeUnit>())
288+
popEvaluationList();
289+
}
290+
289291
/// Initialize a new function-like unit and make it the builder's focus.
290292
template <typename A>
291293
bool enterFunction(const A &func,
292294
const semantics::SemanticsContext &semanticsContext) {
295+
cleanModuleEvaluationList();
293296
endFunctionBody(); // enclosing host subprogram body, if any
294297
Fortran::lower::pft::FunctionLikeUnit &unit =
295298
addFunction(lower::pft::FunctionLikeUnit{func, pftParentStack.back(),
@@ -323,12 +326,6 @@ class PFTBuilder {
323326
pushEvaluationList(eval.evaluationList.get());
324327
pftParentStack.emplace_back(eval);
325328
constructAndDirectiveStack.emplace_back(&eval);
326-
if constexpr (lower::pft::isDeclConstruct<A>) {
327-
popEvaluationList();
328-
pftParentStack.pop_back();
329-
constructAndDirectiveStack.pop_back();
330-
popEvaluationList();
331-
}
332329
return true;
333330
}
334331

flang/test/Lower/pre-fir-tree06.f90

Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,3 +10,45 @@ module m
1010
end
1111
! CHECK: End ModuleLike
1212

13+
! CHECK: ModuleLike
14+
module m2
15+
integer, save :: i
16+
! CHECK-NEXT: OpenMPDeclarativeConstruct
17+
!$omp threadprivate(i)
18+
contains
19+
subroutine sub()
20+
i = 1;
21+
end
22+
subroutine sub2()
23+
i = 2;
24+
end
25+
end
26+
! CHECK: End ModuleLike
27+
28+
! CHECK: Program main
29+
program main
30+
real :: y
31+
! CHECK-NEXT: OpenMPDeclarativeConstruct
32+
!$omp threadprivate(y)
33+
end
34+
! CHECK: End Program main
35+
36+
! CHECK: Subroutine sub1
37+
subroutine sub1()
38+
real, save :: p
39+
! CHECK-NEXT: OpenMPDeclarativeConstruct
40+
!$omp threadprivate(p)
41+
end
42+
! CHECK: End Subroutine sub1
43+
44+
! CHECK: Subroutine sub2
45+
subroutine sub2()
46+
real, save :: q
47+
! CHECK-NEXT: OpenMPDeclarativeConstruct
48+
!$omp threadprivate(q)
49+
contains
50+
subroutine sub()
51+
end
52+
end
53+
! CHECK: End Subroutine sub2
54+

0 commit comments

Comments
 (0)