Practicing Fortran and C interoperability : Passing variable length array from Fortran to C and vice versa

Hello,
I am taking @everythingfunctional 's tutorial to the next level by practising all the tutorials from the learn-c website through Fortran’s interoperability and back .

I am trying to pass an array whose length is defined at runtime to C and back to Fortran however I have trouble bringing it back to Fortran after passing it to C. I am doing it this way to exercise C interoperability and learn it.
I get a segfault when trying to send it to C and back to Fortran
My code is as follows

arrays_experiment.c

#include <stdio.h>

 extern void average_calculator_fort_int(int * array);

int calculate_average_of_elements_int(int elements,int array[elements])
  {
    int sum_of_elements;
    sum_of_elements=0;

    for (int i=0;i<elements;i++)
    {
      sum_of_elements=sum_of_elements+array[i];
    }

    printf("The sum is: %d \n",sum_of_elements);
    return sum_of_elements/elements;
  }

void ask_fortran_too(int elements,int array[elements])
  {
    average_calculator_fort_int(array);
  }

averages_module.f90

module average_calculator
  use,intrinsic :: iso_c_binding,only: c_int
  implicit none
  private

  public :: average_calculator_c_int,ask_fortran_too

  interface
     pure function average_calculator_c_int(length,array) result(average_of_elements)&
          bind(C,name="calculate_average_of_elements_int")
       import c_int
       implicit none
       integer(kind=c_int),intent(in),value :: length
       integer(kind=c_int),intent(in) :: array(length)
       integer(kind=c_int) :: average_of_elements
     end function average_calculator_c_int
  end interface

  interface
     subroutine ask_fortran_too(array) bind(C,name="ask_fortran_too")
       import c_int
       implicit none
       integer(kind=c_int),dimension(:),intent(in) :: array
     end subroutine ask_fortran_too
  end interface


contains

  subroutine average_calculator_fort_int(array) bind(C)
    integer(kind=c_int),dimension(:),intent(in) :: array

    print "(a,1x,i0)", "Fortran says the sum is:",sum(array,1)
    print "(a,1x,i0)", "Fortran says the average is:",sum(array,1)/size(array)

  end subroutine average_calculator_fort_int

end module average_calculator

main.f90

program main
  use,intrinsic :: iso_c_binding,only: c_int
  use average_calculator,only: average_calculator_c_int,ask_fortran_too
  implicit none

  integer(kind=c_int),dimension(:),allocatable :: given_array
  integer(kind=c_int) :: given_size

  write(unit=*,fmt="(a,1x)",advance="no") "Please enter the number of elements in the array:"
  read *, given_size;allocate(given_array(given_size))
  write(unit=*,fmt="(a,1x)",advance="no") "Please enter the elements of the array:";read *, given_array

  print "(a,1x,i0)", "The average is:",average_calculator_c_int(given_size,given_array)

  call ask_fortran_too(given_array)

  deallocate(given_array)
end program main

Compiled with

gfortran -O3 arrays_experiment.c averages_module.f90 main.f90 -o average_calculator

run with

./average_calculator

the error I get :

Please enter the number of elements in the array: 3
Please enter the elements of the array: 80 85 90
The sum is: 255 
The average is: 85

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

Backtrace for this error:
#0  0x7ff018223a12 in ???
#1  0x7ff018222ba5 in ???
#2  0x7ff017f7fb1f in ???
#3  0x401327 in ???
#4  0x4017af in ???
#5  0x40113c in ???
#6  0x7ff017f6a50f in ???
#7  0x7ff017f6a5c8 in ???
#8  0x401174 in ???
#9  0xffffffffffffffff in ???
Segmentation fault (core dumped)

The array argument of ask_fortran_too and average_calculator_fort_int can’t be assumed shape to interoperate with a C array. You’ll need to make it either assumed size, or more likely, automatic size. I.e.

interface
     subroutine ask_fortran_too(array, n) bind(C,name="ask_fortran_too")
       import c_int
       implicit none
       integer(kind=c_int), intent(in), value :: n
       integer(kind=c_int),dimension(n),intent(in) :: array
     end subroutine ask_fortran_too
  end interface
1 Like

Thanks brad

here is what the code looks like after applying your solution
arrays_experiment.c

#include <stdio.h>

 extern void average_calculator_fort_int(int elements,int array[elements]);

int calculate_average_of_elements_int(int elements,int array[elements])
  {
    int sum_of_elements;
    sum_of_elements=0;

    for (int i=0;i<elements;i++)
    {
      sum_of_elements=sum_of_elements+array[i];
    }

    printf("The sum is: %d \n",sum_of_elements);
    return sum_of_elements/elements;
  }

void ask_fortran_too(int elements,int array[elements])
  {
    average_calculator_fort_int(elements,array);
  }

averages_module.f90

module average_calculator
  use,intrinsic :: iso_c_binding,only: c_int
  implicit none
  private

  public :: average_calculator_c_int,ask_fortran_too

  interface
     pure function average_calculator_c_int(length,array) result(average_of_elements)&
          bind(C,name="calculate_average_of_elements_int")
       import c_int
       implicit none
       integer(kind=c_int),intent(in),value :: length
       integer(kind=c_int),intent(in) :: array(length)
       integer(kind=c_int) :: average_of_elements
     end function average_calculator_c_int
  end interface

  interface
     subroutine ask_fortran_too(length,array) bind(C,name="ask_fortran_too")
       import c_int
       implicit none
       integer(kind=c_int),intent(in),value :: length
       integer(kind=c_int),dimension(length),intent(in) :: array
     end subroutine ask_fortran_too
  end interface


contains

  subroutine average_calculator_fort_int(length,array) bind(C)
    integer(kind=c_int),intent(in),value :: length
    integer(kind=c_int),dimension(length),intent(in) :: array

    print "(a,1x,i0)", "Fortran says the sum is:",sum(array,1)
    print "(a,1x,i0)", "Fortran says the average is:",sum(array,1)/size(array)

  end subroutine average_calculator_fort_int

end module average_calculator

main.f90

program main
  use,intrinsic :: iso_c_binding,only: c_int
  use average_calculator,only: average_calculator_c_int,ask_fortran_too
  implicit none

  integer(kind=c_int),dimension(:),allocatable :: given_array
  integer(kind=c_int) :: given_size

  write(unit=*,fmt="(a,1x)",advance="no") "Please enter the number of elements in the array:"
  read *, given_size;allocate(given_array(given_size))
  write(unit=*,fmt="(a,1x)",advance="no") "Please enter the elements of the array:";read *, given_array

  print "(a,1x,i0)", "The average is:",average_calculator_c_int(given_size,given_array)

  call ask_fortran_too(given_size,given_array)

  deallocate(given_array)
end program main

output :

Please enter the number of elements in the array: 3
Please enter the elements of the array: 80 85 90
The sum is: 255 
The average is: 85
Fortran says the sum is: 255
Fortran says the average is: 85

Is there anything else I can improve on ?

@Aurelius_Nero , yes. You can now move to enhanced interoperability with C facilities introduced in Fortran 2018.

With the code in the original post, you can retry with the following C “library” code:

#include <stdio.h>
#include "ISO_Fortran_binding.h"

extern void average_calculator_fort_int(CFI_cdesc_t *);

int calculate_average_of_elements_int(int elements,int array[elements]) {
   int sum_of_elements;
   sum_of_elements=0;

   for (int i=0;i<elements;i++)
   {
     sum_of_elements=sum_of_elements+array[i];
   }

   printf("The sum is: %d \n",sum_of_elements);
   return sum_of_elements/elements;
}

void ask_fortran_too(CFI_cdesc_t *array) {
   average_calculator_fort_int(array);
}

@everythingfunctional , you may want to update your tutorials to current standard as opposed to Fortran 2003 which is getting old.

1 Like

I believe my example mentioned CFI_cdesc_t, but treated it as a black box. It was really just a brief intro. If you want to get into advanced stuff you can start allocating and manipulating arrays from C, but I haven’t had time to put a tutorial together for that.

1 Like

Not exactly improvements, but rather a matter of style:

  • Is there a reason you deallocate given_array in main program? Allocatable arrays don’t need to be deallocated. It doesn’t hurt to manually deallocate them, it’s just not needed. This is not C… Try the program on valgrind with or without manual deallocation. You will see there is no memory leak either way.
  • I prefer not to use separate interfaces for each bind(c) procedure, but rather one interface for each group of similar procedures. In this case, the two bind(c) procedures in your module could be in one interface, for clarity. I see binding software using separate interfaces for every single procedure, and I honestly don’t see any reason it has to be like that.
  • Again, more like a matter of style, but in one procedure array is declared as array(length), in the other procedure you use the dimension attribute instead. I’d say, pick one style and use it everywhere. The latter is modern Fortran and that’s the one I would recommend.
1 Like

Will take this into consideration, thanks.

points 2 and 3 are noted, as for point 1
I commented out the deallocation and recompiled and used valgrind on it and this is what I got

==607677== Memcheck, a memory error detector
==607677== Copyright (C) 2002-2022, and GNU GPL'd, by Julian Seward et al.
==607677== Using Valgrind-3.20.0 and LibVEX; rerun with -h for copyright info
==607677== Command: ./average_calculator
==607677== 
Please enter the number of elements in the array: 3
Please enter the elements of the array: 80 85 90
The sum from C is: 255 
The average from C is: 85
Fortran says the sum is: 255
Fortran says the average is: 85
==607677== 
==607677== HEAP SUMMARY:
==607677==     in use at exit: 12 bytes in 1 blocks
==607677==   total heap usage: 31 allocs, 30 frees, 24,189 bytes allocated
==607677== 
==607677== LEAK SUMMARY:
==607677==    definitely lost: 12 bytes in 1 blocks
==607677==    indirectly lost: 0 bytes in 0 blocks
==607677==      possibly lost: 0 bytes in 0 blocks
==607677==    still reachable: 0 bytes in 0 blocks
==607677==         suppressed: 0 bytes in 0 blocks
==607677== Rerun with --leak-check=full to see details of leaked memory
==607677== 
==607677== For lists of detected and suppressed errors, rerun with: -s
==607677== ERROR SUMMARY: 0 errors from 0 contexts (suppressed: 0 from 0)

Ah yes, that’s probably because array is declared in the main program. When a procedure is terminated, any allocatable arrays declared there go out of scope, thus they are deallocated automatically (provided they don’t have the save attribute, of course - which I recommend you never use anyway.) This is standard Fortran 95+, and you don’t have to deallocate manually. However it seems automatic deallocation does not occur when an allocatable array is declared in the main program and goes out of scope by an end program statement.
To see for yourself, try to move everything from the main program to a subroutine, say test, then have the main program to just call test. You will see there is no memory leak, even without the deallocate statement. You may have array declared in the subroutine itself, or you may have it declared in a module, together with the test subroutine. In both cases, manual deallocating of array is not needed.

I apologize, I am so used to main programs that do nothing but using modules and calling procedures that I didn’t notice you do otherwise. In this case it’s just a testing program, so it makes sense to have an allocatable array defined in the main program. In “real world” applications though, it is a good practice to never have the main program do the actual work. Virtually all my main programs don’t have any variable declared; they just call procedures defined in modules. Divide and conquer…

1 Like

Thank you once again for your insight :pray:

Just an additional remark: if the allocatable array is declared in a module (and you don’t manually deallocate it,) valgrind may report some bytes as “still reachable”. This is expected and harmless (not a memory leak.) You won’t see any bytes “definitely”, “indirectly”, or “possibly” lost.
However if the allocatable array is declared in a subroutine, even “still reachable” will be zero (not that it makes any difference, just in case you are wondering what’s going on.)

1 Like