Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
28467 Discussions

segfaults with iso_c_binding (inconsistent data sizes?)

AlexRichert-RedLine
1,030 Views

With ifx, I am seeing segfaults that I don't get with other compilers when using a C-based executable to call a Fortran function defined through bindings. The following is the Fortran code defining the C function:

module bufr_c2f_interface
use iso_c_binding
implicit none
private
public :: ibfms_c
contains
function ibfms_c(r8val) result(ires) bind(C, name='ibfms_f')
real(c_double), intent(in), value :: r8val
integer(c_int) :: ires
integer :: ibfms
ires = ibfms(r8val)
end function ibfms_c
end module bufr_c2f_interface

 The following is the definition of the 'ibfms' Fortran function (modv_bmiss provides the BMISS variable, that's it):

INTEGER FUNCTION IBFMS ( R8VAL )
USE MODV_BMISS
REAL*8 R8VAL
IF ( R8VAL .EQ. BMISS ) THEN
IBFMS = 1
ELSE
IBFMS = 0
ENDIF
RETURN
END

 Here is main() from the C code calling the 'ibfms_f' function:

int main() {
int jj;
double r8arr[180][15];
for ( jj = 0; jj < 11; jj++ ) {
r8arr[0][jj] = 1.0;
if ( ibfms_f( r8arr[0][jj] ) ) {
printf( "%s\n", "ibfms check FAILED!" );
exit(1);
}
}
}

 The segfault happens when it attempts to access R8VAL in the 'IF ( R8VAL .EQ. BMISS ) THEN' line:

(gdb) bt
#0 0x000000000040487b in ibfms (r8val=<error reading variable: Cannot access memory at address 0x1>) at /n/NCEPLIBS_CI_Updates_Nov2023/bufrtestcaseoneapi/src/ibfms.f:34
#1 0x0000000000404770 in main () at /n/NCEPLIBS_CI_Updates_Nov2023/bufrtestcaseoneapi/test/test_c_interface_2.c:13

I can resolve the segfault by modifying ibfms_f, changing 'ires = ibfms(r8val)' to 'ires = ibfms(real(r8val,kind=8))', but this doesn't make sense to me, because ostensibly 'c_double' and 'real*8' should be the same size. Am I missing something? For what it's worth, I tested building the Fortran component with ifort and the C component still with icx, and that resolved it, so whatever the difference between compilers is, I'm fairly certain it's something on the Fortran side. I have tried this with a couple of ifx versions including 2024.0 and they all give the same behavior.

11 Replies
Barbara_P_Intel
Moderator
993 Views

Can you please provide the module MODV_BMISS and anything it depends on?

 

0 Kudos
AlexRichert-RedLine
977 Views

Here's the module definition (no further dependencies):

module modv_bmiss
!> Current placeholder value to represent "missing" data when reading
!> from or writing to BUFR files; this value can be changed at any
!> time via a call to subroutine setbmiss().
real*8, public :: BMISS = 10E10_8
end module modv_bmiss

 

0 Kudos
Barbara_P_Intel
Moderator
968 Views

Thank you for that Fortran module.

That C mainline doesn't compile. I could try to fix it, but I may not do what you intend. Can you please update it?

Are you using any special compiler options?

Thanks.



0 Kudos
AlexRichert-RedLine
957 Views

Sorry for not providing a complete setup, I'll do so here:

 

Build steps:

export CC="icx -g -traceback"
export FC="ifx -g -traceback"
${FC:?} -c ibfms.f -o ibfms.o
${FC:?} -c bufr_c2f_interface.F90 -o bufr_c2f_interface.o
/usr/bin/rm -f libbufr.a
/usr/bin/ar qc libbufr.a ibfms.o bufr_c2f_interface.o
${CC:?} -c test_c_interface_2.c -o test_c_interface_2.c.o
${CC:?} test_c_interface_2.c.o -o test_c_interface.x libbufr.a
# Expected segfault:
./test_c_interface.x

 

test_c_interface_2.c:

#include <stdio.h>
#include <stdlib.h>

int ibfms_f(double r8val);

int main() {
int jj;
double r8arr[180][15];
for ( jj = 0; jj < 11; jj++ ) {
r8arr[0][jj] = 1.0;
if ( ibfms_f( r8arr[0][jj] ) ) {
printf( "%s\n", "ibfms check FAILED!" );
exit(1);
}
}
}

 

bufr_c2f_interface.F90:

module bufr_c2f_interface

use iso_c_binding
implicit none
private
public :: ibfms_c

contains
function ibfms_c(r8val) result(ires) bind(C, name='ibfms_f')
real(c_double), intent(in), value :: r8val
integer(c_int) :: ires
integer :: ibfms
ires = ibfms(r8val)
end function ibfms_c

end module bufr_c2f_interface

 

ibfms.f:

        INTEGER FUNCTION IBFMS ( R8VAL )

REAL*8 :: BMISS = 10E10_8
REAL*8 R8VAL

IF ( R8VAL .EQ. BMISS ) THEN
IBFMS = 1
ELSE
IBFMS = 0
ENDIF

RETURN
END

 

0 Kudos
Barbara_P_Intel
Moderator
924 Views

Thank you for all the details, @AlexRichert-RedLine! I filed a bug report, CMPLRLLVM-54110, We'll let you know its progress to a fix.



Barbara_P_Intel
Moderator
838 Views

One of the Fortran compiler team members has a workaround for you.

module bufr_c2f_interface

use iso_c_binding
implicit none
private
public :: ibfms_c

contains
function ibfms_c(r8val) result(ires) bind(C, name='ibfms_f')
real(c_double), intent(in), value :: r8val
integer(c_int) :: ires
!integer :: ibfms
interface
    integer function ibfms(a)
        use iso_c_binding
        real(c_double), intent(in) :: a
    end function 
end interface

ires = ibfms(r8val)
end function ibfms_c

end module bufr_c2f_interface

 

0 Kudos
AlexRichert-RedLine
823 Views

Thanks Barbara. Do you have a sense yet of how far off a fix to the compiler might be? For the moment it's not out of the question to wait for a fix in order to keep the code clean (we have a fair number of these cases in our code).

0 Kudos
Barbara_P_Intel
Moderator
795 Views

Sorry, I don't have an estimate as to when the fix will be available. I don't know how complicated the implementation is.



0 Kudos
AlexRichert-RedLine
327 Views

Do we have any update on the progress of this issue?

0 Kudos
Barbara_P_Intel
Moderator
267 Views

The compiler engineer reports that the fix is in review.

I don't know if will make the code cutoff for 2024.2 which is next week. (fingers-crossed)

0 Kudos
Barbara_P_Intel
Moderator
118 Views

This issue with iso_c_binding is fixed in the 2024.2 compiler. This release is planned for mid-2024.



0 Kudos
Reply