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