Skip to content

Commit 388eb4d

Browse files
authored
[flang] Review usage of auto in Lower/OpenACC.cpp (#1299)
1 parent cbdad4d commit 388eb4d

File tree

1 file changed

+38
-36
lines changed

1 file changed

+38
-36
lines changed

flang/lib/Lower/OpenACC.cpp

Lines changed: 38 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@ static void genObjectList(const Fortran::parser::AccObjectList &objectList,
4646
operands.push_back(converter.getSymbolAddress(details->symbol()));
4747
}
4848
};
49-
for (const auto &accObject : objectList.v) {
49+
for (const Fortran::parser::AccObject &accObject : objectList.v) {
5050
std::visit(Fortran::common::visitors{
5151
[&](const Fortran::parser::Designator &designator) {
5252
if (const auto *name =
@@ -106,7 +106,7 @@ static Op createRegionOp(fir::FirOpBuilder &builder, mlir::Location loc,
106106
llvm::ArrayRef<mlir::Type> argTy;
107107
Op op = builder.create<Op>(loc, argTy, operands);
108108
builder.createBlock(&op.getRegion());
109-
auto &block = op.getRegion().back();
109+
mlir::Block &block = op.getRegion().back();
110110
builder.setInsertionPointToStart(&block);
111111
builder.create<Terminator>(loc);
112112

@@ -156,7 +156,7 @@ static void genDeviceTypeClause(
156156
operands.push_back(expr);
157157
}
158158
} else {
159-
auto &firOpBuilder = converter.getFirOpBuilder();
159+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
160160
// * was passed as value and will be represented as a special constant.
161161
mlir::Value star = firOpBuilder.createIntegerConstant(
162162
converter.getCurrentLocation(), firOpBuilder.getIndexType(), starCst);
@@ -168,7 +168,7 @@ static void genIfClause(Fortran::lower::AbstractConverter &converter,
168168
const Fortran::parser::AccClause::If *ifClause,
169169
mlir::Value &ifCond,
170170
Fortran::lower::StatementContext &stmtCtx) {
171-
auto &firOpBuilder = converter.getFirOpBuilder();
171+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
172172
Value cond = fir::getBase(converter.genExprValue(
173173
*Fortran::semantics::GetExpr(ifClause->v), stmtCtx));
174174
ifCond = firOpBuilder.createConvert(converter.getCurrentLocation(),
@@ -204,8 +204,8 @@ static void genWaitClause(Fortran::lower::AbstractConverter &converter,
204204
static mlir::acc::LoopOp
205205
createLoopOp(Fortran::lower::AbstractConverter &converter,
206206
const Fortran::parser::AccClauseList &accClauseList) {
207-
auto &firOpBuilder = converter.getFirOpBuilder();
208-
auto currentLocation = converter.getCurrentLocation();
207+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
208+
mlir::Location currentLocation = converter.getCurrentLocation();
209209
Fortran::lower::StatementContext stmtCtx;
210210

211211
mlir::Value workerNum;
@@ -215,7 +215,7 @@ createLoopOp(Fortran::lower::AbstractConverter &converter,
215215
SmallVector<mlir::Value, 2> tileOperands, privateOperands, reductionOperands;
216216
std::int64_t executionMapping = mlir::acc::OpenACCExecMapping::NONE;
217217

218-
for (const auto &clause : accClauseList.v) {
218+
for (const Fortran::parser::AccClause &clause : accClauseList.v) {
219219
if (const auto *gangClause =
220220
std::get_if<Fortran::parser::AccClause::Gang>(&clause.u)) {
221221
if (gangClause->v) {
@@ -302,11 +302,12 @@ createLoopOp(Fortran::lower::AbstractConverter &converter,
302302
firOpBuilder.getI64IntegerAttr(executionMapping));
303303

304304
// Lower clauses mapped to attributes
305-
for (const auto &clause : accClauseList.v) {
305+
for (const Fortran::parser::AccClause &clause : accClauseList.v) {
306306
if (const auto *collapseClause =
307307
std::get_if<Fortran::parser::AccClause::Collapse>(&clause.u)) {
308308
const auto *expr = Fortran::semantics::GetExpr(collapseClause->v);
309-
const auto collapseValue = Fortran::evaluate::ToInt64(*expr);
309+
const std::optional<int64_t> collapseValue =
310+
Fortran::evaluate::ToInt64(*expr);
310311
if (collapseValue) {
311312
loopOp->setAttr(mlir::acc::LoopOp::getCollapseAttrName(),
312313
firOpBuilder.getI64IntegerAttr(*collapseValue));
@@ -367,14 +368,14 @@ createParallelOp(Fortran::lower::AbstractConverter &converter,
367368
bool addWaitAttr = false;
368369
bool addSelfAttr = false;
369370

370-
auto &firOpBuilder = converter.getFirOpBuilder();
371-
auto currentLocation = converter.getCurrentLocation();
371+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
372+
mlir::Location currentLocation = converter.getCurrentLocation();
372373
Fortran::lower::StatementContext stmtCtx;
373374

374375
// Lower clauses values mapped to operands.
375376
// Keep track of each group of operands separatly as clauses can appear
376377
// more than once.
377-
for (const auto &clause : accClauseList.v) {
378+
for (const Fortran::parser::AccClause &clause : accClauseList.v) {
378379
if (const auto *asyncClause =
379380
std::get_if<Fortran::parser::AccClause::Async>(&clause.u)) {
380381
genAsyncClause(converter, asyncClause, async, addAsyncAttr, stmtCtx);
@@ -407,7 +408,7 @@ createParallelOp(Fortran::lower::AbstractConverter &converter,
407408
std::get_if<std::optional<Fortran::parser::ScalarLogicalExpr>>(
408409
&accSelfClause.u)) {
409410
if (*optCondition) {
410-
auto cond = fir::getBase(converter.genExprValue(
411+
mlir::Value cond = fir::getBase(converter.genExprValue(
411412
*Fortran::semantics::GetExpr(*optCondition), stmtCtx));
412413
selfCond = firOpBuilder.createConvert(currentLocation,
413414
firOpBuilder.getI1Type(), cond);
@@ -503,7 +504,8 @@ createParallelOp(Fortran::lower::AbstractConverter &converter,
503504
addOperands(operands, operandSegments, privateOperands);
504505
addOperands(operands, operandSegments, firstprivateOperands);
505506

506-
auto parallelOp = createRegionOp<mlir::acc::ParallelOp, mlir::acc::YieldOp>(
507+
mlir::acc::ParallelOp parallelOp =
508+
createRegionOp<mlir::acc::ParallelOp, mlir::acc::YieldOp>(
507509
firOpBuilder, currentLocation, operands, operandSegments);
508510

509511
if (addAsyncAttr)
@@ -533,14 +535,14 @@ static void genACCDataOp(Fortran::lower::AbstractConverter &converter,
533535
createOperands, createZeroOperands, noCreateOperands, presentOperands,
534536
deviceptrOperands, attachOperands;
535537

536-
auto &firOpBuilder = converter.getFirOpBuilder();
537-
auto currentLocation = converter.getCurrentLocation();
538+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
539+
mlir::Location currentLocation = converter.getCurrentLocation();
538540
Fortran::lower::StatementContext stmtCtx;
539541

540542
// Lower clauses values mapped to operands.
541543
// Keep track of each group of operands separatly as clauses can appear
542544
// more than once.
543-
for (const auto &clause : accClauseList.v) {
545+
for (const Fortran::parser::AccClause &clause : accClauseList.v) {
544546
if (const auto *ifClause =
545547
std::get_if<Fortran::parser::AccClause::If>(&clause.u)) {
546548
genIfClause(converter, ifClause, ifCond, stmtCtx);
@@ -667,14 +669,14 @@ genACCEnterDataOp(Fortran::lower::AbstractConverter &converter,
667669
bool addAsyncAttr = false;
668670
bool addWaitAttr = false;
669671

670-
auto &firOpBuilder = converter.getFirOpBuilder();
671-
auto currentLocation = converter.getCurrentLocation();
672+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
673+
mlir::Location currentLocation = converter.getCurrentLocation();
672674
Fortran::lower::StatementContext stmtCtx;
673675

674676
// Lower clauses values mapped to operands.
675677
// Keep track of each group of operands separatly as clauses can appear
676678
// more than once.
677-
for (const auto &clause : accClauseList.v) {
679+
for (const Fortran::parser::AccClause &clause : accClauseList.v) {
678680
if (const auto *ifClause =
679681
std::get_if<Fortran::parser::AccClause::If>(&clause.u)) {
680682
genIfClause(converter, ifClause, ifCond, stmtCtx);
@@ -719,7 +721,7 @@ genACCEnterDataOp(Fortran::lower::AbstractConverter &converter,
719721
addOperands(operands, operandSegments, createZeroOperands);
720722
addOperands(operands, operandSegments, attachOperands);
721723

722-
auto enterDataOp = createSimpleOp<mlir::acc::EnterDataOp>(
724+
mlir::acc::EnterDataOp enterDataOp = createSimpleOp<mlir::acc::EnterDataOp>(
723725
firOpBuilder, currentLocation, operands, operandSegments);
724726

725727
if (addAsyncAttr)
@@ -742,14 +744,14 @@ genACCExitDataOp(Fortran::lower::AbstractConverter &converter,
742744
bool addWaitAttr = false;
743745
bool addFinalizeAttr = false;
744746

745-
auto &firOpBuilder = converter.getFirOpBuilder();
746-
auto currentLocation = converter.getCurrentLocation();
747+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
748+
mlir::Location currentLocation = converter.getCurrentLocation();
747749
Fortran::lower::StatementContext stmtCtx;
748750

749751
// Lower clauses values mapped to operands.
750752
// Keep track of each group of operands separatly as clauses can appear
751753
// more than once.
752-
for (const auto &clause : accClauseList.v) {
754+
for (const Fortran::parser::AccClause &clause : accClauseList.v) {
753755
if (const auto *ifClause =
754756
std::get_if<Fortran::parser::AccClause::If>(&clause.u)) {
755757
genIfClause(converter, ifClause, ifCond, stmtCtx);
@@ -790,7 +792,7 @@ genACCExitDataOp(Fortran::lower::AbstractConverter &converter,
790792
addOperands(operands, operandSegments, deleteOperands);
791793
addOperands(operands, operandSegments, detachOperands);
792794

793-
auto exitDataOp = createSimpleOp<mlir::acc::ExitDataOp>(
795+
mlir::acc::ExitDataOp exitDataOp = createSimpleOp<mlir::acc::ExitDataOp>(
794796
firOpBuilder, currentLocation, operands, operandSegments);
795797

796798
if (addAsyncAttr)
@@ -808,14 +810,14 @@ genACCInitShutdownOp(Fortran::lower::AbstractConverter &converter,
808810
mlir::Value ifCond, deviceNum;
809811
SmallVector<mlir::Value, 2> deviceTypeOperands;
810812

811-
auto &firOpBuilder = converter.getFirOpBuilder();
812-
auto currentLocation = converter.getCurrentLocation();
813+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
814+
mlir::Location currentLocation = converter.getCurrentLocation();
813815
Fortran::lower::StatementContext stmtCtx;
814816

815817
// Lower clauses values mapped to operands.
816818
// Keep track of each group of operands separatly as clauses can appear
817819
// more than once.
818-
for (const auto &clause : accClauseList.v) {
820+
for (const Fortran::parser::AccClause &clause : accClauseList.v) {
819821
if (const auto *ifClause =
820822
std::get_if<Fortran::parser::AccClause::If>(&clause.u)) {
821823
genIfClause(converter, ifClause, ifCond, stmtCtx);
@@ -856,14 +858,14 @@ genACCUpdateOp(Fortran::lower::AbstractConverter &converter,
856858
bool addWaitAttr = false;
857859
bool addIfPresentAttr = false;
858860

859-
auto &firOpBuilder = converter.getFirOpBuilder();
860-
auto currentLocation = converter.getCurrentLocation();
861+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
862+
mlir::Location currentLocation = converter.getCurrentLocation();
861863
Fortran::lower::StatementContext stmtCtx;
862864

863865
// Lower clauses values mapped to operands.
864866
// Keep track of each group of operands separatly as clauses can appear
865867
// more than once.
866-
for (const auto &clause : accClauseList.v) {
868+
for (const Fortran::parser::AccClause &clause : accClauseList.v) {
867869
if (const auto *ifClause =
868870
std::get_if<Fortran::parser::AccClause::If>(&clause.u)) {
869871
genIfClause(converter, ifClause, ifCond, stmtCtx);
@@ -899,7 +901,7 @@ genACCUpdateOp(Fortran::lower::AbstractConverter &converter,
899901
addOperands(operands, operandSegments, hostOperands);
900902
addOperands(operands, operandSegments, deviceOperands);
901903

902-
auto updateOp = createSimpleOp<mlir::acc::UpdateOp>(
904+
mlir::acc::UpdateOp updateOp = createSimpleOp<mlir::acc::UpdateOp>(
903905
firOpBuilder, currentLocation, operands, operandSegments);
904906

905907
if (addAsyncAttr)
@@ -952,8 +954,8 @@ static void genACC(Fortran::lower::AbstractConverter &converter,
952954
// represent the clause.
953955
bool addAsyncAttr = false;
954956

955-
auto &firOpBuilder = converter.getFirOpBuilder();
956-
auto currentLocation = converter.getCurrentLocation();
957+
fir::FirOpBuilder &firOpBuilder = converter.getFirOpBuilder();
958+
mlir::Location currentLocation = converter.getCurrentLocation();
957959
Fortran::lower::StatementContext stmtCtx;
958960

959961
if (waitArgument) { // wait has a value.
@@ -976,7 +978,7 @@ static void genACC(Fortran::lower::AbstractConverter &converter,
976978
// Lower clauses values mapped to operands.
977979
// Keep track of each group of operands separatly as clauses can appear
978980
// more than once.
979-
for (const auto &clause : accClauseList.v) {
981+
for (const Fortran::parser::AccClause &clause : accClauseList.v) {
980982
if (const auto *ifClause =
981983
std::get_if<Fortran::parser::AccClause::If>(&clause.u)) {
982984
genIfClause(converter, ifClause, ifCond, stmtCtx);
@@ -994,7 +996,7 @@ static void genACC(Fortran::lower::AbstractConverter &converter,
994996
addOperand(operands, operandSegments, waitDevnum);
995997
addOperand(operands, operandSegments, ifCond);
996998

997-
auto waitOp = createSimpleOp<mlir::acc::WaitOp>(firOpBuilder, currentLocation,
999+
mlir::acc::WaitOp waitOp = createSimpleOp<mlir::acc::WaitOp>(firOpBuilder, currentLocation,
9981000
operands, operandSegments);
9991001

10001002
if (addAsyncAttr)

0 commit comments

Comments
 (0)