Accessing address of a polymorphic value with C_PTR

Hello! I am new to Fortran. I have a function which compiled with previous versions of Intel Fortran Compiler (ifort), but is rejected by more recent versions (2021.6.0), and I hope to fix it. This function accepts a class(*) , and passes its address and length to a C function:

!> Send an arbitrary scalar object.
function SendObject(my,obj) result(ok)
use, intrinsic :: iso_c_binding
implicit none
    class(Socket) :: my
    class(*), target, intent(in)  :: obj

    type(c_ptr)       :: ptr
    integer(c_size_t) :: len

    ptr = c_loc(obj)
    len = c_sizeof(obj)
    ok = my%SendData(ptr,len)

end function

ifort now emits an error:

error #9023: The argument to C_LOC must not be polymorphic.   [OBJ]
ptr = c_loc(obj)

While this function is polymorphic, in practice it is used only for a few simple structs containing scalars.

What is the best way to get this function “working” again, as well as it worked with previous compilers? I just need to get a C pointer to obj. Thanks for any help!

1 Like

Hi @pammon , welcome to the Discourse.

The way to get it working that would be least impactful to the rest of the code base is to use a select type block with the allowed types. If you have a class default section with an error stop, that’s probably good enough for now since as you say:

Unfortunately this is probably not the best way for future maintenance, and the “right” way would be to redesign this aspect of the code.

Note: any objects which do not strictly reside in contiguous memory (i.e. pointer or allocatable ultimate components), can not be “sent” this way.

1 Like

@pammon,

Welcome to this forum.

For the use case you show, try the other unlimited polymorphic option in Fortran that was introduced starting with Fortran 2018 revision viz. TYPE(*) instead of CLASS(*).

TYPE(*) is also referred to assumed-type received argument.

The C_LOC function offered via the intrinsic module ISO_C_BINDING for fetching the C address of an object was updated in Fortran 2018 to work with asumed-type objects.

Here’s a simple example on the topic to try out for any readers interested in interoperability with C and Fortran:

  • C main:
#include <stdio.h>

typedef struct {
   int n;
} foo_t;

void Fsub(void *, size_t);

int main()
{

   enum N { N = 3 };

   int i;
   foo_t foo[N];

   for (i = 0; i < N; i++)
   {
      foo[i].n = 42+i;
   }

   printf("Print from C main:\n");
   printf("Address of foo: %p\n", &foo[0]);

   Fsub(foo, (size_t)N);

   return 0;
}
  • Fortran “library” code:
module m
   use, intrinsic :: iso_c_binding, only : c_int, c_size_t, c_intptr_t, c_loc, c_f_pointer
   type, bind(C) :: foo_t
      integer(c_int) :: n
   end type
contains
   subroutine Fsub( a, sizea ) bind(C, name="Fsub")

      ! Argument list
      type(*), intent(inout), target :: a(*)
      integer(c_size_t), intent(in), value :: sizea

      ! Local variables
      integer(c_intptr_t) :: adda
      type(foo_t), pointer :: foo(:)
      integer :: i 

      adda = transfer( source=c_loc(a), mold=adda )
      print *, "In Fsub:"
      print *, "sizea = ", sizea
      print "(g0,z0)", "Address of argument: ", adda
      call c_f_pointer( cptr=c_loc(a), fptr=foo, shape=[ sizea ] )
      do i = 1, sizea
         print "(*(g0))", "foo[",i,"] = ", foo(i)%n
      end do

   end subroutine 
end module 

C:\temp>gfortran -c c.c

C:\temp>gfortran -c m.f90

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

C:\temp>c.exe
Print from C main:
Address of foo: 000000a69cbffc50
In Fsub:
sizea = 3
Address of argument: A69CBFFC50
foo[1] = 42
foo[2] = 43
foo[3] = 44

1 Like

Thank you to @everythingfunctional and @FortranFan for the help. I agree this code is fragile. type(*) was a good tip; unfortunately AFAICT it is not possible to get the size of a value referenced by type(*). I settled on using type(*), and adjusting every call site to pass in the size as an additional parameter. This seems to work.

@pammon ,

In the context of interoperability with C and Fortran, please note Fortran will generally not succeed with anything you cannot or will not achieve in C. Note TYPE(*) facility in Fortran starting with the Fortran 2018 revision can be viewed - crudely - as the equivalent of void * function parameter in C. And in C, with such a function parameter, the sizeof function will fetch you the size of the void pointer type. Fortran will only do as much. Passing the size of the data with a size_t type is good practice that will help you avoid a lot of issues.