@@ -37,7 +37,8 @@ static void noRuntimeSupport(mlir::Location loc, llvm::StringRef stmt) {
37
37
// / terminating the current basic block with an unreachable op.
38
38
static void genUnreachable (fir::FirOpBuilder &builder, mlir::Location loc) {
39
39
builder.create <fir::UnreachableOp>(loc);
40
- auto *newBlock = builder.getBlock ()->splitBlock (builder.getInsertionPoint ());
40
+ mlir::Block *newBlock =
41
+ builder.getBlock ()->splitBlock (builder.getInsertionPoint ());
41
42
builder.setInsertionPointToStart (newBlock);
42
43
}
43
44
@@ -48,8 +49,8 @@ static void genUnreachable(fir::FirOpBuilder &builder, mlir::Location loc) {
48
49
void Fortran::lower::genStopStatement (
49
50
Fortran::lower::AbstractConverter &converter,
50
51
const Fortran::parser::StopStmt &stmt) {
51
- auto &builder = converter.getFirOpBuilder ();
52
- auto loc = converter.getCurrentLocation ();
52
+ fir::FirOpBuilder &builder = converter.getFirOpBuilder ();
53
+ mlir::Location loc = converter.getCurrentLocation ();
53
54
Fortran::lower::StatementContext stmtCtx;
54
55
llvm::SmallVector<mlir::Value> operands;
55
56
mlir::FuncOp callee;
@@ -76,7 +77,8 @@ void Fortran::lower::genStopStatement(
76
77
callee = fir::runtime::getRuntimeFunc<mkRTKey (StopStatement)>(
77
78
loc, builder);
78
79
calleeType = callee.getType ();
79
- auto cast = builder.createConvert (loc, calleeType.getInput (0 ), x);
80
+ mlir::Value cast =
81
+ builder.createConvert (loc, calleeType.getInput (0 ), x);
80
82
operands.push_back (cast);
81
83
},
82
84
[&](auto ) {
@@ -101,7 +103,7 @@ void Fortran::lower::genStopStatement(
101
103
std::get<std::optional<Fortran::parser::ScalarLogicalExpr>>(stmt.t )) {
102
104
auto expr = Fortran::semantics::GetExpr (*quiet);
103
105
assert (expr && " failed getting typed expression" );
104
- auto q = fir::getBase (converter.genExprValue (*expr, stmtCtx));
106
+ mlir::Value q = fir::getBase (converter.genExprValue (*expr, stmtCtx));
105
107
operands.push_back (
106
108
builder.createConvert (loc, calleeType.getInput (operands.size ()), q));
107
109
} else {
@@ -115,9 +117,9 @@ void Fortran::lower::genStopStatement(
115
117
116
118
void Fortran::lower::genFailImageStatement (
117
119
Fortran::lower::AbstractConverter &converter) {
118
- auto &builder = converter.getFirOpBuilder ();
119
- auto loc = converter.getCurrentLocation ();
120
- auto callee =
120
+ fir::FirOpBuilder &builder = converter.getFirOpBuilder ();
121
+ mlir::Location loc = converter.getCurrentLocation ();
122
+ mlir::FuncOp callee =
121
123
fir::runtime::getRuntimeFunc<mkRTKey (FailImageStatement)>(loc, builder);
122
124
builder.create <fir::CallOp>(loc, callee, llvm::None);
123
125
genUnreachable (builder, loc);
@@ -182,9 +184,9 @@ void Fortran::lower::genSyncTeamStatement(
182
184
void Fortran::lower::genPauseStatement (
183
185
Fortran::lower::AbstractConverter &converter,
184
186
const Fortran::parser::PauseStmt &) {
185
- auto &builder = converter.getFirOpBuilder ();
186
- auto loc = converter.getCurrentLocation ();
187
- auto callee =
187
+ fir::FirOpBuilder &builder = converter.getFirOpBuilder ();
188
+ mlir::Location loc = converter.getCurrentLocation ();
189
+ mlir::FuncOp callee =
188
190
fir::runtime::getRuntimeFunc<mkRTKey (PauseStatement)>(loc, builder);
189
191
builder.create <fir::CallOp>(loc, callee, llvm::None);
190
192
}
@@ -193,16 +195,18 @@ mlir::Value Fortran::lower::genAssociated(fir::FirOpBuilder &builder,
193
195
mlir::Location loc,
194
196
mlir::Value pointer,
195
197
mlir::Value target) {
196
- auto func = fir::runtime::getRuntimeFunc<mkRTKey (PointerIsAssociatedWith)>(
197
- loc, builder);
198
- auto args = fir::runtime::createArguments (builder, loc, func.getType (),
199
- pointer, target);
198
+ mlir::FuncOp func =
199
+ fir::runtime::getRuntimeFunc<mkRTKey (PointerIsAssociatedWith)>(loc,
200
+ builder);
201
+ llvm::SmallVector<mlir::Value> args = fir::runtime::createArguments (
202
+ builder, loc, func.getType (), pointer, target);
200
203
return builder.create <fir::CallOp>(loc, func, args).getResult (0 );
201
204
}
202
205
203
206
mlir::Value Fortran::lower::genCpuTime (fir::FirOpBuilder &builder,
204
207
mlir::Location loc) {
205
- auto func = fir::runtime::getRuntimeFunc<mkRTKey (CpuTime)>(loc, builder);
208
+ mlir::FuncOp func =
209
+ fir::runtime::getRuntimeFunc<mkRTKey (CpuTime)>(loc, builder);
206
210
return builder.create <fir::CallOp>(loc, func, llvm::None).getResult (0 );
207
211
}
208
212
@@ -212,9 +216,9 @@ void Fortran::lower::genDateAndTime(fir::FirOpBuilder &builder,
212
216
llvm::Optional<fir::CharBoxValue> time,
213
217
llvm::Optional<fir::CharBoxValue> zone,
214
218
mlir::Value values) {
215
- auto callee =
219
+ mlir::FuncOp callee =
216
220
fir::runtime::getRuntimeFunc<mkRTKey (DateAndTime)>(loc, builder);
217
- auto funcTy = callee.getType ();
221
+ mlir::FunctionType funcTy = callee.getType ();
218
222
mlir::Type idxTy = builder.getIndexType ();
219
223
mlir::Value zero;
220
224
auto splitArg = [&](llvm::Optional<fir::CharBoxValue> arg,
@@ -239,11 +243,11 @@ void Fortran::lower::genDateAndTime(fir::FirOpBuilder &builder,
239
243
mlir::Value zoneLen;
240
244
splitArg (zone, zoneBuffer, zoneLen);
241
245
242
- auto sourceFile = fir::factory::locationToFilename (builder, loc);
243
- auto sourceLine =
246
+ mlir::Value sourceFile = fir::factory::locationToFilename (builder, loc);
247
+ mlir::Value sourceLine =
244
248
fir::factory::locationToLineNo (builder, loc, funcTy.getInput (7 ));
245
249
246
- auto args = fir::runtime::createArguments (
250
+ llvm::SmallVector<mlir::Value> args = fir::runtime::createArguments (
247
251
builder, loc, funcTy, dateBuffer, dateLen, timeBuffer, timeLen,
248
252
zoneBuffer, zoneLen, sourceFile, sourceLine, values);
249
253
builder.create <fir::CallOp>(loc, callee, args);
@@ -252,21 +256,23 @@ void Fortran::lower::genDateAndTime(fir::FirOpBuilder &builder,
252
256
void Fortran::lower::genRandomInit (fir::FirOpBuilder &builder,
253
257
mlir::Location loc, mlir::Value repeatable,
254
258
mlir::Value imageDistinct) {
255
- auto func = fir::runtime::getRuntimeFunc<mkRTKey (RandomInit)>(loc, builder);
256
- auto args = fir::runtime::createArguments (builder, loc, func.getType (),
257
- repeatable, imageDistinct);
259
+ mlir::FuncOp func =
260
+ fir::runtime::getRuntimeFunc<mkRTKey (RandomInit)>(loc, builder);
261
+ llvm::SmallVector<mlir::Value> args = fir::runtime::createArguments (
262
+ builder, loc, func.getType (), repeatable, imageDistinct);
258
263
builder.create <fir::CallOp>(loc, func, args);
259
264
}
260
265
261
266
void Fortran::lower::genRandomNumber (fir::FirOpBuilder &builder,
262
267
mlir::Location loc, mlir::Value harvest) {
263
- auto func = fir::runtime::getRuntimeFunc<mkRTKey (RandomNumber)>(loc, builder);
264
- auto funcTy = func.getType ();
265
- auto sourceFile = fir::factory::locationToFilename (builder, loc);
266
- auto sourceLine =
268
+ mlir::FuncOp func =
269
+ fir::runtime::getRuntimeFunc<mkRTKey (RandomNumber)>(loc, builder);
270
+ mlir::FunctionType funcTy = func.getType ();
271
+ mlir::Value sourceFile = fir::factory::locationToFilename (builder, loc);
272
+ mlir::Value sourceLine =
267
273
fir::factory::locationToLineNo (builder, loc, funcTy.getInput (2 ));
268
- auto args = fir::runtime::createArguments (builder, loc, funcTy, harvest,
269
- sourceFile, sourceLine);
274
+ llvm::SmallVector<mlir::Value> args = fir::runtime::createArguments (
275
+ builder, loc, funcTy, harvest, sourceFile, sourceLine);
270
276
builder.create <fir::CallOp>(loc, func, args);
271
277
}
272
278
@@ -294,12 +300,12 @@ void Fortran::lower::genRandomSeed(fir::FirOpBuilder &builder,
294
300
default :
295
301
llvm::report_fatal_error (" invalid RANDOM_SEED argument index" );
296
302
}
297
- auto funcTy = func.getType ();
298
- auto sourceFile = fir::factory::locationToFilename (builder, loc);
299
- auto sourceLine =
303
+ mlir::FunctionType funcTy = func.getType ();
304
+ mlir::Value sourceFile = fir::factory::locationToFilename (builder, loc);
305
+ mlir::Value sourceLine =
300
306
fir::factory::locationToLineNo (builder, loc, funcTy.getInput (2 ));
301
- auto args = fir::runtime::createArguments (builder, loc, funcTy, argBox,
302
- sourceFile, sourceLine);
307
+ llvm::SmallVector<mlir::Value> args = fir::runtime::createArguments (
308
+ builder, loc, funcTy, argBox, sourceFile, sourceLine);
303
309
builder.create <fir::CallOp>(loc, func, args);
304
310
}
305
311
@@ -308,12 +314,13 @@ void Fortran::lower::genTransfer(fir::FirOpBuilder &builder, mlir::Location loc,
308
314
mlir::Value resultBox, mlir::Value sourceBox,
309
315
mlir::Value moldBox) {
310
316
311
- auto func = fir::runtime::getRuntimeFunc<mkRTKey (Transfer)>(loc, builder);
312
- auto fTy = func.getType ();
313
- auto sourceFile = fir::factory::locationToFilename (builder, loc);
314
- auto sourceLine =
317
+ mlir::FuncOp func =
318
+ fir::runtime::getRuntimeFunc<mkRTKey (Transfer)>(loc, builder);
319
+ mlir::FunctionType fTy = func.getType ();
320
+ mlir::Value sourceFile = fir::factory::locationToFilename (builder, loc);
321
+ mlir::Value sourceLine =
315
322
fir::factory::locationToLineNo (builder, loc, fTy .getInput (4 ));
316
- auto args = fir::runtime::createArguments (
323
+ llvm::SmallVector<mlir::Value> args = fir::runtime::createArguments (
317
324
builder, loc, fTy , resultBox, sourceBox, moldBox, sourceFile, sourceLine);
318
325
builder.create <fir::CallOp>(loc, func, args);
319
326
}
@@ -323,12 +330,13 @@ void Fortran::lower::genTransferSize(fir::FirOpBuilder &builder,
323
330
mlir::Location loc, mlir::Value resultBox,
324
331
mlir::Value sourceBox, mlir::Value moldBox,
325
332
mlir::Value size) {
326
- auto func = fir::runtime::getRuntimeFunc<mkRTKey (TransferSize)>(loc, builder);
327
- auto fTy = func.getType ();
328
- auto sourceFile = fir::factory::locationToFilename (builder, loc);
329
- auto sourceLine =
333
+ mlir::FuncOp func =
334
+ fir::runtime::getRuntimeFunc<mkRTKey (TransferSize)>(loc, builder);
335
+ mlir::FunctionType fTy = func.getType ();
336
+ mlir::Value sourceFile = fir::factory::locationToFilename (builder, loc);
337
+ mlir::Value sourceLine =
330
338
fir::factory::locationToLineNo (builder, loc, fTy .getInput (4 ));
331
- auto args =
339
+ llvm::SmallVector<mlir::Value> args =
332
340
fir::runtime::createArguments (builder, loc, fTy , resultBox, sourceBox,
333
341
moldBox, sourceFile, sourceLine, size);
334
342
builder.create <fir::CallOp>(loc, func, args);
@@ -340,12 +348,12 @@ void Fortran::lower::genSystemClock(fir::FirOpBuilder &builder,
340
348
mlir::Location loc, mlir::Value count,
341
349
mlir::Value rate, mlir::Value max) {
342
350
auto makeCall = [&](mlir::FuncOp func, mlir::Value arg) {
343
- auto kindTy = func.getType ().getInput (0 );
351
+ mlir::Type kindTy = func.getType ().getInput (0 );
344
352
int integerKind = 8 ;
345
353
if (auto intType =
346
354
fir::unwrapRefType (arg.getType ()).dyn_cast <mlir::IntegerType>())
347
355
integerKind = intType.getWidth () / 8 ;
348
- auto kind = builder.createIntegerConstant (loc, kindTy, integerKind);
356
+ mlir::Value kind = builder.createIntegerConstant (loc, kindTy, integerKind);
349
357
mlir::Value res =
350
358
builder.create <fir::CallOp>(loc, func, mlir::ValueRange{kind})
351
359
.getResult (0 );
0 commit comments