OOP and iso_c_binding

I’m wondering if it safe to cast a base class into a parent class in the way shown in test1 below using iso_c_binding. It seems to work for me always.

Is test1 fundamentally doing a similar thing to test2, under the hood?

program main
  use iso_c_binding
  implicit none

  type :: ParentType
    integer :: a = 1
  end type

  type, extends(ParentType) :: ChildType
    integer :: b = 2
  end type

  call test1()
  call test2()

contains

  subroutine test1()

    type(ChildType), target :: c
    type(c_ptr) :: ptr
    type(ParentType), pointer :: p

    ptr = c_loc(c)
    call c_f_pointer(ptr, p)
    print*,p%a

  end subroutine

  subroutine test2()

    type(ChildType), target :: c
    type(c_ptr) :: ptr
    class(ParentType), pointer :: p

    p => c
    print*,p%a
  
  end subroutine

end program

Unless your purpose is related to C interoperability, I believe the let’s call it “conforming” way to do it would be via the parent accessor:

   p => c%ParentType

but interesting to see that both of them work (your C method seems to have interesting implications for C APIs with Fortran classes indeed!)

1 Like

Type casting using iso_c_binding is likely to work but it’s kind of discouraged unless you exactly know what you are doing.
See this SO question additional info
I copy the answer here

Practically, use of C_LOC and C_F_POINTER in this way is likely to work, but formally it is not standard conforming. The type and type parameters of the Fortran pointer passed to C_F_POINTER must either be interoperable with the object nominated by the C address or be the same as the type and type parameters of the object that was originally passed to C_LOC (see the description of the FPTR argument in F2008 15.2.3.3). Depending on what you are trying to serialize, you may also find that formal restrictions on the C_LOC argument (which are progressively less restrictive in later standards than F2003) come into play.
(The C equivalent requires use of unsigned char for this sort of trick - which is not necessarily the same thing as int8_t.)
There are constraints on the items in an EQUIVALENCE set that make that approach not generally applicable (see constraints C591 through C594 in F2008). Interpreting the internal representation of an object through equivalence is also formally subject to the rules around definition and undefinition of variables - see F2008 16.6.6 item 1 in particular.
The conforming way to access the representation of one object as a different type in Fortran is through TRANSFER. Be mindful that serialization of the internal representation of derived types with allocatable or pointer components (is that what you mean by dynamic fields?) may not be useful.
Depending on circumstance, it may be simpler and more robust to simply store your real time results in an array of the type of the thing to be stored.

To further test your approach you may want to add allocatable components in the Parent or Child type and see how it behaves.

And @FedericoPerini is right, you can always access the parent type from the child. It appears in your type as a normal component.

It is more likely to work than not, in this case. Although as pointed out not technically standard conforming. You’re skipping all of the checking that the compiler is required to do to make sure that it is in fact valid to point p at c. test2 is the safe way to do it.

Thanks for the replies! All very helpful. I’ll add a little more context: I’ve been using the test1 type casting method to create a C interface to my Fortran codes for a while now, and it has always worked, even for complicated derived types involving allocatable attributes. Note, I have only tested the Gfortran compiler.

Whether test1 is acceptable or not, in general is relevant to these C bindings. If test1 is NOT accetable, then I have to write a bunch of redundant code. For example, get/set functions need to specified two times.

  subroutine parenttype_get_a(ptr, a) bind(c)
    type(c_ptr), intent(in) :: ptr
    integer(c_int), intent(out) :: a
    type(ParentType), pointer :: p
    call c_f_pointer(ptr, p)
    a = p%a
  end subroutine

  subroutine childtype_get_a(ptr, a) bind(c)
    type(c_ptr), intent(in) :: ptr
    integer(c_int), intent(out) :: a
    type(ChildType), pointer :: c
    call c_f_pointer(ptr, c)
    a = c%a
  end subroutine

BTW, it looks like both test1 in the original post and test3 (see below) produced nearly the same assembly with Gfortran. Here is test3

  subroutine test3()
    type(ChildType), target :: c
    type(c_ptr) :: ptr
    type(ParentType), pointer :: p

    ptr = c_loc(c)
    p => c%ParentType

    print*,p%a
  end subroutine

Here is the x86 diff for both assembly outputs (Gfortran 13.2). I can’t read assembly, so I’m not sure if this one line difference is important