Arrays of pointers

@msz59 , @rwmsu ,

Re: " Why the Standard creators choose not to introduce raw arrays of pointers?" you will note the next question that comes up, as seen in this thread, is why not “introduce raw arrays of pointers” now?

Toward this, you will realize there are a couple of considerations:

  1. The primary use case brought up by the few practitioners who have expressed interest in this facility has been in the context of interoperability with C where one occasionally comes across codes making use of arrays of pointers to C structs. Under the circumstances a true Fortran facility toward “raw arrays of pointers” is likely not going to be directly interoperable anyway and in that case, a whole another edifice in the context of further enhancements to the interoperability with C needs to be built and that is not straightforward.
  2. In the context of Fortran itself, where things stand, any work toward this points toward another intrinsic derived type in an intrinsic module, a la type(c_ptr). Somehow there is great hesitancy toward this among the standard bearers, especially among the compiler vendors. Under the circumstances, trying something out first in Fortran stdlib might be preferable. That may provide further insight into the benefits of such a type.

Now in the context of interoperability of Fortran with C that makes use of arrays of pointers to C structs and perhaps a pointer to such an array, surely there is need to be careful with the indirections on the Fortran side. But note most on the standard committee will find the language standard already provides the tools and mechanisms and it is no more “tricky” than what a coder in C has to keep in mind - see an example below. Thus this will likely not be a priority.

// Example with C array of pointers to structures
#include <stdio.h>
#include <stdlib.h>

typedef struct {
   int data;
} DAT;
typedef DAT *PDAT;

void Fsub(PDAT *, size_t);   // Prototype Fortran sub toward an array of pointers to a C struct
void Csub(PDAT **, size_t);  // Prototype C function toward a pointer to an array of pointers to a C struct

int main(int argc, char **argv)
{

    enum N { N = 3 };

    PDAT *adat = malloc((int)N * sizeof(PDAT));

    for (int i = 0; i < (int)N; i++) {
        adat[i] = malloc(sizeof(DAT));
    }

    for (int i = 0; i < N; i++) {
        adat[i]->data = i;
    }

    Csub(&adat, (size_t)N);
    Fsub(adat, (size_t)N);

    return 0;
}

void Csub(PDAT **x, size_t n) {
    if (n >= 3) {
        printf("In Csub: (*x)[2]->data = %d\n", (*x)[2]->data);
    }
}
  • A “library” procedure in Fortran working with the type of code above
module m
   use, intrinsic :: iso_c_binding, only : c_int, c_size_t, c_ptr, c_f_pointer, c_intptr_t, c_loc
   interface
      subroutine Csub(px, n) bind(C, name="Csub")
         import :: c_ptr, c_size_t
         ! Argument list
         type(c_ptr), intent(in) :: px  !<-- Note no VALUE attribute
         integer(c_size_t), intent(in), value :: n
      end subroutine 
   end interface
   type, bind(C) :: aptrs_t
      type(c_ptr) :: ptr
   end type
   type, bind(C) :: dat_t
      integer(c_int) :: data
   end type
contains
   subroutine Fsub(px, n) bind(C, name="Fsub")
      ! Argument list
      type(c_ptr), intent(in), value :: px   !<-- Note the VALUE attribute
      integer(c_size_t), intent(in), value :: n
      ! Local variables
      type(aptrs_t), pointer :: aptrs(:)   !<-- A local object for indirection
      type(dat_t), pointer :: pdat
      integer(c_int) :: x 
      ! Error handling elided for invalid values of n
      call c_f_pointer( cptr=px, fptr=aptrs, shape=[ n ] )
      ! Work with 3rd element
      call c_f_pointer( cptr=aptrs(3)%ptr, fptr=pdat )
      x = 42
      print *, "In Fortran sub: set data of 3rd element to = ", x
      pdat%data = x
      call Csub(px, n)
      aptrs => null()
      pdat => null()
      return
   end subroutine 
end module 
  • Compiler response:
C:\temp>gfortran c.c f.f90 -o c.exe

C:\temp>c.exe
In Csub: (*x)[2]->data = 2
 In Fortran sub: set data of 3rd element to =           42
In Csub: (*x)[2]->data = 42

C:\temp>