Send vector of doubles in a C-struct to Fortran Derived Type

I am wanting to pass a vector of doubles, in a C-struct, from C to FORTRAN, so that it is stored in a derived type.
So far, I am able to pass a vector of int’s, via pointer. However when I pass a vector of doubles, I do not recover correct data.

This suggests to me the memory is not aligned properly, or that the types, even though I am using real(c_double), is not correct.

Hopefully, I can use this approach, because it is quite simple. I read usage of C descriptors, but hopefully this is not necessary (because this approach seems quite more involved).

I’ve also read this thread and taken what it says into account.

I posted the fortran code, and then the c++ code, below.

Fortran code to grab a vector of reals contained in a C-struct

subroutine send_cstruct_to_fortran(cstruct)
    use iso_c_binding, only : c_int, c_ptr, c_f_pointer, C_FLOAT, C_DOUBLE
    implicit none

    ! Fortran doesn't know how the c struct is defined, So, we use bind(c) to
    ! define a user defined type to match the c struct.
    !
    type, bind(c) :: cstruct_interface
        integer(c_int) :: n
        type(c_ptr)    :: array
        type(c_ptr)    :: myvec
        type(c_ptr)    :: D
    end type

    ! The struct that has been passed from c to fortran
    type(cstruct_interface), intent(inout) :: cstruct

    ! We want to access cstruct%array.
    ! Thus we define array_local as a pointer to an array.
    ! We then use c_f_pointer to cast the c pointer cstruct%array to a
    ! fortran compatible pointer array_local. We can then use array_local
    !
    integer(4), pointer, dimension(:) :: array_local
    integer(4), pointer, dimension(:) :: myvec_local
    !integer(4), pointer, dimension(:) :: myvec2_local
    real(kind=C_DOUBLE), pointer, dimension(:) :: myvec2_local
    !real(C_FLOAT), pointer, dimension(:) :: myvec2_local !no!
    !real(8), pointer, dimension(:) :: myvec2_local
    call c_f_pointer(cstruct%array, array_local, [cstruct%n])
    call c_f_pointer(cstruct%myvec, myvec_local, [cstruct%n])
    call c_f_pointer(cstruct%D, myvec2_local, [cstruct%n])
end subroutine

cpp-code* → C++ function declaration

extern "C"
{
  void send_cstruct_to_fortran_(struct blah* s);
}

cpp-code → C++ function declaration

    struct blah s;
    s.n = n;

    //myvec2 is just a vector of doubles; n=5...
    // try using fancy copy stuff in order to troubleshoot.
    // in any case, the vector of doubles is being copied correctly. 
    s.D = (double*) malloc(sizeof(double) * myvec2.size());
    size_t nbytes = sizeof(double) * myvec2.size();
    std::memcpy(s.D, myvec2.data(), nbytes);

    send_cstruct_to_fortran_(&s);

Where is the bind(C) clause on your Fortran procedure meant to interoperate with a C companion processor? Note bind(C) is what enables the interoperability.

Separately, use the KIND named constants defined in the iso_c_binding uniformly across the interoperating code, shy away from hard-wired KINDs such as 4.

call in main.cpp:

    struct blah s;
    s.n = n;
    s.array = array;
    s.array2 = array2;
    s.myvec = myvec;
    s.D = (double*) malloc(sizeof(double) * myvec2.size());
    size_t nbytes = sizeof(double) * myvec2.size();
    std::memcpy(s.D, myvec2.data(), nbytes);
    send_cstruct_to_fortran_(&s);
    free(array);

.h file:

struct blah //define structure
{
    int  n;
    int* array;
    double* array2;
    std::vector<int> myvec;
    //std::vector<double> myvec2;
    double* D;
};

extern "C"
{ 
  void send_cstruct_to_fortran_(struct blah* s);

Apart that you haven’t answered @FortranFan question

Where is the bind(C) clause on your Fortran procedure […] ?

it’s still unclear what your problem is.

That said, if what you have posted is your actual code, then there is an obvious problem: on the Fortran side the structure is described with 4 components, while on the C side it is described with 5 components.

I am able to recover a vector of int’s on the fortran side, but i am unable to for a vector of doubles. However, I am able to recover an array of doubles:

 -0- okay try for vecs:
   '- ARRAY_LOCAL  :          666         667         668         669         670
 -0- okay try for DOUBLE Vecs:
   '- ARRAY_LOCAL  :    1.0397779375729834E-312  -2.3534379293677286E-185  -2.3534382829001283E-185  -2.3534382829007972E-185  -2.3534382829014661E-185

You are correct that there is an extra component. But this was just an oversight that appears not to modify the outcome

A C++ vector type is not interoperable with Fortran (maybe with descriptors it is possible, but without descriptor for sure it is not). So no wonder why it doesn’t work. By the way in your code I don’t see where you supposedly pass a vector of int’s, I can see only an int pointer/array.

Programing and debugging requires to be a bit strict, and not letting such inconsistency in your code.

And as written of course that it modifies the outcome. In C the 4th component is a double vector, the 5th is a double*. In Fortran the 4th component is a pointer. How do think the compiler will map the components?

Can you give some guidence how to use descriptors to accomplish this? I was reading about descriptors in Modern Fortran Explained (Metcalf). I know just that one should use #include <ISO_Fortran_binding.h>. Also I was reading your thread, which led me to this wonderful community via stackexchange

Regarding the extra component, that arose from last minute so it wasn’t part of the original struct

I don’t know, and I don’t even know if it’s possible or not. But you don’t need that at all.

If you want to map the vector content to the Fortran structure, just write:

s.D = myvec2.data()

originally I did s.D = myvec2.data(), but it didn’t work out (I had the similar output that I posted above), so I tried using a verbose memcopy.

For now, I’ll stick with arrays, but if someone has anything to add, I would welcome it

There’s no “output posted above”.

passdouble.cpp:

#include <vector>

struct blah {
    	int  n;
	double* D;
};

extern "C" { 
  void send2fortran(struct blah* s);
}

int main() {

	std::vector<double> myvec{1.,2.,3.,4.,5.};

	struct blah s;

	s.n = 5;
	s.D = myvec.data();
	
	send2fortran(&s);
}

passdouble_f.f90:

module passdouble

use iso_c_binding
implicit none

type, bind(C) :: blah
	integer(c_int) :: n
	type(c_ptr) :: D
end type

contains

	subroutine send2fortran(s) bind(C,name="send2fortran")
	type(blah), intent(in) :: s
	
	real(c_double), pointer :: fd(:)
	
	call c_f_pointer(s%D,fd,[s%n])
	write(*,"(5F10.6)") fd
	end subroutine

end module

Compilation & execution:

% gfortran -c passdouble_f.f90 && g++ passdouble.cpp passdouble_f.o -lgfortran && `./a.out
  1.000000  2.000000  3.000000  4.000000  5.000000

So yes, it works.

1 Like

1 d vectors of real and integer types are interoperable, as are 1 d arrays of real and integer types. Note that we mean the in built C++ “vector” and “array” types, but we can’t use the C++ characters normally used due to the characters disappearing when submitting to Fortran Discourse. Jane and I have examples of each available in our 4th edition update notes and examples. Here is a link Fortranplus - 4th edition new examples We do training for the UK Met Office and some of the people on one of their courses asked about doing it, and we wrote the examples to show them how to do it.

1 Like

You could have posted the example here instead of a link to your course (all characters are protected in discourse code blocks). I have had a look to your examples, and what you are doing is passing the address of the first element of the array. Whether we are doing it with &myvec[0] (your example) or myvec.data() (my example) doesn’t matter, it’s essentially the same. This doesn’t mean that the vector object in itself is interoperable (if it was, we could simply pass it with &myvec)

1 Like

The derived types have to be listed in the same order as the C struct’s vectors -
if the order of the components of c in the derived type does not match the order of the members in the corresponding C struct cstruct, the data will be misaligned when it is passed between the two languages, and the values of the data may be incorrect or undefined, which is what happened.

A good question is: would the C-descriptor in Fortran2018 prevent this, if that is used? It seems that, the descriptor can also be used to specify the memory allocation and alignment requirements for the C object. That could help to avoid issues with misaligned data or undefined behavior

My group has for a long time been passing vector to fortran, so it seems they are indeed interoperable, unless that term is somehow used in some super specific sense, I am not sure how this could not be the case. Also I am happy to read Mr. cmaapic’s course - it seems that fortran is less dense in learning materials so the more books and notes, the better for me.

Thank you all for all the posts, as you can see I have a lot to learn in fortran so I appreciate the feedback.

-Michael

Yes, we do it via the base address of the vector or array. Here is the source code.


C++ Source code

#include <iostream>
#include <vector>
using namespace std;
extern "C" float summation(float *,int );
int main()
{
  const int n=10;
  vector<float> x(n);
  int i;
  for (i=0;i<n;i++)
    x[i]=1.0f;
  cout << " C++ calling Fortran" << endl;
  cout << " 1 d vector as parameter" << endl;
  cout << " Sum is " << summation(&x[0],n) << endl;
  return(0);
}

Fortran source code

function summation(x, n) bind (c, name='summation')
  use iso_c_binding
  implicit none
  integer (c_int), value :: n
  real (c_float), dimension (1:n), intent (in) :: x
  real (c_float) :: summation
  integer :: i

  summation = sum(x(1:n))
end function



1 Like

This is why it is important, when you ask for help, to post an actual code that produce the bug or the unexpected results, and not a pseudo-code that just “looks like” the actual code. What doesn’t look important to you at first (e.g. the component order here) can be the reason of the problem.

Definitely not. The descriptor has to be consistent with what is written on the Fortran side.

Nope. Your group is passing the data component of the vector object, which is not the same thing as “passing the vector object”.

You claimed that

A C++ vector type is not interoperable with Fortran (maybe with descriptors it is possible, but without descriptor for sure it is not).

based on cmaapic’s example, this seems not to be true?

My understanding is that it can be passed by reference

By default everything is passed by reference to Fortran. Don’t you understand the difference between “passing the vector object” and “passing the data component of the vector object” ? This is NOT the same thing.

1 Like