xref: /llvm-project/flang/test/Semantics/init01.f90 (revision 8f01ecaeb8e537511718c4df123fb92633d9f73d)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2! Initializer error tests
3
4subroutine objectpointers(j)
5  integer, intent(in) :: j
6  real, allocatable, target, save :: x1
7  real, codimension[*], target, save :: x2
8  real, save :: x3
9  real, target :: x4
10  real, target, save :: x5(10)
11  real, pointer :: x6
12  type t1
13    real, allocatable :: c1
14    real, allocatable, codimension[:] :: c2
15    real :: c3
16    real :: c4(10)
17    real, pointer :: c5
18  end type
19  type(t1), target, save :: o1
20  type(t1), save :: o2
21  type(t1), target :: o3
22!ERROR: An initial data target may not be a reference to an ALLOCATABLE 'x1'
23  real, pointer :: p1 => x1
24!ERROR: An initial data target may not be a reference to a coarray 'x2'
25  real, pointer :: p2 => x2
26!ERROR: An initial data target may not be a reference to an object 'x3' that lacks the TARGET attribute
27  real, pointer :: p3 => x3
28!ERROR: An initial data target may not be a reference to an object 'x4' that lacks the SAVE attribute
29  real, pointer :: p4 => x4
30!ERROR: An initial data target must be a designator with constant subscripts
31  real, pointer :: p5 => x5(j)
32!ERROR: Pointer has rank 0 but target has rank 1
33  real, pointer :: p6 => x5
34!ERROR: An initial data target may not be a reference to a POINTER 'x6'
35  real, pointer :: p7 => x6
36!ERROR: An initial data target may not be a reference to an ALLOCATABLE 'c1'
37  real, pointer :: p1o => o1%c1
38!ERROR: An initial data target may not be a reference to a coarray 'c2'
39  real, pointer :: p2o => o1%c2
40!ERROR: An initial data target may not be a reference to an object 'o2' that lacks the TARGET attribute
41  real, pointer :: p3o => o2%c3
42!ERROR: An initial data target may not be a reference to an object 'o3' that lacks the SAVE attribute
43  real, pointer :: p4o => o3%c3
44!ERROR: An initial data target must be a designator with constant subscripts
45  real, pointer :: p5o => o1%c4(j)
46!ERROR: Pointer has rank 0 but target has rank 1
47  real, pointer :: p6o => o1%c4
48!ERROR: An initial data target may not be a reference to a POINTER 'c5'
49  real, pointer :: p7o => o1%c5
50  type t2
51    !ERROR: An initial data target may not be a reference to an ALLOCATABLE 'x1'
52    real, pointer :: p1 => x1
53    !ERROR: An initial data target may not be a reference to a coarray 'x2'
54    real, pointer :: p2 => x2
55    !ERROR: An initial data target may not be a reference to an object 'x3' that lacks the TARGET attribute
56    real, pointer :: p3 => x3
57    !ERROR: An initial data target may not be a reference to an object 'x4' that lacks the SAVE attribute
58    real, pointer :: p4 => x4
59    !ERROR: An initial data target must be a designator with constant subscripts
60    real, pointer :: p5 => x5(j)
61    !ERROR: Pointer has rank 0 but target has rank 1
62    real, pointer :: p6 => x5
63    !ERROR: An initial data target may not be a reference to a POINTER 'x6'
64    real, pointer :: p7 => x6
65    !ERROR: An initial data target may not be a reference to an ALLOCATABLE 'c1'
66    real, pointer :: p1o => o1%c1
67    !ERROR: An initial data target may not be a reference to a coarray 'c2'
68    real, pointer :: p2o => o1%c2
69    !ERROR: An initial data target may not be a reference to an object 'o2' that lacks the TARGET attribute
70    real, pointer :: p3o => o2%c3
71    !ERROR: An initial data target may not be a reference to an object 'o3' that lacks the SAVE attribute
72    real, pointer :: p4o => o3%c3
73    !ERROR: An initial data target must be a designator with constant subscripts
74    real, pointer :: p5o => o1%c4(j)
75    !ERROR: Pointer has rank 0 but target has rank 1
76    real, pointer :: p6o => o1%c4
77    !ERROR: An initial data target may not be a reference to a POINTER 'c5'
78    real, pointer :: p7o => o1%c5
79  end type
80
81!TODO: type incompatibility, non-deferred type parameter values, contiguity
82
83end subroutine
84
85subroutine dataobjects(j)
86  integer, intent(in) :: j
87  real, parameter :: x1(*) = [1., 2.]
88!ERROR: Implied-shape parameter 'x2' has rank 2 but its initializer has rank 1
89  real, parameter :: x2(*,*) = [1., 2.]
90!ERROR: Named constant 'x3' array must have constant shape
91  real, parameter :: x3(j) = [1., 2.]
92!ERROR: Shape of initialized object 'x4' must be constant
93  real :: x4(j) = [1., 2.]
94!ERROR: Rank of initialized object is 2, but initialization expression has rank 1
95  real :: x5(2,2) = [1., 2., 3., 4.]
96  real :: x6(2,2) = 5.
97!ERROR: Rank of initialized object is 0, but initialization expression has rank 1
98  real :: x7 = [1.]
99  real :: x8(2,2) = reshape([1., 2., 3., 4.], [2, 2])
100!ERROR: Dimension 1 of initialized object has extent 3, but initialization expression has extent 2
101  real :: x9(3) = [1., 2.]
102!ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
103  real :: x10(2,3) = reshape([real::(k,k=1,6)], [3, 2])
104end subroutine
105
106subroutine components(n)
107  integer, intent(in) :: n
108  real, target, save :: a1(3)
109  real, target :: a2
110  real, save :: a3
111  real, target, save :: a4
112  type :: t1
113!ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
114    real :: x1(2) = [1., 2., 3.]
115  end type
116  type :: t2(kind, len)
117    integer, kind :: kind
118    integer, len :: len
119!ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
120!ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
121    real :: x1(2) = [1., 2., 3.]
122!ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
123    real :: x2(kind) = [1., 2., 3.]
124!ERROR: Dimension 1 of initialized object has extent 2, but initialization expression has extent 3
125!ERROR: Shape of initialized object 'x3' must be constant
126    real :: x3(len) = [1., 2., 3.]
127    real, pointer :: p1(:) => a1
128!ERROR: An initial data target may not be a reference to an object 'a2' that lacks the SAVE attribute
129!ERROR: An initial data target may not be a reference to an object 'a2' that lacks the SAVE attribute
130    real, pointer :: p2 => a2
131!ERROR: An initial data target may not be a reference to an object 'a3' that lacks the TARGET attribute
132!ERROR: An initial data target may not be a reference to an object 'a3' that lacks the TARGET attribute
133    real, pointer :: p3 => a3
134!ERROR: Pointer has rank 0 but target has rank 1
135!ERROR: Pointer has rank 0 but target has rank 1
136    real, pointer :: p4 => a1
137!ERROR: Pointer has rank 1 but target has rank 0
138!ERROR: Pointer has rank 1 but target has rank 0
139    real, pointer :: p5(:) => a4
140  end type
141  type(t2(3,2)) :: o1
142  type(t2(2,n)) :: o2
143  type :: t3
144    real :: x
145  end type
146  type(t3), save, target :: o3
147  real, pointer :: p10 => o3%x
148  associate (a1 => o3, a2 => o3%x)
149    block
150      type(t3), pointer :: p11 => a1
151      real, pointer :: p12 => a2
152    end block
153  end associate
154end subroutine
155
156subroutine notObjects
157!ERROR: 'x1' is not an object that can be initialized
158  real, external :: x1 = 1.
159!ERROR: 'x2' is not a pointer but is initialized like one
160  real, external :: x2 => sin
161!ERROR: 'x3' is not a known intrinsic procedure
162!ERROR: 'x3' is not an object that can be initialized
163  real, intrinsic :: x3 = 1.
164!ERROR: 'x4' is not a known intrinsic procedure
165!ERROR: 'x4' is not a pointer but is initialized like one
166  real, intrinsic :: x4 => cos
167end subroutine
168
169subroutine edgeCases
170  integer :: j = 1, m = 2
171  !ERROR: Data statement object must be a variable
172  data k/3/
173  data n/4/
174  !ERROR: Named constant 'j' already has a value
175  parameter(j = 5)
176  !ERROR: Named constant 'k' already has a value
177  parameter(k = 6)
178  parameter(l = 7)
179  !ERROR: 'm' was initialized earlier as a scalar
180  dimension m(1)
181  !ERROR: 'l' was initialized earlier as a scalar
182  dimension l(1)
183  !ERROR: 'n' was initialized earlier as a scalar
184  dimension n(1)
185end
186