llvm-project

Форк
0
/
dispatch.f90 
338 строк · 16.7 Кб
1
! RUN: bbc -emit-hlfir %s -o - | fir-opt --fir-polymorphic-op | FileCheck %s
2
! RUN: bbc -emit-hlfir %s -o - | FileCheck %s --check-prefix=BT
3

4
! Tests codegen of fir.dispatch operation. This test is intentionally run from
5
! Fortran through bbc and tco so we have all the binding tables lowered to FIR
6
! from semantics.
7

8
module dispatch1
9

10
  type p1
11
    integer :: a
12
    integer :: b
13
  contains
14
    procedure :: aproc
15
    procedure :: display1 => display1_p1
16
    procedure :: display2 => display2_p1
17
    procedure :: get_value => get_value_p1
18
    procedure :: proc_with_values => proc_p1
19
    procedure, nopass :: proc_nopass => proc_nopass_p1
20
    procedure, pass(this) :: proc_pass => proc_pass_p1
21
  end type
22

23
  type, extends(p1) :: p2
24
    integer :: c
25
  contains
26
    procedure :: display1 => display1_p2
27
    procedure :: display2 => display2_p2
28
    procedure :: display3
29
    procedure :: get_value => get_value_p2
30
    procedure :: proc_with_values => proc_p2
31
    procedure, nopass :: proc_nopass => proc_nopass_p2
32
    procedure, pass(this) :: proc_pass => proc_pass_p2
33
  end type
34

35
  type, abstract :: a1
36
    integer a
37
  contains
38
    procedure :: a1_proc
39
  end type
40

41
  type, extends(a1) :: a2
42
    integer b
43
  contains
44
    procedure :: a1_proc => a2_proc
45
  end type
46

47
  type ty_kind(i, j)
48
    integer, kind :: i, j
49
    integer :: a(i)
50
  end Type
51

52
  type, extends(ty_kind) :: ty_kind_ex
53
    integer :: b(j)
54
  end type
55
  type(ty_kind(10,20)) :: tk1
56
  type(ty_kind_ex(10,20)) :: tke1
57
contains
58

59
  subroutine display1_p1(this)
60
    class(p1) :: this
61
    print*,'call display1_p1'
62
  end subroutine
63

64
  subroutine display2_p1(this)
65
    class(p1) :: this
66
    print*,'call display2_p1'
67
  end subroutine
68

69
  subroutine display1_p2(this)
70
    class(p2) :: this
71
    print*,'call display1_p2'
72
  end subroutine
73

74
  subroutine display2_p2(this)
75
    class(p2) :: this
76
    print*,'call display2_p2'
77
  end subroutine
78

79
  subroutine aproc(this)
80
    class(p1) :: this
81
    print*,'call aproc'
82
  end subroutine
83

84
  subroutine display3(this)
85
    class(p2) :: this
86
    print*,'call display3'
87
  end subroutine
88

89
  function get_value_p1(this)
90
    class(p1) :: this
91
    integer :: get_value_p1
92
    get_value_p1 = 10
93
  end function
94

95
  function get_value_p2(this)
96
    class(p2) :: this
97
    integer :: get_value_p2
98
    get_value_p2 = 10
99
  end function
100

101
  subroutine proc_p1(this, v)
102
    class(p1) :: this
103
    real :: v
104
    print*, 'call proc1 with ', v
105
  end subroutine
106

107
  subroutine proc_p2(this, v)
108
    class(p2) :: this
109
    real :: v
110
    print*, 'call proc1 with ', v
111
  end subroutine
112

113
  subroutine proc_nopass_p1()
114
    print*, 'call proc_nopass_p1'
115
  end subroutine
116

117
  subroutine proc_nopass_p2()
118
    print*, 'call proc_nopass_p2'
119
  end subroutine
120

121
  subroutine proc_pass_p1(i, this)
122
    integer :: i
123
    class(p1) :: this
124
    print*, 'call proc_nopass_p1'
125
  end subroutine
126

127
  subroutine proc_pass_p2(i, this)
128
    integer :: i
129
    class(p2) :: this
130
    print*, 'call proc_nopass_p2'
131
  end subroutine
132

133
  subroutine display_class(p)
134
    class(p1) :: p
135
    integer :: i
136
    call p%display2()
137
    call p%display1()
138
    call p%aproc()
139
    i = p%get_value()
140
    call p%proc_with_values(2.5)
141
    call p%proc_nopass()
142
    call p%proc_pass(1)
143
  end subroutine
144

145
  subroutine no_pass_array(a)
146
    class(p1) :: a(:)
147
    call a(1)%proc_nopass()
148
  end subroutine
149

150
  subroutine no_pass_array_allocatable(a)
151
    class(p1), allocatable :: a(:)
152
    call a(1)%proc_nopass()
153
  end subroutine
154

155
  subroutine no_pass_array_pointer(a)
156
    class(p1), allocatable :: a(:)
157
    call a(1)%proc_nopass()
158
  end subroutine
159

160
  subroutine a1_proc(this)
161
    class(a1) :: this
162
  end subroutine
163

164
  subroutine a2_proc(this)
165
    class(a2) :: this
166
  end subroutine
167

168
  subroutine call_a1_proc(p)
169
    class(a1), pointer :: p
170
    call p%a1_proc()
171
  end subroutine
172

173
end module
174

175
program test_type_to_class
176
  use dispatch1
177
  type(p1) :: t1 = p1(1,2)
178
  type(p2) :: t2 = p2(1,2,3)
179

180
  call display_class(t1)
181
  call display_class(t2)
182
end
183

184

185
! CHECK-LABEL: func.func @_QMdispatch1Pdisplay_class(
186
! CHECK-SAME: %[[ARG:.*]]: [[CLASS:!fir.class<.*>>]]
187
! CHECK: %[[ARG_DECL:.*]]:2 = hlfir.declare %[[ARG]] dummy_scope %{{[0-9]+}} {uniq_name = "_QMdispatch1Fdisplay_classEp"} : (!fir.class<!fir.type<_QMdispatch1Tp1{a:i32,b:i32}>>, !fir.dscope) -> (!fir.class<!fir.type<_QMdispatch1Tp1{a:i32,b:i32}>>, !fir.class<!fir.type<_QMdispatch1Tp1{a:i32,b:i32}>>)
188

189
! Check dynamic dispatch equal to `call p%display2()` with binding index = 2.
190
! CHECK: %[[BOXDESC:.*]] = fir.box_tdesc %[[ARG_DECL]]#0 : ([[CLASS]]) -> !fir.tdesc<none>
191
! CHECK: %[[TYPEDESCPTR:.*]] = fir.convert %[[BOXDESC]] : (!fir.tdesc<none>) -> !fir.ref<[[TYPEINFO:!fir.type<_QM__fortran_type_infoTderivedtype{.*}>]]>
192
! CHECK: %[[BINDING_FIELD:.*]] = fir.field_index binding, [[TYPEINFO]]
193
! CHECK: %[[BINDING_BOX_ADDR:.*]] =  fir.coordinate_of %[[TYPEDESCPTR]], %[[BINDING_FIELD]] : (!fir.ref<[[TYPEINFO]]>, !fir.field) -> !fir.ref<[[BINDING_BOX_TYPE:.*]]>
194
! CHECK: %[[BINDING_BOX:.*]] = fir.load %[[BINDING_BOX_ADDR]] : !fir.ref<[[BINDING_BOX_TYPE]]>
195
! CHECK: %[[BINDING_BASE_ADDR:.*]] = fir.box_addr %[[BINDING_BOX]] : ([[BINDING_BOX_TYPE]]) -> !fir.ptr<[[BINDINGSINFO:.*]]>
196
! CHECK: %[[BINDING_PTR:.*]] = fir.coordinate_of %[[BINDING_BASE_ADDR]], %c2{{.*}} : (!fir.ptr<[[BINDINGSINFO]]>, index) -> !fir.ref<[[BINDINGINFO:.*]]>
197
! CHECK: %[[PROC_FIELD:.*]] = fir.field_index proc, [[BINDINGINFO]]
198
! CHECK: %[[BUILTIN_FUNC_PTR:.*]] = fir.coordinate_of %[[BINDING_PTR]], %[[PROC_FIELD]] : ({{.*}}) -> !fir.ref<[[BUILTIN_FUNC_TYPE:.*]]>
199
! CHECK: %[[ADDRESS_FIELD:.*]] = fir.field_index __address, [[BUILTIN_FUNC_TYPE]]
200
! CHECK: %[[FUNC_ADDR_PTR:.*]] = fir.coordinate_of %[[BUILTIN_FUNC_PTR]], %[[ADDRESS_FIELD]]
201
! CHECK: %[[FUNC_ADDR:.*]] = fir.load %[[FUNC_ADDR_PTR]] : !fir.ref<i64>
202
! CHECK: %[[FUNC_PTR:.*]] = fir.convert %[[FUNC_ADDR]] : (i64) -> (([[CLASS]]) -> ())
203
! CHECK: fir.call %[[FUNC_PTR]](%[[ARG_DECL]]#0) : (!fir.class<!fir.type<_QMdispatch1Tp1{a:i32,b:i32}>>) -> ()
204

205
! Check dynamic dispatch equal to `call p%display1()` with binding index = 1.
206
! CHECK: %[[BOXDESC:.*]] = fir.box_tdesc %[[ARG_DECL]]#0 : ([[CLASS]]) -> !fir.tdesc<none>
207
! CHECK: %[[TYPEDESCPTR:.*]] = fir.convert %[[BOXDESC]] : (!fir.tdesc<none>) -> !fir.ref<[[TYPEINFO:!fir.type<_QM__fortran_type_infoTderivedtype{.*}>]]>
208
! CHECK: %[[BINDING_FIELD:.*]] = fir.field_index binding, [[TYPEINFO]]
209
! CHECK: %[[BINDING_BOX_ADDR:.*]] =  fir.coordinate_of %[[TYPEDESCPTR]], %[[BINDING_FIELD]] : (!fir.ref<[[TYPEINFO]]>, !fir.field) -> !fir.ref<[[BINDING_BOX_TYPE:.*]]>
210
! CHECK: %[[BINDING_BOX:.*]] = fir.load %[[BINDING_BOX_ADDR]] : !fir.ref<[[BINDING_BOX_TYPE]]>
211
! CHECK: %[[BINDING_BASE_ADDR:.*]] = fir.box_addr %[[BINDING_BOX]] : ([[BINDING_BOX_TYPE]]) -> !fir.ptr<[[BINDINGSINFO:.*]]>
212
! CHECK: %[[BINDING_PTR:.*]] = fir.coordinate_of %[[BINDING_BASE_ADDR]], %c1{{.*}} : (!fir.ptr<[[BINDINGSINFO]]>, index) -> !fir.ref<[[BINDINGINFO:.*]]>
213
! CHECK: %[[PROC_FIELD:.*]] = fir.field_index proc, [[BINDINGINFO]]
214
! CHECK: %[[BUILTIN_FUNC_PTR:.*]] = fir.coordinate_of %[[BINDING_PTR]], %[[PROC_FIELD]] : ({{.*}}) -> !fir.ref<[[BUILTIN_FUNC_TYPE:.*]]>
215
! CHECK: %[[ADDRESS_FIELD:.*]] = fir.field_index __address, [[BUILTIN_FUNC_TYPE]]
216
! CHECK: %[[FUNC_ADDR_PTR:.*]] = fir.coordinate_of %[[BUILTIN_FUNC_PTR]], %[[ADDRESS_FIELD]]
217
! CHECK: %[[FUNC_ADDR:.*]] = fir.load %[[FUNC_ADDR_PTR]] : !fir.ref<i64>
218
! CHECK: %[[FUNC_PTR:.*]] = fir.convert %[[FUNC_ADDR]] : (i64) -> (([[CLASS]]) -> ())
219
! CHECK: fir.call %[[FUNC_PTR]](%[[ARG_DECL]]#0) : (!fir.class<!fir.type<_QMdispatch1Tp1{a:i32,b:i32}>>) -> ()
220

221
! Check dynamic dispatch equal to `call p%aproc()` with binding index = 0.
222
! CHECK: %[[BOXDESC:.*]] = fir.box_tdesc %[[ARG_DECL]]#0 : ([[CLASS]]) -> !fir.tdesc<none>
223
! CHECK: %[[TYPEDESCPTR:.*]] = fir.convert %[[BOXDESC]] : (!fir.tdesc<none>) -> !fir.ref<[[TYPEINFO:!fir.type<_QM__fortran_type_infoTderivedtype{.*}>]]>
224
! CHECK: %[[BINDING_FIELD:.*]] = fir.field_index binding, [[TYPEINFO]]
225
! CHECK: %[[BINDING_BOX_ADDR:.*]] =  fir.coordinate_of %[[TYPEDESCPTR]], %[[BINDING_FIELD]] : (!fir.ref<[[TYPEINFO]]>, !fir.field) -> !fir.ref<[[BINDING_BOX_TYPE:.*]]>
226
! CHECK: %[[BINDING_BOX:.*]] = fir.load %[[BINDING_BOX_ADDR]] : !fir.ref<[[BINDING_BOX_TYPE]]>
227
! CHECK: %[[BINDING_BASE_ADDR:.*]] = fir.box_addr %[[BINDING_BOX]] : ([[BINDING_BOX_TYPE]]) -> !fir.ptr<[[BINDINGSINFO:.*]]>
228
! CHECK: %[[BINDING_PTR:.*]] = fir.coordinate_of %[[BINDING_BASE_ADDR]], %c0{{.*}}: (!fir.ptr<[[BINDINGSINFO]]>, index) -> !fir.ref<[[BINDINGINFO:.*]]>
229
! CHECK: %[[PROC_FIELD:.*]] = fir.field_index proc, [[BINDINGINFO]]
230
! CHECK: %[[BUILTIN_FUNC_PTR:.*]] = fir.coordinate_of %[[BINDING_PTR]], %[[PROC_FIELD]] : ({{.*}}) -> !fir.ref<[[BUILTIN_FUNC_TYPE:.*]]>
231
! CHECK: %[[ADDRESS_FIELD:.*]] = fir.field_index __address, [[BUILTIN_FUNC_TYPE]]
232
! CHECK: %[[FUNC_ADDR_PTR:.*]] = fir.coordinate_of %[[BUILTIN_FUNC_PTR]], %[[ADDRESS_FIELD]]
233
! CHECK: %[[FUNC_ADDR:.*]] = fir.load %[[FUNC_ADDR_PTR]] : !fir.ref<i64>
234
! CHECK: %[[FUNC_PTR:.*]] = fir.convert %[[FUNC_ADDR]] : (i64) -> (([[CLASS]]) -> ())
235
! CHECK: fir.call %[[FUNC_PTR]](%[[ARG_DECL]]#0) : (!fir.class<!fir.type<_QMdispatch1Tp1{a:i32,b:i32}>>) -> ()
236

237
! Check dynamic dispatch of a function with result.
238
! CHECK: %[[BOXDESC:.*]] = fir.box_tdesc %[[ARG_DECL]]#0 : ([[CLASS]]) -> !fir.tdesc<none>
239
! CHECK: %[[TYPEDESCPTR:.*]] = fir.convert %[[BOXDESC]] : (!fir.tdesc<none>) -> !fir.ref<[[TYPEINFO:!fir.type<_QM__fortran_type_infoTderivedtype{.*}>]]>
240
! CHECK: %[[BINDING_FIELD:.*]] = fir.field_index binding, [[TYPEINFO]]
241
! CHECK: %[[BINDING_BOX_ADDR:.*]] =  fir.coordinate_of %[[TYPEDESCPTR]], %[[BINDING_FIELD]] : (!fir.ref<[[TYPEINFO]]>, !fir.field) -> !fir.ref<[[BINDING_BOX_TYPE:.*]]>
242
! CHECK: %[[BINDING_BOX:.*]] = fir.load %[[BINDING_BOX_ADDR]] : !fir.ref<[[BINDING_BOX_TYPE]]>
243
! CHECK: %[[BINDING_BASE_ADDR:.*]] = fir.box_addr %[[BINDING_BOX]] : ([[BINDING_BOX_TYPE]]) -> !fir.ptr<[[BINDINGSINFO:.*]]>
244
! CHECK: %[[BINDING_PTR:.*]] = fir.coordinate_of %[[BINDING_BASE_ADDR]], %c3 : (!fir.ptr<[[BINDINGSINFO]]>, index) -> !fir.ref<[[BINDINGINFO:.*]]>
245
! CHECK: %[[PROC_FIELD:.*]] = fir.field_index proc, [[BINDINGINFO]]
246
! CHECK: %[[BUILTIN_FUNC_PTR:.*]] = fir.coordinate_of %[[BINDING_PTR]], %[[PROC_FIELD]] : ({{.*}}) -> !fir.ref<[[BUILTIN_FUNC_TYPE:.*]]>
247
! CHECK: %[[ADDRESS_FIELD:.*]] = fir.field_index __address, [[BUILTIN_FUNC_TYPE]]
248
! CHECK: %[[FUNC_ADDR_PTR:.*]] = fir.coordinate_of %[[BUILTIN_FUNC_PTR]], %[[ADDRESS_FIELD]]
249
! CHECK: %[[FUNC_ADDR:.*]] = fir.load %[[FUNC_ADDR_PTR]] : !fir.ref<i64>
250
! CHECK: %[[FUNC_PTR:.*]] = fir.convert %[[FUNC_ADDR]] : (i64) -> (([[CLASS]]) -> i32)
251
! CHECK: %[[RES:.*]] = fir.call %[[FUNC_PTR]](%[[ARG_DECL]]#0) : (!fir.class<!fir.type<_QMdispatch1Tp1{a:i32,b:i32}>>) -> i32
252

253
! Check dynamic dispatch of call with passed-object and additional argument
254
! CHECK: %[[BOXDESC:.*]] = fir.box_tdesc %[[ARG_DECL]]#0 : ([[CLASS]]) -> !fir.tdesc<none>
255
! CHECK: %[[TYPEDESCPTR:.*]] = fir.convert %[[BOXDESC]] : (!fir.tdesc<none>) -> !fir.ref<[[TYPEINFO:!fir.type<_QM__fortran_type_infoTderivedtype{.*}>]]>
256
! CHECK: %[[BINDING_FIELD:.*]] = fir.field_index binding, [[TYPEINFO]]
257
! CHECK: %[[BINDING_BOX_ADDR:.*]] =  fir.coordinate_of %[[TYPEDESCPTR]], %[[BINDING_FIELD]] : (!fir.ref<[[TYPEINFO]]>, !fir.field) -> !fir.ref<[[BINDING_BOX_TYPE:.*]]>
258
! CHECK: %[[BINDING_BOX:.*]] = fir.load %[[BINDING_BOX_ADDR]] : !fir.ref<[[BINDING_BOX_TYPE]]>
259
! CHECK: %[[BINDING_BASE_ADDR:.*]] = fir.box_addr %[[BINDING_BOX]] : ([[BINDING_BOX_TYPE]]) -> !fir.ptr<[[BINDINGSINFO:.*]]>
260
! CHECK: %[[BINDING_PTR:.*]] = fir.coordinate_of %[[BINDING_BASE_ADDR]], %c6{{.*}} : (!fir.ptr<[[BINDINGSINFO]]>, index) -> !fir.ref<[[BINDINGINFO:.*]]>
261
! CHECK: %[[PROC_FIELD:.*]] = fir.field_index proc, [[BINDINGINFO]]
262
! CHECK: %[[BUILTIN_FUNC_PTR:.*]] = fir.coordinate_of %[[BINDING_PTR]], %[[PROC_FIELD]] : ({{.*}}) -> !fir.ref<[[BUILTIN_FUNC_TYPE:.*]]>
263
! CHECK: %[[ADDRESS_FIELD:.*]] = fir.field_index __address, [[BUILTIN_FUNC_TYPE]]
264
! CHECK: %[[FUNC_ADDR_PTR:.*]] = fir.coordinate_of %[[BUILTIN_FUNC_PTR]], %[[ADDRESS_FIELD]]
265
! CHECK: %[[FUNC_ADDR:.*]] = fir.load %[[FUNC_ADDR_PTR]] : !fir.ref<i64>
266
! CHECK: %[[FUNC_PTR:.*]] = fir.convert %[[FUNC_ADDR]] : (i64) -> (([[CLASS]], !fir.ref<f32>) -> ())
267
! CHECK: fir.call %[[FUNC_PTR]](%[[ARG_DECL]]#0, %{{.*}}) : (!fir.class<!fir.type<_QMdispatch1Tp1{a:i32,b:i32}>>, !fir.ref<f32>) -> ()
268

269
! Check dynamic dispatch of a call with NOPASS
270
! CHECK: %[[BOXDESC:.*]] = fir.box_tdesc %[[ARG_DECL]]#1 : ([[CLASS]]) -> !fir.tdesc<none>
271
! CHECK: %[[TYPEDESCPTR:.*]] = fir.convert %[[BOXDESC]] : (!fir.tdesc<none>) -> !fir.ref<[[TYPEINFO:!fir.type<_QM__fortran_type_infoTderivedtype{.*}>]]>
272
! CHECK: %[[BINDING_FIELD:.*]] = fir.field_index binding, [[TYPEINFO]]
273
! CHECK: %[[BINDING_BOX_ADDR:.*]] =  fir.coordinate_of %[[TYPEDESCPTR]], %[[BINDING_FIELD]] : (!fir.ref<[[TYPEINFO]]>, !fir.field) -> !fir.ref<[[BINDING_BOX_TYPE:.*]]>
274
! CHECK: %[[BINDING_BOX:.*]] = fir.load %[[BINDING_BOX_ADDR]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?x!fir.type<{{.*}}>>>>>
275
! CHECK: %[[BINDING_BASE_ADDR:.*]] = fir.box_addr %[[BINDING_BOX]] : (!fir.box<!fir.ptr<!fir.array<?x!fir.type<{{.*}}>>>
276
! CHECK: %[[BINDING_PTR:.*]] = fir.coordinate_of %[[BINDING_BASE_ADDR]], %c4{{.*}} :  (!fir.ptr<!fir.array<?x!fir.type<{{.*}}>>>, index) -> !fir.ref<!fir.type<{{.*}}>>
277
! CHECK: %[[PROC_FIELD:.*]] = fir.field_index proc, [[BINDINGINFO]]
278
! CHECK: %[[BUILTIN_FUNC_PTR:.*]] = fir.coordinate_of %[[BINDING_PTR]], %[[PROC_FIELD]] : ({{.*}}) -> !fir.ref<[[BUILTIN_FUNC_TYPE:.*]]>
279
! CHECK: %[[ADDRESS_FIELD:.*]] = fir.field_index __address, [[BUILTIN_FUNC_TYPE]]
280
! CHECK: %[[FUNC_ADDR_PTR:.*]] = fir.coordinate_of %[[BUILTIN_FUNC_PTR]], %[[ADDRESS_FIELD]]
281
! CHECK: %[[FUNC_ADDR:.*]] = fir.load %[[FUNC_ADDR_PTR]] : !fir.ref<i64>
282
! CHECK: %[[FUNC_PTR:.*]] = fir.convert %[[FUNC_ADDR]] : (i64) -> (() -> ())
283
! CHECK: fir.call %[[FUNC_PTR]]() : () -> ()
284

285
! CHECK: %[[BOXDESC:.*]] = fir.box_tdesc %[[ARG_DECL]]#0 : ([[CLASS]]) -> !fir.tdesc<none>
286
! CHECK: %[[TYPEDESCPTR:.*]] = fir.convert %[[BOXDESC]] : (!fir.tdesc<none>) -> !fir.ref<[[TYPEINFO:!fir.type<_QM__fortran_type_infoTderivedtype{.*}>]]>
287
! CHECK: %[[BINDING_FIELD:.*]] = fir.field_index binding, [[TYPEINFO]]
288
! CHECK: %[[BINDING_BOX_ADDR:.*]] =  fir.coordinate_of %[[TYPEDESCPTR]], %[[BINDING_FIELD]] : (!fir.ref<[[TYPEINFO]]>, !fir.field) -> !fir.ref<[[BINDING_BOX_TYPE:.*]]>
289
! CHECK: %[[BINDING_BOX:.*]] = fir.load %[[BINDING_BOX_ADDR]] : !fir.ref<[[BINDING_BOX_TYPE]]>
290
! CHECK: %[[BINDING_BASE_ADDR:.*]] = fir.box_addr %[[BINDING_BOX]] : ([[BINDING_BOX_TYPE]]) -> !fir.ptr<[[BINDINGSINFO:.*]]>
291
! CHECK: %[[BINDING_PTR:.*]] = fir.coordinate_of %[[BINDING_BASE_ADDR]], %c5{{.*}} : (!fir.ptr<[[BINDINGSINFO]]>, index) -> !fir.ref<[[BINDINGINFO:.*]]>
292
! CHECK: %[[PROC_FIELD:.*]] = fir.field_index proc, [[BINDINGINFO]]
293
! CHECK: %[[BUILTIN_FUNC_PTR:.*]] = fir.coordinate_of %[[BINDING_PTR]], %[[PROC_FIELD]] : ({{.*}}) -> !fir.ref<[[BUILTIN_FUNC_TYPE:.*]]>
294
! CHECK: %[[ADDRESS_FIELD:.*]] = fir.field_index __address, [[BUILTIN_FUNC_TYPE]]
295
! CHECK: %[[FUNC_ADDR_PTR:.*]] = fir.coordinate_of %[[BUILTIN_FUNC_PTR]], %[[ADDRESS_FIELD]]
296
! CHECK: %[[FUNC_ADDR:.*]] = fir.load %[[FUNC_ADDR_PTR]] : !fir.ref<i64>
297
! CHECK: %[[FUNC_PTR:.*]] = fir.convert %[[FUNC_ADDR]] : (i64) -> ((!fir.ref<i32>, [[CLASS]]) -> ())
298
! CHECK: fir.call %[[FUNC_PTR]](%{{.*}}, %[[ARG_DECL]]#0) : (!fir.ref<i32>, [[CLASS]]) -> ()
299

300
! CHECK-LABEL: _QMdispatch1Pno_pass_array
301
! CHECK-LABEL: _QMdispatch1Pno_pass_array_allocatable
302
! CHECK-LABEL: _QMdispatch1Pno_pass_array_pointer
303
! CHECK-LABEL: _QMdispatch1Pcall_a1_proc
304

305
! Check the layout of the binding table. This is easier to do in FIR than in 
306
! LLVM IR.
307

308
! BT-LABEL: fir.type_info @_QMdispatch1Tty_kindK10K20
309
! BT-LABEL: fir.type_info @_QMdispatch1Tty_kind_exK10K20 {{.*}}extends !fir.type<_QMdispatch1Tty_kindK10K20{{.*}}>
310

311
! BT-LABEL: fir.type_info @_QMdispatch1Tp1
312
! BT: fir.dt_entry "aproc", @_QMdispatch1Paproc
313
! BT: fir.dt_entry "display1", @_QMdispatch1Pdisplay1_p1
314
! BT: fir.dt_entry "display2", @_QMdispatch1Pdisplay2_p1
315
! BT: fir.dt_entry "get_value", @_QMdispatch1Pget_value_p1
316
! BT: fir.dt_entry "proc_nopass", @_QMdispatch1Pproc_nopass_p1
317
! BT: fir.dt_entry "proc_pass", @_QMdispatch1Pproc_pass_p1
318
! BT: fir.dt_entry "proc_with_values", @_QMdispatch1Pproc_p1
319
! BT: }
320

321
! BT-LABEL: fir.type_info @_QMdispatch1Ta1
322
! BT: fir.dt_entry "a1_proc", @_QMdispatch1Pa1_proc
323
! BT: }
324

325
! BT-LABEL: fir.type_info @_QMdispatch1Ta2 {{.*}}extends !fir.type<_QMdispatch1Ta1{{.*}}>
326
! BT:  fir.dt_entry "a1_proc", @_QMdispatch1Pa2_proc
327
! BT: }
328

329
! BT-LABEL: fir.type_info @_QMdispatch1Tp2 {{.*}}extends !fir.type<_QMdispatch1Tp1{{.*}}>
330
! BT:  fir.dt_entry "aproc", @_QMdispatch1Paproc
331
! BT:  fir.dt_entry "display1", @_QMdispatch1Pdisplay1_p2
332
! BT:  fir.dt_entry "display2", @_QMdispatch1Pdisplay2_p2
333
! BT:  fir.dt_entry "get_value", @_QMdispatch1Pget_value_p2
334
! BT:  fir.dt_entry "proc_nopass", @_QMdispatch1Pproc_nopass_p2
335
! BT:  fir.dt_entry "proc_pass", @_QMdispatch1Pproc_pass_p2
336
! BT:  fir.dt_entry "proc_with_values", @_QMdispatch1Pproc_p2
337
! BT:  fir.dt_entry "display3", @_QMdispatch1Pdisplay3
338
! BT: }
339

Использование cookies

Мы используем файлы cookie в соответствии с Политикой конфиденциальности и Политикой использования cookies.

Нажимая кнопку «Принимаю», Вы даете АО «СберТех» согласие на обработку Ваших персональных данных в целях совершенствования нашего веб-сайта и Сервиса GitVerse, а также повышения удобства их использования.

Запретить использование cookies Вы можете самостоятельно в настройках Вашего браузера.