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.