[Flang][RISCV] Set vscale_range based off zvl*b (#77277)
[llvm-project.git] / flang / test / Semantics / select-rank.f90
blobfa8d2fc4d461dfc7b5b56038dfe783bf57aa84a4
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
3 !Tests for SELECT RANK Construct(R1148)
4 program select_rank
5 implicit none
6 integer, dimension(10:30, 10:20, -1:20) :: x
7 integer, parameter :: y(*) = [1,2,3,4]
8 integer, dimension(5) :: z
9 integer, allocatable :: a(:)
11 allocate(a(10:20))
13 call CALL_SHAPE(x)
14 call CALL_SHAPE(y)
15 call CALL_SHAPE(z)
16 call CALL_SHAPE(a)
18 contains
19 !No error expected
20 subroutine CALL_ME(x)
21 implicit none
22 integer :: x(..)
23 SELECT RANK(x)
24 RANK (0)
25 print *, "PRINT RANK 0"
26 RANK (1)
27 print *, "PRINT RANK 1"
28 END SELECT
29 end
31 subroutine CALL_ME9(x)
32 implicit none
33 integer :: x(..),j
34 boo: SELECT RANK(x)
35 RANK (1+0)
36 print *, "PRINT RANK 1"
37 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(x) == (1+0)))
38 END SELECT boo
39 end subroutine
41 !Error expected
42 subroutine CALL_ME2(x)
43 implicit none
44 integer :: x(..)
45 integer :: y(3),j
46 !ERROR: Selector 'y' is not an assumed-rank array variable
47 SELECT RANK(y)
48 RANK (0)
49 print *, "PRINT RANK 0"
50 RANK (1)
51 print *, "PRINT RANK 1"
52 END SELECT
54 SELECT RANK(x)
55 RANK(0)
56 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(x) == 0)) ! will fail when RANK(x) is not zero here
57 END SELECT
58 end subroutine
60 subroutine CALL_ME3(x)
61 implicit none
62 integer :: x(..),j
63 SELECT RANK(x)
64 !ERROR: The value of the selector must be between zero and 15
65 RANK (16)
66 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(x) == 16))
67 END SELECT
68 end subroutine
70 subroutine CALL_ME4(x)
71 implicit none
72 integer :: x(..)
73 SELECT RANK(x)
74 RANK DEFAULT
75 print *, "ok "
76 !ERROR: Not more than one of the selectors of SELECT RANK statement may be DEFAULT
77 RANK DEFAULT
78 print *, "not ok"
79 RANK (3)
80 print *, "IT'S 3"
81 END SELECT
82 end subroutine
84 subroutine CALL_ME5(x)
85 implicit none
86 integer :: x(..),j
87 SELECT RANK(x)
88 RANK (0)
89 print *, "PRINT RANK 0"
90 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(x) == 0))
91 RANK(1)
92 print *, "PRINT RANK 1"
93 !ERROR: Same rank value (0) not allowed more than once
94 RANK(0)
95 print *, "ERROR"
96 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(x) == 0))
97 RANK(1+1)
98 !ERROR: Same rank value (2) not allowed more than once
99 RANK(1+1)
100 END SELECT
101 end subroutine
103 subroutine CALL_ME6(x)
104 implicit none
105 integer :: x(..),j
106 SELECT RANK(x)
107 RANK (3)
108 print *, "one"
109 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(x) == 3))
110 !ERROR: The value of the selector must be between zero and 15
111 RANK(-1)
112 print *, "rank: negative"
113 !ERROR: 'kind=' argument must be a constant scalar integer whose value is a supported kind for the intrinsic result type
114 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(x) == -1))
115 END SELECT
116 end subroutine
118 subroutine CALL_ME7(arg)
119 implicit none
120 integer :: i,j
121 integer, dimension(..), pointer :: arg
122 integer, pointer :: arg2
123 select RANK(arg)
124 !ERROR: RANK (*) cannot be used when selector is POINTER or ALLOCATABLE
125 RANK (*)
126 print *, arg(1:1)
127 RANK (1)
128 print *, arg
129 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(arg) == 1))
130 end select
132 !ERROR: Selector 'arg2' is not an assumed-rank array variable
133 select RANK(arg2)
134 RANK (*)
135 print *,"This would lead to crash when saveSelSymbol has std::nullptr"
136 RANK (1)
137 print *, "Rank is 1"
138 end select
140 end subroutine
142 subroutine CALL_ME8(x)
143 implicit none
144 integer :: x(..),j
145 SELECT RANK(x)
146 Rank(2)
147 print *, "Now it's rank 2 "
148 RANK (*)
149 print *, "Going for another rank"
150 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(x) == 1))
151 !ERROR: Not more than one of the selectors of SELECT RANK statement may be '*'
152 RANK (*)
153 print *, "This is Wrong"
154 END SELECT
155 end subroutine
157 subroutine CALL_ME10(x)
158 implicit none
159 integer:: x(..), a=10,b=20,j
160 integer, dimension(5) :: arr = (/1,2,3,4,5/),brr
161 integer :: const_variable=10
162 integer, pointer :: ptr,nullptr=>NULL()
163 type derived
164 character(len = 50) :: title
165 end type derived
166 type(derived) :: obj1
168 SELECT RANK(x)
169 Rank(2)
170 print *, "Now it's rank 2 "
171 RANK (*)
172 print *, "Going for a other rank"
173 !ERROR: Not more than one of the selectors of SELECT RANK statement may be '*'
174 RANK (*)
175 print *, "This is Wrong"
176 END SELECT
178 !ERROR: Selector 'brr' is not an assumed-rank array variable
179 SELECT RANK(ptr=>brr)
180 !ERROR: Must be a constant value
181 RANK(const_variable)
182 print *, "PRINT RANK 3"
183 !j = INT(0, KIND=MERGE(KIND(0), -1, RANK(ptr) == 1))
184 !ERROR: Must be a constant value
185 RANK(nullptr)
186 print *, "PRINT RANK 3"
187 END SELECT
189 !ERROR: Selector 'x(1) + x(2)' is not an assumed-rank array variable
190 SELECT RANK (x(1) + x(2))
192 END SELECT
194 !ERROR: Selector 'x(1)' is not an assumed-rank array variable
195 SELECT RANK(x(1))
197 END SELECT
199 !ERROR: Selector 'x(1:2)' is not an assumed-rank array variable
200 SELECT RANK(x(1:2))
202 END SELECT
204 !ERROR: 'x' is not an object of derived type
205 SELECT RANK(x(1)%x(2))
207 END SELECT
209 !ERROR: Selector 'obj1%title' is not an assumed-rank array variable
210 SELECT RANK(obj1%title)
212 END SELECT
214 !ERROR: Selector 'arr(1:2)+ arr(4:5)' is not an assumed-rank array variable
215 SELECT RANK(arr(1:2)+ arr(4:5))
217 END SELECT
219 SELECT RANK(ptr=>x)
220 RANK (3)
221 PRINT *, "PRINT RANK 3"
222 !ERROR: 'ptr' is not an object that can appear in an expression
223 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(ptr) == 0))
224 RANK (1)
225 PRINT *, "PRINT RANK 1"
226 !ERROR: 'ptr' is not an object that can appear in an expression
227 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(ptr) == 1))
228 END SELECT
229 end subroutine
230 subroutine CALL_ME_TYPES(x)
231 implicit none
232 integer :: x(..),j
233 SELECT RANK(x)
234 !ERROR: Must have INTEGER type, but is LOGICAL(4)
235 RANK(.TRUE.)
236 !ERROR: Must have INTEGER type, but is REAL(4)
237 RANK(1.0)
238 !ERROR: Must be a constant value
239 RANK(RANK(x))
240 !ERROR: Must have INTEGER type, but is CHARACTER(KIND=1,LEN=6_8)
241 RANK("STRING")
242 END SELECT
243 end subroutine
244 subroutine CALL_SHAPE(x)
245 implicit none
246 integer :: x(..)
247 integer :: j
248 integer, pointer :: ptr
249 SELECT RANK(x)
250 RANK(1)
251 print *, "RANK 1"
252 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(x) == 1))
253 RANK (3)
254 print *, "RANK 3"
255 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(x) == 3))
256 END SELECT
257 SELECT RANK(ptr => x )
258 RANK(1)
259 print *, "RANK 1"
260 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(ptr) == 1))
261 RANK (3)
262 print *, "RANK 3"
263 j = INT(0, KIND=MERGE(KIND(0), -1, RANK(ptr) == 3))
264 END SELECT
266 end subroutine
268 end program