llvm-project/flang/test/Semantics/data06.f90
Emil Kieri 93dca9fbee [flang][test] Fix semantics tests with respect to warnings
Make tests expect the (correctly) emitted warnings using the WARNING
directive. This directive is non-functional now, but will be recognised
by test_errors.py when D125804 is landed. This patch is a preparation
for D125804.

For most tests, we add missing WARNING directives for emitted warnings,
but there are exceptions:

 - for int-literals.f90 and resolve31.f90 we pass -pedantic to the
   frontend driver, so that the expected warnings are actually emitted.

 - for block-data01.f90 and resolve42.f90 we change the tests so that
   warnings, which appear unintentional, are not emitted. While testing
   the warning in question (padding added for alignment in common block)
   would be desired, that is beyond the scope of this patch. This
   warning is target-dependent.

Reviewed By: PeteSteinfeld

Differential Revision: https://reviews.llvm.org/D131987
2022-08-18 19:16:20 +02:00

59 lines
2.0 KiB
Fortran

! RUN: %python %S/test_errors.py %s %flang_fc1
! DATA statement errors
subroutine s1
type :: t1
integer :: j = 666
end type t1
type(t1) :: t1x
!ERROR: Default-initialized 't1x' must not be initialized in a DATA statement
data t1x%j / 777 /
type :: t2
integer, allocatable :: j
integer :: k
end type t2
type(t2) :: t2x
data t2x%k / 777 / ! allocatable component is ok
integer :: ja = 888
!ERROR: Default-initialized 'ja' must not be initialized in a DATA statement
data ja / 999 /
integer :: a1(10)
!ERROR: DATA statement set has more values than objects
data a1(1:9:2) / 6 * 1 /
integer :: a2(10)
!ERROR: DATA statement set has no value for 'a2(2_8)'
data (a2(k),k=10,1,-2) / 4 * 1 /
integer :: a3(2)
!ERROR: DATA statement implied DO loop has a step value of zero
data (a3(j),j=1,2,0)/2*333/
integer :: a4(3)
!ERROR: DATA statement designator 'a4(5_8)' is out of range
data (a4(j),j=1,5,2) /3*222/
integer :: a5(3)
!ERROR: DATA statement designator 'a5(-2_8)' is out of range
data a5(-2) / 1 /
interface
real function rfunc(x)
real, intent(in) :: x
end function
end interface
real, pointer :: rp
!ERROR: Procedure 'rfunc' may not be used to initialize 'rp', which is not a procedure pointer
data rp/rfunc/
procedure(rfunc), pointer :: rpp
real, target :: rt
!WARNING: Procedure pointer 'rpp' in a DATA statement is not standard
!ERROR: Data object 'rt' may not be used to initialize 'rpp', which is a procedure pointer
data rpp/rt/
!ERROR: Initializer for 'rt' must not be a pointer
data rt/null()/
!ERROR: Initializer for 'rt' must not be a procedure
data rt/rfunc/
integer :: jx, jy
!WARNING: DATA statement value initializes 'jx' of type 'INTEGER(4)' with CHARACTER
data jx/'abc'/
!ERROR: DATA statement value could not be converted to the type 'INTEGER(4)' of the object 'jx'
data jx/t1()/
!ERROR: DATA statement value 'jy' for 'jx' is not a constant
data jx/jy/
end subroutine