1! RUN: %S/test_errors.sh %s %t %flang_fc1
2! REQUIRES: shell
3! Check for semantic errors in ALLOCATE statements
4
5!TODO: mixing expr and source-expr?
6!TODO: using subcomponent in source expressions
7
8subroutine C939_C942a_C945b(xsrc1a, xsrc1c, xsrc0, xsrc2a, xsrc2c, pos)
9! C939: If an allocate-object is an array, either allocate-shape-spec-list shall
10! appear in its allocation, or source-expr shall appear in the ALLOCATE
11! statement and have the same rank as the allocate-object.
12  type A
13    real, pointer :: x(:)
14  end type
15  real, allocatable :: x0
16  real, allocatable :: x1(:)
17  real, pointer :: x2(:, :, :)
18  type(A) a1
19  type(A), allocatable :: a2(:, :)
20
21  real xsrc0
22  real xsrc1a(*)
23  real xsrc1b(2:7)
24  real, pointer :: xsrc1c(:)
25  real xsrc2a(4:8, 12, *)
26  real xsrc2b(2:7, 5, 9)
27  real, pointer :: xsrc2c(:, :, :)
28  integer pos
29
30  allocate(x1(5))
31  allocate(x1(2:7))
32  allocate(x1, SOURCE=xsrc1a(2:7))
33  allocate(x1, MOLD=xsrc1b)
34  allocate(x1, SOURCE=xsrc1c)
35
36  allocate(x2(2,3,4))
37  allocate(x2(2:7,3:8,4:9))
38  allocate(x2, SOURCE=xsrc2a(4:8, 1:12, 2:5))
39  allocate(x2, MOLD=cos(xsrc2b))
40  allocate(x2, SOURCE=xsrc2c)
41
42  allocate(x1(5), x2(2,3,4), a1%x(5), a2(1,2)%x(4))
43  allocate(x1, a1%x, a2(1,2)%x, SOURCE=xsrc1a(2:7))
44  allocate(x1, a1%x, a2(1,2)%x, MOLD=xsrc1b)
45  allocate(x1, a1%x, a2(1,2)%x, SOURCE=xsrc1c)
46
47  allocate(x0, x1(5), x2(2,3,4), a1%x(5), SOURCE=xsrc0)
48
49  ! There are NO requirements that mold expression rank match the
50  ! allocated-objects when allocate-shape-spec-lists are given.
51  ! If it is not needed, the shape of MOLD should be simply ignored.
52  allocate(x0, x1(5), x2(2,3,4), a1%x(5), MOLD=xsrc0)
53  allocate(x0, x1(5), x2(2,3,4), a1%x(5), MOLD=xsrc1b)
54  allocate(x0, x1(5), x2(2,3,4), a1%x(5), MOLD=xsrc2b)
55
56  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
57  allocate(x1)
58  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
59  allocate(x1, SOURCE=xsrc0)
60  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
61  allocate(x1, MOLD=xsrc2c)
62
63  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
64  allocate(x2, SOURCE=xsrc1a(2:7))
65  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
66  allocate(x2, MOLD=xsrc1b)
67  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
68  allocate(x2, SOURCE=xsrc1c)
69
70  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
71  allocate(a1%x)
72  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
73  allocate(a2(5,3)%x)
74  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
75  allocate(x1(5), x2(2,3,4), a1%x, a2(1,2)%x(4))
76  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
77  allocate(x2, a2(1,2)%x, SOURCE=xsrc2a(4:8, 1:12, 2:5))
78  !ERROR: Arrays in ALLOCATE must have a shape specification or an expression of the same rank must appear in SOURCE or MOLD
79  allocate(a1%x, MOLD=xsrc0)
80
81 !C942a: The number of allocate-shape-specs in an allocate-shape-spec-list shall
82 !be the same as the rank of the allocate-object. [...] (co-array stuffs).
83
84 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
85 allocate(x1(5, 5))
86 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
87 allocate(x1(2:3, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 1, 2, 1, 2))
88 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
89 allocate(x2(pos))
90 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
91 allocate(x2(2, 3, pos+1, 5))
92 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
93 allocate(x1(5), x2(2,4), a1%x(5), a2(1,2)%x(4))
94
95 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
96 allocate(x1(2), a1%x(2,5), a2(1,2)%x(2))
97
98 ! Test the check is not influenced by SOURCE
99 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
100 allocate(a1%x(5, 4, 3), SOURCE=xsrc2a(1:5, 1:4, 1:3))
101 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
102 allocate(x2(5), MOLD=xsrc1a(1:5))
103 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
104 allocate(a1%x(5, 4, 3), MOLD=xsrc1b)
105 !ERROR: The number of shape specifications, when they appear, must match the rank of allocatable object
106 allocate(x2(5), SOURCE=xsrc2b)
107
108 ! C945b: If SOURCE= appears, source-expr shall be a scalar or have the same
109 ! rank as each allocate-object.
110 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
111 allocate(x0, SOURCE=xsrc1b)
112 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
113 allocate(x2(2, 5, 7), SOURCE=xsrc1a(2:7))
114 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
115 allocate(x2(2, 5, 7), SOURCE=xsrc1c)
116
117 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
118 allocate(x1(5), SOURCE=xsrc2a(4:8, 1:12, 2:5))
119 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
120 allocate(x1(3), SOURCE=cos(xsrc2b))
121 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
122 allocate(x1(100), SOURCE=xsrc2c)
123
124 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
125 allocate(a1%x(10), x2(20, 30, 40), a2(1,2)%x(50), SOURCE=xsrc1c)
126 !ERROR: If SOURCE appears, the related expression must be scalar or have the same rank as each allocatable object in ALLOCATE
127 allocate(a1%x(25), SOURCE=xsrc2b)
128
129end subroutine
130
131subroutine C940(a1, pos)
132! If allocate-object is scalar, allocate-shape-spec-list shall not appear.
133  type A
134    integer(kind=8), allocatable :: i
135  end type
136
137  type B(k, l1, l2, l3)
138    integer, kind :: k
139    integer, len :: l1, l2, l3
140    real(kind=k) x(-1:l1, 0:l2, 1:l3)
141  end type
142
143  integer pos
144  class(A), allocatable :: a1(:)
145  real, pointer :: x
146  type(B(8,4,5,6)), allocatable :: b1
147
148  ! Nominal
149  allocate(x)
150  allocate(a1(pos)%i)
151  allocate(b1)
152
153  !ERROR: Shape specifications must not appear when allocatable object is scalar
154  allocate(x(pos))
155  !ERROR: Shape specifications must not appear when allocatable object is scalar
156  allocate(a1(pos)%i(5:2))
157  !ERROR: Shape specifications must not appear when allocatable object is scalar
158  allocate(b1(1))
159end subroutine
160