Extending derived bind(c) types

Consider a derived type like this:

type, bind(c), public :: RenderTexture
  < C-interoperable members here >
end type RenderTexture

Now, suppose I want to extend this type, or to just duplicate it as, say, Rendertexture2D. Some C libraries actually do the latter, and I will discuss this case here, since it is the simplest case of extending.
The naive approach is to try extending the derived type without actually adding anything, like this:

type, bind(c), extends(RenderTexture), public :: RenderTexture2D ! Wrong!
end type RenderTexture2D

But this won’t work because derived types with the C-binding attribute shall not have the extends attribute. Is there a trick to somehow bypass this restriction? Renaming with => won’t work. Using a non C-bindable abstract type and extending it to a bindable one won’t work. The obvious way is to just copy/paste renderTexture and rename it, but I wonder if there is a more “sophisticated” solution.

Hi @Pap ,

AFAIK, the only way is by nesting parents into children types (equivalent of C structs)

type, bind(c), public :: RenderTexture2D
   type(RendererTexture) :: rendererTexture_
   < other C-interoperable members here, if any >
end type RenderTexture2D

This might become a bit too verbose if many level of nesting, but in this case types do not act as Fortran’s types anymore (if you want C interoperability).

What do you mean by “won’t work”? If you are just trying to rename the type to avoid a name conflict, then this should work.

I mean stuff like

type, bind(c), public :: RenderTexture2D => RenderTexture

or any other trick I tried with => doesn’t work (unclassified statements.)

Unfortunately, a derived type RenderTexture2D that has type(RenderTexture) as its only member is not the same as a “normal” derived type RenderTexture2D with the members of RenderTexture copied and pasted.

There is no ready mechanism in standard C language for type extension / polymorphism and inheritance and “class hierarchy”. However C being a low-level language with strong effort to be highly flexible down to the systems level, anyone can try to imitate Stroustsup again and again and attempt to create their own “C with classes”. Attempting to do so in Fortran makes little sense.

And given the Fortran standard, derived types with bind(C) and SEQUENCE are not extensible, period,

1 Like

I wasn’t looking for something like that. I see the title of my question was misleading, and I apologize for that - but I think it is too late to change the title, since it will make things more confusing if I do it now. What I meant is some C libraries make a copy of a struct with

typedef RenderTexture RenderTexture2D

so that RenderTexture2D is a new struct, but essentially just a copy of RenderTexture. Extending the derived type was just a way I tried to do the same in Fortran. The trivial way to duplicate a derived type is to “extend” it without actually adding more members in the “extended” type. But that’s not possible if the derived type is C-interoperable.

Indeed, and I have seen that in some C libraries. I definitely, absolutely don’t want to imitate Stroustsup in any way - but there are people out there who do that.
In my case, the C developers just make a copy of an existing struct for some reason. That triggered my question, originally “how to make a copy of a bind(c) derived type”. I was just wondering if there is a way to do that, without copy/pasting. I didn’t really expect there is such a way, just wanted to be sure there no trick I don’t see.

Oh ok, that makes far more sense.

Note you are not alone in what you request here. Along similar lines, quite a few Fortranners have requested the same.

That is, some reasonable support toward at least type aliasing which is a common use case with typedef in C-like languages.

See this: unfortunately it too quickly died on the vine.
https://j3-fortran.org/doc/year/18/18-255.txt

That was my first full J3 meeting I attended, paying my own way and letting go of vacation, the way the above proposal got ignored left me really saddened.

1 Like

Note the semantics here is not as you describe. RenderTexture2D is not a new struct, but is an alias to refer to the original struct by a different name. Thus, you can accomplish this in Fortran by

use render_module, only: RenderTexture2D => RenderTexture

Something like what you proposed,

type, new :: new_type => old_type

would be the exact solution I was looking for (provided old_type can be C-interoperable.)

Why I am not surprised it got ignored, even though it seems pretty easy to implement?
Look at the awful state of the enum structure, just to name another example. Introduced in Fortran 2003 and still sucking big time… Good luck defining an enum in a private module but declare it public, as you can do with any parameter, derived type, procedure, whatever else defined in the same module. But you can’t do the same with enum. Hell, you can’t even name it… You must declare every single member of the enumerator as public instead. :slightly_frowning_face:

I stand corrected, it is an alias in C. However what you suggested requires a second module just for the aliasing. It will work, but I wanted both derived types to be defined in the same module (which includes all rendering procedures in this case, so it makes little sense to split the module in two.)
I think just copying & pasting then renaming the copy is preferable. There is no need to split the module, and submodules won’t help here either. Since there is usually just a few type members to copy, the code won’t be cluttered, so I guess copy/paste it is. It is not elegant by any means, but it woks.

It is not uncommon that modules must be split into pieces in order to have the correct hierarchy within the code. For example, one module can contain the low-level derived type definitions, which are used by higher-level modules that extend those types and have also the subroutines that work with them. Of course, you can put these multiple modules into the same file if you want, so all the definitions are there for the programmer to see them.

I think your request to have an extended derived type that is also interoperable with C might be unrealistic to begin with. The C structure defines not only the member names and types, but also the memory layout. Fortran has enough C interop capabilities to match that (within whatever interoperable types are supported). But when you declare a type extension, you are not inserting new members into the memory layout, you are really doing something like declaring a parallel array. The extends() syntax allows the compiler to sugar coat things so that it “looks like” the new derived type has those new members, but under the hood it is really like two different derived types that are indexed together. A C processor does not have this capability to begin with, so it seems unrealistic to expect such a data layout to be interoperable with a normal structure of a companion C processor. Of course, such capability could be given to the C processor, for example, through iso_fortran_binding.h, but the C code would need to use that header information, it would not be using just its own normal structure definitions.

Sorry for reactivating this year old conversation. I hope I did not miss a more recent thread touching the bind(c) & type extension subject.

As many before I also have the problem that I would like to pass an extended Fortran type to C but it is not allowed. The reason for this seems to be that C just does not have the capabilities to follow Fortrans type semantics. I understand this partly (but why can’t we make the Fortran base type C-interop?), however, my request is more modest: I would like to have any portable means to represent (data of) an extended Fortran type in C - even if the data access pattern is different from Fortran (I also think there is one natural way to do this). This picks up the nesting approach mentioned by mEm earlier, however, only for the C side. Thus, any Fortran type extension would be represented by a nested structure on the C side. Why is this natural? Because in Fortran the extended type can also be viewed as having a component of the base type, giving you the same nested view as proposed for C. I don’t understand why Fortran must forbid this just because we cannot also bring the flat view provided by Fortrans type extension to the C side.

1 Like

@LocalSimplicity ,

Welcome to Fortran DIscourse!

Re: your problem, I suggest you start a new thread with specific issues re: the workarounds you have to adopt given the existing semantics with interoperability with C in the Fortran standard. Note there is no changing of the language on this front for a long, long time. So the practitioners are left with having to “take it or leave it”.

With “take it”, it really depends on what one truly needs to do in a processor other than Fortran with one’s code. Note, some then make do with an opaque object.

Here’s an example toward this with consuming C++ classes in Fortran that I had provided on another forum a while ago. If such a pattern suits your needs, you can do the reverse: consume Fortran derived types (“classes”), including extended ones, in C, with some limitations of course.

1 Like

Thanks for your quick answer and the example. If I understand it correctly then you used cross-language support from C++ (using extern “C”) and Fortran (using bind(C)) which makes your implementation portable. However, this is different from the problem at hand where no such support is available since the involved Fortran types are forced into non-bind(C) specification. Instead it seems that we would have to figure out ourselves the C representation of the Fortran type-layouts (for each compiler & version). I had the impression that this level of complexity should be hidden from the user and therefore would be a problem to be solved by the language. No support here from Fortran “for a long, long time” would probably mean that we will avoid inheritance in Fortran.

Welcome @LocalSimplicity !

If sentence n. 1 is true, then sentence n. 2 could be true if and only if data layout matches between Fortran and C sides. The “problem” (for these kind of problems) stands on the Fortran side, since Fortran compilers are allowed to reorder data. The only way to enforce it is by either using bind(c) or sequence types, which as stated by others already, are not extensible, by definition

There exists of course one exception, that is indeed, when the compiler effectively keeps the same data layout as expressely declared in the type definition. Of course, when this is the case or not, except for the very, very simple cases, one cannot (and should not) answer. Indeed, the programmer must not rely on this fate. But, in such cases, one could “interoperate” with C using non-interoperable extended Fortran types.

Following an example on how you could use an “extended” fortran type (in both the interoperable bind(c) and Fortran extends fashions) in a C unit:

#include "stdio.h"

typedef struct a_t {
   int i;
} a_t;
typedef struct b_t {
   a_t a;
   int j;
} b_t;

#ifdef __cplusplus
extern "C" {
#endif
void printAt_c(void *ptr) {
   
   if (ptr == NULL) return;
   a_t * pcast = (a_t *)ptr;
   printf("\n\t  %d\n", pcast->i);
};
#ifdef __cplusplus
} // extern "C"
#endif

Main Fortran program:

program test

   use, intrinsic :: iso_c_binding
   implicit none (type, external)

   interface
      subroutine printAtype(ptr) bind(c, name="printAt_c")
         import c_ptr
         type(c_ptr), intent(in), value :: ptr
      end subroutine
   end interface

#define __use_bindc_types__
#ifdef __use_bindc_types__
   type, bind(c) :: a_t
      integer(c_int) :: i = 1
   end type
   type, bind(c) :: b_t
      type(a_t)  :: a
      integer(c_int) :: j = 2
   end type
#else
   type :: a_t
      integer(c_int) :: i = 1
   end type
   type, extends(a_t) :: b_t
      integer(c_int) :: j = 2
   end type
#endif
   type(b_t), pointer :: b_ptr => null()

   allocate(b_ptr)
#ifdef __use_bindc_types__
   b_ptr%a%i = 10
#else
   b_ptr%i   = 10
#endif
   
   call printAtype  (c_loc(b_ptr))
   call printAtype_f(c_loc(b_ptr))
   
   deallocate(b_ptr)
   nullify(b_ptr)
contains

   subroutine printAtype_f(aptr)
      type(c_ptr), intent(in) :: aptr
      type(a_t), pointer :: a_ptr_ => null()

      if (.not. c_associated(aptr)) return
      call c_f_pointer(aptr, a_ptr_)
      print *, a_ptr_%i
   end subroutine

end program

Thanks for the quick answer and the example. If I understand it correctly then it demonstrates the portability of type composition (defined __use_bindc_types__) compared to non-portable type extension (undefined __use_bindc_types__) in Fortran. You also show single source data access code for both variants. In my case C-interop of type t_a is a must, so I go for type composition.

But then t_b instances are not polymorphic and I cannot infer t_b from class(t_a) arguments - which would be nice. I guess that, following your example, I could add an opaque c_ptr component to type t_a and reach the t_b instance (if it exists) using c_f_pointer. This could actually be mapped to my use case. I guess I found my workaround. Thanks to all contributors for the stimulus!

Edit: I just realized that you also show practical C-interop for the extended type case. This, however, may break down if t_a and t_b have more than one component with different sizes/alignments.

@LocalSimplicity ,

Will it be possible for you to open a thread where you explain in sufficient detail what exactly you seek to do now in C with Fortran derived types?

It is a somewhat complex matter: I want to explore portability, performance and usability of certain C++ abstraction layers (e.g., Kokkos, Sycl) together with the existing Fortran code base. The C data representation would only be used in the C++ code portion. I am currently not sure how to put this into a readable example with sufficient details. For this thread I focus on the data access between C/C++ and Fortran which seems to follow the logic: The more structured Fortran data I can capture via BIND(c) the less getters I need to use. In other words: For portability with less BIND(C) properties it seems that I have to lower cross-language data access more to individual type components.

@LocalSimplicity ,

That is a tall order.

Chances are you can achieve one goal, possibly usability - see a silly example here as just some food for thought!

But that might fall short of the other two; or, at best, get two of your goals, perhaps performance also with some processors and companion processors e.g., Intel +LLVM. However that may not yield true portability.

@FortranFan Yes, it is a tough triple - Fortran & OpenACC is my current benchmark for this. Thanks for the inspiring example demonstrating how to use a C++ view on Fortran (character) data.
What I haven’t understood yet is your pessimistic view on support by a (near) future Fortran standard/technical report for C-interoperability of extended types. I could understand that such a feature may be seen as less important than other paths for language evolution, and that limited resources require a stronger focus. But the mentioned C-interoperability enhancement seems to be natural - maybe even (structurally) not too far away from what is happening already under the hood of Fortran compilers.

Edit: spelling

@LocalSimplicity ,

Note my point regarding regarding the difficulty with “support by a (near) future Fortran standard/technical report for C-interoperability of extended types” is due to most basic and practical considerations:

  1. The next standard revision is Fortran 202Y for which the worklist is mostly defined and from this point forward until the eventual publication (in 2028 or whenever) you will find few, if any, who are open to any additions to the worklist; deletions of items from worklist are usually no problem!. Note the standard bearers seek relatively minor revisions with at most one or two big enhancements; 202Y may be subsumed by Generics.

  2. But even otherwise, unless you endeavor to join the committee with an enormous amount of influence or can bring about such influence on existing members, getting any new feature accepted for consideration that they have not already thought of and is on someone’s pet list is nearly impossible. NIH “not invented here” syndrome is way too rampant. All non-pet proposals start with “minus 100 points”.

  3. The standard has gone through two major efforts toward interoperability with C, as you will know once with Fortran 2003 and another with 2018. And the established semantics has focused on BIND(C) clause for interoperable derived types that are decidedly inextensible. Your proposal involves a major rethink of this established design against which you can expect to encounter insurmountable resistance unless those proposing this can bring major influence and carry a big stick.

Obviously “influence” has several dimensions: I won’t get into details but do you represent a major world body with a 3 or 4-letter acronym for the organization that also has a humungous budget dependent on taxpayers like me and who might order a lot of hardware from the vendors who sent reps to the Fortran committee? That will be a start…

2 Likes