Occasionally it is not possible to implement all of an application in Fortran 90. You may need to call external procedures written in C, C++, or some other language—or you may need to call a Fortran 90 procedure from one of those languages. This chapter focuses on the interface between Fortran and the most common other language, C.
(This topic amplifies topic 3.1.1 in the Fortran 90 Handbook.)
When your Fortran 90 program defines the body of a procedure, the compiler places the name of the procedure, as a character string, in the object module it generates. This is a public name, which is accessible to other modules.
When your Fortran 90 program declares a procedure as EXTERNAL, the compiler places the name of the procedure, as a character string, in the generated object module. This is an external name, which is needed by the module but not defined in it. Names of common blocks and names of data and procedures declared within modules are also external names. (You can display the public and external names defined in a module using the nm utility, as discussed in the MIPS Compiling and Performance Tuning Guide.)
It is up to the IRIX linker, ld, to resolve each reference to an external name by finding that same name as a public name in some other module. This is the main job of the linker.
The Fortran compiler forces all input source text (other than the contents of character literals) to lowercase as the first step of compilation. As a result, it changes the names of procedures and named common blocks while it translates the source file. As recorded in the object file, these names are changed in two ways from the way you may have written them:
They are converted to all lowercase letters
They are normally extended with a final underscore (_) character
The following declarations produce the identifiers matrix_, mixedcase_, and cblk_ in the object file:
SUBROUTINE MATRIX external function MixedCase() COMMON /CBLK/a,b,c |
These changes cause no problem when linking modules compiled by Fortran 90 or Fortran 77, since the same convention is used for both the public and external names. Therefore the names match and the linker can resolve them.
The names of procedures defined within a MODULE are qualified with the module name, also in lowercase. If SUBROUTINE MATMUL is defined in MODULE MATRIX, its public name string is matrix$matmul_ ; that is, the module name, `$,' the procedure name, and an underscore.
In order to call a Fortran 90 subprogram from a C module you must spell the name the way the Fortran compiler spells it—using all lowercase letters and a trailing underscore. A subprogram declared as follows:
SUBROUTINE HYPOT() |
must be declared in a C function as follows (lowercase with a trailing underscore):
extern int hypot_() |
![]() | Note: Since the public name of a procedure in a MODULE contains a “$” character, and since C does not allow “$” in identifiers, it is not possible to call directly from a C program to a MODULE procedure. |
The public names of C functions can have uppercase or mixed-case names, and they have terminal underscores only when the programmer writes them that way. However, there is no way by which you can make the MIPSpro Fortran 90 compiler generate an external name containing uppercase letters or lacking an underscore. As a result, you cannot link a Fortran 90 module to some procedures in other languages. The linker reports an unresolved name.
In order to call a C function from a Fortran program, you must ensure that the C function's name is spelled the way the Fortran compiler expects it to be. When you control the name of the C function, the simplest solution is to give it a name that consists of lowercase letters with a terminal underscore. For example, the following C function:
int fromfort_() {...} |
could be declared in a Fortran program as follows:
external fromfort |
When you do not control the name of a C function, you must supply a function name that Fortran 90 can call. The only solution is to write a C function that takes the same arguments, but that has a name composed of lowercase letters and ending in an underscore. This C function can then call the function whose name contains mixed-case letters. You can write such a “wrapper” function manually, or you can use the mkf2c utility to do it automatically (see “Making C Wrappers With mkf2c”).
When you exchange data values between Fortran 90 and C, either as parameters, as function results, or as elements of common blocks, you must make sure that the two languages agree on the size, alignment, and subscript of each data value.
The correspondence between Fortran and C scalar data types is shown in Table 3-1. This table assumes the default precisions. Use of compiler options such as -i2 or -r8 affects the meaning of the words LOGICAL, INTEGER, and REAL.
Table 3-1. Corresponding Fortran and C Data Types
Fortran Data Type | Corresponding C Type |
---|---|
BYTE, INTEGER(1), LOGICAL(1) | signed char |
CHARACTER(1) | unsigned char |
INTEGER(2), LOGICAL(2) | short |
INTEGER[a], INTEGER(4), LOGICALa, LOGICAL(4) | int or long |
INTEGER(8), LOGICAL(8) | long long |
REALa, REAL(4) | float |
DOUBLE PRECISION, REAL(8) | double |
REAL(16) | long double |
COMPLEXa, COMPLEX(kind=4) | typedef struct{float real, imag; } cpxk4; |
DOUBLE COMPLEX, COMPLEX(kind=8) | typedef struct{double real, imag;} cpxk8; |
COMPLEX(kind=16) | typedef struct{long double re, im;} cpxk16; |
CHARACTER(n) (n>1) | typedef char fstr_n[n]; |
[a] Assuming default kind-parameter |
The Fortran CHARACTER(1) data type corresponds to the C type unsigned char. However, the two languages differ in the treatment of strings of characters.
A Fortran CHARACTER(n) (for n>1) variable contains exactly n characters at all times. When a shorter character expression is assigned to it, it is padded on the right with spaces to reach n characters.
A C vector of characters is normally sized 1 greater than the longest string assigned to it. It may contain fewer meaningful characters than its size allows, and the end of meaningful data is marked by a null byte. There is no null byte at the end of a Fortran string (except by chance memory alignment).
Since there is no terminal null byte, most of the string library functions familiar to C programmers (strcpy(), strcat(), strcmp(), and so on) cannot be used with Fortran string values. The strncpy(), strncmp(), bcopy(), and bcmp() functions can be used because they depend on a count rather than a delimiter.
Fortran and C use different arrangements for the elements of an array in memory. Fortran uses column-major order (when iterating sequentially through memory, the leftmost subscript varies fastest), whereas C uses row-major order (the rightmost subscript varies fastest to generate sequential storage locations). In addition, Fortran array indices are by default origin-1, and can be declared as any origin, while C indices are always origin-0.
To use a Fortran array in C,
reverse the order of dimension limits when declaring the array
reverse the sequence of subscript variables in a subscript expression
adjust the subscripts to origin-0 (usually, decrement by 1)
The correspondence between Fortran and C subscript values is depicted in Figure 3-1. You derive the C subscripts for a given element by decrementing the Fortran subscripts and using them in reverse order; for example, Fortran (99,9) corresponds to C [8][98].
![]() | Note: A Fortran array can be declared with some other lower bound than the default of 1. If the Fortran subscript is origin-0, no adjustment is needed. If the Fortran lower bound is greater than 1, the C subscript is adjusted by that amount. |
Fortran 90 supports assumed-shape and deferred-shape arrays (see “Assumed-Shape and Deferred-Shape Arrays”) as well as array slices. You cannot pass any of these types of array to a non-Fortran procedure. The reason is that Fortran 90 represents such arrays in memory using a descriptor record containing indirect pointers and other data. The format of this record is not part of the published programming interface to MIPSpro Fortran 90, as it is subject to change.
If you attempt to pass an assumed-shape or deferred-shape array, or an array slice, to a non-Fortran function, the function does not receive the address of array elements in memory as it would when an array is passed. Instead it receives the address of a descriptive record of undocumented contents, resulting in unpredictable behavior.
The MIPSpro Fortran 90 compiler generates code to pass parameters according to simple, uniform rules; and it generates subprogram code that expects parameters to be passed according to these rules. When calling non-Fortran functions, you must know how parameters will be passed; and when calling Fortran subprograms from other languages, you must cause the other language to pass parameters correctly.
![]() | Note: You should be aware that all compilers for a given version of IRIX use identical conventions for passing parameters. These conventions are documented at the machine instruction level in the MIPSpro Assembly Language Programmer's Guide, which also details the differences in the conventions used in different releases. |
Every parameter passed to a subprogram, regardless of its data type, is passed as the address of the actual parameter value in memory. This simple rule is extended for two special cases:
The length of each CHARACTER(n) parameter (for n>1) is passed as an additional INTEGER(4) value, following the explicit parameters.
When a function returns type CHARACTER(n) (for n>1), the address of the space to receive the result is passed as the first parameter to the function, and the length of the result space is passed as the second parameter, preceding all explicit parameters.
COMPLEX(8) cp8 CHARACTER(16) creal, cimag EXTERNAL CPXASC CALL CPXASC(creal,cimag,cp8) |
The code generated from the CALL in Example 3-1 prepares the following five argument values:
The address of creal
The address of cimag
The address of cp8
The length of creal, an integer value of 16
The length of cimag, an integer value of 16
CHARACTER(8) symbl,picksym CHARACTER(100) sentence INTEGER nsym symbl = picksym(sentence,nsym) |
The code generated from the function call in Example 3-2 prepares the following five argument values:
The address of temporary space to hold the function result (after the function call, the contents of the temporary are copied to variable symbl)
The length of symbl, an integer value of 8
The address of sentence, the first explicit parameter
The addrss of nsym, the second explicit parameter
The length of sentence, an integer value of 100
There are two types of callable Fortran subprograms: subroutines and functions. In C terminology, both types of subprogram are external functions. The difference is the use of the function return value from each.
From the standpoint of a C module, a Fortran subroutine is an external function returning int. The integer return value is normally ignored by a C caller (it is the alternate return statement number, if any).
Example 3-3 shows a simple Fortran 90 subroutine that takes adds arrays of complex numbers.
SUBROUTINE ADDC32(Z,A,B,N) COMPLEX(32) Z(1),A(1),B(1) INTEGER N,I DO 10 I = 1,N Z(I) = A(I) + B(I) 10 CONTINUE RETURN END |
Example 3-4 shows a sketch of how the Fortran 90 subroutine could be called from C.
typedef struct{long double real, imag;} cpx32; extern int addc32_(cpx32*pz,cpx32*pa,cpx32*pb,int*pn); cpx32 z[MAXARRAY], a[MAXARRAY], b[MAXARRAY]; ... int n = MAXARRAY; (void)addc32_(&z, &a, &b, &n); |
The Fortran subroutine in Example 3-3 is named in Example 3-4 using lowercase letters and a terminal underscore—the way the Fortran 90 compiler spells the public name in the object file. The subroutine is declared as returning an integer. This return value is ignored but, for clarity, the actual call is cast to void to show that the return value is ignored intentionally, not by accident.
The trivial subroutine in Example 3-5 takes adjustable-length character parameters.
SUBROUTINE PRT(BEF,VAL,AFT) CHARACTER*(*)BEF,AFT REAL VAL PRINT *,BEF,VAL,AFT RETURN END |
The C program in Example 3-6 prepares CHARACTER*16 values and passes them to the subroutine in Example 3-5.
typedef char fstr_16[16]; extern int prt_(fstr_16*pbef, float*pval, fstr_16*paft, int lbef, int laft); main() { float val = 2.1828e0; fstr_16 bef,aft; strncpy(bef,”Before..........”,sizeof(bef)); strncpy(aft,”...........After”,sizeof(aft)); (void)prt_(bef,&val,aft,sizeof(bef),sizeof(aft)); } |
Observe that the subroutine call requires five parameters: the addresses of the three explicit parameters, and the lengths of the two string parameters. In Example 3-6, the string length parameters are generated using sizeof(), which returns the memory size of the typedef fstr_16.
When the Fortran code does not require a specific length of string, the C code that calls it can pass an ordinary C character vector, as shown in Example 3-7. In this example, the string length parameter length values are calculated dynamically using strlen().
extern int prt_(char*pbef, float*pval, char*paft, int lbef, int laft); main() { float val = 2.1828e0; char *bef = "Start:"; char *aft = ":End"; (void)prt_(bef,&val,aft,strlen(bef),strlen(aft)); } |
A Fortran function returns a scalar value as its explicit result. This corresponds exactly to the C concept of a function with an explicit return value. When the Fortran function returns any type shown in Table 3-1 other than CHARACTER(n) (n>1), you can call the function from C and handle its return value exactly as if it were a C function returning that data type.
The trivial function shown in Example 3-8 accepts and returns COMPLEX(8) values.
COMPLEX(kind=8) FUNCTION FSUB8(INP) COMPLEX(kind=8) INP FSUB8 = INP END |
Although a COMPLEX value is declared as a structure in C, it can be used as the return type of a function. The C program in Example 3-9 shows how the function in Example 3-8 is declared and called.
typedef struct{ double real, imag; } cpx8; extern cpx8 fsub8_( cpx8 * inp ); main() { cpx8 inp = { -3.333, -5.555 }; cpx8 oup = { 0.0, 0.0 }; printf("testing fsub8..."); oup = fsub8_( &inp ); if ( inp.real == oup.real && inp.imag == oup.imag ) printf("Ok\n"); else printf("Nope\n"); } |
Observe that the parameters to a function, like the parameters to a subroutine, are passed as pointers, but the value returned is a value, not a pointer to a value.
![]() | Note: In IRIX 5.3 and earlier 32-bit systems, you can not call a Fortran function that returns COMPLEX (although you can call one that returns any other arithmetic scalar type). The register conventions used by 32-bit compilers prior to IRIX 6.0 do not permit returning a structure value from a Fortran function to a C caller. |
FUNCTION FS16(J,K,S) CHARACTER(16) S INTEGER J,K FS16 = S(J:K) RETURN END |
The function in Example 3-10 has a CHARACTER(16) return value. When a Fortran function returns a CHARACTER*n (n>1) value, the returned value is not the explicit result of the function. Instead, you must pass the address and length of the result area as the first two parameters of the function, preceding the explicit parameters. This is demonstrated in Example 3-11.
typedef char fstr_16[16]; extern void fs16_ (fstr_16 *pz,int lz,int *pj,int *pk,fstr_16*ps,int ls); main() { char work[64]; fstr_16 inp,oup; int j=7; int k=11; strncpy(inp,"0123456789abcdef",sizeof(inp)); fs16_ ( oup, sizeof(oup), &j, &k, inp, sizeof(inp) ); strncpy(work,oup,sizeof(oup)); work[sizeof(oup)] = '\0'; printf("FS16 returns <%s>\n",work); } |
In Example 3-11, the address and length of the function result are the first two parameters of the function. (Since type fstr_16 is an array, its name, oup, evaluates to the address of its first element.) The next three parameters are the addresses of the three named parameters. The final parameter is the length of the string parameter.
In general, you can call units of C code from Fortran as if they were written in Fortran, provided that the C modules follow the Fortran conventions for passing parameters (see “How Fortran Passes Subprogram Parameters”). When the C function expects parameters passed using other conventions, you normally need to build a “wrapper” for the C function using the mkf2c command.
The C function in Example 3-12 is written to use the Fortran conventions for its name (lowercase with final underscore) and for parameter passing.
/* || C functions to export the facilities of strtoll() || to Fortran 77 programs. Effective Fortran declaration: || || INTEGER*8 FUNCTION ISCAN(S,J) || CHARACTER*(*) S || INTEGER J || || String S(J:) is scanned for the next signed long value || as specified by strtoll(3c) for a "base" argument of 0 || (meaning that octal and hex literals are accepted). || || The converted long long is the function value, and J is || updated to the nonspace character following the last || converted character, or to 1+LEN(S). || || Note: if this routine is called when S(J:J) is neither || whitespace nor the initial of a valid numeric literal, || it returns 0 and does not advance J. */ #include <ctype.h> /* for isspace() */ long long iscan_(char *ps, int *pj, int ls) { int scanPos, scanLen; long long ret = 0; char wrk[1024]; char *endpt; /* when J>LEN(S), do nothing, return 0 */ if (ls >= *pj) { /* convert J to origin-0, permit J=0 */ scanPos = (0 < *pj)? *pj-1 : 0 ; /* calculate effective length of S(J:) */ scanLen = ls - scanPos; /* copy S(J:) and append a null for strtoll() */ strncpy(wrk,(ps+scanPos),scanLen); wrk[scanLen] = `\0'; /* scan for the integer */ ret = strtoll(wrk, &endpt, 0); /* || Advance over any whitespace following the number. || Trailing spaces are common at the end of Fortran || fixed-length char vars. */ while(isspace(*endpt)) { ++endpt; } *pj = (endpt - wrk)+scanPos+1; } return ret; } |
The program in Example 3-13 demonstrates a call to the function in Example 3-12.
EXTERNAL ISCAN INTEGER(8) ISCAN INTEGER(8) RET INTEGER J,K CHARACTER(50) INP INP = '1 -99 3141592 0xfff 033 ' J = 0 DO WHILE (J .LT. LEN(INP)) K = J RET = ISCAN(INP,J) PRINT *, K,': ',RET,' -->',J END DO END |
A C function can refer to the contents of a COMMON block defined in a Fortran program. The name of the block as given in the COMMON statement is altered as described in “How Fortran 90 Handles External and Public Names” (that is, forced to lowercase and extended with an underscore). The name of the “blank common” is _BLNK__ (one leading underscore and two final ones).
In order to refer to the contents of a common block, take these steps:
Declare a C structure whose fields have the appropriate data types to match the successive elements of the Fortran common block. (See Table 3-1 for corresponding data types.)
Declare the common block name as an external structure of that type.
A sketch of the method is shown in Example 3-14.
INTEGER STKTOP,STKLEN,STACK(100) COMMON /WITHC/STKTOP,STKLEN,STACK struct fstack { int stktop, stklen; int stack[100]; } extern fstack withc_; int peektop_() { if (withc_.stktop) /* stack not empty */ return withc_.stack[withc_.stktop-1]; else... } |
There are two important restrictions on this capability.
First, you cannot map a common block that contains pointer-based variables. The data object that represents a pointer-based variable is not documented, so you cannot know what kind of C data type to use at that point in the C structure declaration.
Second, if the common block contains a variable of Fortran 90 derived type (a structure), you must be sure that the derived type is declared with the SEQUENCE attribute. Otherwise, you cannot be sure that its fields will appear in the expected sequence in memory.
As described under “Corresponding Array Elements”, a C program must take special steps to access arrays created in Fortran. The Fortran fragment in Example 3-15 prepares a matrix in a common block, then calls a C subroutine to modify the array.
INTEGER IMAT(10,100),R,C COMMON /WITHC/IMAT R = 74 C = 6 CALL CSUB(C,R,746) PRINT *,IMAT(6,74) END |
The C function in Example 3-16 stores its third argument in the common array using the subscripts passed in the first two arguments. In the C function, the order of the dimensions of the array are reversed, so the subscript values are reversed to match, and decremented by 1 to provide 0-origin indexing.
extern struct { int imat[100][10]; } withc_; int csub_(int *pc, int *pr, int *pval) { withc_.imat[*pr-1][*pc-1] = *pval; return 0; /* all Fortran subrtns return int */ } |
Using the special intrinsic functions %VAL and %LOC you can pass parameters in ways other than the standard Fortran conventions described under `“How Fortran Passes Subprogram Parameters”.
%VAL is used in parameter lists to cause parameters to be passed by value rather than by reference. Suppose that you need to call a C function having the following prototype:
int takesint_ (int p1, char *p2, int len) |
The first argument to this function is an integer value (not the address of an integer value in memory). You could call this function from Fortran 90 code similar to that in Example 3-17.
character(80) sentence integer(4) j call takesint(%VAL(j),sentence) |
The use of %VAL(j) causes the contents of j to be passed, rather than the address of j.
The program mkf2c provides an alternate interface for C routines called by Fortran. (Some details of mkf2c are covered in the mkf2c(1) reference page.)
The mkf2c program reads a file of C function prototype declarations and generates an assembly language module. This module contains one callable entry point for each C function. The entry point, or “wrapper,” accepts parameters in the Fortran calling convention, and passes the same values to the C function using the C conventions.
A simple case of using a function as input to mkf2c is
simplefunc (int a, double df) { /* function body ignored */ } |
For this function, mkf2c (with no options) generates a wrapper function named simple_ (truncated to 6 characters, made lowercase, with an underscore appended). The wrapper function expects two parameters, an integer and a REAL*8, passed according to Fortran conventions; that is, by reference. The code of the wrapper loads the values of the parameters into registers using C conventions for passing parameters by value, and calls simplefunc().
Since mkf2c processes only the C source, not the Fortran source, it treats the Fortran parameters based on the data types specified in the C function header. These treatments are summarized in Table 3-2.
Table 3-2. How mkf2c Treats Function Arguments
Data Type in C Prototype | Treatment by Generated Wrapper Code |
---|---|
unsigned char | Load CHARACTER(1) from memory to register, no sign extension. |
char | Load CHARACTER(1) from memory to register; sign extension only when -signed is specified. |
unsigned short, unsigned int | Load INTEGER(2) or INTEGER(4) from memory to register, no sign extension. |
short | Load INTEGER(2) from memory to register with sign extension. |
int, long | Load INTEGER(4) from memory to register with sign extension. |
long long | Load INTEGER(8) from memory to register with sign extension. |
float | Load REAL(4) from memory to register, extending to double unless -f is specified. |
double | Load REAL(8) from memory to register. |
long double | Load REAL(16) from memory to register. |
char name[], name[n] | Pass address of CHARACTER(n) and pass length as integer parameter as Fortran does. |
char * | Copy CHARACTER(n) value into allocated space, append null byte, pass address of copy. |
In Table 3-2, notice the different treatments for an argument declared as a character array and one declared as a character address (even though these two declarations are semantically the same in C).
When the C function expects a character address, mkf2c generates the code to dynamically allocate memory and to copy the Fortran character value, for its specified length, to memory. This creates a null-terminated string. In this case,
the address passed to C points to allocated memory
the length of the value is not passed as an implicit argument
there is a terminating null byte in the value
changes in the string are not reflected back to Fortran
A character array is passed by mkf2c as a Fortran CHARACTER*n value. In this case,
the address prepared by Fortran is passed to the C function
the length of the value is passed as an implicit argument (see “Normal Treatment of Parameters”)
the character array contains no terminating null byte
changes in the array by the C function are visible to Fortran
Since the C function cannot declare the extra string-length parameter (if it declared the parameter, mkf2c would process it as an explicit argument), the C programmer has a choice of ways to access the string length. When the Fortran program always passes character values of the same size, the length parameter can simply be ignored. If its value is needed, the varargs macro can be used to retrieve it.
Suppose the C function prototype is specified as follows:
void func1 (char carr1[],int i, char *str, char carr2[]); |
In this case, mkf2c passes a total of six parameters to C. The fifth parameter is the length of the Fortran value corresponding to carr1. The sixth is the length of carr2. The C function can use the varargs macros to retrieve these hidden parameters. mkf2c ignores the varargs macro va_alist appearing at the end of the parameter name list.
When func1 is changed to use varargs, the C source file is as shown in Example 3-18.
#include "varargs.h" void func1 (char carr1[],int i,char *str,char carr2[],va_alist); {} |
The C routine would retrieve the lengths of carr1 and carr2, placing them in the local variables carr1_len and carr2_len, using code like the fragment shown in Example 3-19.
va_list ap; int carr1_len, carr2_len; va_start(ap); carr1_len = va_arg (ap, int) carr2_len = va_arg (ap, int) |
When it does not recognize the data type specified in the C function, mkf2c issues a warning message and generates code to simply pass the pointer set up by Fortran. It does this in the following cases:
any nonstandard data type name, for example a data type that might be declared using typedef or a data type defined as a macro
any structure argument
any argument with multiple indirection (two or more asterisks, for example char**)
Since mkf2c does not support structure-valued arguments, it does not support passing COMPLEX*n values or derived types. Nor does mkf2c have any means of passing assumed-shape or deferred-shape arrays.
mkf2c understands only a limited subset of the C grammar. This subset includes common C syntax for function entry point, C-style comments, and function bodies. However, it does not include constructs such as typedefs, external function declarations, or C preprocessor directives. The presence of these things in the input to mkf2c can confuse it.
To ensure that only the constructs understood by mkf2c are included in wrapper input, you need to place special comments around each function for which Fortran-to-C wrappers are to be generated (see example below).
Once these special comments, /* CENTRY */ and /* ENDCENTRY */, are placed around the code, use the program excentry(1) before mkf2c to generate the input file for mkf2c.
Example 3-20 illustrates the use of extcentry. It shows the C file foo.c containing the function foo, which is to be made Fortran callable.
typedef unsigned short grunt [4]; struct { long 1,11; char *str; } bar; main () { int kappa =7; foo (kappa,bar.str); } /* CENTRY */ foo (integer, cstring) int integer; char *cstring; { if (integer==1) printf("%s",cstring); } /* ENDCENTRY */ |
The special comments /* CENTRY */ and /* ENDCENTRY */ surround the section that is to be made Fortran callable. To generate the assembly language wrapper foowrp.s from the above file foo.c, use the following set of commands:
% extcentry foo.c foowrp.fc % mkf2c foowrp.fc foowrp.s |
The programs mkf2c and extcentry are found in the directory /usr/bin.
make(1) contains default rules to help automate the control of wrapper generation. The following example of a makefile illustrates the use of these rules. In the example below, an executable object file is created from the files main.f (a Fortran main program) and callc.c:
test: main.o callc.o f90 -o test main.o callc.o callc.o: callc.fc clean: rm -f *.o test *.fc |
In this program, main calls a C routine in callc.c. The extension .fc has been adopted for Fortran-to-call-C wrapper source files. The wrappers created from callc.fc will be assembled and combined with the binary created from callc.c. Also, the dependency of callc.o on callc.fc will cause callc.fc to be recreated from callc.c whenever the C source file changes. (The programmer is responsible for placing the special comments for extcentry in the C source as required.)
![]() | Note: Options to mkf2c can be specified when make is invoked by setting the make variable F2CFLAGS. Also, do not create a .fc file for the modules that need to have wrappers created. These files are both created and removed by make in response to the file.o:file.fc dependency. |
The makefile above controls the generation of wrappers and Fortran objects. You can add modules to the executable object file in one of the following ways:
If the file is a native C file whose routines are not to be called from Fortran using a wrapper interface, or if it is a native Fortran file, add the .o specification of the final make target and dependencies.
If the file is a C file containing routines to be called from Fortran using a wrapper interface, the comments for extcentry must be placed in the C source, and the .o file placed in the target list. In addition, the dependency of the .o file on the .fc file must be placed in the makefile. This dependency is illustrated in the example makefile above, where callf.o depends on callf.fc.
You can write modules in MIPS assembly language, following the guidelines in the MIPSpro Assembly Language Programmer's Guide. Procedures in these modules can be called from Fortran. There is only one special consideration.
Operating in assembly language, you can change the operating mode of the CPU, and in particular you can change the rounding mode. When running Fortran 90 programs that contain quad-precision operations, you must run the compiler in round-to-nearest mode. Because this mode is the default, you usually do not need to be concerned with setting it. You usually need to set this mode when writing programs that call your own assembly routines. Refer to the swapRM manual page for further details.