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

Fortran -> C Interop Struggle

Krob__Jeff
Beginner
777 Views

All,

Trying to bone-up on calling C routines from Fortran in IVF Parallel Studio XE 2015 Composer. I thought the code was fairly simple & straight forward but a persistent error is stumping me...

error #6634: The shape matching rules of actual arguments and dummy arguments have been violated.   [IX] [IY] 

The error is at the call to C_routine - "call C_croutine (ix, iy, icountsin, icountsout)"

I thought everything pertaining to arrays ix & iy was in agreement but...IVF doesn't agree. I'm sure it is something simple.


Here is the code - Thanks in advance, Jeff

***********************************************************************************************

    program Fortran2C

    use, intrinsic :: ISO_C_BINDING
   
     interface
     SUBROUTINE C_croutine(ix, iy, icountsin, icountsout) BIND(C)
        IMPORT ! Use declarations from host

        implicit none
        integer (C_INT), value :: ix
        integer (C_INT), value :: iy
        integer (C_INT), value :: icountsin
        integer (C_INT), value :: icountsout

     end SUBROUTINE C_croutine
   end interface
!    implicit none

    ! Variables
    integer  :: ix(10)
    integer  :: iy(10)
    integer  :: icountsin
    integer  :: icountsout

    ! Body of Fortran2C
    OPEN(25,FILE='Fortran2C.txt',STATUS='UNKNOWN')

    icountsout = 0
    icountsin = 0
    do i=1,10
      ix(i) = i
      iy(i) = i
      icountsin = icountsin + 1
      write(25,*)'itestx/y in = ',i,ix(i),iy(i)
    enddo

    call C_croutine (ix, iy, icountsin, icountsout)

    do i=1,icountsout
      write(25,*)'itestx/y out = ',i,ix(i),iy(i)
    enddo

    end program Fortran2C

void C_croutine (int ix[], int iy[], int icountsin, int icountsout)

{
int    ii;

    icountsout = 0;
    for ( ii = 1; ii < icountsin; ii++ )  {
    ix[ii] = ix[ii]+1;
    iy[ii] = iy[ii]+1;
    icountsout = icountsout+1;
    }

    return;
}

 

0 Kudos
5 Replies
FortranFan
Honored Contributor III
777 Views

See this thread: https://software.intel.com/en-us/forums/intel-visual-fortran-compiler-for-windows/topic/505505

Here's a modified version of your code you can review and evaluate: note the modification to the last dummy argument (parameter in C parlance) and the change to the interface on the Fortran side, given how arrays are passed in C (reference to a pointer address):

void C_routine(int ix[], int iy[], int icountsin, int *icountsout)
{
   int ii;

   *icountsout = 0;
   for ( ii = 0; ii < icountsin; ii++ )  {
      ix[ii] = ix[ii]+1;
      iy[ii] = iy[ii]+1;
      *icountsout = *icountsout+1;
   }

   return;
}
program Fortran2C

   use, intrinsic :: iso_c_binding, only : c_int
   use, intrinsic :: iso_fortran_env, only : output_unit

   implicit none

   interface

      subroutine C_routine(ix, iy, icountsin, icountsout) bind(C, name="C_routine")

         import :: c_int

         implicit none

         integer(c_int), intent(inout) :: ix(*)
         integer(c_int), intent(inout) :: iy(*)
         integer(c_int), value         :: icountsin
         integer(c_int), intent(inout) :: icountsout

      end subroutine C_routine

   end interface

   ! Variables
   integer :: ix(10)
   integer :: iy(10)
   integer :: icountsin
   integer :: icountsout
   integer :: i

   icountsout = 0
   icountsin = 0
   do i=1,10
      ix(i) = i
      iy(i) = i
      icountsin = icountsin + 1
      write(output_unit,*)'itestx/y in  = ',i,ix(i),iy(i)
   end do

   call C_routine (ix, iy, icountsin, icountsout)

   do i=1,icountsout
      write(output_unit,*)'itestx/y out = ',i,ix(i),iy(i)
   end do

   stop

end program Fortran2C
 itestx/y in  =  1 1 1
 itestx/y in  =  2 2 2
 itestx/y in  =  3 3 3
 itestx/y in  =  4 4 4
 itestx/y in  =  5 5 5
 itestx/y in  =  6 6 6
 itestx/y in  =  7 7 7
 itestx/y in  =  8 8 8
 itestx/y in  =  9 9 9
 itestx/y in  =  10 10 10
 itestx/y out =  1 2 2
 itestx/y out =  2 3 3
 itestx/y out =  3 4 4
 itestx/y out =  4 5 5
 itestx/y out =  5 6 6
 itestx/y out =  6 7 7
 itestx/y out =  7 8 8
 itestx/y out =  8 9 9
 itestx/y out =  9 10 10
 itestx/y out =  10 11 11
Press any key to continue . . .

 

0 Kudos
Krob__Jeff
Beginner
777 Views

Thanks for the reply - I'm pretty sure I made all the changes you noted...but now I'm getting;

error LNK2019: unresolved external symbol _C_routine referenced in function _MAIN__    Fortran2C.obj    

Are there some 'Properties' settings which need to be adjusted (Fortran or C)?

Also, as to passing "icountsout", if it is not used as a pointer within C_routine, does it still need to be passed as a pointer (I prefer to avoid pointer use)?

Thanks again,

Jeff

 

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
777 Views

That is a linker error. Either

a) you are not linking in C_routine.obj (or whatever name of the object file was when you built it)
or
b) You compiled the C_routine.cpp as a .CPP file type which uses name mangled entry points. If you do use CPP compiler then you must decorate your function with

extern "C"

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor III
777 Views

Jeff K. wrote:

Thanks for the reply - I'm pretty sure I made all the changes you noted...but now I'm getting;

error LNK2019: unresolved external symbol _C_routine referenced in function _MAIN__    Fortran2C.obj    

Are there some 'Properties' settings which need to be adjusted (Fortran or C)?

Also, as to passing "icountsout", if it is not used as a pointer within C_routine, does it still need to be passed as a pointer (I prefer to avoid pointer use)?

Thanks again,

Jeff

As Jim indicated, you need to make sure the object for your C routine is appropriately included in the link command.

Re: your other question on icountsout, you need to spend some time to learn how C works and what you need to do if you want a variable to be modified within a C function.  As you'd know, there are lots of resources online e.g., http://www.tutorialspoint.com/cprogramming/c_function_call_by_reference.htm.

0 Kudos
Krob__Jeff
Beginner
777 Views

All,

OK - got it ironed out. The Build Order/Dependencies was backwards - C_routine was dependent to & built after Fortran2C instead of vice-versa. Now, time to start experimenting with passing different arguments/parameters to C_routine, modifying them & see what is returned.

OH JOY!! ;-)

Thanks again,

Jeff

0 Kudos
Reply