Skip to content

Commit 2237e33

Browse files
NimishMishrakiranchandramohan
authored andcommitted
Added OpenMP 5.0 specification based lowering of sections
This implementation adds lowering support for sections construct. In the frontend, a sections construct is further granularized as section blocks instead of OpenMPConstructs. The constructs, therefore, need special handling in the Bridge wherein division of executable statements into different section blocks happens depending on how the statements appear in the source code.
1 parent 249743c commit 2237e33

File tree

4 files changed

+234
-27
lines changed

4 files changed

+234
-27
lines changed

flang/include/flang/Lower/OpenMP.h

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -36,6 +36,8 @@ void genOpenMPConstruct(AbstractConverter &, pft::Evaluation &,
3636
void genOpenMPDeclarativeConstruct(AbstractConverter &, pft::Evaluation &,
3737
const parser::OpenMPDeclarativeConstruct &);
3838

39+
void genOpenMPSectionsBlock(Fortran::lower::AbstractConverter &,
40+
pft::Evaluation &);
3941
int64_t getCollapseValue(const Fortran::parser::OmpClauseList &clauseList);
4042

4143
} // namespace lower

flang/lib/Lower/Bridge.cpp

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1581,6 +1581,35 @@ class FirConverter : public Fortran::lower::AbstractConverter {
15811581
curEval = &*std::next(curEval->getNestedEvaluations().begin());
15821582
}
15831583
}
1584+
// If a 'sections' construct is encountered, loop over all 'section'
1585+
// directives nested within and generate FIR for the same. The individual
1586+
// 'section' inside a 'sections' construct are not constructs rather
1587+
// 'Section Blocks'. Hence, nested handling of constructs doesn't apply and
1588+
// we need special handling
1589+
if (const auto &ompSections =
1590+
std::get_if<Fortran::parser::OpenMPSectionsConstruct>(&omp.u)) {
1591+
const auto &ompSectionBlocks =
1592+
std::get<Fortran::parser::OmpSectionBlocks>(ompSections->t);
1593+
auto &sectionsBlockEvaluationList = curEval->getNestedEvaluations();
1594+
std::list<Fortran::lower::pft::Evaluation>::iterator
1595+
sectionsBlockEvalIterator = sectionsBlockEvaluationList.begin();
1596+
for (const auto &block : ompSectionBlocks.v) {
1597+
auto insertPt = builder->saveInsertionPoint();
1598+
// create a 'section' operation for every 'Section Block'
1599+
genOpenMPSectionsBlock(*this, *curEval);
1600+
for (auto it = block.begin(); it != block.end(); it++) {
1601+
// generate FIR for every 'ExecutionPartConstruct' and encapsulate it
1602+
// within the corresponding 'Section Block'
1603+
genFIR(*sectionsBlockEvalIterator);
1604+
sectionsBlockEvalIterator++;
1605+
}
1606+
builder->restoreInsertionPoint(insertPt);
1607+
}
1608+
if (--constructDepth == 0)
1609+
localSymbols.popScope();
1610+
builder->restoreInsertionPoint(insertPt);
1611+
return;
1612+
}
15841613

15851614
for (Fortran::lower::pft::Evaluation &e : curEval->getNestedEvaluations())
15861615
genFIR(e);

flang/lib/Lower/OpenMP.cpp

Lines changed: 97 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -107,7 +107,39 @@ static void genObjectList(const Fortran::parser::OmpObjectList &objectList,
107107
ompObject.u);
108108
}
109109
}
110+
static void handleAllocateClause(
111+
Fortran::lower::AbstractConverter &converter,
112+
const Fortran::parser::OmpAllocateClause &ompAllocateClause,
113+
SmallVector<Value> &allocatorOperands,
114+
SmallVector<Value> &allocateOperands) {
115+
auto &firOpBuilder = converter.getFirOpBuilder();
116+
auto currentLocation = converter.getCurrentLocation();
117+
Fortran::lower::StatementContext stmtCtx;
110118

119+
mlir::Value allocatorOperand;
120+
const Fortran::parser::OmpObjectList &ompObjectList =
121+
std::get<Fortran::parser::OmpObjectList>(ompAllocateClause.t);
122+
const auto &allocatorValue =
123+
std::get<std::optional<Fortran::parser::OmpAllocateClause::Allocator>>(
124+
ompAllocateClause.t);
125+
// Check if allocate clause has allocator specified. If so, add it
126+
// to list of allocators, otherwise, add default allocator to
127+
// list of allocators.
128+
129+
if (allocatorValue) {
130+
allocatorOperand = fir::getBase(converter.genExprValue(
131+
*Fortran::semantics::GetExpr(allocatorValue->v), stmtCtx));
132+
allocatorOperands.insert(allocatorOperands.end(), ompObjectList.v.size(),
133+
allocatorOperand);
134+
} else {
135+
allocatorOperand = firOpBuilder.createIntegerConstant(
136+
currentLocation, firOpBuilder.getI32Type(), 1);
137+
allocatorOperands.insert(allocatorOperands.end(), ompObjectList.v.size(),
138+
allocatorOperand);
139+
}
140+
141+
genObjectList(ompObjectList, converter, allocateOperands);
142+
}
111143
/// Create empty blocks for the current region.
112144
/// These blocks replace blocks parented to an enclosing region.
113145
void createEmptyRegionBlocks(
@@ -306,9 +338,9 @@ static void createParallelOp(Fortran::lower::AbstractConverter &converter,
306338
Fortran::lower::StatementContext stmtCtx;
307339
llvm::ArrayRef<mlir::Type> argTy;
308340
mlir::Value ifClauseOperand, numThreadsClauseOperand;
309-
llvm::SmallVector<Value, 4> privateClauseOperands, firstprivateClauseOperands,
310-
sharedClauseOperands, copyinClauseOperands, allocatorOperands,
311-
allocateOperands;
341+
SmallVector<Value, 4> privateClauseOperands, firstprivateClauseOperands,
342+
sharedClauseOperands, copyinClauseOperands;
343+
SmallVector<Value> allocatorOperands, allocateOperands;
312344
Attribute defaultClauseOperand, procBindClauseOperand;
313345
const auto &opClauseList =
314346
std::get<Fortran::parser::OmpClauseList>(directive.t);
@@ -334,29 +366,8 @@ static void createParallelOp(Fortran::lower::AbstractConverter &converter,
334366
} else if (const auto &allocateClause =
335367
std::get_if<Fortran::parser::OmpClause::Allocate>(
336368
&clause.u)) {
337-
mlir::Value allocatorOperand;
338-
const Fortran::parser::OmpAllocateClause &ompAllocateClause =
339-
allocateClause->v;
340-
const Fortran::parser::OmpObjectList &ompObjectList =
341-
std::get<Fortran::parser::OmpObjectList>(ompAllocateClause.t);
342-
// Check if allocate clause has allocator specified. If so, add it
343-
// to list of allocators, otherwise, add default allocator to
344-
// list of allocators.
345-
const auto &allocatorValue = std::get<
346-
std::optional<Fortran::parser::OmpAllocateClause::Allocator>>(
347-
ompAllocateClause.t);
348-
if (allocatorValue) {
349-
allocatorOperand = fir::getBase(converter.genExprValue(
350-
*Fortran::semantics::GetExpr(allocatorValue->v), stmtCtx));
351-
allocatorOperands.insert(allocatorOperands.end(),
352-
ompObjectList.v.size(), allocatorOperand);
353-
} else {
354-
allocatorOperand = firOpBuilder.createIntegerConstant(
355-
currentLocation, firOpBuilder.getI32Type(), 1);
356-
allocatorOperands.insert(allocatorOperands.end(),
357-
ompObjectList.v.size(), allocatorOperand);
358-
}
359-
genObjectList(ompObjectList, converter, allocateOperands);
369+
handleAllocateClause(converter, allocateClause->v, allocatorOperands,
370+
allocateOperands);
360371
}
361372
}
362373
// Create and insert the operation.
@@ -746,6 +757,65 @@ genOMP(Fortran::lower::AbstractConverter &converter,
746757
createBodyOfOp<omp::CriticalOp>(criticalOp, converter, currentLocation, eval);
747758
}
748759

760+
void Fortran::lower::genOpenMPSectionsBlock(
761+
Fortran::lower::AbstractConverter &converter,
762+
Fortran::lower::pft::Evaluation &eval) {
763+
auto &firOpBuilder = converter.getFirOpBuilder();
764+
auto currentLocation = converter.getCurrentLocation();
765+
mlir::omp::SectionOp sectionOp =
766+
firOpBuilder.create<mlir::omp::SectionOp>(currentLocation);
767+
createBodyOfOp<omp::SectionOp>(sectionOp, converter, currentLocation, eval);
768+
}
769+
770+
// TODO: Add support for reduction and lastprivate
771+
static void
772+
genOMP(Fortran::lower::AbstractConverter &converter,
773+
Fortran::lower::pft::Evaluation &eval,
774+
const Fortran::parser::OpenMPSectionsConstruct &sectionsConstruct) {
775+
auto &firOpBuilder = converter.getFirOpBuilder();
776+
auto currentLocation = converter.getCurrentLocation();
777+
SmallVector<Value> privateClauseOperands, firstPrivateClauseOperands,
778+
lastPrivateClauseOperands, reductionVars, allocateOperands,
779+
allocatorOperands;
780+
mlir::UnitAttr noWaitClauseOperand;
781+
const auto &sectionsClauseList = std::get<Fortran::parser::OmpClauseList>(
782+
std::get<Fortran::parser::OmpBeginSectionsDirective>(
783+
sectionsConstruct.t)
784+
.t);
785+
for (const auto &clause : sectionsClauseList.v) {
786+
if (std::get_if<Fortran::parser::OmpClause::Lastprivate>(&clause.u)) {
787+
TODO(currentLocation, "OMPC_LastPrivate");
788+
}
789+
if (std::get_if<Fortran::parser::OmpClause::Reduction>(&clause.u)) {
790+
TODO(currentLocation, "OMPC_Reduction");
791+
}
792+
if (const auto &allocateClause =
793+
std::get_if<Fortran::parser::OmpClause::Allocate>(&clause.u)) {
794+
handleAllocateClause(converter, allocateClause->v, allocatorOperands,
795+
allocateOperands);
796+
}
797+
}
798+
const auto &endSectionsClauseList =
799+
std::get<Fortran::parser::OmpEndSectionsDirective>(
800+
sectionsConstruct.t);
801+
const auto &clauseList =
802+
std::get<Fortran::parser::OmpClauseList>(endSectionsClauseList.t);
803+
for (const auto &clause : clauseList.v) {
804+
if (std::get_if<Fortran::parser::OmpClause::Nowait>(&clause.u)) {
805+
noWaitClauseOperand = firOpBuilder.getUnitAttr();
806+
}
807+
}
808+
809+
mlir::omp::SectionsOp sectionsOp =
810+
firOpBuilder.create<mlir::omp::SectionsOp>(
811+
currentLocation, privateClauseOperands, firstPrivateClauseOperands,
812+
lastPrivateClauseOperands, reductionVars, nullptr,
813+
allocateOperands, allocatorOperands, noWaitClauseOperand);
814+
815+
createBodyOfOp<omp::SectionsOp>(sectionsOp, converter, currentLocation,
816+
eval, &sectionsClauseList);
817+
}
818+
749819
void Fortran::lower::genOpenMPConstruct(
750820
Fortran::lower::AbstractConverter &converter,
751821
Fortran::lower::pft::Evaluation &eval,
@@ -759,7 +829,7 @@ void Fortran::lower::genOpenMPConstruct(
759829
},
760830
[&](const Fortran::parser::OpenMPSectionsConstruct
761831
&sectionsConstruct) {
762-
TODO(converter.getCurrentLocation(), "OpenMPSectionsConstruct");
832+
genOMP(converter, eval, sectionsConstruct);
763833
},
764834
[&](const Fortran::parser::OpenMPLoopConstruct &loopConstruct) {
765835
genOMP(converter, eval, loopConstruct);
Lines changed: 106 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,106 @@
1+
! This test checks the lowering of OpenMP sections construct with several clauses present
2+
3+
! RUN: bbc -fopenmp -emit-fir %s -o - | \
4+
! RUN: FileCheck %s --check-prefix=FIRDialect
5+
6+
!FIRDialect: func @_QQmain() {
7+
!FIRDialect: %[[COUNT:.*]] = fir.alloca i32 {bindc_name = "count", pinned, uniq_name = "_QFEcount"}
8+
!FIRDialect: %[[DOUBLE_COUNT:.*]] = fir.alloca i32 {bindc_name = "double_count", pinned, uniq_name = "_QFEdouble_count"}
9+
!FIRDialect: %[[ETA:.*]] = fir.alloca f32 {bindc_name = "eta", uniq_name = "_QFEeta"}
10+
!FIRDialect: %[[ALLOCATOR:.*]] = arith.constant 1 : i32
11+
!FIRDialect: omp.sections allocate(%[[ALLOCATOR]] : i32 -> %[[ETA]] : !fir.ref<f32>) {
12+
!FIRDialect: omp.section {
13+
!FIRDialect: {{.*}} = arith.constant 5 : i32
14+
!FIRDialect: fir.store {{.*}} to {{.*}} : !fir.ref<i32>
15+
!FIRDialect: {{.*}} = fir.load %[[COUNT]] : !fir.ref<i32>
16+
!FIRDialect: {{.*}} = fir.load %[[DOUBLE_COUNT]] : !fir.ref<i32>
17+
!FIRDialect: {{.*}} = arith.muli {{.*}}, {{.*}} : i32
18+
!FIRDialect: {{.*}} = fir.convert {{.*}} : (i32) -> f32
19+
!FIRDialect: fir.store {{.*}} to %[[ETA]] : !fir.ref<f32>
20+
!FIRDialect: omp.terminator
21+
!FIRDialect: }
22+
!FIRDialect: omp.section {
23+
!FIRDialect: {{.*}} = fir.load {{.*}} : !fir.ref<i32>
24+
!FIRDialect: {{.*}} = arith.constant 1 : i32
25+
!FIRDialect: {{.*}} = arith.addi {{.*}} : i32
26+
!FIRDialect: fir.store {{.*}} to %[[DOUBLE_COUNT]] : !fir.ref<i32>
27+
!FIRDialect: omp.terminator
28+
!FIRDialect: }
29+
!FIRDialect: omp.section {
30+
!FIRDialect: {{.*}} = fir.load {{.*}} : !fir.ref<f32>
31+
!FIRDialect: {{.*}} = arith.constant 7.000000e+00 : f32
32+
!FIRDialect: {{.*}} = arith.subf {{.*}} : f32
33+
!FIRDialect: fir.store {{.*}} to {{.*}} : !fir.ref<f32>
34+
!FIRDialect: {{.*}} = fir.load %[[COUNT]] : !fir.ref<i32>
35+
!FIRDialect: {{.*}} = fir.convert {{.*}} : (i32) -> f32
36+
!FIRDialect: {{.*}} = fir.load %[[ETA]] : !fir.ref<f32>
37+
!FIRDialect: {{.*}} = arith.mulf {{.*}}, {{.*}} : f32
38+
!FIRDialect: {{.*}} = fir.convert {{.*}} : (f32) -> i32
39+
!FIRDialect: fir.store {{.*}} to %[[COUNT]] : !fir.ref<i32>
40+
!FIRDialect: {{.*}} = fir.load %[[COUNT]] : !fir.ref<i32>
41+
!FIRDialect: {{.*}} = fir.convert {{.*}} : (i32) -> f32
42+
!FIRDialect: {{.*}} = fir.load %[[ETA]] : !fir.ref<f32>
43+
!FIRDialect: {{.*}} = arith.subf {{.*}}, {{.*}} : f32
44+
!FIRDialect: {{.*}} = fir.convert {{.*}} : (f32) -> i32
45+
!FIRDialect: fir.store {{.*}} to %[[DOUBLE_COUNT]] : !fir.ref<i32>
46+
!FIRDialect: omp.terminator
47+
!FIRDialect: }
48+
!FIRDialect: omp.terminator
49+
!FIRDialect: }
50+
!FIRDialect: omp.sections nowait {
51+
!FIRDialect: omp.terminator
52+
!FIRDialect: }
53+
!FIRDialect: return
54+
!FIRDialect: }
55+
56+
program sample
57+
use omp_lib
58+
integer :: count = 0, double_count = 1
59+
!$omp sections private (count, double_count) allocate(omp_default_mem_alloc: eta)
60+
!$omp section
61+
count = 1 + 4
62+
eta = count * double_count
63+
!$omp section
64+
double_count = double_count + 1
65+
!$omp section
66+
eta = eta - 7
67+
count = count * eta
68+
double_count = count - eta
69+
!$omp end sections
70+
71+
!$omp sections
72+
!$omp end sections nowait
73+
end program sample
74+
75+
!FIRDialect: func @_QPfirstprivate(%[[ARG:.*]]: !fir.ref<f32> {fir.bindc_name = "alpha"}) {
76+
!FIRDialect: %[[ALPHA:.*]] = fir.alloca f32 {bindc_name = "alpha", pinned, uniq_name = "_QFfirstprivateEalpha"}
77+
!FIRDialect: %[[ALPHA_STORE:.*]] = fir.load %[[ARG]] : !fir.ref<f32>
78+
!FIRDialect: fir.store %[[ALPHA_STORE]] to %[[ALPHA]] : !fir.ref<f32>
79+
!FIRDialect: omp.sections {
80+
!FIRDialect: omp.section {
81+
!FIRDialect: omp.terminator
82+
!FIRDialect: }
83+
!FIRDialect: omp.terminator
84+
!FIRDialect: }
85+
!FIRDialect: omp.sections {
86+
!FIRDialect: omp.section {
87+
!FIRDialect: %[[PRIVATE_VAR:.*]] = fir.load %[[ARG]] : !fir.ref<f32>
88+
!FIRDialect: %[[CONSTANT:.*]] = arith.constant 5.000000e+00 : f32
89+
!FIRDialect: %[[PRIVATE_VAR_2:.*]] = arith.mulf %[[PRIVATE_VAR]], %[[CONSTANT]] : f32
90+
!FIRDialect: fir.store %[[PRIVATE_VAR_2]] to %[[ARG]] : !fir.ref<f32>
91+
!FIRDialect: omp.terminator
92+
!FIRDialect: }
93+
!FIRDialect: omp.terminator
94+
!FIRDialect: }
95+
!FIRDialect: return
96+
!FIRDialect: }
97+
98+
subroutine firstprivate(alpha)
99+
real :: alpha
100+
!$omp sections firstprivate(alpha)
101+
!$omp end sections
102+
103+
!$omp sections
104+
alpha = alpha * 5
105+
!$omp end sections
106+
end subroutine

0 commit comments

Comments
 (0)