[Clang] Make OpenMP offloading consistently use the bound architecture (#125135)
[llvm-project.git] / flang / test / Lower / HLFIR / assumed-rank-iface.f90
blob0e094cc6646d1f4e1e5c7c43124eb0539f0cae23
1 ! Test lowering of calls to interface with non pointer non allocatable
2 ! assumed rank dummy arguments.
3 ! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
5 module ifaces
6 interface
7 subroutine int_assumed_rank(y)
8 integer :: y(..)
9 end subroutine
10 subroutine int_opt_assumed_rank(y)
11 integer, optional :: y(..)
12 end subroutine
13 subroutine int_assumed_rank_bindc(y) bind(c)
14 integer :: y(..)
15 end subroutine
16 end interface
17 end module
19 subroutine int_scalar_to_assumed_rank(x)
20 use ifaces, only : int_assumed_rank
21 integer :: x
22 call int_assumed_rank(x)
23 end subroutine
24 ! CHECK-LABEL: func.func @_QPint_scalar_to_assumed_rank(
25 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<i32> {fir.bindc_name = "x"}) {
26 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %{{[0-9]+}} {uniq_name = "_QFint_scalar_to_assumed_rankEx"} : (!fir.ref<i32>, !fir.dscope) -> (!fir.ref<i32>, !fir.ref<i32>)
27 ! CHECK: %[[VAL_2:.*]] = fir.embox %[[VAL_1]]#0 : (!fir.ref<i32>) -> !fir.box<i32>
28 ! CHECK: %[[VAL_3:.*]] = fir.convert %[[VAL_2]] : (!fir.box<i32>) -> !fir.box<!fir.array<*:i32>>
29 ! CHECK: fir.call @_QPint_assumed_rank(%[[VAL_3]]) fastmath<contract> : (!fir.box<!fir.array<*:i32>>) -> ()
31 subroutine int_scalar_to_assumed_rank_bindc(x)
32 use ifaces, only : int_assumed_rank_bindc
33 integer :: x
34 call int_assumed_rank_bindc(x)
35 end subroutine
36 ! CHECK-LABEL: func.func @_QPint_scalar_to_assumed_rank_bindc(
37 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<i32> {fir.bindc_name = "x"}) {
38 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %{{[0-9]+}} {uniq_name = "_QFint_scalar_to_assumed_rank_bindcEx"} : (!fir.ref<i32>, !fir.dscope) -> (!fir.ref<i32>, !fir.ref<i32>)
39 ! CHECK: %[[VAL_2:.*]] = fir.embox %[[VAL_1]]#0 : (!fir.ref<i32>) -> !fir.box<i32>
40 ! CHECK: %[[VAL_3:.*]] = fir.convert %[[VAL_2]] : (!fir.box<i32>) -> !fir.box<!fir.array<*:i32>>
41 ! CHECK: fir.call @int_assumed_rank_bindc(%[[VAL_3]]) proc_attrs<bind_c> fastmath<contract> : (!fir.box<!fir.array<*:i32>>) -> ()
43 subroutine int_r1_to_assumed_rank(x)
44 use ifaces, only : int_assumed_rank
45 integer :: x(10)
46 call int_assumed_rank(x)
47 end subroutine
48 ! CHECK-LABEL: func.func @_QPint_r1_to_assumed_rank(
49 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.array<10xi32>> {fir.bindc_name = "x"}) {
50 ! CHECK: %[[VAL_1:.*]] = arith.constant 10 : index
51 ! CHECK: %[[VAL_2:.*]] = fir.shape %[[VAL_1]] : (index) -> !fir.shape<1>
52 ! CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_0]](%[[VAL_2]]) dummy_scope %{{[0-9]+}} {uniq_name = "_QFint_r1_to_assumed_rankEx"} : (!fir.ref<!fir.array<10xi32>>, !fir.shape<1>, !fir.dscope) -> (!fir.ref<!fir.array<10xi32>>, !fir.ref<!fir.array<10xi32>>)
53 ! CHECK: %[[VAL_4:.*]] = fir.embox %[[VAL_3]]#0(%[[VAL_2]]) : (!fir.ref<!fir.array<10xi32>>, !fir.shape<1>) -> !fir.box<!fir.array<10xi32>>
54 ! CHECK: %[[VAL_5:.*]] = fir.convert %[[VAL_4]] : (!fir.box<!fir.array<10xi32>>) -> !fir.box<!fir.array<*:i32>>
55 ! CHECK: fir.call @_QPint_assumed_rank(%[[VAL_5]]) fastmath<contract> : (!fir.box<!fir.array<*:i32>>) -> ()
57 subroutine int_r4_to_assumed_rank(x)
58 use ifaces, only : int_assumed_rank
59 integer :: x(2,3,4,5)
60 call int_assumed_rank(x)
61 end subroutine
62 ! CHECK-LABEL: func.func @_QPint_r4_to_assumed_rank(
63 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.array<2x3x4x5xi32>> {fir.bindc_name = "x"}) {
64 ! CHECK: %[[VAL_1:.*]] = arith.constant 2 : index
65 ! CHECK: %[[VAL_2:.*]] = arith.constant 3 : index
66 ! CHECK: %[[VAL_3:.*]] = arith.constant 4 : index
67 ! CHECK: %[[VAL_4:.*]] = arith.constant 5 : index
68 ! CHECK: %[[VAL_5:.*]] = fir.shape %[[VAL_1]], %[[VAL_2]], %[[VAL_3]], %[[VAL_4]] : (index, index, index, index) -> !fir.shape<4>
69 ! CHECK: %[[VAL_6:.*]]:2 = hlfir.declare %[[VAL_0]](%[[VAL_5]]) dummy_scope %{{[0-9]+}} {uniq_name = "_QFint_r4_to_assumed_rankEx"} : (!fir.ref<!fir.array<2x3x4x5xi32>>, !fir.shape<4>, !fir.dscope) -> (!fir.ref<!fir.array<2x3x4x5xi32>>, !fir.ref<!fir.array<2x3x4x5xi32>>)
70 ! CHECK: %[[VAL_7:.*]] = fir.embox %[[VAL_6]]#0(%[[VAL_5]]) : (!fir.ref<!fir.array<2x3x4x5xi32>>, !fir.shape<4>) -> !fir.box<!fir.array<2x3x4x5xi32>>
71 ! CHECK: %[[VAL_8:.*]] = fir.convert %[[VAL_7]] : (!fir.box<!fir.array<2x3x4x5xi32>>) -> !fir.box<!fir.array<*:i32>>
72 ! CHECK: fir.call @_QPint_assumed_rank(%[[VAL_8]]) fastmath<contract> : (!fir.box<!fir.array<*:i32>>) -> ()
74 subroutine int_assumed_shape_to_assumed_rank(x)
75 use ifaces, only : int_assumed_rank
76 integer :: x(:, :)
77 call int_assumed_rank(x)
78 end subroutine
79 ! CHECK-LABEL: func.func @_QPint_assumed_shape_to_assumed_rank(
80 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.box<!fir.array<?x?xi32>> {fir.bindc_name = "x"}) {
81 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %{{[0-9]+}} {uniq_name = "_QFint_assumed_shape_to_assumed_rankEx"} : (!fir.box<!fir.array<?x?xi32>>, !fir.dscope) -> (!fir.box<!fir.array<?x?xi32>>, !fir.box<!fir.array<?x?xi32>>)
82 ! CHECK: %[[VAL_2:.*]] = fir.convert %[[VAL_1]]#0 : (!fir.box<!fir.array<?x?xi32>>) -> !fir.box<!fir.array<*:i32>>
83 ! CHECK: fir.call @_QPint_assumed_rank(%[[VAL_2]]) fastmath<contract> : (!fir.box<!fir.array<*:i32>>) -> ()
85 subroutine int_assumed_shape_to_assumed_rank_bindc(x)
86 use ifaces, only : int_assumed_rank_bindc
87 integer :: x(:, :)
88 call int_assumed_rank_bindc(x)
89 end subroutine
90 ! CHECK-LABEL: func.func @_QPint_assumed_shape_to_assumed_rank_bindc(
91 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.box<!fir.array<?x?xi32>> {fir.bindc_name = "x"}) {
92 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %{{[0-9]+}} {uniq_name = "_QFint_assumed_shape_to_assumed_rank_bindcEx"} : (!fir.box<!fir.array<?x?xi32>>, !fir.dscope) -> (!fir.box<!fir.array<?x?xi32>>, !fir.box<!fir.array<?x?xi32>>)
93 ! CHECK: %[[VAL_2:.*]] = arith.constant 0 : index
94 ! CHECK: %[[VAL_3:.*]] = fir.shift %[[VAL_2]], %[[VAL_2]] : (index, index) -> !fir.shift<2>
95 ! CHECK: %[[VAL_4:.*]] = fir.rebox %[[VAL_1]]#0(%[[VAL_3]]) : (!fir.box<!fir.array<?x?xi32>>, !fir.shift<2>) -> !fir.box<!fir.array<?x?xi32>>
96 ! CHECK: %[[VAL_5:.*]] = fir.convert %[[VAL_4]] : (!fir.box<!fir.array<?x?xi32>>) -> !fir.box<!fir.array<*:i32>>
97 ! CHECK: fir.call @int_assumed_rank_bindc(%[[VAL_5]]) proc_attrs<bind_c> fastmath<contract> : (!fir.box<!fir.array<*:i32>>) -> ()
99 subroutine int_allocatable_to_assumed_rank(x)
100 use ifaces, only : int_assumed_rank
101 integer, allocatable :: x(:, :)
102 call int_assumed_rank(x)
103 end subroutine
104 ! CHECK-LABEL: func.func @_QPint_allocatable_to_assumed_rank(
105 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>> {fir.bindc_name = "x"}) {
106 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %{{[0-9]+}} {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFint_allocatable_to_assumed_rankEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>>, !fir.dscope) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>>)
107 ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>>
108 ! CHECK: %[[VAL_3:.*]] = fir.rebox %[[VAL_2]] : (!fir.box<!fir.heap<!fir.array<?x?xi32>>>) -> !fir.box<!fir.array<?x?xi32>>
109 ! CHECK: %[[VAL_4:.*]] = fir.convert %[[VAL_3]] : (!fir.box<!fir.array<?x?xi32>>) -> !fir.box<!fir.array<*:i32>>
110 ! CHECK: fir.call @_QPint_assumed_rank(%[[VAL_4]]) fastmath<contract> : (!fir.box<!fir.array<*:i32>>) -> ()
112 subroutine int_allocatable_to_assumed_rank_opt(x)
113 use ifaces, only : int_opt_assumed_rank
114 integer, allocatable :: x(:, :)
115 call int_opt_assumed_rank(x)
116 end subroutine
117 ! CHECK-LABEL: func.func @_QPint_allocatable_to_assumed_rank_opt(
118 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>> {fir.bindc_name = "x"}) {
119 ! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %{{[0-9]+}} {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFint_allocatable_to_assumed_rank_optEx"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>>, !fir.dscope) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>>)
120 ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>>
121 ! CHECK: %[[VAL_3:.*]] = fir.box_addr %[[VAL_2]] : (!fir.box<!fir.heap<!fir.array<?x?xi32>>>) -> !fir.heap<!fir.array<?x?xi32>>
122 ! CHECK: %[[VAL_4:.*]] = fir.convert %[[VAL_3]] : (!fir.heap<!fir.array<?x?xi32>>) -> i64
123 ! CHECK: %[[VAL_5:.*]] = arith.constant 0 : i64
124 ! CHECK: %[[VAL_6:.*]] = arith.cmpi ne, %[[VAL_4]], %[[VAL_5]] : i64
125 ! CHECK: %[[VAL_7:.*]] = fir.if %[[VAL_6]] -> (!fir.box<!fir.array<?x?xi32>>) {
126 ! CHECK: %[[VAL_8:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>>
127 ! CHECK: %[[VAL_9:.*]] = fir.rebox %[[VAL_8]] : (!fir.box<!fir.heap<!fir.array<?x?xi32>>>) -> !fir.box<!fir.array<?x?xi32>>
128 ! CHECK: fir.result %[[VAL_9]] : !fir.box<!fir.array<?x?xi32>>
129 ! CHECK: } else {
130 ! CHECK: %[[VAL_10:.*]] = fir.absent !fir.box<!fir.array<?x?xi32>>
131 ! CHECK: fir.result %[[VAL_10]] : !fir.box<!fir.array<?x?xi32>>
132 ! CHECK: }
133 ! CHECK: %[[VAL_11:.*]] = fir.convert %[[VAL_7]] : (!fir.box<!fir.array<?x?xi32>>) -> !fir.box<!fir.array<*:i32>>
134 ! CHECK: fir.call @_QPint_opt_assumed_rank(%[[VAL_11]]) fastmath<contract> : (!fir.box<!fir.array<*:i32>>) -> ()
136 subroutine int_r2_assumed_size_to_assumed_rank(x)
137 use ifaces, only : int_assumed_rank
138 integer :: x(10, *)
139 call int_assumed_rank(x)
140 end subroutine
141 ! CHECK-LABEL: func.func @_QPint_r2_assumed_size_to_assumed_rank(
142 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.array<10x?xi32>> {fir.bindc_name = "x"}) {
143 ! CHECK: %[[VAL_1:.*]] = arith.constant 10 : i64
144 ! CHECK: %[[VAL_2:.*]] = fir.convert %[[VAL_1]] : (i64) -> index
145 ! CHECK: %[[VAL_3:.*]] = arith.constant 0 : index
146 ! CHECK: %[[VAL_4:.*]] = arith.cmpi sgt, %[[VAL_2]], %[[VAL_3]] : index
147 ! CHECK: %[[VAL_5:.*]] = arith.select %[[VAL_4]], %[[VAL_2]], %[[VAL_3]] : index
148 ! CHECK: %[[VAL_6:.*]] = arith.constant -1 : index
149 ! CHECK: %[[VAL_7:.*]] = fir.shape %[[VAL_5]], %[[VAL_6]] : (index, index) -> !fir.shape<2>
150 ! CHECK: %[[VAL_8:.*]]:2 = hlfir.declare %[[VAL_0]](%[[VAL_7]]) dummy_scope %{{[0-9]+}} {uniq_name = "_QFint_r2_assumed_size_to_assumed_rankEx"} : (!fir.ref<!fir.array<10x?xi32>>, !fir.shape<2>, !fir.dscope) -> (!fir.box<!fir.array<10x?xi32>>, !fir.ref<!fir.array<10x?xi32>>)
151 ! CHECK: %[[VAL_9:.*]] = fir.convert %[[VAL_8]]#0 : (!fir.box<!fir.array<10x?xi32>>) -> !fir.box<!fir.array<*:i32>>
152 ! CHECK: fir.call @_QPint_assumed_rank(%[[VAL_9]]) fastmath<contract> : (!fir.box<!fir.array<*:i32>>) -> ()