Skip to content

Commit 45b5779

Browse files
committed
Fix missing terminator in user-defined assignment case.
Fix bug and examine arguments of elemental procedures. Comments from review. Fix shape differences between successive passes. Rip out some usage of GetShape. Throw away unused code left over from refactoring. Fix tests.
1 parent c94047e commit 45b5779

File tree

11 files changed

+329
-403
lines changed

11 files changed

+329
-403
lines changed

flang/include/flang/Lower/ConvertExpr.h

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -166,7 +166,6 @@ void createAllocatableArrayAssignment(
166166
/// is fully evaluated prior to being assigned back to a temporary array.
167167
fir::ExtendedValue
168168
createSomeArrayTempValue(AbstractConverter &converter,
169-
const std::optional<evaluate::Shape> &shape,
170169
const evaluate::Expr<evaluate::SomeType> &expr,
171170
SymMap &symMap, StatementContext &stmtCtx);
172171

flang/include/flang/Optimizer/Builder/FIRBuilder.h

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -250,7 +250,7 @@ class FirOpBuilder : public mlir::OpBuilder {
250250
/// Construct one of the two forms of shape op from an array box.
251251
mlir::Value genShape(mlir::Location loc, const fir::AbstractArrayBox &arr);
252252
mlir::Value genShape(mlir::Location loc, llvm::ArrayRef<mlir::Value> shift,
253-
llvm::ArrayRef<mlir::Value> exts);
253+
llvm::ArrayRef<mlir::Value> exts);
254254
mlir::Value genShape(mlir::Location loc, llvm::ArrayRef<mlir::Value> exts);
255255

256256
/// Create one of the shape ops given an extended value. For a boxed value,
@@ -340,6 +340,12 @@ class FirOpBuilder : public mlir::OpBuilder {
340340
/// Generate code testing \p addr is a null address.
341341
mlir::Value genIsNull(mlir::Location loc, mlir::Value addr);
342342

343+
/// Compute the extent of (lb:ub:step) as max((ub-lb+step)/step, 0). See
344+
/// Fortran 2018 9.5.3.3.2 section for more details.
345+
mlir::Value genExtentFromTriplet(mlir::Location loc, mlir::Value lb,
346+
mlir::Value ub, mlir::Value step,
347+
mlir::Type type);
348+
343349
private:
344350
const KindMapping &kindMap;
345351
};
@@ -454,11 +460,6 @@ void genRecordAssignment(fir::FirOpBuilder &builder, mlir::Location loc,
454460
const fir::ExtendedValue &lhs,
455461
const fir::ExtendedValue &rhs);
456462

457-
/// Compute the extent of (lb:ub:step) as max((ub-lb+step)/step, 0). See Fortran
458-
/// 2018 9.5.3.3.2 section for more details.
459-
mlir::Value computeTripletExtent(fir::FirOpBuilder &builder, mlir::Location loc,
460-
mlir::Value lb, mlir::Value ub,
461-
mlir::Value step, mlir::Type type);
462463
} // namespace fir::factory
463464

464465
#endif // FORTRAN_OPTIMIZER_BUILDER_FIRBUILDER_H

flang/include/flang/Optimizer/Dialect/FIRType.h

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -162,6 +162,16 @@ inline bool sequenceWithNonConstantShape(fir::SequenceType seqTy) {
162162
/// Returns true iff the type `t` does not have a constant size.
163163
bool hasDynamicSize(mlir::Type t);
164164

165+
inline unsigned getRankOfShapeType(mlir::Type t) {
166+
if (auto shTy = t.dyn_cast<fir::ShapeType>())
167+
return shTy.getRank();
168+
if (auto shTy = t.dyn_cast<fir::ShapeShiftType>())
169+
return shTy.getRank();
170+
if (auto shTy = t.dyn_cast<fir::ShiftType>())
171+
return shTy.getRank();
172+
return 0;
173+
}
174+
165175
/// If `t` is a SequenceType return its element type, otherwise return `t`.
166176
inline mlir::Type unwrapSequenceType(mlir::Type t) {
167177
if (auto seqTy = t.dyn_cast<fir::SequenceType>())

flang/lib/Lower/Bridge.cpp

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1947,6 +1947,9 @@ class FirConverter : public Fortran::lower::AbstractConverter {
19471947
: stmtCtx;
19481948
Fortran::lower::createSubroutineCall(
19491949
*this, expr, localSymbols, ctx, /*isUserDefAssignment=*/true);
1950+
if (explicitIterationSpace())
1951+
builder->create<fir::ResultOp>(
1952+
loc, explicitIterSpace.getInnerArgs());
19501953
},
19511954

19521955
// [3] Pointer assignment with possibly empty bounds-spec. R1035: a

0 commit comments

Comments
 (0)