Exposing polymorphic objects to C

This is an issue I recently stumbled upon when trying to expose a class polymorphic object via bind(C) in Fortran.

Let’s take a simplified C API wrapping Fortran objects (mainly removing the error handling for readability), exposing a constructor for a specific type extending from an abstract base class and a deconstructor for a polymorphic object as well as a method to actually calculate something with such a polymorphic object:

module m_api
  use, intrinsic :: iso_c_binding
  ! Defines the abstract base class (ABC)
  use m_abc, only : abc_type
  ! Defines an implementation extending the ABC,
  ! usually there is more than one
  use m_impl, only : impl_type
  implicit none

  ! Thin wrapper to make class polymorphic object bind(C) compatible
  ! typedef struct _m_abc* m_abc;
  type :: vp_abc
    class(abc_type), allocatable :: ptr
  end type vp_class

contains

! extern m_abc new_impl(double param);
function new_impl_api(input) result(vabc) bind(C, name="new_impl")
  ! Void pointer to Fortran data
  type(c_ptr) :: vabc
  ! Actual object exposed to C
  type(vp_abc), pointer :: abc
  ! Some input parameter for this specific implementation
  real(c_double), value :: param

  allocate(abc)
  abc%ptr = impl_type(param)
  vabc = c_loc(abc)
end function new_impl_api

! extern void abc_get_prop(m_abc abc, double* val);
subroutine abc_get_prop_api(vabc, val) bind(C, name="abc_get_prop")
  ! Void pointer to Fortran data
  type(c_ptr), value :: vabc
  ! Actual object exposed to C
  type(vp_abc), pointer :: abc
  ! Output property of the ABC
  real(c_double), intent(out) :: val

  val = 0.0_c_double
  if (c_associated(vabc)) then
    call c_f_pointer(vabc, abc)
    if (allocated(abc%ptr)) then
      call abc%ptr%get_prop(val)
    end if
  end if
end subroutine get_prop_api

! extern void delete_abc
subroutine delete_abc_api(vabc) bind(C, name="delete_abc")
  ! Void pointer to Fortran data
  type(c_ptr), intent(inout) :: vabc
  ! Actual object exposed to C
  type(vp_abc), pointer :: abc

  if (c_associated(vabc)) then
    call c_f_pointer(vabc, abc)
    deallocate(abc)
    vabc = c_null_ptr
  end if
end subroutine delete_abc_api

end module m_api

In C one creates an instance of the polymorphic object, with the specific constructor, perform the calculation and than cleanup again:

include <stdio.h>
include "m.h"

int main(void) {
  double res;
  m_abc obj = new_impl(1.0);
  abc_get_prop(obj, &res);
  delete_abc(&obj);

  printf("Result: %lf\n", res);

  return 0;
}

Now the question is, how can I create an API to allow the C side user to query the actual type of the object conveniently and use it as the specific type rather than the abstract type in further calculations? The problem feels like I’m trying to expose the select type mechanism of Fortran to C.


A more concrete example would be simple-dftd3/api.f90 at main · awvwgk/simple-dftd3 · GitHub.

2 Likes

Given how both C and Fortran strongly retain aspects of low-level languages whereas you seek higher-levels of abstraction here, it may be useful to keep in mind one of the many variants of the “famous” Djikstra quote that goes, “clever code considered harmful”!!

Should you retain the polymorphic component in the wrapper derived type, whatever you end up doing to avoid SELECT TYPE will be “too clever” for your good and for anyone else working with the code which can be you but in a future incarnation where it can be rather difficult to remember the details.

Current Fortran standard has “blessed” verbosity on its practitioners, thus there is always the verbose and headaches-minimizing solution: more lines of code via specific C API wrappers for each “concrete” extension of your abc_type.

2 Likes

Though not very sure about details, is it one option to write a query function to ask whether obj is a given specific type (on the Fortran side)? like…

if (is_typeA(obj)) get_propX_typeA(obj, &res);   // is_typeA() returns true/false from Fortran (using select type)

Another option might be to define some IDs (constants) for distinguishing specific types (e.g. typeA = 1) and use them for calling specific routines?

if (type_of_abc(obj) == typeA) get_propX_typeA(obj, &res);  

I really appreciate the warning words here. The original intent of the wrapper derived type was to expose a polymorphic object to C without requiring the user to know more details about it than its constructor. Given that the user could only meaningfully access the components they provided in the constructor, in the concrete example, I see limited use for this. Still, this feature was requested and I want at least to explore if it is possible. There is of course always the option to not provide this functionality if it turns out more complicated than practical.

This might be the most viable option, using an enum type on both C and Fortran side allows to “expose” the select type mechanism in a C switch/case statement coming close to the original intent. The namespacing in the API for the specific types might become a bit lengthy, but I don’t mind the extra verbosity here, since this would be a rather specific use case.

In general I would consider this a “code smell”. It is a sign that you may want to rethink your type/class hierarchy and the design for the base class’s API. The general design principle is that users of a polymorphic object (i.e. via it’s base class), should not need to know it’s actual (dynamic) type in order use it.

Granted sometimes that is easier said than done, and there may be some edge cases where it’s necessary. For an example of a place where one might have initially thought it necessary to use a select type, but a slight redesign was able to eliminate it, see this branch of my heterogeneous list example repository from my Intermediate Fortran Course. The “naive implementation” with the select type is also available on this branch.