Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
Announcements
FPGA community forums and blogs on community.intel.com are migrating to the new Altera Community and are read-only. For urgent support needs during this transition, please visit the FPGA Design Resources page or contact an Altera Authorized Distributor.
29285 Discussions

Unhandled Exception when trying to pass Types with arrays from Fortran to C++

Denis2
Beginner
2,285 Views

I have defined Types in my Fortran program. In those Types there are 1-D and 2-D arrays defined. But when I try to call a routine defined in a C++ DLL I get an "Unhandled Exception" error. 

To better explain my issue I've written a basic Fortran code and basic C++ code that demonstrates the issue.

The Fortran code calling the C++ DLL is:

 
   IMPLICIT NONE
   
   TYPE :: ProbType
      INTEGER*4 :: mxw
      INTEGER*4 :: npr
      INTEGER*4, DIMENSION(:), POINTER :: pr
   END TYPE ProbType
   
   TYPE :: SolType
      INTEGER*4 :: npt
      INTEGER*4, DIMENSION(:), POINTER :: sc
      INTEGER*4, DIMENSION(:), POINTER :: nro
      INTEGER*4, DIMENSION(:,:), POINTER :: pt
   END TYPE SolType
 
   INTERFACE
      SUBROUTINE CPPRoutine(prob, solinit, solresult, action)
         import :: ProbType, SolType
         IMPLICIT NONE
         !DEC$ ATTRIBUTES STDCALL, DECORATE, ALIAS:"CPPRoutine" :: CPPRoutine
         !DEC$ATTRIBUTES VALUE :: action
         !DEC$ATTRIBUTES REFERENCE :: prob, solinit, solresult
         TYPE(ProbType)  prob
         TYPE(SolType) solinit
         TYPE(SolType) solresult
         INTEGER*4 action
      END SUBROUTINE CPPRoutine
   END INTERFACE
   
   TYPE(ProbType) :: prob
   TYPE(SolType)  :: solinit
   TYPE(SolType)  :: solresult
   INTEGER*4      :: action
   INTEGER*4      :: i, j
        
   
   prob%mxw = 600000
   prob%npr = 80 
   ALLOCATE (prob%pr(prob%npr))
   DO i = 1, prob%npr
      prob%pr(i) = i * 75
   ENDDO
   
   solinit%npt = 8
   ALLOCATE (solinit%sc(solinit%npt))
   ALLOCATE (solinit%nro(solinit%npt))
   ALLOCATE (solinit%pt(solinit%npt,prob%npr))
   DO i = 1, solinit%npt
      solinit%sc(i) = i*3
      solinit%nro(i) = i+1
      DO j = 1, solinit%nro(i)
         solinit%pt(i,j) = i * j
      ENDDO
   ENDDO
   
   CALL CPPRoutine(prob, solinit, solresult, action)
   
   DEALLOCATE(prob%pr)
   DEALLOCATE(solinit%sc)
   DEALLOCATE(solinit%nro)
   DEALLOCATE(solinit%pt)
    
   RETURN
    
   END

The C++ code inside the DLL is:

The KBP.cpp file contains:

#include "KBP.h"

#include <algorithm>
#include <fstream>
#include <iostream>
using namespace std;

void __declspec(dllexport) _stdcall CPPRoutine(Prob* prob, Sol* sol, Sol* result, int action)
{

    ofstream file("c:\\input.txt");
    file << "mxw = " << prob->mxw << endl;
    file << "npr = " << prob->npr << endl;

    file << "pr = ";
    for (int i = 0; i < prob->npr; ++i) file << prob->pr << " ";
    file << endl;

    file << "npt = " << sol->npt << endl;
    file << "sc = ";
    for (int i = 0; i < sol->npt; ++i) file << sol->sc << " ";
    file << endl;
    file << "nro = ";
    for (int i = 0; i < sol->npt; ++i) file << sol->nro << " ";
    file << endl;

    for (int i = 0; i < sol->npt; ++i)
    {
        file << "pt[" << i << "] = ";
        for (int j = 0; j < sol->nro; ++j)
            file << sol->pt << " ";
        file << endl;
    }
    file << endl;
    file.close();

    int npt = sol->npt - 1;

    result->npt = npt;
    result->sc = new int[npt];
    result->nro = new int[npt];
    result->pt = new int*[npt];

    for (int i = 0; i < npt; ++i)
    {
        result->sc = sol->sc;
        result->nro = sol->nro;
        result->pt = new int[sol->nro];
        for (int j = 0; j < sol->nro; ++j)
            result->pt = sol->pt;
    }

    return;
    
}

The KBP.h file contains:

extern "C"
{
    struct Prob
    {
        int mxw;
        int npr;
        int* pr;
    };

    struct Sol
    {
        int npt;
        int* sc;
        int* nro;
        int** pt;
    };

    void __declspec(dllexport) _stdcall CPPRoutine(Prob* prob, Sol* sol, Sol* result, int action);
}

What am I doing wrong? Any help is much appreciated. 

Thanks,

Denis

PS: For your info, I'm running Intel Parallel Studio XE 2015 Composer Edition For Fortran Windows and Visual Studio 2013  

0 Kudos
11 Replies
TimP
Honored Contributor III
2,285 Views

As you're talking about Fortran (not about legacy DVF/CVF extensions which predate f2003?), you might consider USE ISO_C_BINDING. MR&C "modern fortran explained" has fairly complete examples; there are more, including POINTER, in gfortran on-line docs (not to mention what comes with ifort).

You didn't say if you are trying to use stdcall in a way restricted to 32-bit mode.  stdcall is usually to be avoided when possible, as it was obsoleted 15 years ago, except for its continued use in Windows OS calls.

0 Kudos
Denis2
Beginner
2,285 Views

Hello Tim,

Thanks for your response. I have followed your suggestion: I have removed the stdcall keyword from the C++ code and I have used USE_ISO_BINDING in Fortran. The Fortran code becomes:


   USE ISO_C_BINDING
   
   IMPLICIT NONE
   
   TYPE, BIND(C) :: ProbType
      INTEGER(C_INT) :: mxw
      INTEGER(C_INT) :: npr
      INTEGER(C_INT) :: pr(80)
   END TYPE ProbType
   
   TYPE, BIND(C)  :: SolType
      INTEGER(C_INT) :: npt
      INTEGER(C_INT) :: sc(100)
      INTEGER(C_INT) :: nro(100)
      INTEGER(C_INT) :: pt(100,80)
   END TYPE SolType
 
   INTERFACE
      SUBROUTINE CPPRoutine(prob, solinit, solresult, action) BIND (c, name="CPPRoutine")
         USE ISO_C_BINDING
         IMPORT :: ProbType, SolType
         IMPLICIT NONE
         TYPE(ProbType) :: prob
         TYPE(SolType)  :: solinit
         TYPE(SolType)  :: solresult
         INTEGER(C_INT), VALUE :: action
      END SUBROUTINE CPPRoutine
   END INTERFACE
   
   TYPE(ProbType) :: prob
   TYPE(SolType)  :: solinit
   TYPE(SolType)  :: solresult
   INTEGER*4      :: action
   INTEGER*4      :: i, j
        
   
   prob%mxw = 600000
   prob%npr = 80 
   DO i = 1, prob%npr
      prob%pr(i) = i * 75
   ENDDO
   
   solinit%npt = 8
   DO i = 1, solinit%npt
      solinit%sc(i) = i*3
      solinit%nro(i) = i+1
      DO j = 1, solinit%nro(i)
         solinit%pt(i,j) = i * j
      ENDDO
   ENDDO
   
   CALL CPPRoutine(prob, solinit, solresult, action)
   
   RETURN
    
   END

Unfortunately this still doesn't work. It still raises an unhandled exception error. What am I still doing wrong?

Thanks,

Denis 

0 Kudos
mecej4
Honored Contributor III
2,285 Views

From looking at the two attempts above to get C and Fortran working in a complex situation, I am afraid that I must say that this is going to fail. There are far too many things wrong. Here are a few points that you must understand and master before trying again.

  • Fortran and C have similarities, but they have plenty of dissimilarities. Two dimensional arrays declared as int ** in C are very different from a Fortran two-dimensional array. In your case, on the C side you have an array of pointers to arrays. On the Fortran side, what you have is really a one dimensional array plus a convention for obtaining an offset into the 1-D array from a pair of subscripts and the leading dimension in the declaration of the array. A Fortran integer array of M X N elements consumes M.N times 4 or 8 bytes, depending on the size of the integer. The C version, on the other hand, is going to need that much for the array contents plus space for an additions M or N C-pointers, which themselves can be 4 or 8 bytes each. 
  • Fortran pointers are far more complicated objects than C pointers. Often, there is no simple one-to-conversion from one to the other, which is why in the chapter on Fortran-C interoperability of your Fortran manual or the Fortran standard you will find lots of restrictions on passing arguments from one to the other and a number of intrinsic "helper" functions that you are required to use. When you bring in structures too, in addition to intrinsic types, things get even more complicated.

Although what you are attempting to do may be achievable, the work involved will be considerable, and you will probably not like the results. Please consider redesigning the boundary (where C and Fortran are to interface in your code) in such a way that you pass only simple variables and arrays of simple variables across the boundary.

The access violations that you saw are caused by the C code using variable values as addresses, and vice versa. The Fortran side did not give C what the latter expects, nor is it possible to do so in a reasonable way.

One of the other regular posters here, "Repeat Offender", is an expert in this topic. I look forward to hearing his assessment of your situation.

0 Kudos
FortranFan
Honored Contributor III
2,285 Views

Denis wrote:

..I have used USE_ISO_BINDING in Fortran. The Fortran code becomes:

   USE ISO_C_BINDING
   
   IMPLICIT NONE
   
   TYPE, BIND(C) :: ProbType
      INTEGER(C_INT) :: mxw
      INTEGER(C_INT) :: npr
      INTEGER(C_INT) :: pr(80)
   END TYPE ProbType
   
   TYPE, BIND(C)  :: SolType
      INTEGER(C_INT) :: npt
      INTEGER(C_INT) :: sc(100)
      INTEGER(C_INT) :: nro(100)
      INTEGER(C_INT) :: pt(100,80)
   END TYPE SolType
 
 ..

Have you tried the following in your C++ code:

extern "C"
{
    struct Prob
    {
        int mxw;
        int npr;
        int pr[80];
    };

    struct Sol
    {
        int npt;
        int sc[100];
        int nro[100];
        int pt[80][100];
    };

 

0 Kudos
Denis2
Beginner
2,285 Views

FortranFan - Yes I did and it works. But ideally I would like to avoid hard-coding the size of the arrays in both the Fortran TYPE and in the C struct.

0 Kudos
FortranFan
Honored Contributor III
2,285 Views

Denis wrote:

FortranFan - Yes I did and it works. But ideally I would like to avoid hard-coding the size of the arrays in both the Fortran TYPE and in the C struct.

Ok, good -so you've a foundation to build on.  I think if you want to interoperate Fortran allocatable types with C/C++, then you need to look into enhanced C interoperability features in Fortran 2015 that Intel has now incorporated into 16.0 compiler version.  See Steve Lionel's posts in this thread: https://software.intel.com/en-us/forums/intel-fortran-compiler-for-linux-and-mac-os-x/topic/590170

 

 

0 Kudos
Lorri_M_Intel
Employee
2,285 Views

Just a quick note about the enhanced C interoperability features; these do not extend to fields in a derived type.

That is, you will not be able to declare this Fortran derived type using the enhanced interoperability:

   TYPE :: SolType
      INTEGER*4 :: npt
      INTEGER*4, DIMENSION(:), POINTER :: sc
      INTEGER*4, DIMENSION(:), POINTER :: nro
      INTEGER*4, DIMENSION(:,:), POINTER :: pt
   END TYPE SolType

However, you would be able to pass any of the fields to a C routine.

Wait.  Wow.  That sounded confusing when I re-read it, so let me try again.

You can pass solType%nro or solType%sc or solType%pt to a C routine expecting a standard Fortran descriptor, but you will not be able to pass solType to a C routine, and have the C routine see the "nro" or "sc" or "pt" fields as standard Fortran descriptors.

    Does this make sense?

                              --Lorri

 

 

0 Kudos
mecej4
Honored Contributor III
2,285 Views

Lorri Menard (Intel) wrote:

Just a quick note about the enhanced C interoperability features; these do not extend to fields in a derived type.

That is, you will not be able to declare this Fortran derived type using the enhanced interoperability:

   TYPE :: SolType
      INTEGER*4 :: npt
      INTEGER*4, DIMENSION(:), POINTER :: sc
      INTEGER*4, DIMENSION(:), POINTER :: nro
      INTEGER*4, DIMENSION(:,:), POINTER :: pt
   END TYPE SolType

However, you would be able to pass any of the fields to a C routine.

Wait.  Wow.  That sounded confusing when I re-read it, so let me try again.

What's wrong with me? It made perfect sense!

You can pass solType%nro or solType%sc or solType%pt to a C routine expecting a standard Fortran descriptor, but you will not be able to pass solType to a C routine, and have the C routine see the "nro" or "sc" or "pt" fields as standard Fortran descriptors.

    Does this make sense?

Unless C has been recently changed to allow declaring variables with the attribute "___Fortran_______descriptor____" or something like that, C would continue to see everything through the C-thru lens! After all, the C programmer's view of Fortran, as codified in http://www.netlib.org/clapack/f2c.h , is 

/**  barf  [ba:rf]  2.  "He suggested using FORTRAN, and everybody barfed."

    - From The Shogakukan DICTIONARY OF NEW ENGLISH (Second edition) */

 

0 Kudos
Denis2
Beginner
2,285 Views

Many thanks all!

I will for now stick to the simple solution that is to use arrays of explicit shape in the derived type with BIND attribute.

Later when we'll upgrade to Intel Parallel Studio XE 2016 I will give a try to the solution that is to remove the derived types and use a C routine expecting Fortran descriptors.

Best Regards,

Denis.  

0 Kudos
FortranFan
Honored Contributor III
2,285 Views

Denis wrote:

.. I will for now stick to the simple solution that is to use arrays of explicit shape in the derived type with BIND attribute. ..

Is it possible for you to do the malloc'ing and freeing of the struct on the C++ DLL side instead of in Fortran?  You can introduce something like CPRInit and CPRFree functions; the former can take parameters from Fortran for the problem size and C++ could then allocate the struct of component(s) of appropriate size(s).  You can then define the derived type in Fortran to be interoperable with C struct as in:

   use, intrinsic :: iso_c_binding, only : c_int, c_ptr
   
   ..

   type, bind(c) :: Prob
      integer(c_int) :: mxw
      integer(c_int) :: npr
      type(c_ptr)    :: pr
   end type t

and use c_f_pointer function is ISO_C_BINDING to create an allocatable array of the right size on the Fortran to work with the data.  This way you won't need to constrain yourself to use explicitly sized arrays which would mean working with problem of up to some ("large enough") size and wasted memory for smaller problems.

 

 

0 Kudos
Denis2
Beginner
2,285 Views

FortranFan - Sorry for the late reply. I have finally do what you suggested, i.e.  do the malloc'ing, freeing of the struct on the C++ DLL and use c_f_pointer function. This works well. Many thanks!

Denis.

0 Kudos
Reply