Fortran sending real pointer to C program: REAL*8?

How should I define an array of reals that will eventually be sent to a C program as a C pointer?

subroutine test ()
    implicit none
    integer*8 :: i
    integer (kind=8) :: j

    real :: sizetest(50)
    real*8 :: sizetest2(50)

    print *,kind(i), ' and ', kind(j)    
    print *,' Size of real is ',kind(sizetest), ' and size of real*8 is ',kind(sizetest2)
end subroutine
#include <stdio.h>
#include <string.h>

void test_();

int main ()
{
    test_();
}
  gfortran -c -g test.f90 -o test.o
  gcc -c -g main.c -o main.o 
  gfortran -g test.o main.o -o main.exe
  ./main.exe
           8  and            8
  Size of real is            4  and size of real*8 is            8

A lot is left unknown in your question and example code. Does your array live in the local scope of the subroutine or do you have an array in global memory (for example in a common block)?

Use BIND(C) and the named types from ISO_C_BINDING. Also, REAL*8 is not portable, since different Fortran compilers might use different constants to represent DOUBLE PRECISION. Alternatively, there are also named types in ISO_FORTRAN_ENV like int64 and real64 if you want to keep them just in the Fortran code and not pass them into C.

I would do it along these lines:

subroutine test () bind(C, name='test')

  use ISO_C_BINDING, only: C_LONG, C_FLOAT, C_DOUBLE
  implicit none

  integer(C_LONG) :: i, j
  real(C_FLOAT) :: sizetest(50)
  real(C_DOUBLE) :: sizetest2(50)

  print *, 'Size of real(c_float) is ', kind(sizetest), ' and size of real(c_double) is ', kind(sizetest2)

end subroutine

And the C counterpart:

#include <stdio.h>
#include <string.h>

void test();

int main ()
{
    test();
}

Notice that we don’t need the trailing underscore anymore, since BIND(C) takes care of that.

To compile, you also need to link libgfortran:

$ gfortran -c -g test.f90 -o test.o
$ gcc -c -g main.c -o main.o 
$ gcc main.o test.o -o test.exe -lgfortran
$ ./test.exe
 Size of real(c_float) is            4  and size of real(c_double) is            8

What about ISO_FORTRAN_ENV? Is that too new as well?

So inside the Fortran routine test, you will call a C routine (which is not shown), that will access the array sizetest? At the moment your sample program just has declarations, there is zero notion of which direction you’re trying to pass data.

In this case, the “lifetime” of the array is limited to the subroutine call. If you want to manipulate the array in C, there must be another C function involved:

main (enter) → test (enter) → ??? (do stuff with array in C) → test (return) → main (return)

1 Like

Should I define it as real, real *8, real* 16 etc?

Yes, but as I warned before, the code wouldn’t be portable.

PS: pro tip, use backticks ` to write code so asterisks wouldn’t be interpreted as bold/italic syntax.

That depends if you want float or double. You haven’t specified what precision you want.

Btw, don’t forget about name mangling, in C you’ll need

void gimme_(float *dummy);

to call it the way you’ve shown.

1 Like

I probably need not mention that type-casting through argument passing is a quite dangerous programming practice for many reasons…

In that case you’re already set-up. Just pass the first element:

subroutine test()
   real :: sizetest(50)

   call gimme(sizetest(1))
end subroutine

Make sure you calculate the storage sizes correctly, and how many elements your array new aliased array has. Unless you also want to cross the boundary on purpose :warning: (that’s a joke).

There are too many implicit assumptions in your question to give any definitive answer.

Which compilers are you using (it influences the kind parameter)? What is the word size (in bits) of your processor and platform? Size of a C pointer is larger than 4 what? Bytes?

If you’re planning to write importable programs, at least share the platform details.

An acknowledgement in the product, or perhaps a donation from you or your employer would be nice, if this is for commercial purposes.

Have you tried it already, and did it work the way you expected? If you’re not willing to do the reading, you can still get far with experimentation:

Take a look
/* main.c */
extern void alias_();

int main(int argc, char const *argv[])
{
    alias_();
    return 0;
}
! alias.f90
subroutine alias()
real :: a(3)
a(1) = transfer(2,a(1))
a(2) = transfer(4,a(1))
a(3) = transfer(6,a(1))
call print_ints_in_c(a(1))
end subroutine
/* print_ints_in_c_.c */
#include <stdio.h>
void print_ints_in_c_(int *a) {
    for (int i = 0; i < 3; i++) {
        printf("a[%d] = %d\n",i, a[i]);
    }
}
$ gfortran -c alias.f90 
$ gcc -c print_ints_in_c_.c 
$ gcc main.c alias.o print_ints_in_c_.o -o main
$ ./main
a[0] = 2
a[1] = 4
a[2] = 6

At this point I think it’s clear. I suggest to stop what you’re doing and to read this book:

This book is about software professionalism. …

… It is a willingness to accept the dire responsibility of being a craftsman and an engineer. …

But that responsibility includes one other thing – one frightening thing. As an engineer, you have a depth of knowledge about your systems and projects that no managers can possibly have. With that knowledge comes the responsibility to act.

In continuing to work in a direction you know to be contrary to the best interests of the project, and thus ultimately contrary to the best interests of your employer, you are acting unprofessionally and unethically. As the developer of the project, it is your responsibility to work to the best of your abilities towards what is best for the project, not simply do what you’re told. As hard as it may be some times, that’s what it means to be a professional.

Now, you may think that my statement above is harsh and unhelpful for your situation, but I contend that like a road block with a sign saying “Bridge out ahead” impedes your travel, it encourages you to not to go down a dangerous path.

7 Likes