On Linux moving 32 bit program to 64 bit: 3 segmentation faults for invalid memory references (malloc?)

This particular error message may very much have something to do with your include file, ref: line that has INCLUDE "STUFF". What is in it?

Here’s a option you can consider given your opening line “The program runs perfectly on 32 bit Linux”.

  • Since you cannot post your employer’s actual code, learn enough of it to create a model (a mock up / prototype) which does not have any proprietary details but only enough of the C ↔ Fortran interoperability aspects in it that mimic as closely as possible the employer’s program
  • Then get a working version of it “on 32-bit Linux” which goes with your line, “The program runs perfectly on 32 bit Linux”
  • Now try it on “64-bit Linux” and get to the stage where you can reproduce the segmentation fault with this minimal example as you encounter with your employer’s program
  • Post this reproducer on online forums such as this one.
4 Likes

First, I don’t think this is standards conforming C. func_ is supposed to return an integer, but does not. Next, I’m not as familiar with C, but I presume the syntax should be

struct my_data2 {
  int value;
};

int func_(my_data2** dest, my_data2* src) {
  (*dest)->value = src->value;
 return;
}

Now, the Fortran interface to this function would be

interface
  function func(dest, src) result(res) bind(C, name='func_')
    import :: c_int, c_ptr
    type(c_ptr), intent(in), value :: DEST
    type(c_ptr), intent(in), value :: src
    integer(c_int) :: res
  end function
end interface

As far as Fortran is concerned, a C pointer is a C pointer, whether it points to another pointer or not.

Wrapping this is a bit more involved and seems to require changes both on the C and Fortran side. An example is given below. I agree that it would be preferable to work just with type(c_ptr) rather than integer(c_intptr_t), having the integer representation of the pointer address doesn’t really make it more transparent than dealing with an opaque pointer to begin with.

Example Fortran/C interop for malloc/free

The C function we want to wrap using pointer to pointer

// file: malloc.c
#include <stdlib.h>
#include <stdio.h>
#include <stdint.h>

int
mallocate_float(float** addr, int* mfloat)
{
   int stat = 0;

   if (!*addr) {
      *addr = (float*) malloc(sizeof(float)*(*mfloat));
   } else {
      *addr = (float*) realloc(*addr, sizeof(float)*(*mfloat));
   }

   if (!*addr) {
      stat = -1;
   } else {
      for(int i = 0; i < *mfloat; i++) {
         (*addr)[i] = *mfloat - i;
      }
   }

   return stat;
}

int
free_float(float** addr)
{
   int stat = 0;

   if (*addr) {
      free(*addr);
      *addr = NULL;
   } else {
      stat = -1;
   }

   return stat;
}

Fortran/C interoperable code storing our points as actual integer.

! file: malloc.f90
module mallocator
   implicit none
contains
subroutine example
   use, intrinsic :: iso_c_binding
   integer(c_intptr_t) :: addr
   integer(c_int) :: mfloat
   integer(c_int) :: stat

   interface
      function mallocate_float(addr, mfloat) result(stat) bind(c)
         import :: c_intptr_t, c_int
         integer(c_intptr_t), intent(in) :: addr
         integer(c_int), intent(in) :: mfloat
         integer(c_int) :: stat
      end function mallocate_float

      function free_float(addr) result(stat) bind(c)
         import :: c_intptr_t, c_int
         integer(c_intptr_t), intent(in) :: addr
         integer(c_int) :: stat
      end function free_float
   end interface

   ! allocate memory in C
   addr = 0
   mfloat = 10
   stat = mallocate_float(addr, mfloat)
   print '(*(g0))', "stat = ", stat

   ! check if addr actual contains the expected data
   block
      type(c_ptr) :: ptr
      real(c_float), pointer :: areal(:)
      ptr = transfer(addr, ptr)

      call c_f_pointer(ptr, areal, [mfloat])
      print '(*(g0, 1x))', "areal(:) = [", areal(:), "]"
   end block

   ! call free function in C
   stat = free_float(addr)
   print '(*(g0))', "stat = ", stat
end subroutine example
end module mallocator

program demo
   use mallocator
   implicit none

   call example
end program demo
❯ gfortran malloc.f90 malloc.c
❯ ./a,out
stat = 0
areal(:) = [ 10.0000000 9.00000000 8.00000000 7.00000000 6.00000000 5.00000000 4.00000000 3.00000000 2.00000000 1.00000000 ]
stat = 0
gdb and valgrind run
❯ gdb ./a.out
GNU gdb (GDB) 11.2
Copyright (C) 2022 Free Software Foundation, Inc.
License GPLv3+: GNU GPL version 3 or later <http://gnu.org/licenses/gpl.html>
This is free software: you are free to change and redistribute it.
There is NO WARRANTY, to the extent permitted by law.
Type "show copying" and "show warranty" for details.
This GDB was configured as "x86_64-pc-linux-gnu".
Type "show configuration" for configuration details.
For bug reporting instructions, please see:
<https://www.gnu.org/software/gdb/bugs/>.
Find the GDB manual and other documentation resources online at:
    <http://www.gnu.org/software/gdb/documentation/>.

For help, type "help".
Type "apropos word" to search for commands related to "word"...
Reading symbols from a.out...
(No debugging symbols found in a.out)
(gdb) run
Starting program: /home/awvwgk/projects/src/git/stuff/3128/a.out 
[Thread debugging using libthread_db enabled]
Using host libthread_db library "/usr/lib/libthread_db.so.1".
stat = 0
areal(:) = [ 10.0000000 9.00000000 8.00000000 7.00000000 6.00000000 5.00000000 4.00000000 3.00000000 2.00000000 1.00000000 ]
stat = 0
[Inferior 1 (process 45241) exited normally]
quit)
❯ valgrind ./a.out
==45251== Memcheck, a memory error detector
==45251== Copyright (C) 2002-2017, and GNU GPL'd, by Julian Seward et al.
==45251== Using Valgrind-3.18.1 and LibVEX; rerun with -h for copyright info
==45251== Command: ./a.out
==45251== 
stat = 0
areal(:) = [ 10.0000000 9.00000000 8.00000000 7.00000000 6.00000000 5.00000000 4.00000000 3.00000000 2.00000000 1.00000000 ]
stat = 0
==45251== 
==45251== HEAP SUMMARY:
==45251==     in use at exit: 0 bytes in 0 blocks
==45251==   total heap usage: 26 allocs, 26 frees, 21,996 bytes allocated
==45251== 
==45251== All heap blocks were freed -- no leaks are possible
==45251== 
==45251== For lists of detected and suppressed errors, rerun with: -s
==45251== ERROR SUMMARY: 0 errors from 0 contexts (suppressed: 0 from 0)
</details>

This is not how you use a function in Fortran. Only subroutines can be called this way. The return value of the function has to go somewhere; passed as an intent(in) argument to another procedure, as a value in some expression, assigned to a variable, etc.

This is exactly why your original code is non-conforming. You are passing a Fortran default integer to a procedure that expects a C pointer. Now that you’ve provided an interface to the Fortran compiler that matches the C function, it can tell you about the mismatch.

The answer to that question depends highly on context. What is the intended behavior of the program? It looks like you’re trying to do pointer arithmetic on the Fortran side. You shouldn’t do that. You should do the pointer arithmetic on the C side. You probably want a new C function for that.

Maybe something like

void* with_offset(void* orig, int offset, int factor) {
  return orig + offset*factor;
}
interface
  function with_offset(orig, offset, factor) result(new_pointer) bind(C, name='with_offset')
    import :: c_ptr, c_int
    type(c_ptr), intent(in), value :: orig
    type(c_int), intent(in), value :: offset, factor
    type(c_ptr) :: new_pointer
  end function
end interface

type(c_ptr) :: the_addr
integer(c_int) :: x

if (func(with_offset(the_addr, x, 2_c_int), 0) /= 0) then

Of course I’m not as confident on the C side if that’s valid.

I’m guessing you meant integer(c_int). c_ptr is not a valid kind value for integer.

This is why I don’t play “guess the source code”.

5 Likes

@giraffe,

Please see the nice and valuable example by @awvwgk . I suggest you take a close look at it and try it out and see what you can apply from it.

Note the advice, "it would be preferable to work just with type(c_ptr) rather than integer(c_intptr_t) ".

But it appears you somehow are capturing memory addresses in an integer type and trying to work them using C_INT which, as advised to you upthread, will not work on 64-bit environments.

If the above is not clear, try to take a close look at the following C and Fortran examples and try them out on both your 32-bit Linux and 64-bit Linux environments and see the program behavior.

  • C code (say in c.c file) using your struct mydata_2 and func_:
Click to see
#include <stdio.h>

#define A 2
#define B 3

typedef struct my_data2 {
   int value;
} DAT;

int func_(DAT **, DAT *);
extern void Fsub();

int main ()
{

   int i;
   int j;
   DAT dat[A][B];
   DAT foo;

   for (i = 0; i < A; i++)
   {
      for (j = 0; j < B; j++)
      {
         dat[i][j].value = i*B+j;
      }
   }

   printf("Before _func call:\n");
   for (i = 0; i < A; i++)
   {
      for (j = 0; j < B; j++)
      {
         printf("dat[%d][%d].value = %d\n", i, j, dat[i][j].value);
      }
   }

   foo.value = 42;
   DAT *THE_ADDR, *x;
   int N = 1;
   THE_ADDR = dat[0];
   x = THE_ADDR+N*2;
   func_(&x, &foo);
   printf("bar.value = %d\n", bar.value);

   printf("After _func call:\n");
   for (i = 0; i < A; i++)
   {
      for (j = 0; j < B; j++)
      {
         printf("dat[%d][%d].value = %d\n", i, j, dat[i][j].value);
      }
   }

   Fsub();

   return 0;
}

int func_( DAT **dest, DAT *src )
{
  (*dest)->value=src->value;
  return 0;
}
  • Fortran code (say in f.f90 file) working with your C struct mydata_2 and C func_
Click to see
module m
   use, intrinsic :: iso_c_binding, only : c_int, c_ptr, c_loc, c_intptr_t
   interface
      function func(dest, src) result(r) bind(C, name="func_")
         import :: c_int, c_ptr
         ! Argument list
         type(c_ptr), intent(in)        :: dest(*)
         type(c_ptr), intent(in), value :: src
         ! Function result
         integer(c_int) :: r
      end function
   end interface
   type, bind(C) :: my_data2
      integer(c_int) :: value
   end type
contains
   subroutine Fsub() bind(C, name="Fsub")
      ! Local variables
      type(my_data2), target :: dat(2,3)
      type(my_data2), target :: foo
      type(c_ptr) :: addr
      integer :: i, j, idx
      integer :: N
      integer(c_intptr_t) :: THE_ADDR(size(dat))
      do i = 1, size(dat,dim=2)
         do j = 1, size(dat,dim=1)
            idx = j + (i-1)*size(dat,dim=1)
            dat(j,i)%value = idx
            THE_ADDR(idx) = transfer( source=c_loc(dat(j,i)), mold=THE_ADDR(1) )
         end do
      end do
      print *, "In Fortran subroutine:"
      print *, "Before func_invocation", dat
      foo%value = 42
      N = 1
      addr = transfer( source=THE_ADDR(1+N*2), mold=addr )
      i = func( dest=[addr], src=c_loc(foo) )
      print *, "Before func_invocation", dat
   end subroutine
end module
  • The expected program behavior is as follows:
Click to see

C:\temp>gfortran -c c.c

C:\temp>gfortran -c f.f90

C:\temp>gfortran c.o f.o -o c.exe

C:\temp>c.exe
Before _func call:
dat[0][0].value = 0
dat[0][1].value = 1
dat[0][2].value = 2
dat[1][0].value = 3
dat[1][1].value = 4
dat[1][2].value = 5
bar.value = 0
After _func call:
dat[0][0].value = 0
dat[0][1].value = 1
dat[0][2].value = 42
dat[1][0].value = 3
dat[1][1].value = 4
dat[1][2].value = 5
In Fortran subroutine:
Before func_invocation 1 2 3 4 5 6
Before func_invocation 1 2 42 4 5 6

1 Like

@giraffe ,

With the C and Fortran exampIe in the previous post, note a few points:

  1. The INTERFACE setting in Fortran can be as follows:
   interface
      function func(dest, src) result(r) bind(C, name="func_")
         ! C prototype as follows 
         ! typedef struct my_data2 {
         !    int value;
         ! } DAT;
         ! 
         ! int func_(DAT **, DAT *)
         import :: c_int, c_ptr
         ! Argument list
         type(c_ptr), intent(in)        :: dest(*)
         type(c_ptr), intent(in), value :: src
         ! Function result
         integer(c_int) :: r
      end function
   end interface
  1. Note the call on the Fortran side:
      ..
      addr = transfer( source=THE_ADDR(1+N*2), mold=addr )
      i = func( dest=[addr], src=c_loc(foo) )
      ..

So if you cannot follow earlier advice but you need to work with integer types for memory addresses, then try to do as advised by @everythingfunctional which is no pointer arithmetic in Fortran. Instead, locate the memory addresses (the above example does so by calls to C_LOC on the source data) and place in an integer type of kind c_intptr_t and do the TRANSFER operation to “cast” it to type(c_ptr) prior to invoking the C function in a rank-1 object. So note again the line

i = func( dest=[addr], src=c_loc(foo) )

Now if you replace the c_intptr_t with c_int, you will find it work on 32-bit systems but segfault on 64-bit ones. Once you start to track this aspect in your employer code, you will find how to resolve the issues. Note of course, this is only based on the information you have shared thus far.

P.S.> In all of above, I presume you have a use case to work with rank-2 objects of your mydata_2 struct and that is why you have the pointer to pointer (mydata_2 **) parameter in the C function. And that is why the above examples use rank-2 objects.

2 Likes

It’s starting to look like you’re just throwing stuff at the compiler to see what sticks without actually trying to understand what any of it means. That’s a recipe to end up right back in the same situation; it works, but only incidentally, not based on any sound foundations. You then won’t be able to understand why it suddenly doesn’t work when you change something.

I would be happy to work with you more closely and help you figure this out if you are willing to hire me as a contractor, but this roundabout way of working will take up way too much of both of our time.

5 Likes

@everythingfunctional and any other interested readers,

Re: “As far as Fortran is concerned, a C pointer is a C pointer, whether it points to another pointer or not.” note that is not the case.

Note a pointer to a pointer as a C function parameter can require the interface in Fortran to not have the VALUE attribute if the pointer is additionally dereferenced in C like as shown in OP’s snippet with (*dest)->value.

The INTERFACE in Fortran under such circumstances will be along the following lines where the current context is used as an example

   interface
      function func(dest, src) result(r) bind(C, name="func_")
         import :: c_int, c_ptr
         ! Argument list
         type(c_ptr), intent(in)        :: dest  !<-- No VALUE attribute
         type(c_ptr), intent(in), value :: src
         ! Function result
         integer(c_int) :: r
      end function
   end interface

Here is a somewhat stripped version of my earlier example if anyone wants to try it out to learn:

Click to see
#include <stdio.h>

typedef struct my_data2 {
   int value;
} DAT;

int func_(DAT **, DAT *);
extern void Fsub();

int main ()
{
   DAT foo;
   DAT bar;
   foo.value = 42;
   DAT *baz = &bar;
   func_(&baz, &foo);
   printf("In C main: bar.value = %d; expected is %d\n", bar.value, foo.value);
   Fsub();
   return 0;
}

int func_( DAT **dest, DAT *src )
{
  (*dest)->value=src->value;
  return 0;
}
  • Fortran code
module m
   use, intrinsic :: iso_c_binding, only : c_int, c_ptr, c_loc
   interface
      function func(dest, src) result(r) bind(C, name="func_")
         import :: c_int, c_ptr
         ! Argument list
         type(c_ptr), intent(in)        :: dest
         type(c_ptr), intent(in), value :: src
         ! Function result
         integer(c_int) :: r
      end function
   end interface
   type, bind(C) :: my_data2
      integer(c_int) :: value
   end type
contains
   subroutine Fsub() bind(C, name="Fsub")
      ! Local variables
      type(my_data2), target :: foo
      type(my_data2), target :: bar
      foo%value = 42
      i = func( dest=c_loc(bar), src=c_loc(foo) )
      print *, "In Fortran sub: bar%value = ", bar%value, "; expected is ", foo%value
   end subroutine
end module
  • Expected program behavior

C:\temp>gfortran -c c.c

C:\temp>gfortran -c f.f90

C:\temp>gfortran c.o f.o -o c.exe

C:\temp>c.exe
In C main: bar.value = 42; expected is 42
In Fortran sub: bar%value = 42 ; expected is 42

1 Like

That shouldn’t make any difference. Here’s a demo:

PROGRAM DEMO

IMPLICIT NONE

CALL V1()
CALL V2()

CONTAINS

SUBROUTINE V1()
INTEGER THE_ADDR
PRINT *, KIND(THE_ADDR)
END SUBROUTINE

SUBROUTINE V2()
INTEGER * 4 THE_ADDR    ! <-- non-standard extension
PRINT *, KIND(THE_ADDR)
END SUBROUTINE

END PROGRAM

Those integers have the same kind, unless you are using a nasty compiler flag like -fdefault-integer-8, which you really should not be doing. Here’s the output from program above:

$ gfortran demo.f90 
$ ./a.out
           4
           4

This thread seems a lot like an XY problem. It would probably be good to take a step back, and explain what you expect the program to do.

It will not. integer * 4 is not standard Fortran, is not different from integer in most cases, and can not hold a 64 bit address, since it is only 32 bits. You have to change the declaration of the_addr to type(c_ptr) :: the_addr and then the code will work on both 32 and 64 bit machines.

This might work, but then the program won’t work on 32 bit systems, and is still not standard Fortran.

1 Like

Syntax such as integer*8 or real*8 has never been endorsed in a Fortran standard. Here is a code showing two alternatives:

program main
use iso_fortran_env, only: int64
implicit none
integer*8 :: i ! non-standard
integer (kind=8) :: j ! non-portable, since some compilers may support 64-bit integers 
                      ! but not use kind=8 for them
integer (kind=int64) :: k ! portable
print*,kind(i),kind(j),kind(k)
end program main
1 Like

An additional reason that it is not standards conforming is that without the iso_c_binding module, even if you provide an explicit interface (and if you don’t an interface is assumed), it does not actually match the interface of the C function.

As an example

program
  interface
    subroutine print_it(var)
      integer, intent(in) :: var
    end subroutine
  end interface

  call print_it(0)
end program

subroutine print_it(var)
  real, intent(in) :: var
  print *, var
end subroutine

might actually print 0.0, but that is completely incidental and isn’t a standards conforming program.