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

There are some very odd (even for Fortran) rules in F'2023 subclause 19.4 (paras 6 & 8) pertaining to the index variables of FORALL and DO CONCURRENT constructs/statements, and they are not currently implemented correctly. Although these index variables are construct entities, they have restrictions in the standard that would essentially allow them to also be variables in their enclosing scopes. If their names are present in the enclosing scope, and the construct does not have an explicit type specification for its indices, then the names in the enclosing scope must either be scalar variables or COMMON blocks, and their type must be integer. Reimplement these restrictions largely with portability warnings rather than hard errors. Retain the semantic interpretation that the type of an untyped index variable be taken from the type of a variable of the same name in the enclosing scope, if it exists, although that bit of the standard could be interpreted otherwise. Fixes https://github.com/llvm/llvm-project/issues/76978.
53 lines
1.5 KiB
Fortran
53 lines
1.5 KiB
Fortran
! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
|
|
! Tests for the index-name of a FORALL statement
|
|
|
|
module m1
|
|
integer modVar
|
|
end module m1
|
|
|
|
program indexName
|
|
common /iCommonName/ x
|
|
type :: typeName
|
|
end type
|
|
iGlobalVar = 216
|
|
|
|
contains
|
|
subroutine hostAssoc()
|
|
integer, dimension(4) :: table
|
|
|
|
! iGlobalVar is host associated with the global variable
|
|
iGlobalVar = 1
|
|
FORALL (iGlobalVar=1:4) table(iGlobalVar) = 343
|
|
end subroutine hostAssoc
|
|
|
|
subroutine useAssoc()
|
|
use m1
|
|
integer, dimension(4) :: tab
|
|
! modVar is use associated with the module variable
|
|
FORALL (modVar=1:4) tab(modVar) = 343
|
|
end subroutine useAssoc
|
|
|
|
subroutine constructAssoc()
|
|
integer, dimension(4) :: table
|
|
integer :: localVar
|
|
associate (assocVar => localVar)
|
|
!PORTABILITY: Index variable 'assocvar' should be a scalar object or common block if it is present in the enclosing scope
|
|
FORALL (assocVar=1:4) table(assocVar) = 343
|
|
end associate
|
|
end subroutine constructAssoc
|
|
|
|
subroutine commonSub()
|
|
integer, dimension(4) :: tab
|
|
! This reference is OK
|
|
FORALL (iCommonName=1:4) tab(iCommonName) = 343
|
|
end subroutine commonSub
|
|
|
|
subroutine mismatch()
|
|
integer, dimension(4) :: table
|
|
!PORTABILITY: Index variable 'typename' should be a scalar object or common block if it is present in the enclosing scope
|
|
!ERROR: Must have INTEGER type, but is REAL(4)
|
|
!ERROR: Must have INTEGER type, but is REAL(4)
|
|
FORALL (typeName=1:4) table(typeName) = 343
|
|
end subroutine mismatch
|
|
end program indexName
|