C-interoperable polymorphic classes via pointers

Hello all,

I have a use case of C interoperability (with C++, but could be Python or else) where I want to interface polymorphic classes to C, and I want to avoid writing interfaces to all type-bound functions from the parent class also in the extended classes, when they’re only defined in the parent (maybe abstract) class.

So far I think the best case scenario is to define a pointer to the parent class accessor, like in the following example:

module extend_c
   use iso_c_binding
   implicit none

   ! The Fortran classes
   type :: a
      integer :: i = 42
      contains
        procedure :: get_i
   end type a

   type, extends(a) :: b
   end type b

   ! The C opaque pointer classes
   type, bind(C) :: a_c
      type(c_ptr) :: cptr = c_null_ptr
   end type a_c 

   type, bind(C) :: b_c
      type(c_ptr) :: cptr = c_null_ptr
   end type 

   contains

   ! sample function in the parent class
   elemental integer function get_i(this)
      class(a), intent(in) :: this
      get_i = this%i
   end function get_i

   ! its interface is only defined for the interoperable parent class
   integer(c_int) function get_i_c(this) bind(C,name="get_i_c")
      type(a_c), intent(in) :: this
      type(a), pointer :: athis
      call c_f_pointer(this%cptr,athis)
      get_i_c = get_i(athis)
   end function get_i_c 

   ! this is similar to a dynamic_cast
   type(a_c) function get_parent_class(this) result(that) bind(C,name="get_parent_class")
      type(b_c), intent(in), value :: this
      type(b), pointer :: fthis
      type(a), pointer :: fthat
      
      call c_f_pointer(this%cptr,fthis)
      if (.not.associated(fthis)) return

      ! Point to parent class 
      fthat => fthis%a

      ! Save it in C type
      that%cptr = c_loc(fthat)

   end function get_parent_class   

end module extend_c

! This could be a C program
program blabla
  use extend_c
  implicit none

  type(b), pointer :: bx => null()
  type(b_c) :: bc
  type(a_c) :: ac

  allocate(bx)
  bc%cptr = c_loc(bx)

  ac = get_parent_class(bc)
  print *, get_i_c(ac)

end program blabla 

This is similar to what a dynamic_cast would do in C++.
The example works great with gfortran, but I’m not sure if:

  • is it standard conforming to point to the parent class accessor?
  • C++/Fortran gurus (@ivanpribec :slight_smile: ) is this the best way to achieve that?
  • This of course does not work if type(a) is abstract and I fear this case would be a dead end?

Thank you all!

1 Like

Not a definitive answer, but here are two sections from MRC (the “red” book):

The target in a pointer assignment statement may be a subobject of a pointer target. [pg. 50]

Additionally, an extended type has a parent component; this is a component that has the type and type parameters of the old type and its name is that of the old type. It allows the inherited portion to be referenced as a whole. […] The parent component is particularly useful when invoking procedures that operate on the parent type but which were not written with type extension in mind. [pg. 292]

I’m not 100 % sure if a sub-object only refers to a section of an array, or also to components of derived types (including the parent component).

FWIW, the Intel compilers don’t return an error, nor does the NAG compiler. As a result of Hyrum’s law, I think we can safely assume this behavior will remain valid.

I tried merging the two statements into one, and it also works:

      ! Save it in C type
      that%cptr = c_loc(fthis%a)

In Fortran you should probably have the target attribute on the bc variable (even if the actual association is with the contents of bc%cptr), but don’t know if this is a requirement in this case. In C this is not an issue, since you can point to any variable.

I think a dynamic_cast is more similar to select type in Fortran. In C++ upcasting is permitted (when the parent class is public):

class Parent {
public:
    int i{42};
};

class Child : public Parent {
public:
    Child(int j_) : j(j_) {}
    int j;
};

int get_i(Parent &p) { return p.i; }

int main() {

    Child c{43};
    
    // upcast, dynamic_cast may be used, but unnecessary
    Parent &p = c;

    std::cout << p.i << '\n';
    std::cout << get_i(c) << ' ' << c.j << '\n';
    return 0;
}

This is great news, it means there’s a reasonable way forward to expose Fortran classes to other object-oriented languages.

The only limitation is we can’t pass actual routines from abstract classes, as also discussed in this thread. For them, I think there is no other solution than writing interface wrappers for each actual child type.

@ivanpribec said “I’m not 100 % sure if a sub-object only refers to a section of an array, or also to components of derived types (including the parent component).” MRC(2018) pg.28 says it can refer to derived types. See also the f2023 standard 19.6.1 that says inter alia “Arrays, including sections, and variables of derived, character, or complex type are objects that consist of zero or more subobjects.” Also “If an object is undefined, at least one (but not necessarily all) of its subobjects are undefined.”

1 Like