To type(*) or to type(c_ptr), that is the question (or is not?)

First of all, let me clarify the following is not exactly a problem that needs to be solved, but rather a “problem of elegance” in code - which may or may not be even that, depending on your personal preferences when it comes to C interoperability. I apologize in advance since this post might be long. It has to do with a rather special case, and I see no way to make it shorter.

When I need to use a C library, I try to implement as “Fortran-friendly” bindings as possible (eliminate the need for any C-related stuff in the Fortran programs that will use the API, or at least reduce it to the absolute minimum.) Now, consider a C function addCallback, prototyped as

int (* CallbackFunc) (int interval, void *param)
void addCallback(int interval, CallbackFunc callback, void *param)

(this actually comes from a C library, I just stripped it down and simplified it.) Essentially addCallback does what its name says: it sets a callback function (prototyped as CallbackFunc) to be executed after a specified amount of time interval. The void param points to additional data the callback function might need; such data can be anything, and the callback function can change their values as well.

Now, a quick way to port this functionality in Fortran is

interface

subroutine addCallback1(interval, callback, param) bind(c, name="addCallback")
import :: c_funptr, c_int
integer(kind=c_int), intent(in), value :: interval
type(c_funptr), intent(in), value :: callback
type(*) :: param
end subroutine addCallback1

end interface

I opted to use type(*) instead of c_ptr for param. I didn’t specify any intent attribute for param because it might be c_null_ptr (thus strictly intent(in),) or it might be intent(inout) in a more general case.
The main program can include something like this:

integer :: par
...
par = 2
call addCallback1(1000, c_funloc(callback1), par)

where the callback function is

function callback1(interval, param) bind(c)
integer(kind=c_int) :: callback
integer(kind=c_int), intent(in), value :: interval
integer(kind=c_int), intent(inout) :: param
! An integer is needed as param, which is changed in the actual code that goes here.
end function callback1

And this works as expected. In this particular case param is an integer, it is compatible with type(*), and everything works. It could be a real, or even a derived type as well. Improved C interoperability introduced in Fortran 2018 definitely simplifies things. The “problem” is that I want to get rid of c_funloc in the main program. And I can, at the cost of a more complicated binding - which I am perfectly ok with, as long the main program gets rid of any C-related stuff:

subroutine addCallback2(interval, callback, param)
integer(kind=c_int), intent(in) :: interval
type(*), intent(in) :: param
interface
  function callback(interval, param) bind(c)
  import :: c_int
  integer(kind=c_int) :: callback
  integer(kind=c_int), intent(in), value :: interval
  type(*), intent(inout), target :: param
  end function callback
end interface
call addCallback1(interval, c_funloc(callback), param)
end subroutine addCallback2

addCallback2 is just a convenience subroutine which can be called by the user with the actual name of the Fortran callback function as the second argument (instead of a C pointer to said function.) Of course, an interface for the actual Fortran callback is necessary, and there I declared param as type(*). The reason I added the target attribute will be explained below.

Unfortunately, I can’t just do this in the main program:

call addCallback2(1000, callback1, par)

This doesn’t work with callback1 as defined above, because param is an integer in callback1, while the interface in addCallback2 defines the callback function with a more general type(*) for param - and I want it to be like that, as param can be anything, not just an integer. I understand why this doesn’t work: type(*) was introduced to make interoperability with C void pointers easier, but there is no interoperability here, because both addCallback2 and callback1 are Fortran procedures.
So I am now forced to change the actual Fortran callback:

call addCallback2(1000, callback2, par)
...
function callback2(interval, param) bind(c)
integer(kind=c_int) :: callback2
integer(kind=c_int), intent(in), value :: interval
type(*), intent(inout), target :: param
integer, pointer :: param_extracted
type(c_ptr) :: cptr
cptr=c_loc(param); call c_f_pointer(cptr, param_extracted)
! Actual code for the function goes here, but that's irrelevant.
end function callback2

This works, but notice how extra work was needed to “extract” the actual value of param (“hidden” behind an assumed-type) to an integer variable. According to the F2018 draft (7.3.2.2, C710) assumed-type variables can only be actual arguments and, even then, only in a few specific intrinsic functions. The most recent draft I could find for F2023 doesn’t seem to change anything there (see 7.3.2.2, C715.) Luckily c_loc is among the (very few) intrinsic functions that accept assumed-type variables as arguments. So the only way I could find to finally get the integer value was to use a pointer integer variable, then an auxiliary c_ptr variable, then call c_f_pointer to transfer the integer value from an assumed-type variable to a normal integer variable. But what’s the point of all that, I could do the same by just defining param as an “old-school” c_ptr everywhere instead, and get the same functionality. Assumed-type variables are quite restricted - and I understand why. Fortran is a strongly-typed language (and I like it as it is.)

The net result of all the above is: The first solution has a simpler callback function, but sacrifices Fortran’s ability to eliminate the use of direct c_funloc calls in the main program. The second solution makes main program as “clean” as it gets, but makes the callback function unnecessarily complicated. So my question (if you managed to read all the above) is, am I missing something here? Is there another, more “elegant” way I just don’t see? (I don’t consider using c_ptr instead of type(*) as elegant.)

My conclusion so far is that you can’t have C interoperability without sacrificing some elegance - at least in the “quirk” way I define the term “elegance”. Afterall, Fortran is strongly-typed, while C is the exact opposite. How can you possibly “marry” those two, without doing small sacrifices in your very Fortran-oriented programming style? But I might be wrong, and there is a simpler, more elegant way to do all the above I just don’t see.

2 Likes

Why don’t you just add a wrapper procedure around your interface? You could then simply pass a procedure argument to the wrapper (and implement all the logic there). That keeps the interface binding short and simple.

1 Like

The “extra” work is present also in C, it’s just that C type-casting is much less verbose.

You can make the callback interface anything you want on the Fortran side, by using an internal procedure as an adaptor (I believe this is the same solution @interkosmos has in mind):

!> Fortran callbacks (no C types used)
abstract interface
   !> A) No data supplied
   !>    Callers can always "inject" data using three methods: 
   !>    1) host association (an internal procedure)
   !>    2) import from a module (global state, not thread-safe in general)
   !>    3) a common block (obsolescent, don't do it!)
   integer function f_callback(interval) 
      integer, intent(in) :: interval
   end function
   !> B) Data supplied as pair of real and integer arrays
   integer function f_callback_array(interval,rpar,ipar)
      integer, intent(in) :: interval
      real, intent(inout) :: rpar(:)
      integer, intent(inout) :: ipar(:)
   end function
   !> C) Data supplied as unlimited polymorphic variable
   !>    Caveat: Requires `select type` guard in the callback implementation
   integer function f_callback_any(interval,params)
      integer, intent(in) :: interval
      class(*), intent(inout) :: params
   end function
   !> D) Any interface you want (could also be a subroutine)
   !> ...
end interface

!> The C function we are wrapping
interface
   subroutine c_addCallback(interval, callback, param) bind(c, name="addCallback")
      import :: c_funptr, c_int
      integer(kind=c_int), intent(in), value :: interval
      ! int (* CallbackFunc) (int interval, void *param)
      type(c_funptr), intent(in), value :: callback
      type(*) :: param
   end subroutine addCallback1
end interface

!> The Fortran wrappers
interface addCallback
   module procedure addCallbackA
   module procedure addCallbackB
   module procedure addCallbackC
end interface

contains

!> A) Call back with no data supplied
subroutine addCallbackA(interval,callback)
   integer, intent(in) :: interval
   procedure(f_callback) :: callback
   call c_addCallback(interval,c_funloc(adaptor),c_null_ptr)
contains
   function adaptor(interval,param) bind(c)
      integer(c_int), value :: interval
      type(c_ptr), value :: param  ! unused
      integer(c_int) :: adaptor
      adaptor = callback(interval)
   end function
end subroutine

!> B) Data supplied as pair of real and integer arrays
subroutine addCallbackB(interval,callback,rpar,ipar)
   integer, intent(in) :: interval
   procedure(f_callback_array) :: callback
   integer, intent(inout) :: rpar(:)
   integer, intent(inout) :: ipar(:)
   call c_addCallback(interval,c_funloc(adaptor),c_null_ptr)
contains
   function adaptor(interval,param) bind(c)
      integer(c_int), value :: interval
      type(c_ptr), value :: param  ! unused
      integer(c_int) :: adaptor
      adaptor = callback(interval,rpar,ipar)
   end function
end subroutine

!> C) Data supplied as unlimited polymorphic object
subroutine addCallbackC(interval,callback,params)
   integer, intent(in) :: interval
   procedure(f_callback_any) :: callback
   class(*), intent(inout) :: params
   call c_addCallback(interval,c_funloc(adaptor),c_null_ptr)
contains
   function adaptor(interval,param) bind(c)
      integer(c_int), value :: interval
      type(c_ptr), value :: param  ! unused
      integer(c_int) :: adaptor
      adaptor = callback(interval,params)
   end function
end subroutine

As pointed out to me by @awvwgk, host scope association and import from a module can always be used, whatever the interface may be.

In some sense C makes thing simple by giving you only one common solution (the void *) to pass data, while in Fortran you have many different conventions, which all boil down to an internal procedure in the end.

In C++ things are a bit more complicated because you have functions, function objects or functors, and lambdas, however you can write a common callback for all three of them by using the std::function polymorphic function wrapper template. Instead of writing N wrappers which you combine in a generic interface like I’ve done above, the template-mechanism in C++ instantiates whatever you need, depending on the procedure you pass.

3 Likes

For some additional type safety and since OP is not keen to use c_funloc, a variant of your solution can be:

   .
!> The C function we are wrapping
abstract interface
   function Icallback( interval, param ) result(r) bind(C)
      import :: c_int, c_ptr
      ! Argument list
      integer(c_int), intent(in), value :: interval
      type(c_ptr), intent(in), value    :: param
      ! Function result
      integer(c_int) :: r
   end function
end interface 
interface
   subroutine c_addCallback(interval, callback, param) bind(c, name="addCallback")
      import :: c_int, Icallback
      integer(kind=c_int), intent(in), value :: interval
      ! int (* CallbackFunc) (int interval, void *param)
      procedure(Icallback) :: callback
      type(*) :: param
   end subroutine
end interface

!> The Fortran wrappers
interface addCallback
   module procedure addCallbackA
   module procedure addCallbackB
   module procedure addCallbackC
end interface

contains

!> A) Call back with no data supplied
subroutine addCallbackA(interval,callback)
   integer, intent(in) :: interval
   procedure(f_callback) :: callback
   call c_addCallback(interval,adaptor,c_null_ptr)
contains
   function adaptor(interval,param) bind(c)
      integer(c_int), intent(in), value :: interval
      type(c_ptr), intent(in), value :: param  ! unused
      integer(c_int) :: adaptor
      adaptor = callback(interval)
   end function
end subroutine
   .
1 Like

True, and I could also “hide” that verbosity in Fotran under a simple utility function. I was just wondering if there is a better way to simplify things without relying on that.

This was the first solution it came in mind, in fact my API had very similar wrappers, which I deleted recently, keeping only the case where param=NULL. I was looking for something simpler that will cover all cases. I didn’t even mentioned wrappers in my original post because I quickly rejected this solution. What if param is actually three arrays? Another adaptor, as you call it - or create a class just for this in the main program (which in many cases seems like overkill to me.)
Calling c_funloc in the main program still seems to be the easiest general way, and the one I was wondering if I can do without the need of c_funloc. After all, C APIs love to have callback functions and, even worse, sometimes as members of a struct, to make things even more complicated to interop (still can be done, just a pain though.) If I need wrappers for every single callback function with voids, I would say assumed-type with c_funloc is a more elegant (and much simpler) general solution.

You are perfectly right here. However, I never liked templates, despite the convenience they offer. I am aware there is interest for similar functionality in Fortran, and LFortran already has plans for that as well. But in my experience C++'s template mechanism is very slow at compile time, with a delay noticeable even on pretty recent machines.

In some C API’s there is also an option to set a callback to NULL (e.g. to turn a callback something off), in that case the solution you gave as addCallback2 can’t be used, because the function must receive a callback. In this case you need to use a wrapper and a Fortran optional argument. This complication arises the in the freeGLUT/OpenGL bindings: https://www-stone.ch.cam.ac.uk/pub/f03gl/index.xhtml#Callbacks

It can be slow indeed, and the C compilation model with includes makes things even worse. But there are remedies today. Personally, I’d be willing to trade some compile speed for a less verbose syntax.

For fun, I’ve made two examples:

1) Fortran calling C

// timestwo.c
float timestwo(float x)
{
    return 2.0f * x;
}
! main.f90
module doit_mod
use, intrinsic :: iso_c_binding
implicit none
private
public :: doit, c_float
abstract interface
  function c_func(x) bind(c)
    import c_float
    real(c_float), intent(in), value :: x
    real(c_float) :: func
  end function
end interface
contains
  subroutine doit(f,x)
    procedure(c_func) :: f
    real(c_float), intent(in) :: x
    write(*,'("The result f(",G0,") is ",G0)') x, f(x)
  end subroutine
end module

program main
use doit_mod
implicit none
interface
  function timestwo(x) bind(c,name="timestwo")
    import c_float
    real(c_float), intent(in), value :: x
    real(c_float) :: timestwo
  end function
end interface
call doit(timestwo,4.0)
end program

2) C++ calling Fortran

! timestwo.f90
function timestwo(x) bind(c)
    use, intrinsic :: iso_c_binding, only: c_float
    implicit none
    real(c_float), intent(in), value :: x
    real(c_float) :: timestwo
    timestwo = 2.0_c_float*x
end function
// main.cpp
#include <functional>
#include <cstdio>

// Fortran subroutine
extern "C" float timestwo(float x);

// C++ function accepting callback
void doit(std::function<float(float)> f, float x)
{
    std::printf("The result f(%f) is %f\n", x, f(x));
}

int main(void)
{
    doit(timestwo,4.0);
    return 0;
}

Output

$ make FC=gfortran-12 CXX=g++-12 run
gfortran-12  -o main-f90 main.f90 timestwo.c
gfortran-12  -c timestwo.f90
g++-12  -o main-cpp main.cpp timestwo.o
./main-f90
The result f(4.00000000) is 8.00000000
./main-cpp
The result f(4.000000) is 8.000000

It can interesting to compare the symbols and disassembly of the two using nm -C and objdump -d. On my Mac both executables are about 49-50 KB:

    55K May  2 01:03 main-cpp
    49K May  2 01:03 main-f90
   300B May  2 00:28 main.cpp
   673B May  2 00:36 main.f90
    48B May  2 00:36 timestwo.c
   203B May  2 00:26 timestwo.f90

In terms of source-code, Fortran is 2-4 times more verbose…

This comment is some general feedback keeping in mind various readers with differing backgrounds toward interoperating Fortran with C.

  1. Note there is no support for Generics in C and the support in Fortran is limited,
  2. Given void * type of parameters in C function prototypes, note type safety during interoperation with such functions with Fortran will be limited generally and specifically by how the interoperating code is structured in Fortran,
  3. Use type(*) in Fortran to interoperate with void * in C function prototype when the object is effectively a pass-through. You can view it as such in the addcallback function in the original post.
  4. Use type(c_ptr) in Fortran to interoperate with void * in a C function prototype when the object needs to be operated upon in any manner in a Fortran instruction. Chances are high the actual callback functions in the example in the original post fall in such a category.

Thus with the situation in the original post, a hybrid approach with type(*) and type(c_ptr) is something that authors can consider. So to play around with this, consider the following: here, note with the Fortran code as structured, there is no need for c_funloc nor c_loc. The limitation is there is no true type safety e.g., an author might supply callback_real with the integer case and encounter run-time data corruption.

  • Say the C “library” code is like so:
#include <stdio.h>

typedef int (*CallbackFunc) (int interval, void *param);

void addCallback(int interval, CallbackFunc callback, void *param) {
    printf("In C addCallback: interval = %d\n", interval);
    int iret = callback(interval, param);
    printf("In C addCallback: after callback, iret = %d\n", iret);
    return;
}
  • A consumer in Fortran of such C code might then do:
Click to see code
    use, intrinsic :: iso_c_binding, only : c_int, c_float, c_ptr, c_f_pointer
    abstract interface
       function Icallback( interval, param ) result(r) bind(C)
          import :: c_int, c_ptr
          ! Argument list
          integer(c_int), intent(in), value :: interval
          type(c_ptr), intent(in), value    :: param
          ! Function result
          integer(c_int) :: r
       end function
    end interface
    interface
       subroutine addCallback( interval, callback, param ) bind(C, name="addCallback")
          import :: c_int, Icallback
          ! Argument list
          integer(c_int), intent(in), value :: interval
          procedure(ICallback)              :: callback
          type(*), intent(inout)            :: param
       end subroutine
    end interface
    integer(c_int) :: interval
    blk1: block
       integer(c_int) :: param
       print *, "Block 1: param as c_int"
       interval = -1
       call addCallback( interval, mycallback_int, param )
       print *, "In main: param = ", param
    end block blk1
    print *
    blk2: block
       real(c_float) :: param
       print *, "Block 2: param as c_float"
       interval = -2
       call addCallback( interval, mycallback_real, param )
       print *, "In main: param = ", param
    end block blk2
contains
    function mycallback_int( interval, param ) result(r) bind(C)
       ! Argument list
       integer(c_int), intent(in), value :: interval
       type(c_ptr), intent(in), value    :: param
       ! Function result
       integer(c_int) :: r
       ! Local variables
       integer(c_int), pointer :: fparam
       print *, "In mycallback_int: interval = ", interval
       call c_f_pointer( param, fparam )
       fparam = 42
       r = 1
    end function
    function mycallback_real( interval, param ) result(r) bind(C)
       ! Argument list
       integer(c_int), intent(in), value :: interval
       type(c_ptr), intent(in), value    :: param
       ! Function result
       integer(c_int) :: r
       ! Local variables
       real(c_float), pointer :: fparam
       print *, "In mycallback_real: interval = ", interval
       call c_f_pointer( param, fparam )
       fparam = 99.0
       r = 2
    end function
end

Upon execution, a processor might do:

C:\temp>gfortran -ffree-form p.f c.c -o p.exe
cc1.exe: warning: command-line option '-ffree-form' is valid for Fortran but not for C

C:\temp>p.exe
 Block 1: param as c_int
In C addCallback: interval = -1
 In mycallback_int: interval =           -1
In C addCallback: after callback, iret = 1
 In main: param =           42

 Block 2: param as c_float
In C addCallback: interval = -2
 In mycallback_real: interval =           -2
In C addCallback: after callback, iret = 2
 In main: param =    99.0000000
2 Likes

My API actually wraps two versions of addCallBack in a generic interface: one version without param (for the case it’s NULL,) and one as addCallback1. This is very similar to the the solution you mentioned, but without an optional argument.

I am aware of F03GL, and they have some interesting comments about the challenges they faced there. However, in a typical “@Pap way”, I wrote my own OpenGL bindings long before I actually learned about F03GL, and rejected FreeGLUT altogether (it’s not a bad library by any means, it just lacked functionality I needed - and found in GLFW.)

Good points about type(*) for the pass-through which removes the need for c_loc, and the use of an explicit procedure interface for the function pointer which gives both type-checking, and removes the need for c_funloc.

The use c_ptr in the actual callback also mirrors closely what would be done if the callback were in C,

int *fparam = (int *) param;
*fparam = 42;

so a certain usage symmetry is preserved.

In my C++ example above, the std::function template, can be replaced with a compile-time template abstraction which has less overhead:

template<typename Func>
void doit(Func f, float x)
{
    std::printf("The result f(%f) is %f\n", x, f(x));
}

The call to doit in the main routine, would then instantiate the following routine:

template<>
void doit<float (*)(float)>(float (*f)(float), float x)
{
  printf("The result f(%f) is %f\n", static_cast<double>(x), static_cast<double>(f(x)));
}
// note: apparently in variadic argument lists, 
//       floats get implicitly promoted to double

If I now compare the symbols in the Fortran and C++ versions,

~/fortran/lto$ nm -C main-f90 
0000000100003da0 T ___doit_mod_MOD_doit
0000000100008028 d __dyld_private
                 U __gfortran_set_args
                 U __gfortran_set_options
                 U __gfortran_st_write
                 U __gfortran_st_write_done
                 U __gfortran_transfer_real_write
0000000100000000 T __mh_execute_header
0000000100003e50 S _main
0000000100003f20 s _options.1.0
0000000100003e40 T _timestwo
                 U dyld_stub_binder
~/fortran/lto$ nm -C main-cpp 
0000000100008008 d __dyld_private
0000000100000000 T __mh_execute_header
0000000100003ee0 T _main
                 U _printf
0000000100003f10 T _timestwo
                 U dyld_stub_binder

we can see there is zero over-head in the C++ executable, as the doit procedure has been optimized away, and the Fortran timestwo procedure is called directly in main. With Fortran on the other hand, the doit module procedure persists. This did not change even after I made doit an internal procedure in the main program block:

~/fortran/lto$ nm -C main-f90 
0000000100008028 d __dyld_private
                 U __gfortran_set_args
                 U __gfortran_set_options
                 U __gfortran_st_write
                 U __gfortran_st_write_done
                 U __gfortran_transfer_real_write
0000000100000000 T __mh_execute_header
0000000100003dd0 t _doit.0.constprop.0
0000000100003e80 S _main
0000000100003f40 s _options.1.1
0000000100003e70 T _timestwo
                 U dyld_stub_binder

(these results were for GCC-10)

I’d be curious to see how the planned Fortran generics might handle a simple callback argument; from the examples I’ve seen so far it might be something like this:

module doit_mod
use, intrinsic :: iso_c_binding
implicit none
private
public :: do_it_tmpl
requirement r(c_func)
    pure function c_func(x) bind(c)
        import c_float
        real(c_float), intent(in), value :: x
        real(c_float) :: c_func
    end function
end requirement
template doit_tmpl(c_func)
    requires r(c_func)
contains
    subroutine doit(x)
        real(c_float), intent(in), value :: x
        write(*,'("The result f(",G0,") is ",G0)') x, c_func(x)
    end subroutine
end template
end module

program main
use doit_mod, only: doit_tmpl
interface
  function timestwo(x) bind(c,name="timestwo")
    import c_float
    real(c_float), intent(in), value :: x
    real(c_float) :: timestwo
  end function
end interface
instantiate doit_tmpl(timestwo), only: dotimestwo => doit
call dotimestwo(4.0)
end program

It’s only one extra line for the caller, which I guess is not that bad, but the template itself feels kind of heavy… (I know the templates are closer to C++ concepts, so there will likely be other usage cases where it shines).

1 Like

@ivanpribec , interesting. If you have some free time, can you please try out LFortran with its current support for 202Y Generics, perhaps in contrast with a “container” option (see an option below) that is currently viable and give your feedback on your takeaways. Perhaps @everythingfunctional and team working on 202Y Generics may be able to apply your learnings toward the design of the standard feature.

  • C “library” code
float Cfunc( float x ) {
    float y = 2.0f * x;
    return y;
}
  • Fortran “container” and consumer
module doit_m
   use, intrinsic :: iso_c_binding, only : c_float
   abstract interface
      pure function Ifunc( x ) result(r) bind(C)
         import :: c_float
         real(c_float), intent(in), value :: x
         real(c_float) :: r
      end function
   end interface
   type :: doit_t
      procedure(Ifunc), nopass, pointer :: func => null()
   contains
      procedure :: doit
   end type
contains
    subroutine doit(this, x)
       class(doit_t), intent(in) :: this 
       real(c_float), intent(in), value :: x
       write(*,'("The result f(",G0,") is ",G0)') x, this%func(x)
    end subroutine
end module
   use, intrinsic :: iso_c_binding, only : c_float
   use doit_m, only : doit_t
   interface
      pure function Cfunc( x ) result(r) bind(C, name="Cfunc")
         import :: c_float
         real(c_float), intent(in), value :: x
         real(c_float) :: r
      end function
   end interface
   type(doit_t) :: a
   a = doit_t( Cfunc )
   call a%doit( 4.0_c_float )
end  
  • Program execution
C:\temp>gfortran -ffree-form p.f c.c -o p.exe
cc1.exe: warning: command-line option '-ffree-form' is valid for Fortran but not for C

C:\temp>p.exe
The result f(4.00000000) is 8.00000000
1 Like

Thank you all for your comments and suggestions. I ended up with a hybrid approach, pretty much as @FortranFan recommended. I was hesitating to define param both as an assumed-type type(*) entity and as a “traditional” c_ptr, but apparently in this case it is indeed the most “elegant” solution. In addCallback, it’s more convenient to define param as a type(*), there is no question about that. However in the actual callback function prototype, it’s better to just define param as an old-school c_ptr, otherwise the user would have to write actual callback functions as ugly as my callback2 function in the original post. We have a special case here, param is present both in the call of a C-interoperable subroutine and in a C-interoperable function that happens to be an argument of said subroutine. So it needs special treatment.

The hybrid solution also eliminates the need of c_funloc in the main program. Yes, it may be somewhat less type-safe, but let’s be honest here, if the user of a library wants to mess things up, they can - and we aren’t going to stop them no matter how hard we can try. This is even more pronounced if a Fortran program uses a C library in the background.

However, I opted to let the user have a choice, so a generic interface allows to call addCallback either with a normal Fortran function as its second argument, or with a c_funloc instead. A third option added is to completely omit param both in addCallback, and in the callback function itself. This covers the case param is actually NULL.
And it turns out param=NULL is the most common case, since the user will probably need to pass Fortran classes to the actual callback function, and doing so is problematic if we use param. This is because said classes won’t be C-interoperable in the most general case, and it’s much easier to just pass additional information the callback function might need “the Fortran way”, that is, by “use-ing” modules.
For the same reason, it made little to no sense to add special cases, such as param is an integer, a real number, etc. Even if this is the case, extracting that information from a generic c_ptr is just a c_f_pointer away.

So, the best answer to the question in the title of this thread is… it depends; type(*) preferably, but don’t hesitate to use c_ptr as well, if it simplifies things. I’m going to mark @FortranFan’s suggestion as solution. It’s not the most elegant solution I was hoping it exists and I just don’t see it, but it is the best solution possible. And, to be honest, I didn’t expect anything better could be possible. Like I said right away in the beginning this was not a problem, but rather a question of programming style, and having other Fortraners` opinions was indeed quite interesting and productive.