Skip to content

Commit 41f237a

Browse files
committed
Merge branch 'sam3' into fir-dev
2 parents c8f3f05 + 4dea57f commit 41f237a

File tree

3 files changed

+112
-18
lines changed

3 files changed

+112
-18
lines changed

flang/lib/Lower/Bridge.cpp

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -788,11 +788,12 @@ class FirConverter : public Fortran::lower::AbstractConverter {
788788
info.isStructured() ? builder->getIndexType() : info.loopVariableType;
789789
auto lowerValue = genFIRLoopIndex(info.lowerExpr, type);
790790
auto upperValue = genFIRLoopIndex(info.upperExpr, type);
791-
info.stepValue =
792-
info.stepExpr.has_value() ? genFIRLoopIndex(*info.stepExpr, type)
793-
: info.isStructured()
794-
? builder->create<mlir::ConstantIndexOp>(loc, 1)
795-
: builder->createIntegerConstant(loc, info.loopVariableType, 1);
791+
info.stepValue = info.stepExpr.has_value()
792+
? genFIRLoopIndex(*info.stepExpr, type)
793+
: info.isStructured()
794+
? builder->create<mlir::ConstantIndexOp>(loc, 1)
795+
: builder->createIntegerConstant(
796+
loc, info.loopVariableType, 1);
796797
assert(info.stepValue && "step value must be set");
797798
info.loopVariable = createTemp(loc, *info.loopVariableSym);
798799

@@ -1106,9 +1107,9 @@ class FirConverter : public Fortran::lower::AbstractConverter {
11061107
}
11071108
void genFIR(const Fortran::parser::InquireStmt &stmt) {
11081109
auto iostat = genInquireStatement(*this, stmt);
1109-
genIoConditionBranches(
1110-
getEval(), std::get<std::list<Fortran::parser::InquireSpec>>(stmt.u),
1111-
iostat);
1110+
if (const auto *specs =
1111+
std::get_if<std::list<Fortran::parser::InquireSpec>>(&stmt.u))
1112+
genIoConditionBranches(getEval(), *specs, iostat);
11121113
}
11131114
void genFIR(const Fortran::parser::OpenStmt &stmt) {
11141115
auto iostat = genOpenStatement(*this, stmt);

flang/lib/Lower/IO.cpp

Lines changed: 86 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1399,18 +1399,95 @@ mlir::Value Fortran::lower::genReadStatement(
13991399
assignMap);
14001400
}
14011401

1402+
/// Get the file expression from the inquire spec list. Also return if the
1403+
/// expression is a file name.
1404+
static std::pair<const Fortran::semantics::SomeExpr *, bool>
1405+
getInquireFileExpr(const std::list<Fortran::parser::InquireSpec> *stmt) {
1406+
if (!stmt)
1407+
return {nullptr, false};
1408+
for (const auto &spec : *stmt) {
1409+
if (auto *f = std::get_if<Fortran::parser::FileUnitNumber>(&spec.u))
1410+
return {Fortran::semantics::GetExpr(*f), false};
1411+
if (auto *f = std::get_if<Fortran::parser::FileNameExpr>(&spec.u))
1412+
return {Fortran::semantics::GetExpr(*f), true};
1413+
}
1414+
// semantics should have already caught this condition
1415+
llvm_unreachable("inquire spec must have a file");
1416+
}
1417+
14021418
mlir::Value Fortran::lower::genInquireStatement(
14031419
Fortran::lower::AbstractConverter &converter,
1404-
const Fortran::parser::InquireStmt &) {
1420+
const Fortran::parser::InquireStmt &stmt) {
14051421
auto &builder = converter.getFirOpBuilder();
14061422
auto loc = converter.getCurrentLocation();
14071423
mlir::FuncOp beginFunc;
1408-
// if (...
1409-
beginFunc = getIORuntimeFunc<mkIOKey(BeginInquireUnit)>(loc, builder);
1410-
// else if (...
1411-
beginFunc = getIORuntimeFunc<mkIOKey(BeginInquireFile)>(loc, builder);
1412-
// else
1413-
beginFunc = getIORuntimeFunc<mkIOKey(BeginInquireIoLength)>(loc, builder);
1414-
// TODO: implement this!
1415-
llvm::report_fatal_error("INQUIRE statement is not implemented");
1424+
mlir::Value cookie;
1425+
ConditionSpecifierInfo csi{};
1426+
const auto *list =
1427+
std::get_if<std::list<Fortran::parser::InquireSpec>>(&stmt.u);
1428+
auto exprPair = getInquireFileExpr(list);
1429+
auto inquireFileUnit = [&]() -> bool {
1430+
return exprPair.first && !exprPair.second;
1431+
};
1432+
auto inquireFileName = [&]() -> bool {
1433+
return exprPair.first && exprPair.second;
1434+
};
1435+
1436+
// Determine which BeginInquire call to make.
1437+
if (inquireFileUnit()) {
1438+
// File unit call.
1439+
beginFunc = getIORuntimeFunc<mkIOKey(BeginInquireUnit)>(loc, builder);
1440+
mlir::FunctionType beginFuncTy = beginFunc.getType();
1441+
auto unit = converter.genExprValue(exprPair.first, loc);
1442+
auto un = builder.createConvert(loc, beginFuncTy.getInput(0), unit);
1443+
auto file = getDefaultFilename(builder, loc, beginFuncTy.getInput(1));
1444+
auto line = getDefaultLineNo(builder, loc, beginFuncTy.getInput(2));
1445+
llvm::SmallVector<mlir::Value, 4> beginArgs{un, file, line};
1446+
cookie =
1447+
builder.create<mlir::CallOp>(loc, beginFunc, beginArgs).getResult(0);
1448+
// Handle remaining arguments in specifier list.
1449+
genConditionHandlerCall(converter, loc, cookie, *list, csi);
1450+
} else if (inquireFileName()) {
1451+
// Filename call.
1452+
beginFunc = getIORuntimeFunc<mkIOKey(BeginInquireFile)>(loc, builder);
1453+
mlir::FunctionType beginFuncTy = beginFunc.getType();
1454+
auto file = converter.genExprValue(exprPair.first, loc);
1455+
// Helper to query [BUFFER, LEN].
1456+
Fortran::lower::CharacterExprHelper helper(builder, loc);
1457+
auto dataLen = helper.materializeCharacter(file);
1458+
auto buff =
1459+
builder.createConvert(loc, beginFuncTy.getInput(0), dataLen.first);
1460+
auto len =
1461+
builder.createConvert(loc, beginFuncTy.getInput(1), dataLen.second);
1462+
auto kindInt = helper.getCharacterKind(file.getType());
1463+
mlir::Value kindValue =
1464+
builder.createIntegerConstant(loc, beginFuncTy.getInput(2), kindInt);
1465+
auto sourceFile = getDefaultFilename(builder, loc, beginFuncTy.getInput(3));
1466+
auto line = getDefaultLineNo(builder, loc, beginFuncTy.getInput(4));
1467+
llvm::SmallVector<mlir::Value, 5> beginArgs = {
1468+
buff, len, kindValue, sourceFile, line,
1469+
};
1470+
cookie =
1471+
builder.create<mlir::CallOp>(loc, beginFunc, beginArgs).getResult(0);
1472+
// Handle remaining arguments in specifier list.
1473+
genConditionHandlerCall(converter, loc, cookie, *list, csi);
1474+
} else {
1475+
// Io length call.
1476+
const auto *ioLength =
1477+
std::get_if<Fortran::parser::InquireStmt::Iolength>(&stmt.u);
1478+
assert(ioLength && "must have an io length");
1479+
beginFunc = getIORuntimeFunc<mkIOKey(BeginInquireIoLength)>(loc, builder);
1480+
mlir::FunctionType beginFuncTy = beginFunc.getType();
1481+
auto file = getDefaultFilename(builder, loc, beginFuncTy.getInput(0));
1482+
auto line = getDefaultLineNo(builder, loc, beginFuncTy.getInput(1));
1483+
llvm::SmallVector<mlir::Value, 4> beginArgs{file, line};
1484+
cookie =
1485+
builder.create<mlir::CallOp>(loc, beginFunc, beginArgs).getResult(0);
1486+
// Handle remaining arguments in output list.
1487+
genConditionHandlerCall(
1488+
converter, loc, cookie,
1489+
std::get<std::list<Fortran::parser::OutputItem>>(ioLength->t), csi);
1490+
}
1491+
// Generate end statement call.
1492+
return genEndIO(converter, loc, cookie, csi);
14161493
}

flang/test/Lower/io-stmt01.f90

Lines changed: 17 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,9 @@
11
! RUN: bbc %s -o - | FileCheck %s
22

3+
logical :: existsvar
4+
integer :: length
5+
real :: a(100)
6+
37
! CHECK-LABEL: _QQmain
48
! CHECK: call {{.*}}BeginOpenUnit
59
! CHECK-DAG: call {{.*}}SetFile
@@ -35,7 +39,7 @@
3539
read (8,*) i, f
3640

3741
! CHECK: call {{.*}}BeginExternalListOutput
38-
! 32 bit integers are output as 64 bits in the runtime API
42+
! 32 bit integers are output as 64 bits in the runtime API
3943
! CHECK: call {{.*}}OutputInteger64
4044
! CHECK: call {{.*}}OutputReal32
4145
! CHECK: call {{.*}}EndIoStatement
@@ -49,4 +53,16 @@
4953
! CHECK: call {{.*}}OutputAscii
5054
! CHECK: call {{.*}}EndIoStatement
5155
print *, "A literal string"
56+
57+
! CHECK: call {{.*}}BeginInquireUnit
58+
! CHECK: call {{.*}}EndIoStatement
59+
inquire(4, EXIST=existsvar)
60+
61+
! CHECK: call {{.*}}BeginInquireFile
62+
! CHECK: call {{.*}}EndIoStatement
63+
inquire(FILE="fail.f90", EXIST=existsvar)
64+
65+
! CHECK: call {{.*}}BeginInquireIoLength
66+
! CHECK: call {{.*}}EndIoStatement
67+
inquire (iolength=length) a
5268
end

0 commit comments

Comments
 (0)