llvm/flang/test/Semantics/resolve77.f90
Tim Keith b297563a75 [flang] Fix erroneous application of SAVE statement
A SAVE statement with no entity list applies the SAVE attribute only to
the entities that it is allowed on. We were applying it to automatic
data objects and reporting an error that they can't have SAVE.

The fix is to change `DeclarationVisitor::CheckSaveAttr` to check for
automatic objects. That controls both checking and setting the
attribute. This allows us to remove the check from `CheckSpecExpr`
(along with `symbolBeingChecked_`). Also, it was only called on constant
objects so the non-const overload can be eliminated.

The check in `CheckSpecExpr` is replaced by an explicit check for
automatic objects in modules. This caught an error in modfile03.f90 so
that part of the test was eliminated.

Differential Revision: https://reviews.llvm.org/D83899
2020-07-15 13:02:33 -07:00

53 lines
1.4 KiB
Fortran

! RUN: %S/test_errors.sh %s %t %f18
! Tests valid and invalid usage of forward references to procedures
! in specification expressions.
module m
interface ifn2
module procedure if2
end interface
interface ifn3
module procedure if3
end interface
!ERROR: Automatic data object 'a' may not appear in the specification part of a module
real :: a(if1(1))
!ERROR: No specific procedure of generic 'ifn2' matches the actual arguments
real :: b(ifn2(1))
contains
subroutine t1(n)
integer :: iarr(if1(n))
end subroutine
pure integer function if1(n)
integer, intent(in) :: n
if1 = n
end function
subroutine t2(n)
integer :: iarr(ifn3(n)) ! should resolve to if3
end subroutine
pure integer function if2(n)
integer, intent(in) :: n
if2 = n
end function
pure integer function if3(n)
integer, intent(in) :: n
if3 = n
end function
end module
subroutine nester
!ERROR: The internal function 'if1' may not be referenced in a specification expression
real :: a(if1(1))
contains
subroutine t1(n)
!ERROR: The internal function 'if2' may not be referenced in a specification expression
integer :: iarr(if2(n))
end subroutine
pure integer function if1(n)
integer, intent(in) :: n
if1 = n
end function
pure integer function if2(n)
integer, intent(in) :: n
if2 = n
end function
end subroutine