Skip to content

Commit 05756e6

Browse files
committed
[flang] Add more support for alternate returns
Add `hasAlternateReturns` to `evaluate::ProcedureRef`. Add `HasAlternateReturns` to test subprogram symbols. Fix `label01.F90` test: It was checking that "error: " didn't appear in the output. But that was erroneously matching a warning that ends "would be in error:". So change it to check for ": error: " instead. Differential Revision: https://reviews.llvm.org/D83007
1 parent c5b4f03 commit 05756e6

File tree

5 files changed

+26
-8
lines changed

5 files changed

+26
-8
lines changed

flang/include/flang/Evaluate/call.h

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -190,8 +190,10 @@ struct ProcedureDesignator {
190190
class ProcedureRef {
191191
public:
192192
CLASS_BOILERPLATE(ProcedureRef)
193-
ProcedureRef(ProcedureDesignator &&p, ActualArguments &&a)
194-
: proc_{std::move(p)}, arguments_(std::move(a)) {}
193+
ProcedureRef(ProcedureDesignator &&p, ActualArguments &&a,
194+
bool hasAlternateReturns = false)
195+
: proc_{std::move(p)}, arguments_{std::move(a)},
196+
hasAlternateReturns_{hasAlternateReturns} {}
195197
~ProcedureRef();
196198

197199
ProcedureDesignator &proc() { return proc_; }
@@ -202,12 +204,14 @@ class ProcedureRef {
202204
std::optional<Expr<SubscriptInteger>> LEN() const;
203205
int Rank() const;
204206
bool IsElemental() const { return proc_.IsElemental(); }
207+
bool hasAlternateReturns() const { return hasAlternateReturns_; }
205208
bool operator==(const ProcedureRef &) const;
206209
llvm::raw_ostream &AsFortran(llvm::raw_ostream &) const;
207210

208211
protected:
209212
ProcedureDesignator proc_;
210213
ActualArguments arguments_;
214+
bool hasAlternateReturns_;
211215
};
212216

213217
template <typename A> class FunctionRef : public ProcedureRef {

flang/include/flang/Semantics/tools.h

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -100,6 +100,7 @@ bool IsInitialized(const Symbol &, bool ignoreDATAstatements = false);
100100
bool HasIntrinsicTypeName(const Symbol &);
101101
bool IsSeparateModuleProcedureInterface(const Symbol *);
102102
bool IsAutomatic(const Symbol &);
103+
bool HasAlternateReturns(const Symbol &);
103104

104105
// Return an ultimate component of type that matches predicate, or nullptr.
105106
const Symbol *FindUltimateComponent(const DerivedTypeSpec &type,

flang/lib/Semantics/expression.cpp

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2006,7 +2006,8 @@ void ExpressionAnalyzer::Analyze(const parser::CallStmt &callStmt) {
20062006
const parser::Call &call{callStmt.v};
20072007
auto restorer{GetContextualMessages().SetLocation(call.source)};
20082008
ArgumentAnalyzer analyzer{*this, call.source, true /* allowAssumedType */};
2009-
for (const auto &arg : std::get<std::list<parser::ActualArgSpec>>(call.t)) {
2009+
const auto &actualArgList{std::get<std::list<parser::ActualArgSpec>>(call.t)};
2010+
for (const auto &arg : actualArgList) {
20102011
analyzer.Analyze(arg, true /* is subroutine call */);
20112012
}
20122013
if (!analyzer.fatalErrors()) {
@@ -2016,8 +2017,10 @@ void ExpressionAnalyzer::Analyze(const parser::CallStmt &callStmt) {
20162017
ProcedureDesignator *proc{std::get_if<ProcedureDesignator>(&callee->u)};
20172018
CHECK(proc);
20182019
if (CheckCall(call.source, *proc, callee->arguments)) {
2019-
callStmt.typedCall.reset(
2020-
new ProcedureRef{std::move(*proc), std::move(callee->arguments)});
2020+
bool hasAlternateReturns{
2021+
analyzer.GetActuals().size() < actualArgList.size()};
2022+
callStmt.typedCall.reset(new ProcedureRef{std::move(*proc),
2023+
std::move(callee->arguments), hasAlternateReturns});
20212024
}
20222025
}
20232026
}
@@ -2678,6 +2681,7 @@ void ArgumentAnalyzer::Analyze(
26782681
// be detected and represented (they're not expressions).
26792682
// TODO: C1534: Don't allow a "restricted" specific intrinsic to be passed.
26802683
std::optional<ActualArgument> actual;
2684+
bool isAltReturn{false};
26812685
std::visit(common::visitors{
26822686
[&](const common::Indirection<parser::Expr> &x) {
26832687
// TODO: Distinguish & handle procedure name and
@@ -2690,6 +2694,7 @@ void ArgumentAnalyzer::Analyze(
26902694
"alternate return specification may not appear on"
26912695
" function reference"_err_en_US);
26922696
}
2697+
isAltReturn = true;
26932698
},
26942699
[&](const parser::ActualArg::PercentRef &) {
26952700
context_.Say("TODO: %REF() argument"_err_en_US);
@@ -2704,7 +2709,7 @@ void ArgumentAnalyzer::Analyze(
27042709
actual->set_keyword(argKW->v.source);
27052710
}
27062711
actuals_.emplace_back(std::move(*actual));
2707-
} else {
2712+
} else if (!isAltReturn) {
27082713
fatalErrors_ = true;
27092714
}
27102715
}

flang/lib/Semantics/tools.cpp

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1292,4 +1292,13 @@ void LabelEnforce::SayWithConstruct(SemanticsContext &context,
12921292
.Attach(constructLocation, GetEnclosingConstructMsg());
12931293
}
12941294

1295+
bool HasAlternateReturns(const Symbol &subprogram) {
1296+
for (const auto *dummyArg : subprogram.get<SubprogramDetails>().dummyArgs()) {
1297+
if (!dummyArg) {
1298+
return true;
1299+
}
1300+
}
1301+
return false;
1302+
}
1303+
12951304
} // namespace Fortran::semantics

flang/test/Semantics/label01.F90

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,12 @@
11
! RUN: %f18 -funparse-with-symbols -DSTRICT_F18 -Mstandard %s 2>&1 | FileCheck %s
22
! RUN: %f18 -funparse-with-symbols -DARCHAIC_FORTRAN %s 2>&1 | FileCheck %s
3-
! CHECK-NOT: error:{{[[:space:]]}}
3+
! CHECK-NOT: :{{[[:space:]]}}error:{{[[:space:]]}}
44
! FIXME: the above check line does not work because diags are not emitted with error: in them.
55

66
! these are the conformance tests
77
! define STRICT_F18 to eliminate tests of features not in F18
88
! define ARCHAIC_FORTRAN to add test of feature found in Fortran before F95
99

10-
1110
subroutine sub00(a,b,n,m)
1211
integer :: n, m
1312
real a(n)

0 commit comments

Comments
 (0)