Passing an array of structs from C to Fortran

I would like to pass an array of structs from C to fortran. The struct will carry a string, the length of that string, and another number that represents an index.

I guess I don’t understand what the proper syntax should be to correctly identify the memory location when passed back from C. Before you suggest, I cannot use the ISO_Fortran_binding.h header. I also need to support the apple clang compiler which, to my knowledge, does not support this header.

C++ side of things:

#include <iostream>
#include <string>
#include <map>
#include <cstring>

struct Mapping {
    char name[256];
    int string_length; // Length of the string
    int index;
};

std::map<std::string, int> get_fake_species_ordering() {
    std::map<std::string, int> fake_data;
    fake_data["Species1"] = 1;
    fake_data["Species2"] = 2;
    fake_data["Species3"] = 3;
    return fake_data;
}

extern "C" {
    Mapping* get_species_ordering(size_t* array_size) {
        auto map = get_fake_species_ordering();
        *array_size = map.size();
        Mapping* species_ordering = new Mapping[*array_size];
        size_t i = 0;
        for (const auto &entry : map) {
            std::string name = entry.first;
            std::strcpy(species_ordering[i].name, name.c_str());
            species_ordering[i].string_length = name.size(); // Set string length
            species_ordering[i].index = entry.second;
            ++i;
        }
        return species_ordering;
    }
}

Fortran interface

module micm_core

   use iso_c_binding, only: c_ptr, c_char, c_size_t, c_f_pointer
   implicit none

   public :: micm_t
   private

   type, bind(c) :: Mapping
      character(kind=c_char, len=1) :: name(256)
      integer(c_size_t) :: string_length ! Length of the string
      integer(c_size_t) :: index
   end type Mapping

   interface
      function get_species_ordering(array_size) bind(c, name="get_species_ordering")
         import :: c_ptr, c_size_t
         integer(kind=c_size_t), intent(out) :: array_size
         type(c_ptr)                         :: get_species_ordering
      end function get_species_ordering
   end interface

   type :: micm_t
      type(Mapping), pointer :: species_ordering(:)
      integer(c_size_t)      :: species_ordering_length
   end type micm_t

   interface micm_t
      procedure constructor
   end interface micm_t

contains

   function constructor() result( this )
      type(micm_t), pointer         :: this
      integer                       :: i
      type(c_ptr) :: mappings_ptr

      allocate( this )

      mappings_ptr = get_species_ordering(this%species_ordering_length)
      call c_f_pointer(mappings_ptr, this%species_ordering, [this%species_ordering_length])

      print *, "Length: " , this%species_ordering_length

      do i = 1, this%species_ordering_length
         print *, "Species Name:", this%species_ordering(i)%name(this%species_ordering(i)%string_length), &
                  ", Index:", this%species_ordering(i)%index
      end do

   end function constructor

end module micm_core

and using it

program micm_main
    use micm_core, only: micm_t
    implicit none

    type(micm_t) :: micm
    micm = micm_t()

end program micm_main

and to compile I’m doing this

g++-13 -c example.cpp -std=c++11 -o example.o && gfortran-13 -o test micm.f90 prog.f90 -lstdc++ example.o

when I run the program, I get junk data and then a segfault:

:: ./test                                                                                                   
 Length:                     3
 Species Name:�, Index:  3635360827531685971

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

Backtrace for this error:
#0  0x104c85b07
#1  0x104c84b53
#2  0x186469a23
#3  0x104d7b7d7
zsh: segmentation fault  ./test

I think I spotted it. c_size_t /= c_int (probably), so you’re struct and type, bind(C) declarations are likely not actually equivalent.

2 Likes

Embarrassed to have missed that, but yes. Thanks for catching that!

1 Like