[XCOFF] make related SD symbols as isFunction (#69553)
[llvm-project.git] / flang / docs / ProcedurePointer.md
blobda4848ff197bdcd8f05fe7af1e8e7bfe7a8952f3
1 <!--===- docs/ProcedurePointer.md
3    Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4    See https://llvm.org/LICENSE.txt for license information.
5    SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
7 -->
9 # Procedure Pointer
11 A procedure pointer is a procedure that has the EXTERNAL and POINTER attributes.
13 This document summarizes what of context the procedure pointers should appear,
14 and how they are lowered to FIR.
16 The current plan is to use/extend the `BoxedProcedure` pass for the conversion
17 to LLVM IR, and thus will not be lowering the procedure-pointer-related
18 operations to LLVM IR in `CodeGen.cpp`.
20 ## Fortran standard
22 Here is a list of the sections and constraints of the Fortran standard involved
23 for procedure pointers.
25 - 8.5.4 Components
26   - C757
27   - C758
28   - C759
29 - 8.5.9: EXTERNAL attribute
30 - 8.5.14: POINTER attribute
31   - C853
32   - A procedure pointer shall not be referenced unless it is pointer associated
33     with a target procedure.
34 - 8.5.15 PROTECTED attribute
35   - C855
36 - 8.5.16 SAVE attribute
37   - (4) A procedure pointer declared in the scoping unit of a main program,
38         module, or submodule implicitly has the SAVE attribute.
39 - 8.10.2.1 COMMON statement
40   - C8119
41 - 10.2.2.2 Pointer assignment statement
42   - C1028
43   - C1029
44 - 10.2.2.4 Procedure pointer assignment
45 - 11.1.3 ASSOCIATE construct
46   - C1005
47 - 12.6.3 Data transfer input/output list
48   - C1233
49 - 15.2.2.4 Procedure pointers
50   - A procedure pointer may be pointer associated with an external procedure, an
51     internal procedure, an intrinsic procedure, a module procedure, or a dummy
52     procedure that is not a procedure pointer.
53 - 15.4.3.6 Procedure declaration statement
54 - 15.5.2.9(5) Actual arguments associated with dummy procedure entities
55 - 16.9.16 ASSOCIATED(POINTER [, TARGET])
56   - POINTER may be a procedure pointer, and TARGET may be proc-target in a
57     pointer assignment statement (10.2.2).
58 - 16.9.144 NULL([MOLD])
59   - MOLD may be a procedure pointer.
60 - 18.2.3.4 C_F_PROCPOINTER(CPTR, FPTR)
61   - FPTR shall be a procedure pointer, and not be a component of a coindexed
62     object.
63 - C.1.1 A procedure that is not a procedure pointer can be an actual argument
64   that corresponds to a procedure pointer dummy argument with the INTENT(IN)
65   attribute.
67 ---
69 ## Representation in FIR
71 ### Procedure pointer `!fir.ref<!fir.boxproc<T>>`
73 A procedure pointer may have an explicit or implicit interface. T in
74 `!fir.ref<!fir.boxproc<T>>` is the function type, which is `() -> ()` if the
75 procedure pointer has the implicit interface declared as
76 `procedure(), pointer :: p`.
78 A procedure declaration statement specifies EXTERNAL attribute (8.5.9) for all
79 entities for all entities in the procedure declaration list.
81 ### Actual arguments associated with dummy procedure entities
83 The actual argument may be a procedure pointer, a valid target for the dummy
84 pointer, a reference to the NULL() intrinsic, or a reference to a function that
85 returns a procedure pointer.
87 If the interface is explicit, and the dummy argument is procedure pointer, the
88 reference is resolved as the pointer to the procedure; otherwise, the reference
89 is resolved as the pointer target.
91 **Fortran case 1**
92 ```fortran
93 subroutine proc_pointer_dummy_argument(p)
94   interface
95     function func(x)
96       integer :: x
97     end function func
98   end interface
99   procedure(func), pointer :: p
100   call foo1(p)
101   call foo2(p)
102 contains
103   subroutine foo2(q)
104     interface
105       function func(x)
106         integer :: x
107       end function func
108     end interface
109     procedure(func), pointer :: q
110   end subroutine foo2
111 end subroutine proc_pointer_dummy_argument
114 **FIR for case 1**
116 func.func private @foo1(!fir.boxproc<(!fir.ref<i32>) -> f32>)
117 func.func private @foo2(!fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>)
119 func.func @proc_pointer_dummy_argument(%0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>) {
120   %1 = fir.load %0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
121   fir.call @foo1(%1) : (!fir.boxproc<(!fir.ref<i32>) -> f32>) -> ()
122   fir.call @foo2(%0) : (!fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>) -> ()
123   return
127 **Fortran case 2**
128 ```fortran
129 subroutine proc_pointer_global()
130   interface
131     function func(x)
132       integer :: x
133     end function func
134   end interface
135   procedure(func), pointer, save :: p
136   call foo1(p)
137   call foo2(p)
138 contains
139   subroutine foo2(q)
140     interface
141       function func(x)
142         integer :: x
143       end function func
144     end interface
145     procedure(func), pointer :: q
146   end subroutine foo2
147 end subroutine proc_pointer_global
150 **FIR for case 2**
152 func.func private @foo1(!fir.boxproc<(!fir.ref<i32>) -> f32>)
153 func.func private @foo2(!fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>)
155 fir.global internal @ProcedurePointer : !fir.boxproc<(!fir.ref<i32>) -> f32> {
156   %0 = fir.zero_bits (!fir.ref<i32>) -> f32
157   %1 = fir.emboxproc %0 : ((!fir.ref<i32>) -> f32) -> !fir.boxproc<(!fir.ref<i32>) -> f32>
158   fir.has_value %1 : !fir.boxproc<(!fir.ref<i32>) -> f32>
161 func.func @proc_pointer_global() {
162   %0 = fir.address_of(@ProcedurePointer) : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
163   %1 = fir.load %0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
164   fir.call @foo1(%1) : (!fir.boxproc<(!fir.ref<i32>) -> f32>) -> ()
165   fir.call @foo2(%0) : (!fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>) -> ()
166   return
170 **Fortran case 3**
171 ```fortran
172 subroutine proc_pointer_local()
173   interface
174     function func(x)
175       integer :: x
176     end function func
177   end interface
178   procedure(func), pointer :: p
179   call foo1(p)
180   call foo2(p)
181 contains
182   subroutine foo2(q)
183     interface
184       function func(x)
185         integer :: x
186       end function func
187     end interface
188     procedure(func), pointer :: q
189   end subroutine foo2
190 end subroutine proc_pointer_local
193 **FIR for case 3**
195 func.func private @foo1(!fir.boxproc<(!fir.ref<i32>) -> f32>)
196 func.func private @foo2(!fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>)
198 func.func @proc_pointer_local() {
199   %0 = fir.alloca !fir.boxproc<(!fir.ref<i32>) -> f32>
200   %1 = fir.zero_bits (!fir.ref<i32>) -> f32
201   %2 = fir.emboxproc %1 : ((!fir.ref<i32>) -> f32) -> !fir.boxproc<(!fir.ref<i32>) -> f32>
202   fir.store %2 to %0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
203   %4 = fir.load %0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
204   fir.call @foo1(%4) : (!fir.boxproc<(!fir.ref<i32>) -> f32>) -> ()
205   fir.call @foo2(%0) : (!fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>) -> ()
206   return
210 It is possible to pass procedure pointers to a C function. If the C function has
211 an explicit interface in fortran code, and the dummy argument is a procedure
212 pointer, the code passes a pointer to the procedure as the actual argument
213 (see Case 5); Otherwise, the code passes the procedure pointer target as the
214 actual argument (see Case 4).
216 **Case 4**
217 ```c
218 void func_(void (*foo)(int *)) {
219   int *x, y = 1;
220   x = &y;
221   foo(x);
224 ```fortran
225 program main
226   procedure(), pointer :: pp
227   pp=>print_x
228   call func(pp)
229 contains
230   subroutine print_x(x)
231     integer :: x
232     print *, x
233   end
237 Note that the internal procedure is not one good usage, but it works in
238 implementation. It is better to use BIND(C) external or module procedure as
239 right-hand side proc-target.
241 **Case 5**
242 ```c
243 void func_(void (**foo)(int *)) {
244   int *x, y = 1;
245   x = &y;
246   (*foo)(x);
249 ```fortran
250 program main
251   interface
252     subroutine func(p)
253       procedure(), pointer :: p
254     end
255   end interface
256   procedure(), pointer :: pp
257   pp=>print_x
258   call func(pp)
259 contains
260   subroutine print_x(x)
261     integer :: x
262     print *, x
263   end
267 Case 4 and Case 5 are not recommended from Fortran 2003 standard, which provides
268 the feature of interoperability with C to handle this. Specifically,
269 C_F_PROCPOINTER is used to associate a procedure pointer with the target of a C
270 function pointer. C_FUNPTR is also designed for interoperability with any C
271 function pointer type.
273 ### Procedure pointer to function returning a character type
275 The dummy procedure pointer may not have a function type with an assumed length
276 due to C721 and C723.
278 ### Procedure pointer to internal procedure
280 Initially the current plan is to implement pointers to internal procedures
281 using the LLVM Trampoline intrinsics. This has the drawback of requiring the
282 stack to be executable, which is a security hole. To avoid this, we will need
283 [improve the implementation](InternalProcedureTrampolines.md) to use heap-resident thunks.
285 ### Procedure pointer assignment `p => proc`
287 The right-hand side may be a procedure, a procedure pointer, or a function whose
288 result is a procedure pointer.
290 The procedure could be a BIND(C) procedure. The lowering of it is the same as
291 that of an external or module procedure. The case of internal procedure has been
292 discussed above.
294 ```c
295 #include<stdio.h>
296 void func_(int *x) {
297   printf("%d\n", *x);
300 ```fortran
301 program main
302   interface
303     subroutine func(x) bind(C)
304       integer :: x
305     end
306   end interface
307   procedure(func), bind(C, name="func_") :: proc
308   procedure(func), pointer :: pp
309   integer :: x = 5
310   pp=>proc
311   call pp(x)
315 **Fortran case**
316 ```fortran
317 subroutine proc_pointer_assignment(arg0, arg1)
318   interface
319     function func(x)
320       integer :: x
321     end
322   end interface
323   procedure(func), pointer :: arg0, arg1
324   real, external, bind(C, name="Procedure") :: proc
325   arg0=>proc    ! case 1
326   arg0=>arg1    ! case 2
327   arg0=>reffunc ! case 3
328 contains
329   function reffunc() result(pp)
330     interface
331       function func(x)
332         integer :: x
333       end
334     end interface
335     procedure(func), pointer :: pp
336   end
338 function proc(x) bind(C, name="Procedure")
339   integer :: x
340   proc = real(x)
344 **FIR**
346 func.func @Procedure(%arg0 : !fir.ref<i32>) -> f32 {
347   %0 = fir.alloca f32 {bindc_name = "res", uniq_name = "_QFfuncEres"}
348   %1 = fir.load %arg0 : !fir.ref<i32>
349   %2 = fir.convert %1 : (i32) -> f32
350   fir.store %2 to %0 : !fir.ref<f32>
351   %3 = fir.load %0 : !fir.ref<f32>
352   return %3 : f32
355 func.func @Reference2Function() -> !fir.boxproc<(!fir.ref<i32>) -> f32> {
356   %0 = fir.alloca !fir.boxproc<(!fir.ref<i32>) -> f32>
357   %1 = fir.load %0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
358   return %1 : !fir.boxproc<(!fir.ref<i32>) -> f32>
361 func.func @proc_pointer_assignment(%arg0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>, %arg1 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>) {
362   %0 = fir.alloca !fir.boxproc<(!fir.ref<i32>) -> f32> {bindc_name = ".result"}
363   // case 1: assignment from external procedure
364   %1 = fir.address_of(@Procedure) : (!fir.ref<i32>) -> f32
365   %2 = fir.emboxproc %1 : ((!fir.ref<i32>) -> f32) -> !fir.boxproc<(!fir.ref<i32>) -> f32>
366   fir.store %2 to %arg0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
367   // case2: assignment from procdure pointer
368   %3 = fir.load %arg1 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
369   fir.store %3 to %arg0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
370   // case3: assignment from a reference to a function whose result is a procedure pointer
371   %4 = fir.call @Reference2Function() : () -> !fir.boxproc<(!fir.ref<i32>) -> f32>
372   fir.store %4 to %0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
373   %5 = fir.load %0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
374   fir.store %5 to %arg0 : !fir.ref<!fir.boxproc<(!fir.ref<i32>) -> f32>>
375   return
379 ### Procedure pointer components
381 Having procedure pointers in derived types permits `methods` to be dynamically
382 bound to objects. Such procedure pointer components will have the type
383 !fir.boxproc<T>.
385 **Fortran**
386 ```fortran
387 subroutine proc_pointer_component(a, i, f)
388   interface
389     function func(x)
390       integer :: x
391     end
392   end interface
393   type matrix
394     real :: element(2,2)
395     procedure(func), pointer, nopass :: solve
396   end type
397   integer :: i
398   procedure(func) :: f
399   type(matrix) :: a
400   a%solve=>f
401   r = a%solve(i)
402 end subroutine proc_pointer_component
405 **FIR**
407 func.func @proc_pointer_component(%arg0 : !fir.boxproc<(!fir.ref<i32>) -> f32>, %arg1: !fir.ref<i32>) {
408   %0 = fir.alloca !fir.type<_QFtestTmatrix{element:!fir.array<2x2xf32>,solve:!fir.boxproc<() -> ()>}>
409   %1 = fir.field_index solve, !fir.type<_QFtestTmatrix{element:!fir.array<2x2xf32>,solve:!fir.boxproc<() -> ()>}>
410   %2 = fir.coordinate_of %0, %1 : (!fir.ref<!fir.type<_QFtestTmatrix{element:!fir.array<2x2xf32>,solve:!fir.boxproc<() -> ()>}>>, !fir.field) -> !fir.ref<!fir.boxproc<() -> ()>>
411   %3 = fir.convert %arg0 : (!fir.boxproc<(!fir.ref<i32>) -> f32>) ->  !fir.boxproc<() -> ()>
412   fir.store %3 to %2 : !fir.ref<!fir.boxproc<() -> ()>>
413   %4 = fir.field_index solve, !fir.type<_QFtestTmatrix{element:!fir.array<2x2xf32>,solve:!fir.boxproc<() -> ()>}>
414   %5 = fir.coordinate_of %0, %4 : (!fir.ref<!fir.type<_QFtestTmatrix{element:!fir.array<2x2xf32>,solve:!fir.boxproc<() -> ()>}>>, !fir.field) -> !fir.ref<!fir.boxproc<() -> ()>>
415   %6 = fir.load %5 : !fir.ref<!fir.boxproc<() -> ()>>
416   %7 = fir.convert %6 : (!fir.boxproc<() -> ()>) -> !fir.boxproc<(!fir.ref<i32>) -> f32>
417   %8 = fir.box_addr %7 : (!fir.boxproc<(!fir.ref<i32>) -> f32>) -> ((!fir.ref<i32>) -> f32)
418   %9 = fir.call %8(%arg1) : (!fir.ref<i32>) -> f32
419   return
425 # Testing
427 The lowering part is tested with LIT tests in tree, but the execution tests are
428 useful for full testing.
430 LLVM IR testing is also helpful with the initial check. A C function pointer is
431 semantically equivalent to a Fortran procedure in LLVM IR level, and a pointer
432 to a C function pointer is semantically equivalent to a Fortran procedure
433 pointer in LLVM IR level. That is, a Fortran procedure will be converted to a
434 opaque pointer in LLVM IR level, which is the same for a C function pointer;
435 a Fortran procedure pointer will be converted to a opaque pointer pointing to
436 a opaque pointer, which is the same for a pointer to a C function pointer.
438 The tests should include the following
439 - function result, subroutine/function arguments with varying types
440   - non-character scalar
441   - character (assumed-length and non-assumed-length)
442   - array (static and dynamic)
443   - character array
444   - derived type
445   - ... (polymorphic?)
446 - internal/external/module procedure or a C function as the target
447   - procedure pointer initialization
448   - procedure pointer assignment
449 - procedure pointer, procedure pointer target passed to a C function
450 - procedure pointer, procedure pointer target passed to a Fortran procedure
451 - procedure pointer component in derived types
455 # Current TODOs
456 Current list of TODOs in lowering:
457 - `flang/lib/Lower/CallInterface.cpp:708`: not yet implemented: procedure pointer result not yet handled
458 - `flang/lib/Lower/CallInterface.cpp:961`: not yet implemented: procedure pointer arguments
459 - `flang/lib/Lower/CallInterface.cpp:993`: not yet implemented: procedure pointer results
460 - `flang/lib/Lower/ConvertExpr.cpp:1119`: not yet implemented: procedure pointer component in derived type assignment
461 - `flang/lib/Lower/ConvertType.cpp:228`: not yet implemented: procedure pointers
462 - `flang/lib/Lower/Bridge.cpp:2438`: not yet implemented: procedure pointer assignment
463 - `flang/lib/Lower/ConvertVariable.cpp:348`: not yet implemented: procedure pointer component default initialization
464 - `flang/lib/Lower/ConvertVariable.cpp:416`: not yet implemented: procedure pointer globals
465 - `flang/lib/Lower/ConvertVariable.cpp:1459`: not yet implemented: procedure pointers
466 - `flang/lib/Lower/HostAssociations.cpp:162`: not yet implemented: capture procedure pointer in internal procedure
467 - lowering of procedure pointers in ASSOCIATED, NULL, and C_F_PROCPOINTER
469 Current list of TODOs in code generation:
471 NOTE: There are any number of possible implementations.
473 BoxedProcedure pass
477 - `flang/lib/Optimizer/CodeGen/TypeConverter.h:64` TODO: BoxProcType type conversion
478 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:2080` not yet implemented: fir.emboxproc codegen
479 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:629` not yet implemented: fir.boxproc_host codegen
480 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:1078` not yet implemented: fir.len_param_index codegen
481 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:3166` not yet implemented: fir.unboxproc codegen
485 Resources:
486 - [1] Fortran standard