Skip to content

Commit 16c4b32

Browse files
committed
[flang] Correct handling of non-default lower bounds in ASSOCIATE with named constants
Work through several issues with LBOUND() and UBOUND() of ASSOCIATE construct entities that have been associated with named constants or subobjects of named constants that are sporting non-default lower bounds. Sometimes the non-default lower bounds matter, sometimes they don't. Add a fairly exhaustive test to work through the possibilities. Differential Revision: https://reviews.llvm.org/D156756
1 parent 048458f commit 16c4b32

File tree

10 files changed

+181
-54
lines changed

10 files changed

+181
-54
lines changed

flang/include/flang/Evaluate/constant.h

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -63,12 +63,23 @@ class ConstantBounds {
6363
explicit ConstantBounds(ConstantSubscripts &&shape);
6464
~ConstantBounds();
6565
const ConstantSubscripts &shape() const { return shape_; }
66+
int Rank() const { return GetRank(shape_); }
67+
Constant<SubscriptInteger> SHAPE() const;
68+
69+
// It is possible in this representation for a constant array to have
70+
// lower bounds other than 1, which is of course not expressible in
71+
// Fortran. This case arises only from definitions of named constant
72+
// arrays with such bounds, as in:
73+
// REAL, PARAMETER :: NAMED(0:1) = [1.,2.]
74+
// Bundling the lower bounds of the named constant with its
75+
// constant value allows folding of subscripted array element
76+
// references, LBOUND, and UBOUND without having to thread the named
77+
// constant or its bounds throughout folding.
6678
const ConstantSubscripts &lbounds() const { return lbounds_; }
6779
ConstantSubscripts ComputeUbounds(std::optional<int> dim) const;
6880
void set_lbounds(ConstantSubscripts &&);
6981
void SetLowerBoundsToOne();
70-
int Rank() const { return GetRank(shape_); }
71-
Constant<SubscriptInteger> SHAPE() const;
82+
bool HasNonDefaultLowerBound() const;
7283

7384
// If no optional dimension order argument is passed, increments a vector of
7485
// subscripts in Fortran array order (first dimension varying most quickly).

flang/lib/Evaluate/constant.cpp

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,15 @@ Constant<SubscriptInteger> ConstantBounds::SHAPE() const {
5656
return AsConstantShape(shape_);
5757
}
5858

59+
bool ConstantBounds::HasNonDefaultLowerBound() const {
60+
for (auto n : lbounds_) {
61+
if (n != 1) {
62+
return true;
63+
}
64+
}
65+
return false;
66+
}
67+
5968
ConstantSubscript ConstantBounds::SubscriptsToOffset(
6069
const ConstantSubscripts &index) const {
6170
CHECK(GetRank(index) == GetRank(shape_));

flang/lib/Evaluate/fold-implementation.h

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -255,11 +255,11 @@ std::optional<Constant<T>> Folder<T>::ApplyComponent(
255255
const std::vector<Constant<SubscriptInteger>> *subscripts) {
256256
if (auto scalar{structures.GetScalarValue()}) {
257257
if (std::optional<Expr<SomeType>> expr{scalar->Find(component)}) {
258-
if (const Constant<T> *value{UnwrapConstantValue<T>(expr.value())}) {
259-
if (!subscripts) {
260-
return std::move(*value);
261-
} else {
258+
if (const Constant<T> *value{UnwrapConstantValue<T>(*expr)}) {
259+
if (subscripts) {
262260
return ApplySubscripts(*value, *subscripts);
261+
} else {
262+
return *value;
263263
}
264264
}
265265
}

flang/lib/Evaluate/fold-integer.cpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -126,7 +126,7 @@ class GetConstantArrayBoundHelper {
126126
}
127127

128128
template <typename T> ConstantSubscripts Get(const Parentheses<T> &x) {
129-
// Cause of temp variable inside parentheses - return [1, ... 1] for lower
129+
// Case of temp variable inside parentheses - return [1, ... 1] for lower
130130
// bounds and shape for upper bounds
131131
if (getLbound_) {
132132
return ConstantSubscripts(x.Rank(), ConstantSubscript{1});

flang/lib/Evaluate/formatting.cpp

Lines changed: 21 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -19,23 +19,35 @@
1919

2020
namespace Fortran::evaluate {
2121

22-
static void ShapeAsFortran(
23-
llvm::raw_ostream &o, const ConstantSubscripts &shape) {
24-
if (GetRank(shape) > 1) {
22+
static void ShapeAsFortran(llvm::raw_ostream &o,
23+
const ConstantSubscripts &shape, const ConstantSubscripts &lbounds,
24+
bool hasNonDefaultLowerBound) {
25+
if (GetRank(shape) > 1 || hasNonDefaultLowerBound) {
2526
o << ",shape=";
2627
char ch{'['};
2728
for (auto dim : shape) {
2829
o << ch << dim;
2930
ch = ',';
3031
}
31-
o << "])";
32+
o << ']';
33+
if (hasNonDefaultLowerBound) {
34+
o << ",%lbound=";
35+
ch = '[';
36+
for (auto lb : lbounds) {
37+
o << ch << lb;
38+
ch = ',';
39+
}
40+
o << ']';
41+
}
42+
o << ')';
3243
}
3344
}
3445

3546
template <typename RESULT, typename VALUE>
3647
llvm::raw_ostream &ConstantBase<RESULT, VALUE>::AsFortran(
3748
llvm::raw_ostream &o) const {
38-
if (Rank() > 1) {
49+
bool hasNonDefaultLowerBound{HasNonDefaultLowerBound()};
50+
if (Rank() > 1 || hasNonDefaultLowerBound) {
3951
o << "reshape(";
4052
}
4153
if (Rank() > 0) {
@@ -71,14 +83,15 @@ llvm::raw_ostream &ConstantBase<RESULT, VALUE>::AsFortran(
7183
if (Rank() > 0) {
7284
o << ']';
7385
}
74-
ShapeAsFortran(o, shape());
86+
ShapeAsFortran(o, shape(), lbounds(), hasNonDefaultLowerBound);
7587
return o;
7688
}
7789

7890
template <int KIND>
7991
llvm::raw_ostream &Constant<Type<TypeCategory::Character, KIND>>::AsFortran(
8092
llvm::raw_ostream &o) const {
81-
if (Rank() > 1) {
93+
bool hasNonDefaultLowerBound{HasNonDefaultLowerBound()};
94+
if (Rank() > 1 || hasNonDefaultLowerBound) {
8295
o << "reshape(";
8396
}
8497
if (Rank() > 0) {
@@ -98,7 +111,7 @@ llvm::raw_ostream &Constant<Type<TypeCategory::Character, KIND>>::AsFortran(
98111
if (Rank() > 0) {
99112
o << ']';
100113
}
101-
ShapeAsFortran(o, shape());
114+
ShapeAsFortran(o, shape(), lbounds(), hasNonDefaultLowerBound);
102115
return o;
103116
}
104117

flang/lib/Evaluate/shape.cpp

Lines changed: 46 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -314,7 +314,7 @@ class GetLowerBoundHelper
314314
DescriptorInquiry::Field::LowerBound, dimension_}};
315315
}
316316
} else {
317-
auto exprLowerBound{((*this)(assoc->expr()))};
317+
Result exprLowerBound{((*this)(assoc->expr()))};
318318
if (IsActuallyConstant(exprLowerBound)) {
319319
return std::move(exprLowerBound);
320320
} else {
@@ -334,8 +334,8 @@ class GetLowerBoundHelper
334334
}
335335
}
336336

337-
Result operator()(const Symbol &symbol0) const {
338-
return GetLowerBound(symbol0, NamedEntity{symbol0});
337+
Result operator()(const Symbol &symbol) const {
338+
return GetLowerBound(symbol, NamedEntity{symbol});
339339
}
340340

341341
Result operator()(const Component &component) const {
@@ -346,8 +346,30 @@ class GetLowerBoundHelper
346346
return Result{1};
347347
}
348348

349+
template <typename T> Result operator()(const Expr<T> &expr) const {
350+
if (const Symbol * whole{UnwrapWholeSymbolOrComponentDataRef(expr)}) {
351+
return (*this)(*whole);
352+
} else if constexpr (common::HasMember<Constant<T>, decltype(expr.u)>) {
353+
if (const auto *con{std::get_if<Constant<T>>(&expr.u)}) {
354+
ConstantSubscripts lb{con->lbounds()};
355+
if (dimension_ < GetRank(lb)) {
356+
return Result{lb[dimension_]};
357+
}
358+
} else { // operation
359+
return Result{1};
360+
}
361+
} else {
362+
return (*this)(expr.u);
363+
}
364+
if constexpr (LBOUND_SEMANTICS) {
365+
return Result{};
366+
} else {
367+
return Result{1};
368+
}
369+
}
370+
349371
private:
350-
int dimension_;
372+
int dimension_; // zero-based
351373
FoldingContext *context_{nullptr};
352374
};
353375

@@ -618,16 +640,27 @@ static MaybeExtentExpr GetUBOUND(
618640
if (auto ubound{GetExplicitUBOUND(context, shapeSpec)}) {
619641
return *ubound;
620642
} else if (details->IsAssumedSize() && dimension + 1 == symbol.Rank()) {
621-
return std::nullopt;
643+
return std::nullopt; // UBOUND() folding replaces with -1
622644
} else if (auto lb{GetLBOUND(base, dimension)}) {
623645
return ComputeUpperBound(std::move(*lb), GetExtent(base, dimension));
624646
}
625647
}
626648
} else if (const auto *assoc{
627649
symbol.detailsIf<semantics::AssocEntityDetails>()}) {
628-
if (auto extent{GetAssociatedExtent(base, *assoc, dimension)}) {
629-
if (auto lb{GetLBOUND(base, dimension)}) {
630-
return ComputeUpperBound(std::move(*lb), std::move(extent));
650+
if (assoc->rank()) { // SELECT RANK case
651+
const Symbol &resolved{ResolveAssociations(symbol)};
652+
if (IsDescriptor(resolved) && dimension < *assoc->rank()) {
653+
ExtentExpr lb{DescriptorInquiry{NamedEntity{base},
654+
DescriptorInquiry::Field::LowerBound, dimension}};
655+
ExtentExpr extent{DescriptorInquiry{
656+
std::move(base), DescriptorInquiry::Field::Extent, dimension}};
657+
return ComputeUpperBound(std::move(lb), std::move(extent));
658+
}
659+
} else if (assoc->expr()) {
660+
if (auto extent{GetAssociatedExtent(base, *assoc, dimension)}) {
661+
if (auto lb{GetLBOUND(base, dimension)}) {
662+
return ComputeUpperBound(std::move(*lb), std::move(extent));
663+
}
631664
}
632665
}
633666
}
@@ -644,29 +677,12 @@ MaybeExtentExpr GetUBOUND(
644677
}
645678

646679
static Shape GetUBOUNDs(FoldingContext *context, const NamedEntity &base) {
647-
const Symbol &symbol{
648-
ResolveAssociationsExceptSelectRank(base.GetLastSymbol())};
649-
if (const auto *details{symbol.detailsIf<semantics::ObjectEntityDetails>()}) {
650-
Shape result;
651-
int dim{0};
652-
for (const auto &shapeSpec : details->shape()) {
653-
if (auto ubound{GetExplicitUBOUND(context, shapeSpec)}) {
654-
result.emplace_back(*ubound);
655-
} else if (details->IsAssumedSize() && dim + 1 == base.Rank()) {
656-
result.emplace_back(std::nullopt); // UBOUND folding replaces with -1
657-
} else if (auto lb{GetLBOUND(base, dim)}) {
658-
result.emplace_back(
659-
ComputeUpperBound(std::move(*lb), GetExtent(base, dim)));
660-
} else {
661-
result.emplace_back(); // unknown
662-
}
663-
++dim;
664-
}
665-
CHECK(GetRank(result) == symbol.Rank());
666-
return result;
667-
} else {
668-
return std::move(GetShape(symbol).value());
680+
Shape result;
681+
int rank{base.Rank()};
682+
for (int dim{0}; dim < rank; ++dim) {
683+
result.emplace_back(GetUBOUND(context, base, dim));
669684
}
685+
return result;
670686
}
671687

672688
Shape GetUBOUNDs(FoldingContext &context, const NamedEntity &base) {

flang/lib/Semantics/expression.cpp

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -311,9 +311,10 @@ MaybeExpr ExpressionAnalyzer::ApplySubscripts(
311311

312312
void ExpressionAnalyzer::CheckConstantSubscripts(ArrayRef &ref) {
313313
// Fold subscript expressions and check for an empty triplet.
314-
Shape lb{GetLBOUNDs(foldingContext_, ref.base())};
314+
const Symbol &arraySymbol{ref.base().GetLastSymbol()};
315+
Shape lb{GetLBOUNDs(foldingContext_, NamedEntity{arraySymbol})};
315316
CHECK(lb.size() >= ref.subscript().size());
316-
Shape ub{GetUBOUNDs(foldingContext_, ref.base())};
317+
Shape ub{GetUBOUNDs(foldingContext_, NamedEntity{arraySymbol})};
317318
CHECK(ub.size() >= ref.subscript().size());
318319
bool anyPossiblyEmptyDim{false};
319320
int dim{0};

flang/lib/Semantics/resolve-names.cpp

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8599,8 +8599,7 @@ void ResolveNamesVisitor::FinishDerivedTypeInstantiation(Scope &scope) {
85998599
auto origDetails{origComp.get<ObjectEntityDetails>()};
86008600
if (const MaybeExpr & init{origDetails.init()}) {
86018601
SomeExpr newInit{*init};
8602-
MaybeExpr folded{
8603-
evaluate::Fold(foldingContext, std::move(newInit))};
8602+
MaybeExpr folded{FoldExpr(std::move(newInit))};
86048603
details->set_init(std::move(folded));
86058604
}
86068605
}

flang/test/Lower/HLFIR/constant.f90

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -42,11 +42,11 @@ subroutine test_constant_array_char()
4242
subroutine test_constant_with_lower_bounds()
4343
integer, parameter :: i(-1:0, -1:0) = reshape([1,2,3,4], shape=[2,2])
4444
print *, i
45-
! CHECK: %[[VAL_12:.*]] = fir.address_of(@_QQro[[name:.*]]) : !fir.ref<!fir.array<2x2xi32>>
46-
! CHECK: %[[VAL_13:.*]] = arith.constant 2 : index
45+
! CHECK: %[[VAL_12:.*]] = fir.address_of(@_QFtest_constant_with_lower_boundsECi) : !fir.ref<!fir.array<2x2xi32>>
46+
! CHECK: %[[VAL_13:.*]] = arith.constant -1 : index
4747
! CHECK: %[[VAL_14:.*]] = arith.constant 2 : index
4848
! CHECK: %[[VAL_15:.*]] = arith.constant -1 : index
49-
! CHECK: %[[VAL_16:.*]] = arith.constant -1 : index
50-
! CHECK: %[[VAL_17:.*]] = fir.shape_shift %[[VAL_15]], %[[VAL_13]], %[[VAL_16]], %[[VAL_14]] : (index, index, index, index) -> !fir.shapeshift<2>
51-
! CHECK: hlfir.declare %[[VAL_12]](%[[VAL_17]]) {fortran_attrs = #fir.var_attrs<parameter>, uniq_name = "_QQro[[name]]"} : (!fir.ref<!fir.array<2x2xi32>>, !fir.shapeshift<2>) -> (!fir.box<!fir.array<2x2xi32>>, !fir.ref<!fir.array<2x2xi32>>)
49+
! CHECK: %[[VAL_16:.*]] = arith.constant 2 : index
50+
! CHECK: %[[VAL_17:.*]] = fir.shape_shift %[[VAL_13]], %[[VAL_14]], %[[VAL_15]], %[[VAL_16]] : (index, index, index, index) -> !fir.shapeshift<2>
51+
! CHECK: hlfir.declare %[[VAL_12]](%[[VAL_17]]) {fortran_attrs = #fir.var_attrs<parameter>, uniq_name = "_QFtest_constant_with_lower_boundsECi"} : (!fir.ref<!fir.array<2x2xi32>>, !fir.shapeshift<2>) -> (!fir.box<!fir.array<2x2xi32>>, !fir.ref<!fir.array<2x2xi32>>)
5252
end subroutine

flang/test/Semantics/associate02.f90

Lines changed: 78 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,78 @@
1+
! RUN: %flang_fc1 -fdebug-unparse %s 2>&1 | FileCheck %s
2+
! Sometimes associations with named constants involving non-default
3+
! lower bounds expose those bounds to LBOUND()/UBOUND(), sometimes
4+
! they do not.
5+
subroutine s(n)
6+
integer, intent(in) :: n
7+
type t
8+
real component(0:1,2:3)
9+
end type
10+
real, parameter :: abcd(2,2) = reshape([1.,2.,3.,4.], shape(abcd))
11+
real, parameter :: namedConst1(-1:0,-2:-1) = abcd
12+
type(t), parameter :: namedConst2 = t(abcd)
13+
type(t), parameter :: namedConst3(2:3,3:4) = reshape([(namedConst2,j=1,size(namedConst3))], shape(namedConst3))
14+
!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
15+
print *, lbound(abcd), ubound(abcd), shape(abcd)
16+
!CHECK: PRINT *, [INTEGER(4)::-1_4,-2_4], [INTEGER(4)::0_4,-1_4], [INTEGER(4)::2_4,2_4]
17+
print *, lbound(namedConst1), ubound(namedConst1), shape(namedConst1)
18+
!CHECK: PRINT *, [INTEGER(4)::0_4,2_4], [INTEGER(4)::1_4,3_4], [INTEGER(4)::2_4,2_4]
19+
print *, lbound(namedConst2%component), ubound(namedConst2%component), shape(namedConst2%component)
20+
!CHECK: PRINT *, [INTEGER(4)::2_4,3_4], [INTEGER(4)::3_4,4_4], [INTEGER(4)::2_4,2_4]
21+
print *, lbound(namedConst3), ubound(namedConst3), shape(namedConst3)
22+
!CHECK: PRINT *, [INTEGER(4)::0_4,2_4], [INTEGER(4)::1_4,3_4], [INTEGER(4)::2_4,2_4]
23+
print *, lbound(namedConst3(n,n)%component), ubound(namedConst3(n,n)%component), shape(namedConst3(n,n)%component)
24+
!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
25+
print *, lbound(namedConst3%component(0,2)), ubound(namedConst3%component(0,2)), shape(namedConst3%component(0,2))
26+
associate (a => abcd)
27+
!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
28+
print *, lbound(a), ubound(a), shape(a)
29+
end associate
30+
associate (a => namedConst1)
31+
!CHECK: PRINT *, [INTEGER(4)::-1_4,-2_4], [INTEGER(4)::0_4,-1_4], [INTEGER(4)::2_4,2_4]
32+
print *, lbound(a), ubound(a), shape(a)
33+
end associate
34+
associate (a => (namedConst1))
35+
!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
36+
print *, lbound(a), ubound(a), shape(a)
37+
end associate
38+
associate (a => namedConst1 * 2.)
39+
!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
40+
print *, lbound(a), ubound(a), shape(a)
41+
end associate
42+
associate (a => namedConst2%component)
43+
!CHECK: PRINT *, [INTEGER(4)::0_4,2_4], [INTEGER(4)::1_4,3_4], [INTEGER(4)::2_4,2_4]
44+
print *, lbound(a), ubound(a), shape(a)
45+
end associate
46+
associate (a => (namedConst2%component))
47+
!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
48+
print *, lbound(a), ubound(a), shape(a)
49+
end associate
50+
associate (a => namedConst2%component * 2.)
51+
!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
52+
print *, lbound(a), ubound(a), shape(a)
53+
end associate
54+
associate (a => namedConst3)
55+
!CHECK: PRINT *, [INTEGER(4)::2_4,3_4], [INTEGER(4)::3_4,4_4], [INTEGER(4)::2_4,2_4]
56+
print *, lbound(a), ubound(a), shape(a)
57+
end associate
58+
associate (a => (namedConst3))
59+
!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
60+
print *, lbound(a), ubound(a), shape(a)
61+
end associate
62+
associate (a => namedConst3(n,n)%component)
63+
!CHECK: PRINT *, [INTEGER(4)::0_4,2_4], [INTEGER(4)::1_4,3_4], [INTEGER(4)::2_4,2_4]
64+
print *, lbound(a), ubound(a), shape(a)
65+
end associate
66+
associate (a => (namedConst3(n,n)%component))
67+
!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
68+
print *, lbound(a), ubound(a), shape(a)
69+
end associate
70+
associate (a => namedConst3(n,n)%component * 2.)
71+
!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
72+
print *, lbound(a), ubound(a), shape(a)
73+
end associate
74+
associate (a => namedConst3%component(0,2))
75+
!CHECK: PRINT *, [INTEGER(4)::1_4,1_4], [INTEGER(4)::2_4,2_4], [INTEGER(4)::2_4,2_4]
76+
print *, lbound(a), ubound(a), shape(a)
77+
end associate
78+
end

0 commit comments

Comments
 (0)