llvm-project/flang/test/Semantics/resolve42.f90

Ignoring revisions in .git-blame-ignore-revs. Click here to bypass and see the normal blame view.

115 lines
2.4 KiB
Fortran
Raw Normal View History

! RUN: %S/test_errors.sh %s %t %f18
subroutine s1
!ERROR: Array 'z' without ALLOCATABLE or POINTER attribute must have explicit shape
common x, y(4), z(:)
end
subroutine s2
common /c1/ x, y, z
!ERROR: 'y' is already in a COMMON block
common y
end
subroutine s3
[flang] Fix bug accessing implicit variable in specification expression A specification expression can reference an implicitly declared variable in the host procedure. Because we have to process specification parts before execution parts, this may be the first time we encounter the variable. We were assuming the variable was implicitly declared in the scope where it was encountered, leading to an error because local variables may not be referenced in specification expressions. The fix is to tentatively create the implicit variable in the host procedure because that is the only way the specification expression can be valid. We mark it with the flag `ImplicitOrError` to indicate that either it must be implicitly defined in the host (by being mentioned in the execution part) or else its use turned out to be an error. We need to apply the implicit type rules of the host, which requires some changes to implicit typing. Variables in common blocks are allowed to appear in specification expressions (because they are not locals) but the common block definition may not appear until after their use. To handle this we create common block symbols and object entities for each common block object during the `PreSpecificationConstruct` pass. This allows us to remove the corresponding code in the main visitor and `commonBlockInfo_.curr`. The change in order of processing causes some different error messages to be emitted. Some cleanup is included with this change: - In `ExpressionAnalyzer`, if an unresolved name is encountered but no error has been reported, emit an internal error. - Change `ImplicitRulesVisitor` to hide the `ImplicitRules` object that implements it. Change the interface to pass in names rather than having to get the first character of the name. - Change `DeclareObjectEntity` to have the `attrs` argument default to an empty set; that is the typical case. - In `Pre(parser::SpecificationPart)` use "structured bindings" to give names to the pieces that make up a specification-part. - Enhance `parser::Unwrap` to unwrap `Statement` and `UnlabeledStatement` and make use of that in PreSpecificationConstruct. Differential Revision: https://reviews.llvm.org/D86322
2020-08-25 03:53:44 +08:00
!ERROR: 'x' may not be a procedure as it is in a COMMON block
procedure(real) :: x
common x
common y
[flang] Fix bug accessing implicit variable in specification expression A specification expression can reference an implicitly declared variable in the host procedure. Because we have to process specification parts before execution parts, this may be the first time we encounter the variable. We were assuming the variable was implicitly declared in the scope where it was encountered, leading to an error because local variables may not be referenced in specification expressions. The fix is to tentatively create the implicit variable in the host procedure because that is the only way the specification expression can be valid. We mark it with the flag `ImplicitOrError` to indicate that either it must be implicitly defined in the host (by being mentioned in the execution part) or else its use turned out to be an error. We need to apply the implicit type rules of the host, which requires some changes to implicit typing. Variables in common blocks are allowed to appear in specification expressions (because they are not locals) but the common block definition may not appear until after their use. To handle this we create common block symbols and object entities for each common block object during the `PreSpecificationConstruct` pass. This allows us to remove the corresponding code in the main visitor and `commonBlockInfo_.curr`. The change in order of processing causes some different error messages to be emitted. Some cleanup is included with this change: - In `ExpressionAnalyzer`, if an unresolved name is encountered but no error has been reported, emit an internal error. - Change `ImplicitRulesVisitor` to hide the `ImplicitRules` object that implements it. Change the interface to pass in names rather than having to get the first character of the name. - Change `DeclareObjectEntity` to have the `attrs` argument default to an empty set; that is the typical case. - In `Pre(parser::SpecificationPart)` use "structured bindings" to give names to the pieces that make up a specification-part. - Enhance `parser::Unwrap` to unwrap `Statement` and `UnlabeledStatement` and make use of that in PreSpecificationConstruct. Differential Revision: https://reviews.llvm.org/D86322
2020-08-25 03:53:44 +08:00
!ERROR: 'y' may not be a procedure as it is in a COMMON block
procedure(real) :: y
end
subroutine s5
integer x(2)
!ERROR: The dimensions of 'x' have already been declared
common x(4), y(4)
!ERROR: The dimensions of 'y' have already been declared
real y(2)
end
function f6(x) result(r)
!ERROR: Dummy argument 'x' may not appear in a COMMON block
!ERROR: ALLOCATABLE object 'y' may not appear in a COMMON block
common x,y,z
allocatable y
!ERROR: Function result 'r' may not appear in a COMMON block
common r
end
module m7
!ERROR: Variable 'w' with BIND attribute may not appear in a COMMON block
!ERROR: Variable 'z' with BIND attribute may not appear in a COMMON block
common w,z
integer, bind(c) :: z
integer, bind(c,name="w") :: w
end
module m8
type t
end type
class(*), pointer :: x
!ERROR: Unlimited polymorphic pointer 'x' may not appear in a COMMON block
!ERROR: Unlimited polymorphic pointer 'y' may not appear in a COMMON block
common x, y
class(*), pointer :: y
end
module m9
integer x
end
subroutine s9
use m9
!ERROR: 'x' is use-associated from module 'm9' and cannot be re-declared
common x
end
module m10
type t
end type
type(t) :: x
!ERROR: Derived type 'x' in COMMON block must have the BIND or SEQUENCE attribute
common x
end
module m11
type t1
sequence
integer, allocatable :: a
end type
type t2
sequence
type(t1) :: b
integer:: c
end type
type(t2) :: x2
!ERROR: Derived type variable 'x2' may not appear in a COMMON block due to ALLOCATABLE component
common x2
end
module m12
type t1
sequence
integer :: a = 123
end type
type t2
sequence
type(t1) :: b
integer:: c
end type
type(t2) :: x2
!ERROR: Derived type variable 'x2' may not appear in a COMMON block due to component with default initialization
common x2
end
subroutine s13
block
!ERROR: COMMON statement is not allowed in a BLOCK construct
common x
end block
end
subroutine s14
!ERROR: 'c' appears as a COMMON block in a BIND statement but not in a COMMON statement
bind(c) :: /c/
end