xref: /llvm-project/flang/test/Semantics/data06.f90 (revision 1c91d9bdea3b6c38e8fbce46ec8181a9c0aa26f8)
1! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
2! DATA statement errors
3subroutine s1
4  type :: t1
5    integer :: j = 666
6  end type t1
7  type(t1) :: t1x
8  !ERROR: Default-initialized 't1x' must not be initialized in a DATA statement
9  data t1x%j / 777 /
10  type :: t2
11    integer, allocatable :: j
12    integer :: k
13  end type t2
14  type(t2) :: t2x
15  data t2x%k / 777 / ! allocatable component is ok
16  integer :: ja = 888
17  !ERROR: Default-initialized 'ja' must not be initialized in a DATA statement
18  data ja / 999 /
19  integer :: a1(10)
20  !ERROR: DATA statement set has more values than objects
21  data a1(1:9:2) / 6 * 1 /
22  integer :: a2(10)
23  !ERROR: DATA statement set has no value for 'a2(2_8)'
24  data (a2(k),k=10,1,-2) / 4 * 1 /
25  integer :: a3(2)
26  !ERROR: DATA statement implied DO loop has a step value of zero
27  data (a3(j),j=1,2,0)/2*333/
28  integer :: a4(3)
29  !ERROR: DATA statement designator 'a4(5_8)' is out of range
30  data (a4(j),j=1,5,2) /3*222/
31  integer :: a5(3)
32  !ERROR: DATA statement designator 'a5(-2_8)' is out of range
33  data       a5(-2) / 1 /
34  interface
35    real function rfunc(x)
36      real, intent(in) :: x
37    end function
38  end interface
39  real, pointer :: rp
40  !ERROR: Procedure 'rfunc' may not be used to initialize 'rp', which is not a procedure pointer
41  data rp/rfunc/
42  procedure(rfunc), pointer :: rpp
43  real, target :: rt
44  !WARNING: Procedure pointer 'rpp' in a DATA statement is not standard
45  !ERROR: Data object 'rt' may not be used to initialize 'rpp', which is a procedure pointer
46  data rpp/rt/
47  !ERROR: Initializer for 'rt' must not be a pointer
48  data rt/null()/
49  !ERROR: Initializer for 'rt' must not be a procedure
50  data rt/rfunc/
51  integer :: jx, jy
52  !WARNING: DATA statement value initializes 'jx' of type 'INTEGER(4)' with CHARACTER
53  data jx/'abc'/
54  !ERROR: DATA statement value could not be converted to the type 'INTEGER(4)' of the object 'jx'
55  data jx/t1()/
56  !ERROR: DATA statement value 'jy' for 'jx' is not a constant
57  data jx/jy/
58end subroutine
59