Skip to content

Commit 1ad2ba5

Browse files
klauslerjeanPerier
authored andcommitted
[flang] Adjust names in Semantics that imply too much (NFC)
Some kinds of Fortran arrays are declared with the same syntax, and it is impossible to tell from a shape (:, :) or (*) whether the object is assumed shape, deferred shape, assumed size, implied shape, or whatever without recourse to more information about the symbol in question. This patch softens the names of some predicate functions (IsAssumedShape to CanBeAssumedShape) and makes others more reflective of the syntax they represent (isAssumed to isStar) in an attempt to encourage coders to seek and find definitive predicate functions whose names deliver what they seem to mean. Address TODO comments in IsSimplyContiguous() by using the updated IsAssumedShape() predicate. Differential Revision: https://reviews.llvm.org/D114829
1 parent 2d0edd5 commit 1ad2ba5

File tree

12 files changed

+117
-93
lines changed

12 files changed

+117
-93
lines changed

flang/include/flang/Evaluate/tools.h

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1054,6 +1054,8 @@ bool IsProcedurePointer(const Symbol &);
10541054
bool IsAutomatic(const Symbol &);
10551055
bool IsSaved(const Symbol &); // saved implicitly or explicitly
10561056
bool IsDummy(const Symbol &);
1057+
bool IsAssumedShape(const Symbol &);
1058+
bool IsDeferredShape(const Symbol &);
10571059
bool IsFunctionResult(const Symbol &);
10581060
bool IsKindTypeParameter(const Symbol &);
10591061
bool IsLenTypeParameter(const Symbol &);

flang/include/flang/Semantics/symbol.h

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -188,11 +188,11 @@ class ObjectEntityDetails : public EntityDetails {
188188
}
189189
bool IsArray() const { return !shape_.empty(); }
190190
bool IsCoarray() const { return !coshape_.empty(); }
191-
bool IsAssumedShape() const { return isDummy() && shape_.IsAssumedShape(); }
192-
bool IsDeferredShape() const {
193-
return !isDummy() && shape_.IsDeferredShape();
191+
bool CanBeAssumedShape() const {
192+
return isDummy() && shape_.CanBeAssumedShape();
194193
}
195-
bool IsAssumedSize() const { return isDummy() && shape_.IsAssumedSize(); }
194+
bool CanBeDeferredShape() const { return shape_.CanBeDeferredShape(); }
195+
bool IsAssumedSize() const { return isDummy() && shape_.CanBeAssumedSize(); }
196196
bool IsAssumedRank() const { return isDummy() && shape_.IsAssumedRank(); }
197197

198198
private:

flang/include/flang/Semantics/type.h

Lines changed: 39 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -47,20 +47,26 @@ using SubscriptIntExpr = evaluate::Expr<evaluate::SubscriptInteger>;
4747
using MaybeSubscriptIntExpr = std::optional<SubscriptIntExpr>;
4848
using KindExpr = SubscriptIntExpr;
4949

50-
// An array spec bound: an explicit integer expression or ASSUMED or DEFERRED
50+
// An array spec bound: an explicit integer expression, assumed size
51+
// or implied shape(*), or assumed or deferred shape(:). In the absence
52+
// of explicit lower bounds it is not possible to distinguish assumed
53+
// shape bounds from deferred shape bounds without knowing whether the
54+
// particular symbol is an allocatable/pointer or a non-allocatable
55+
// non-pointer dummy; use the symbol-based predicates for those
56+
// determinations.
5157
class Bound {
5258
public:
53-
static Bound Assumed() { return Bound(Category::Assumed); }
54-
static Bound Deferred() { return Bound(Category::Deferred); }
59+
static Bound Star() { return Bound(Category::Star); }
60+
static Bound Colon() { return Bound(Category::Colon); }
5561
explicit Bound(MaybeSubscriptIntExpr &&expr) : expr_{std::move(expr)} {}
5662
explicit Bound(common::ConstantSubscript bound);
5763
Bound(const Bound &) = default;
5864
Bound(Bound &&) = default;
5965
Bound &operator=(const Bound &) = default;
6066
Bound &operator=(Bound &&) = default;
6167
bool isExplicit() const { return category_ == Category::Explicit; }
62-
bool isAssumed() const { return category_ == Category::Assumed; }
63-
bool isDeferred() const { return category_ == Category::Deferred; }
68+
bool isStar() const { return category_ == Category::Star; }
69+
bool isColon() const { return category_ == Category::Colon; }
6470
MaybeSubscriptIntExpr &GetExplicit() { return expr_; }
6571
const MaybeSubscriptIntExpr &GetExplicit() const { return expr_; }
6672
void SetExplicit(MaybeSubscriptIntExpr &&expr) {
@@ -69,7 +75,7 @@ class Bound {
6975
}
7076

7177
private:
72-
enum class Category { Explicit, Deferred, Assumed };
78+
enum class Category { Explicit, Star, Colon };
7379
Bound(Category category) : category_{category} {}
7480
Bound(Category category, MaybeSubscriptIntExpr &&expr)
7581
: category_{category}, expr_{std::move(expr)} {}
@@ -78,7 +84,8 @@ class Bound {
7884
friend llvm::raw_ostream &operator<<(llvm::raw_ostream &, const Bound &);
7985
};
8086

81-
// A type parameter value: integer expression or assumed or deferred.
87+
// A type parameter value: integer expression, assumed/implied(*),
88+
// or deferred(:).
8289
class ParamValue {
8390
public:
8491
static ParamValue Assumed(common::TypeParamAttr attr) {
@@ -176,28 +183,26 @@ class ShapeSpec {
176183
return MakeExplicit(Bound{1}, std::move(ub));
177184
}
178185
// 1:
179-
static ShapeSpec MakeAssumed() {
180-
return ShapeSpec(Bound{1}, Bound::Deferred());
186+
static ShapeSpec MakeAssumedShape() {
187+
return ShapeSpec(Bound{1}, Bound::Colon());
181188
}
182189
// lb:
183-
static ShapeSpec MakeAssumed(Bound &&lb) {
184-
return ShapeSpec(std::move(lb), Bound::Deferred());
190+
static ShapeSpec MakeAssumedShape(Bound &&lb) {
191+
return ShapeSpec(std::move(lb), Bound::Colon());
185192
}
186193
// :
187194
static ShapeSpec MakeDeferred() {
188-
return ShapeSpec(Bound::Deferred(), Bound::Deferred());
195+
return ShapeSpec(Bound::Colon(), Bound::Colon());
189196
}
190197
// 1:*
191-
static ShapeSpec MakeImplied() {
192-
return ShapeSpec(Bound{1}, Bound::Assumed());
193-
}
198+
static ShapeSpec MakeImplied() { return ShapeSpec(Bound{1}, Bound::Star()); }
194199
// lb:*
195200
static ShapeSpec MakeImplied(Bound &&lb) {
196-
return ShapeSpec(std::move(lb), Bound::Assumed());
201+
return ShapeSpec(std::move(lb), Bound::Star());
197202
}
198203
// ..
199204
static ShapeSpec MakeAssumedRank() {
200-
return ShapeSpec(Bound::Assumed(), Bound::Assumed());
205+
return ShapeSpec(Bound::Star(), Bound::Star());
201206
}
202207

203208
ShapeSpec(const ShapeSpec &) = default;
@@ -220,11 +225,15 @@ class ShapeSpec {
220225
struct ArraySpec : public std::vector<ShapeSpec> {
221226
ArraySpec() {}
222227
int Rank() const { return size(); }
228+
// These names are not exclusive, as some categories cannot be
229+
// distinguished without knowing whether the particular symbol
230+
// is allocatable, pointer, or a non-allocatable non-pointer dummy.
231+
// Use the symbol-based predicates for exact results.
223232
inline bool IsExplicitShape() const;
224-
inline bool IsAssumedShape() const;
225-
inline bool IsDeferredShape() const;
226-
inline bool IsImpliedShape() const;
227-
inline bool IsAssumedSize() const;
233+
inline bool CanBeAssumedShape() const;
234+
inline bool CanBeDeferredShape() const;
235+
inline bool CanBeImpliedShape() const;
236+
inline bool CanBeAssumedSize() const;
228237
inline bool IsAssumedRank() const;
229238

230239
private:
@@ -399,25 +408,25 @@ class ProcInterface {
399408
inline bool ArraySpec::IsExplicitShape() const {
400409
return CheckAll([](const ShapeSpec &x) { return x.ubound().isExplicit(); });
401410
}
402-
inline bool ArraySpec::IsAssumedShape() const {
403-
return CheckAll([](const ShapeSpec &x) { return x.ubound().isDeferred(); });
411+
inline bool ArraySpec::CanBeAssumedShape() const {
412+
return CheckAll([](const ShapeSpec &x) { return x.ubound().isColon(); });
404413
}
405-
inline bool ArraySpec::IsDeferredShape() const {
414+
inline bool ArraySpec::CanBeDeferredShape() const {
406415
return CheckAll([](const ShapeSpec &x) {
407-
return x.lbound().isDeferred() && x.ubound().isDeferred();
416+
return x.lbound().isColon() && x.ubound().isColon();
408417
});
409418
}
410-
inline bool ArraySpec::IsImpliedShape() const {
419+
inline bool ArraySpec::CanBeImpliedShape() const {
411420
return !IsAssumedRank() &&
412-
CheckAll([](const ShapeSpec &x) { return x.ubound().isAssumed(); });
421+
CheckAll([](const ShapeSpec &x) { return x.ubound().isStar(); });
413422
}
414-
inline bool ArraySpec::IsAssumedSize() const {
415-
return !empty() && !IsAssumedRank() && back().ubound().isAssumed() &&
423+
inline bool ArraySpec::CanBeAssumedSize() const {
424+
return !empty() && !IsAssumedRank() && back().ubound().isStar() &&
416425
std::all_of(begin(), end() - 1,
417426
[](const ShapeSpec &x) { return x.ubound().isExplicit(); });
418427
}
419428
inline bool ArraySpec::IsAssumedRank() const {
420-
return Rank() == 1 && front().lbound().isAssumed();
429+
return Rank() == 1 && front().lbound().isStar();
421430
}
422431

423432
inline IntrinsicTypeSpec *DeclTypeSpec::AsIntrinsic() {

flang/lib/Evaluate/characteristics.cpp

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -189,21 +189,21 @@ std::optional<Expr<SubscriptInteger>> TypeAndShape::MeasureSizeInBytes(
189189
}
190190

191191
void TypeAndShape::AcquireAttrs(const semantics::Symbol &symbol) {
192+
if (IsAssumedShape(symbol)) {
193+
attrs_.set(Attr::AssumedShape);
194+
}
195+
if (IsDeferredShape(symbol)) {
196+
attrs_.set(Attr::DeferredShape);
197+
}
192198
if (const auto *object{
193199
symbol.GetUltimate().detailsIf<semantics::ObjectEntityDetails>()}) {
194200
corank_ = object->coshape().Rank();
195201
if (object->IsAssumedRank()) {
196202
attrs_.set(Attr::AssumedRank);
197203
}
198-
if (object->IsAssumedShape()) {
199-
attrs_.set(Attr::AssumedShape);
200-
}
201204
if (object->IsAssumedSize()) {
202205
attrs_.set(Attr::AssumedSize);
203206
}
204-
if (object->IsDeferredShape()) {
205-
attrs_.set(Attr::DeferredShape);
206-
}
207207
if (object->IsCoarray()) {
208208
attrs_.set(Attr::Coarray);
209209
}

flang/lib/Evaluate/check-expression.cpp

Lines changed: 3 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -659,18 +659,12 @@ class IsSimplyContiguousHelper
659659
// simple contiguity to allow their use in contexts like
660660
// data targets in pointer assignments with remapping.
661661
return true;
662-
} else if (semantics::IsPointer(ultimate)) {
662+
} else if (semantics::IsPointer(ultimate) ||
663+
semantics::IsAssumedShape(ultimate)) {
663664
return false;
664-
} else if (semantics::IsAllocatable(ultimate)) {
665-
// TODO: this could be merged with the case below if
666-
// details->IsAssumedShape() did not return true for allocatables. Current
667-
// ArraySpec building in semantics does not allow making a difference
668-
// between some_assumed_shape(:) and some_allocatable(:). Both
669-
// isDeferredShape() and isAssumedShape() are true in each case.
670-
return true;
671665
} else if (const auto *details{
672666
ultimate.detailsIf<semantics::ObjectEntityDetails>()}) {
673-
return !details->IsAssumedShape() && !details->IsAssumedRank();
667+
return !details->IsAssumedRank();
674668
} else if (auto assoc{Base::operator()(ultimate)}) {
675669
return assoc;
676670
} else {

flang/lib/Evaluate/shape.cpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ bool IsImpliedShape(const Symbol &original) {
2727
const Symbol &symbol{ResolveAssociations(original)};
2828
const auto *details{symbol.detailsIf<semantics::ObjectEntityDetails>()};
2929
return details && symbol.attrs().test(semantics::Attr::PARAMETER) &&
30-
details->shape().IsImpliedShape();
30+
details->shape().CanBeImpliedShape();
3131
}
3232

3333
bool IsExplicitShape(const Symbol &original) {

flang/lib/Evaluate/tools.cpp

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1252,6 +1252,20 @@ bool IsDummy(const Symbol &symbol) {
12521252
ResolveAssociations(symbol).details());
12531253
}
12541254

1255+
bool IsAssumedShape(const Symbol &symbol) {
1256+
const Symbol &ultimate{ResolveAssociations(symbol)};
1257+
const auto *object{ultimate.detailsIf<ObjectEntityDetails>()};
1258+
return object && object->CanBeAssumedShape() &&
1259+
!evaluate::IsAllocatableOrPointer(ultimate);
1260+
}
1261+
1262+
bool IsDeferredShape(const Symbol &symbol) {
1263+
const Symbol &ultimate{ResolveAssociations(symbol)};
1264+
const auto *object{ultimate.detailsIf<ObjectEntityDetails>()};
1265+
return object && object->CanBeDeferredShape() &&
1266+
evaluate::IsAllocatableOrPointer(ultimate);
1267+
}
1268+
12551269
bool IsFunctionResult(const Symbol &original) {
12561270
const Symbol &symbol{GetAssociationRoot(original)};
12571271
return (symbol.has<ObjectEntityDetails>() &&

flang/lib/Semantics/check-call.cpp

Lines changed: 13 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -161,9 +161,13 @@ static void CheckExplicitDataArg(const characteristics::DummyDataObject &dummy,
161161
characteristics::TypeAndShape::Attr::AssumedRank)) {
162162
} else if (!dummy.type.attrs().test(
163163
characteristics::TypeAndShape::Attr::AssumedShape) &&
164+
!dummy.type.attrs().test(
165+
characteristics::TypeAndShape::Attr::DeferredShape) &&
164166
(actualType.Rank() > 0 || IsArrayElement(actual))) {
165167
// Sequence association (15.5.2.11) applies -- rank need not match
166-
// if the actual argument is an array or array element designator.
168+
// if the actual argument is an array or array element designator,
169+
// and the dummy is not assumed-shape or an INTENT(IN) pointer
170+
// that's standing in for an assumed-shape dummy.
167171
} else {
168172
// Let CheckConformance accept scalars; storage association
169173
// cases are checked here below.
@@ -322,7 +326,7 @@ static void CheckExplicitDataArg(const characteristics::DummyDataObject &dummy,
322326
"Scalar POINTER target may not be associated with a %s array"_err_en_US,
323327
dummyName);
324328
}
325-
if (actualLastObject && actualLastObject->IsAssumedShape()) {
329+
if (actualLastSymbol && IsAssumedShape(*actualLastSymbol)) {
326330
messages.Say(
327331
"Element of assumed-shape array may not be associated with a %s array"_err_en_US,
328332
dummyName);
@@ -362,13 +366,13 @@ static void CheckExplicitDataArg(const characteristics::DummyDataObject &dummy,
362366
}
363367

364368
// Cases when temporaries might be needed but must not be permitted.
369+
bool actualIsContiguous{IsSimplyContiguous(actual, context)};
370+
bool dummyIsAssumedShape{dummy.type.attrs().test(
371+
characteristics::TypeAndShape::Attr::AssumedShape)};
365372
bool dummyIsPointer{
366373
dummy.attrs.test(characteristics::DummyDataObject::Attr::Pointer)};
367374
bool dummyIsContiguous{
368375
dummy.attrs.test(characteristics::DummyDataObject::Attr::Contiguous)};
369-
bool actualIsContiguous{IsSimplyContiguous(actual, context)};
370-
bool dummyIsAssumedShape{dummy.type.attrs().test(
371-
characteristics::TypeAndShape::Attr::AssumedShape)};
372376
if ((actualIsAsynchronous || actualIsVolatile) &&
373377
(dummyIsAsynchronous || dummyIsVolatile) && !dummyIsValue) {
374378
if (actualIsCoindexed) { // C1538
@@ -675,9 +679,10 @@ static void CheckExplicitInterfaceArg(evaluate::ActualArgument &arg,
675679
messages.Say(
676680
"Assumed-type '%s' may be associated only with an assumed-type %s"_err_en_US,
677681
assumed.name(), dummyName);
678-
} else if (const auto *details{
679-
assumed.detailsIf<ObjectEntityDetails>()}) {
680-
if (!(details->IsAssumedShape() || details->IsAssumedRank())) {
682+
} else {
683+
const auto *details{assumed.detailsIf<ObjectEntityDetails>()};
684+
if (!(IsAssumedShape(assumed) ||
685+
(details && details->IsAssumedRank()))) {
681686
messages.Say( // C711
682687
"Assumed-type '%s' must be either assumed shape or assumed rank to be associated with assumed-type %s"_err_en_US,
683688
assumed.name(), dummyName);

flang/lib/Semantics/check-declarations.cpp

Lines changed: 21 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -455,7 +455,7 @@ void CheckHelper::CheckObjectEntity(
455455
CheckAssumedTypeEntity(symbol, details);
456456
WarnMissingFinal(symbol);
457457
if (!details.coshape().empty()) {
458-
bool isDeferredCoshape{details.coshape().IsDeferredShape()};
458+
bool isDeferredCoshape{details.coshape().CanBeDeferredShape()};
459459
if (IsAllocatable(symbol)) {
460460
if (!isDeferredCoshape) { // C827
461461
messages_.Say("'%s' is an ALLOCATABLE coarray and must have a deferred"
@@ -469,7 +469,7 @@ void CheckHelper::CheckObjectEntity(
469469
" attribute%s"_err_en_US,
470470
symbol.name(), deferredMsg);
471471
} else {
472-
if (!details.coshape().IsAssumedSize()) { // C828
472+
if (!details.coshape().CanBeAssumedSize()) { // C828
473473
messages_.Say(
474474
"'%s' is a non-ALLOCATABLE coarray and must have an explicit coshape"_err_en_US,
475475
symbol.name());
@@ -670,16 +670,18 @@ void CheckHelper::CheckArraySpec(
670670
return;
671671
}
672672
bool isExplicit{arraySpec.IsExplicitShape()};
673-
bool isDeferred{arraySpec.IsDeferredShape()};
674-
bool isImplied{arraySpec.IsImpliedShape()};
675-
bool isAssumedShape{arraySpec.IsAssumedShape()};
676-
bool isAssumedSize{arraySpec.IsAssumedSize()};
673+
bool canBeDeferred{arraySpec.CanBeDeferredShape()};
674+
bool canBeImplied{arraySpec.CanBeImpliedShape()};
675+
bool canBeAssumedShape{arraySpec.CanBeAssumedShape()};
676+
bool canBeAssumedSize{arraySpec.CanBeAssumedSize()};
677677
bool isAssumedRank{arraySpec.IsAssumedRank()};
678678
std::optional<parser::MessageFixedText> msg;
679-
if (symbol.test(Symbol::Flag::CrayPointee) && !isExplicit && !isAssumedSize) {
679+
if (symbol.test(Symbol::Flag::CrayPointee) && !isExplicit &&
680+
!canBeAssumedSize) {
680681
msg = "Cray pointee '%s' must have must have explicit shape or"
681682
" assumed size"_err_en_US;
682-
} else if (IsAllocatableOrPointer(symbol) && !isDeferred && !isAssumedRank) {
683+
} else if (IsAllocatableOrPointer(symbol) && !canBeDeferred &&
684+
!isAssumedRank) {
683685
if (symbol.owner().IsDerivedType()) { // C745
684686
if (IsAllocatable(symbol)) {
685687
msg = "Allocatable array component '%s' must have"
@@ -697,22 +699,22 @@ void CheckHelper::CheckArraySpec(
697699
}
698700
}
699701
} else if (IsDummy(symbol)) {
700-
if (isImplied && !isAssumedSize) { // C836
702+
if (canBeImplied && !canBeAssumedSize) { // C836
701703
msg = "Dummy array argument '%s' may not have implied shape"_err_en_US;
702704
}
703-
} else if (isAssumedShape && !isDeferred) {
705+
} else if (canBeAssumedShape && !canBeDeferred) {
704706
msg = "Assumed-shape array '%s' must be a dummy argument"_err_en_US;
705-
} else if (isAssumedSize && !isImplied) { // C833
707+
} else if (canBeAssumedSize && !canBeImplied) { // C833
706708
msg = "Assumed-size array '%s' must be a dummy argument"_err_en_US;
707709
} else if (isAssumedRank) { // C837
708710
msg = "Assumed-rank array '%s' must be a dummy argument"_err_en_US;
709-
} else if (isImplied) {
711+
} else if (canBeImplied) {
710712
if (!IsNamedConstant(symbol)) { // C835, C836
711713
msg = "Implied-shape array '%s' must be a named constant or a "
712714
"dummy argument"_err_en_US;
713715
}
714716
} else if (IsNamedConstant(symbol)) {
715-
if (!isExplicit && !isImplied) {
717+
if (!isExplicit && !canBeImplied) {
716718
msg = "Named constant '%s' array must have constant or"
717719
" implied shape"_err_en_US;
718720
}
@@ -1965,15 +1967,13 @@ void CheckHelper::CheckDioVlistArg(
19651967
if (CheckDioDummyIsData(subp, arg, argPosition)) {
19661968
CheckDioDummyIsDefaultInteger(subp, *arg);
19671969
CheckDioDummyAttrs(subp, *arg, Attr::INTENT_IN);
1968-
if (const auto *objectDetails{arg->detailsIf<ObjectEntityDetails>()}) {
1969-
if (objectDetails->shape().IsDeferredShape()) {
1970-
return;
1971-
}
1970+
const auto *objectDetails{arg->detailsIf<ObjectEntityDetails>()};
1971+
if (!objectDetails || !objectDetails->shape().CanBeDeferredShape()) {
1972+
messages_.Say(arg->name(),
1973+
"Dummy argument '%s' of a defined input/output procedure must be"
1974+
" deferred shape"_err_en_US,
1975+
arg->name());
19721976
}
1973-
messages_.Say(arg->name(),
1974-
"Dummy argument '%s' of a defined input/output procedure must be"
1975-
" deferred shape"_err_en_US,
1976-
arg->name());
19771977
}
19781978
}
19791979

0 commit comments

Comments
 (0)