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

How to pass an allocated array to C?

AONym
New Contributor II
2,409 Views

In a Fortran subroutine, I allocate an array. This subroutine calls a C++ function, which will store its results in the allocated array. I am having trouble passing the address of the allocated array to the C++ function.

Here is what I am doing now:

    REAL(C_DOUBLE), DIMENSION(:,:,:), ALLOCATABLE, TARGET :: output
    TYPE(C_PTR) :: pOutput  

    INTERFACE
        INTEGER(C_INT) FUNCTION CFunction&
            (p1, p2, p3, p4, pOutput) &
            BIND(C, name='CFunction')
            USE, INTRINSIC :: ISO_C_BINDING
            IMPLICIT NONE
            REAL(C_DOUBLE), INTENT(IN), VALUE :: p1
            REAL(C_DOUBLE), INTENT(IN), VALUE :: p2
            REAL(C_DOUBLE), INTENT(IN), VALUE :: p3
            REAL(C_DOUBLE), INTENT(IN), VALUE :: p4
           TYPE(C_PTR) :: pOutput
        END FUNCTION CFunction
    END INTERFACE

ALLOCATE(output(n1, n2, n3), STAT = allocationStatus)
    pOutput=C_LOC(output)

    err = CFunction(p1,p2, p3, p4, pOutput)

The C++ function looks like

extern "C" int LammSolve(const double p1, const double p2,
    const double p3, const double p4, double *output)

and stores values as

output=value;

This definitely doesn't work. The returned value of the output array looks as if its array descriptor has been overwritten by C++ (presumably by storing into output[0]). Is there a way I can pass the address of the Fortran-allocated array to C, without parsing array descriptors?

64-bit Windows 7, Visual Studio 2015, Intel Fortran XE 2017 u 4.

 

0 Kudos
6 Replies
Arjen_Markus
Honored Contributor I
2,409 Views

Since the array descriptors used in Fortran are not exposed (at least not in the C-Fortran interfacing defined in Fortran 2003, there is a technical report regarding this aspect), you should not try to take advantage of that. The difficulty is actually quite simple:

TYPE(C_PTR) :: pOutput

means that you pass an address to C++ as void ** - you can use instead:

REAL(C_DOUBLE), DIMENSION(*) :: pOutput

which on the C++ becomes "double *", so the address to the first element of the array.

If you really need a void * pointer, then "TYPE(C_PTR), VALUE" will do it.

 

 

0 Kudos
AONym
New Contributor II
2,409 Views

 I changed the declaration to

  REAL(C_DOUBLE), DIMENSION(*) :: pOutput

and line

    pOutput=C_LOC(output)

gets error #6364: The upper bound shall not be omitted in the last dimension of a reference to an assumed size array.   [POUTPUT].

Changing it to

   pOutput(1)=C_LOC(output)

gives error #6303: The assignment operation or the binary expression operation is invalid for the data types of the two operands.

So I guess I don't understand your suggestion; can you clarify?. The C function does need double *, although I could easily cast void * to that if necessary.

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,409 Views

pOutput=C_LOC(output(1))

Jim Dempsey

0 Kudos
AONym
New Contributor II
2,409 Views

 With the declarations

   REAL(C_DOUBLE), DIMENSION(:,:,:), ALLOCATABLE, TARGET :: output
  REAL(C_DOUBLE), DIMENSION(*) :: pOutput

I get with

    pOutput=C_LOC(output(1))

error #6364: The upper bound shall not be omitted in the last dimension of a reference to an assumed size array.   [POUTPUT]
error #6351: The number of subscripts is incorrect.   [OUTPUT]
error #6303: The assignment operation or the binary expression operation is invalid for the data types of the two operands.
error #6633: The type of the actual argument differs from the type of the dummy argument.   [POUTPUT]
 error #6634: The shape matching rules of actual arguments and dummy arguments have been violated.   [POUTPUT]
 error #6221: The assumed-size array must be a dummy argument.   [POUTPUT]

 And with

  pOutput=C_LOC(output(1,1,1))

 error #6364: The upper bound shall not be omitted in the last dimension of a reference to an assumed size array.   [POUTPUT]
 error #6303: The assignment operation or the binary expression operation is invalid for the data types of the two operands.
error #6633: The type of the actual argument differs from the type of the dummy argument.   [POUTPUT]
error #6634: The shape matching rules of actual arguments and dummy arguments have been violated.   [POUTPUT]
error #6221: The assumed-size array must be a dummy argument.   [POUTPUT]

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,409 Views

REAL(C_DOUBLE), DIMENSION(:,:,:), ALLOCATABLE, TARGET :: output
you want something like this:

subroutine foo
    implicit none
    real, dimension(:,:,:), allocatable, target :: output
    real, dimension(:), pointer :: pOutput
    
    allocate(output(10,20,30))
    pOutput(1:size(output)) => output(:,:,:)
    output(1,1,1) = 123.456

    print *, size(output), size(pOutput), output(1,1,1), pOutput(1)
!    err = CFunction(p1,p2, p3, p4, C_LOC(pOutput(1))
! *** err and CFunction, p1,p2, p3, p4 are for you to define ***
end subroutine foo

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor II
2,409 Views

jimdempseyatthecove wrote:

.. you want something like this:

subroutine foo
    implicit none
    real, dimension(:,:,:), allocatable, target :: output
    real, dimension(:), pointer :: pOutput
    
..

Jim,

If there is a separate need for a local variable with a POINTER attribute, then it is a separate matter but otherwise it is generally better for most coders to stay away from variables with the POINTER attribute to avoid potential issues with such variables.

@Ann O.,

You can follow Arjen Markus' suggestion in Message #5 which was only to modifiy the INTERFACE block to include the VALUE attribute with your pOutput dummy argument.  Here's a complete example you can review and try out:

#include "stdio.h"

// Function prototype
int CFunction(const double p1, const double p2,
    const double p3, const double p4, double *output);

// Function implementation
int CFunction(const double p1, const double p2,
    const double p3, const double p4, double *output) {

   printf("In CFunction:\n");

   output[0] = 99.0;

   printf("p1 = %f\n", p1);
   printf("p2 = %f\n", p2);
   printf("p3 = %f\n", p3);
   printf("p4 = %f\n", p4);
   printf("output[0] set to %f\n", output[0]);

   return(0);

}
module m

   use, intrinsic :: iso_c_binding, only : c_int, c_double, c_ptr, c_loc

   implicit none

   private

   interface

      function CFunction( p1, p2, p3, p4, pOutput) result( iret ) bind(C, name='CFunction')

         import :: c_int, c_double, c_ptr

         implicit none

         ! Argument list
         real(c_double), intent(in), value :: p1
         real(c_double), intent(in), value :: p2
         real(c_double), intent(in), value :: p3
         real(c_double), intent(in), value :: p4
         type(c_ptr), intent(in), value    :: pOutput  !<- note the VALUE attribute
         ! Function result
         integer(c_int) :: iret

      end function CFunction

   end interface

   public :: sub

contains

   subroutine sub()

      ! Local variables
      real(c_double), allocatable, target :: Output(:,:,:)
      real(c_double) :: p1
      real(c_double) :: p2
      real(c_double) :: p3
      real(c_double) :: p4
      integer :: n1
      integer :: n2
      integer :: n3
      integer(c_int) :: istat

      n1 = 2
      n2 = 2
      n3 = 2
      allocate( Output(n1,n2,n3), stat=istat )
      if ( istat /= 0 ) then
         ! error handling elided; error stop for this simple example
         error stop
      end if

      Output = 0.0_c_double
      p1 = 1.0_c_double
      p2 = 2.0_c_double
      p3 = 3.0_c_double
      p4 = 4.0_c_double
      istat = CFunction(p1, p2, p3, p4, c_loc(Output))

      print *, "In sub: Output = ", Output

      return

   end subroutine sub

end module m
program p

   use, intrinsic :: iso_fortran_env, only : compiler_version

   use m, only : sub

   print *, "Compiler Version: ", compiler_version()

   call sub()

   stop

end program p

Upon execution with Intel Fortran,

 Compiler Version:
 Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on IA-32,

  Version 18.0.0.065 Beta Build 20170320

In CFunction:
p1 = 1.000000
p2 = 2.000000
p3 = 3.000000
p4 = 4.000000
output[0] set to 99.000000
 In sub: Output =  99.0000000000000 0.00000000000000
 0.00000000000000 0.00000000000000 0.00000000000000
 0.00000000000000 0.00000000000000 0.00000000000000

 

Reply