Skip to content

Commit 73b357f

Browse files
committed
Put the check for dropping implied array arguments in the subexpressions per review comment.
1 parent db84c08 commit 73b357f

File tree

1 file changed

+26
-18
lines changed

1 file changed

+26
-18
lines changed

flang/lib/Lower/ConvertExpr.cpp

Lines changed: 26 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -2757,11 +2757,8 @@ class ArrayExprLowering {
27572757
const Fortran::evaluate::Expr<Fortran::evaluate::SomeType> &exp) {
27582758
auto resTy = explicitSpace ? destination->getResult(0).getType()
27592759
: converter.genType(exp);
2760-
bool explicitScalar = explicitSpace && exp.Rank() == 0;
27612760
return std::visit(
2762-
[&](const auto &e) {
2763-
return lowerArrayExpression(genarr(e), resTy, explicitScalar);
2764-
},
2761+
[&](const auto &e) { return lowerArrayExpression(genarr(e), resTy); },
27652762
exp.u);
27662763
}
27672764
ExtValue lowerArrayExpression(const ExtValue &exv) {
@@ -2788,15 +2785,15 @@ class ArrayExprLowering {
27882785
/// Otherwise, \p resultTy is ignored and the expression is evaluated
27892786
/// in the destination. \p f is a continuation built from an
27902787
/// evaluate::Expr or an ExtendedValue.
2791-
ExtValue lowerArrayExpression(CC f, mlir::Type resultTy,
2792-
bool explicitScalar = false) {
2788+
ExtValue lowerArrayExpression(CC f, mlir::Type resultTy) {
27932789
auto loc = getLoc();
27942790
auto [iterSpace, insPt] = genIterSpace(resultTy);
2795-
auto rhsIterSpace = iterSpace;
2791+
#if 0
27962792
if (explicitScalar)
27972793
rhsIterSpace.removeImplicit();
2794+
#endif
27982795
auto innerArg = iterSpace.innerArgument();
2799-
auto exv = f(rhsIterSpace);
2796+
auto exv = f(iterSpace);
28002797
mlir::Value upd;
28012798
if (ccDest.hasValue()) {
28022799
auto element = fir::getBase(exv);
@@ -4435,7 +4432,8 @@ class ArrayExprLowering {
44354432

44364433
RaiseRT
44374434
raiseToArray(const Fortran::evaluate::DataRef &x,
4438-
llvm::ArrayRef<const Fortran::semantics::Symbol *> ctrlSet) {
4435+
llvm::ArrayRef<const Fortran::semantics::Symbol *> ctrlSet,
4436+
bool isScalar) {
44394437
return std::visit(
44404438
Fortran::common::visitors{
44414439
[&](const Fortran::semantics::SymbolRef &s) -> RaiseRT {
@@ -4449,13 +4447,16 @@ class ArrayExprLowering {
44494447
TODO(getLoc(), "coarray reference");
44504448
return {llvm::None, mlir::Type{}, false, false};
44514449
},
4452-
[&](const auto &y) -> RaiseRT { return raiseToArray(y, ctrlSet); }},
4450+
[&](const auto &y) -> RaiseRT {
4451+
return raiseToArray(y, ctrlSet, isScalar);
4452+
}},
44534453
x.u);
44544454
}
44554455
RaiseRT
44564456
raiseToArray(const Fortran::evaluate::Component &x,
4457-
llvm::ArrayRef<const Fortran::semantics::Symbol *> ctrlSet) {
4458-
auto [fopt, ty, inrank, ranked] = raiseToArray(x.base(), ctrlSet);
4457+
llvm::ArrayRef<const Fortran::semantics::Symbol *> ctrlSet,
4458+
bool isScalar) {
4459+
auto [fopt, ty, inrank, ranked] = raiseToArray(x.base(), ctrlSet, isScalar);
44594460
if (fopt.hasValue()) {
44604461
if (!ranked && x.Rank() > 0) {
44614462
auto [fopt2, ty2] = raiseRankedComponent(fopt, x, ty);
@@ -4472,7 +4473,8 @@ class ArrayExprLowering {
44724473
}
44734474
RaiseRT
44744475
raiseToArray(const Fortran::evaluate::ArrayRef &x,
4475-
llvm::ArrayRef<const Fortran::semantics::Symbol *> ctrlSet) {
4476+
llvm::ArrayRef<const Fortran::semantics::Symbol *> ctrlSet,
4477+
bool isScalar) {
44764478
const auto &base = x.base();
44774479
auto accessUsesControlVariable = [&]() {
44784480
for (const auto &subs : x.subscript())
@@ -4502,16 +4504,16 @@ class ArrayExprLowering {
45024504
}
45034505
// Otherwise, it's a component.
45044506
auto [fopt, ty, inrank, ranked] =
4505-
raiseToArray(base.GetComponent(), ctrlSet);
4507+
raiseToArray(base.GetComponent(), ctrlSet, isScalar);
45064508
if (fopt.hasValue())
4507-
return RaiseRT{fopt, ty, inrank, ranked};
4509+
return RaiseRT{fopt, ty, inrank, x.Rank() > 0};
45084510
if (x.Rank() > 0 || accessUsesControlVariable()) {
45094511
auto [fopt2, ty2] = raiseBase(base.GetComponent());
45104512
return RaiseRT{fopt2, ty2, inrank, x.Rank() > 0};
45114513
}
45124514
return RaiseRT{fopt, ty, inrank, ranked};
45134515
}(),
4514-
x);
4516+
x, isScalar);
45154517
}
45164518
static mlir::Type unwrapBoxEleTy(mlir::Type ty) {
45174519
if (auto boxTy = ty.dyn_cast<fir::BoxType>()) {
@@ -4556,7 +4558,7 @@ class ArrayExprLowering {
45564558
return {};
45574559
}
45584560
RaiseRT raiseSubscript(const RaiseRT &tup,
4559-
const Fortran::evaluate::ArrayRef &x) {
4561+
const Fortran::evaluate::ArrayRef &x, bool isScalar) {
45604562
auto fopt = std::get<llvm::Optional<CC>>(tup);
45614563
if (fopt.hasValue()) {
45624564
auto arrTy = std::get<mlir::Type>(tup);
@@ -4635,8 +4637,14 @@ class ArrayExprLowering {
46354637
}
46364638
}
46374639
auto one = builder.createIntegerConstant(loc, idxTy, 1);
4640+
llvm::errs() << "DBG: " << isScalar << ' ' << implicitArguments << ' '
4641+
<< x.GetFirstSymbol() << '\n';
46384642
auto pc = [=](IterSpace iters) {
46394643
IterationSpace newIters = iters;
4644+
if (isScalar) {
4645+
newIters.removeImplicit();
4646+
assert(!implicitArguments);
4647+
}
46404648
const auto firstImplicitIndex = iters.beginImplicitIndex();
46414649
auto implicitIndex = iters.endImplicitIndex();
46424650
assert(firstImplicitIndex <= implicitIndex);
@@ -4724,7 +4732,7 @@ class ArrayExprLowering {
47244732
/// variables, i.e. `array(func(i))`, are not.
47254733
template <typename A>
47264734
CC raiseToArray(const A &x) {
4727-
auto tup = raiseToArray(x, collectControlSymbols());
4735+
auto tup = raiseToArray(x, collectControlSymbols(), x.Rank() == 0);
47284736
auto fopt = std::get<llvm::Optional<CC>>(tup);
47294737
assert(fopt.hasValue() && "continuation must be returned");
47304738
return fopt.getValue();

0 commit comments

Comments
 (0)