Skip to content

Commit 6318951

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 ff7bb17 commit 6318951

File tree

5 files changed

+104
-22
lines changed

5 files changed

+104
-22
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/include/flang/Support/Fortran-features.h

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ ENUM_CLASS(LanguageFeature, BackslashEscapes, OldDebugLines,
5555
UndefinableAsynchronousOrVolatileActual, AutomaticInMainProgram, PrintCptr,
5656
SavedLocalInSpecExpr, PrintNamelist, AssumedRankPassedToNonAssumedRank,
5757
IgnoreIrrelevantAttributes, Unsigned, AmbiguousStructureConstructor,
58-
ContiguousOkForSeqAssociation)
58+
ContiguousOkForSeqAssociation, ForwardRefExplicitTypeDummy)
5959

6060
// Portability and suspicious usage warnings
6161
ENUM_CLASS(UsageWarning, Portability, PointerToUndefinable,

flang/lib/Semantics/resolve-names.cpp

Lines changed: 90 additions & 11 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 {
@@ -1976,6 +1988,9 @@ class ResolveNamesVisitor : public virtual ScopeHandler,
19761988
Scope &topScope_;
19771989

19781990
void PreSpecificationConstruct(const parser::SpecificationConstruct &);
1991+
void EarlyDummyTypeDeclaration(
1992+
const parser::Statement<common::Indirection<parser::TypeDeclarationStmt>>
1993+
&);
19791994
void CreateCommonBlockSymbols(const parser::CommonStmt &);
19801995
void CreateObjectSymbols(const std::list<parser::ObjectDecl> &, Attr);
19811996
void CreateGeneric(const parser::GenericSpec &);
@@ -5611,6 +5626,7 @@ Symbol &DeclarationVisitor::DeclareUnknownEntity(
56115626
} else {
56125627
Symbol &symbol{DeclareEntity<EntityDetails>(name, attrs)};
56135628
if (auto *type{GetDeclTypeSpec()}) {
5629+
ForgetEarlyDeclaredDummyArgument(symbol);
56145630
SetType(name, *type);
56155631
}
56165632
charInfo_.length.reset();
@@ -5687,6 +5703,7 @@ Symbol &DeclarationVisitor::DeclareProcEntity(
56875703
symbol.set(Symbol::Flag::Subroutine);
56885704
}
56895705
} else if (auto *type{GetDeclTypeSpec()}) {
5706+
ForgetEarlyDeclaredDummyArgument(symbol);
56905707
SetType(name, *type);
56915708
symbol.set(Symbol::Flag::Function);
56925709
}
@@ -5701,6 +5718,7 @@ Symbol &DeclarationVisitor::DeclareObjectEntity(
57015718
Symbol &symbol{DeclareEntity<ObjectEntityDetails>(name, attrs)};
57025719
if (auto *details{symbol.detailsIf<ObjectEntityDetails>()}) {
57035720
if (auto *type{GetDeclTypeSpec()}) {
5721+
ForgetEarlyDeclaredDummyArgument(symbol);
57045722
SetType(name, *type);
57055723
}
57065724
if (!arraySpec().empty()) {
@@ -5711,9 +5729,11 @@ Symbol &DeclarationVisitor::DeclareObjectEntity(
57115729
context().SetError(symbol);
57125730
}
57135731
} else if (MustBeScalar(symbol)) {
5714-
context().Warn(common::UsageWarning::PreviousScalarUse, name.source,
5715-
"'%s' appeared earlier as a scalar actual argument to a specification function"_warn_en_US,
5716-
name.source);
5732+
if (!context().HasError(symbol)) {
5733+
context().Warn(common::UsageWarning::PreviousScalarUse, name.source,
5734+
"'%s' appeared earlier as a scalar actual argument to a specification function"_warn_en_US,
5735+
name.source);
5736+
}
57175737
} else if (details->init() || symbol.test(Symbol::Flag::InDataStmt)) {
57185738
Say(name, "'%s' was initialized earlier as a scalar"_err_en_US);
57195739
} else {
@@ -8467,6 +8487,11 @@ const parser::Name *DeclarationVisitor::ResolveDataRef(
84678487
x.u);
84688488
}
84698489

8490+
static bool TypesMismatchIfNonNull(
8491+
const DeclTypeSpec *type1, const DeclTypeSpec *type2) {
8492+
return type1 && type2 && *type1 != *type2;
8493+
}
8494+
84708495
// If implicit types are allowed, ensure name is in the symbol table.
84718496
// Otherwise, report an error if it hasn't been declared.
84728497
const parser::Name *DeclarationVisitor::ResolveName(const parser::Name &name) {
@@ -8488,13 +8513,30 @@ const parser::Name *DeclarationVisitor::ResolveName(const parser::Name &name) {
84888513
symbol->set(Symbol::Flag::ImplicitOrError, false);
84898514
if (IsUplevelReference(*symbol)) {
84908515
MakeHostAssocSymbol(name, *symbol);
8491-
} else if (IsDummy(*symbol) ||
8492-
(!symbol->GetType() && FindCommonBlockContaining(*symbol))) {
8516+
} else if (IsDummy(*symbol)) {
84938517
CheckEntryDummyUse(name.source, symbol);
8518+
ConvertToObjectEntity(*symbol);
8519+
if (IsEarlyDeclaredDummyArgument(*symbol)) {
8520+
ForgetEarlyDeclaredDummyArgument(*symbol);
8521+
if (isImplicitNoneType()) {
8522+
context().Warn(common::LanguageFeature::ForwardRefImplicitNone,
8523+
name.source,
8524+
"'%s' was used under IMPLICIT NONE(TYPE) before being explicitly typed"_warn_en_US,
8525+
name.source);
8526+
} else if (TypesMismatchIfNonNull(
8527+
symbol->GetType(), GetImplicitType(*symbol))) {
8528+
context().Warn(common::LanguageFeature::ForwardRefExplicitTypeDummy,
8529+
name.source,
8530+
"'%s' was used before being explicitly typed (and its implicit type would differ)"_warn_en_US,
8531+
name.source);
8532+
}
8533+
}
8534+
ApplyImplicitRules(*symbol);
8535+
} else if (!symbol->GetType() && FindCommonBlockContaining(*symbol)) {
84948536
ConvertToObjectEntity(*symbol);
84958537
ApplyImplicitRules(*symbol);
84968538
} else if (const auto *tpd{symbol->detailsIf<TypeParamDetails>()};
8497-
tpd && !tpd->attr()) {
8539+
tpd && !tpd->attr()) {
84988540
Say(name,
84998541
"Type parameter '%s' was referenced before being declared"_err_en_US,
85008542
name.source);
@@ -9037,11 +9079,6 @@ static bool IsLocallyImplicitGlobalSymbol(
90379079
return false;
90389080
}
90399081

9040-
static bool TypesMismatchIfNonNull(
9041-
const DeclTypeSpec *type1, const DeclTypeSpec *type2) {
9042-
return type1 && type2 && *type1 != *type2;
9043-
}
9044-
90459082
// Check and set the Function or Subroutine flag on symbol; false on error.
90469083
bool ResolveNamesVisitor::SetProcFlag(
90479084
const parser::Name &name, Symbol &symbol, Symbol::Flag flag) {
@@ -9258,6 +9295,10 @@ void ResolveNamesVisitor::PreSpecificationConstruct(
92589295
const parser::SpecificationConstruct &spec) {
92599296
common::visit(
92609297
common::visitors{
9298+
[&](const parser::Statement<
9299+
common::Indirection<parser::TypeDeclarationStmt>> &y) {
9300+
EarlyDummyTypeDeclaration(y);
9301+
},
92619302
[&](const parser::Statement<Indirection<parser::GenericStmt>> &y) {
92629303
CreateGeneric(std::get<parser::GenericSpec>(y.statement.value().t));
92639304
},
@@ -9286,6 +9327,44 @@ void ResolveNamesVisitor::PreSpecificationConstruct(
92869327
spec.u);
92879328
}
92889329

9330+
void ResolveNamesVisitor::EarlyDummyTypeDeclaration(
9331+
const parser::Statement<common::Indirection<parser::TypeDeclarationStmt>>
9332+
&stmt) {
9333+
context().set_location(stmt.source);
9334+
const auto &[declTypeSpec, attrs, entities] = stmt.statement.value().t;
9335+
if (const auto *intrin{
9336+
std::get_if<parser::IntrinsicTypeSpec>(&declTypeSpec.u)}) {
9337+
if (const auto *intType{std::get_if<parser::IntegerTypeSpec>(&intrin->u)}) {
9338+
if (const auto &kind{intType->v}) {
9339+
if (!parser::Unwrap<parser::KindSelector::StarSize>(*kind) &&
9340+
!parser::Unwrap<parser::IntLiteralConstant>(*kind)) {
9341+
return;
9342+
}
9343+
}
9344+
const DeclTypeSpec *type{nullptr};
9345+
for (const auto &ent : entities) {
9346+
const auto &objName{std::get<parser::ObjectName>(ent.t)};
9347+
Resolve(objName, FindInScope(currScope(), objName));
9348+
if (Symbol * symbol{objName.symbol};
9349+
symbol && IsDummy(*symbol) && NeedsType(*symbol)) {
9350+
if (!type) {
9351+
type = ProcessTypeSpec(declTypeSpec);
9352+
if (!type || !type->IsNumeric(TypeCategory::Integer)) {
9353+
break;
9354+
}
9355+
}
9356+
symbol->SetType(*type);
9357+
NoteEarlyDeclaredDummyArgument(*symbol);
9358+
// Set the Implicit flag to disable bogus errors from
9359+
// being emitted later when this declaration is processed
9360+
// again normally.
9361+
symbol->set(Symbol::Flag::Implicit);
9362+
}
9363+
}
9364+
}
9365+
}
9366+
}
9367+
92899368
void ResolveNamesVisitor::CreateCommonBlockSymbols(
92909369
const parser::CommonStmt &commonStmt) {
92919370
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)