@@ -34,11 +34,12 @@ static void createPrivateVarSyms(Fortran::lower::AbstractConverter &converter,
34
34
const T *clause) {
35
35
Fortran::semantics::Symbol *sym = nullptr ;
36
36
const Fortran::parser::OmpObjectList &ompObjectList = clause->v ;
37
- for (const auto &ompObject : ompObjectList.v ) {
37
+ for (const Fortran::parser::OmpObject &ompObject : ompObjectList.v ) {
38
38
std::visit (
39
39
Fortran::common::visitors{
40
40
[&](const Fortran::parser::Designator &designator) {
41
- if (const auto *name = getDesignatorNameIfDataRef (designator)) {
41
+ if (const Fortran::parser::Name *name =
42
+ getDesignatorNameIfDataRef (designator)) {
42
43
sym = name->symbol ;
43
44
}
44
45
},
@@ -61,10 +62,10 @@ static void createPrivateVarSyms(Fortran::lower::AbstractConverter &converter,
61
62
62
63
static void privatizeVars (Fortran::lower::AbstractConverter &converter,
63
64
const Fortran::parser::OmpClauseList &opClauseList) {
64
- auto &firOpBuilder = converter.getFirOpBuilder ();
65
+ fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder ();
65
66
auto insPt = firOpBuilder.saveInsertionPoint ();
66
67
firOpBuilder.setInsertionPointToStart (firOpBuilder.getAllocaBlock ());
67
- for (const auto &clause : opClauseList.v ) {
68
+ for (const Fortran::parser::OmpClause &clause : opClauseList.v ) {
68
69
if (const auto &privateClause =
69
70
std::get_if<Fortran::parser::OmpClause::Private>(&clause.u )) {
70
71
createPrivateVarSyms (converter, privateClause);
@@ -81,7 +82,7 @@ static void genObjectList(const Fortran::parser::OmpObjectList &objectList,
81
82
Fortran::lower::AbstractConverter &converter,
82
83
SmallVectorImpl<Value> &operands) {
83
84
auto addOperands = [&](Fortran::lower::SymbolRef sym) {
84
- const auto variable = converter.getSymbolAddress (sym);
85
+ const mlir::Value variable = converter.getSymbolAddress (sym);
85
86
if (variable) {
86
87
operands.push_back (variable);
87
88
} else {
@@ -92,10 +93,10 @@ static void genObjectList(const Fortran::parser::OmpObjectList &objectList,
92
93
}
93
94
}
94
95
};
95
- for (const auto &ompObject : objectList.v ) {
96
+ for (const Fortran::parser::OmpObject &ompObject : objectList.v ) {
96
97
std::visit (Fortran::common::visitors{
97
98
[&](const Fortran::parser::Designator &designator) {
98
- if (const auto *name =
99
+ if (const Fortran::parser::Name *name =
99
100
getDesignatorNameIfDataRef (designator)) {
100
101
addOperands (*name->symbol );
101
102
}
@@ -112,14 +113,14 @@ static void genObjectList(const Fortran::parser::OmpObjectList &objectList,
112
113
void createEmptyRegionBlocks (
113
114
fir::FirOpBuilder &firOpBuilder,
114
115
std::list<Fortran::lower::pft::Evaluation> &evaluationList) {
115
- auto *region = &firOpBuilder.getRegion ();
116
- for (auto &eval : evaluationList) {
116
+ mlir::Region *region = &firOpBuilder.getRegion ();
117
+ for (Fortran::lower::pft::Evaluation &eval : evaluationList) {
117
118
if (eval.block ) {
118
119
if (eval.block ->empty ()) {
119
120
eval.block ->erase ();
120
121
eval.block = firOpBuilder.createBlock (region);
121
122
} else {
122
- [[maybe_unused]] auto &terminatorOp = eval.block ->back ();
123
+ [[maybe_unused]] mlir::Operation &terminatorOp = eval.block ->back ();
123
124
assert ((mlir::isa<mlir::omp::TerminatorOp>(terminatorOp) ||
124
125
mlir::isa<mlir::omp::YieldOp>(terminatorOp)) &&
125
126
" expected terminator op" );
@@ -163,22 +164,22 @@ static void createBodyOfOp(
163
164
Fortran::lower::pft::Evaluation &eval,
164
165
const Fortran::parser::OmpClauseList *clauses = nullptr ,
165
166
const SmallVector<const Fortran::semantics::Symbol *> &args = {}) {
166
- auto &firOpBuilder = converter.getFirOpBuilder ();
167
+ fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder ();
167
168
// If an argument for the region is provided then create the block with that
168
169
// argument. Also update the symbol's address with the mlir argument value.
169
170
// e.g. For loops the argument is the induction variable. And all further
170
171
// uses of the induction variable should use this mlir value.
171
172
if (args.size ()) {
172
173
std::uint64_t loopVarTypeSize = 0 ;
173
- for (auto & arg : args)
174
+ for (const Fortran::semantics::Symbol * arg : args)
174
175
loopVarTypeSize = std::max (loopVarTypeSize, arg->GetUltimate ().size ());
175
176
mlir::Type loopVarType = getLoopVarType (converter, loopVarTypeSize);
176
177
SmallVector<Type> tiv;
177
178
for (int i = 0 ; i < (int )args.size (); i++)
178
179
tiv.push_back (loopVarType);
179
180
firOpBuilder.createBlock (&op.getRegion (), {}, tiv);
180
181
int argIndex = 0 ;
181
- for (auto & arg : args) {
182
+ for (const Fortran::semantics::Symbol * arg : args) {
182
183
fir::ExtendedValue exval = op.getRegion ().front ().getArgument (argIndex);
183
184
[[maybe_unused]] bool success = converter.bindSymbol (*arg, exval);
184
185
assert (success && " Existing binding prevents setting MLIR value for the "
@@ -188,7 +189,7 @@ static void createBodyOfOp(
188
189
} else {
189
190
firOpBuilder.createBlock (&op.getRegion ());
190
191
}
191
- auto &block = op.getRegion ().back ();
192
+ mlir::Block &block = op.getRegion ().back ();
192
193
firOpBuilder.setInsertionPointToStart (&block);
193
194
if (eval.lowerAsUnstructured ())
194
195
createEmptyRegionBlocks (firOpBuilder, eval.getNestedEvaluations ());
@@ -277,8 +278,8 @@ template <typename Directive, bool isCombined>
277
278
static void createParallelOp (Fortran::lower::AbstractConverter &converter,
278
279
Fortran::lower::pft::Evaluation &eval,
279
280
const Directive &directive) {
280
- auto &firOpBuilder = converter.getFirOpBuilder ();
281
- auto currentLocation = converter.getCurrentLocation ();
281
+ fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder ();
282
+ mlir::Location currentLocation = converter.getCurrentLocation ();
282
283
Fortran::lower::StatementContext stmtCtx;
283
284
llvm::ArrayRef<mlir::Type> argTy;
284
285
mlir::Value ifClauseOperand, numThreadsClauseOperand;
@@ -288,7 +289,7 @@ static void createParallelOp(Fortran::lower::AbstractConverter &converter,
288
289
Attribute defaultClauseOperand, procBindClauseOperand;
289
290
const auto &opClauseList =
290
291
std::get<Fortran::parser::OmpClauseList>(directive.t );
291
- for (const auto &clause : opClauseList.v ) {
292
+ for (const Fortran::parser::OmpClause &clause : opClauseList.v ) {
292
293
if (const auto &ifClause =
293
294
std::get_if<Fortran::parser::OmpClause::If>(&clause.u )) {
294
295
auto &expr = std::get<Fortran::parser::ScalarLogicalExpr>(ifClause->v .t );
@@ -342,7 +343,7 @@ static void createParallelOp(Fortran::lower::AbstractConverter &converter,
342
343
privateClauseOperands, firstprivateClauseOperands, sharedClauseOperands,
343
344
copyinClauseOperands, allocateOperands, allocatorOperands,
344
345
procBindClauseOperand.dyn_cast_or_null <StringAttr>());
345
- for (const auto &clause : opClauseList.v ) {
346
+ for (const Fortran::parser::OmpClause &clause : opClauseList.v ) {
346
347
if (const auto &defaultClause =
347
348
std::get_if<Fortran::parser::OmpClause::Default>(&clause.u )) {
348
349
const auto &ompDefaultClause{defaultClause->v };
@@ -406,8 +407,8 @@ genOMP(Fortran::lower::AbstractConverter &converter,
406
407
converter, eval,
407
408
std::get<Fortran::parser::OmpBeginBlockDirective>(blockConstruct.t ));
408
409
} else if (blockDirective.v == llvm::omp::OMPD_master) {
409
- auto &firOpBuilder = converter.getFirOpBuilder ();
410
- auto currentLocation = converter.getCurrentLocation ();
410
+ fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder ();
411
+ mlir::Location currentLocation = converter.getCurrentLocation ();
411
412
auto masterOp = firOpBuilder.create <mlir::omp::MasterOp>(currentLocation);
412
413
createBodyOfOp<omp::MasterOp>(masterOp, converter, currentLocation, eval);
413
414
}
@@ -479,7 +480,7 @@ getSIMDModifier(const Fortran::parser::OmpScheduleClause &x) {
479
480
480
481
int64_t Fortran::lower::getCollapseValue (
481
482
const Fortran::parser::OmpClauseList &clauseList) {
482
- for (const auto &clause : clauseList.v ) {
483
+ for (const Fortran::parser::OmpClause &clause : clauseList.v ) {
483
484
if (const auto &collapseClause =
484
485
std::get_if<Fortran::parser::OmpClause::Collapse>(&clause.u )) {
485
486
const auto *expr = Fortran::semantics::GetExpr (collapseClause->v );
@@ -493,8 +494,8 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
493
494
Fortran::lower::pft::Evaluation &eval,
494
495
const Fortran::parser::OpenMPLoopConstruct &loopConstruct) {
495
496
496
- auto &firOpBuilder = converter.getFirOpBuilder ();
497
- auto currentLocation = converter.getCurrentLocation ();
497
+ fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder ();
498
+ mlir::Location currentLocation = converter.getCurrentLocation ();
498
499
SmallVector<Value, 4 > lowerBound, upperBound, step, privateClauseOperands,
499
500
firstPrivateClauseOperands, lastPrivateClauseOperands, linearVars,
500
501
linearStepVars, reductionVars;
@@ -511,7 +512,7 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
511
512
converter, eval,
512
513
std::get<Fortran::parser::OmpBeginLoopDirective>(loopConstruct.t ));
513
514
}
514
- for (const auto &clause : wsLoopOpClauseList.v ) {
515
+ for (const Fortran::parser::OmpClause &clause : wsLoopOpClauseList.v ) {
515
516
if (const auto &lastPrivateClause =
516
517
std::get_if<Fortran::parser::OmpClause::Lastprivate>(&clause.u )) {
517
518
const Fortran::parser::OmpObjectList &ompObjectList =
@@ -520,7 +521,7 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
520
521
}
521
522
}
522
523
523
- for (const auto &clause : wsLoopOpClauseList.v ) {
524
+ for (const Fortran::parser::OmpClause &clause : wsLoopOpClauseList.v ) {
524
525
if (const auto &scheduleClause =
525
526
std::get_if<Fortran::parser::OmpClause::Schedule>(&clause.u )) {
526
527
if (const auto &chunkExpr =
@@ -536,14 +537,16 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
536
537
}
537
538
538
539
// Collect the loops to collapse.
539
- auto *doConstructEval = &eval.getFirstNestedEvaluation ();
540
+ Fortran::lower::pft::Evaluation *doConstructEval =
541
+ &eval.getFirstNestedEvaluation ();
540
542
541
543
std::int64_t collapseValue =
542
544
Fortran::lower::getCollapseValue (wsLoopOpClauseList);
543
545
std::uint64_t loopVarTypeSize = 0 ;
544
546
SmallVector<const Fortran::semantics::Symbol *> iv;
545
547
do {
546
- auto *doLoop = &doConstructEval->getFirstNestedEvaluation ();
548
+ Fortran::lower::pft::Evaluation *doLoop =
549
+ &doConstructEval->getFirstNestedEvaluation ();
547
550
auto *doStmt = doLoop->getIf <Fortran::parser::NonLabelDoStmt>();
548
551
assert (doStmt && " Expected do loop to be in the nested evaluation" );
549
552
const auto &loopControl =
@@ -604,17 +607,19 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
604
607
firOpBuilder.getUnitAttr () /* Inclusive stop */ , false /* buildBody */ );
605
608
606
609
// Handle attribute based clauses.
607
- for (const auto &clause : wsLoopOpClauseList.v ) {
610
+ for (const Fortran::parser::OmpClause &clause : wsLoopOpClauseList.v ) {
608
611
if (const auto &collapseClause =
609
612
std::get_if<Fortran::parser::OmpClause::Collapse>(&clause.u )) {
610
613
const auto *expr = Fortran::semantics::GetExpr (collapseClause->v );
611
- const auto collapseValue = Fortran::evaluate::ToInt64 (*expr);
614
+ const std::optional<std::int64_t > collapseValue =
615
+ Fortran::evaluate::ToInt64 (*expr);
612
616
wsLoopOp.collapse_valAttr (firOpBuilder.getI64IntegerAttr (*collapseValue));
613
617
} else if (const auto &orderedClause =
614
618
std::get_if<Fortran::parser::OmpClause::Ordered>(
615
619
&clause.u )) {
616
620
const auto *expr = Fortran::semantics::GetExpr (orderedClause->v );
617
- const auto orderedValue = Fortran::evaluate::ToInt64 (*expr);
621
+ const std::optional<std::int64_t > orderedValue =
622
+ Fortran::evaluate::ToInt64 (*expr);
618
623
wsLoopOp.ordered_valAttr (firOpBuilder.getI64IntegerAttr (*orderedValue));
619
624
} else if (const auto &scheduleClause =
620
625
std::get_if<Fortran::parser::OmpClause::Schedule>(
@@ -664,7 +669,7 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
664
669
loopConstruct.t )) {
665
670
const auto &clauseList =
666
671
std::get<Fortran::parser::OmpClauseList>((*endClauseList).t );
667
- for (const auto &clause : clauseList.v )
672
+ for (const Fortran::parser::OmpClause &clause : clauseList.v )
668
673
if (std::get_if<Fortran::parser::OmpClause::Nowait>(&clause.u ))
669
674
wsLoopOp.nowaitAttr (firOpBuilder.getUnitAttr ());
670
675
}
@@ -677,8 +682,8 @@ static void
677
682
genOMP (Fortran::lower::AbstractConverter &converter,
678
683
Fortran::lower::pft::Evaluation &eval,
679
684
const Fortran::parser::OpenMPCriticalConstruct &criticalConstruct) {
680
- auto &firOpBuilder = converter.getFirOpBuilder ();
681
- auto currentLocation = converter.getCurrentLocation ();
685
+ fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder ();
686
+ mlir::Location currentLocation = converter.getCurrentLocation ();
682
687
std::string name;
683
688
const Fortran::parser::OmpCriticalDirective &cd =
684
689
std::get<Fortran::parser::OmpCriticalDirective>(criticalConstruct.t );
@@ -689,7 +694,7 @@ genOMP(Fortran::lower::AbstractConverter &converter,
689
694
690
695
uint64_t hint = 0 ;
691
696
const auto &clauseList = std::get<Fortran::parser::OmpClauseList>(cd.t );
692
- for (const auto &clause : clauseList.v )
697
+ for (const Fortran::parser::OmpClause &clause : clauseList.v )
693
698
if (auto hintClause =
694
699
std::get_if<Fortran::parser::OmpClause::Hint>(&clause.u )) {
695
700
const auto *expr = Fortran::semantics::GetExpr (hintClause->v );
@@ -702,7 +707,7 @@ genOMP(Fortran::lower::AbstractConverter &converter,
702
707
return firOpBuilder.create <mlir::omp::CriticalOp>(currentLocation,
703
708
FlatSymbolRefAttr ());
704
709
} else {
705
- auto module = firOpBuilder.getModule ();
710
+ mlir::ModuleOp module = firOpBuilder.getModule ();
706
711
mlir::OpBuilder modBuilder (module .getBodyRegion ());
707
712
auto global = module .lookupSymbol <mlir::omp::CriticalDeclareOp>(name);
708
713
if (!global)
0 commit comments