mirror of
https://github.com/llvm/llvm-project.git
synced 2025-04-17 15:56:40 +00:00

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
63 lines
1.2 KiB
Fortran
63 lines
1.2 KiB
Fortran
! RUN: %python %S/test_errors.py %s %flang_fc1
|
|
|
|
! Test use of implicitly declared variable in specification expression
|
|
|
|
subroutine s1()
|
|
m = 1
|
|
contains
|
|
subroutine s1a()
|
|
implicit none
|
|
!ERROR: No explicit type declared for 'n'
|
|
real :: a(m, n)
|
|
end
|
|
subroutine s1b()
|
|
!ERROR: Implicitly typed local entity 'n' not allowed in specification expression
|
|
real :: a(m, n)
|
|
end
|
|
end
|
|
|
|
subroutine s2()
|
|
type :: t(m, n)
|
|
integer, len :: m
|
|
integer, len :: n
|
|
end type
|
|
n = 1
|
|
contains
|
|
subroutine s2a()
|
|
!ERROR: Implicitly typed local entity 'm' not allowed in specification expression
|
|
type(t(m, n)) :: a
|
|
end
|
|
subroutine s2b()
|
|
implicit none
|
|
!ERROR: No explicit type declared for 'm'
|
|
character(m) :: a
|
|
end
|
|
end
|
|
|
|
subroutine s3()
|
|
m = 1
|
|
contains
|
|
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
|
|
subroutine s3b()
|
|
! n is okay here because it is in a common block
|
|
real :: a(m, n)
|
|
common n
|
|
end
|
|
end
|
|
|
|
subroutine s4()
|
|
implicit none
|
|
contains
|
|
subroutine s4a()
|
|
!ERROR: No explicit type declared for 'n'
|
|
real :: a(n)
|
|
end
|
|
end
|
|
|