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

It is not standard conforming under IMPLICIT NONE(TYPE) for a name to appear in a DATA statement prior to its explicit type declaration, but it is benign, supported in other compilers, and attested in real applications. Support it with an optional portability warning. Fixes GitHub LLVM bug https://github.com/llvm/llvm-project/issues/63783.
47 lines
988 B
Fortran
47 lines
988 B
Fortran
! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
|
|
subroutine s1
|
|
integer x
|
|
block
|
|
import, none
|
|
!ERROR: 'x' from host scoping unit is not accessible due to IMPORT
|
|
x = 1
|
|
end block
|
|
end
|
|
|
|
subroutine s2
|
|
block
|
|
import, none
|
|
!ERROR: 'y' from host scoping unit is not accessible due to IMPORT
|
|
y = 1
|
|
end block
|
|
end
|
|
|
|
subroutine s3
|
|
implicit none
|
|
integer :: i, j
|
|
block
|
|
import, none
|
|
!ERROR: No explicit type declared for 'i'
|
|
real :: a(16) = [(i, i=1, 16)]
|
|
real :: b(16)
|
|
!ERROR: No explicit type declared for 'j'
|
|
data(b(j), j=1, 16) / 16 * 0.0 /
|
|
end block
|
|
end
|
|
|
|
subroutine s4
|
|
real :: j
|
|
!ERROR: Must have INTEGER type, but is REAL(4)
|
|
real :: a(16) = [(x, x=1, 16)]
|
|
real :: b(16)
|
|
!ERROR: Must have INTEGER type, but is REAL(4)
|
|
data(b(j), j=1, 16) / 16 * 0.0 /
|
|
end
|
|
|
|
subroutine s5
|
|
implicit none
|
|
data x/1./
|
|
!PORTABILITY: 'x' appeared in a DATA statement before its type was declared under IMPLICIT NONE(TYPE)
|
|
real x
|
|
end
|