Stdlib system interaction API: call for feedback

Isn’t the intent(in),pointer combination for dummy arguments a special case within fortran? I think it is the same as a target declaration, followed by a local pointer assignment to that target. If the actual argument is not a target, or a pointer, then the local pointer changes do not get propagated back to the caller, so it is still up to the programmer to enforce the right argument association when that is required.

1 Like

me too but stdlib is more functional than object-oriented, so I try to stick with that :slight_smile:

You have a great point on the pointer lifetime: but wouldn’t it be the same with the derived type?
Let me try to understand the OO approach here: we will have to store it as a pointer into the process variable anyways, right?

type :: process_type
...
class(callback_interface), pointer :: callback => null()
end type process_type

so you have

! Process variable goes out of scope: ensure no dangling process
subroutine process_completion(process)
    type(process_type), intent(inout) :: process
    .... ! collect stdout, stderr
    
    ! run callback
    if (associated(process%callback)) call process%callback%callback(process%exit_code,...)
end subroutine

so it does bind the data and their function which is great, but we’re still not guaranteed that the derived type variable that was an argument on process creation is still alive. (in C++ you’d do this with a shared_ptr or a weak_ptr at least, but in Fortran we don’t have that).

Plus, I worry that if we declare the data as pointer, intent(in), then the callback function cannot modify its content, i.e. calling a TBP with argument class(callback_interface), intent(inout) :: this would be catched by the compiler I guess.

In both cases, you want to create a pointer, which is warranted to remain valid after the scope had been left (so that you can store it and use it at a later point). One of the necessary requirements is that the caller must declare the pointer or the target attribute for the actual argument. (Otherwise compilers could create a copy on entering the subroutine, and the pointer you create within the subroutine will point to this copy and will be obviously invalid once the scope had been left.)

The two approaches for the dummy argument differ, how compilers react, when the caller forgot do declare the target argument.

module demomod
  implicit none
contains

  subroutine dummy_trg_inout(trg)
    integer, intent(inout), target :: trg
    trg = trg + 1
  end subroutine dummy_trg_inout

  subroutine dummy_ptr_in(trg)
    integer, intent(in), pointer :: trg
    trg = trg + 1
  end subroutine dummy_ptr_in

end module demomod

program demoprog
  use demomod
  implicit none

  integer, target :: with_trg
  integer :: without_trg

  call dummy_trg_inout(with_trg)
  call dummy_ptr_in(with_trg)
  ! This unfortunately does not trigger a compiler error
  call dummy_trg_inout(without_trg)
  ! Next line fortunately would trigger a compiler error if uncommented
  ! call dummy_ptr_in(without_trg)

end program demoprog

If the dummy argument uses the pointer attribute, the caller is forced (by the compiler) to declare the target or the pointer attribute. If the dummy argument uses the target attribute, forgetting to declare the necessary attributes for the actual argument does not trigger any compiler error, not even a compiler warning.

2 Likes

That’s true, we can not enforce a lifetime warranty for any pointer unless we implement reference counting (as in shared_ptr), which is probably an overkill. And there is no difference between the OOP and the procedural approach in this respect.

With the pointer lifetime I was referring to the target attribute for the dummy argument. If the caller forgot to declare target or pointer for the actual argument, the pointer you create to the dummy argument with the target attribute might point to a temporary copy, which is gone, once you leave the subroutine. (See my post above.)

As for the OOP approach: I’d probably not store a pointer to an instance, but a copy the instance itself:

type :: process_type
...
class(callback_interface), allocatable :: callback
end type process_type``

If the derived class contains only non-pointer data fields, the availability of the data is warranted when the callback function is called.

exactly, or the only guarantee is that it’ll be valid for the duration of the parent scope only (the procedure the process constructor is called from)

This would be great to ensure the lifetime, however, wouldn’t it cause data duplication? only the copy inside the process variable would be updated on completion, not the one that was used as an argument in runasync. So I think that from an inexperienced user’s perspective, I’m not sure if I would encourage this approach.

We may then require a move_alloc, which wouldn’t be easy too, due to polymorphism (the runasync argument should also be of type class(callback_interface), allocatable, intent(inout), so one would have to do:

class(callback_interface), allocatable :: my_callback

allocate(my_callback_type :: my_callback)
p = runasync(... , my_callback) ! takes ownership of my_callback with move_alloc
print *, allocated(my_callback) ! F

so, this move_alloc thing is not exactly a great solution imho.

Yes, it would. But the caller is free to put a pointer in the derived class, if data duplication matters, or the data must be shared.

I also thought about the move_alloc, which is indeed a cool way of expressing “ownership” in Fortran. But I am not sure, whether users will appreciate the extra effort of allocation… :smile:

1 Like

For the intent(inout) to be fully applicable, doesn’t a pointer in some “global storage” work better?

For example, assuming pthreads (and unix):

module processes
    ...
    type :: global_storage
        integer(C_INT) :: id
        class(*), pointer :: payload => null()
        procedure(i_callback), pointer :: callback
    end type

    abstract interface
        subroutine i_callback(pid, status, payload)
            integer(C_PID_T), intent(in) :: pid
            integer(C_INT), intent(in) :: status
            class(*), optional, intent(inout) :: payload
        end subroutine
    end interface

    ...

contains
    subroutine runasync(..., callback, payload)
        procedure(i_callback) :: callback
        class(*), target, intent(in) :: payload
        type(global_storage), pointer :: storage
        ...
        storage => global_storage_new()
        storage%payload => payload
        storage%callback => callback
        res = pthread_create(thread, C_NULL_PTR, c_funloc(start_process), c_loc(storage%id))
        ...
    end subroutine

    function start_process(arg) result(res) bind(C)
        type(C_PTR) :: res
        type(C_PTR), value :: arg
        integer(C_INT), pointer :: id
        type(global_storage), pointer :: storage

        res = C_NULL_PTR
        call c_f_pointer(arg, id)
        call get_global_storage(id, storage)

        ! run process, getting pid and status
        call fork_exec(...)

        call storage%callback(pid, status, storage%payload)
        call free_global_storage(id)
        call pthread_exit(c_loc(status))
    end subroutine
    ...
end module

Of course, the caller of runasync will have to ensure the lifetime of the payload argument.

1 Like

Correct! Your proposal matches the one at this post.

The whole discussion revolves around this one:

I did not imagine that suggesting a callback function would trigger that level of discussion :smile:.

If the shared_ptr is necessary in this case, I recall that the MEGMS has an implementation in Fortran. There is also the smart-pointers from the sourcery institute.

I am not sure I totally grasp the problem discussed here. But from what I read the procedure pointer approach seems to present some drawbacks. There is another approach that can be used to store a callback function which involves some dark magic :mage: and the iso_c_binding. One could store the callback as type(c_funptr) returned from c_funloc. The procedure pointer could be restored on demand using c_f_procpointer.

1 Like