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

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

123 lines
3.0 KiB
Fortran
Raw Normal View History

! RUN: %S/test_errors.sh %s %t %f18
[flang] Changes for constraint C1128. Specifically, these changes enforce the last sentence of the constraint, which prohibits names that cannot appear in a variable definition context from appearing in a locality-spec. Here are the details. - Created the function "IsModifiableName" to return "true" when its parameter is the name of a variable that can appear in a variable definition context. - Created the function "GetAssociationRoot" to follow construct associations to potentially get to an underlying variable. This function is similar to the existing "GetUltimate" function that follows use associations and host associations. One difference is that "GetAssociationRoot" requires access to the types "MaybeExpr" and "SomeExpr", which makes is inappropriate to put into symbol.cc, which is where "GetUltimate" lives. Perhaps we should move "GetUltimate" to tools.[h,cc]. - Generalized the functions "IsPureFunction" to "IsPureProcedure" since either a pure function or subroutine can provide a context for variables that cannot be modified. Changed "FindPureFunctionContaining" to "FindPureProcedueContaining" to go along with this. - Added the function "IsExternalInPureContext" to detect the case where a nominally pure procedure potentially modifies a variable. - Created the function "IsOrContainsEventOrLockComponent" to detect variables that either are of EVENT_TYPE or LOCK_TYPE or contain components of these types. Such variables cannot appear in variable definition contexts. - Added the test resolve56.f90 to test most of these conditions. Note that I only tested the new code from the perspective of locality-specs. Original-commit: flang-compiler/f18@c9d2507b74da881dda2eb11805a0394a415db2e4 Reviewed-on: https://github.com/flang-compiler/f18/pull/596 Tree-same-pre-rewrite: false
2019-07-20 06:17:14 +08:00
! Tests for the last sentence of C1128:
!A variable-name that is not permitted to appear in a variable definition
!context shall not appear in a LOCAL or LOCAL_INIT locality-spec.
subroutine s1(arg)
real, intent(in) :: arg
! This is not OK because "arg" is "intent(in)"
!ERROR: INTENT IN argument 'arg' not allowed in a locality-spec
do concurrent (i=1:5) local(arg)
end do
end subroutine s1
subroutine s2(arg)
real, value, intent(in) :: arg
! This is not OK even though "arg" has the "value" attribute. C1128
! explicitly excludes dummy arguments of INTENT(IN)
!ERROR: INTENT IN argument 'arg' not allowed in a locality-spec
do concurrent (i=1:5) local(arg)
end do
end subroutine s2
module m3
real, protected :: prot
real var
contains
subroutine sub()
! C857 This is OK because of the "protected" attribute only applies to
! accesses outside the module
do concurrent (i=1:5) local(prot)
end do
end subroutine sub
endmodule m3
subroutine s4()
use m3
! C857 This is not OK because of the "protected" attribute
!ERROR: 'prot' may not appear in a locality-spec because it is not definable
[flang] Changes for constraint C1128. Specifically, these changes enforce the last sentence of the constraint, which prohibits names that cannot appear in a variable definition context from appearing in a locality-spec. Here are the details. - Created the function "IsModifiableName" to return "true" when its parameter is the name of a variable that can appear in a variable definition context. - Created the function "GetAssociationRoot" to follow construct associations to potentially get to an underlying variable. This function is similar to the existing "GetUltimate" function that follows use associations and host associations. One difference is that "GetAssociationRoot" requires access to the types "MaybeExpr" and "SomeExpr", which makes is inappropriate to put into symbol.cc, which is where "GetUltimate" lives. Perhaps we should move "GetUltimate" to tools.[h,cc]. - Generalized the functions "IsPureFunction" to "IsPureProcedure" since either a pure function or subroutine can provide a context for variables that cannot be modified. Changed "FindPureFunctionContaining" to "FindPureProcedueContaining" to go along with this. - Added the function "IsExternalInPureContext" to detect the case where a nominally pure procedure potentially modifies a variable. - Created the function "IsOrContainsEventOrLockComponent" to detect variables that either are of EVENT_TYPE or LOCK_TYPE or contain components of these types. Such variables cannot appear in variable definition contexts. - Added the test resolve56.f90 to test most of these conditions. Note that I only tested the new code from the perspective of locality-specs. Original-commit: flang-compiler/f18@c9d2507b74da881dda2eb11805a0394a415db2e4 Reviewed-on: https://github.com/flang-compiler/f18/pull/596 Tree-same-pre-rewrite: false
2019-07-20 06:17:14 +08:00
do concurrent (i=1:5) local(prot)
end do
! C857 This is OK because of there's no "protected" attribute
do concurrent (i=1:5) local(var)
end do
end subroutine s4
subroutine s5()
real :: a, b, c, d, e
associate (a => b + c, d => e)
b = 3.0
! C1101 This is OK because 'd' is associated with a variable
do concurrent (i=1:5) local(d)
end do
! C1101 This is not OK because 'a' is not associated with a variable
!ERROR: 'a' may not appear in a locality-spec because it is not definable
[flang] Changes for constraint C1128. Specifically, these changes enforce the last sentence of the constraint, which prohibits names that cannot appear in a variable definition context from appearing in a locality-spec. Here are the details. - Created the function "IsModifiableName" to return "true" when its parameter is the name of a variable that can appear in a variable definition context. - Created the function "GetAssociationRoot" to follow construct associations to potentially get to an underlying variable. This function is similar to the existing "GetUltimate" function that follows use associations and host associations. One difference is that "GetAssociationRoot" requires access to the types "MaybeExpr" and "SomeExpr", which makes is inappropriate to put into symbol.cc, which is where "GetUltimate" lives. Perhaps we should move "GetUltimate" to tools.[h,cc]. - Generalized the functions "IsPureFunction" to "IsPureProcedure" since either a pure function or subroutine can provide a context for variables that cannot be modified. Changed "FindPureFunctionContaining" to "FindPureProcedueContaining" to go along with this. - Added the function "IsExternalInPureContext" to detect the case where a nominally pure procedure potentially modifies a variable. - Created the function "IsOrContainsEventOrLockComponent" to detect variables that either are of EVENT_TYPE or LOCK_TYPE or contain components of these types. Such variables cannot appear in variable definition contexts. - Added the test resolve56.f90 to test most of these conditions. Note that I only tested the new code from the perspective of locality-specs. Original-commit: flang-compiler/f18@c9d2507b74da881dda2eb11805a0394a415db2e4 Reviewed-on: https://github.com/flang-compiler/f18/pull/596 Tree-same-pre-rewrite: false
2019-07-20 06:17:14 +08:00
do concurrent (i=1:5) local(a)
end do
end associate
end subroutine s5
subroutine s6()
type point
real :: x, y
end type point
type, extends(point) :: color_point
integer :: color
end type color_point
type(point), target :: c, d
class(point), pointer :: p_or_c
p_or_c => c
select type ( a => p_or_c )
type is ( point )
! C1158 This is OK because 'a' is associated with a variable
do concurrent (i=1:5) local(a)
end do
end select
select type ( a => func() )
type is ( point )
! C1158 This is not OK because 'a' is not associated with a variable
!ERROR: 'a' may not appear in a locality-spec because it is not definable
[flang] Changes for constraint C1128. Specifically, these changes enforce the last sentence of the constraint, which prohibits names that cannot appear in a variable definition context from appearing in a locality-spec. Here are the details. - Created the function "IsModifiableName" to return "true" when its parameter is the name of a variable that can appear in a variable definition context. - Created the function "GetAssociationRoot" to follow construct associations to potentially get to an underlying variable. This function is similar to the existing "GetUltimate" function that follows use associations and host associations. One difference is that "GetAssociationRoot" requires access to the types "MaybeExpr" and "SomeExpr", which makes is inappropriate to put into symbol.cc, which is where "GetUltimate" lives. Perhaps we should move "GetUltimate" to tools.[h,cc]. - Generalized the functions "IsPureFunction" to "IsPureProcedure" since either a pure function or subroutine can provide a context for variables that cannot be modified. Changed "FindPureFunctionContaining" to "FindPureProcedueContaining" to go along with this. - Added the function "IsExternalInPureContext" to detect the case where a nominally pure procedure potentially modifies a variable. - Created the function "IsOrContainsEventOrLockComponent" to detect variables that either are of EVENT_TYPE or LOCK_TYPE or contain components of these types. Such variables cannot appear in variable definition contexts. - Added the test resolve56.f90 to test most of these conditions. Note that I only tested the new code from the perspective of locality-specs. Original-commit: flang-compiler/f18@c9d2507b74da881dda2eb11805a0394a415db2e4 Reviewed-on: https://github.com/flang-compiler/f18/pull/596 Tree-same-pre-rewrite: false
2019-07-20 06:17:14 +08:00
do concurrent (i=1:5) local(a)
end do
end select
contains
function func()
class(point), pointer :: func
func => c
end function func
end subroutine s6
module m4
real, protected :: prot
real var
endmodule m4
pure subroutine s7()
use m4
! C1594 This is not OK because we're in a PURE subroutine
!ERROR: 'var' may not appear in a locality-spec because it is not definable
[flang] Changes for constraint C1128. Specifically, these changes enforce the last sentence of the constraint, which prohibits names that cannot appear in a variable definition context from appearing in a locality-spec. Here are the details. - Created the function "IsModifiableName" to return "true" when its parameter is the name of a variable that can appear in a variable definition context. - Created the function "GetAssociationRoot" to follow construct associations to potentially get to an underlying variable. This function is similar to the existing "GetUltimate" function that follows use associations and host associations. One difference is that "GetAssociationRoot" requires access to the types "MaybeExpr" and "SomeExpr", which makes is inappropriate to put into symbol.cc, which is where "GetUltimate" lives. Perhaps we should move "GetUltimate" to tools.[h,cc]. - Generalized the functions "IsPureFunction" to "IsPureProcedure" since either a pure function or subroutine can provide a context for variables that cannot be modified. Changed "FindPureFunctionContaining" to "FindPureProcedueContaining" to go along with this. - Added the function "IsExternalInPureContext" to detect the case where a nominally pure procedure potentially modifies a variable. - Created the function "IsOrContainsEventOrLockComponent" to detect variables that either are of EVENT_TYPE or LOCK_TYPE or contain components of these types. Such variables cannot appear in variable definition contexts. - Added the test resolve56.f90 to test most of these conditions. Note that I only tested the new code from the perspective of locality-specs. Original-commit: flang-compiler/f18@c9d2507b74da881dda2eb11805a0394a415db2e4 Reviewed-on: https://github.com/flang-compiler/f18/pull/596 Tree-same-pre-rewrite: false
2019-07-20 06:17:14 +08:00
do concurrent (i=1:5) local(var)
end do
end subroutine s7
subroutine s8()
integer, parameter :: iconst = 343
!ERROR: 'iconst' may not appear in a locality-spec because it is not definable
[flang] Changes for constraint C1128. Specifically, these changes enforce the last sentence of the constraint, which prohibits names that cannot appear in a variable definition context from appearing in a locality-spec. Here are the details. - Created the function "IsModifiableName" to return "true" when its parameter is the name of a variable that can appear in a variable definition context. - Created the function "GetAssociationRoot" to follow construct associations to potentially get to an underlying variable. This function is similar to the existing "GetUltimate" function that follows use associations and host associations. One difference is that "GetAssociationRoot" requires access to the types "MaybeExpr" and "SomeExpr", which makes is inappropriate to put into symbol.cc, which is where "GetUltimate" lives. Perhaps we should move "GetUltimate" to tools.[h,cc]. - Generalized the functions "IsPureFunction" to "IsPureProcedure" since either a pure function or subroutine can provide a context for variables that cannot be modified. Changed "FindPureFunctionContaining" to "FindPureProcedueContaining" to go along with this. - Added the function "IsExternalInPureContext" to detect the case where a nominally pure procedure potentially modifies a variable. - Created the function "IsOrContainsEventOrLockComponent" to detect variables that either are of EVENT_TYPE or LOCK_TYPE or contain components of these types. Such variables cannot appear in variable definition contexts. - Added the test resolve56.f90 to test most of these conditions. Note that I only tested the new code from the perspective of locality-specs. Original-commit: flang-compiler/f18@c9d2507b74da881dda2eb11805a0394a415db2e4 Reviewed-on: https://github.com/flang-compiler/f18/pull/596 Tree-same-pre-rewrite: false
2019-07-20 06:17:14 +08:00
do concurrent (i=1:5) local(iconst)
end do
end subroutine s8