Totally agree with you @aradi. Generally, when dealing with these anonymous interfaces, I use temporary wrappers see
subroutine solve_ode(problem)
class(ode_problem), intent(inout) :: problem
...
! Call ODE integrator
call VODE(fun, ...)
contains
! wrap to VODE interface
subroutine ode_fun(n,t,y,rpar,ipar)
integer, intent(in) :: n
real(wp), intent(inout) :: t,y(n),rpar(*)
integer, intent(inout) :: ipar(*)
! Access everything from the parent scope
end subroutine ode_fun
end subroutine solve_ode
So yes, it is possible to have a callback interface with no pointers. But as you say, it’s clunky: in the case of a process, one must ensure that the temporary function does not go out of scope before the process exits, otherwise when called, the program would segfault. I also do not like the idea of a special derived type just for callback handling.
So maybe we should do like you’re suggesting: something like
abstract interface
procedure process_oncomplete(exit_state,stdin,stdout,stderr,data)
integer, intent(in) :: exit_state
! presence depends on allocation status in process type (<- user request)
character(len=*), optional, intent(in) :: stdin,stdout,stderr
! optional pointer to a user-defined class
class(*), optional, intent(in) :: data
end procedure process_oncomplete
end interface
So in the actual implementation, one can cast the pointer to their known class and use the data
subroutine my_process_exit(exit_state,stdin,stdout,stderr,data)
integer, intent(in) :: exit_state
character(len=*), optional, intent(in) :: stdin,stdout,stderr
class(*), optional, intent(inout) :: data
if (present(data)) then
select type (typed_data => data)
type is (...)
! do stuff
end select
endif
end subroutine my_process_exit
Then in the process creation interface, we add
p = runasync(cmd [,...] [, callback] [,data])
which is declared as
class(*), optional, intent(inout), target :: data
then storing both inside the process variable
procedure(process_oncomplete), pointer :: callback => null()
class(*), pointer :: callback_data => null()
So that the classes the user has attached to that process gets passed as an argument to the callback function.
This is the best approach I can think about, was this what you were envisioning? (example here)