Skip to content

Commit 925d347

Browse files
authored
[flang] fix IsSimplyContiguous with expressions (#125708)
IsSymplyContiguous was visiting expressions and returning false on expressions like `x(::2) + y`, which triggered an assert in lowering when preparing arguments for copy-in/out. Update it to return false for everything that is not a variable, except when provided a flag to treat PARAMETER bases as variables. This flags is required for internal usages in lowering where lowering needs to now if the read-only memory is being addressed contiguously or not. Update call lowering to always copy parameter array section into contiguous writable memory when passing them. The rational here is that copy-out generated in nested calls using the dummy arguments will cause a segfault.
1 parent c94d930 commit 925d347

File tree

8 files changed

+163
-52
lines changed

8 files changed

+163
-52
lines changed

flang/include/flang/Evaluate/check-expression.h

Lines changed: 34 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -99,29 +99,44 @@ extern template void CheckSpecificationExpr(
9999
FoldingContext &, bool forElementalFunctionResult);
100100

101101
// Contiguity & "simple contiguity" (9.5.4)
102+
// Named constant sections are expressions, and as such their evaluation is
103+
// considered to be contiguous. This avoids funny situations where
104+
// IS_CONTIGUOUS(cst(1:10:2)) would fold to true because `cst(1:10:2)` is
105+
// folded into an array constructor literal, but IS_CONTIGUOUS(cst(i:i+9:2))
106+
// folds to false because the named constant reference cannot be folded.
107+
// Note that these IS_CONTIGUOUS usages are not portable (can probably be
108+
// considered to fall into F2023 8.5.7 (4)), and existing compilers are not
109+
// consistent here.
110+
// However, the compiler may very well decide to create a descriptor over
111+
// `cst(i:i+9:2)` when it can to avoid copies, and as such it needs internally
112+
// to be able to tell the actual contiguity of that array section over the
113+
// read-only data.
102114
template <typename A>
103-
std::optional<bool> IsContiguous(const A &, FoldingContext &);
115+
std::optional<bool> IsContiguous(const A &, FoldingContext &,
116+
bool namedConstantSectionsAreContiguous = true);
117+
extern template std::optional<bool> IsContiguous(const Expr<SomeType> &,
118+
FoldingContext &, bool namedConstantSectionsAreContiguous);
119+
extern template std::optional<bool> IsContiguous(const ArrayRef &,
120+
FoldingContext &, bool namedConstantSectionsAreContiguous);
121+
extern template std::optional<bool> IsContiguous(const Substring &,
122+
FoldingContext &, bool namedConstantSectionsAreContiguous);
123+
extern template std::optional<bool> IsContiguous(const Component &,
124+
FoldingContext &, bool namedConstantSectionsAreContiguous);
125+
extern template std::optional<bool> IsContiguous(const ComplexPart &,
126+
FoldingContext &, bool namedConstantSectionsAreContiguous);
127+
extern template std::optional<bool> IsContiguous(const CoarrayRef &,
128+
FoldingContext &, bool namedConstantSectionsAreContiguous);
104129
extern template std::optional<bool> IsContiguous(
105-
const Expr<SomeType> &, FoldingContext &);
106-
extern template std::optional<bool> IsContiguous(
107-
const ArrayRef &, FoldingContext &);
108-
extern template std::optional<bool> IsContiguous(
109-
const Substring &, FoldingContext &);
110-
extern template std::optional<bool> IsContiguous(
111-
const Component &, FoldingContext &);
112-
extern template std::optional<bool> IsContiguous(
113-
const ComplexPart &, FoldingContext &);
114-
extern template std::optional<bool> IsContiguous(
115-
const CoarrayRef &, FoldingContext &);
116-
extern template std::optional<bool> IsContiguous(
117-
const Symbol &, FoldingContext &);
118-
static inline std::optional<bool> IsContiguous(
119-
const SymbolRef &s, FoldingContext &c) {
120-
return IsContiguous(s.get(), c);
130+
const Symbol &, FoldingContext &, bool namedConstantSectionsAreContiguous);
131+
static inline std::optional<bool> IsContiguous(const SymbolRef &s,
132+
FoldingContext &c, bool namedConstantSectionsAreContiguous = true) {
133+
return IsContiguous(s.get(), c, namedConstantSectionsAreContiguous);
121134
}
122135
template <typename A>
123-
bool IsSimplyContiguous(const A &x, FoldingContext &context) {
124-
return IsContiguous(x, context).value_or(false);
136+
bool IsSimplyContiguous(const A &x, FoldingContext &context,
137+
bool namedConstantSectionsAreContiguous = true) {
138+
return IsContiguous(x, context, namedConstantSectionsAreContiguous)
139+
.value_or(false);
125140
}
126141

127142
template <typename A> bool IsErrorExpr(const A &);

flang/include/flang/Evaluate/tools.h

Lines changed: 26 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -321,28 +321,38 @@ template <typename A> const Symbol *ExtractBareLenParameter(const A &expr) {
321321
// of a substring or complex part.
322322
template <typename A>
323323
common::IfNoLvalue<std::optional<DataRef>, A> ExtractDataRef(
324-
const A &, bool intoSubstring, bool intoComplexPart) {
325-
return std::nullopt; // default base case
324+
const A &x, bool intoSubstring, bool intoComplexPart) {
325+
if constexpr (common::HasMember<decltype(x), decltype(DataRef::u)>) {
326+
return DataRef{x};
327+
} else {
328+
return std::nullopt; // default base case
329+
}
330+
}
331+
332+
std::optional<DataRef> ExtractSubstringBase(const Substring &);
333+
334+
inline std::optional<DataRef> ExtractDataRef(const Substring &x,
335+
bool intoSubstring = false, bool intoComplexPart = false) {
336+
if (intoSubstring) {
337+
return ExtractSubstringBase(x);
338+
} else {
339+
return std::nullopt;
340+
}
341+
}
342+
inline std::optional<DataRef> ExtractDataRef(const ComplexPart &x,
343+
bool intoSubstring = false, bool intoComplexPart = false) {
344+
if (intoComplexPart) {
345+
return x.complex();
346+
} else {
347+
return std::nullopt;
348+
}
326349
}
327350
template <typename T>
328351
std::optional<DataRef> ExtractDataRef(const Designator<T> &d,
329352
bool intoSubstring = false, bool intoComplexPart = false) {
330353
return common::visit(
331354
[=](const auto &x) -> std::optional<DataRef> {
332-
if constexpr (common::HasMember<decltype(x), decltype(DataRef::u)>) {
333-
return DataRef{x};
334-
}
335-
if constexpr (std::is_same_v<std::decay_t<decltype(x)>, Substring>) {
336-
if (intoSubstring) {
337-
return ExtractSubstringBase(x);
338-
}
339-
}
340-
if constexpr (std::is_same_v<std::decay_t<decltype(x)>, ComplexPart>) {
341-
if (intoComplexPart) {
342-
return x.complex();
343-
}
344-
}
345-
return std::nullopt; // w/o "else" to dodge bogus g++ 8.1 warning
355+
return ExtractDataRef(x, intoSubstring, intoComplexPart);
346356
},
347357
d.u);
348358
}
@@ -376,8 +386,6 @@ std::optional<DataRef> ExtractDataRef(
376386
std::optional<DataRef> ExtractDataRef(const ActualArgument &,
377387
bool intoSubstring = false, bool intoComplexPart = false);
378388

379-
std::optional<DataRef> ExtractSubstringBase(const Substring &);
380-
381389
// Predicate: is an expression is an array element reference?
382390
template <typename T>
383391
bool IsArrayElement(const Expr<T> &expr, bool intoSubstring = true,

flang/lib/Evaluate/check-expression.cpp

Lines changed: 31 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -833,7 +833,10 @@ class IsContiguousHelper
833833
public:
834834
using Result = std::optional<bool>; // tri-state
835835
using Base = AnyTraverse<IsContiguousHelper, Result>;
836-
explicit IsContiguousHelper(FoldingContext &c) : Base{*this}, context_{c} {}
836+
explicit IsContiguousHelper(
837+
FoldingContext &c, bool namedConstantSectionsAreContiguous)
838+
: Base{*this}, context_{c}, namedConstantSectionsAreContiguous_{
839+
namedConstantSectionsAreContiguous} {}
837840
using Base::operator();
838841

839842
template <typename T> Result operator()(const Constant<T> &) const {
@@ -856,6 +859,11 @@ class IsContiguousHelper
856859
// RANK(*) associating entity is contiguous.
857860
if (details->IsAssumedSize()) {
858861
return true;
862+
} else if (!IsVariable(details->expr()) &&
863+
(namedConstantSectionsAreContiguous_ ||
864+
!ExtractDataRef(details->expr(), true, true))) {
865+
// Selector is associated to an expression value.
866+
return true;
859867
} else {
860868
return Base::operator()(ultimate); // use expr
861869
}
@@ -1113,22 +1121,34 @@ class IsContiguousHelper
11131121
}
11141122

11151123
FoldingContext &context_;
1124+
bool namedConstantSectionsAreContiguous_{false};
11161125
};
11171126

11181127
template <typename A>
1119-
std::optional<bool> IsContiguous(const A &x, FoldingContext &context) {
1120-
return IsContiguousHelper{context}(x);
1128+
std::optional<bool> IsContiguous(const A &x, FoldingContext &context,
1129+
bool namedConstantSectionsAreContiguous) {
1130+
if (!IsVariable(x) &&
1131+
(namedConstantSectionsAreContiguous || !ExtractDataRef(x, true, true))) {
1132+
return true;
1133+
} else {
1134+
return IsContiguousHelper{context, namedConstantSectionsAreContiguous}(x);
1135+
}
11211136
}
11221137

1138+
template std::optional<bool> IsContiguous(const Expr<SomeType> &,
1139+
FoldingContext &, bool namedConstantSectionsAreContiguous);
1140+
template std::optional<bool> IsContiguous(const ArrayRef &, FoldingContext &,
1141+
bool namedConstantSectionsAreContiguous);
1142+
template std::optional<bool> IsContiguous(const Substring &, FoldingContext &,
1143+
bool namedConstantSectionsAreContiguous);
1144+
template std::optional<bool> IsContiguous(const Component &, FoldingContext &,
1145+
bool namedConstantSectionsAreContiguous);
1146+
template std::optional<bool> IsContiguous(const ComplexPart &, FoldingContext &,
1147+
bool namedConstantSectionsAreContiguous);
1148+
template std::optional<bool> IsContiguous(const CoarrayRef &, FoldingContext &,
1149+
bool namedConstantSectionsAreContiguous);
11231150
template std::optional<bool> IsContiguous(
1124-
const Expr<SomeType> &, FoldingContext &);
1125-
template std::optional<bool> IsContiguous(const ArrayRef &, FoldingContext &);
1126-
template std::optional<bool> IsContiguous(const Substring &, FoldingContext &);
1127-
template std::optional<bool> IsContiguous(const Component &, FoldingContext &);
1128-
template std::optional<bool> IsContiguous(
1129-
const ComplexPart &, FoldingContext &);
1130-
template std::optional<bool> IsContiguous(const CoarrayRef &, FoldingContext &);
1131-
template std::optional<bool> IsContiguous(const Symbol &, FoldingContext &);
1151+
const Symbol &, FoldingContext &, bool namedConstantSectionsAreContiguous);
11321152

11331153
// IsErrorExpr()
11341154
struct IsErrorExprHelper : public AnyTraverse<IsErrorExprHelper, bool> {

flang/lib/Lower/ConvertCall.cpp

Lines changed: 25 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@
3232
#include "flang/Optimizer/Dialect/FIROpsSupport.h"
3333
#include "flang/Optimizer/HLFIR/HLFIROps.h"
3434
#include "mlir/IR/IRMapping.h"
35+
#include "llvm/ADT/TypeSwitch.h"
3536
#include "llvm/Support/CommandLine.h"
3637
#include "llvm/Support/Debug.h"
3738
#include <optional>
@@ -1135,6 +1136,27 @@ isSimplyContiguous(const Fortran::evaluate::ActualArgument &arg,
11351136
Fortran::evaluate::IsSimplyContiguous(*sym, foldingContext);
11361137
}
11371138

1139+
static bool isParameterObjectOrSubObject(hlfir::Entity entity) {
1140+
mlir::Value base = entity;
1141+
bool foundParameter = false;
1142+
while (mlir::Operation *op = base ? base.getDefiningOp() : nullptr) {
1143+
base =
1144+
llvm::TypeSwitch<mlir::Operation *, mlir::Value>(op)
1145+
.Case<hlfir::DeclareOp>([&](auto declare) -> mlir::Value {
1146+
foundParameter |= hlfir::Entity{declare}.isParameter();
1147+
return foundParameter ? mlir::Value{} : declare.getMemref();
1148+
})
1149+
.Case<hlfir::DesignateOp, hlfir::ParentComponentOp, fir::EmboxOp>(
1150+
[&](auto op) -> mlir::Value { return op.getMemref(); })
1151+
.Case<fir::ReboxOp>(
1152+
[&](auto rebox) -> mlir::Value { return rebox.getBox(); })
1153+
.Case<fir::ConvertOp>(
1154+
[&](auto convert) -> mlir::Value { return convert.getValue(); })
1155+
.Default([](mlir::Operation *) -> mlir::Value { return nullptr; });
1156+
}
1157+
return foundParameter;
1158+
}
1159+
11381160
/// When dummy is not ALLOCATABLE, POINTER and is not passed in register,
11391161
/// prepare the actual argument according to the interface. Do as needed:
11401162
/// - address element if this is an array argument in an elemental call.
@@ -1298,8 +1320,9 @@ static PreparedDummyArgument preparePresentUserCallActualArgument(
12981320
// 'parameter' attribute. Even though the constant expressions
12991321
// are not definable and explicit assignments to them are not
13001322
// possible, we have to create a temporary copies when we pass
1301-
// them down the call stack.
1302-
entity.isParameter()) {
1323+
// them down the call stack because of potential compiler
1324+
// generated writes in copy-out.
1325+
isParameterObjectOrSubObject(entity)) {
13031326
// Make a copy in a temporary.
13041327
auto copy = builder.create<hlfir::AsExprOp>(loc, entity);
13051328
mlir::Type storageType = entity.getType();

flang/lib/Lower/ConvertExprToHLFIR.cpp

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@
2121
#include "flang/Lower/ConvertProcedureDesignator.h"
2222
#include "flang/Lower/ConvertType.h"
2323
#include "flang/Lower/ConvertVariable.h"
24+
#include "flang/Lower/DumpEvaluateExpr.h"
2425
#include "flang/Lower/StatementContext.h"
2526
#include "flang/Lower/SymbolMap.h"
2627
#include "flang/Optimizer/Builder/Complex.h"
@@ -220,7 +221,8 @@ class HlfirDesignatorBuilder {
220221
// Non simply contiguous ref require a fir.box to carry the byte stride.
221222
if (mlir::isa<fir::SequenceType>(resultValueType) &&
222223
!Fortran::evaluate::IsSimplyContiguous(
223-
designatorNode, getConverter().getFoldingContext()))
224+
designatorNode, getConverter().getFoldingContext(),
225+
/*namedConstantSectionsAreAlwaysContiguous=*/false))
224226
return fir::BoxType::get(resultValueType);
225227
// Other designators can be handled as raw addresses.
226228
return fir::ReferenceType::get(resultValueType);

flang/test/Evaluate/folding09.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ module m
99
logical, parameter :: test_param1 = is_contiguous(cst(:,1))
1010
logical, parameter :: test_param2 = is_contiguous(cst(1,:))
1111
logical, parameter :: test_param3 = is_contiguous(cst(:,n))
12-
logical, parameter :: test_param4 = .not. is_contiguous(cst(n,:))
12+
logical, parameter :: test_param4 = is_contiguous(cst(n,:))
1313
logical, parameter :: test_param5 = is_contiguous(empty_cst(n,-1:n:2))
1414
contains
1515
function f()
Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
! Reproducer for https://github.com/llvm/llvm-project/issues/124043 lowering
2+
! crash.
3+
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
4+
5+
subroutine repro(a)
6+
integer a(10)
7+
associate (b => a(::2)+1)
8+
call bar(b)
9+
end associate
10+
end
11+
! CHECK-LABEL: func.func @_QPrepro(
12+
! CHECK: %[[VAL_11:.*]] = hlfir.elemental
13+
! CHECK: %[[VAL_16:.*]]:3 = hlfir.associate %[[VAL_11]]
14+
! CHECK: %[[VAL_18:.*]]:2 = hlfir.declare %[[VAL_16]]#1
15+
! CHECK: fir.call @_QPbar(%[[VAL_18]]#1)

flang/test/Lower/HLFIR/calls-constant-expr-arg.f90

Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -62,3 +62,31 @@ end subroutine test
6262
! CHECK: hlfir.end_associate %[[VAL_7]]#1, %[[VAL_7]]#2 : !fir.ref<i32>, i1
6363
! CHECK: return
6464
! CHECK: }
65+
66+
subroutine test_associate(i)
67+
interface
68+
subroutine foo(x)
69+
real :: x(:)
70+
end subroutine
71+
end interface
72+
real, parameter :: p(*) = [1.,2.,3.,4.]
73+
integer(8) :: i
74+
associate(a => p(1:i))
75+
associate(b => a(1:1:2))
76+
call foo(b)
77+
end associate
78+
end associate
79+
end subroutine
80+
! CHECK-LABEL: func.func @_QPtest_associate(
81+
! CHECK: %[[VAL_3:.*]] = fir.address_of(@_QFtest_associateECp) : !fir.ref<!fir.array<4xf32>>
82+
! CHECK: %[[VAL_6:.*]]:2 = hlfir.declare %[[VAL_3]](%{{.*}}) {fortran_attrs = #fir.var_attrs<parameter>, uniq_name = "_QFtest_associateECp"} : (!fir.ref<!fir.array<4xf32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<4xf32>>, !fir.ref<!fir.array<4xf32>>)
83+
! CHECK: %[[VAL_18:.*]] = hlfir.designate %[[VAL_6]]#0 {{.*}}
84+
! CHECK: %[[VAL_19:.*]]:2 = hlfir.declare %[[VAL_18]] {{.*}}
85+
! CHECK: %[[VAL_25:.*]] = hlfir.designate %[[VAL_19]]#0 {{.*}}
86+
! CHECK: %[[VAL_26:.*]]:2 = hlfir.declare %[[VAL_25]] {uniq_name = "_QFtest_associateEb"} : (!fir.box<!fir.array<1xf32>>) -> (!fir.box<!fir.array<1xf32>>, !fir.box<!fir.array<1xf32>>)
87+
! CHECK: %[[VAL_27:.*]] = hlfir.as_expr %[[VAL_26]]#0 : (!fir.box<!fir.array<1xf32>>) -> !hlfir.expr<1xf32>
88+
! CHECK: %[[VAL_30:.*]]:3 = hlfir.associate %[[VAL_27]]({{.*}}) {adapt.valuebyref} : (!hlfir.expr<1xf32>, !fir.shape<1>) -> (!fir.ref<!fir.array<1xf32>>, !fir.ref<!fir.array<1xf32>>, i1)
89+
! CHECK: %[[VAL_31:.*]] = fir.embox %[[VAL_30]]
90+
! CHECK: %[[VAL_32:.*]] = fir.convert %[[VAL_31]] : (!fir.box<!fir.array<1xf32>>) -> !fir.box<!fir.array<?xf32>>
91+
! CHECK: fir.call @_QPfoo(%[[VAL_32]]) {{.*}} : (!fir.box<!fir.array<?xf32>>) -> ()
92+
! CHECK: hlfir.end_associate %[[VAL_30]]#1, %[[VAL_30]]#2 : !fir.ref<!fir.array<1xf32>>, i1

0 commit comments

Comments
 (0)