xref: /llvm-project/flang/test/Lower/HLFIR/select-rank.f90 (revision 0b54e33fd5ab362dfa5eacb61d7cbdb9cc3a89ac)
1! Test lowering of select rank to HLFIR
2! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
3
4module iface_helpers
5interface
6  subroutine r0(x)
7    real :: x
8  end subroutine
9  subroutine r1(x)
10    real :: x(:)
11  end subroutine
12  subroutine r2(x)
13    real :: x(:, :)
14  end subroutine
15  subroutine r15(x)
16    real :: x(:,:,:,:,:,:,:,:,:,:,:,:,:,:,:)
17  end subroutine
18  subroutine rdefault(x)
19    real :: x(..)
20  end subroutine
21  subroutine rcdefault(x)
22    character(*) :: x(..)
23  end subroutine
24  subroutine rassumed_size(x)
25    real :: x(*)
26  end subroutine
27
28  subroutine ra0(x)
29    real, allocatable  :: x
30  end subroutine
31  subroutine ra1(x)
32    real, allocatable  :: x(:)
33  end subroutine
34  subroutine ra2(x)
35    real, allocatable  :: x(:, :)
36  end subroutine
37  subroutine ra15(x)
38    real, allocatable  :: x(:,:,:,:,:,:,:,:,:,:,:,:,:,:,:)
39  end subroutine
40  subroutine radefault(x)
41    real, allocatable  :: x(..)
42  end subroutine
43
44  subroutine rup0(x)
45    class(*) :: x
46  end subroutine
47  subroutine rup1(x)
48    class(*)  :: x(:)
49  end subroutine
50  subroutine rupdefault(x)
51    class(*) :: x(..)
52  end subroutine
53
54end interface
55end module
56
57subroutine test_single_case(x)
58  use iface_helpers
59  real :: x(..)
60  select rank (x)
61   rank (1)
62    call r1(x)
63  end select
64end subroutine
65
66subroutine test_simple_case(x)
67  use iface_helpers
68  real :: x(..)
69  select rank (x)
70   rank default
71      call rdefault(x)
72   rank (1)
73      call r1(x)
74   rank (15)
75      call r15(x)
76   rank (0)
77      call r0(x)
78  end select
79end subroutine
80
81subroutine test_rank_star(x)
82  use iface_helpers
83  real :: x(..)
84  select rank (x)
85   rank (2)
86      call r2(x)
87   rank default
88      call rdefault(x)
89   rank (1)
90      call r1(x)
91   rank (*)
92      ! test no copy in/out is generated here.
93      call rassumed_size(x)
94  end select
95end subroutine
96
97
98subroutine test_renaming(x)
99  use iface_helpers
100  real :: x(..)
101  select rank (new_name => x)
102   rank (1)
103    call r1(new_name)
104    call rdefault(x)
105  end select
106end subroutine
107
108subroutine test_no_case(x)
109  real :: x(..)
110  select rank (x)
111  end select
112end subroutine
113
114subroutine test_rank_star_attributes(x)
115  use iface_helpers
116  real, optional, asynchronous, target :: x(..)
117  ! The declare generated for the associating entity should have the
118  ! TARGET and ASYNCHRONOUS attribute, but not the OPTIONAL attribute.
119  ! F'2023 11.1.3.3 and 11.1.10.3.
120  select rank (x)
121   rank (2)
122      call r2(x)
123   rank default
124      call rdefault(x)
125   rank (*)
126      call rassumed_size(x)
127  end select
128end subroutine
129
130subroutine test_rank_star_contiguous(x)
131  use iface_helpers
132  real, target, contiguous :: x(..)
133  ! Test simple hlfir.declare without fir.box are generated for
134  ! ranked case and that non copy-in/out is generated when passing
135  ! associating entity to implicit interfaces.
136  select rank (x)
137   rank (2)
138    call r2_implicit(x)
139   rank default
140    ! TODO: hlfir.declare could be given the CONTIGUOUS attribute.
141    call rdefault(x)
142   rank (1)
143    call r1_implicit(x)
144   rank (*)
145    call r1_implicit(x)
146  end select
147end subroutine
148
149subroutine test_rank_star_contiguous_character(x, n)
150  use iface_helpers
151  integer(8) :: n
152  character(n), contiguous :: x(..)
153  select rank (x)
154   ! test fir.box is properly converted to fir.boxchar in the hlfir.declare
155   ! for the associating entity.
156   rank (0)
157    call rc0_implicit(x)
158   rank default
159    call rcdefault(x)
160   rank (1)
161    call rc1_implicit(x)
162   rank (*)
163    call rc1_implicit(x)
164  end select
165end subroutine
166
167subroutine test_simple_alloc(x)
168  use iface_helpers
169  real, allocatable :: x(..)
170  ! test no is_assumed_size if generated and that associating entity
171  ! hlfir.declare has allocatable attrbute.
172  select rank (x)
173   rank (2)
174    call ra2(x)
175   rank (0)
176    call ra0(x)
177   rank default
178    call radefault(x)
179   rank (1)
180    call ra1(x)
181  end select
182end subroutine
183
184subroutine test_character_alloc(x)
185  character(:), allocatable :: x(..)
186  ! test hlfir.declare for associating entities do not not have
187  ! explicit type parameters.
188  select rank (x)
189   rank default
190   rank (1)
191  end select
192end subroutine
193
194subroutine test_explicit_character_ptr(x, n)
195  use iface_helpers
196  integer(8) :: n
197  character(n), allocatable :: x(..)
198  ! test hlfir.declare for associating entities have
199  ! explicit type parameters.
200  select rank (x)
201   rank default
202   rank (0)
203  end select
204end subroutine
205
206subroutine test_assumed_character_ptr(x)
207  use iface_helpers
208  character(*), allocatable :: x(..)
209  ! test hlfir.declare for associating entities have
210  ! explicit type parameters.
211  select rank (x)
212   rank default
213   rank (0)
214  end select
215end subroutine
216
217subroutine test_polymorphic(x)
218  use iface_helpers
219  class(*) :: x(..)
220  select rank (x)
221   rank (1)
222     call rup1(x)
223   rank default
224     call rupdefault(x)
225   rank (0)
226     call rup0(x)
227  end select
228end subroutine
229
230subroutine test_nested_select_rank(x1, x2)
231  use iface_helpers
232  real :: x1(..), x2(..)
233  select rank(x1)
234    rank(0)
235      select rank(x2)
236        rank(0)
237          call r0(x1)
238          call r0(x2)
239        rank(1)
240          call r0(x1)
241          call r1(x2)
242        rank default
243          call r0(x1)
244          call rdefault(x2)
245      end select
246    rank(1)
247      select rank(x2)
248        rank(0)
249          call r1(x1)
250          call r0(x2)
251        rank(1)
252          call r1(x1)
253          call r1(x2)
254        rank default
255          call r1(x1)
256          call rdefault(x2)
257      end select
258    rank default
259      select rank(x2)
260        rank(0)
261          call rdefault(x1)
262          call r0(x2)
263        rank(1)
264          call rdefault(x1)
265          call r1(x2)
266        rank default
267          call rdefault(x1)
268          call rdefault(x2)
269      end select
270  end select
271end subroutine
272
273subroutine test_branching(x)
274! Note branching into a select rank, or between cases, is illegal
275! and caught by semantics.
276  use iface_helpers
277  real :: x(..)
278  logical, external :: leave_now
279  logical, external :: jump
280  select rank (x)
281   rank default
282    if (jump()) goto 1
283    call one()
2841   call rdefault(x)
285   rank (1)
286    if (leave_now()) goto 3
287    call r1(x)
288   rank (2)
289  end select
2903 call the_end()
291end subroutine
292
293! CHECK-LABEL:   func.func @_QPtest_single_case(
294! CHECK-SAME:                                   %[[VAL_0:.*]]: !fir.box<!fir.array<*:f32>> {fir.bindc_name = "x"}) {
295! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
296! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_1]] {uniq_name = "_QFtest_single_caseEx"} : (!fir.box<!fir.array<*:f32>>, !fir.dscope) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
297! CHECK:           %[[VAL_3:.*]] = arith.constant 1 : i8
298! CHECK:           %[[VAL_4:.*]] = fir.is_assumed_size %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
299! CHECK:           cf.cond_br %[[VAL_4]], ^bb3, ^bb1
300! CHECK:         ^bb1:
301! CHECK:           %[[VAL_5:.*]] = fir.box_rank %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
302! CHECK:           fir.select_case %[[VAL_5]] : i8 [#fir.point, %[[VAL_3]], ^bb2, unit, ^bb3]
303! CHECK:         ^bb2:
304! CHECK:           %[[VAL_6:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?xf32>>
305! CHECK:           %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_6]] {uniq_name = "_QFtest_single_caseEx"} : (!fir.box<!fir.array<?xf32>>) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>)
306! CHECK:           fir.call @_QPr1(%[[VAL_7]]#0) fastmath<contract> : (!fir.box<!fir.array<?xf32>>) -> ()
307! CHECK:           cf.br ^bb3
308! CHECK:         ^bb3:
309! CHECK:           return
310! CHECK:         }
311
312! CHECK-LABEL:   func.func @_QPtest_simple_case(
313! CHECK-SAME:                                   %[[VAL_0:.*]]: !fir.box<!fir.array<*:f32>> {fir.bindc_name = "x"}) {
314! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
315! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_1]] {uniq_name = "_QFtest_simple_caseEx"} : (!fir.box<!fir.array<*:f32>>, !fir.dscope) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
316! CHECK:           %[[VAL_3:.*]] = arith.constant 1 : i8
317! CHECK:           %[[VAL_4:.*]] = arith.constant 15 : i8
318! CHECK:           %[[VAL_5:.*]] = arith.constant 0 : i8
319! CHECK:           %[[VAL_6:.*]] = fir.is_assumed_size %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
320! CHECK:           cf.cond_br %[[VAL_6]], ^bb1, ^bb2
321! CHECK:         ^bb1:
322! CHECK:           %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_2]]#0 {uniq_name = "_QFtest_simple_caseEx"} : (!fir.box<!fir.array<*:f32>>) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
323! CHECK:           fir.call @_QPrdefault(%[[VAL_7]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
324! CHECK:           cf.br ^bb6
325! CHECK:         ^bb2:
326! CHECK:           %[[VAL_8:.*]] = fir.box_rank %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
327! CHECK:           fir.select_case %[[VAL_8]] : i8 [#fir.point, %[[VAL_3]], ^bb3, #fir.point, %[[VAL_4]], ^bb4, #fir.point, %[[VAL_5]], ^bb5, unit, ^bb1]
328! CHECK:         ^bb3:
329! CHECK:           %[[VAL_9:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?xf32>>
330! CHECK:           %[[VAL_10:.*]]:2 = hlfir.declare %[[VAL_9]] {uniq_name = "_QFtest_simple_caseEx"} : (!fir.box<!fir.array<?xf32>>) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>)
331! CHECK:           fir.call @_QPr1(%[[VAL_10]]#0) fastmath<contract> : (!fir.box<!fir.array<?xf32>>) -> ()
332! CHECK:           cf.br ^bb6
333! CHECK:         ^bb4:
334! CHECK:           %[[VAL_11:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?x?x?x?x?x?x?x?x?x?x?x?x?x?x?xf32>>
335! CHECK:           %[[VAL_12:.*]]:2 = hlfir.declare %[[VAL_11]] {uniq_name = "_QFtest_simple_caseEx"} : (!fir.box<!fir.array<?x?x?x?x?x?x?x?x?x?x?x?x?x?x?xf32>>) -> (!fir.box<!fir.array<?x?x?x?x?x?x?x?x?x?x?x?x?x?x?xf32>>, !fir.box<!fir.array<?x?x?x?x?x?x?x?x?x?x?x?x?x?x?xf32>>)
336! CHECK:           fir.call @_QPr15(%[[VAL_12]]#0) fastmath<contract> : (!fir.box<!fir.array<?x?x?x?x?x?x?x?x?x?x?x?x?x?x?xf32>>) -> ()
337! CHECK:           cf.br ^bb6
338! CHECK:         ^bb5:
339! CHECK:           %[[VAL_13:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<f32>
340! CHECK:           %[[VAL_14:.*]] = fir.box_addr %[[VAL_13]] : (!fir.box<f32>) -> !fir.ref<f32>
341! CHECK:           %[[VAL_15:.*]]:2 = hlfir.declare %[[VAL_14]] {uniq_name = "_QFtest_simple_caseEx"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
342! CHECK:           fir.call @_QPr0(%[[VAL_15]]#1) fastmath<contract> : (!fir.ref<f32>) -> ()
343! CHECK:           cf.br ^bb6
344! CHECK:         ^bb6:
345! CHECK:           return
346! CHECK:         }
347
348! CHECK-LABEL:   func.func @_QPtest_rank_star(
349! CHECK-SAME:                                 %[[VAL_0:.*]]: !fir.box<!fir.array<*:f32>> {fir.bindc_name = "x"}) {
350! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
351! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_1]] {uniq_name = "_QFtest_rank_starEx"} : (!fir.box<!fir.array<*:f32>>, !fir.dscope) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
352! CHECK:           %[[VAL_3:.*]] = arith.constant 2 : i8
353! CHECK:           %[[VAL_4:.*]] = arith.constant 1 : i8
354! CHECK:           %[[VAL_5:.*]] = fir.is_assumed_size %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
355! CHECK:           cf.cond_br %[[VAL_5]], ^bb5, ^bb1
356! CHECK:         ^bb1:
357! CHECK:           %[[VAL_6:.*]] = fir.box_rank %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
358! CHECK:           fir.select_case %[[VAL_6]] : i8 [#fir.point, %[[VAL_3]], ^bb2, #fir.point, %[[VAL_4]], ^bb4, unit, ^bb3]
359! CHECK:         ^bb2:
360! CHECK:           %[[VAL_7:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?x?xf32>>
361! CHECK:           %[[VAL_8:.*]]:2 = hlfir.declare %[[VAL_7]] {uniq_name = "_QFtest_rank_starEx"} : (!fir.box<!fir.array<?x?xf32>>) -> (!fir.box<!fir.array<?x?xf32>>, !fir.box<!fir.array<?x?xf32>>)
362! CHECK:           fir.call @_QPr2(%[[VAL_8]]#0) fastmath<contract> : (!fir.box<!fir.array<?x?xf32>>) -> ()
363! CHECK:           cf.br ^bb6
364! CHECK:         ^bb3:
365! CHECK:           %[[VAL_9:.*]]:2 = hlfir.declare %[[VAL_2]]#0 {uniq_name = "_QFtest_rank_starEx"} : (!fir.box<!fir.array<*:f32>>) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
366! CHECK:           fir.call @_QPrdefault(%[[VAL_9]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
367! CHECK:           cf.br ^bb6
368! CHECK:         ^bb4:
369! CHECK:           %[[VAL_10:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?xf32>>
370! CHECK:           %[[VAL_11:.*]]:2 = hlfir.declare %[[VAL_10]] {uniq_name = "_QFtest_rank_starEx"} : (!fir.box<!fir.array<?xf32>>) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>)
371! CHECK:           fir.call @_QPr1(%[[VAL_11]]#0) fastmath<contract> : (!fir.box<!fir.array<?xf32>>) -> ()
372! CHECK:           cf.br ^bb6
373! CHECK:         ^bb5:
374! CHECK:           %[[VAL_12:.*]] = arith.constant -1 : index
375! CHECK:           %[[VAL_13:.*]] = fir.box_addr %[[VAL_2]]#1 : (!fir.box<!fir.array<*:f32>>) -> !fir.ref<!fir.array<*:f32>>
376! CHECK:           %[[VAL_14:.*]] = fir.convert %[[VAL_13]] : (!fir.ref<!fir.array<*:f32>>) -> !fir.ref<!fir.array<?xf32>>
377! CHECK:           %[[VAL_15:.*]] = fir.shape %[[VAL_12]] : (index) -> !fir.shape<1>
378! CHECK:           %[[VAL_16:.*]]:2 = hlfir.declare %[[VAL_14]](%[[VAL_15]]) {uniq_name = "_QFtest_rank_starEx"} : (!fir.ref<!fir.array<?xf32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xf32>>, !fir.ref<!fir.array<?xf32>>)
379! CHECK:           fir.call @_QPrassumed_size(%[[VAL_16]]#1) fastmath<contract> : (!fir.ref<!fir.array<?xf32>>) -> ()
380! CHECK:           cf.br ^bb6
381! CHECK:         ^bb6:
382! CHECK:           return
383! CHECK:         }
384
385! CHECK-LABEL:   func.func @_QPtest_renaming(
386! CHECK-SAME:                                %[[VAL_0:.*]]: !fir.box<!fir.array<*:f32>> {fir.bindc_name = "x"}) {
387! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
388! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_1]] {uniq_name = "_QFtest_renamingEx"} : (!fir.box<!fir.array<*:f32>>, !fir.dscope) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
389! CHECK:           %[[VAL_3:.*]] = arith.constant 1 : i8
390! CHECK:           %[[VAL_4:.*]] = fir.is_assumed_size %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
391! CHECK:           cf.cond_br %[[VAL_4]], ^bb3, ^bb1
392! CHECK:         ^bb1:
393! CHECK:           %[[VAL_5:.*]] = fir.box_rank %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
394! CHECK:           fir.select_case %[[VAL_5]] : i8 [#fir.point, %[[VAL_3]], ^bb2, unit, ^bb3]
395! CHECK:         ^bb2:
396! CHECK:           %[[VAL_6:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?xf32>>
397! CHECK:           %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_6]] {uniq_name = "_QFtest_renamingEnew_name"} : (!fir.box<!fir.array<?xf32>>) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>)
398! CHECK:           fir.call @_QPr1(%[[VAL_7]]#0) fastmath<contract> : (!fir.box<!fir.array<?xf32>>) -> ()
399! CHECK:           fir.call @_QPrdefault(%[[VAL_2]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
400! CHECK:           cf.br ^bb3
401! CHECK:         ^bb3:
402! CHECK:           return
403! CHECK:         }
404
405! CHECK-LABEL:   func.func @_QPtest_no_case(
406! CHECK-SAME:                               %[[VAL_0:.*]]: !fir.box<!fir.array<*:f32>> {fir.bindc_name = "x"}) {
407! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
408! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_1]] {uniq_name = "_QFtest_no_caseEx"} : (!fir.box<!fir.array<*:f32>>, !fir.dscope) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
409! CHECK:           %[[VAL_3:.*]] = fir.is_assumed_size %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
410! CHECK:           cf.cond_br %[[VAL_3]], ^bb2, ^bb1
411! CHECK:         ^bb1:
412! CHECK:           %[[VAL_4:.*]] = fir.box_rank %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
413! CHECK:           fir.select_case %[[VAL_4]] : i8 [unit, ^bb2]
414! CHECK:         ^bb2:
415! CHECK:           return
416! CHECK:         }
417
418! CHECK-LABEL:   func.func @_QPtest_rank_star_attributes(
419! CHECK-SAME:                                            %[[VAL_0:.*]]: !fir.box<!fir.array<*:f32>> {fir.asynchronous, fir.bindc_name = "x", fir.optional, fir.target}) {
420! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
421! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_1]] {fortran_attrs = #fir.var_attrs<asynchronous, optional, target>, uniq_name = "_QFtest_rank_star_attributesEx"} : (!fir.box<!fir.array<*:f32>>, !fir.dscope) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
422! CHECK:           %[[VAL_3:.*]] = arith.constant 2 : i8
423! CHECK:           %[[VAL_4:.*]] = fir.is_assumed_size %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
424! CHECK:           cf.cond_br %[[VAL_4]], ^bb4, ^bb1
425! CHECK:         ^bb1:
426! CHECK:           %[[VAL_5:.*]] = fir.box_rank %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
427! CHECK:           fir.select_case %[[VAL_5]] : i8 [#fir.point, %[[VAL_3]], ^bb2, unit, ^bb3]
428! CHECK:         ^bb2:
429! CHECK:           %[[VAL_6:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?x?xf32>>
430! CHECK:           %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_6]] {fortran_attrs = #fir.var_attrs<asynchronous, target>, uniq_name = "_QFtest_rank_star_attributesEx"} : (!fir.box<!fir.array<?x?xf32>>) -> (!fir.box<!fir.array<?x?xf32>>, !fir.box<!fir.array<?x?xf32>>)
431! CHECK:           fir.call @_QPr2(%[[VAL_7]]#0) fastmath<contract> : (!fir.box<!fir.array<?x?xf32>>) -> ()
432! CHECK:           cf.br ^bb5
433! CHECK:         ^bb3:
434! CHECK:           %[[VAL_8:.*]]:2 = hlfir.declare %[[VAL_2]]#0 {fortran_attrs = #fir.var_attrs<asynchronous, target>, uniq_name = "_QFtest_rank_star_attributesEx"} : (!fir.box<!fir.array<*:f32>>) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
435! CHECK:           fir.call @_QPrdefault(%[[VAL_8]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
436! CHECK:           cf.br ^bb5
437! CHECK:         ^bb4:
438! CHECK:           %[[VAL_9:.*]] = arith.constant -1 : index
439! CHECK:           %[[VAL_10:.*]] = fir.box_addr %[[VAL_2]]#1 : (!fir.box<!fir.array<*:f32>>) -> !fir.ref<!fir.array<*:f32>>
440! CHECK:           %[[VAL_11:.*]] = fir.convert %[[VAL_10]] : (!fir.ref<!fir.array<*:f32>>) -> !fir.ref<!fir.array<?xf32>>
441! CHECK:           %[[VAL_12:.*]] = fir.shape %[[VAL_9]] : (index) -> !fir.shape<1>
442! CHECK:           %[[VAL_13:.*]]:2 = hlfir.declare %[[VAL_11]](%[[VAL_12]]) {fortran_attrs = #fir.var_attrs<asynchronous, target>, uniq_name = "_QFtest_rank_star_attributesEx"} : (!fir.ref<!fir.array<?xf32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xf32>>, !fir.ref<!fir.array<?xf32>>)
443! CHECK:           fir.call @_QPrassumed_size(%[[VAL_13]]#1) fastmath<contract> : (!fir.ref<!fir.array<?xf32>>) -> ()
444! CHECK:           cf.br ^bb5
445! CHECK:         ^bb5:
446! CHECK:           return
447! CHECK:         }
448
449! CHECK-LABEL:   func.func @_QPtest_rank_star_contiguous(
450! CHECK-SAME:                                            %[[VAL_0:.*]]: !fir.box<!fir.array<*:f32>> {fir.bindc_name = "x", fir.contiguous, fir.target}) {
451! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
452! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_1]] {fortran_attrs = #fir.var_attrs<contiguous, target>, uniq_name = "_QFtest_rank_star_contiguousEx"} : (!fir.box<!fir.array<*:f32>>, !fir.dscope) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
453! CHECK:           %[[VAL_3:.*]] = arith.constant 2 : i8
454! CHECK:           %[[VAL_4:.*]] = arith.constant 1 : i8
455! CHECK:           %[[VAL_5:.*]] = fir.is_assumed_size %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
456! CHECK:           cf.cond_br %[[VAL_5]], ^bb5, ^bb1
457! CHECK:         ^bb1:
458! CHECK:           %[[VAL_6:.*]] = fir.box_rank %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
459! CHECK:           fir.select_case %[[VAL_6]] : i8 [#fir.point, %[[VAL_3]], ^bb2, #fir.point, %[[VAL_4]], ^bb4, unit, ^bb3]
460! CHECK:         ^bb2:
461! CHECK:           %[[VAL_7:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?x?xf32>>
462! CHECK:           %[[VAL_8:.*]] = fir.box_addr %[[VAL_7]] : (!fir.box<!fir.array<?x?xf32>>) -> !fir.ref<!fir.array<?x?xf32>>
463! CHECK:           %[[VAL_9:.*]] = arith.constant 0 : index
464! CHECK:           %[[VAL_10:.*]]:3 = fir.box_dims %[[VAL_7]], %[[VAL_9]] : (!fir.box<!fir.array<?x?xf32>>, index) -> (index, index, index)
465! CHECK:           %[[VAL_11:.*]] = arith.constant 1 : index
466! CHECK:           %[[VAL_12:.*]]:3 = fir.box_dims %[[VAL_7]], %[[VAL_11]] : (!fir.box<!fir.array<?x?xf32>>, index) -> (index, index, index)
467! CHECK:           %[[VAL_13:.*]] = fir.shape %[[VAL_10]]#1, %[[VAL_12]]#1 : (index, index) -> !fir.shape<2>
468! CHECK:           %[[VAL_14:.*]]:2 = hlfir.declare %[[VAL_8]](%[[VAL_13]]) {fortran_attrs = #fir.var_attrs<target>, uniq_name = "_QFtest_rank_star_contiguousEx"} : (!fir.ref<!fir.array<?x?xf32>>, !fir.shape<2>) -> (!fir.box<!fir.array<?x?xf32>>, !fir.ref<!fir.array<?x?xf32>>)
469! CHECK:           fir.call @_QPr2_implicit(%[[VAL_14]]#1) fastmath<contract> : (!fir.ref<!fir.array<?x?xf32>>) -> ()
470! CHECK:           cf.br ^bb6
471! CHECK:         ^bb3:
472! CHECK:           %[[VAL_15:.*]]:2 = hlfir.declare %[[VAL_2]]#0 {fortran_attrs = #fir.var_attrs<target>, uniq_name = "_QFtest_rank_star_contiguousEx"} : (!fir.box<!fir.array<*:f32>>) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
473! CHECK:           fir.call @_QPrdefault(%[[VAL_15]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
474! CHECK:           cf.br ^bb6
475! CHECK:         ^bb4:
476! CHECK:           %[[VAL_16:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?xf32>>
477! CHECK:           %[[VAL_17:.*]] = fir.box_addr %[[VAL_16]] : (!fir.box<!fir.array<?xf32>>) -> !fir.ref<!fir.array<?xf32>>
478! CHECK:           %[[VAL_18:.*]] = arith.constant 0 : index
479! CHECK:           %[[VAL_19:.*]]:3 = fir.box_dims %[[VAL_16]], %[[VAL_18]] : (!fir.box<!fir.array<?xf32>>, index) -> (index, index, index)
480! CHECK:           %[[VAL_20:.*]] = fir.shape %[[VAL_19]]#1 : (index) -> !fir.shape<1>
481! CHECK:           %[[VAL_21:.*]]:2 = hlfir.declare %[[VAL_17]](%[[VAL_20]]) {fortran_attrs = #fir.var_attrs<target>, uniq_name = "_QFtest_rank_star_contiguousEx"} : (!fir.ref<!fir.array<?xf32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xf32>>, !fir.ref<!fir.array<?xf32>>)
482! CHECK:           fir.call @_QPr1_implicit(%[[VAL_21]]#1) fastmath<contract> : (!fir.ref<!fir.array<?xf32>>) -> ()
483! CHECK:           cf.br ^bb6
484! CHECK:         ^bb5:
485! CHECK:           %[[VAL_22:.*]] = arith.constant -1 : index
486! CHECK:           %[[VAL_23:.*]] = fir.box_addr %[[VAL_2]]#1 : (!fir.box<!fir.array<*:f32>>) -> !fir.ref<!fir.array<*:f32>>
487! CHECK:           %[[VAL_24:.*]] = fir.convert %[[VAL_23]] : (!fir.ref<!fir.array<*:f32>>) -> !fir.ref<!fir.array<?xf32>>
488! CHECK:           %[[VAL_25:.*]] = fir.shape %[[VAL_22]] : (index) -> !fir.shape<1>
489! CHECK:           %[[VAL_26:.*]]:2 = hlfir.declare %[[VAL_24]](%[[VAL_25]]) {fortran_attrs = #fir.var_attrs<target>, uniq_name = "_QFtest_rank_star_contiguousEx"} : (!fir.ref<!fir.array<?xf32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xf32>>, !fir.ref<!fir.array<?xf32>>)
490! CHECK:           fir.call @_QPr1_implicit(%[[VAL_26]]#1) fastmath<contract> : (!fir.ref<!fir.array<?xf32>>) -> ()
491! CHECK:           cf.br ^bb6
492! CHECK:         ^bb6:
493! CHECK:           return
494! CHECK:         }
495
496! CHECK-LABEL:   func.func @_QPtest_rank_star_contiguous_character(
497! CHECK-SAME:                                                      %[[VAL_0:.*]]: !fir.box<!fir.array<*:!fir.char<1,?>>> {fir.bindc_name = "x", fir.contiguous},
498! CHECK-SAME:                                                      %[[VAL_1:.*]]: !fir.ref<i64> {fir.bindc_name = "n"}) {
499! CHECK:           %[[VAL_2:.*]] = fir.dummy_scope : !fir.dscope
500! CHECK:           %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_1]] dummy_scope %[[VAL_2]] {uniq_name = "_QFtest_rank_star_contiguous_characterEn"} : (!fir.ref<i64>, !fir.dscope) -> (!fir.ref<i64>, !fir.ref<i64>)
501! CHECK:           %[[VAL_4:.*]] = fir.load %[[VAL_3]]#0 : !fir.ref<i64>
502! CHECK:           %[[VAL_5:.*]] = arith.constant 0 : i64
503! CHECK:           %[[VAL_6:.*]] = arith.cmpi sgt, %[[VAL_4]], %[[VAL_5]] : i64
504! CHECK:           %[[VAL_7:.*]] = arith.select %[[VAL_6]], %[[VAL_4]], %[[VAL_5]] : i64
505! CHECK:           %[[VAL_8:.*]]:2 = hlfir.declare %[[VAL_0]] typeparams %[[VAL_7]] dummy_scope %[[VAL_2]] {fortran_attrs = #fir.var_attrs<contiguous>, uniq_name = "_QFtest_rank_star_contiguous_characterEx"} : (!fir.box<!fir.array<*:!fir.char<1,?>>>, i64, !fir.dscope) -> (!fir.box<!fir.array<*:!fir.char<1,?>>>, !fir.box<!fir.array<*:!fir.char<1,?>>>)
506! CHECK:           %[[VAL_9:.*]] = arith.constant 0 : i8
507! CHECK:           %[[VAL_10:.*]] = arith.constant 1 : i8
508! CHECK:           %[[VAL_11:.*]] = fir.is_assumed_size %[[VAL_8]]#0 : (!fir.box<!fir.array<*:!fir.char<1,?>>>) -> i1
509! CHECK:           cf.cond_br %[[VAL_11]], ^bb5, ^bb1
510! CHECK:         ^bb1:
511! CHECK:           %[[VAL_12:.*]] = fir.box_rank %[[VAL_8]]#0 : (!fir.box<!fir.array<*:!fir.char<1,?>>>) -> i8
512! CHECK:           fir.select_case %[[VAL_12]] : i8 [#fir.point, %[[VAL_9]], ^bb2, #fir.point, %[[VAL_10]], ^bb4, unit, ^bb3]
513! CHECK:         ^bb2:
514! CHECK:           %[[VAL_13:.*]] = fir.convert %[[VAL_8]]#0 : (!fir.box<!fir.array<*:!fir.char<1,?>>>) -> !fir.box<!fir.char<1,?>>
515! CHECK:           %[[VAL_14:.*]] = fir.box_addr %[[VAL_13]] : (!fir.box<!fir.char<1,?>>) -> !fir.ref<!fir.char<1,?>>
516! CHECK:           %[[VAL_15:.*]] = fir.box_elesize %[[VAL_13]] : (!fir.box<!fir.char<1,?>>) -> index
517! CHECK:           %[[VAL_16:.*]]:2 = hlfir.declare %[[VAL_14]] typeparams %[[VAL_15]] {uniq_name = "_QFtest_rank_star_contiguous_characterEx"} : (!fir.ref<!fir.char<1,?>>, index) -> (!fir.boxchar<1>, !fir.ref<!fir.char<1,?>>)
518! CHECK:           fir.call @_QPrc0_implicit(%[[VAL_16]]#0) fastmath<contract> : (!fir.boxchar<1>) -> ()
519! CHECK:           cf.br ^bb6
520! CHECK:         ^bb3:
521! CHECK:           %[[VAL_17:.*]]:2 = hlfir.declare %[[VAL_8]]#0 typeparams %[[VAL_7]] {uniq_name = "_QFtest_rank_star_contiguous_characterEx"} : (!fir.box<!fir.array<*:!fir.char<1,?>>>, i64) -> (!fir.box<!fir.array<*:!fir.char<1,?>>>, !fir.box<!fir.array<*:!fir.char<1,?>>>)
522! CHECK:           fir.call @_QPrcdefault(%[[VAL_17]]#0) fastmath<contract> : (!fir.box<!fir.array<*:!fir.char<1,?>>>) -> ()
523! CHECK:           cf.br ^bb6
524! CHECK:         ^bb4:
525! CHECK:           %[[VAL_18:.*]] = fir.convert %[[VAL_8]]#0 : (!fir.box<!fir.array<*:!fir.char<1,?>>>) -> !fir.box<!fir.array<?x!fir.char<1,?>>>
526! CHECK:           %[[VAL_19:.*]] = fir.box_addr %[[VAL_18]] : (!fir.box<!fir.array<?x!fir.char<1,?>>>) -> !fir.ref<!fir.array<?x!fir.char<1,?>>>
527! CHECK:           %[[VAL_20:.*]] = arith.constant 0 : index
528! CHECK:           %[[VAL_21:.*]]:3 = fir.box_dims %[[VAL_18]], %[[VAL_20]] : (!fir.box<!fir.array<?x!fir.char<1,?>>>, index) -> (index, index, index)
529! CHECK:           %[[VAL_22:.*]] = fir.box_elesize %[[VAL_18]] : (!fir.box<!fir.array<?x!fir.char<1,?>>>) -> index
530! CHECK:           %[[VAL_23:.*]] = fir.shape %[[VAL_21]]#1 : (index) -> !fir.shape<1>
531! CHECK:           %[[VAL_24:.*]]:2 = hlfir.declare %[[VAL_19]](%[[VAL_23]]) typeparams %[[VAL_22]] {uniq_name = "_QFtest_rank_star_contiguous_characterEx"} : (!fir.ref<!fir.array<?x!fir.char<1,?>>>, !fir.shape<1>, index) -> (!fir.box<!fir.array<?x!fir.char<1,?>>>, !fir.ref<!fir.array<?x!fir.char<1,?>>>)
532! CHECK:           %[[VAL_25:.*]] = fir.convert %[[VAL_24]]#1 : (!fir.ref<!fir.array<?x!fir.char<1,?>>>) -> !fir.ref<!fir.char<1,?>>
533! CHECK:           %[[VAL_26:.*]] = fir.emboxchar %[[VAL_25]], %[[VAL_22]] : (!fir.ref<!fir.char<1,?>>, index) -> !fir.boxchar<1>
534! CHECK:           fir.call @_QPrc1_implicit(%[[VAL_26]]) fastmath<contract> : (!fir.boxchar<1>) -> ()
535! CHECK:           cf.br ^bb6
536! CHECK:         ^bb5:
537! CHECK:           %[[VAL_27:.*]] = arith.constant -1 : index
538! CHECK:           %[[VAL_28:.*]] = fir.box_addr %[[VAL_8]]#1 : (!fir.box<!fir.array<*:!fir.char<1,?>>>) -> !fir.ref<!fir.array<*:!fir.char<1,?>>>
539! CHECK:           %[[VAL_29:.*]] = fir.convert %[[VAL_28]] : (!fir.ref<!fir.array<*:!fir.char<1,?>>>) -> !fir.ref<!fir.array<?x!fir.char<1,?>>>
540! CHECK:           %[[VAL_30:.*]] = fir.shape %[[VAL_27]] : (index) -> !fir.shape<1>
541! CHECK:           %[[VAL_31:.*]]:2 = hlfir.declare %[[VAL_29]](%[[VAL_30]]) typeparams %[[VAL_7]] {uniq_name = "_QFtest_rank_star_contiguous_characterEx"} : (!fir.ref<!fir.array<?x!fir.char<1,?>>>, !fir.shape<1>, i64) -> (!fir.box<!fir.array<?x!fir.char<1,?>>>, !fir.ref<!fir.array<?x!fir.char<1,?>>>)
542! CHECK:           %[[VAL_32:.*]] = fir.convert %[[VAL_31]]#1 : (!fir.ref<!fir.array<?x!fir.char<1,?>>>) -> !fir.ref<!fir.char<1,?>>
543! CHECK:           %[[VAL_33:.*]] = fir.emboxchar %[[VAL_32]], %[[VAL_7]] : (!fir.ref<!fir.char<1,?>>, i64) -> !fir.boxchar<1>
544! CHECK:           fir.call @_QPrc1_implicit(%[[VAL_33]]) fastmath<contract> : (!fir.boxchar<1>) -> ()
545! CHECK:           cf.br ^bb6
546! CHECK:         ^bb6:
547! CHECK:           return
548! CHECK:         }
549
550! CHECK-LABEL:   func.func @_QPtest_simple_alloc(
551! CHECK-SAME:                                    %[[VAL_0:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>> {fir.bindc_name = "x"}) {
552! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
553! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_1]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_simple_allocEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>>, !fir.dscope) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>>)
554! CHECK:           %[[VAL_3:.*]] = arith.constant 2 : i8
555! CHECK:           %[[VAL_4:.*]] = arith.constant 0 : i8
556! CHECK:           %[[VAL_5:.*]] = arith.constant 1 : i8
557! CHECK-NOT: fir.is_assumed_size
558! CHECK:           %[[VAL_6:.*]] = fir.box_rank %[[VAL_2]]#0 : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>>) -> i8
559! CHECK:           fir.select_case %[[VAL_6]] : i8 [#fir.point, %[[VAL_3]], ^bb1, #fir.point, %[[VAL_4]], ^bb2, #fir.point, %[[VAL_5]], ^bb4, unit, ^bb3]
560! CHECK:         ^bb1:
561! CHECK:           %[[VAL_7:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>>) -> !fir.ref<!fir.box<!fir.heap<!fir.array<?x?xf32>>>>
562! CHECK:           %[[VAL_8:.*]]:2 = hlfir.declare %[[VAL_7]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_simple_allocEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?x?xf32>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?x?xf32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?x?xf32>>>>)
563! CHECK:           fir.call @_QPra2(%[[VAL_8]]#0) fastmath<contract> : (!fir.ref<!fir.box<!fir.heap<!fir.array<?x?xf32>>>>) -> ()
564! CHECK:           cf.br ^bb5
565! CHECK:         ^bb2:
566! CHECK:           %[[VAL_9:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>>) -> !fir.ref<!fir.box<!fir.heap<f32>>>
567! CHECK:           %[[VAL_10:.*]]:2 = hlfir.declare %[[VAL_9]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_simple_allocEx"} : (!fir.ref<!fir.box<!fir.heap<f32>>>) -> (!fir.ref<!fir.box<!fir.heap<f32>>>, !fir.ref<!fir.box<!fir.heap<f32>>>)
568! CHECK:           fir.call @_QPra0(%[[VAL_10]]#0) fastmath<contract> : (!fir.ref<!fir.box<!fir.heap<f32>>>) -> ()
569! CHECK:           cf.br ^bb5
570! CHECK:         ^bb3:
571! CHECK:           %[[VAL_11:.*]]:2 = hlfir.declare %[[VAL_2]]#0 {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_simple_allocEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>>)
572! CHECK:           fir.call @_QPradefault(%[[VAL_11]]#0) fastmath<contract> : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>>) -> ()
573! CHECK:           cf.br ^bb5
574! CHECK:         ^bb4:
575! CHECK:           %[[VAL_12:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:f32>>>>) -> !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>
576! CHECK:           %[[VAL_13:.*]]:2 = hlfir.declare %[[VAL_12]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_simple_allocEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>)
577! CHECK:           fir.call @_QPra1(%[[VAL_13]]#0) fastmath<contract> : (!fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>) -> ()
578! CHECK:           cf.br ^bb5
579! CHECK:         ^bb5:
580! CHECK:           return
581! CHECK:         }
582
583! CHECK-LABEL:   func.func @_QPtest_character_alloc(
584! CHECK-SAME:                                       %[[VAL_0:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>> {fir.bindc_name = "x"}) {
585! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
586! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_1]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_character_allocEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>, !fir.dscope) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>)
587! CHECK:           %[[VAL_3:.*]] = arith.constant 1 : i8
588! CHECK:           %[[VAL_4:.*]] = fir.box_rank %[[VAL_2]]#0 : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>) -> i8
589! CHECK:           fir.select_case %[[VAL_4]] : i8 [#fir.point, %[[VAL_3]], ^bb2, unit, ^bb1]
590! CHECK:         ^bb1:
591! CHECK:           %[[VAL_5:.*]]:2 = hlfir.declare %[[VAL_2]]#0 {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_character_allocEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>)
592! CHECK:           cf.br ^bb3
593! CHECK:         ^bb2:
594! CHECK:           %[[VAL_6:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>) -> !fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>>
595! CHECK:           %[[VAL_7:.*]] = fir.load %[[VAL_2]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>
596! CHECK:           %[[VAL_8:.*]] = fir.box_elesize %[[VAL_7]] : (!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>) -> index
597! CHECK:           %[[VAL_9:.*]]:2 = hlfir.declare %[[VAL_6]] typeparams %[[VAL_8]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_character_allocEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>>, index) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.char<1,?>>>>>)
598! CHECK:           cf.br ^bb3
599! CHECK:         ^bb3:
600! CHECK:           return
601! CHECK:         }
602
603! CHECK-LABEL:   func.func @_QPtest_explicit_character_ptr(
604! CHECK-SAME:                                              %[[VAL_0:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>> {fir.bindc_name = "x"},
605! CHECK-SAME:                                              %[[VAL_1:.*]]: !fir.ref<i64> {fir.bindc_name = "n"}) {
606! CHECK:           %[[VAL_2:.*]] = fir.dummy_scope : !fir.dscope
607! CHECK:           %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_1]] dummy_scope %[[VAL_2]] {uniq_name = "_QFtest_explicit_character_ptrEn"} : (!fir.ref<i64>, !fir.dscope) -> (!fir.ref<i64>, !fir.ref<i64>)
608! CHECK:           %[[VAL_4:.*]] = fir.load %[[VAL_3]]#0 : !fir.ref<i64>
609! CHECK:           %[[VAL_5:.*]] = arith.constant 0 : i64
610! CHECK:           %[[VAL_6:.*]] = arith.cmpi sgt, %[[VAL_4]], %[[VAL_5]] : i64
611! CHECK:           %[[VAL_7:.*]] = arith.select %[[VAL_6]], %[[VAL_4]], %[[VAL_5]] : i64
612! CHECK:           %[[VAL_8:.*]]:2 = hlfir.declare %[[VAL_0]] typeparams %[[VAL_7]] dummy_scope %[[VAL_2]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_explicit_character_ptrEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>, i64, !fir.dscope) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>)
613! CHECK:           %[[VAL_9:.*]] = arith.constant 0 : i8
614! CHECK:           %[[VAL_10:.*]] = fir.box_rank %[[VAL_8]]#0 : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>) -> i8
615! CHECK:           fir.select_case %[[VAL_10]] : i8 [#fir.point, %[[VAL_9]], ^bb2, unit, ^bb1]
616! CHECK:         ^bb1:
617! CHECK:           %[[VAL_11:.*]]:2 = hlfir.declare %[[VAL_8]]#0 typeparams %[[VAL_7]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_explicit_character_ptrEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>, i64) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>)
618! CHECK:           cf.br ^bb3
619! CHECK:         ^bb2:
620! CHECK:           %[[VAL_12:.*]] = fir.convert %[[VAL_8]]#0 : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>) -> !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>
621! CHECK:           %[[VAL_13:.*]]:2 = hlfir.declare %[[VAL_12]] typeparams %[[VAL_7]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_explicit_character_ptrEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, i64) -> (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>)
622! CHECK:           cf.br ^bb3
623! CHECK:         ^bb3:
624! CHECK:           return
625! CHECK:         }
626
627! CHECK-LABEL:   func.func @_QPtest_assumed_character_ptr(
628! CHECK-SAME:                                             %[[VAL_0:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>> {fir.bindc_name = "x"}) {
629! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
630! CHECK:           %[[VAL_2:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>
631! CHECK:           %[[VAL_3:.*]] = fir.box_elesize %[[VAL_2]] : (!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>) -> index
632! CHECK:           %[[VAL_4:.*]]:2 = hlfir.declare %[[VAL_0]] typeparams %[[VAL_3]] dummy_scope %[[VAL_1]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_assumed_character_ptrEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>, index, !fir.dscope) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>)
633! CHECK:           %[[VAL_5:.*]] = arith.constant 0 : i8
634! CHECK:           %[[VAL_6:.*]] = fir.box_rank %[[VAL_4]]#0 : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>) -> i8
635! CHECK:           fir.select_case %[[VAL_6]] : i8 [#fir.point, %[[VAL_5]], ^bb2, unit, ^bb1]
636! CHECK:         ^bb1:
637! CHECK:           %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_4]]#0 typeparams %[[VAL_3]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_assumed_character_ptrEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>, index) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>)
638! CHECK:           cf.br ^bb3
639! CHECK:         ^bb2:
640! CHECK:           %[[VAL_8:.*]] = fir.convert %[[VAL_4]]#0 : (!fir.ref<!fir.box<!fir.heap<!fir.array<*:!fir.char<1,?>>>>>) -> !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>
641! CHECK:           %[[VAL_9:.*]]:2 = hlfir.declare %[[VAL_8]] typeparams %[[VAL_3]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFtest_assumed_character_ptrEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, index) -> (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>)
642! CHECK:           cf.br ^bb3
643! CHECK:         ^bb3:
644! CHECK:           return
645! CHECK:         }
646
647! CHECK-LABEL:   func.func @_QPtest_polymorphic(
648! CHECK-SAME:                                   %[[VAL_0:.*]]: !fir.class<!fir.array<*:none>> {fir.bindc_name = "x"}) {
649! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
650! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_1]] {uniq_name = "_QFtest_polymorphicEx"} : (!fir.class<!fir.array<*:none>>, !fir.dscope) -> (!fir.class<!fir.array<*:none>>, !fir.class<!fir.array<*:none>>)
651! CHECK:           %[[VAL_3:.*]] = arith.constant 1 : i8
652! CHECK:           %[[VAL_4:.*]] = arith.constant 0 : i8
653! CHECK:           %[[VAL_5:.*]] = fir.is_assumed_size %[[VAL_2]]#0 : (!fir.class<!fir.array<*:none>>) -> i1
654! CHECK:           cf.cond_br %[[VAL_5]], ^bb3, ^bb1
655! CHECK:         ^bb1:
656! CHECK:           %[[VAL_6:.*]] = fir.box_rank %[[VAL_2]]#0 : (!fir.class<!fir.array<*:none>>) -> i8
657! CHECK:           fir.select_case %[[VAL_6]] : i8 [#fir.point, %[[VAL_3]], ^bb2, #fir.point, %[[VAL_4]], ^bb4, unit, ^bb3]
658! CHECK:         ^bb2:
659! CHECK:           %[[VAL_7:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.class<!fir.array<*:none>>) -> !fir.class<!fir.array<?xnone>>
660! CHECK:           %[[VAL_8:.*]]:2 = hlfir.declare %[[VAL_7]] {uniq_name = "_QFtest_polymorphicEx"} : (!fir.class<!fir.array<?xnone>>) -> (!fir.class<!fir.array<?xnone>>, !fir.class<!fir.array<?xnone>>)
661! CHECK:           fir.call @_QPrup1(%[[VAL_8]]#0) fastmath<contract> : (!fir.class<!fir.array<?xnone>>) -> ()
662! CHECK:           cf.br ^bb5
663! CHECK:         ^bb3:
664! CHECK:           %[[VAL_9:.*]]:2 = hlfir.declare %[[VAL_2]]#0 {uniq_name = "_QFtest_polymorphicEx"} : (!fir.class<!fir.array<*:none>>) -> (!fir.class<!fir.array<*:none>>, !fir.class<!fir.array<*:none>>)
665! CHECK:           fir.call @_QPrupdefault(%[[VAL_9]]#0) fastmath<contract> : (!fir.class<!fir.array<*:none>>) -> ()
666! CHECK:           cf.br ^bb5
667! CHECK:         ^bb4:
668! CHECK:           %[[VAL_10:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.class<!fir.array<*:none>>) -> !fir.class<none>
669! CHECK:           %[[VAL_11:.*]]:2 = hlfir.declare %[[VAL_10]] {uniq_name = "_QFtest_polymorphicEx"} : (!fir.class<none>) -> (!fir.class<none>, !fir.class<none>)
670! CHECK:           fir.call @_QPrup0(%[[VAL_11]]#0) fastmath<contract> : (!fir.class<none>) -> ()
671! CHECK:           cf.br ^bb5
672! CHECK:         ^bb5:
673! CHECK:           return
674! CHECK:         }
675
676! CHECK-LABEL:   func.func @_QPtest_nested_select_rank(
677! CHECK-SAME:                                          %[[VAL_0:.*]]: !fir.box<!fir.array<*:f32>> {fir.bindc_name = "x1"},
678! CHECK-SAME:                                          %[[VAL_1:.*]]: !fir.box<!fir.array<*:f32>> {fir.bindc_name = "x2"}) {
679! CHECK:           %[[VAL_2:.*]] = fir.dummy_scope : !fir.dscope
680! CHECK:           %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_2]] {uniq_name = "_QFtest_nested_select_rankEx1"} : (!fir.box<!fir.array<*:f32>>, !fir.dscope) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
681! CHECK:           %[[VAL_4:.*]]:2 = hlfir.declare %[[VAL_1]] dummy_scope %[[VAL_2]] {uniq_name = "_QFtest_nested_select_rankEx2"} : (!fir.box<!fir.array<*:f32>>, !fir.dscope) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
682! CHECK:           %[[VAL_5:.*]] = arith.constant 0 : i8
683! CHECK:           %[[VAL_6:.*]] = arith.constant 1 : i8
684! CHECK:           %[[VAL_7:.*]] = fir.is_assumed_size %[[VAL_3]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
685! CHECK:           cf.cond_br %[[VAL_7]], ^bb14, ^bb1
686! CHECK:         ^bb1:
687! CHECK:           %[[VAL_8:.*]] = fir.box_rank %[[VAL_3]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
688! CHECK:           fir.select_case %[[VAL_8]] : i8 [#fir.point, %[[VAL_5]], ^bb2, #fir.point, %[[VAL_6]], ^bb8, unit, ^bb14]
689! CHECK:         ^bb2:
690! CHECK:           %[[VAL_9:.*]] = fir.convert %[[VAL_3]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<f32>
691! CHECK:           %[[VAL_10:.*]] = fir.box_addr %[[VAL_9]] : (!fir.box<f32>) -> !fir.ref<f32>
692! CHECK:           %[[VAL_11:.*]]:2 = hlfir.declare %[[VAL_10]] {uniq_name = "_QFtest_nested_select_rankEx1"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
693! CHECK:           %[[VAL_12:.*]] = arith.constant 0 : i8
694! CHECK:           %[[VAL_13:.*]] = arith.constant 1 : i8
695! CHECK:           %[[VAL_14:.*]] = fir.is_assumed_size %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
696! CHECK:           cf.cond_br %[[VAL_14]], ^bb6, ^bb3
697! CHECK:         ^bb3:
698! CHECK:           %[[VAL_15:.*]] = fir.box_rank %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
699! CHECK:           fir.select_case %[[VAL_15]] : i8 [#fir.point, %[[VAL_12]], ^bb4, #fir.point, %[[VAL_13]], ^bb5, unit, ^bb6]
700! CHECK:         ^bb4:
701! CHECK:           %[[VAL_16:.*]] = fir.convert %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<f32>
702! CHECK:           %[[VAL_17:.*]] = fir.box_addr %[[VAL_16]] : (!fir.box<f32>) -> !fir.ref<f32>
703! CHECK:           %[[VAL_18:.*]]:2 = hlfir.declare %[[VAL_17]] {uniq_name = "_QFtest_nested_select_rankEx2"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
704! CHECK:           fir.call @_QPr0(%[[VAL_11]]#1) fastmath<contract> : (!fir.ref<f32>) -> ()
705! CHECK:           fir.call @_QPr0(%[[VAL_18]]#1) fastmath<contract> : (!fir.ref<f32>) -> ()
706! CHECK:           cf.br ^bb7
707! CHECK:         ^bb5:
708! CHECK:           %[[VAL_19:.*]] = fir.convert %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?xf32>>
709! CHECK:           %[[VAL_20:.*]]:2 = hlfir.declare %[[VAL_19]] {uniq_name = "_QFtest_nested_select_rankEx2"} : (!fir.box<!fir.array<?xf32>>) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>)
710! CHECK:           fir.call @_QPr0(%[[VAL_11]]#1) fastmath<contract> : (!fir.ref<f32>) -> ()
711! CHECK:           fir.call @_QPr1(%[[VAL_20]]#0) fastmath<contract> : (!fir.box<!fir.array<?xf32>>) -> ()
712! CHECK:           cf.br ^bb7
713! CHECK:         ^bb6:
714! CHECK:           %[[VAL_21:.*]]:2 = hlfir.declare %[[VAL_4]]#0 {uniq_name = "_QFtest_nested_select_rankEx2"} : (!fir.box<!fir.array<*:f32>>) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
715! CHECK:           fir.call @_QPr0(%[[VAL_11]]#1) fastmath<contract> : (!fir.ref<f32>) -> ()
716! CHECK:           fir.call @_QPrdefault(%[[VAL_21]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
717! CHECK:           cf.br ^bb7
718! CHECK:         ^bb7:
719! CHECK:           cf.br ^bb20
720! CHECK:         ^bb8:
721! CHECK:           %[[VAL_22:.*]] = fir.convert %[[VAL_3]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?xf32>>
722! CHECK:           %[[VAL_23:.*]]:2 = hlfir.declare %[[VAL_22]] {uniq_name = "_QFtest_nested_select_rankEx1"} : (!fir.box<!fir.array<?xf32>>) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>)
723! CHECK:           %[[VAL_24:.*]] = arith.constant 0 : i8
724! CHECK:           %[[VAL_25:.*]] = arith.constant 1 : i8
725! CHECK:           %[[VAL_26:.*]] = fir.is_assumed_size %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
726! CHECK:           cf.cond_br %[[VAL_26]], ^bb12, ^bb9
727! CHECK:         ^bb9:
728! CHECK:           %[[VAL_27:.*]] = fir.box_rank %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
729! CHECK:           fir.select_case %[[VAL_27]] : i8 [#fir.point, %[[VAL_24]], ^bb10, #fir.point, %[[VAL_25]], ^bb11, unit, ^bb12]
730! CHECK:         ^bb10:
731! CHECK:           %[[VAL_28:.*]] = fir.convert %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<f32>
732! CHECK:           %[[VAL_29:.*]] = fir.box_addr %[[VAL_28]] : (!fir.box<f32>) -> !fir.ref<f32>
733! CHECK:           %[[VAL_30:.*]]:2 = hlfir.declare %[[VAL_29]] {uniq_name = "_QFtest_nested_select_rankEx2"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
734! CHECK:           fir.call @_QPr1(%[[VAL_23]]#0) fastmath<contract> : (!fir.box<!fir.array<?xf32>>) -> ()
735! CHECK:           fir.call @_QPr0(%[[VAL_30]]#1) fastmath<contract> : (!fir.ref<f32>) -> ()
736! CHECK:           cf.br ^bb13
737! CHECK:         ^bb11:
738! CHECK:           %[[VAL_31:.*]] = fir.convert %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?xf32>>
739! CHECK:           %[[VAL_32:.*]]:2 = hlfir.declare %[[VAL_31]] {uniq_name = "_QFtest_nested_select_rankEx2"} : (!fir.box<!fir.array<?xf32>>) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>)
740! CHECK:           fir.call @_QPr1(%[[VAL_23]]#0) fastmath<contract> : (!fir.box<!fir.array<?xf32>>) -> ()
741! CHECK:           fir.call @_QPr1(%[[VAL_32]]#0) fastmath<contract> : (!fir.box<!fir.array<?xf32>>) -> ()
742! CHECK:           cf.br ^bb13
743! CHECK:         ^bb12:
744! CHECK:           %[[VAL_33:.*]]:2 = hlfir.declare %[[VAL_4]]#0 {uniq_name = "_QFtest_nested_select_rankEx2"} : (!fir.box<!fir.array<*:f32>>) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
745! CHECK:           fir.call @_QPr1(%[[VAL_23]]#0) fastmath<contract> : (!fir.box<!fir.array<?xf32>>) -> ()
746! CHECK:           fir.call @_QPrdefault(%[[VAL_33]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
747! CHECK:           cf.br ^bb13
748! CHECK:         ^bb13:
749! CHECK:           cf.br ^bb20
750! CHECK:         ^bb14:
751! CHECK:           %[[VAL_34:.*]]:2 = hlfir.declare %[[VAL_3]]#0 {uniq_name = "_QFtest_nested_select_rankEx1"} : (!fir.box<!fir.array<*:f32>>) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
752! CHECK:           %[[VAL_35:.*]] = arith.constant 0 : i8
753! CHECK:           %[[VAL_36:.*]] = arith.constant 1 : i8
754! CHECK:           %[[VAL_37:.*]] = fir.is_assumed_size %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
755! CHECK:           cf.cond_br %[[VAL_37]], ^bb18, ^bb15
756! CHECK:         ^bb15:
757! CHECK:           %[[VAL_38:.*]] = fir.box_rank %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
758! CHECK:           fir.select_case %[[VAL_38]] : i8 [#fir.point, %[[VAL_35]], ^bb16, #fir.point, %[[VAL_36]], ^bb17, unit, ^bb18]
759! CHECK:         ^bb16:
760! CHECK:           %[[VAL_39:.*]] = fir.convert %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<f32>
761! CHECK:           %[[VAL_40:.*]] = fir.box_addr %[[VAL_39]] : (!fir.box<f32>) -> !fir.ref<f32>
762! CHECK:           %[[VAL_41:.*]]:2 = hlfir.declare %[[VAL_40]] {uniq_name = "_QFtest_nested_select_rankEx2"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
763! CHECK:           fir.call @_QPrdefault(%[[VAL_34]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
764! CHECK:           fir.call @_QPr0(%[[VAL_41]]#1) fastmath<contract> : (!fir.ref<f32>) -> ()
765! CHECK:           cf.br ^bb19
766! CHECK:         ^bb17:
767! CHECK:           %[[VAL_42:.*]] = fir.convert %[[VAL_4]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?xf32>>
768! CHECK:           %[[VAL_43:.*]]:2 = hlfir.declare %[[VAL_42]] {uniq_name = "_QFtest_nested_select_rankEx2"} : (!fir.box<!fir.array<?xf32>>) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>)
769! CHECK:           fir.call @_QPrdefault(%[[VAL_34]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
770! CHECK:           fir.call @_QPr1(%[[VAL_43]]#0) fastmath<contract> : (!fir.box<!fir.array<?xf32>>) -> ()
771! CHECK:           cf.br ^bb19
772! CHECK:         ^bb18:
773! CHECK:           %[[VAL_44:.*]]:2 = hlfir.declare %[[VAL_4]]#0 {uniq_name = "_QFtest_nested_select_rankEx2"} : (!fir.box<!fir.array<*:f32>>) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
774! CHECK:           fir.call @_QPrdefault(%[[VAL_34]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
775! CHECK:           fir.call @_QPrdefault(%[[VAL_44]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
776! CHECK:           cf.br ^bb19
777! CHECK:         ^bb19:
778! CHECK:           cf.br ^bb20
779! CHECK:         ^bb20:
780! CHECK:           return
781! CHECK:         }
782
783! CHECK-LABEL:   func.func @_QPtest_branching(
784! CHECK-SAME:                                 %[[VAL_0:.*]]: !fir.box<!fir.array<*:f32>> {fir.bindc_name = "x"}) {
785! CHECK:           %[[VAL_1:.*]] = fir.dummy_scope : !fir.dscope
786! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %[[VAL_1]] {uniq_name = "_QFtest_branchingEx"} : (!fir.box<!fir.array<*:f32>>, !fir.dscope) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
787! CHECK:           %[[VAL_3:.*]] = arith.constant 1 : i8
788! CHECK:           %[[VAL_4:.*]] = arith.constant 2 : i8
789! CHECK:           %[[VAL_5:.*]] = fir.is_assumed_size %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i1
790! CHECK:           cf.cond_br %[[VAL_5]], ^bb1, ^bb2
791! CHECK:         ^bb1:
792! CHECK:           %[[VAL_6:.*]]:2 = hlfir.declare %[[VAL_2]]#0 {uniq_name = "_QFtest_branchingEx"} : (!fir.box<!fir.array<*:f32>>) -> (!fir.box<!fir.array<*:f32>>, !fir.box<!fir.array<*:f32>>)
793! CHECK:           %[[VAL_7:.*]] = fir.call @_QPjump() fastmath<contract> : () -> !fir.logical<4>
794! CHECK:           %[[VAL_8:.*]] = fir.convert %[[VAL_7]] : (!fir.logical<4>) -> i1
795! CHECK:           %[[VAL_9:.*]] = arith.constant true
796! CHECK:           %[[VAL_10:.*]] = arith.xori %[[VAL_8]], %[[VAL_9]] : i1
797! CHECK:           fir.if %[[VAL_10]] {
798! CHECK:             fir.call @_QPone() fastmath<contract> : () -> ()
799! CHECK:           }
800! CHECK:           fir.call @_QPrdefault(%[[VAL_6]]#0) fastmath<contract> : (!fir.box<!fir.array<*:f32>>) -> ()
801! CHECK:           cf.br ^bb7
802! CHECK:         ^bb2:
803! CHECK:           %[[VAL_11:.*]] = fir.box_rank %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> i8
804! CHECK:           fir.select_case %[[VAL_11]] : i8 [#fir.point, %[[VAL_3]], ^bb3, #fir.point, %[[VAL_4]], ^bb6, unit, ^bb1]
805! CHECK:         ^bb3:
806! CHECK:           %[[VAL_12:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?xf32>>
807! CHECK:           %[[VAL_13:.*]]:2 = hlfir.declare %[[VAL_12]] {uniq_name = "_QFtest_branchingEx"} : (!fir.box<!fir.array<?xf32>>) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>)
808! CHECK:           %[[VAL_14:.*]] = fir.call @_QPleave_now() fastmath<contract> : () -> !fir.logical<4>
809! CHECK:           %[[VAL_15:.*]] = fir.convert %[[VAL_14]] : (!fir.logical<4>) -> i1
810! CHECK:           cf.cond_br %[[VAL_15]], ^bb4, ^bb5
811! CHECK:         ^bb4:
812! CHECK:           cf.br ^bb8
813! CHECK:         ^bb5:
814! CHECK:           fir.call @_QPr1(%[[VAL_13]]#0) fastmath<contract> : (!fir.box<!fir.array<?xf32>>) -> ()
815! CHECK:           cf.br ^bb7
816! CHECK:         ^bb6:
817! CHECK:           %[[VAL_16:.*]] = fir.convert %[[VAL_2]]#0 : (!fir.box<!fir.array<*:f32>>) -> !fir.box<!fir.array<?x?xf32>>
818! CHECK:           %[[VAL_17:.*]]:2 = hlfir.declare %[[VAL_16]] {uniq_name = "_QFtest_branchingEx"} : (!fir.box<!fir.array<?x?xf32>>) -> (!fir.box<!fir.array<?x?xf32>>, !fir.box<!fir.array<?x?xf32>>)
819! CHECK:           cf.br ^bb7
820! CHECK:         ^bb7:
821! CHECK:           cf.br ^bb8
822! CHECK:         ^bb8:
823! CHECK:           fir.call @_QPthe_end() fastmath<contract> : () -> ()
824! CHECK:           return
825! CHECK:         }
826