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

Mixed language: Passing a type and pointer variables between FORTRAN and C

fdc_dhi
Beginner
286 Views
I have a problem when mixing FORTRAN and C and passing types (struct in C) and pointers from a FORTRAN program to a C function. (Visual studio 6.6). Below of this post, the code for both the FORTRAN and the C are shown:
I can pass a very simple type variable (See TEST CASE in the code) of the type:
type comstruct
nteger n
real*4 a
endtype
type(comstruct) kurt

However the more complex type, I can?t pass it correctly and an error occurs ion the C-code (marked in the code with ERROR; WHAT SHOULD I DO ?)
The complex type variables:
! THE REAL CASE:
! Points for a polygon:
type tPoint
real*8 x
real*8 y
endtype
! A polygon:
type tPolygon
integer nPoints
integer iPoints
type(tPoint),pointer:: Node(:)=> NULL()
endtype


Please see the code below here) and reply to my post, if you can come up with a good idee to solve my problem.

!################################################
!###### FORTRAN CODE ##########################
!################################################
logical function calculatePolygon()
INTERFACE
! THE TEST CASE:
SUBROUTINE GETZONATIONPOLYGON_C_TEST [stdcall](block,block2,kurt)
INTEGER block [REFERENCE]
END SUBROUTINE GETZONATIONPOLYGON_C_TEST
! THE REAL CASE:
SUBROUTINE GETZONATIONPOLYGON_C [stdcall](block,block2,kurt)
INTEGER block [REFERENCE]
INTEGER block2 [REFERENCE]
integer kurt [VALUE]
END SUBROUTINE GETZONATIONPOLYGON_C
END INTERFACE

! ... some code ....
! THE TEST CASE:
type comstruct
integer n
real*4 a
endtype
type(comstruct) kurt

! THE REAL CASE:
! Points for a polygon:
type tPoint
real*8 x
real*8 y
endtype
! A polygon:
type tPolygon
integer nPoints
integer iPoints
type(tPoint),pointer:: Node(:)=> NULL()
endtype

type(tPolygon),pointer:: Polygon(:) => NULL()
integer iscatch,nsubcatch
! ... some more code ...
nsubcatch=25 ! found by a function call

Allocate(Polygon(nsubcatch),stat=irc)
! ... some more code ...
do iscatch=1,nsubcatch
Allocate(Polygon(iscatch)%Node(Polygon(iscatch)%nPoints),stat=irc)
enddo
! THE TEST CASE:
kurt%n=1
kurt%a=0
call getzonationpolygon_c_test(kurt%n) !Works fine
call getzonationpolygon_c(kurt%n,Polygon(1)%nPoints,GET_NSCATCH()) !Problem in the C-code

!###################################################
!#### C CODE (not cpp) ############
!###################################################
#include
#include
#define GETZONATIONPOLYGON_C getzonationpolygon_c
#define GETZONATIONPOLYGON_C_TEST getzonationpolygon_c_test

// / Test case struct variable
#pragma pack(2)
struct comstruct
{
int n;
double A;
};
#pragma pack()

#pragma pack(2)
// /Real case struct variable
struct Point
{
double x;
double y;
};
#pragma pack()
#pragma pack(2)
struct Polygon
{
int nPoints;
int iPoints;
struct Point *pNode;
};
#pragma pack()
// The real function
extern void __stdcall GETZONATIONPOLYGON_C(struct comstruct *TEST,
struct Polygon **pPolygon,
int nsubcatch)
{
int i;
TEST->n =500; // just fo r test WORKS FINE
TEST->A = TEST->A + 25.; // just for test WORKS FINE
for(j=1;j<=nsubcatch;i++)
{
pPolygon->nPoints =25; ! ERROR; WHAT SHOULD I DO ????
// some more code ....
}
}
// Test function for the test struct variable->WORKS FINE
extern void __stdcall GETZONATIONPOLYGON_C_TEST(struct comstruct *TEST)
{
TEST->n =500;
TEST->A = TEST->A + 25.;
}

0 Kudos
1 Reply
Jugoslav_Dujic
Valued Contributor II
286 Views
OK, let's examine it step by step. Let's assume that the block for Polygon is allocated at 0x4000; that's the address of Polygon(1)%nPoints as well. This is what is passed on the stack. However, you're referencing

pPolygon->nPoints

meaning

*(0x4000 + j*sizeof(Polygon) + 0)

I.e. you're referencing an invalid address. For the start, you'd probably want to declare pPolygon as struct Polygon*, not struct Polygon**, and reference it as pPolygon.nPoints.

However, there are more problems than that. Fortran POINTER is not the same as C pointer -- neither on semantic nor on hardware level. Thus,

struct Point *pNode;

is not equivalent of

type(tPoint),pointer:: Node(:)

neither is SIZEOF(tPolygon) == sizeof(Polygon). {Type(tPoint),pointer} can be described as a struct whose format is described in "Handling Arrays and Visual Fortran Array Descriptors" page. But you probably don't want to cope with its contents -- consider rewriting without POINTER components, if possible.

Few stylistic nitpicks: you're using deprecated form of attributes such as [STDCALL]. This originates from MS FPS and is not documented (and possibly won't be supported in future VF releases) -- the official form is !DEC$ATTRIBUTES. Further, a much more readable way to pass a structure to C is to put the TYPEd argument in the interface and pass just kurt instead of kurt%n (the first member). It took me some time to realize your intent :-).

Jugoslav
0 Kudos
Reply