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