Skip to content

Commit

Permalink
[flang] Forward references to COMMON from specification expr under IM…
Browse files Browse the repository at this point in the history
…PLICIT NONE

As a near-universal extension, Fortran compilers permit forward references
to dummy arguments and variables in COMMON blocks from specification expressions
before an explicit type-declaration-stmt appears for those variables
under IMPLICIT NONE, so long as those variables are later explicitly typed
with the types that regular implicit typing rules would have given them
(usually default INTEGER).

F18 implemented this extension for dummy arguments, but not variables in
COMMON blocks.  Extend the extension to also accept variables in COMMON.

Differential Revision: https://reviews.llvm.org/D145743
  • Loading branch information
klausler committed Mar 10, 2023
1 parent 30705e9 commit d387656
Show file tree
Hide file tree
Showing 5 changed files with 49 additions and 21 deletions.
8 changes: 4 additions & 4 deletions flang/docs/Extensions.md
Expand Up @@ -199,10 +199,10 @@ end
* DATA statement initialization is allowed for procedure pointers outside
structure constructors.
* Nonstandard intrinsic functions: ISNAN, SIZEOF
* A forward reference to a default INTEGER scalar dummy argument is
permitted to appear in a specification expression, such as an array
bound, in a scope with IMPLICIT NONE(TYPE) if the name
of the dummy argument would have caused it to be implicitly typed
* A forward reference to a default INTEGER scalar dummy argument or
`COMMON` block variable is permitted to appear in a specification
expression, such as an array bound, in a scope with IMPLICIT NONE(TYPE)
if the name of the variable would have caused it to be implicitly typed
as default INTEGER if IMPLICIT NONE(TYPE) were absent.
* OPEN(ACCESS='APPEND') is interpreted as OPEN(POSITION='APPEND')
to ease porting from Sun Fortran.
Expand Down
2 changes: 1 addition & 1 deletion flang/include/flang/Common/Fortran-features.h
Expand Up @@ -31,7 +31,7 @@ ENUM_CLASS(LanguageFeature, BackslashEscapes, OldDebugLines,
EquivalenceSameNonSequence, AdditionalIntrinsics, AnonymousParents,
OldLabelDoEndStatements, LogicalIntegerAssignment, EmptySourceFile,
ProgramReturn, ImplicitNoneTypeNever, ImplicitNoneTypeAlways,
ForwardRefDummyImplicitNone, OpenAccessAppend, BOZAsDefaultInteger,
ForwardRefImplicitNone, OpenAccessAppend, BOZAsDefaultInteger,
DistinguishableSpecifics, DefaultSave, PointerInSeqType, NonCharacterFormat,
SaveMainProgram, SaveBigMainProgramVariables)

Expand Down
26 changes: 14 additions & 12 deletions flang/lib/Semantics/resolve-names.cpp
Expand Up @@ -2435,13 +2435,15 @@ void ScopeHandler::ApplyImplicitRules(
}

// Extension: Allow forward references to scalar integer dummy arguments
// to appear in specification expressions under IMPLICIT NONE(TYPE) when
// what would otherwise have been their implicit type is default INTEGER.
// or variables in COMMON to appear in specification expressions under
// IMPLICIT NONE(TYPE) when what would otherwise have been their implicit
// type is default INTEGER.
bool ScopeHandler::ImplicitlyTypeForwardRef(Symbol &symbol) {
if (!inSpecificationPart_ || context().HasError(symbol) || !IsDummy(symbol) ||
if (!inSpecificationPart_ || context().HasError(symbol) ||
!(IsDummy(symbol) || FindCommonBlockContaining(symbol)) ||
symbol.Rank() != 0 ||
!context().languageFeatures().IsEnabled(
common::LanguageFeature::ForwardRefDummyImplicitNone)) {
common::LanguageFeature::ForwardRefImplicitNone)) {
return false;
}
const DeclTypeSpec *type{
Expand All @@ -2456,11 +2458,11 @@ bool ScopeHandler::ImplicitlyTypeForwardRef(Symbol &symbol) {
if (!ConvertToObjectEntity(symbol)) {
return false;
}
// TODO: check no INTENT(OUT)?
// TODO: check no INTENT(OUT) if dummy?
if (context().languageFeatures().ShouldWarn(
common::LanguageFeature::ForwardRefDummyImplicitNone)) {
common::LanguageFeature::ForwardRefImplicitNone)) {
Say(symbol.name(),
"Dummy argument '%s' was used without being explicitly typed"_warn_en_US,
"'%s' was used without (or before) being explicitly typed"_warn_en_US,
symbol.name());
}
symbol.set(Symbol::Flag::Implicit);
Expand Down Expand Up @@ -2639,13 +2641,13 @@ bool ScopeHandler::CheckPossibleBadForwardRef(const Symbol &symbol) {
context().SetError(symbol);
return true;
}
if (IsDummy(symbol) && isImplicitNoneType() &&
symbol.test(Symbol::Flag::Implicit) && !context().HasError(symbol)) {
// Dummy was implicitly typed despite IMPLICIT NONE(TYPE) in
if ((IsDummy(symbol) || FindCommonBlockContaining(symbol)) &&
isImplicitNoneType() && symbol.test(Symbol::Flag::Implicit) &&
!context().HasError(symbol)) {
// Dummy or COMMON was implicitly typed despite IMPLICIT NONE(TYPE) in
// ApplyImplicitRules() due to use in a specification expression,
// and no explicit type declaration appeared later.
Say(symbol.name(),
"No explicit type declared for dummy argument '%s'"_err_en_US);
Say(symbol.name(), "No explicit type declared for '%s'"_err_en_US);
context().SetError(symbol);
return true;
}
Expand Down
1 change: 1 addition & 0 deletions flang/test/Semantics/implicit11.f90
Expand Up @@ -40,6 +40,7 @@ subroutine s3()
subroutine s3a()
implicit none
real :: a(m, n)
!WARN: '%s' was used without (or before) being explicitly typed
!ERROR: No explicit type declared for 'n'
common n
end
Expand Down
33 changes: 29 additions & 4 deletions flang/test/Semantics/resolve103.f90
@@ -1,28 +1,53 @@
! RUN: not %flang_fc1 -pedantic %s 2>&1 | FileCheck %s
! Test extension: allow forward references to dummy arguments
! Test extension: allow forward references to dummy arguments or COMMON
! from specification expressions in scopes with IMPLICIT NONE(TYPE),
! as long as those symbols are eventually typed later with the
! same integer type they would have had without IMPLICIT NONE.

!CHECK: Dummy argument 'n1' was used without being explicitly typed
!CHECK: warning: 'n1' was used without (or before) being explicitly typed
!CHECK: error: No explicit type declared for dummy argument 'n1'
subroutine foo1(a, n1)
implicit none
real a(n1)
end

!CHECK: Dummy argument 'n2' was used without being explicitly typed
!CHECK: warning: 'n2' was used without (or before) being explicitly typed
subroutine foo2(a, n2)
implicit none
real a(n2)
!CHECK: error: The type of 'n2' has already been implicitly declared
double precision n2
end

!CHECK: Dummy argument 'n3' was used without being explicitly typed
!CHECK: warning: 'n3' was used without (or before) being explicitly typed
!CHECK-NOT: error: Dummy argument 'n3'
subroutine foo3(a, n3)
implicit none
real a(n3)
integer n3
end

!CHECK: warning: 'n4' was used without (or before) being explicitly typed
!CHECK: error: No explicit type declared for 'n4'
subroutine foo4(a)
implicit none
real a(n4)
common /b4/ n4
end

!CHECK: warning: 'n5' was used without (or before) being explicitly typed
subroutine foo5(a)
implicit none
real a(n5)
common /b5/ n5
!CHECK: error: The type of 'n5' has already been implicitly declared
double precision n5
end

!CHECK: warning: 'n6' was used without (or before) being explicitly typed
subroutine foo6(a)
implicit none
real a(n6)
common /b6/ n6
integer n6
end

0 comments on commit d387656

Please sign in to comment.