Skip to content

Commit 916ef33

Browse files
authored
Review usage of auto in Lower/OpenMP.cpp (#1308)
1 parent b348545 commit 916ef33

File tree

1 file changed

+40
-35
lines changed

1 file changed

+40
-35
lines changed

flang/lib/Lower/OpenMP.cpp

Lines changed: 40 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -34,11 +34,12 @@ static void createPrivateVarSyms(Fortran::lower::AbstractConverter &converter,
3434
const T *clause) {
3535
Fortran::semantics::Symbol *sym = nullptr;
3636
const Fortran::parser::OmpObjectList &ompObjectList = clause->v;
37-
for (const auto &ompObject : ompObjectList.v) {
37+
for (const Fortran::parser::OmpObject &ompObject : ompObjectList.v) {
3838
std::visit(
3939
Fortran::common::visitors{
4040
[&](const Fortran::parser::Designator &designator) {
41-
if (const auto *name = getDesignatorNameIfDataRef(designator)) {
41+
if (const Fortran::parser::Name *name =
42+
getDesignatorNameIfDataRef(designator)) {
4243
sym = name->symbol;
4344
}
4445
},
@@ -61,10 +62,10 @@ static void createPrivateVarSyms(Fortran::lower::AbstractConverter &converter,
6162

6263
static void privatizeVars(Fortran::lower::AbstractConverter &converter,
6364
const Fortran::parser::OmpClauseList &opClauseList) {
64-
auto &firOpBuilder = converter.getFirOpBuilder();
65+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
6566
auto insPt = firOpBuilder.saveInsertionPoint();
6667
firOpBuilder.setInsertionPointToStart(firOpBuilder.getAllocaBlock());
67-
for (const auto &clause : opClauseList.v) {
68+
for (const Fortran::parser::OmpClause &clause : opClauseList.v) {
6869
if (const auto &privateClause =
6970
std::get_if<Fortran::parser::OmpClause::Private>(&clause.u)) {
7071
createPrivateVarSyms(converter, privateClause);
@@ -81,7 +82,7 @@ static void genObjectList(const Fortran::parser::OmpObjectList &objectList,
8182
Fortran::lower::AbstractConverter &converter,
8283
SmallVectorImpl<Value> &operands) {
8384
auto addOperands = [&](Fortran::lower::SymbolRef sym) {
84-
const auto variable = converter.getSymbolAddress(sym);
85+
const mlir::Value variable = converter.getSymbolAddress(sym);
8586
if (variable) {
8687
operands.push_back(variable);
8788
} else {
@@ -92,10 +93,10 @@ static void genObjectList(const Fortran::parser::OmpObjectList &objectList,
9293
}
9394
}
9495
};
95-
for (const auto &ompObject : objectList.v) {
96+
for (const Fortran::parser::OmpObject &ompObject : objectList.v) {
9697
std::visit(Fortran::common::visitors{
9798
[&](const Fortran::parser::Designator &designator) {
98-
if (const auto *name =
99+
if (const Fortran::parser::Name *name =
99100
getDesignatorNameIfDataRef(designator)) {
100101
addOperands(*name->symbol);
101102
}
@@ -112,14 +113,14 @@ static void genObjectList(const Fortran::parser::OmpObjectList &objectList,
112113
void createEmptyRegionBlocks(
113114
fir::FirOpBuilder &firOpBuilder,
114115
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) {
117118
if (eval.block) {
118119
if (eval.block->empty()) {
119120
eval.block->erase();
120121
eval.block = firOpBuilder.createBlock(region);
121122
} else {
122-
[[maybe_unused]] auto &terminatorOp = eval.block->back();
123+
[[maybe_unused]] mlir::Operation &terminatorOp = eval.block->back();
123124
assert((mlir::isa<mlir::omp::TerminatorOp>(terminatorOp) ||
124125
mlir::isa<mlir::omp::YieldOp>(terminatorOp)) &&
125126
"expected terminator op");
@@ -163,22 +164,22 @@ static void createBodyOfOp(
163164
Fortran::lower::pft::Evaluation &eval,
164165
const Fortran::parser::OmpClauseList *clauses = nullptr,
165166
const SmallVector<const Fortran::semantics::Symbol *> &args = {}) {
166-
auto &firOpBuilder = converter.getFirOpBuilder();
167+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
167168
// If an argument for the region is provided then create the block with that
168169
// argument. Also update the symbol's address with the mlir argument value.
169170
// e.g. For loops the argument is the induction variable. And all further
170171
// uses of the induction variable should use this mlir value.
171172
if (args.size()) {
172173
std::uint64_t loopVarTypeSize = 0;
173-
for (auto &arg : args)
174+
for (const Fortran::semantics::Symbol *arg : args)
174175
loopVarTypeSize = std::max(loopVarTypeSize, arg->GetUltimate().size());
175176
mlir::Type loopVarType = getLoopVarType(converter, loopVarTypeSize);
176177
SmallVector<Type> tiv;
177178
for (int i = 0; i < (int)args.size(); i++)
178179
tiv.push_back(loopVarType);
179180
firOpBuilder.createBlock(&op.getRegion(), {}, tiv);
180181
int argIndex = 0;
181-
for (auto &arg : args) {
182+
for (const Fortran::semantics::Symbol *arg : args) {
182183
fir::ExtendedValue exval = op.getRegion().front().getArgument(argIndex);
183184
[[maybe_unused]] bool success = converter.bindSymbol(*arg, exval);
184185
assert(success && "Existing binding prevents setting MLIR value for the "
@@ -188,7 +189,7 @@ static void createBodyOfOp(
188189
} else {
189190
firOpBuilder.createBlock(&op.getRegion());
190191
}
191-
auto &block = op.getRegion().back();
192+
mlir::Block &block = op.getRegion().back();
192193
firOpBuilder.setInsertionPointToStart(&block);
193194
if (eval.lowerAsUnstructured())
194195
createEmptyRegionBlocks(firOpBuilder, eval.getNestedEvaluations());
@@ -277,8 +278,8 @@ template <typename Directive, bool isCombined>
277278
static void createParallelOp(Fortran::lower::AbstractConverter &converter,
278279
Fortran::lower::pft::Evaluation &eval,
279280
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();
282283
Fortran::lower::StatementContext stmtCtx;
283284
llvm::ArrayRef<mlir::Type> argTy;
284285
mlir::Value ifClauseOperand, numThreadsClauseOperand;
@@ -288,7 +289,7 @@ static void createParallelOp(Fortran::lower::AbstractConverter &converter,
288289
Attribute defaultClauseOperand, procBindClauseOperand;
289290
const auto &opClauseList =
290291
std::get<Fortran::parser::OmpClauseList>(directive.t);
291-
for (const auto &clause : opClauseList.v) {
292+
for (const Fortran::parser::OmpClause &clause : opClauseList.v) {
292293
if (const auto &ifClause =
293294
std::get_if<Fortran::parser::OmpClause::If>(&clause.u)) {
294295
auto &expr = std::get<Fortran::parser::ScalarLogicalExpr>(ifClause->v.t);
@@ -342,7 +343,7 @@ static void createParallelOp(Fortran::lower::AbstractConverter &converter,
342343
privateClauseOperands, firstprivateClauseOperands, sharedClauseOperands,
343344
copyinClauseOperands, allocateOperands, allocatorOperands,
344345
procBindClauseOperand.dyn_cast_or_null<StringAttr>());
345-
for (const auto &clause : opClauseList.v) {
346+
for (const Fortran::parser::OmpClause &clause : opClauseList.v) {
346347
if (const auto &defaultClause =
347348
std::get_if<Fortran::parser::OmpClause::Default>(&clause.u)) {
348349
const auto &ompDefaultClause{defaultClause->v};
@@ -406,8 +407,8 @@ genOMP(Fortran::lower::AbstractConverter &converter,
406407
converter, eval,
407408
std::get<Fortran::parser::OmpBeginBlockDirective>(blockConstruct.t));
408409
} 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();
411412
auto masterOp = firOpBuilder.create<mlir::omp::MasterOp>(currentLocation);
412413
createBodyOfOp<omp::MasterOp>(masterOp, converter, currentLocation, eval);
413414
}
@@ -479,7 +480,7 @@ getSIMDModifier(const Fortran::parser::OmpScheduleClause &x) {
479480

480481
int64_t Fortran::lower::getCollapseValue(
481482
const Fortran::parser::OmpClauseList &clauseList) {
482-
for (const auto &clause : clauseList.v) {
483+
for (const Fortran::parser::OmpClause &clause : clauseList.v) {
483484
if (const auto &collapseClause =
484485
std::get_if<Fortran::parser::OmpClause::Collapse>(&clause.u)) {
485486
const auto *expr = Fortran::semantics::GetExpr(collapseClause->v);
@@ -493,8 +494,8 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
493494
Fortran::lower::pft::Evaluation &eval,
494495
const Fortran::parser::OpenMPLoopConstruct &loopConstruct) {
495496

496-
auto &firOpBuilder = converter.getFirOpBuilder();
497-
auto currentLocation = converter.getCurrentLocation();
497+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
498+
mlir::Location currentLocation = converter.getCurrentLocation();
498499
SmallVector<Value, 4> lowerBound, upperBound, step, privateClauseOperands,
499500
firstPrivateClauseOperands, lastPrivateClauseOperands, linearVars,
500501
linearStepVars, reductionVars;
@@ -511,7 +512,7 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
511512
converter, eval,
512513
std::get<Fortran::parser::OmpBeginLoopDirective>(loopConstruct.t));
513514
}
514-
for (const auto &clause : wsLoopOpClauseList.v) {
515+
for (const Fortran::parser::OmpClause &clause : wsLoopOpClauseList.v) {
515516
if (const auto &lastPrivateClause =
516517
std::get_if<Fortran::parser::OmpClause::Lastprivate>(&clause.u)) {
517518
const Fortran::parser::OmpObjectList &ompObjectList =
@@ -520,7 +521,7 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
520521
}
521522
}
522523

523-
for (const auto &clause : wsLoopOpClauseList.v) {
524+
for (const Fortran::parser::OmpClause &clause : wsLoopOpClauseList.v) {
524525
if (const auto &scheduleClause =
525526
std::get_if<Fortran::parser::OmpClause::Schedule>(&clause.u)) {
526527
if (const auto &chunkExpr =
@@ -536,14 +537,16 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
536537
}
537538

538539
// Collect the loops to collapse.
539-
auto *doConstructEval = &eval.getFirstNestedEvaluation();
540+
Fortran::lower::pft::Evaluation *doConstructEval =
541+
&eval.getFirstNestedEvaluation();
540542

541543
std::int64_t collapseValue =
542544
Fortran::lower::getCollapseValue(wsLoopOpClauseList);
543545
std::uint64_t loopVarTypeSize = 0;
544546
SmallVector<const Fortran::semantics::Symbol *> iv;
545547
do {
546-
auto *doLoop = &doConstructEval->getFirstNestedEvaluation();
548+
Fortran::lower::pft::Evaluation *doLoop =
549+
&doConstructEval->getFirstNestedEvaluation();
547550
auto *doStmt = doLoop->getIf<Fortran::parser::NonLabelDoStmt>();
548551
assert(doStmt && "Expected do loop to be in the nested evaluation");
549552
const auto &loopControl =
@@ -604,17 +607,19 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
604607
firOpBuilder.getUnitAttr() /* Inclusive stop */, false /* buildBody */);
605608

606609
// Handle attribute based clauses.
607-
for (const auto &clause : wsLoopOpClauseList.v) {
610+
for (const Fortran::parser::OmpClause &clause : wsLoopOpClauseList.v) {
608611
if (const auto &collapseClause =
609612
std::get_if<Fortran::parser::OmpClause::Collapse>(&clause.u)) {
610613
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);
612616
wsLoopOp.collapse_valAttr(firOpBuilder.getI64IntegerAttr(*collapseValue));
613617
} else if (const auto &orderedClause =
614618
std::get_if<Fortran::parser::OmpClause::Ordered>(
615619
&clause.u)) {
616620
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);
618623
wsLoopOp.ordered_valAttr(firOpBuilder.getI64IntegerAttr(*orderedValue));
619624
} else if (const auto &scheduleClause =
620625
std::get_if<Fortran::parser::OmpClause::Schedule>(
@@ -664,7 +669,7 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
664669
loopConstruct.t)) {
665670
const auto &clauseList =
666671
std::get<Fortran::parser::OmpClauseList>((*endClauseList).t);
667-
for (const auto &clause : clauseList.v)
672+
for (const Fortran::parser::OmpClause &clause : clauseList.v)
668673
if (std::get_if<Fortran::parser::OmpClause::Nowait>(&clause.u))
669674
wsLoopOp.nowaitAttr(firOpBuilder.getUnitAttr());
670675
}
@@ -677,8 +682,8 @@ static void
677682
genOMP(Fortran::lower::AbstractConverter &converter,
678683
Fortran::lower::pft::Evaluation &eval,
679684
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();
682687
std::string name;
683688
const Fortran::parser::OmpCriticalDirective &cd =
684689
std::get<Fortran::parser::OmpCriticalDirective>(criticalConstruct.t);
@@ -689,7 +694,7 @@ genOMP(Fortran::lower::AbstractConverter &converter,
689694

690695
uint64_t hint = 0;
691696
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)
693698
if (auto hintClause =
694699
std::get_if<Fortran::parser::OmpClause::Hint>(&clause.u)) {
695700
const auto *expr = Fortran::semantics::GetExpr(hintClause->v);
@@ -702,7 +707,7 @@ genOMP(Fortran::lower::AbstractConverter &converter,
702707
return firOpBuilder.create<mlir::omp::CriticalOp>(currentLocation,
703708
FlatSymbolRefAttr());
704709
} else {
705-
auto module = firOpBuilder.getModule();
710+
mlir::ModuleOp module = firOpBuilder.getModule();
706711
mlir::OpBuilder modBuilder(module.getBodyRegion());
707712
auto global = module.lookupSymbol<mlir::omp::CriticalDeclareOp>(name);
708713
if (!global)

0 commit comments

Comments
 (0)