next up previous
Next: 3- Argument Passing Up: Interfacing Fortran and Previous: 1- Type Definitions

2- External Identifiers Naming

First of all, there are differences in the naming of external identifiers (SUBROUTINE, FUNCTION and COMMON block names in Fortran and their C equivalent).

2.1- SUBROUTINE

For a Fortran CALL SUB the corresponding C routine has to be named:

SUB
all upper case on Cray with cft77 compiler
sub
all lower case on Apollo with ftn compiler
case insensitive on IBM/370 and VMS
sub_
lower case with underscore added on all other system

The HP/UX and RS-6000 Fortran compilers need a special switch (+ppu and -qextname, respectively) in order to generate sub_ instead of sub. CERN program library policy is to use the form with the appended underscore to avoid the risk of name clashes between Fortran user routines and C library functions.

For convenience I decided to define the capitalized form Sub as a preprocessor identifier:

#define Sub F77_NAME(sub,SUB)

where the preprocessor macro F77_NAME maps to the appropriate external name:

/* Cray, VM/CMS, MVS, VMS */
#define F77_NAME(name,NAME) NAME

/* Apollo FTN */
#define F77_NAME(name,NAME) name

/* others */
#define F77_NAME(name,NAME) name##_

The IBM C/370 compiler requires in addition a

#pragma linkage(SUB,FORTRAN)

in order to use the correct argument passing mechanism which is different between Fortran and C. Unfortunately the #pragma cannot be included into the F77_NAME macro and must be specified separately.

2.2- FUNCTION

The same rules as for SUBROUTINE apply also for FUNCTION names. We found, however, that only INTEGER and LOGICAL FUNCTIONs can be emulated in C. REAL FUNCTIONs and others are not guaranteed to work on all platforms.

2.3- COMMON

Fortran COMMON blocks can be accessed from C code. Most compilers apply the same rule for generating the external identifier as for routines but up to now we came across two exceptions: the Convex compiler adds an underscore both in front and at the end. The Absoft Fortran compiler for the NeXT uses the plain lower-case name without underscores.

Again for convenience we define the capitalized form Com as a preprocessor identifier:

#define Com F77_BLOCK(com,COM)

where the preprocessor macro expands to the appropriate identifier:

/* Convex */
#define F77_BLOCK(name,NAME) _##name##_

/* NeXT */
#define F77_BLOCK(name,NAME) name

/* others */
#define F77_BLOCK(name,NAME) \ol
         F77_NAME(name,NAME)

Naively one would assume that the C structure mapping the COMMON block should be a declaration (i.e. ``extern struct ...'') since the storage should be allocated by the Fortran side. Some platforms, however, require the form of a definition, i.e.\ leaving out the extern keyword.

In order to cope with this difference we define

/* Apollo, Convex, Cray */
#define EXTERN

/* others */
#define EXTERN extern

One last complication is that on Apollo the C definition has to be given a special attribute. Otherwise the linker allocates the C structure separate from the COMMON block it should map.

Again we can define a system-dependent preprocessor macro to cope with this difference:

/* Apollo */
#define F77_COMMON(name) name \ol
       __attribute((__section(name)))  

/* others */
#define F77_COMMON(name) name

Having these ingredients it is straightforward to translate any Fortran COMMON block into a C struct. For example,

      INTEGER I
      REAL X
      DOUBLE PRECISION D
      COMMON /COMX/ I,X(3,3),D

      CHARACTER*80 CHTEXT(10)
      COMMON /COMC/ CHTEXT

is described by

#define Comx F77_BLOCK(comx,COMX)

EXTERN struct {
  INTEGER i;
  REAL x[3][3];
  DBLPREC d;
} F77_COMMON(Comx);

#define Comc F77_BLOCK(comc,COMC)

EXTERN struct {
  char text[10][80];
} F77_COMMON(Comc);

and the values are accessible as Comx.i, Comx.x[1][2] for X(3,2), Comc.text[4][0] for CHTEXT(5)(1:1) etc.

Note that one should not rely on the possibility to extend the COMMON block size by changing the dimensions in the C code. It is platform dependent whether

EXTERN struct {
  char text[1000][80];
} F77_COMMON(Comc);

without changing the Fortran definition accordingly will actually reserve the requested amount of memory for the COMMON block

Also one has to be careful with the placement of DOUBLE PRECISION variables. They should always be at an even offset from the start of the COMMON block because otherwise in a case like

      REAL X,Y
      DOUBLE PRECISION D
      COMMON /COM/ X,D,Y

it is not guaranteed that it can be mapped as

struct {
  REAL x;
  DBLPREC d;
  REAL y;
} ...

While the C compiler is allowed to add padding in order to align d, the Fortran compiler is obliged to allocate X and D at consecutive machine words. Many CPUs signal a bus error upon unaligned access to DOUBLE PRECISION variables, and compilers usually add protective code and issue a warning message.

One exception is the HP/UX Fortran compiler which silently adds padding in the same way the C compiler does. That makes the Fortran-C interface easier but at the same time violates the rules of Fortran storage association. In principle the same COMMON block could be declared in a different routine as

      REAL Z
      COMMON /COM/ Z(4)
and for the HP/UX Fortran compiler Y and Z(4) do not refer to the same memory location anymore.

2.4- /PAWC/

Some of the complications in accessing COMMON blocks from C could be avoided by defining a structure pointer which is filled by a call from a Fortran routine passing the first variable in the COMMON block.

In fact in KUIP this possibility is used for the /PAWC/ Zebra store. The C structure definition looks like

#define Pawc kc_pawc

EXTERN struct COMMON_PAWC {
  INTEGER NWPAR;
  INTEGER IXPAWC;
  INTEGER IHBOOK;
  INTEGER IXHIGZ;
  INTEGER IXKUIP;
  INTEGER IFENCE[5];
  INTEGER LQDATA[8];
  INTEGER IQDATA[999];
} *Pawc;

and the pointer is initialized by a CALL KIPAWC(NWPAR) to

void Kipawc( struct COMMON_PAWC *pawc )
{
  Pawc = pawc;
}

Linking to /PAWC/ in this way was introduced due to a request from W. Wojcik of IN2P3 in Lyon. They wanted to exploit the option DC(name) of the VS-Fortran compiler which allows to allocate COMMON blocks at execution time. The generated code references COMMON block variables indirectly through a pointer to dynamic memory rather than as an absolute address resolved by the loader. (The libraries produced on CERNVM do not make use of the DC option. The C code works either way without change.)

Preprocessor macros allow to write C code accessing the Zebra store in a Fortran-ish style. For example, the equivalent of

      DO 10 I = 1, IQ(LX-1)
        Q(LX+1) = 3.14
 10   CONTINUE

can be written as

#define LQ(n)           Pawc->LQDATA[n-1]
#define IQ(n)           Pawc->IQDATA[n-1]
#define  Q(n) (((REAL*)(Pawc->IQDATA))[n-1])

  for( i = 1; i <= IQ(lx-1); i++ ) {
    Q(lx+1) = 3.14;
  }



next up previous
Next: 3- Argument Passing Up: Interfacing Fortran and Previous: 1- Type Definitions



Janne Saarela
Mon May 22 15:43:10 METDST 1995