Quoting @greenrongreen in another thread:
Admittedly, it doesn’t help in this situation, as it still crashes with even with 2024.0.
I’ve managed to find a few leads. The first thing I did was to eliminate every line I could, but would still lead to a segmentation fault:
! recursion.F90
!
module mymodule_mod
use, intrinsic :: iso_c_binding
implicit none
private
public :: callback_wrapper
abstract interface
subroutine callback() bind(c)
end subroutine callback
end interface
contains
#if RECURSION
recursive subroutine callback_wrapper(callback_ptr)
#else
subroutine callback_wrapper(callback_ptr)
#endif
type(c_funptr), value :: callback_ptr
procedure(callback), pointer :: callback_procedure
call c_f_procpointer(callback_ptr, callback_procedure)
call callback_closure
contains
subroutine callback_closure
call callback_procedure()
end subroutine callback_closure
end subroutine callback_wrapper
end module mymodule_mod
program main
use, intrinsic :: iso_c_binding
use mymodule_mod
implicit none
call callback_wrapper(c_funloc(callback))
contains
subroutine callback() bind(c)
print *, "callback called"
end subroutine
end program
When compiled normally the callback is called as expected. However when you turn on the definition -DRECURSION
, or equivalently the flag -assume recursion
, the program suffers a segmention fault.
Looking at the diff view in compiler explorer there are a few noticeable changes (red is the one that works, green is the one that segfaults):
The recursive attribute appears to changes a few load instructions, but I can’t really why . From here I noticed if I add -O1
, the internal procedure gets inlined (the equivalent of removing the closure), and the problem disappears:
(You can see the internal procedure is left empty in the right panel. In the left panel, it consists just of a jump to the to the target of the procedure pointer callback_procedure
, and was also inlined). In your original example, -O1
doesn’t help however, for whatever bug-related reason.
The second observation, is that initialising the procedure pointer, also makes the segfault disappear:
procedure(callback), pointer :: callback_procedure => null() ! initalization
In fact, the generated assembly is now the same with or without the recursive
attribute. I’ve also checked that the initialization to null()
works in your original example.
Note that it doesn’t work if you nullify the pointer in as the first statement:
procedure(callback), pointer :: callback_procedure
nullify(callback_procedure) ! first statement
I’d need to consult the standard to say if this is semantically equivalent to the initialisation or not.
The thing about recursive
is that “the values of variables allocated in one activation of a recursive procedure must be protected from change by other activations,” quoting from a random IBM page on PL/I. If one of the local variables in a recursive procedure is a pointer, how do you make sure that other calls of the recursive procedure don’t invalidate the pointer? What if other threads change it?