Previous Next Contents Index Doc Set Home


Fortran 77 Interface

8



Introduction

This chapter describes the Fortran 77 interface with C++. We suggest you follow these steps:

1. Study Code Example 8-1 and "Sample Interface" on page 122.

2. Read "Fortran Calls C++" on page 129 or "C++ Calls Fortran" on page 153.

3. Within either of the two sections mentioned in step 2, choose one of these subsections:

4. Within any of the subsections mentioned in step 3, choose one of these examples:

For the arguments, there is an example for each of these:

For the function return values, there is an example for each of these:


Sample Interface

In Code Example 8-1, a Fortran main calls a C++ function. Both i and f are references.

Code  Example  8-1     Sample C++--Fortran Interface
Samp.cc
extern "C" void Samp ( int &i, float& f ) {
    i = 9;
	f = 9.9;
}
Sampmain.f
      integer i
      real r
      external Samp !$pragma C ( Samp )
      call Samp ( i, r )
      write( *, "(I2, F4.1)" ) i, r
      end

Here, both i and r are passed by reference to the default. The following command lines compile and execute Samp.cc, with output:

% CC -c Samp.cc 
% f77 -c -silent Sampmain.f
% f77 Samp.o Sampmain.o -Bstatic -lC -Bdynamic
% a.out 
 9 9.9 


Compatibility Issues

Most C++ and Fortran interfaces must be correct in the following:

Some C++ and Fortran interfaces must also be correct on these constructs:

Function versus Subroutine

The word function means different things in C++ and Fortran.

Fortran Calls C++

If the C++ function returns a value, call it from Fortran as a function. If it does not return a value, call it as a subroutine.

C++ Calls Fortran

Call a Fortran function from C++ as a function. Call a Fortran subroutine from C++ as a function that returns a value of int (comparable to Fortran INTEGER*4) or void. This return value is useful if the Fortran routine does a nonstandard return.

Data Type Compatibility

Table 8-1 shows the default data type sizes and alignments (that is, without -f, -i2, -misalign, -r4, or -r8).


Note - In the following table, REAL*16 and COMPLEX*32 can be passed between Fortran and C++, but not between Fortran and C++ versions prior to C++ 4.0.


Table  8-1 Argument Sizes and Alignments, Passed by Reference 


Fortran Type


C++ Type

Size (bytes)
Alignment (bytes)

byte x

char x

1

1

character x

char x

1

1

character*n x

char x[n]

n

1

complex x

struct {float r,i;} x;

8

4

complex*8 x

struct {float r,i;} x;

8

4

double complex x

struct {double dr,di;}x;

16

4

complex*16 x

struct {double dr,di;}x;

16

4

double precision x

double x

8

4

real x

float x

4

4

real*4 x

float x

4

4

real*8 x

double x

8

4

integer x

int x

4

4

integer*2 x

short x

2

2

integer*4 x

int x

4

4

logical x

int x

4

4

logical*4 x

int x

4

4

logical*2 x

short x

2

2

logical*1 x

char x

1

1

Note that:

Arguments Passed by Reference or Value

In general, Fortran passes arguments by reference. In a call, if you enclose an argument with the nonstandard function %VAL(), Fortran passes it by value.

In C++, the function declaration tells whether an argument is passed by value or by reference.

Uppercase and Lowercase

C++ is case-sensitive; uppercase and lowercase have different meanings. The Fortran default is to ignore case by converting subprogram names to lower-case, except within character-string constants.

There are two common solutions to the uppercase and lowercase problem:

Use one of these solutions, but not both.

Most examples in this chapter use lowercase letters for the name in the C++ function; they do not use the Fortran -U compiler option.

Underscore in Names of Routines

The Fortran compiler normally appends an underscore (_) to the names of subprograms, for both a subprogram and a call to a subprogram. The underscore distinguishes it from C++ procedures or external variables with the same user-assigned name. If the name has exactly 32 characters, the underscore is not appended. All Fortran library procedure names have double leading underscores to reduce clashes with user-assigned subroutine names.

There are two common solutions to the underscore problem:

Use one of these solutions, but not both.

Most of the examples in this chapter use the Fortran C() compiler pragma and do not use the underscores.

The C() pragma directive takes the names of external functions as arguments. It specifies that these functions are written in the C or C++ language, so the Fortran compiler does not append an underscore to such names, as it ordinarily does with external names. The C() directive for a particular function must appear before the first reference to that function. It must also appear in each subprogram that contains such a reference. The conventional usage is:

	EXTERNAL ABC, XYZ	!$PRAGMA C( ABC, XYZ ) 

If you use this pragma, then in the C++ function do not append an underscore to external names.


C++ Name Encoding

To implement function overloading and type-safe linkage, the C++ compiler normally appends type information to the names of functions. To prevent the C++ compiler from appending type information to the names of functions, and to allow Fortran to call functions, declare C++ functions with the extern "C" language construct. One common way to do this is in the declaration of a function:

extern "C" void abc ( int, float );
...
void abc ( int x, float y ) { /* ... body of abc ... */ }

For brevity, you can also combine extern "C" with the function definition, as in:

extern "C" void abc ( int x, float y )
{
        /* ... body of abc ... */
}  

Most of the C++ examples in this chapter use this combined form. You cannot use the extern "C" language construct for member functions.

Array Indexing and Order

C++ arrays always start at zero, but by default, Fortran arrays start at 1. There are two common ways of approaching this.

This way, the Fortran element B(1) is equivalent to the C element b[1].

Fortran arrays are stored in column-major order, C++ arrays in row-major order. For one-dimensional arrays, this is no problem. For two-dimensional arrays, this is only a minor problem, as long as the array is square. Sometimes it is enough to just switch subscripts.

For two-dimensional arrays that are not square, it is not enough to just switch subscripts. Try passing the whole array to the other language and do all the matrix manipulation there.

File Descriptors and stdio

Fortran I/O channels are in terms of unit numbers. The I/O system does not deal with unit numbers, but with file descriptors. The Fortran runtime system translates from one to the other, so most Fortran programs don't have to know about file descriptors. Many C++ programs use a set of subroutines called standard I/O (or stdio). Many functions of Fortran I/O use standard I/O, which in turn uses operating system I/O calls.

Table 6-2 describes some of the characteristics of these I/O systems:

Table  8-2 Characteristics of Three I/O Systems 


Fortran Units
Standard I/O File Pointers
File Descriptors

Files Open

Opened for reading and writing

Opened for reading, or opened for writing, or opened for both, or
opened for appending
see OPEN(3S)

Opened for reading, or opened for writing, or opened for both

Attributes

Formatted or
unformatted

Always unformatted, but can be read or written with format-interpreting routines

Always unformatted

Access

Direct or sequential

Direct access if the physical file representation is direct access, but can always be read sequentially

Direct access if the
physical file representation is direct access, but can always be read sequentially

Structure

Record

Character stream

Character stream

Form

Arbitrary,
nonnegative
integers

Pointers to structures
in the user's address space

Integers from 0-63

File Permissions

C++ programmers traditionally open input files for reading and output files for writing, sometimes for both. In Fortran, the system cannot foresee what use you will make of the file since there's no parameter to the OPEN statement that gives that information.

Fortran tries to OPEN a file with the maximum permissions possible--first for both reading and writing, then for each separately.

This process takes place transparently and should be of concern only if you try to perform a READ, WRITE, or ENDFILE, when you do not have permission to do so. Magnetic tape operations are an exception to this general freedom, since you could have write permissions on a file but not a write ring on the tape.


Fortran Calls C++

This section describes the interface when Fortran calls C++.

Arguments Passed by Reference

There are two types of arguments: simple types and complex types.

Simple Types

For simple types, define each C++ argument as a reference.

Code  Example  8-2     Passing Arguments by Reference--C++ Program
SimRef.cc
extern "C" void simref (
    char& t,
    char& f,
    char& c,
    int& i,
    float& r,
    double& d,
    short& si )
{
    t = 1;
    f = 0;
    c = 'z';
    i = 9;
    r = 9.9;
    d = 9.9;
    si = 9;
}

Default: Pass each Fortran argument by reference.

Code  Example  8-3     Passing Arguments by Reference--Fortran Program
SimRefmain.f
      logical*1 t, f
      character c
      integer*4 i
      real r
      double precision d
      integer*2 si
      external SimRef !$pragma C( SimRef )
      call SimRef ( t, f, c, i, r, d, si )
      write( *, "(L2,L2,A2,I2,F4.1,F4.1,I2)" )
&	t,f,c,i,r,d,si
      end

Compile and execute, with output, as follows:

% CC -c SimRef.cc
% f77 -c -silent SimRefmain.f
% f77 SimRef.o SimRefmain.o -Bstatic -lC -Bdynamic
% a.out
 T F z 9 9.9 9.9 9 

Complex Types

Here, the C++ argument is a pointer to a structure.

Code  Example  8-4     Passing Arguments by Reference--Fortran Calls C++
CmplxRef.cc
struct complex { float r, i; };
struct dcomplex { double r, i; };

extern "C" void cmplxref ( complex& w, dcomplex& z ) {
    w.r = 6;
    w.i = 7;
    z.r = 8;
    z.i = 9;
}
CmplxRefmain.f
      complex w
      double complex z
      external CmplxRef !$pragma C ( CmplxRef )
      call CmplxRef( w, z )
      write(*,*) w
      write(*,*) z
      end

Compile and execute, with output.

% CC -c CmplxRef.cc
% f77 -c -silent CmplxRefmain.f
% f77 CmplxRef.o CmplxRefmain.o -Bstatic -lC -Bdynamic
% a.out 
  ( 6.00000, 			7.00000) 
  ( 8.0000000000000, 				9.0000000000000) 

A C++ reference to a float matches a REAL passed by reference.

Character Strings Passed by Reference

Passing strings between C++ and Fortran is not recommended.

For every Fortran argument of character type, Fortran associates an extra argument, giving the length of the string. The string lengths are equivalent to C++ long int quantities passed by value. In standard C++ use, all C++ strings are passed by reference. The order of arguments is:

The whole list of string lengths comes after the whole list of other arguments.

The Fortran call in:

    CHARACTER*7 S 
    INTEGER B(3) 
(arguments)
    CALL SAM( B(2), S ) 

is equivalent to the C++ call in:

    char s[7]; 
    long int b[3]; 
(arguments)
    sam_( &b[1], s, 7L );

Ignoring the Extra Arguments
You can ignore these extra arguments, since they are after the list of other arguments.

Code  Example  8-5     Passing Strings by Reference--Ignoring the Extra Arguments  
StrRef.cc
#include <string.h>

extern "C" void strref ( char (&one)[], char (&two)[] ) {
    static char letters[27] = "abcdefghijklmnopqrstuvwxyz";

    strncpy( one, letters, 10 );
    strncpy( two, letters, 26 );
}
StrRefmain.f

      character s10*10, s26*26
      external StrRef !$pragma C( StrRef )
      Call StrRef( s10, s26 )
      write( *, 1 ) s10, s26
 1    format( "s10='", A, "'", / "s26='", A, "'" )
      end

Compile and execute, with output:

% CC -c StrRef.cc 
% f77 -c -silent StrRefmain.f
% f77 StrRef.o StrRefmain.o -Bstatic -lC -Bdynamic
% a.out 
s10='abcdefghij' 
s26='abcdefghijklmnopqrstuvwxyz'

Using the Extra Arguments
You can use the extra arguments. In the following example, the C++ function uses the lengths to match the actual arguments:



Code  Example  8-6     Passing Strings by Reference--Using the Extra Arguments
StrRef2.cc
#include <string.h>
#include <stdio.h>

extern "C" void strref ( char (&one)[], char (&two)[], 
int one_len, int two_len ) {
    static char letters[27] = "abcdefghijklmnopqrstuvwxyz";
    printf( "%d %d\n", L10, L26 );
    strncpy( one, letters, one_len );
    strncpy( two, letters, two_len );
}

Compile and execute, with output:

% CC -c StrRef2.cc 
% f77 -c -silent StrRefmain.f
% f77 StrRef2.o StrRefmain.o -Bstatic -lC -Bdynamic
% a.out 
10 26 
s10='abcdefghij' 
s26='abcdefghijklmnopqrstuvwxyz'

One-Dimensional Arrays Passed by Reference

Code Example 8-7 shows a C++ array, indexed from 0 through 8:



Code  Example  8-7     Passing Arrays by Reference (C++ code)
FixVec.cc 
extern "C" void fixvec ( int V[9], int& Sum )
{
    Sum= 0;
    for( int i= 0; i < 9; ++i ) {
        Sum += V[i];
    }
}

Code Example 8-8 shows a Fortran array, implicitly indexed from 1 through 9:



Code  Example  8-8     Passing Arrays by Reference (Fortran code)
FixVecmain.f 
      integer i, Sum
      integer a(9) / 1,2,3,4,5,6,7,8,9 /
      external FixVec !$pragma C( FixVec )
      call FixVec( a, Sum )
      write( *, '(9I2, " ->" I3)') (a(i),i=1,9), Sum
      end

Compile and execute, with output:

% CC -c FixVec.cc 
% f77 -c -silent FixVecmain.f
% f77 FixVec.o FixVecmain.o -Bstatic -lC -Bdynamic
% a.out 
 1 2 3 4 5 6 7 8 9 -> 45 

Two-Dimensional Arrays Passed by Reference

In a two-dimensional array, the rows and columns are switched. Such arrays are either incompatible between C++ and Fortran, or awkward to keep straight. Non-square arrays are even more difficult to maintain.

Code Example 8-9 shows a 2 by 2 C++ array, indexed from 0 to 1, and 0 to 1.



Code  Example  8-9     A Two-Dimensional C++ Array
FixMat.cc
extern "C" void fixmat ( int a[2][2] )
{
    a[0][1] = 99;
}

Code Example 8-10 shows a 2 by 2 Fortran array, explicitly indexed from 0 to 1, and 0 to 1.



Code  Example  8-10     A Two-Dimensional Fortran Array
FixMatmain.f
      integer c, m(0:1,0:1) / 00, 10, 01, 11 /, r
      external FixMat !$pragma C( FixMat )
      do r= 0, 1
         do c= 0, 1
            write( *, '("m(",I1,",",I1,")=",I2.2)')  r, c, m(r,c)
         end do
      end do

      call FixMat( m )
      write( *, * )

      do r= 0, 1
         do c= 0, 1
            write( *, '("m(",I1,",",I1,")=",I2.2)')  r, c, m(r,c)
         end do
      end do

      end

Compile and execute. Show m before and after the C call.


% CC -c FixMat.cc 
% f77 -c -silent FixMatmain.f
% f77 FixMat.o FixMatmain.o -Bstatic -lC -Bdynamic
% a.out 
m(0,0) = 00 
m(0,1) = 01 
m(1,0) = 10 
m(1,1) = 11 

m(0,0) = 00 
m(0,1) = 01 
m(1,0) = 99 
m(1,1) = 11 

Compare a[0][1] with m(1,0): C++ changes a[0][1], which is Fortran m(1,0).

Structured Records Passed by Reference

Code Example 8-11 and Code Example 8-12 show how to pass a structure to Fortran:



Code  Example  8-11     Passing Structures to Fortran (C++ Code)
StruRef.cc
struct VarLenStr {
    int nbytes ;
    char a[26];
};

#include <stdlib.h>
#include <string.h>
extern "C" void struchr ( VarLenStr& v )
{
    memcpy(v.a, "oyvay", 5);
    v.nbytes= 5;
}



Code  Example  8-12     Passing Structures to Fortran (Fortran Code)
StruRefmain.f
      structure /VarLenStr/
          integer nbytes
          character a*25
      end structure
      record /VarLenStr/ vls
      character s25*25

      external StruChr !$pragma C(StruChr)

      vls.nbytes= 0
      call StruChr( vls )
      s25(1:5) = vls.a(1:vls.nbytes)
      write(*, 1 ) vls.nbytes, s25
 1    format( "size =", I2, ", s25='", A, "'" )
      end

Compile and execute, with output:

% CC -c StruRef.cc 
% f77 -c -silent StruRefmain.f
% f77 StruRef.o StruRefmain.o -Bstatic -lC -Bdynamic
% a.out 
size = 5, s25='oyvay' 

Pointers Passed by Reference

C++ gets a reference to a pointer, as follows:



Code  Example  8-13     Passing Pointers by Reference (C++ Code)
PassPtr.cc
extern "C" void passptr ( int* & i, double* & d )
{
    *i = 9;
    *d = 9.9;
}

Code Example 8-14 shows how Fortran passes the pointer by reference:



Code  Example  8-14     Passing Pointers by Reference (Fortran code)
PassPtrmain.f
      program PassPtrmain
      integer i
      double precision d
      pointer (iPtr, i), (dPtr, d)
      external PassPtr !$pragma C ( PassPtr )
      iPtr = malloc( 4 )
      dPtr = malloc( 8 )
      i = 0
      d = 0.0
      call PassPtr( iPtr, dPtr )
      write( *, "(i2, f4.1)" ) i, d
      end

Compile and execute, with output:

% CC -c PassPtr.cc 
% f77 -c -silent PassPtrmain.f
% f77 PassPtr.o PassPtrmain.o -Bstatic -lC -Bdynamic
% a.out 
 9 9.9 

Arguments Passed by Value

In the call, enclose an argument in the nonstandard function %VAL().

Simple Types Passed by Value

Code Example 8-15 and Code Example 8-16 show how to pass simple types by value.



Code  Example  8-15     Passing Simple Types by Value (C++ Code)
SimVal.cc
extern "C" void simval (
    char   t,
    char   f,
    char   c,
    int    i,
    double d,
    short  s,
    int&   reply )
{
    reply= 0;
    // If nth arg ok, set nth octal digit to one
    if( t        ) reply +=      01;
    if( ! f      ) reply +=     010;
    if( c == 'z' ) reply +=    0100;
    if( i == 9   ) reply +=   01000;
    if( d == 9.9 ) reply +=  010000;
    if( s == 9   ) reply += 0100000;
}



Code  Example  8-16     Passing Simple Types by Value (Fortran Code)
SimValmain.f
      logical*1 t, f
      character c
      integer*4 i
      double precision d
      integer*2 s
      integer*4 args

      data t/.true./, f/.false./, c/'z'/
&    i/9/, d/9.9/, s/9/

      external SimVal !$pragma C( SimVal )
      call SimVal ( %VAL(t), %VAL(f), %VAL(c),
&        %VAL(i), %VAL(d), %VAL(s), args )
      write( *, 1 ) args
 1    format( 'args=', o6, ' (If nth digit=1, arg n OK)' )
      end

Pass each Fortran argument by value, except for args. The same rule applies to CHARACTER*1, COMPLEX, DOUBLE COMPLEX, INTEGER, LOGICAL, DOUBLE PRECISION, structures, and pointers.

Compile and execute, with output:

% CC -c SimVal.cc 
% f77 -c -silent SimValmain.f
% f77 SimVal.o SimValmain.o -Bstatic -lC -Bdynamic
% a.out 
args=111111(If nth digit=1, arg n OK) 

Real Variables Passed by Value

Real variables are passed by value the same way other simple types are. Code Example 8-17 shows how to pass a real variable:



Code  Example  8-17     Passing a Real Variable
  FloatVal.cc
#include <math.h>

extern "C" void floatval ( float f, double& d ) {
    float x=f;
    d = double(x) + 1.0 ;
}
  FloatValmain.f
      double precision d
      real r / 8.0 /
      external FloatVal !$pragma C( FloatVal )
      call FloatVal( %VAL(r), d )
      write( *, * ) r, d
      end

Compile and execute, with output:

% CC -c FloatVal.cc 
% f77 -c -silent FloatValmain.f
% f77 FloatVal.o FloatValmain.o -Bstatic -lC -Bdynamic
% a.out 
    8.00000 9.0000000000000 

Complex Types Passed by Value

You can pass the complex structure by value, as Code Example 8-18 shows:



Code  Example  8-18     Passing Complex Types
CmplxVal.cc
struct complex { float r, i; };

extern "C" void cmplxval ( complex  w, complex& z ) {
    z.r = w.r * 2.0 ;
    z.i = w.i * 2.0 ;
    w.r = 0.0 ;
    w.i = 0.0 ;
}
CmplxValmain.f
      complex w / (4.0, 4.5 ) /
      complex z
      external CmplxVal !$pragma C( CmplxVal )
      call CmplxVal( %VAL(w), z )
      write ( *, * ) w
      write ( *, * ) z
      end

Compile and execute, with output

% CC -c CmplxVal.cc 
% f77 -c -silent CmplxValmain.f
% f77 CmplVal.o CmplxValmain.o -Bstatic -lC -Bdynamic
% a.out 
  ( 4.00000, 4.50000) 
  ( 8.00000, 9.00000) 

Arrays, Strings, Structures Passed by Value

There is no reliable way to pass arrays, character strings, or structures by value on all architectures. The workaround is to pass them by reference.

Pointers Passed by Value

C++ gets a pointer.



Code  Example  8-19     Passing Pointers by Value (C++ Code)
PassPtrVal.cc
extern "C" void passptrval ( int* i, double* d )
{
    *i = 9;
    *d = 9.9;
}

Fortran passes a pointer by value:



Code  Example  8-20     Passing Pointers by Value (Fortran Code)
PassPtrValmain.f
      program PassPtrValmain
      integer i
      double precision d
      pointer (iPtr, i), (dPtr, d)
      external PassPtrVal !$pragma C ( PassPtrVal )
      iPtr = malloc( 4 )
      dPtr = malloc( 8 )
      i = 0
      d = 0.0
      call PassPtrVal( %VAL(iPtr), %VAL(dPtr) ) ! Nonstandard?
      write( *, "(i2, f4.1)" ) i, d
      end

Compile and execute, with output:

% CC -c PassPtrVal.cc 
% f77 -c -silent PassPtrValmain.f
% f77 PassPtrVal.o PassPtrValmain.o -Bstatic -lC -Bdynamic
% a.out 
 9 9.9 

Function Return Values

For function return values, a Fortran function of type BYTE, INTEGER, REAL, LOGICAL, or DOUBLE PRECISION is equivalent to a C++ function that returns the corresponding type. There are two extra arguments for the return values of character functions, and one extra argument for the return values of complex functions.

int

Code Example 8-21 shows how to return an int to a Fortran program.



Code  Example  8-21     Returning an int to Fortran
RetInt.cc 
extern "C" int retint ( int& r )
{
    int s;
    s = r;
    ++s;
    return s;
}
RetIntmain.f
      integer r, s, RetInt
      external RetInt !$pragma C( RetInt )
      r = 2
      s = RetInt( r )
      write( *, "(2I4)") r, s
      end

Compile, link, and execute, with output.

% CC -c RetInt.cc
% f77 -c -silent RetInt.o RetIntmain.f
% f77 RetInt.o RetIntmain.o -Bstatic -lC -Bdynamic
% a.out 
 2 3 
%

Do a function of type BYTE, LOGICAL, REAL, or DOUBLE PRECISION in the same way. Use matching types according to Table 8-1 on page 124.

float

Code Example 8-22 shows how to return a float to a Fortran program:



Code  Example  8-22     Return a float to Fortran
RetFloat.cc
extern "C" float retfloat ( float& pf )
{
    float f;
    f = pf;
    ++f;
    return f;
}
RetFloatmain.f
      real RetFloat, r, s
      external RetFloat !$pragma C( RetFloat )
      r = 8.0
      s = RetFloat( r )
      print *, r, s
      end



% CC -c RetFloat.cc 
% f77 -c -silent RetFloatmain.f
% f77 RetFloat.o RetFloatmain.o -Bstatic -lC -Bdynamic
% a.out 
    8.00000 9.00000 

A Pointer to a float

Code Example 8-23 shows how to return a function value that is a pointer to a float.



Code  Example  8-23     Return a pointer to a float to Fortran
RetPtrF.cc
static float f;

extern "C" float* retptrf ( float& a )
{
    f = a;
    ++f;
    return &f;
}
RetPtrFmain.f
      integer RetPtrF
      external RetPtrF !$pragma C( RetPtrF )
      pointer (p, s)
      real r, s
      r = 8.0
      p = RetPtrF( r )
      print *, s
      end

Compile and execute, with output:

% CC -c RetPtrF.cc 
% f77 -c -silent RetPtrFmain.f
% f77 RetPtrF.o RetPtrFmain.o -Bstatic -lC -Bdynamic
% a.out 
9.00000 

The function return value is an address; you can assign it to the pointer value, or do some pointer arithmetic. You cannot use it in an expression with reals, such as RetPtrF(R)+100.0.

Double Precision

Code Example 8-24 is an example of C++ returning a type double function value to a Fortran DOUBLE PRECISION variable:



Code  Example  8-24     Return a double to Fortran
RetDbl.cc 
extern "C" double retdbl ( double& r )
{
    double s;
    s = r;
    ++s;
    return s;
}
RetDblmain.f 
      double precision r, s, RetDbl
      external RetDbl !$pragma C( RetDbl )
      r = 8.0
      s = RetDbl( r )
      write( *, "(2F6.1)" ) r, s
      end

Compile and execute, with output.

% CC -c RetDbl.cc 
% f77 -c -silent RetDblmain.f
% f77 RetDbl.o RetDblmain.o -Bstatic -lC -Bdynamic
% a.out 
   8.0 9.0 

COMPLEX

A COMPLEX or DOUBLE COMPLEX function is equivalent to a C++ routine having an additional initial argument that points to the return value storage location. A general pattern for such a Fortran function is:

	COMPLEX FUNCTION F ( arguments ) 

The pattern for a corresponding C++ function is:

struct complex { float r, i; };
f_ ( complex temp, arguments ); 

Code Example 8-25 shows how to return a type COMPLEX function value to Fortran.

Code  Example  8-25     Returning a COMPLEX value to Fortran 
RetCmplx.cc 
struct complex { float r, i; };

extern "C" void retcmplx ( complex& RetVal, complex& w ) {
    RetVal.r = w.r + 1.0 ;
    RetVal.i = w.i + 1.0 ;
    return;
}
RetCmplxmain.f
      complex u, v, RetCmplx
      external RetCmplx !$pragma C( RetCmplx )
      u = ( 7.0, 8.0 )
      v = RetCmplx( u )
      write( *, * ) u
      write( *, * ) v
      end

Compile and execute, with output:

% CC -c -silent RetCmplx.cc 
% f77 -c -silent RetCmplxmain.f
% f77 RetCmplx.o RetCmplxmain.o -Bstatic -lC -Bdynamic
% a.out 
  ( 7.00000, 8.00000) 
  ( 8.00000, 9.00000) 

Character Strings

Passing strings between C++ and Fortran is not recommended. A character-string-valued Fortran function is equivalent to a C++ function with the two extra initial arguments--data address and length. A Fortran function of this form:

	CHARACTER*15 FUNCTION G (arguments) 

and a C++ function of this form:

g_ (char * result, long int length, other arguments) 
char result[ ]; 
long int length; 

are equivalent and can be invoked in C++ with this call:

char chars[15]; 
(other arguments) 
	g_ (chars, 15L, other arguments); 

Code Example 8-26 shows how to return a character string to a Fortran program.



Code  Example  8-26     Returning a String to Fortran (C++ Code)
RetStr.cc
#include <stdio.h>

extern "C" void retstr_ ( char *retval_ptr, int retval_len,
    char& ch_ref,
    int& n_ref,
    int  ch_len )
{
    int count = n_ref;
    char *cp = retval_ptr;
    for( int i= 0; i < count; ++i ) {
    *cp++ = ch_ref;
    }
}

In Fortran, use the preceding C++ function as shown here:



Code  Example  8-27     Returning a String to Fortran (Fortran Code)
RetStrmain.f 
      character String*100, RetStr*50
      String = RetStr( '*', 10 )
      print *, "'", String(1:10), "'"
      end

Compile and execute with output:

% CC -c RetStr.cc
% f77 -c -silent RetStrmain.f
% f77 RetStr.o RetStrmain.o -Bstatic -lC -Bdynamic
% a.out
'**********'

Labeled Common

C++ and Fortran can share values in labeled common. The method is the same no matter which language calls the other, as shown by Code Example 8-28 and Code Example 8-29:



Code  Example  8-28     Using Labeled Common (Fortran Code)
UseCom.cc 	
#include <stdio.h> 
#include <stdlib.h>
struct ilk_type { 
    float p; 
    float q; 
    float r; 
}; 

extern ilk_type ilk_; 
extern "C" void usecom_ ( int& count ){ 
    ilk_.p = 7.0; 
    ilk_.q = 8.0; 
    ilk_.r = 9.0; 
}



Code  Example  8-29     Using Labeled Common (C++ Code)
UseCommain.f
integer n
real u, v, w
common /ilk/ u, v, w
    n = 3 
    u = 1.0 
    v = 2.0 
    w = 3.0 
call usecom (n)
print *, u, v, w
end 

Compile and execute, with output:

% f77 -c -silent UseCom.f 
% CC -c UseCommain.cc
% f77 UseCom.o UseCommain.o -Bstatic -lC -Bdynamic
% a.out 
 ilk_p = 7.0, ilk_q = 8.0, ilk_r = 9.0 

Any of the options that change size or alignment, or any equivalences that change alignment, may invalidate such sharing.

I/O Sharing

It's not a good idea to mix Fortran I/O with C++ I/O. It's safer to pick one and not alternate.

The Fortran I/O library is implemented largely on top of the C standard I/O library. Every open unit in a Fortran program has an associated standard I/O file structure. For the stdin, stdout, and stderr streams, the file structure need not be explicitly referenced, so it is possible to share them. However, the C++ stream I/O system uses a different mechanism.

If a Fortran main program calls C++, then before the Fortran program starts, the Fortran I/O library is initialized to connect units 0, 5, and 6 to stderr, stdin, and stdout, respectively. The C++ function must take the Fortran I/O environment into consideration to perform I/O on open file descriptors.

stdout

Code Example 8-30 shows a C++ function that writes to stderr and to stdout, and the Fortran code that calls the C++ function:



Code  Example  8-30     Mixing with stdout
MixIO.cc
#include <stdio.h>

extern "C" void mixio ( int& n ) {
    if( n <= 0 ) {
    fprintf( stderr, "Error:  negative line number (%d)\n", n );
    n= 1;
    }
    printf( "In   C++:    line # = %2d\n", n );
}
MixIOmain.f 
      integer n/ -9 /
      external MixIO !$pragma C( MixIO )
      do i= 1, 6
         n = n +1
         if ( abs(mod(n,2)) .eq. 1 ) then
            call MixIO( n )
         else
            write( *, '("In Fortran:  line # = ", i2)' ) n
         end if
      end do
      end

Compile and execute, with output:

% CC -c MixIO.cc 
% f77 -c -silent MixIOmain.f
% f77 MixIO.o MixIOmain.o -Bstatic -lC -Bdynamic
% a.out 
In Fortran: line # =-8 
error: negative line # 
In C: line # = 1 
In Fortran: line # = 2 
In C: line # = 3 
In Fortran: line # = 4 
In C: line # = 5 

stdin

Code Example 8-31 shows a C++ function that reads from stdin, and the Fortran code that calls the C++ function:



Code  Example  8-31     Mixing with stdin
MixStdin.cc 
#include <stdio.h>

extern "C" int c_read_ ( FILE* &fp, char *buf, int& nbytes, int 
buf_len )
{
    return fread( buf, 1, nbytes, fp );
}
MixStdinmain.f 
      character*1 inbyte
      integer*4 c_read, getfilep
      external getfilep
      write( *, '(a, $)') 'What is the digit? '
      flush (6)
      irtn = c_read( getfilep( 5 ), inbyte, 1 )
      write( *, 9 ) inbyte
 9    format( 'The digit read by C++ is ', a )
      end

Fortran does the prompt; C++ does the read, as follows:

% CC -c MixStdin.cc 
% f77 -c -silent MixStdinmain.f
% f77 MixSdin.o MixStdinmain.o -Bstatic -lC -Bdynamic
% a.out 
What is the digit? 3 
The digit read by C is 3 
demo%

Alternate Returns

C++ does not have an alternate return. The workaround is to pass an argument and branch on that.


C++ Calls Fortran

This section describes the interface when C++ calls Fortran.

Arguments Passed by Reference

Simple Variables Passed by Reference

Here, Fortran expects all these arguments to be passed by reference, which is the default.

Code  Example  8-32     Passing Variables by Reference (Fortran Code)
SimRef.f 
      subroutine SimRef ( t, f, c, i, d, si, sr )
      logical*1 t, f
      character c
      integer i
      double precision d
      integer*2 si
      real sr
      t = .true.
      f = .false.
      c = 'z'
      i = 9
      d = 9.9
      si = 9
      sr = 9.9
      return
      end

Here, C++ passes the address of each.



Code  Example  8-33     Passing Variables by Reference (C++ Code)
SimRefmain.cc
extern "C" void simref_( char&, char&, char&, int&, double&, 
short&, float& );
#include <stdio.h>
#include <stdlib.h>

main ( ) {
    char t, f, c;
    int i;
    double d;
    short si;
    float sr;

    simref_( t, f, c, i, d, si, sr );
    printf( "%08o %08o %c %d %3.1f %d %3.1f\n",
	   t, f, c, i, d, si, sr );
    return 0;
}

Compile and execute, with output:

% f77 -c -silent SimRef.f 
% CC -c SimRefmain.cc 
% f77 SimRef.o SimRefmain.o -Bstatic -lC -Bdynamic  
% a.out 
00000001 00000000 z 9 9.9 9 9.9 
demo%

Complex Variables Passed by Reference

The complex types require a simple structure as shown in Code Example 8-34. In this example w and z are passed by reference, which is the default:



Code  Example  8-34     Passing Complex Variables
CmplxRef.f 
      subroutine CmplxRef ( w, z )
      complex w
      double complex z
      w = ( 6, 7 )
      z = ( 8, 9 )
      return
      end
CmplxRefmain.cc
#include <stdlib.h>
#include <stdio.h>

struct complex { float r, i; };
struct dcomplex { double r, i; };

extern "C" void cmplxref_ ( complex& w, dcomplex& z );

main ( ) {
    complex d1;
    dcomplex d2;

    cmplxref_( d1, d2 );
    printf( "%3.1f %3.1f\n%3.1f %3.1f\n", d1.r, d1.i, d2.r, d2.i );
    return 0;
}

The following example shows CmplxRef.f compiled and executed with output:

% f77 -c -silent CmplxRef.f
% CC -c CmplxRefmain.cc 
% f77 CmplxRef.o CmplxRefmain.o -Bstatic -lC -Bdynamic
% a.out 
6.0 7.0 
8.0 9.0 

Character Strings Passed by Reference

Character strings match in a straightforward manner. If you make the string in Fortran, you must provide the explicit null terminator. Fortran does not automatically provide the terminator, and C++ expects it.


Note - Avoid passing strings between C++ and Fortran.


Code  Example  8-35     Passing Strings by Reference
StrRef.f 
      subroutine StrRef ( a, s )
      character a*10, s*80
      a = 'abcdefghi' // char(0)
      s = 'abcdefghijklmnopqrstuvwxyz' // char(0)
      return
      end
StrRefmain.cc 
#include <stdlib.h>
#include <stdio.h>

extern "C" void strref_ ( char*, char* );

main ( ) {
    char s10[10], s80[80];

    strref_( s10, s80 );
    printf( " s10='%s'\n s80='%s'\n", s10, s80 );
    return 0;
}

Compile and execute, with output:

% f77 -c -silent StrRef.f 
% CC -c StrRefmain.cc 
% f77 StrRef.o StrRefmain.o -Bstatic -lC -Bdynamic
% a.out 
s10='abcdefghi' 
s80='abcdefghijklmnopqrstuvwxyz' 

Arguments Passed by Value

Fortran can call C++ and pass an argument by value. However Fortran cannot handle an argument passed by value. The workaround is to pass all arguments by reference.

Function Return Values

For function return values, a Fortran function of type BYTE, INTEGER, LOGICAL, or DOUBLE PRECISION is equivalent to a C++ function that returns the corresponding type. There are two extra arguments for the return values of character functions and one extra argument for the return values of complex functions.

int

Code Example 8-36 shows how Fortran returns an INTEGER function value to C++:

Code  Example  8-36     Returning an Integer to C++
RetInt.f 
      integer function RetInt ( k )
      integer k
      RetInt = k + 1
      return
      end
RetIntmain.cc 
#include <stdio.h>
#include <stdlib.h>

extern "C" int retint_ ( int& );

main ( ) {
      int k = 8;
      int m = retint_( k );
      printf( "%d %d\n", k, m );
      return 0;
}

Compile and execute, with output:

% f77 -c -silent RetInt.f 
% CC -c RetIntmain.cc 
% f77 RetInt.o RetIntmain.o -Bstatic -lC -Bdynamic
% a.out 
8 9 

float

Code Example 8-37 shows how to return a float to a C++ program.



Code  Example  8-37     Returning a float to C++
RetFloat.f
      real function RetReal ( x )
      real x
      RetReal = x + 1.0
      return
      end
RetFloatmain.cc 	
#include <stdio.h>
extern "C" float retreal_ (float*) ;
main ( )
{
        float r, s ;
        r = 8.0 ;
        s = retreal_ ( &r ) ;
        printf( " %8.6f %8.6f \n", r, s ) ;
        return 0;
}

Compile and execute, with output:

% f77 -c -silent RetFloat.f 
% CC -c -w RetFloatmain.cc 
% f77 RetFloat.o RetFloatmain.o -Bstatic -lC -Bdynamic
% a.out 
 8.000000 9.000000 

double

Code Example 8-38 shows how Fortran returns a DOUBLE PRECISION function value to C++.



Code  Example  8-38     Returning a double to C++
RetDbl.f
      double precision function RetDbl ( x )
      double precision x
      RetDbl = x + 1.0
      return
      end
RetDblmain.cc
#include <stdio.h>
#include <stdlib.h>

extern "C" double retdbl_ ( double& );

main ( ) {
      double x = 8.0;
      double y = retdbl_( x );
      printf( "%8.6f %8.6f\n", x, y );
      return 0;
}

Compile and execute, with output:

% f77 -c -silent RetDbl.f 
% CC -c RetDblmain.cc 
% f77 RetDbl.o RetDblmain.o -Bstatic -lC -Bdynamic
% a.out 
8.000000 9.000000 

COMPLEX or DOUBLE COMPLEX

A COMPLEX or DOUBLE COMPLEX function is equivalent to a C++ routine having an additional initial argument that points to the return value storage location. A general pattern for such a Fortran function is:



	COMPLEX FUNCTION F ( arguments ) 

The pattern for a corresponding C++ function is:

struct complex { float r, i; }; 
void f_ ( complex &, other arguments )

Code Example 8-39 shows how to return a COMPLEX:



Code  Example  8-39     Returning a COMPLEX
RetCmplx.f 
      complex function RetCmplx ( x )
      complex x
      RetCmplx = x * 2.0
      return
      end
RetCmplxmain.cc 
#include <stdlib.h>
#include <stdio.h>
struct complex { float r, i; };

extern "C" void retcmplx_( complex&, complex& );

main ( ) {
    complex c1, c2 ;

    c1.r = 4.0;
    c1.i = 4.5;

    retcmplx_( c2, c1 );

    printf( " %3.1f %3.1f\n %3.1f %3.1f\n", c1.r, c1.i, c2.r, c2.i 
);
    return 0;
}

Compile, link, and execute, with output:

% f77 -c -silent RetCmplx.f 
% CC -c -w RetCmplxmain.cc 
% f77 RetCmplx.o RetCmplxmain.o -Bstatic -lC -Bdynamic
% a.out 
 4.0 4.5 
 8.0 9.0 

When you use f77 to pass files to the linker, the linker uses the f77 libraries.

Character Strings


Note - Avoid passing strings between C++ and Fortran.
A Fortran string function has two extra initial arguments: data address and length. If you have a Fortran function of the following form:

	CHARACTER*15 FUNCTION G ( arguments )

and a C++ function of this form:

g_ ( char * result, long int length, other arguments )   

they are equivalent, and can be invoked in C++ with:

char chars[15]; 
g_ ( chars, 15L, arguments );

The lengths are passed by value. You must provide the null terminator. Code Example 8-40 shows how to pass a string to C++.



Code  Example  8-40     Returning a String to C++ 
RetChr.f
      function RetChr( c, n )
      character RetChr*(*), c
      RetChr = ''
      do i = 1, n
         RetChr(i:i) = c
      end do

      RetChr(n+1:n+1) = char(0) ! Put in the null terminator.
      return
      end
RetChrmain.cc
#include <stdio.h>
#include <stdlib.h>
#include <string.h>

extern "C" void retchr_( char*, int, char*, int&, int );

main ( ) {
    char string[100], repeat_val[50];

    int repeat_len = sizeof( repeat_val );
    int count = 10;

    retchr_( repeat_val, repeat_len, "*", count, sizeof("*")-1 );

    strncpy( string, repeat_val, repeat_len );
    printf( " '%s'\n", repeat_val );
    return 0;
}

Compile, link, and execute, with output.

% f77 -c -silent RetChr.f 
% CC -c RetChrmain.cc 
% f77 RetChr.o RetChrmain.o -Bstatic -lC -Bdynamic
% a.out 
 '**********' 

The caller must set up more arguments than are apparent as formal parameters to the Fortran function. Arguments that are lengths of character strings are passed by value. Those that are not are passed by reference.

Labeled Common

C++ and Fortran can share values in labeled common. Any of the options that change size or alignment, or any equivalences that change alignment, may invalidate such sharing.

The method is the same, no matter which language calls the other.



Code  Example  8-41     Using Labeled Common (Fortran Code)
UseCom.f	
      subroutine UseCom ( n )
      integer n
      real u, v, w
      common /ilk/ u, v, w
      n = 3
      u = 7.0
      v = 8.0
      w = 9.0
      return
      end



Code  Example  8-42     Using Labeled Common (C++ Code)
UseCommain.cc 
#include <stdio.h>

struct ilk_type {
    float p;
    float q;
    float r;
};

extern ilk_type ilk_ ;
extern "C" void usecom_ ( int& );

main ( ) {
    char *string = "abc0" ;
    int count = 3;
    ilk_.p = 1.0;
    ilk_.q = 2.0;
    ilk_.r = 3.0;
    usecom_( count );
    printf( " ilk_.p=%4.1f,  ilk_.q=%4.1f,  ilk_.r=%4.1f\n",
	   ilk_.p, ilk_.q, ilk_.r );
    return 0;
}

Compile and execute, with output:

% f77 -c -silent UseCom.f 
% CC -c UseCommain.cc
% f77 UseCom.o UseCommain.o -Bstatic -lC -Bdynamic
% a.out 
 ilk_.p = 7.0, ilk_.q = 8.0, ilk_.r = 9.0 

I/O Sharing

Avoid mixing Fortran I/O with C++ I/O. It is usually safer to pick one and not alternate.

The Fortran I/O library uses the C++ standard I/O library. Every open unit in a Fortran program has an associated standard I/O file structure. For the stdin, stdout, and stderr streams, the file structure need not be explicitly referenced, so it is possible to share them.

If a C++ main program calls a Fortran subprogram, there is no automatic initialization of the Fortran I/O library (connect units 0, 5, and 6 to stderr, stdin, and stdout, respectively). If a Fortran function attempts to reference the stderr stream (unit 0), then any output is written to a file named fort.0 instead of to the stderr stream.

To make the C++ program initialize I/O and establish the preconnection of units 0, 5, and 6, insert the following line at the start of the C++ main.

	f_init();

At the end of the C++ main, you can insert:

	f_exit();

although it may not be necessary.

Code Example 8-43 and Code Example 8-44 show how to share I/O using a C++ main program and a Fortran subroutine.



Code  Example  8-43     Sharing I/O (Fortran Code)
MixIO.f 
      subroutine MixIO ( n )
      integer n
      if ( n .le. 0 ) then
         write(0,*) "error: negative line #"
         n = 1
      end if

      write( *, '("In Fortran:  line # = ", i2 )' ) n
      end



Code  Example  8-44     Sharing I/O (C++ Code)
MixIOmain.cc
#include <stdio.h>

extern "C" {
    void mixio_( int& );
    void f_init();
    void f_exit();
};

main ( ) {
    f_init();
    int m= -9;

    for( int i= 0; i < 5; ++i ) {
	++m;
	if( m == 2  ||  m == 4 ) {
	    printf( "In  C++  :  line # = %d\n", m );
	} else {
	    mixio_( m );
	}
    }
    f_exit();
    return 0;
}

Code  Example  8-45     Compile and execute, with output:

% f77 -c -silent MixIO.f 
% CC -c -w MixIOmain.cc 
% f77 MixIO.o MixIOmain.o -Bstatic -lC -Bdynamic
% a.out 
error: negative line # 
In Fortran: line # = 1 
In C: line # = 2 
In Fortran: line # = 3 
In C: line # = 4 
In Fortran: line # = 5 

With a C++ main() program, the following Fortran library routines may not work correctly: signal(), getarg(), iargc()

Alternate Returns

Your C++ program may need to use a Fortran subroutine that has nonstandard returns. To C++, such subroutines return an int (INTEGER*4). The return value specifies which alternate return to use. If the subroutine has no entry points with alternate return arguments, the returned value is undefined.

Code Example 8-46 returns one regular argument and two alternate returns.

Code  Example  8-46     Alternate Returns 
AltRet.f
      subroutine AltRet ( i, *, * )
      integer i, k
      i = 9
      write( *, * ) 'k:'
      read( *, * ) k
      if( k .eq. 10 ) return 1
      if( k .eq. 20 ) return 2
      return
      end
AltRetmain.cc
#include <stdio.h>
#include <stdlib.h>

extern "C" int altret_ ( int& );

main ( ) {
    int k = 0;
    int m = altret_( k );
    printf( "%d %d\n", k, m );
    return 0;
}

C++ invokes the subroutine as a function.

Compile, link, and execute:

% f77 -c -silent AltRet.f
% CC -c AltRetmain.cc
% f77 AltRet.o AltRetmain.o -Bstatic -lC -Bdynamic
% a.out
k:
20
9 2

In this example, the C++ main() receives a 2 as the return value of the subroutine, because you typed in a 20.




Previous Next Contents Index Doc Set Home