Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Lower / procedure-declarations.f90
blob9a407c894c5c17be72e1f0dfaa21ee630024feee
1 ! RUN: bbc -emit-fir %s -o - | FileCheck %s
3 ! Test procedure declarations. Change appearance order of definition and usages
4 ! (passing a procedure and calling it), with and without definitions.
5 ! Check that the definition type prevail if available and that casts are inserted to
6 ! accommodate for the signature mismatch in the different location due to implicit
7 ! typing rules and Fortran loose interface compatibility rule history.
10 ! Note: all the cases where their is a definition are exactly the same,
11 ! since definition should be processed first regardless.
13 ! pass, call, define
14 ! CHECK-LABEL: func @_QPpass_foo() {
15 subroutine pass_foo()
16 external :: foo
17 ! CHECK: %[[f:.*]] = fir.address_of(@_QPfoo)
18 ! CHECK: fir.emboxproc %[[f]] : ((!fir.ref<!fir.array<2x5xi32>>) -> ()) -> !fir.boxproc<() -> ()>
19 call bar(foo)
20 end subroutine
21 ! CHECK-LABEL: func @_QPcall_foo(
22 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<10xi32>>{{.*}}) {
23 subroutine call_foo(i)
24 integer :: i(10)
25 ! %[[argconvert:*]] = fir.convert %arg0 :
26 ! fir.call @_QPfoo(%[[argconvert]]) {{.*}}: (!fir.ref<!fir.array<2x5xi32>>) -> ()
27 call foo(i)
28 end subroutine
29 ! CHECK-LABEL: func @_QPfoo(
30 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<2x5xi32>>{{.*}}) {
31 subroutine foo(i)
32 integer :: i(2, 5)
33 call do_something(i)
34 end subroutine
36 ! call, pass, define
37 ! CHECK-LABEL: func @_QPcall_foo2(
38 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<10xi32>>{{.*}}) {
39 subroutine call_foo2(i)
40 integer :: i(10)
41 ! %[[argconvert:*]] = fir.convert %arg0 :
42 ! fir.call @_QPfoo2(%[[argconvert]]) {{.*}}: (!fir.ref<!fir.array<2x5xi32>>) -> ()
43 call foo2(i)
44 end subroutine
45 ! CHECK-LABEL: func @_QPpass_foo2() {
46 subroutine pass_foo2()
47 external :: foo2
48 ! CHECK: %[[f:.*]] = fir.address_of(@_QPfoo2)
49 ! CHECK: fir.emboxproc %[[f]] : ((!fir.ref<!fir.array<2x5xi32>>) -> ()) -> !fir.boxproc<() -> ()>
50 call bar(foo2)
51 end subroutine
52 ! CHECK-LABEL: func @_QPfoo2(
53 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<2x5xi32>>{{.*}}) {
54 subroutine foo2(i)
55 integer :: i(2, 5)
56 call do_something(i)
57 end subroutine
59 ! call, define, pass
60 ! CHECK-LABEL: func @_QPcall_foo3(
61 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<10xi32>>{{.*}}) {
62 subroutine call_foo3(i)
63 integer :: i(10)
64 ! %[[argconvert:*]] = fir.convert %arg0 :
65 ! fir.call @_QPfoo3(%[[argconvert]]) {{.*}}: (!fir.ref<!fir.array<2x5xi32>>) -> ()
66 call foo3(i)
67 end subroutine
68 ! CHECK-LABEL: func @_QPfoo3(
69 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<2x5xi32>>{{.*}}) {
70 subroutine foo3(i)
71 integer :: i(2, 5)
72 call do_something(i)
73 end subroutine
74 ! CHECK-LABEL: func @_QPpass_foo3() {
75 subroutine pass_foo3()
76 external :: foo3
77 ! CHECK: %[[f:.*]] = fir.address_of(@_QPfoo3)
78 ! CHECK: fir.emboxproc %[[f]] : ((!fir.ref<!fir.array<2x5xi32>>) -> ()) -> !fir.boxproc<() -> ()>
79 call bar(foo3)
80 end subroutine
82 ! define, call, pass
83 ! CHECK-LABEL: func @_QPfoo4(
84 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<2x5xi32>>{{.*}}) {
85 subroutine foo4(i)
86 integer :: i(2, 5)
87 call do_something(i)
88 end subroutine
89 ! CHECK-LABEL: func @_QPcall_foo4(
90 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<10xi32>>{{.*}}) {
91 subroutine call_foo4(i)
92 integer :: i(10)
93 ! %[[argconvert:*]] = fir.convert %arg0 :
94 ! fir.call @_QPfoo4(%[[argconvert]]) {{.*}}: (!fir.ref<!fir.array<2x5xi32>>) -> ()
95 call foo4(i)
96 end subroutine
97 ! CHECK-LABEL: func @_QPpass_foo4() {
98 subroutine pass_foo4()
99 external :: foo4
100 ! CHECK: %[[f:.*]] = fir.address_of(@_QPfoo4)
101 ! CHECK: fir.emboxproc %[[f]] : ((!fir.ref<!fir.array<2x5xi32>>) -> ()) -> !fir.boxproc<() -> ()>
102 call bar(foo4)
103 end subroutine
105 ! define, pass, call
106 ! CHECK-LABEL: func @_QPfoo5(
107 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<2x5xi32>>{{.*}}) {
108 subroutine foo5(i)
109 integer :: i(2, 5)
110 call do_something(i)
111 end subroutine
112 ! CHECK-LABEL: func @_QPpass_foo5() {
113 subroutine pass_foo5()
114 external :: foo5
115 ! CHECK: %[[f:.*]] = fir.address_of(@_QPfoo5)
116 ! CHECK: fir.emboxproc %[[f]] : ((!fir.ref<!fir.array<2x5xi32>>) -> ()) -> !fir.boxproc<() -> ()>
117 call bar(foo5)
118 end subroutine
119 ! CHECK-LABEL: func @_QPcall_foo5(
120 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<10xi32>>{{.*}}) {
121 subroutine call_foo5(i)
122 integer :: i(10)
123 ! %[[argconvert:*]] = fir.convert %arg0 :
124 ! fir.call @_QPfoo5(%[[argconvert]]) {{.*}}: (!fir.ref<!fir.array<2x5xi32>>) -> ()
125 call foo5(i)
126 end subroutine
129 ! Test when there is no definition (declaration at the end of the mlir module)
130 ! First use gives the function type
132 ! call, pass
133 ! CHECK-LABEL: func @_QPcall_foo6(
134 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<10xi32>>{{.*}}) {
135 subroutine call_foo6(i)
136 integer :: i(10)
137 ! CHECK-NOT: convert
138 call foo6(i)
139 end subroutine
140 ! CHECK-LABEL: func @_QPpass_foo6() {
141 subroutine pass_foo6()
142 external :: foo6
143 ! CHECK: %[[f:.*]] = fir.address_of(@_QPfoo6) : (!fir.ref<!fir.array<10xi32>>) -> ()
144 ! CHECK: fir.emboxproc %[[f]] : ((!fir.ref<!fir.array<10xi32>>) -> ()) -> !fir.boxproc<() -> ()>
145 call bar(foo6)
146 end subroutine
148 ! pass, call
149 ! CHECK-LABEL: func @_QPpass_foo7() {
150 subroutine pass_foo7()
151 external :: foo7
152 ! CHECK-NOT: convert
153 call bar(foo7)
154 end subroutine
155 ! CHECK-LABEL: func @_QPcall_foo7(
156 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<10xi32>>{{.*}}) -> f32 {
157 function call_foo7(i)
158 integer :: i(10)
159 ! CHECK: %[[f:.*]] = fir.address_of(@_QPfoo7) : () -> ()
160 ! CHECK: %[[funccast:.*]] = fir.convert %[[f]] : (() -> ()) -> ((!fir.ref<!fir.array<10xi32>>) -> f32)
161 ! CHECK: fir.call %[[funccast]](%arg0) {{.*}}: (!fir.ref<!fir.array<10xi32>>) -> f32
162 call_foo7 = foo7(i)
163 end function
166 ! call, call with different type
167 ! CHECK-LABEL: func @_QPcall_foo8(
168 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<10xi32>>{{.*}}) {
169 subroutine call_foo8(i)
170 integer :: i(10)
171 ! CHECK-NOT: convert
172 call foo8(i)
173 end subroutine
174 ! CHECK-LABEL: func @_QPcall_foo8_2(
175 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<2x5xi32>>{{.*}}) {
176 subroutine call_foo8_2(i)
177 integer :: i(2, 5)
178 ! %[[argconvert:*]] = fir.convert %arg0 :
179 call foo8(i)
180 end subroutine
182 ! Test that target attribute is lowered in declaration of functions that are
183 ! not defined in this file.
184 ! CHECK-LABEL:func @_QPtest_target_in_iface
185 subroutine test_target_in_iface()
186 interface
187 subroutine test_target(i, x)
188 integer, target :: i
189 real, target :: x(:)
190 end subroutine
191 end interface
192 integer :: i
193 real :: x(10)
194 ! CHECK: fir.call @_QPtest_target
195 call test_target(i, x)
196 end subroutine
198 ! CHECK: func private @_QPfoo6(!fir.ref<!fir.array<10xi32>>)
199 ! CHECK: func private @_QPfoo7()
201 ! Test declaration from test_target_in_iface
202 ! CHECK-LABEL: func private @_QPtest_target(!fir.ref<i32> {fir.target}, !fir.box<!fir.array<?xf32>> {fir.target})