Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
28744 Discussions

How to access ALLOCATABLE 4-D Fortran array from C?

AONym
New Contributor II
3,852 Views

In Fortran, I have

    MODULE ScanData
       USE, INTRINSIC :: ISO_C_BINDING
       REAL(8), ALLOCATABLE, DIMENSION(:, :, :,  :: scans

After this 4-dimensional array has been allocated, I need to access it from C (actually, C++).

What is the best way to do this, preferably without parsing the array descriptors?

I'd like to be able to access either individual elements (e g, scans(1,2,3,4)), and vectors (e g, scans(1:100, 2, 3, 4) ) from C.

0 Kudos
16 Replies
jimdempseyatthecove
Honored Contributor III
3,837 Views

You could pass the array together with the size of each dimension...

or...

use the Interoperate with Arguments Using C Descriptors

Note, unfortunately an example of this use is not readily available via the documentation.

Perhaps someone else can provide a link to an example.

Jim Dempsey

 

0 Kudos
Steve_Lionel
Honored Contributor III
3,824 Views

Passing by descriptor and using the CFI routines to access elements is the best way. C multidimension arrays don't look anything like Fortran arrays.

0 Kudos
AONym
New Contributor II
3,784 Views

Steve -

What are "CFI routines"?

0 Kudos
Steve_Lionel
Honored Contributor III
3,776 Views

Fortran 2018 extended C interoperabilty to provide passing additional categories of Fortran entities by "C descriptor" (a Fortran standard concept.) On the C side, you include ISO_Fortran_binding.h (provided by the Fortran compiler). This provides declarations for the descriptor, various constants it uses, and a collection of functions whose names all start with CFI_ (C-Fortran Interoperability). The one you want in particular is CFI_address, where you provide it a pointer to a C descriptor and an array of subscripts and it returns the address of that element.

 

Steve_Lionel_0-1681402714300.png

 

jimdempseyatthecove
Honored Contributor III
3,775 Views

Intel, could you manage to insert into the documentation in the interoperable section an example of use of the CFI_address function inclusive of Fortran and C code.

It would be considerably more helpful than looking in (for) two or three separate documents.

 

Jim Dempsey

 

0 Kudos
AONym
New Contributor II
3,749 Views

OK, I am missing something here.

In Fortran, I have

MODULE ScanData
    USE, INTRINSIC :: ISO_C_BINDING
    IMPLICIT NONE
    REAL(real_precision), ALLOCATABLE, DIMENSION(:, :, :,  :: scansHat
...
END MODULE ScanData

(real_precision is SELECTED_REAL_KIND(10) on the Fortran side and double in C).

In C++, I am trying to get the info from the array descriptor using

#include "ISO_Fortran_binding.h"
CFI_index_t subscripts[4];
//extern CFI_cdesc_t_ *SCANDATA_mp_SCANSHAT;
extern real_precision *SCANDATA_mp_SCANSHAT;
void *pDesc = CFI_address((CFI_cdesc_t_ *)SCANDATA_mp_SCANSHAT,subscripts);

This gives a link unresolved symbol error for "double * SCANDATA_mp_SCANSHAT" , If I use line 3 and comment out line 4 in the above, I get an unresolved symbol error for "struct CFI_cdesc_t_ * SCANDATA_mp_SCANSHAT".

 

FWIW, I am also getting these warnings during C++ compilation:

>C:\Program Files (x86)\Intel\oneAPI\compiler\2023.0.0\windows\compiler\include\ISO_Fortran_binding.h(156,15): warning C4200: nonstandard extension used: zero-sized array in struct/union
1>C:\Program Files (x86)\Intel\oneAPI\compiler\2023.0.0\windows\compiler\include\ISO_Fortran_binding.h(156,15): message : This member will be ignored by a defaulted constructor or copy/move assignment operator
1

 

0 Kudos
FortranFan
Honored Contributor III
3,736 Views

@AONym wrote:

.. without parsing the array descriptors?

I'd like to be able to access either individual elements (e g, scans(1,2,3,4)), and vectors (e g, scans(1:100, 2, 3, 4) ) from C.


  1. What does it even mean "without parsing the array descriptors"?  Someone has to pass the information over to interoperate.  You do understand an "array" in C is not quite the same as in Fortran, right?
  2. Point 1 also means there is no such thing as "vectors" in C.
  3. Also, there is no interoperability between C++ and Fortran, only with - either using the standard facilities or via compiler-specific extensions.

Now, with the standard facilities, there is an option of dispatch the base address to the memory of a Fortran array along with the array descriptors include the type, kind, attributes, element length, rank, extents, and memory stride over to C, or extern "C" section in C++.  One can then set up "views" with such info, or march through them element-by-element.  Below is an example of the latters:

  • Fortran "main" program caller working with an object of rank-3 interoperating with a C (extern "C") function for illustration
   use, intrinsic :: iso_c_binding, only : c_int
   interface
      subroutine Csub( a ) bind(C, name="Csub")
         import :: c_int
         integer(c_int), intent(inout) :: a(:,:,:)
      end subroutine 
   end interface
   integer(c_int), allocatable :: x(:,:,:)
   allocate( x(2,3,4) )
   call Csub( x )
   print *, "x = ", x
end
  • C++ callee under extern "C" working the Fortran standard array descriptors
#include <iostream>
#include <ISO_Fortran_binding.h>
using namespace std;

extern "C" void Csub( CFI_cdesc_t *d ) {
   int *dat;
   CFI_index_t ext[3];
   cout << "In Csub: array rank = " << (int)d->rank << "\n";
   dat = (int *)d->base_addr;
   ext[0] = d->dim[0].extent;
   ext[1] = d->dim[1].extent;
   ext[2] = d->dim[2].extent;
   for (int i=0; i < (int)ext[0]; i++) {
       for (int j=0; j < (int)ext[1]; j++) {
           for (int k=0; k < (int)ext[2]; k++) {
               dat[i*(int)ext[1]*(int)ext[2] + j*(int)ext[2] + k] = i*(int)ext[1]*(int)ext[2] + j*(int)ext[2] + k;
           }
       }
   }
   return;
}
  • Program execution
C:\temp>ifort /c /free /standard-semantics p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.9.0 Build 20230302_000000
Copyright (C) 1985-2023 Intel Corporation.  All rights reserved.


C:\temp>cl /c /W3 /EHsc c++.cpp
Microsoft (R) C/C++ Optimizing Compiler Version 19.34.31937 for x64
Copyright (C) Microsoft Corporation.  All rights reserved.

c++.cpp
C:\Program Files (x86)\Intel\oneAPI\compiler\latest\windows\compiler\include\ISO_Fortran_binding.h(156): warning C4200: nonstandard extension used: zero-sized array in struct/union
C:\Program Files (x86)\Intel\oneAPI\compiler\latest\windows\compiler\include\ISO_Fortran_binding.h(156): note: This member will be ignored by a defaulted constructor or copy/move assignment operator

C:\temp>link p.obj c++.obj /subsystem:console /out:p.exe
Microsoft (R) Incremental Linker Version 14.34.31937.0
Copyright (C) Microsoft Corporation.  All rights reserved.


C:\temp>p.exe
In Csub: array rank = 3
 x =  0 1 2 3 4 5
 6 7 8 9 10 11
 12 13 14 15 16 17
 18 19 20 21 22 23

Left as "homework" is a) how to extend to higher rank arrays in Fortran and b) how to consume the array info on the other side.

 

0 Kudos
AONym
New Contributor II
3,722 Views

FortranFan -

You have shown how to access an allocated array in a subroutine. I need to access an array in a module (see my attempt to do so in a comment above).

As far as accessing as a vector, what I meant was, I will often need access to a 1-D array in Fortran, which has an exact correspondence in C/C++. My example Fortran vector has a stride of 1 (only the first subscript varies).

 

"Without parsing the array descriptors" means, I'd like the info contained in them in a format independent of the Fortran compiler. From discussions I have read elsewhere, this is not possible, although the CFI functionality provides some degree of independence.

0 Kudos
jimdempseyatthecove
Honored Contributor III
3,709 Views

>>I need to access an array in a module

Your original post had: 

I'd like to be able to access either individual elements (e g, scans(1,2,3,4)), and vectors (e g, scans(1:100, 2, 3, 4) ) from C.

 

These are contradictory statements.

On the Fortran side, the code simply uses (use yourModuleNameHere) SCANS(1,2,3,4)

On the C/C++ side, first place the interface as FortranFan shows above in a module (modified for your subroutine/function name, array type), and on the C/C++ side, code as he outlined above (modified for your function requirements)

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor III
3,714 Views

A module entity needs a BIND attribute to be interoperable with C but an object with an allocatable attribute cannot have the BIND(C) attribute.  So you can use a trick to get the raw address of the object, but you would need to set up the array descriptors yourself to use them on the other side.  The standard descriptors only work with function parameters in C.

0 Kudos
jimdempseyatthecove
Honored Contributor III
3,704 Views

>> I will often need access to a 1-D array in Fortran

subroutine Foo(FooBar, N) bind(C, name="Foo")

  use, intrinsic :: iso_c_binding

  integer, value :: N

  real(8) :: FooBar(N)

...

// C/C++ side

extern "C" Foo(double* array, int n);

...

    Foo(yourArray, yourArraySize);

 

Something like that, you do the homework to get it right.

0 Kudos
AONym
New Contributor II
3,677 Views

What I am hearing is there is no simple way to do what I want; the only way is to get the base address using c_loc, and pass the allocated dimensions of the Fortran array using a separate, interoperable Fortran array.

Then I can calculate the pointer to a slice of the Fortran array, and copy either a single element, or a vector (C++ 1-D array) if the Fortran stride is 1.

0 Kudos
jimdempseyatthecove
Honored Contributor III
3,658 Views

IIF the allocation is performed on C/C++ && it is multi-dimensional.

THEN (on C/C++) allocate as single-dimensional (aka blob), then make arrays of pointers for use of multi-dimensional indexing on C/C++.

To pass to Fortran, you pass the base of the blob (and optionally the sizes of each rank). And then the receiving procedure in Fortran can call C_F_POINTER to construct a multi-dimensional array descriptor for use in Fortran.

 

Jim Dempsey

0 Kudos
AONym
New Contributor II
3,487 Views

Allocation is done by Fortran. Fortran then writes into the array; C++ only needs to read it, usually as a vector (meaning, a set of consecutive Fortran values into a 1-D C++ array).

0 Kudos
MWind2
New Contributor III
3,436 Views

Maybe this can help:

 

 

program fc

    USE, INTRINSIC::ISO_C_BINDING
INTERFACE
    SUBROUTINE fndcpp0 (pA,ia,ib,ic,id) BIND(C, name='fndcpp0')
    USE, INTRINSIC::ISO_C_BINDING
         TYPE(c_ptr), intent(IN):: pA
         integer ia,ib,ic,id
    END SUBROUTINE fndcpp0
    SUBROUTINE fndcpp1 (pA,ia,ib,ic,id) BIND(C, name='fndcpp1')
    USE, INTRINSIC::ISO_C_BINDING
         TYPE(c_ptr), intent(IN):: pA [value]
         integer ia [value],ib[value],ic[value],id [value]
    END SUBROUTINE fndcpp1
end INTERFACE
    ! Variables
    TYPE(c_ptr) :: cpA
    integer:: i0,i1,i2,i3
    integer ii,ij,ik,il
    integer irank
    integer isize
    integer itest
    integer, pointer,DIMENSION(:,:,:,:) :: A
    ! Body of fc
    i0=4
    i1=5
    i2=7
    i3=11    
    allocate (A(0:3,0:4,0:6,0:10))
    do ii=0,3
      do ij=0,4
       do ik=0,6
         do il=0,10
             !
             A(ii,ij,ik,il) = ishft(ii,24)+ ishft(ij,16)+ishft(ik,8)+il
         enddo
       enddo
      enddo
    enddo
    cpA = c_loc(A(0,0,0,0))
    itest=A(1,2,3,4)
    irank=rank(a)
    isize=size(a)
    
    
    call fndcpp0(cpA,i0,i1,i2,i3)
    call fndcpp1(cpA,i0,i1,i2,i3)
    print *, 'Hello World'

    end program fc

 

 

and for a cpp dll

 

 

#include "pch.h"
#include "framework.h"
#include "dcpp0.h"
#ifdef __cplusplus 
extern "C" {
#endif

// This is an example of an exported function.
DCPP0_API void fndcpp0(int ** pidata, int *ia,int *ib,int *ic, int *id)
{
    int i0, i1, i2, i3;
    i0 = *ia; i1 = *ib; i2 = *ic; i3 = *id;
    int itest = **(pidata);
    //itest = A(1, 2, 3, 4)
    //A(1,2,3,4)
    itest = *(*pidata + 4 * i2*i1*i0 + 3 * i1*i0 + 2 * i0 + 1);
}
DCPP0_API void fndcpp1(int* pidata, int ia, int ib, int ic, int id)
{
    int itest = *(pidata);
    //itest = A(1, 2, 3, 4)
    //   A(1,2,3,4)
    itest = *(pidata + 4 * ic * ib * ia + 3 * ib * ia + 2 * ia + 1);
}

#ifdef __cplusplus
}
#endif

 

 

0 Kudos
Steve_Lionel
Honored Contributor III
3,472 Views

Then you can pass it by reference, assuming you can compute the offsets into the array properly in C++, keeping in mind Fortran's column-major order and 1-origin.

0 Kudos
Reply