Segmentation Fault when trying to access pointer component of C struct

I wrote a small test to understand how C structs with pointers to arrays work when interfaced with Fortran. All works fine except I cannot access the array in the struct from Fortran. It produces a segmentation fault. Below is the Fortran side:

Either of the last two lines of struct.f90 gives the segmentation fault.

struct.f90

module mod_struct
  use iso_c_binding
  implicit none

  interface
    subroutine foo_bar( a ) bind(c, name="foo_bar")
      import:: c_ptr
      type(c_ptr), intent(inout) :: a
    end subroutine foo_bar
  end interface
end module mod_struct

program main
  use iso_c_binding
  use mod_struct
  
  type Foo
    type(c_ptr) :: cip
  end type Foo
  
  type(Foo), pointer :: fp
  integer(c_int), pointer :: arr(:)

  type(c_ptr) :: c
  call foo_bar( c )
  if ( .not. c_associated(c) ) print *, "C pointer call failed!!!"
  call c_f_pointer( c, fp )  
  if ( .not. associated(fp) ) print *, "c_f_pointer call failed!!!"

  if ( .not. c_associated( fp%cip ) ) print *, "Array in Fortran struct failed!!!"
  call c_f_pointer( fp%cip, arr, [2] )  

  if ( .not. associated(arr) ) print *, "Array c_f_pointer defininetly failed!!!"
  print *, "Array lower bound = ", lbound( arr ), " AND Array upper bound = ", ubound( arr )
  print *, "Array[0] = ", arr(1) !, " AND Array[1] = ", arr(2)   ! Produces seg fault
  print *, "Array = ", arr  ! Produces seg fault
end program main

struct.h

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

typedef struct {
  int* arr;
} Foo;

void foo_bar( Foo* a);

struct.c

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

void foo_bar( Foo* a) {
  a->arr = malloc( 2 * sizeof(int) );
  a->arr[0] = 11;
  a->arr[1] = 1223;

  printf("a.arr[0] = %d and a.arr[1] = %d\n", a->arr[0], a->arr[1]);
}

@general_rishkin , please take a look at suggested changes below, particularly the lines marked “Note this” and the one with N.B.

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

typedef struct {
  int* arr;
  size_t n; //<--  Note this
} Foo;

void foo_bar( Foo* a);

void foo_bar( Foo* a) {
  a->n = (size_t)2; //<--  Note this
  a->arr = malloc( a->n * sizeof(int) );  //<--  Note this
  a->arr[0] = 11;
  a->arr[1] = 1223;

  printf("a.arr[0] = %d and a.arr[1] = %d\n", a->arr[0], a->arr[1]);
}
  use iso_c_binding
  interface
    subroutine foo_bar( a ) bind(c, name="foo_bar")
      import:: c_ptr
      type(c_ptr), intent(in), value :: a  !<-- N.B. Note this
    end subroutine foo_bar
  end interface
  
  type, bind(C) :: Foo   !<-- Note this
     type(c_ptr) :: cip
     integer(c_size_t) :: n    !<-- Note this
  end type Foo
  
  type(Foo), target :: fp   !<-- Note this
  integer(c_int), pointer :: arr(:)

  call foo_bar( c_loc(fp) )    !<-- Note this
  call c_f_pointer( fp%cip, arr, [ fp%n ] )   !<-- Note this

  if ( .not. associated(arr) ) print *, "Array c_f_pointer defininetly failed!!!"
  print *, "Array lower bound = ", lbound( arr ), " AND Array upper bound = ", ubound( arr )
  print *, "Array[0] = ", arr(1) !, " AND Array[1] = ", arr(2)   ! Produces seg fault
  print *, "Array = ", arr  ! Produces seg fault
end
C:\temp>gfortran -c -Wall c.c

C:\temp>gfortran -c -Wall p.f90

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

C:\temp>p.exe
a.arr[0] = 11 and a.arr[1] = 1223
 Array lower bound =            1  AND Array upper bound =            2
 Array[0] =           11
 Array =           11        1223

Thanks @FortranFan. This works fine now.

This might be a stupid question but why did you use the target attribute for type(Foo)?

type(Foo), target :: fp   !<-- Note this
1 Like

Fortran requires anything that is pointed to to have the TARGET attribute. The compiler then knows that anything that isn’t a target can’t be accessed via a pointer (and can’t be aliased).

In particular, it is a requirement of the C_LOC function.

result = C_LOC(x)
x (Input) Is a non-coindexed variable with the TARGET attribute. It must have interoperable type and type parameters, and it must be a non-polymorphic variable with no length type parameters, or an assumed-type variable.

EDIT: It isn’t a stupid question at all.

No such thing at all as a stupid question!! The idea was indeed to raise your eyebrows and wonder why it is needed when you can interoperate the struct/derived type directly! Try out the change below now!

  use iso_c_binding

  type, bind(C) :: Foo
     type(c_ptr) :: cip
     integer(c_size_t) :: n    !<-- Note this
  end type Foo
  
  interface
    subroutine foo_bar( a ) bind(C, name="foo_bar")
      import:: Foo
      type(Foo), intent(inout) :: a  !<-- Note this
    end subroutine foo_bar
  end interface
  
  type(Foo) :: fp   !<-- Note this
  integer(c_int), pointer :: arr(:)

  call foo_bar( fp )    !<-- Note this
  call c_f_pointer( fp%cip, arr, [ fp%n ] )   !<-- Note this

  if ( .not. associated(arr) ) print *, "Array c_f_pointer defininetly failed!!!"
  print *, "Array lower bound = ", lbound( arr ), " AND Array upper bound = ", ubound( arr )
  print *, "Array[0] = ", arr(1) !, " AND Array[1] = ", arr(2)   ! Produces seg fault
  print *, "Array = ", arr  ! Produces seg fault
end

Thanks @FortranFan. This works fine too and provides a more native interface.

Is there any reason to not prefer this approach to the other? Are there pitfalls lurking when interoperating the struct/derived type directly?

Thanks @DavidB.

You will know for direct interoperation (as in the second case I show upthread), the types must be interoperable which you declare with bind(C) clause on the derived types. Then pursuing standard-conforming code will help you avoid pitfalls.

As you will know, the other aspect with pitfalls has to do with the use of pointers and dynamic memory allocation on the C side of code. Here you will know to follow all the good practices with C since C gives coders a “long rope” and to get them all entangled and possibly “shoot” themselves badly in the process.

An option to consider is which “side of the fence” will do all the memory management, C or Fortran. Note “mix and match” can be rather problematic such as allocating memory on one side (say C) and freeing it on the other unless done with great care and attention.

This is definitely something to consider. Unfortunately, for the C library I am trying to wrap, I only have access to the binary and header files. So, all the dynamic memory allocation will be done on the C side with putative calls to C functions that free some allocated objects.

Could you help have a look at a new problem that I have, which I believe has a relation to dynamic memory management here. Thanks.