1

I want to combine C++ and Fortran together. My Fortran code will use a C++ function and C++ function changes variables of Fortran and sends them back. The C++ function is built with other C++ codes, e.g. the C++ function will use some sub-function in other .cpp file. I make the Fortran code with ifort and I added that C++ function as one object file, test.o in my Fortran makefile. I also put every needed C++ .o file(support test.o) in makefile. It shows the error

#6633, "The type of the actual argument differs from the type of the dummy argument".

Here is the code.

Fortran code

  use, intrinsic :: ISO_C_BINDING, only: C_INT, C_DOUBLE   
  implicit double precision(a-h,o-z),integer(i-n)
  Interface
   integer (C_INT) function SolveBIE_(x, y, aa, m) BIND(C, NAME='SolveBIE_')
   use, intrinsic :: ISO_C_BINDING
   implicit none
   type (C_PTR), value :: x
   type (C_PTR), value :: y
   type (C_PTR), value :: aa
   integer (C_INT), value :: m
   end function SolveBIE_
  end Interface
  integer (C_INT) :: m
  real (C_DOUBLE), ALLOCATABLE, DIMENSION(:,:), target :: x
  real (C_DOUBLE), ALLOCATABLE, DIMENSION(:,:), target :: y
  real (C_DOUBLE), ALLOCATABLE, DIMENSION(:,:), target :: aa
  ALLOCATE(x(0:MAXLEN,MAXINTERFACES))
  ALLOCATE(y(0:MAXLEN,MAXINTERFACES))
  ALLOCATE(aa(0:MAXLEN,MAXINTERFACES))

My Fortran code run

  mm = SolveBIE_(x(1,1),y(1,1),aa(1,1),m) 

Using the C++ code and where the error is from, on x, y, aa I use x(1,1) instead of x, because if using x, then there is another error

#6634,"the shape matching rules of actual arguments and dummy arguments have been violated"`

I don't understand why it should be x(1,1). Why is this working, not x?

My C++ code

  #ifdef __cplusplus
  extern "C" {
  #endif
  int solveBIE_(double *ini_bdry_x, double *ini_bdry_y, double *ini_bdry_um, int *fM)
{  
     double(*bdry_node)[2] = new double[M1][2];
     for (int k = 0; k < M; k++) {
        bdry_node[k+1][0] = ini_bdry_x[k+1];
        bdry_node[k+1][1] = ini_bdry_y[k+1];
        bdry_theta[k+1] = Atan(ini_bdry_x[k+1], ini_bdry_y[k+1]);}

    ... some functions in other .cpp file
Yue
  • 23
  • 6
  • Follow this [tutorial](http://docs.cray.com/books/S-2179-52/html-S-2179-52/ppgzmrwh.html) and ask for help when you get stuck – Victor M Perez Feb 06 '18 at 16:10
  • 1
    It would be helpful to break that first paragraph up a little. And also give the full error message. However, the error message, if it's referring to the arguments to `SolveBIE_` seems quite clear to me (`type(c_ptr)` and `real(c_double)` aren't the same). What is it you don't understand about it? – francescalus Feb 06 '18 at 16:21
  • I don't really understand what you are saying. Especially not the bit about `x` and `x(1,1)`. Please always show the complete code and the complete error message (or the whole output). – Vladimir F Героям слава Feb 06 '18 at 19:13
  • @VictorHerasmePerez That tutorial is *very* obsolete. The OP is using techniques which are much more modern. – Vladimir F Героям слава Feb 06 '18 at 19:15

1 Answers1

2

The way your interface is written, you have to construct a C_PTR to array x and pass that as the first argument:

use, intrinsic :: ISO_C_BINDING, only: C_INT, C_DOUBLE, C_PTR, C_LOC
! ...
type(C_PTR) PTRx
! ...
PTRx = C_LOC(x(LBOUND(x,1),LBOUND(x,2)))
! ...
mm = solveBIE_(PTRx, PTRy, PTRaa, m)

As shown above, you would have to fix the next two arguments as well. But you need to rewrite the interface for argument fM because as matters stand, Fortran will pass an integer by value whereas C++ is expecting a pointer. Given that, I would rewrite the interface completely, using the names given for the arguments in the C++ function and passing everything by reference. Names for dummy arguments are potentially visible in Fortran, so it's useful for them to be meaningful. In the following I assume that fM points to a scalar in the callee:

  Interface
   function SolveBIE_(ini_bdry_x, ini_bdry_y, ini_bdry_um, fM) &
      BIND(C, NAME='SolveBIE_')
   import
   implicit none
   integer(C_INT) SolveBIE_
   real(C_DOUBLE) :: ini_bdry_x(*)
   real(C_DOUBLE) :: ini_bdry_y(*)
   real(C_DOUBLE) :: ini_bdry_um(*)
   integer (C_INT) :: fM
   end function SolveBIE_
  end Interface

Then later on you can invoke it more or less normally as

mm = SolveBIE_(x,y,aa,m)

Note that x(1,1) was wrong because LBOUND(x,1) = 0, not 1!

user5713492
  • 954
  • 5
  • 11
  • Thank you for the advise. I have a question, should I use the same way to define the ini_bdry_x(*), e.g. real (C_DOUBLE), ALLOCATABLE, DIMENSION(:,:), target :: x ALLOCATE(x(0:MAXLEN,MAXINTERFACES)) Because I need to set value for them, then pass them to C++. So it is necessary to define them firstly. – Yue Feb 08 '18 at 19:20
  • Right, you have to do all that other stuff that you're already doing. My intent was not to rewrite your whole program for you, just to present the changes I would make. – user5713492 Feb 09 '18 at 04:11
  • Thank you. There is no error now. But I have a compile error. I posted as another question. Here is the link.https://stackoverflow.com/questions/48696645/compile-error-when-binding-c-and-fortran – Yue Feb 12 '18 at 15:26