Skip to content

Commit f3b4d25

Browse files
committed
[flang] Allow forward reference to non-default INTEGER dummy
A dummy argument with an explicit INTEGER type of non-default kind can be forward-referenced from a specification expression in many Fortran compilers. Handle by adding type declaration statements to the initial pass over a specification part's declaration constructs. Emit an optional warning under -pedantic. Fixes #140941.
1 parent b7e13ab commit f3b4d25

File tree

4 files changed

+85
-13
lines changed

4 files changed

+85
-13
lines changed

flang/docs/Extensions.md

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -291,7 +291,10 @@ end
291291
* DATA statement initialization is allowed for procedure pointers outside
292292
structure constructors.
293293
* Nonstandard intrinsic functions: ISNAN, SIZEOF
294-
* A forward reference to a default INTEGER scalar dummy argument or
294+
* A forward reference to an INTEGER dummy argument is permitted to appear
295+
in a specification expression, such as an array bound, in a scope with
296+
IMPLICIT NONE(TYPE).
297+
* A forward reference to a default INTEGER scalar
295298
`COMMON` block variable is permitted to appear in a specification
296299
expression, such as an array bound, in a scope with IMPLICIT NONE(TYPE)
297300
if the name of the variable would have caused it to be implicitly typed

flang/lib/Semantics/resolve-names.cpp

Lines changed: 72 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -768,10 +768,22 @@ class ScopeHandler : public ImplicitRulesVisitor {
768768
deferImplicitTyping_ = skipImplicitTyping_ = skip;
769769
}
770770

771+
void NoteEarlyDeclaredDummyArgument(Symbol &symbol) {
772+
earlyDeclaredDummyArguments_.insert(symbol);
773+
}
774+
bool IsEarlyDeclaredDummyArgument(Symbol &symbol) {
775+
return earlyDeclaredDummyArguments_.find(symbol) !=
776+
earlyDeclaredDummyArguments_.end();
777+
}
778+
void ForgetEarlyDeclaredDummyArgument(Symbol &symbol) {
779+
earlyDeclaredDummyArguments_.erase(symbol);
780+
}
781+
771782
private:
772783
Scope *currScope_{nullptr};
773784
FuncResultStack funcResultStack_{*this};
774785
std::map<Scope *, DeferredDeclarationState> deferred_;
786+
UnorderedSymbolSet earlyDeclaredDummyArguments_;
775787
};
776788

777789
class ModuleVisitor : public virtual ScopeHandler {
@@ -1119,6 +1131,7 @@ class DeclarationVisitor : public ArraySpecVisitor,
11191131
template <typename T>
11201132
Symbol &DeclareEntity(const parser::Name &name, Attrs attrs) {
11211133
Symbol &symbol{MakeSymbol(name, attrs)};
1134+
ForgetEarlyDeclaredDummyArgument(symbol);
11221135
if (context().HasError(symbol) || symbol.has<T>()) {
11231136
return symbol; // OK or error already reported
11241137
} else if (symbol.has<UnknownDetails>()) {
@@ -1976,6 +1989,9 @@ class ResolveNamesVisitor : public virtual ScopeHandler,
19761989
Scope &topScope_;
19771990

19781991
void PreSpecificationConstruct(const parser::SpecificationConstruct &);
1992+
void EarlyDummyTypeDeclaration(
1993+
const parser::Statement<common::Indirection<parser::TypeDeclarationStmt>>
1994+
&);
19791995
void CreateCommonBlockSymbols(const parser::CommonStmt &);
19801996
void CreateObjectSymbols(const std::list<parser::ObjectDecl> &, Attr);
19811997
void CreateGeneric(const parser::GenericSpec &);
@@ -8488,13 +8504,24 @@ const parser::Name *DeclarationVisitor::ResolveName(const parser::Name &name) {
84888504
symbol->set(Symbol::Flag::ImplicitOrError, false);
84898505
if (IsUplevelReference(*symbol)) {
84908506
MakeHostAssocSymbol(name, *symbol);
8491-
} else if (IsDummy(*symbol) ||
8492-
(!symbol->GetType() && FindCommonBlockContaining(*symbol))) {
8507+
} else if (IsDummy(*symbol)) {
84938508
CheckEntryDummyUse(name.source, symbol);
8509+
ConvertToObjectEntity(*symbol);
8510+
if (IsEarlyDeclaredDummyArgument(*symbol)) {
8511+
ForgetEarlyDeclaredDummyArgument(*symbol);
8512+
if (isImplicitNoneType()) {
8513+
context().Warn(common::LanguageFeature::ForwardRefImplicitNone,
8514+
name.source,
8515+
"'%s' was used under IMPLICIT NONE(TYPE) before being explicitly typed"_warn_en_US,
8516+
name.source);
8517+
}
8518+
}
8519+
ApplyImplicitRules(*symbol);
8520+
} else if (!symbol->GetType() && FindCommonBlockContaining(*symbol)) {
84948521
ConvertToObjectEntity(*symbol);
84958522
ApplyImplicitRules(*symbol);
84968523
} else if (const auto *tpd{symbol->detailsIf<TypeParamDetails>()};
8497-
tpd && !tpd->attr()) {
8524+
tpd && !tpd->attr()) {
84988525
Say(name,
84998526
"Type parameter '%s' was referenced before being declared"_err_en_US,
85008527
name.source);
@@ -9258,6 +9285,10 @@ void ResolveNamesVisitor::PreSpecificationConstruct(
92589285
const parser::SpecificationConstruct &spec) {
92599286
common::visit(
92609287
common::visitors{
9288+
[&](const parser::Statement<
9289+
common::Indirection<parser::TypeDeclarationStmt>> &y) {
9290+
EarlyDummyTypeDeclaration(y);
9291+
},
92619292
[&](const parser::Statement<Indirection<parser::GenericStmt>> &y) {
92629293
CreateGeneric(std::get<parser::GenericSpec>(y.statement.value().t));
92639294
},
@@ -9286,6 +9317,44 @@ void ResolveNamesVisitor::PreSpecificationConstruct(
92869317
spec.u);
92879318
}
92889319

9320+
void ResolveNamesVisitor::EarlyDummyTypeDeclaration(
9321+
const parser::Statement<common::Indirection<parser::TypeDeclarationStmt>>
9322+
&stmt) {
9323+
context().set_location(stmt.source);
9324+
const auto &[declTypeSpec, attrs, entities] = stmt.statement.value().t;
9325+
if (const auto *intrin{
9326+
std::get_if<parser::IntrinsicTypeSpec>(&declTypeSpec.u)}) {
9327+
if (const auto *intType{std::get_if<parser::IntegerTypeSpec>(&intrin->u)}) {
9328+
if (const auto &kind{intType->v}) {
9329+
if (!parser::Unwrap<parser::KindSelector::StarSize>(*kind) &&
9330+
!parser::Unwrap<parser::IntLiteralConstant>(*kind)) {
9331+
return;
9332+
}
9333+
}
9334+
const DeclTypeSpec *type{nullptr};
9335+
for (const auto &ent : entities) {
9336+
const auto &objName{std::get<parser::ObjectName>(ent.t)};
9337+
Resolve(objName, FindInScope(currScope(), objName));
9338+
if (Symbol * symbol{objName.symbol};
9339+
symbol && IsDummy(*symbol) && NeedsType(*symbol)) {
9340+
if (!type) {
9341+
type = ProcessTypeSpec(declTypeSpec);
9342+
if (!type || !type->IsNumeric(TypeCategory::Integer)) {
9343+
break;
9344+
}
9345+
}
9346+
symbol->SetType(*type);
9347+
NoteEarlyDeclaredDummyArgument(*symbol);
9348+
// Set the Implicit flag to disable bogus errors from
9349+
// being emitted later when this declaration is processed
9350+
// again normally.
9351+
symbol->set(Symbol::Flag::Implicit);
9352+
}
9353+
}
9354+
}
9355+
}
9356+
}
9357+
92899358
void ResolveNamesVisitor::CreateCommonBlockSymbols(
92909359
const parser::CommonStmt &commonStmt) {
92919360
for (const parser::CommonStmt::Block &block : commonStmt.blocks) {

flang/test/Semantics/OpenMP/linear-clause01.f90

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,10 +20,8 @@ subroutine linear_clause_02(arg_01, arg_02)
2020
!$omp declare simd linear(val(arg_01))
2121
real, intent(in) :: arg_01(:)
2222

23-
!ERROR: The list item 'arg_02' specified without the REF 'linear-modifier' must be of INTEGER type
2423
!ERROR: If the `linear-modifier` is REF or UVAL, the list item 'arg_02' must be a dummy argument without the VALUE attribute
2524
!$omp declare simd linear(uval(arg_02))
26-
!ERROR: The type of 'arg_02' has already been implicitly declared
2725
integer, value, intent(in) :: arg_02
2826

2927
!ERROR: The list item 'var' specified without the REF 'linear-modifier' must be of INTEGER type

flang/test/Semantics/resolve103.f90

Lines changed: 9 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,7 @@
11
! RUN: not %flang_fc1 -pedantic %s 2>&1 | FileCheck %s
22
! Test extension: allow forward references to dummy arguments or COMMON
33
! from specification expressions in scopes with IMPLICIT NONE(TYPE),
4-
! as long as those symbols are eventually typed later with the
5-
! same integer type they would have had without IMPLICIT NONE.
4+
! as long as those symbols are eventually typed later.
65

76
!CHECK: warning: 'n1' was used without (or before) being explicitly typed
87
!CHECK: error: No explicit type declared for dummy argument 'n1'
@@ -19,12 +18,15 @@ subroutine foo2(a, n2)
1918
double precision n2
2019
end
2120

22-
!CHECK: warning: 'n3' was used without (or before) being explicitly typed
23-
!CHECK-NOT: error: Dummy argument 'n3'
24-
subroutine foo3(a, n3)
21+
!CHECK: warning: 'n3a' was used under IMPLICIT NONE(TYPE) before being explicitly typed
22+
!CHECK: warning: 'n3b' was used under IMPLICIT NONE(TYPE) before being explicitly typed
23+
!CHECK-NOT: error: Dummy argument 'n3a'
24+
!CHECK-NOT: error: Dummy argument 'n3b'
25+
subroutine foo3(a, n3a, n3b)
2526
implicit none
26-
real a(n3)
27-
integer n3
27+
integer a(n3a, n3b)
28+
integer n3a
29+
integer(8) n3b
2830
end
2931

3032
!CHECK: warning: 'n4' was used without (or before) being explicitly typed

0 commit comments

Comments
 (0)