I’ve into an odd problem with the classic Intel compiler. It doesn’t seem to be an issue with other compilers, and I believe I have a workaround that works for all compilers, but it seems to go against the standard. The main issue is trying to pass around data from C to Fortran and back to C. Fortran doesn’t modify the data, it just passes it along to a callback function. Here’s a minimal example:
mymodule.f90
module mymodule_mod
implicit none
private
public :: callback_wrapper
abstract interface
subroutine CCALLBACK(data_ptr) bind(C)
use, intrinsic :: iso_c_binding, only : C_PTR
implicit none
type(C_PTR), value :: data_ptr ! If I remove 'value' here and down below, it works.
end subroutine CCALLBACK
end interface
contains
subroutine callback_wrapper(mycallback, data_ptr) bind(C)
use, intrinsic :: iso_c_binding, only : C_FUNPTR, C_F_PROCPOINTER, C_LOC, C_PTR
implicit none
type(C_FUNPTR), intent(in), value :: mycallback
type(C_PTR), intent(in), value :: data_ptr ! If I remove 'value' here and above, it works.
call callback_closure()
contains
subroutine callback_closure()
use, intrinsic :: iso_c_binding, only : C_INT, C_DOUBLE, C_F_PROCPOINTER
implicit none
procedure(CCALLBACK), pointer :: cb_ptr
call C_F_PROCPOINTER(mycallback, cb_ptr)
call cb_ptr(data_ptr)
end subroutine callback_closure
end subroutine callback_wrapper
end module mymodule_mod
main.c
#include <stdio.h>
// Fortran function typedefs and declarations
typedef void (*mycallback_t)(void*);
void callback_wrapper(mycallback_t mycallback, void* data);
int mydata = 240;
void * mydata_ref = &mydata;
// C callback function to be called by fortran code
void c_callback(void * data) {
// I would expect diff to be 0 always
printf("data pointer %p, mydata_ref %p, diff %lu\n", data, mydata_ref, mydata_ref-data);
}
int main(int argc, char * argv[]){
callback_wrapper(&c_callback, mydata_ref);
}
build_ifort.sh
ifort -g -fPIC -c mymodule.f90
cc -g -o main.o -c main.c
cc --g o main_ifort main.o mymodule.o -lifcoremt
build_gfortran.sh
gfortran -g -c mymodule.f90
gfortran -g -o main_gfortran main.c mymodule.o
By removing the value
attribute from type(C_PTR) :: data_ptr
it seems to work across both compilers as well as with flang, but the docs recommend using value
when dealing with void *
.
Any ideas as to why this is happening with ifort, whether or not removing value
is “kosher”, or any other workarounds that don’t go against what documentation suggests?
I should add that if I have the closure capture cb_ptr
instead of capturing mycallback
(i.e. call C_F_PROCPOINTER in the parent function), then it seems to work, but the new Intel fortran compiler ifx chokes hard on this (meaning some versions segfault when trying to compile with a closure that captures a procedure pointer as opposed to capturing a type(C_FUNPTR)).