Skip to content

Commit 1d2f9cc

Browse files
authored
Merge pull request #1321 from flang-compiler/revert-1307-ch-haptr
Revert "Change host associations so they are not "promoted" to !fir.ptr"
2 parents 82ef3d3 + 480dc9c commit 1d2f9cc

File tree

8 files changed

+97
-114
lines changed

8 files changed

+97
-114
lines changed

flang/include/flang/Lower/ConvertExpr.h

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -206,8 +206,7 @@ mlir::Value createSubroutineCall(AbstractConverter &converter,
206206
// pass-by-ref semantics for a VALUE parameter. The optimizer may be able to
207207
// eliminate these.
208208
inline mlir::NamedAttribute getAdaptToByRefAttr(fir::FirOpBuilder &builder) {
209-
return {mlir::Identifier::get(fir::getAdaptToByRefAttrName(),
210-
builder.getContext()),
209+
return {mlir::Identifier::get("adapt.valuebyref", builder.getContext()),
211210
builder.getUnitAttr()};
212211
}
213212

flang/include/flang/Optimizer/Dialect/FIROps.h

Lines changed: 0 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -38,14 +38,6 @@ mlir::ParseResult parseSelector(mlir::OpAsmParser &parser,
3838
mlir::OpAsmParser::OperandType &selector,
3939
mlir::Type &type);
4040

41-
static constexpr llvm::StringRef getAdaptToByRefAttrName() {
42-
return "adapt.valuebyref";
43-
}
44-
45-
static constexpr llvm::StringRef getNormalizedLowerBoundAttrName() {
46-
return "normalized.lb";
47-
}
48-
4941
} // namespace fir
5042

5143
#define GET_OP_CLASSES

flang/lib/Lower/HostAssociations.cpp

Lines changed: 7 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -124,12 +124,12 @@ class CapturedSymbols {
124124

125125
/// Class defining simple scalars are captured in internal procedures.
126126
/// Simple scalars are non character intrinsic scalars. They are captured
127-
/// as `!fir.ref<T>`, for example `!fir.ref<i32>` for `INTEGER*4`.
127+
/// as !fir.ptr<T> (.e.g !fir.ptr<i32> for INTEGER(4)).
128128
class CapturedSimpleScalars : public CapturedSymbols<CapturedSimpleScalars> {
129129
public:
130130
static mlir::Type getType(Fortran::lower::AbstractConverter &converter,
131131
const Fortran::semantics::Symbol &sym) {
132-
return fir::ReferenceType::get(converter.genType(sym));
132+
return fir::PointerType::get(converter.genType(sym));
133133
}
134134

135135
static void instantiateHostTuple(const InstantiateHostTuple &args,
@@ -311,21 +311,21 @@ class CapturedAllocatableAndPointer
311311
};
312312

313313
/// Class defining how arrays are captured inside internal procedures.
314-
/// Array are captured via a `fir.box<fir.array<T>>` descriptor that belongs to
315-
/// the host tuple. This allows capturing lower bounds, which can be done by
316-
/// providing a ShapeShiftOp argument to the EmboxOp.
314+
/// Array are captured via a fir.box<fir.ptr<T>> pointer descriptor that
315+
/// belongs to the host tuple. This allows capturing lower bounds, which
316+
/// a non pointer descriptor (fir.box<T>) would not allow.
317317
class CapturedArrays : public CapturedSymbols<CapturedArrays> {
318318

319319
// Note: Constant shape arrays are not specialized (their base address would
320320
// be sufficient information inside the tuple). They could be specialized in
321-
// a later FIR pass, or a CapturedStaticShapeArrays could be added to deal
321+
// a later FIR pass, or A CapturedStaticShapeArrays could be added to deal
322322
// with them here.
323323
public:
324324
static mlir::Type getType(Fortran::lower::AbstractConverter &converter,
325325
const Fortran::semantics::Symbol &sym) {
326326
mlir::Type type = converter.genType(sym);
327327
assert(type.isa<fir::SequenceType>() && "must be a sequence type");
328-
return fir::BoxType::get(type);
328+
return fir::BoxType::get(fir::PointerType::get(type));
329329
}
330330

331331
static void instantiateHostTuple(const InstantiateHostTuple &args,
@@ -435,7 +435,6 @@ typename T::Result
435435
walkCaptureCategories(T visitor, Fortran::lower::AbstractConverter &converter,
436436
const Fortran::semantics::Symbol &sym) {
437437
if (isDerivedWithLengthParameters(sym))
438-
// Should be boxed.
439438
TODO(converter.genLocation(sym.name()),
440439
"host associated derived type with length parameters");
441440
Fortran::lower::BoxAnalyzer ba;

flang/lib/Optimizer/Builder/BoxValue.cpp

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -182,13 +182,15 @@ llvm::raw_ostream &fir::operator<<(llvm::raw_ostream &os,
182182
/// always be called, so it should not have any functional side effects,
183183
/// the const is here to enforce that.
184184
bool fir::MutableBoxValue::verify() const {
185-
mlir::Type type = fir::dyn_cast_ptrEleTy(getAddr().getType());
185+
auto type = fir::dyn_cast_ptrEleTy(getAddr().getType());
186186
if (!type)
187187
return false;
188188
auto box = type.dyn_cast<fir::BoxType>();
189189
if (!box)
190190
return false;
191-
// A boxed value always takes a memory reference,
191+
auto eleTy = box.getEleTy();
192+
if (!eleTy.isa<fir::PointerType>() && !eleTy.isa<fir::HeapType>())
193+
return false;
192194

193195
auto nParams = lenParams.size();
194196
if (isCharacter()) {

flang/lib/Optimizer/CodeGen/CodeGen.cpp

Lines changed: 5 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1482,19 +1482,13 @@ struct XEmboxOpConversion : public EmboxCommonConversion<fir::cg::XEmboxOp> {
14821482
}
14831483
}
14841484
if (!skipNext) {
1485-
// Lower bound is normalized to 0 for BIND(C) interoperability.
1485+
// store lower bound (normally 0)
14861486
auto lb = zero;
1487-
bool isaPointerOrAllocatable =
1488-
eleTy.isa<fir::PointerType>() || eleTy.isa<fir::HeapType>();
1489-
// Lower bound is defaults to 1 for POINTER, ALLOCATABLE, and
1490-
// denormalized descriptors.
1491-
if (isaPointerOrAllocatable || !normalizedLowerBound(xbox))
1487+
if (eleTy.isa<fir::PointerType>() || eleTy.isa<fir::HeapType>()) {
14921488
lb = one;
1493-
// If there is a shifted origin and this is not a normalized descriptor
1494-
// then use the value from the shift op as the lower bound.
1495-
if (hasShift &&
1496-
(isaPointerOrAllocatable || !normalizedLowerBound(xbox)))
1497-
lb = operands[shiftOff];
1489+
if (hasShift)
1490+
lb = operands[shiftOff];
1491+
}
14981492
dest = insertLowerBound(rewriter, loc, dest, descIdx, lb);
14991493

15001494
// store extent
@@ -1553,13 +1547,6 @@ struct XEmboxOpConversion : public EmboxCommonConversion<fir::cg::XEmboxOp> {
15531547
rewriter.replaceOp(xbox, result);
15541548
return success();
15551549
}
1556-
1557-
/// Return true if `xbox` has a normalized lower bounds attribute. A box value
1558-
/// that is neither a POINTER nor an ALLOCATABLE should be normalized to a
1559-
/// zero origin lower bound for interoperability with BIND(C).
1560-
inline static bool normalizedLowerBound(fir::cg::XEmboxOp xbox) {
1561-
return xbox->hasAttr(fir::getNormalizedLowerBoundAttrName());
1562-
}
15631550
};
15641551

15651552
/// Create a new box given a box reference.

flang/test/Fir/box.fir

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -145,10 +145,10 @@ func @box6(%0 : !fir.ref<!fir.array<?x?x?x?xf32>>, %1 : index, %2 : index) -> i3
145145
// CHECK: %[[sdp2:.*]] = sdiv i64 %[[dp2]], 2
146146
// CHECK: %[[cmp:.*]] = icmp sgt i64 %[[sdp2]], 0
147147
// CHECK: %[[extent:.*]] = select i1 %[[cmp]], i64 %[[sdp2]], i64 0
148-
// CHECK: insertvalue { float*, i64, i32, i8, i8, i8, i8, [2 x [3 x i64]] } { float* undef, i64 4, i32 20180515, i8 2, i8 25, i8 0, i8 0, [2 x [3 x i64]] [{{\[}}3 x i64] [i64 1, i64 undef, i64 undef], [3 x i64] undef] }, i64 %[[extent]], 7, 0, 1
148+
// CHECK: insertvalue { float*, i64, i32, i8, i8, i8, i8, [2 x [3 x i64]] } { float* undef, i64 4, i32 20180515, i8 2, i8 25, i8 0, i8 0, [2 x [3 x i64]] [{{\[}}3 x i64] [i64 0, i64 undef, i64 undef], [3 x i64] undef] }, i64 %[[extent]], 7, 0, 1
149149
// CHECK: insertvalue { float*, i64, i32, i8, i8, i8, i8, [2 x [3 x i64]] } %{{.*}}, i64 800, 7, 0, 2
150150
// CHECK: %[[op25:.*]] = add i64 25000, %[[i100p40]]
151-
// CHECK: insertvalue { float*, i64, i32, i8, i8, i8, i8, [2 x [3 x i64]] } %{{.*}}, i64 1, 7, 1, 0
151+
// CHECK: insertvalue { float*, i64, i32, i8, i8, i8, i8, [2 x [3 x i64]] } %{{.*}}, i64 0, 7, 1, 0
152152
// CHECK: insertvalue { float*, i64, i32, i8, i8, i8, i8, [2 x [3 x i64]] } %{{.*}}, i64 4, 7, 1, 1
153153
// CHECK: insertvalue { float*, i64, i32, i8, i8, i8, i8, [2 x [3 x i64]] } %{{.*}}, i64 120000, 7, 1, 2
154154
// CHECK: %[[op300:.*]] = add i64 300000, %[[op25]]

flang/test/Fir/embox.fir

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ func @_QPtest_slice() {
1313
// CHECK: %[[a3:.*]] = getelementptr [20 x i32], [20 x i32]* %[[a2]], i64 0, i64 0,
1414
// CHECK: %[[a4:.*]] = insertvalue { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }
1515
// CHECK: { i32* undef, i64 4, i32 20180515, i8 1, i8 9, i8 0, i8 0, [1 x [3 x i64]]
16-
// CHECK: [i64 1, i64 5, i64 8]] }, i32* %[[a3]], 0,
16+
// CHECK: [i64 0, i64 5, i64 8]] }, i32* %[[a3]], 0,
1717
// CHECK: store { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] } %[[a4]], { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }* %[[a1]], align 8
1818
// CHECK: call void @_QPtest_callee({ i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }* %[[a1]]),
1919
%c20 = arith.constant 20 : index
@@ -40,7 +40,7 @@ func @_QPtest_dt_slice() {
4040
// CHECK: %[[a4:.*]] = getelementptr [20 x %_QFtest_dt_sliceTt], [20 x %_QFtest_dt_sliceTt]* %[[a3]], i64 0, i64 0, i32 0,
4141
// CHECK: %[[a5:.*]] = insertvalue { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }
4242
// CHECK-SAME: { i32* undef, i64 4, i32 20180515, i8 1, i8 9, i8 0, i8 0, [1 x [3 x i64]]
43-
// CHECK-SAME: [i64 1, i64 5, i64 mul
43+
// CHECK-SAME: [i64 0, i64 5, i64 mul
4444
// CHECK-SAME: (i64 ptrtoint (%_QFtest_dt_sliceTt* getelementptr (%_QFtest_dt_sliceTt, %_QFtest_dt_sliceTt* null, i64 1) to i64), i64 2)]] }
4545
// CHECK-SAME: , i32* %[[a4]], 0
4646

0 commit comments

Comments
 (0)