Problem with ifort compiler and type(C_PTR)

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)).

I wanted to try this myself, but MSVC complained about the printf line:
E0852|expression must be a pointer to a complete object type
C2036|‘void *’: unknown size

I commented out the printf and tried to figure out what is happening.

In 32-bit ifort, it is messing up the call to cb_ptr, passing cb_ptr as the argument instead of data_ptr. That is weird and is a bug.

However, ifx (64-bit only) does this correctly, from what I can see, so try that.

1 Like

The problem appears to be related with the closure. With gcc/gfortran on MacOS, it works correctly:

$ make cmain && ./cmain
gfortran -Wall -c mymodule.f90
gcc-13 -Wall  -o cmain main.c mymodule.o 
value = 240
data pointer 0x101471028, mydata_ref 0x101471028, diff 0

If I move the content of the closure into the body of the callback_wrapper I see the desired behavior with all compiler combinations:

$ make cmain && ./cmain
gfortran -Wall -c mymodule.f90
gcc-13 -Wall  -o cmain main.c mymodule.o 
value = 240
data pointer 0x102f37028, mydata_ref 0x102f37028, diff 0
$ make cmain FC=ifort FCFLAGS="-warn all" CC=icc CFLAGS="-Wall -std=c99 -diag-disable=10441" LDLIBS=-lifcore && ./cmain
ifort -warn all -c mymodule.f90
icc -Wall -std=c99 -diag-disable=10441  -o cmain main.c mymodule.o -lifcore
value = 240
data pointer 0x109b2c090, mydata_ref 0x109b2c090, diff 0
$ make cmain FC=ifort FCFLAGS="-warn all" CC=clang CFLAGS="-Wall -std=c99" LDFLAGS=-L/opt/intel/oneapi/lib LDLIBS="-lifcore" && ./cmain
ifort -warn all -c mymodule.f90
clang -Wall -std=c99 -L/opt/intel/oneapi/lib -o cmain main.c mymodule.o -lifcore
value = 240
data pointer 0x108391020, mydata_ref 0x108391020, diff 0

Note, I added the following two lines into the c_callback function:

    const int *i = (int *) data;
    printf("value = %d\n", *i);
1 Like

Here is a reproducer entirely in Fortran: Compiler Explorer. (Interestingly, ifx doesn’t seem to need an executable stack.)

It appears to be a regression in ifort. With ifort 19.0.0 (the oldest available on Compiler Explorer) it was working correctly.

Addendum: for workarounds, you could either move the callback conversion out of the internal procedure (as you already suggested),

! Workaround #1
!
subroutine callback_wrapper(mycallback, data_ptr) bind(C)
    type(c_funptr), value :: mycallback
    type(c_ptr), value :: data_ptr

    procedure(ccallback), pointer :: cb_ptr => null()
    call c_f_procpointer(mycallback, cb_ptr)
    
    call callback_closure
contains
    subroutine callback_closure
        call cb_ptr(data_ptr)
    end subroutine
end subroutine callback_wrapper

or, pass at least the function pointer explicitly as a dummy argument,

! Workaround #2
!
subroutine callback_wrapper(mycallback, data_ptr) bind(C)
    type(c_funptr), value :: mycallback
    type(c_ptr), value :: data_ptr

    call callback_closure(mycallback)
contains
    subroutine callback_closure(mycallback)
        type(c_funptr), intent(in) :: mycallback ! with value or without, both work here
        procedure(ccallback), pointer :: cb_ptr => null()
        call c_f_procpointer(mycallback, cb_ptr)
        call cb_ptr(data_ptr)
    end subroutine
end subroutine callback_wrapper

But I believe the evidence points toward this being a compiler bug.

2 Likes

Thanks for the replies folks. Moving C_F_PROCPOINTER up into callback_wrapper gave me issues with ifx, although I’m having trouble producing a minimum working example at the moment.* Unfortunately I can’t do workaround 2 either because in actual fact I want the closure to be passed to a Fortran function and I’d like for the signature of the closure to note have anything to do with C interop. Given that ifort will soon not be supported we might just drop support for it altogether.

Something I’m curious about though, is that fact that it works in gfortran and other compilers when both value attributes are removed. Is this a bug or intended behavior?

* Edit: Managed to get a working example, the key was adding the “-assume recursive” flag: Strange issue with ifx compiler and '-assume recursion'"

1 Like

For those who are interested, the problem arises when we add a callback to the C interface of PRIMA. See

1 Like

When you look at a diff view of the assembly between ifort 19.0.0 (works) and ifort 2021.1.2 (doesn’t work), Compiler Explorer, the difference is a single line:

ifort 19.0.0

..B3.2:                         # Preds ..B3.1
        mov       rax, QWORD PTR callback_closure$CB_PTR$_7[rip] #29.14
        mov       rdx, QWORD PTR [-8+rbp]                       #29.14
        mov       rdx, QWORD PTR [8+rdx]                        #29.14
        mov       rdi, rdx                                      #29.14
        call      rax              

ifort 2021.1.2

..B3.2:                         # Preds ..B3.1
        mov       rax, QWORD PTR callback_closure$CB_PTR$_7[rip] #29.14
        mov       rdx, QWORD PTR [-8+rbp]                       #29.14
        mov       rdx, QWORD PTR [rdx]                          #29.14    # in ifort 19.0.0 [8+rdx]
        mov       rdi, rdx                                      #29.14
        call      rax      

So it looks like a wrong offset while copying the value into the registers.

3 Likes

@actinium226 ,

Your post caught my eye as I had a quick glance at this forum after ages; a team at work who collaborates with me uses the callback approach in a similar pattern from one of their last Fortran libraries and which is primarily consumed by C-like companion processors. Should there be an issue with IFORT / IFX, then what I had consulted with them re: their callback pattern from Fortran could prove faulty and thus it raised an alarm for me.

Looking into this further, I reckon this is a bug with IFORT which you may want to post at the Intel Fortran forum for attention of Intel Software Support team. I don’t see an issue with IFX though I am behind the times and have not tried the latest update.

Below is a silly example that might be of help to you to further demonstrate the issue to Intel team in case the issue persists in their latest release.

As illustrated nicely by @ivanpribec using disassembly, the issue is the wrong offset when the callback is before the data in the order of parameters (arguments) in the Fortran subprogram i.e., in one of the four scenarios I looked at based on your original post.

Click to see example code
  • C main program
#include <stdio.h>

typedef void (*Icallback)(const void *);

void FortranFunc1( Icallback, void * );
void FortranFunc2( Icallback, void * );
void FortranFunc3( Icallback, void * );
void FortranFunc4( void *, Icallback );

void callback(const void *dat) {
   printf("In callback, data at address: %p\n", dat);
}

int main( void ) {
    int foo = 42;
    void *pfoo = &foo;
    printf("In main: &foo = %p\n", pfoo);
    FortranFunc1( (Icallback)callback, pfoo ); 
    FortranFunc2( (Icallback)callback, pfoo ); 
    FortranFunc3( (Icallback)callback, pfoo );  //<-- issue with IFORT
    FortranFunc4( pfoo, (Icallback)callback ); 
    return 0; 
}
  • Fortran library code
module m
   use, intrinsic :: iso_c_binding, only : c_ptr, c_funptr, c_f_procpointer
   abstract interface
      subroutine Icallback( pdat ) bind(C)
         import :: c_ptr
         type(c_ptr), value :: pdat
      end subroutine
   end interface
contains
   subroutine FortranFunc1( pcallback, pdat ) bind(C, name="FortranFunc1")
      procedure(Icallback) :: pcallback
      type(c_ptr), intent(in), value :: pdat
      call pcallback( pdat )  
   end subroutine
   subroutine FortranFunc2( pfunc, pdat ) bind(C, name="FortranFunc2")
      type(c_funptr), intent(in), value :: pfunc
      type(c_ptr), intent(in), value :: pdat
      procedure(Icallback), pointer :: pcallback
      call c_f_procpointer( cptr=pfunc, fptr=pcallback )
      call pcallback( pdat )  
   end subroutine
   subroutine FortranFunc3( pfunc, pdat ) bind(C, name="FortranFunc3")
      type(c_funptr), intent(in), value :: pfunc
      type(c_ptr), intent(in), value    :: pdat
      call closure()
   contains
      subroutine closure()
         procedure(Icallback), pointer :: pcallback
         call c_f_procpointer( cptr=pfunc, fptr=pcallback )
         call pcallback( pdat )  
      end subroutine 
   end subroutine
   subroutine FortranFunc4( pdat, pfunc ) bind(C, name="FortranFunc4")
      type(c_ptr), intent(in), value    :: pdat
      type(c_funptr), intent(in), value :: pfunc
      call closure()
   contains
      subroutine closure()
         procedure(Icallback), pointer :: pcallback
         call c_f_procpointer( cptr=pfunc, fptr=pcallback )
         call pcallback( pdat )  
      end subroutine 
   end subroutine
end module 
Program response using `IFX` on Windows:
C:\temp>cl /c /W3 c.c
Microsoft (R) C/C++ Optimizing Compiler Version 19.36.32537 for x64
Copyright (C) Microsoft Corporation.  All rights reserved.

c.c

C:\temp>ifx /c /standard-semantics /free m.f
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2023.2.0 Build 20230627
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.


C:\temp>link c.obj m.obj /subsystem:console /out:c.exe
Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation.  All rights reserved.


C:\temp>c.exe
In main: &foo = 000000F2402FFA90
In callback, data at address: 000000F2402FFA90
In callback, data at address: 000000F2402FFA90
In callback, data at address: 000000F2402FFA90
In callback, data at address: 000000F2402FFA90
Click to see the problematic response using `IFORT` in one instance
C:\temp>cl /c /W3 c.c
Microsoft (R) C/C++ Optimizing Compiler Version 19.36.32537 for x64
Copyright (C) Microsoft Corporation.  All rights reserved.

c.c

C:\temp>ifort /c /standard-semantics /free m.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.10.0 Build 20230609_000000
Copyright (C) 1985-2023 Intel Corporation.  All rights reserved.


C:\temp>link c.obj m.obj /subsystem:console /out:c.exe
Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation.  All rights reserved.


C:\temp>c.exe
In main: &foo = 00000044912FFA80
In callback, data at address: 00000044912FFA80
In callback, data at address: 00000044912FFA80
In callback, data at address: 00007FF65B181380
In callback, data at address: 00000044912FFA80
2 Likes