Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

FORTRAN dynamic arrays used as parameters of functions called from C++

73 views
Skip to first unread message

Matthew Della

unread,
Dec 31, 2008, 12:06:05 PM12/31/08
to
Hello,

I am attempting to call some FORTRAN functions that are included in
some legacy code necessary to complete this project. Before anyone
asks, it is not possible to rewrite the code from FORTRAN to C++.

The issue is how FORTRAN handles dynamic arrays. By dynamic array, I
mean an array where the size of the array is not decided until run
time. I basically want to create such an array in c++ as a member of
a struct to be sent as a parameter to FORTRAN. When i send the struct
from C++ to FORTRAN, the size of the item being sent/received is
different. This is because of FORTRAN's use of what seems to be
called an array descriptor for dynamic arrays. Below is an Example of
the issue:

MODULE mExample

type tX
Real (Kind=4), dimension(:), pointer :: x => NULL()
Integer (Kind=4) :: nx = 0
end type

type tY
type (tx),dimension(:),pointer :: y => NULL()
Integer (Kind=4) :: ny = 0
end type

CONTAINS

!CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
!
! A function to delete a set of offsets
!
!CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
SUBROUTINE SetNY (tempY, numX)

! Implicit none

IMPLICIT NONE

type (tY), Intent (IN OUT) :: tempY
Integer (KIND=4), Intent (IN), optional :: numX

tempY%ny = tempY%ny + 3
PRINT *, 'FORTRAN: setny: tempY%ny = ', tempY%ny ! This is line
31 in Example.f90
tempY%ny = numX

RETURN
END SUBROUTINE

END MODULE

example.cpp:

#include <iostream>
#include <stdio.h>

using namespace std;

struct tX
{
float * x;
int nx;

tX()
:
x(0),
nx(101)
{
// purposefully left empty
}
};

struct tY
{
tX * y;
int ny;

tY()
:
y(),
ny(199634)
{
// purposefully left empty
}
};

extern "C" {

void __mexample__setny
(
tY * y,
int * numX
);
}

int main()
{
tY yObj;
int numX = 54;
//yObj.y->nx = 65;

cout << "C++: Before setny: yObj.ny = " << yObj.ny << endl;
__mexample__setny(&yObj, &numX);
cout << "C++: After setny: yObj.ny = " << yObj.ny << endl;

return 0;

}

Using gdb, and printing tempY as soon as it is received in FORTRAN, we
have:

[user@sentinel2 fortran]$ gdb Ex
GNU gdb Red Hat Linux (6.5-25.el5rh)
Copyright (C) 2006 Free Software Foundation, Inc.
GDB is free software, covered by the GNU General Public License, and
you are
welcome to change it and/or distribute copies of it under certain
conditions.
Type "show copying" to see the conditions.
There is absolutely no warranty for GDB. Type "show warranty" for
details.
This GDB was configured as "x86_64-redhat-linux-gnu"...Using host
libthread_db library "/lib64/libthread_db.so.1".

(gdb) break Example.f90:31
Breakpoint 1 at 0x400be9: file Example.f90, line 31.
(gdb) run
Starting program: /home/u43530/fortran/Ex
C++: Before setny: yObj.y.nx = 65, yObj.ny = 101

Breakpoint 1, __mexample__setny (tempy=@0x7fff14fc45f0,
numx=0x7fff14fc45ec) at Example.f90:31
31 PRINT *, 'FORTRAN: setny: tempY%ny = ', tempY%ny, ',
tempY%y%nx = ', tempY%y%nx
Current language: auto; currently fortran
(gdb) print tempY
$1 = (REF TO -> ( Type ty
Type tx
Type array_descriptor1
PTR TO -> ( VOID ) :: data
int8 :: offset
int8 :: dtype
Type descriptor_dimension
int8 :: stride
int8 :: lbound
int8 :: ubound
End Type descriptor_dimension (0:0) :: dim
End Type array_descriptor1 :: x
int4 :: nx
End Type tx :: y
int4 :: ny
End Type ty )) @0x7fff14fc45f0: { { { 0x0, 249108103233, 101, ({ 0,
250286808000, 0})}, 0}, 1180817572}

In case it matters, I am using gfortran as the FORTRAN compiler and g+
+ for C++. I am operating in redhat enterprise linux version 5.
Also, the current version of gcc installed on the computer is 4.1.2.
However, we are not using this version for compilation of this
program.

The necessary packages were downloaded and extracted into /home/user2/
gccbuild4.3.2/. Then I created gcc-build in /home/user2 and cded to
it. Then used the following commands:

../gccbuild4.3.2/gcc-4.3.2/configure --prefix=/home/user2/gcc-trunk --
enable-languages=c,c++,fortran
make
make install


When compiling with gfortran, the following flags are used: -g -
frepack-arrays -c -Wa,-64

When compiling with g++, only the -g flag is used.

We are attempting to incorporate the FORTRAN basically as is with
little or no modification to a project in C++. This is why we are
attempting to simply call these FORTRAN functions from C++. The
dynamic arrays are defined in the FORTRAN code and we hope to leave
them as they are without modifying the FORTRAN code whatsoever.
Adding additional FORTRAN code is plausible if need be or slightly
modifying the FORTRAN if absolutely need be, but we would like to
minimize the modification of the existing FORTRAN.

Consequently, I can not simply send an empty dynamic array within a
struct from C++ to FORTRAN as well as other parameters and members of
the struct. After modifying values in FORTRAN to the members of the
"struct" or "type" that includes the dynamic array, these changes are
not replicated correctly upon "return" of the function to C++. Could
Someone please let me know if this is an issue with gfortran, or
possibly something else. If this is not an issue, is there an easy
method of doing this, like those found below for non-dynamic arrays.

Basically, I have been able to successfully call numerous functions
originally in FORTRAN from C++, the method of doing this can be found
below. I have been able to successfully pass simple data types such
as floats or integers to FORTRAN functions (which are marked as REAL
(KIND=4) and INTEGER (KIND=4) in FORTRAN). I have also been able to
construct structs of basic types (floats, ints, etc.) in C++ that
correspond to "types" in FORTRAN and send these structs as parameters
to a FORTRAN function where the given parameter is the corresponding
type and things behave as if the parameter was not a struct from c++
but the corresponding type from FORTRAN. Similarly, nested types
where one FORTRAN type is inside another can be successfully sent by
sending corresponding nested structs. I have also been able too send
arrays from C++ to FORTRAN perfectly fine.

Below is an example of two FORTRAN types and their corresponding C++
structs:

FORTRAN:
type A
Real (Kind=4) :: a = 0.0
Real (Kind=4) :: b = 0.0
Real (Kind=4) :: c = 0.0
LOGICAL (Kind=4) :: d = .FALSE.
end type

type B
type (A) :: e
INTEGER (Kind=4) :: f = 0
REAL(Kind=4) :: g(73)
REAL(Kind=4) :: h(73)
end type

C++:

struct A
{
float a;
float b;
float c;
long int d;

A()
:
a(0.0),
b(0.0),
c(0.0),
d(0)
{
// purposefully left empty
}

};


struct B
{
A e;
int f;
float g[73];
float h[73];

B()
:
e(),
f(73),
g(),
h()
{
memset(g, 0, 73);
memset(h, 0, 73);
}

};


Calling the Fortran Function in File Example.f90:

SUBROUTINE SetB (z, y, x, v)
IMPLICIT NONE

! Declare local variables.

type (B) z

INTEGER(4) ierr

REAL(4) y, x, v

z%e%a = y
z%e%b = x
z%e%c = v
z%e%d = .FALSE.
z%f = 3
z%g(1) = -1000.0
z%g(2) = 0.0
z%g(3) = 1000.0
z%h(1) = 0.0
z%h(2) = 0.0
z%h(3) = 0.0


Can be called from C++ (after using extern "C" to declare the FORTRAN
function as extrnal) as follows:

extern "C" {

void __mexample__setb
(
B * z,
float * y,
float * x,
float * v,
);

}

**code snippet** (now in main or some other C++ function):

B z;
float y = 3.0, x = 4.0, v = 5.0;
__mexample__setb(&z, &y, &x, &v);


Richard Maine

unread,
Dec 31, 2008, 12:42:27 PM12/31/08
to
Matthew Della <matthew...@gmail.com> wrote:

> I am attempting to call some FORTRAN functions that are included in
> some legacy code necessary to complete this project. Before anyone
> asks, it is not possible to rewrite the code from FORTRAN to C++.
>
> The issue is how FORTRAN handles dynamic arrays. By dynamic array, I
> mean an array where the size of the array is not decided until run
> time. I basically want to create such an array in c++ as a member of
> a struct to be sent as a parameter to FORTRAN. When i send the struct
> from C++ to FORTRAN, the size of the item being sent/received is
> different. This is because of FORTRAN's use of what seems to be
> called an array descriptor for dynamic arrays.

This is, unfortunately for your purposes, an implementation detail that
is not covered by the Fortran standard. The use of an array descriptor
of some kind is quite common (perhaps even universal), but it is really
part of a particular Fortran compiler rather than part of the language.
And while I think pretty much all compilers use such a descriptor for a
structure component that is an array pointer, the exact layout of the
descriptor is not so universal. I'm afraid I don't know the layout that
gFortran uses, so I'm not prepared to analyze your particular code.

Even the C interop features of f2003 don't directly cover this case.
There was a proposal to add some specifications that I think are related
to this (I confess to not having studied them in detail) in f2008, but I
think that proposal was pulled from f2008 draft; it might still be in a
separate TR. Even if you did that, it would require modifications to the
Fortran code.

I'd probably recommend that you use the f2003 interop features to do
something close to this. Make the structure component be a C_PTR and use
the C_LOC and C_F_POINTER (spelling?) procedures to convert between it
and a Fortran pointer. If you don't want to touch the "legacy" (I'm
minorly amused by the application of that term to code that uses
features new to f95) Fortran code, you could make a wrapper routine,
which uses the f2003 features and sits between the C++ code and the
legacy Fortran code. That's probably what I'd do.

--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain

Matthew Della

unread,
Dec 31, 2008, 2:14:02 PM12/31/08
to
On Dec 31, 12:42 pm, nos...@see.signature (Richard Maine) wrote:

This is something I had not seen before and appears that it may be
useful to do this. The issue I am seeing after a small amount of
research is with the fact that the FORTRAN Functions to be called from
C++ are also potentially called from other FORTRAN functions. It
appears as though making the structure component be a C_PTR will have
ill effects when such a FORTRAN function is being called by another
FORTRAN function. Is this true or am I misinterpreting the use of
C_PTR, C_LOC and C_F_POINTER? Also, if this is not an issue, might it
be possible to convert them using the Example.f90 file at the top
presenting the problem so that the correct manner of doing this can be
visualized?

Thank You for your timely and informative response.

Richard Maine

unread,
Dec 31, 2008, 2:46:07 PM12/31/08
to
Matthew Della <matthew...@gmail.com> wrote:

> On Dec 31, 12:42 pm, nos...@see.signature (Richard Maine) wrote:

> > I'd probably recommend that you use the f2003 interop features to do
> > something close to this. Make the structure component be a C_PTR and use
> > the C_LOC and C_F_POINTER (spelling?) procedures to convert between it
> > and a Fortran pointer. If you don't want to touch the "legacy" (I'm
> > minorly amused by the application of that term to code that uses
> > features new to f95) Fortran code, you could make a wrapper routine,
> > which uses the f2003 features and sits between the C++ code and the
> > legacy Fortran code. That's probably what I'd do.

...


> This is something I had not seen before and appears that it may be
> useful to do this. The issue I am seeing after a small amount of
> research is with the fact that the FORTRAN Functions to be called from
> C++ are also potentially called from other FORTRAN functions. It
> appears as though making the structure component be a C_PTR will have
> ill effects when such a FORTRAN function is being called by another
> FORTRAN function. Is this true or am I misinterpreting the use of
> C_PTR, C_LOC and C_F_POINTER? Also, if this is not an issue, might it
> be possible to convert them using the Example.f90 file at the top
> presenting the problem so that the correct manner of doing this can be
> visualized?

Well, the Fortran calling routines would have to be correspondingly
modified, so yes, I could see that as an extra nuisance. To me, that
argues for the wrapper approach, having the existing Fortran code call
the existing Fortran routine unmodified, and having the C++ code call
the wrapper. That should achieve your objective of not touching any of
the existing code.

I'll let someone else show an illustrative example. While its a
reasonable request to see one, I'm about ready to get up and go eat
instead of sitting here much longer. If I tried to throw something out
off the top of my head, I'd probably screw it up. Well..., ok, just a
quick outline, without details (and without checking the syntax either)

subroutine wrapper(x_c)
use iso_c_binding

type, bind(c) :: tx_c
type(c_ptr) :: x_cptr
integer :: nx
...
end type
type tx_f
real, pointer :: x_fptr(:) => null()
...
end type

type(tx_c) :: x_c
type(tx_f) :: x_f

call c_f_pointer(x_c%x_cptr, x_f%x_fptr, [x_c%nx])
!--- Copy in any other components as needed.

call some_fortran_routine(x_f)

x_c%x_cptr = c_loc(x_f%x_fptr)
!-- Copy out any other components as needed.
return
end

I've shown both copy in and copy out parts. You might not need them both
for every case.

Oh, as an unrelated aside, be aware that your use of kind=4 for integers
and reals is nonportable. The standard does not specify particular kind
values. On the whole, it is probably more portable to just omit the
kind=4 specifier; there are probably more compilers for which omitting
it will give you what you want than there are compilers for which kind=4
will do so. There are several portable ways to get kind values,
including the selected_*_kind intrinsics and, for the C interop, the
kind parameters in iso_c_binding. In any case, even if you just specify
the value 4, I recommend at least putting that specification in a named
constant (aka Fortran parameter) andthen using that constant; that way,
you only need to change it in one place should the need arise.

none

unread,
Jan 2, 2009, 8:05:21 AM1/2/09
to
On Wed, 31 Dec 2008 09:06:05 -0800, Matthew Della wrote:

> Hello,
>
> I am attempting to call some FORTRAN functions that are included in
> some legacy code necessary to complete this project. Before anyone
> asks, it is not possible to rewrite the code from FORTRAN to C++.
>
> The issue is how FORTRAN handles dynamic arrays. By dynamic array, I
> mean an array where the size of the array is not decided until run
> time. I basically want to create such an array in c++ as a member of
> a struct to be sent as a parameter to FORTRAN. When i send the struct
> from C++ to FORTRAN, the size of the item being sent/received is
> different. This is because of FORTRAN's use of what seems to be
> called an array descriptor for dynamic arrays. Below is an Example of
> the issue:
>
> MODULE mExample
>
> type tX
> Real (Kind=4), dimension(:), pointer :: x => NULL()
> Integer (Kind=4) :: nx = 0
> end type
>
> type tY
> type (tx),dimension(:),pointer :: y => NULL()
> Integer (Kind=4) :: ny = 0
> end type
>
> CONTAINS
>

An alternative might be the clumsier, older, style of

MODULE mExample
real (kind = 4), dimension(:), allocatable, target:: x

type tX ...

and later

allocate(x(1:nx))
tX%x = x

Then for the C++ side you call with two parameters, the array and the size
of the array. There is no reason that the C++ side cannot also have a
structure that then points to the passed array.

Jugoslav Dujic

unread,
Jan 5, 2009, 7:43:39 AM1/5/09
to

Matthew Della wrote:
> Hello,
>
> I am attempting to call some FORTRAN functions that are included in
> some legacy code necessary to complete this project. Before anyone
> asks, it is not possible to rewrite the code from FORTRAN to C++.
>
> The issue is how FORTRAN handles dynamic arrays. By dynamic array, I
> mean an array where the size of the array is not decided until run
> time. I basically want to create such an array in c++ as a member of
> a struct to be sent as a parameter to FORTRAN. When i send the struct
> from C++ to FORTRAN, the size of the item being sent/received is
> different. This is because of FORTRAN's use of what seems to be
> called an array descriptor for dynamic arrays. Below is an Example of
> the issue:
>
<snip>

>
> We are attempting to incorporate the FORTRAN basically as is with
> little or no modification to a project in C++. This is why we are
> attempting to simply call these FORTRAN functions from C++. The
> dynamic arrays are defined in the FORTRAN code and we hope to leave
> them as they are without modifying the FORTRAN code whatsoever.
> Adding additional FORTRAN code is plausible if need be or slightly
> modifying the FORTRAN if absolutely need be, but we would like to
> minimize the modification of the existing FORTRAN.
>
> Consequently, I can not simply send an empty dynamic array within a
> struct from C++ to FORTRAN as well as other parameters and members of
> the struct. After modifying values in FORTRAN to the members of the
> "struct" or "type" that includes the dynamic array, these changes are
> not replicated correctly upon "return" of the function to C++. Could
> Someone please let me know if this is an issue with gfortran, or
> possibly something else. If this is not an issue, is there an easy
> method of doing this, like those found below for non-dynamic arrays.

Matthew,
I wrote a C++ template class (actually, two -- VFArray and VFMatrix)
which emulate most of F90 semantics -- and are interoperable with --
Fortran 1-d and 2-d arrays. However, that implementation is for Intel
and Compaq Fortran array descriptors, so you will have to tweak the
code.

One description of gfortran array desciptors can be found here:

http://objectmix.com/fortran/381992-call-array-valued-fortran-function-c.html#post1417358

I don't know whether they assembled the official documentation in the
meantime. Note that gfortran descriptor is very similar to Compaq one
(class VFArray), so you won't have to work too much to adjust the code.
Unfortunately, the comments are sparse (on my too long TODO-list), but I
hope it's self-documenting enough.

I'll try to attach the code (VFArray.h -- the template classes,
VFArray.cpp -- test case in C++, Foo90.f90 -- Fortran routines of
the test case) in the followup. If it doesn't come through (my
newsserver or newsreader tend to think the files are binary), I'll
send it by e-mail.

--
Jugoslav
www.xeffort.com
Please reply to the newsgroup.
You can find my real e-mail on my home page above.

Craig Powers

unread,
Jan 6, 2009, 3:06:24 PM1/6/09
to
Jugoslav Dujic wrote:
>
> Matthew,
> I wrote a C++ template class (actually, two -- VFArray and VFMatrix)
> which emulate most of F90 semantics -- and are interoperable with --
> Fortran 1-d and 2-d arrays. However, that implementation is for Intel
> and Compaq Fortran array descriptors, so you will have to tweak the
> code.
>
> One description of gfortran array desciptors can be found here:
>
> http://objectmix.com/fortran/381992-call-array-valued-fortran-function-c.html#post1417358
>
>
> I don't know whether they assembled the official documentation in the
> meantime. Note that gfortran descriptor is very similar to Compaq one
> (class VFArray), so you won't have to work too much to adjust the code.
> Unfortunately, the comments are sparse (on my too long TODO-list), but I
> hope it's self-documenting enough.

Be aware that there are plans to change the gfortran descriptor for the
next version (4.5).

Matthew

unread,
Jan 7, 2009, 11:16:16 AM1/7/09
to


Richard,
I have spent the last few days amongst other things working on this
suggestion. Currently it appears as though c_loc is not doing
anything. Below is my sample code both FORTRAN and C++, as well as
the gdb output:


FORTRAN:

MODULE mExample

type tY
!type (tx),dimension(:),pointer :: y => NULL()
!type (tx) :: y
REAL (KIND=4), dimension(:),pointer :: y_fptr => NULL()


Integer (Kind=4) :: ny = 0
end type

CONTAINS

!
CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
SUBROUTINE wrapper(y_c)
USE iso_c_binding
type, bind(c) :: ty_c
type(c_ptr) :: y_cptr
Integer ny
end type

type(ty_c) :: y_c
type(tY), target :: y_f
PRINT *, 'FORTRAN: wrapper: y_c%ny = ', y_c%ny!
call c_f_pointer(y_c%y_cptr, y_f%y_fptr, [y_c%ny])
PRINT *, 'FORTRAN: wrapper: y_c%ny = ', y_c%ny!
PRINT *, 'FORTRAN: wrapper: y_f%ny = ', y_f%ny!
call SetNY(y_f, y_c%ny + 6)

y_c%y_cptr = c_loc(y_f%y_fptr(1))

RETURN
END SUBROUTINE

!CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
SUBROUTINE SetNY (tempY, numY)

! Implicit none

IMPLICIT NONE

type (tY), Intent (IN OUT) :: tempY

Integer (KIND=4), Intent (IN), optional :: numY

tempY%ny = tempY%ny


PRINT *, 'FORTRAN: setny: tempY%ny = ', tempY%ny!

tempY%ny = numY

RETURN
END SUBROUTINE

END MODULE


_______________________________________________________________
C++:


#include <iostream>
#include <stdio.h>

using namespace std;

struct tY
{
float * y;
int ny;

tY()
:
y(),
ny(199634)
{
// purposefully left empty
}
};

extern "C" {

void __mexample_MOD_wrapper
(
tY * y,
int * numY
);
}

int main()
{
tY yObj;
int numY = 54;

cout << "C++: Before setny: yObj.ny = " << yObj.ny << endl;

__mexample_MOD_wrapper(&yObj, &numY);


cout << "C++: After setny: yObj.ny = " << yObj.ny << endl;

return 0;

}


____________________________________________________________________
gdb (version 4.3.2):


[user2@compName fortran]$ gdb a.out


GNU gdb Red Hat Linux (6.5-25.el5rh)
Copyright (C) 2006 Free Software Foundation, Inc.
GDB is free software, covered by the GNU General Public License, and
you are
welcome to change it and/or distribute copies of it under certain
conditions.
Type "show copying" to see the conditions.
There is absolutely no warranty for GDB. Type "show warranty" for
details.
This GDB was configured as "x86_64-redhat-linux-gnu"...Using host
libthread_db library "/lib64/libthread_db.so.1".

(gdb) break WrapperExample.f90:28
Breakpoint 1 at 0x400d4c: file WrapperExample.f90, line 28.
(gdb) print y_c
No symbol "y_c" in current context.
(gdb) q
[u43530@sentinel2 fortran]$ gdb a.out


GNU gdb Red Hat Linux (6.5-25.el5rh)
Copyright (C) 2006 Free Software Foundation, Inc.
GDB is free software, covered by the GNU General Public License, and
you are
welcome to change it and/or distribute copies of it under certain
conditions.
Type "show copying" to see the conditions.
There is absolutely no warranty for GDB. Type "show warranty" for
details.
This GDB was configured as "x86_64-redhat-linux-gnu"...Using host
libthread_db library "/lib64/libthread_db.so.1".

(gdb) break WrapperExample.f90:28
Breakpoint 1 at 0x400d4c: file WrapperExample.f90, line 28.
(gdb) run
Starting program: /home/u43530/fortran/a.out
C++: Before setny: yObj.ny = 199634
FORTRAN: wrapper: y_c%ny = 199634

Breakpoint 1, wrapper (y_c=@0x7fffa2662c60) at WrapperExample.f90:28
28 call c_f_pointer(y_c%y_cptr, y_f%y_fptr, [y_c%ny])


Current language: auto; currently fortran

(gdb) print y_c
$1 = (REF TO -> ( Type ty_c
PTR TO -> ( VOID ) :: y_cptr
integer(kind=4) :: ny
End Type ty_c )) @0x7fffa2662c60: { 0x0, 199634}
(gdb) print y_c%y_cptr
$2 = (PTR TO -> ( VOID )) 0x0
(gdb) print y_c%ny
$3 = 199634
(gdb) print y_f
$4 = { (), 0}
(gdb) print y_f%y_fptr
$5 = ()
(gdb) print y_f%ny
$6 = 0
(gdb) print &(y_f)
$7 = (PTR TO -> ( Type ty
real*4 (0:-1) :: y_fptr
integer(kind=4) :: ny
End Type ty )) 0x7fffa2662ba0
(gdb) print &(y_f%y_fptr)
$8 = (PTR TO -> ( real*4 (0:-1))) 0x7fffa2662ba0
(gdb) print &(y_f%ny)
$9 = (PTR TO -> ( integer(kind=4) )) 0x7fffa2662bd0
(gdb) n
29 PRINT *, 'FORTRAN: wrapper: y_c%ny = ', y_c%ny!
(gdb) print y_f
$10 = { (), 0}
(gdb) print y_f%y_fptr
$11 = ()
(gdb) print y_f%ny
$12 = 0
(gdb) print &(y_f)
$13 = (PTR TO -> ( Type ty
real*4 (0:-1) :: y_fptr
integer(kind=4) :: ny
End Type ty )) 0x7fffa2662ba0
(gdb) print &(y_f%y_fptr)
$14 = (PTR TO -> ( real*4 (0:-1))) 0x7fffa2662ba0
(gdb) print &(y_f%ny)
$15 = (PTR TO -> ( integer(kind=4) )) 0x7fffa2662bd0
(gdb) q


___________________________________________

If I remove the '(1)' from the line 'y_c%y_cptr = c_loc(y_f%y_fptr
(1))', the compiler experiences a segmentation fault. Either my
understanding from your example and other examples online is wrong, or
this does not work as expected. Could you please take a look at this
and inform me what the issue is?

Richard Maine

unread,
Jan 7, 2009, 11:38:03 AM1/7/09
to
Matthew <matthew...@gmail.com> wrote:

> Currently it appears as though c_loc is not doing

> anything....

"Not doing anything" doesn't makes sense in this context; I'm not sure
what that would mean.

> If I remove the '(1)' from the line 'y_c%y_cptr = c_loc(y_f%y_fptr
> (1))', the compiler experiences a segmentation fault.

When you say "the compiler experiences a segmentation fault" do you
actually mean that or do you mean that the compiled program does so when
run? Those are very different things. If the compiler gets a
segmentation fault, then that is a compiler bug. Always. No matter what
the code is.

> Could you please take a look at this
> and inform me what the issue is?

Sorry, but I'm not really up to that. Maybe someone else here is. While
it looks to be a nice, small, self-contained sample, and thus ought to
be relatively easy to diagnose, I barely speak C++ at all and also
almost never use debuggers, so my eyes pretty much glaze over when
looking at this. I don't have the tools handy to work with it directly
myself and remote debugging is always hard. Sometimes I get lucky
inspirations, but one isn't comming to me at the moment.

Matthew

unread,
Jan 7, 2009, 12:57:54 PM1/7/09
to
On Jan 7, 11:38 am, nos...@see.signature (Richard Maine) wrote:

> Matthew <matthew.t.de...@gmail.com> wrote:
> > Currently it appears as though c_loc is not doing
> > anything....
>
> "Not doing anything" doesn't makes sense in this context; I'm not sure
> what that would mean.

By not doing anything, I mean that the values of y_f are not changing
as expected, nor is the address of y_f or any of the addresses of the
members of y_f, which is not really expected, but as the values don't
change, it would be the next place to look. So nothing related to y_f
is changing as a result of the function call.


> > If I remove the '(1)' from the line 'y_c%y_cptr = c_loc(y_f%y_fptr
> > (1))', the compiler experiences a segmentation fault.
>
> When you say "the compiler experiences a segmentation fault" do you
> actually mean that or do you mean that the compiled program does so when
> run? Those are very different things. If the compiler gets a
> segmentation fault, then that is a compiler bug. Always. No matter what
> the code is.

Yes, I mean the compiler gets a segmentation fault and I know that I
need to submit this as a bug.

Steven Correll

unread,
Jan 8, 2009, 12:30:33 PM1/8/09
to
On Jan 7, 10:57 am, Matthew <matthew.t.de...@gmail.com> wrote:
> By not doing anything, I mean that the values of y_f are not changing
> as expected, nor is the address of y_f or any of the addresses of the
> members of y_f, which is not really expected, but as the values don't
> change, it would be the next place to look.  So nothing related to y_f
> is changing as a result of the function call.
>
> > > If I remove the '(1)' from the line 'y_c%y_cptr = c_loc(y_f%y_fptr
> > > (1))', the compiler experiences a segmentation fault.

The problem in this example is that the Fortran array has never been
allocated. The Fortran 2003 standard defines the behavior of C_LOC on
allocated arrays only, and doesn't require the compiler to report an
error if you apply it to an unallocated array. If you allocate the
array before using C_LOC, then you'll see a change in the C++ pointer
after using C_LOC. (I'm not sure whether you expected the integer
member of the C++ structure to change, but I notice that you're not
copying the changed integer component of the Fortran structure back to
the corresponding C++ member.)

A couple of suggestions:

1. gdb does a poor job of debugging Fortran. It's handy to create a
function "showaddr" in the C++ world which turns a C_PTR into an
integer so you can print the value of a C_PTR for debugging purposes,
e.g. "print '(z16)', showaddr(my_cptr)":

extern "C" {
long long showaddr(void *p) {
return (long long) p;
}
}

2. For portability, it would be preferable to use the "bind(c)"
attribute on "wrapper" so that the C++ world can refer to it as
"wrapper" not "__mexample_MOD_wrapper", since different Fortran
compilers decorate a module procedure name in different ways. When I
do so, the 4.4.0 Mac gfortran unfortunately complains that type ty_c
is not interoperable, which I believe is another bug.

Tobias Burnus

unread,
Jan 12, 2009, 8:16:32 AM1/12/09
to
Steven Correll wrote:
> A couple of suggestions:
>
> 1. gdb does a poor job of debugging Fortran. It's handy to create a
> function "showaddr" in the C++ world which turns a C_PTR into an
> integer so you can print the value of a C_PTR for debugging purposes,

Regarding gdb: I think the Fortran support improves (esp. with regards
to assumed-shape arrays and allocatable arrays).

Otherwise, I think one could also create a showaddr in Fortran using:
transfer(ptr, 0_c_intptr_t)
which should work on most systems.

> 2. For portability, it would be preferable to use the "bind(c)"
> attribute on "wrapper" so that the C++ world can refer to it as
> "wrapper" not "__mexample_MOD_wrapper", since different Fortran
> compilers decorate a module procedure name in different ways. When I
> do so, the 4.4.0 Mac gfortran unfortunately complains that type ty_c
> is not interoperable, which I believe is another bug.

Can you elaborate? I see a warning "may not be C interoperable" (as one
uses INTEGER and not INTEGER(C_INT)) but this is warning and not an error.

(I do see the segmentation fault mentioned in the thread, I filled a bug
report against gfortran [PR 38813] and I think NAG f95 is right by
rejecting it without "(1)" with: "Error: The argument to C_LOC must not
be an array pointer".)

Tobias

Steven Correll

unread,
Jan 13, 2009, 9:51:13 AM1/13/09
to
Steven Correll wrote:
> ...the 4.4.0 Mac gfortran unfortunately complains that type ty_c

> is not interoperable, which I believe is another bug.

On Jan 12, 6:16 am, Tobias Burnus <bur...@net-b.de> wrote:
> Can you elaborate? I see a warning "may not be C interoperable" (as one
> uses INTEGER and not INTEGER(C_INT)) but this is warning and not an error.

~/clf> uname -a
Darwin Macintosh-5.local 9.6.0 Darwin Kernel Version 9.6.0: Mon Nov 24
17:37:00 PST 2008; root:xnu-1228.9.59~1/RELEASE_I386 i386
~/clf> cat simple.f90
MODULE mExample
CONTAINS
SUBROUTINE wrapper(y_c) bind(c)


USE iso_c_binding
type, bind(c) :: ty_c
type(c_ptr) :: y_cptr

Integer(c_int) ny
end type
type(ty_c) :: y_c
END SUBROUTINE
END MODULE
~/clf> gfortran -v
Using built-in specs.
Target: i386-apple-darwin9.4.0
Configured with: ../gcc-4.4-20080801/configure --enable-
languages=fortran
Thread model: posix
gcc version 4.4.0 20080801 (experimental) (GCC)
~/clf> gfortran -c simple.f90
simple.f90:3.28:

SUBROUTINE wrapper(y_c) bind(c)
1
Error: Type 'y_c' at (1) is a parameter to the BIND(C) procedure
'wrapper' but is not C interoperable because derived type 'ty_c' is
not C interoperable

0 new messages