Compaq Fortran
User Manual for
Tru64 UNIX
and
Linux Alpha Systems
Appendix A
Compatibility: Compaq Fortran 77 and Compaq Fortran on Multiple Platforms
This appendix provides compatibility information for those porting
Compaq Fortran 77 and Compaq Fortran applications from other Compaq
systems and for those designing applications for portability to
multiple platforms.
This appendix contains the following topics:
A.1 Compaq Fortran and Compaq Fortran 77 Compatibility on Various Platforms
Table A-1 summarizes the compatibility of Compaq Fortran for
Compaq Tru64 UNIX and Linux Alpha systems with Compaq Fortran on
OpenVMS Alpha Systems, Compaq Fortran 77 on other platforms
(architecture/operating system pairs), and Compaq Visual Fortran for
Windows systems.
Table A-1 Summary of Language Compatibility
|
Compaq Fortran 77 (CF77) or Compaq Fortran (CF95) for ... Systems |
Language Feature |
CF95 UNIX Alpha |
CF95 Linux Alpha |
CF77 UNIX Alpha |
CF95 Windows |
CF95 OpenVMS Alpha |
CF77 OpenVMS Alpha |
CF77 OpenVMS VAX |
Linking against static and shared libraries
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
Create code for shared libraries
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
Recursive code support
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
AUTOMATIC and STATIC statements
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
STRUCTURE and RECORD declarations
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
INTEGER*1, *2, *4
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
LOGICAL*1, *2, *4
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
INTEGER*8 and LOGICAL*8
|
X
|
X
|
X
|
X
1
|
X
|
X
|
|
REAL*4, *8
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
REAL*16
2
|
X
|
X
|
X
|
|
X
|
X
|
X
|
COMPLEX*8, *16
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
COMPLEX*32
3
|
X
|
X
|
|
|
X
|
|
|
POINTER (CRAY-style)
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
INCLUDE statements
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
IMPLICIT NONE statements
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
Data initialization in type declarations
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
Automatic arrays
|
X
|
X
|
X
|
X
|
X
|
X
|
|
VOLATILE statements
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
NAMELIST-directed I/O
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
31-character names including $ and _
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
Source listing with machine code
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
Debug statements in source
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
Bit constants to initialize data and use in arithmetic
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
DO WHILE and END DO statements
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
Built-in functions %LOC, %REF, %VAL
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
SELECT CASE construct
|
X
|
X
|
X
|
X
|
X
|
X
|
|
EXIT and CYCLE statements
|
X
|
X
|
X
|
X
|
X
|
X
|
|
Variable FORMAT expressions (VFEs)
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
! marks end-of-line comment
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
Optional run-time bounds checking for arrays and substrings
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
Binary (unformatted) I/O in IEEE big endian, IEEE little endian, VAX,
IBM, and CRAY floating-point formats
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
Fortran 95/90 standards checking
|
X
|
X
|
|
X
|
X
|
|
|
FORTRAN-77 standards checking
|
|
|
X
|
X
|
|
X
|
X
|
IEEE exception handling
|
X
|
X
|
X
|
X
|
X
|
X
|
|
VAX floating data type in memory
|
|
|
|
|
X
|
X
|
X
|
IEEE floating data type in memory
|
X
|
X
|
X
|
X
|
X
|
X
|
|
CDD/Repository DICTIONARY support
|
|
|
|
|
|
X
|
X
|
KEYED access and INDEXED files
|
|
|
|
|
X
|
X
|
X
|
Parallel decomposition
|
X
5
|
|
5
|
5
|
5
|
5
|
X
|
OpenMP parallel directives
|
X
|
|
|
|
|
|
|
Conditional compilation using IF...DEF constructs
|
X
|
X
|
|
X
|
X
|
|
|
Vector code support
|
|
|
|
|
|
|
X
|
Direct inlining of Basic Linear Algebra Subroutines (BLAS)
|
6
|
6
|
6
|
6
|
6
|
6
|
X
|
DATE_AND_TIME returns 4-digit year
|
X
|
X
|
X
|
X
|
X
|
X
|
X
|
FORALL statement and construct
|
X
|
X
|
|
X
|
X
|
|
|
Automatic deallocation of ALLOCATABLE arrays
|
X
|
X
|
|
X
|
X
|
|
|
Dim argument to MAXLOC and MINLOC
|
X
|
X
|
|
X
|
X
|
|
|
PURE user-defined subprograms
|
X
|
X
|
|
X
|
X
|
|
|
ELEMENTAL user-defined subprograms
|
X
|
X
|
|
X
|
X
|
|
|
Pointer initialization (initial value)
|
X
|
X
|
|
X
|
X
|
|
|
The NULL intrinsic to nullify a pointer
|
X
|
X
|
|
X
|
X
|
|
|
Derived-type structure initialization
|
X
|
X
|
|
X
|
X
|
|
|
CPU_TIME intrinsic subroutine
|
X
|
X
|
|
X
|
X
|
|
|
Kind argument to CEILING and FLOOR intrinsics
|
X
|
X
|
|
X
|
X
|
|
|
Nested WHERE constructs, masked ELSEWHERE statement, and named WHERE
constructs
|
X
|
X
|
|
X
|
X
|
|
|
Comments allowed in namelist input
|
X
|
X
|
|
X
|
X
|
|
|
Generic identifier in END INTERFACE statements
|
X
|
X
|
|
X
|
X
|
|
|
Minimal FORMAT edit descriptor field width
|
X
|
X
|
|
X
|
X
|
|
|
Detection of Obsolescent and/or Deleted features
7
|
X
|
X
|
|
X
|
X
|
|
|
1Alpha systems only.
2For REAL*16 data, OpenVMS VAX systems use H_float format,
and Alpha systems use IEEE style X_float format.
3For COMPLEX*32 data, Alpha systems use IEEE style X_float
format for both REAL*16 parts.
5For parallel processing, you can also use the optional KAP
performance preprocessor for a shared memory multiprocessor system.
6BLAS and other routines are available with the Compaq
Extended Mathematical Library (CXML) product on Alpha systems.
7Compaq Fortran flags these deleted and obsolescent
features, but fully supports them.
A.2 Compatibility with Compaq Fortran 77 for Compaq Tru64 UNIX Systems
This section provides compatibility information for those porting
Compaq Fortran 77 applications from Compaq Tru64 UNIX systems. It
discusses the following topics:
- Major language features for compatibility with Compaq Fortran 77
for Compaq Tru64 UNIX systems ( Section A.2.1)
- Language differences between Compaq Fortran and Compaq Fortran 77,
including Compaq Fortran 77 extensions on Compaq Tru64 UNIX Systems
that are not supported by this version of Compaq Fortran on Compaq
Tru64 UNIX Systems ( Section A.2.2)
- Language features detected during compilation differently by Compaq
Fortran than Compaq Fortran 77 for Compaq Tru64 UNIX Systems
( Section A.2.3)
A.2.1 Major Language Features for Compatibility with Compaq Fortran 77 for Compaq Tru64 UNIX Systems
To simplify porting applications from Compaq Fortran 77 to
Compaq Fortran on Tru64 UNIX systems, Compaq Fortran supports the
following Compaq Fortran 77 extensions that are not part of the Fortran
95/90 standards:
- Record structures (STRUCTURE and RECORD statements)
- I/O statements, including PRINT, ACCEPT, TYPE, DELETE, and UNLOCK
- I/O statement specifiers, such as the INQUIRE statement specifiers
CARRIAGECONTROL, CONVERT, ORGANIZATION, and RECORDTYPE
- Certain data types, including 8-byte INTEGER and LOGICAL variables
and 16-byte REAL variables (available on Alpha systems)
- Size specifiers for data declaration statements, such as INTEGER*4,
in addition to the KIND type parameter
- IEEE floating-point data type in memory
- The POINTER statement and its associated data type (CRAY pointers).
- The typeless PARAMETER statement
- The VOLATILE statement
- The AUTOMATIC and STATIC statements
- Built-in functions used in argument lists, such as %VAL and %LOC
- Hollerith constants
- Variable-format expressions (VFEs)
- Certain intrinsic functions
- The tab source form (resembles fixed-source form)
- I/O formatting descriptors
- USEROPEN routines for user-defined open routines
- Additional language features, including the DEFINE FILE, ENCODE,
DECODE, and VIRTUAL statements
In addition to language extensions, Compaq Fortran also supports the
following Compaq Fortran 77 features:
- Compaq Fortran 77 compilation control statements and directives
(see the Compaq Fortran Language Reference Manual), including:
- INCLUDE statement forms using /LIST and /NOLIST (requires compiling
with
-vms
)
- OPTIONS statement to override or set compiler command-line options
- General cDEC$ directives, including:
cDEC$ ALIAS
cDEC$ IDENT
cDEC$ OPTIONS
cDEC$ PSECT
cDEC$ TITLE
cDEC$ SUBTITLE
- A nearly identical set of command-line options and their associated
features (see Section A.2.4).
- The ability to call between Compaq Fortran 77 and Compaq Fortran
routines and a common run-time environment. For example, a Compaq
Fortran 77 procedure and a Compaq Fortran procedure can perform I/O to
the same unit number (see Section A.5).
-
foriosdef.for
symbolic parameter definitions for use with run-time (IOSTAT) error
handling (see Chapter 8).
For More Information:
On the Compaq Fortran language, see the Compaq Fortran Language Reference Manual.
A.2.2 Language Features Provided Only by Compaq Fortran 77 for Compaq Tru64 UNIX Systems
Compaq Fortran conforms to the Fortran 95/90 standard, which is a
superset of the FORTRAN-77 standard. Compaq Fortran provides many but
not all of the FORTRAN-77 extensions provided by Compaq Fortran 77.
The following list shows FORTRAN-77 extensions provided by Compaq
Fortran 77 on Compaq Tru64 UNIX systems are not provided by
Compaq Fortran. Where appropriate, this list indicates equivalent
Compaq Fortran language features:
- Octal notation for integer constants is not part of the Compaq
Fortran Language. Compaq Fortran 77 (
f77
command) only supports this feature when the
-vms
option is specified. For example:
I = "0014 ! Assigns 12 to I, not supported by Compaq Fortran
|
- The Compaq Fortran compiler discards leading zeros for
"disp"
in the STOP statement. For example:
STOP 001 ! Prints 1 instead of 001
|
- When a single-precision constant is assigned to a double-precision
variable, Compaq Fortran 77 evaluates the constant in double precision.
The Fortran 95/90 standards require that the constant be evaluated in
single precision.
When a single-precision constant is assigned to a
double-precision variable with Compaq Fortran, it is evaluated in
single precision. You can, however, specify the
f90
-fpconstant
option to request that a single-precision constant assigned to a
double-precision variable be evaluated in double precision.
In the
example below, Compaq Fortran 77 assigns identical values to D1 and D2,
whereas Compaq Fortran obeys the standard and assigns a less precise
value to D1.
For example:
REAL*8 D1,D2
DATA D1 /2.71828182846182/ ! Incorrect - only REAL*4 value
DATA D2 /2.71828182846182D0/ ! Correct - REAL*8 value
|
- The names of intrinsics introduced by Compaq Fortran may conflict
with the names of existing external procedures if the procedures were
not specified in an EXTERNAL declaration. For example:
EXTERNAL SUM
REAL A(10),B(10)
S = SUM(A) ! Correct - invokes external function
T = DOT_PRODUCT(A,B) ! Incorrect - invokes intrinsic function
|
- When writing namelist external records, Compaq Fortran uses the
syntax for namelist external records specified by the Fortran 95/90
standards, rather than the Compaq Fortran 77 syntax (an extension to
the FORTRAN-77 and Fortran 95/90 standards).
Consider the following
program:
% cat test.f
INTEGER I
NAMELIST /N/ I
I = 5
PRINT N
END
|
When this program is compiled by the
f90
command and run, the following output appears:
% f90 test.f
% a.out
&N
I = 5
/
|
When this program is compiled by the
f77
command and run, the following output appears:
% f77 test.f
% a.out
$N
I = 5
$END
|
Use the
-f77rtl
option to tell Compaq Fortran to generate NAMELIST output in
Compaq Fortran 77 format.
Compaq Fortran accepts Fortran 95/90 namelist syntax and Compaq
Fortran 77 namelist syntax for reading records.
- The Compaq Fortran language does not include C-style escape
sequences in standard char constants. For example:
CHARACTER NL
NL = '\n' ! Incorrect
NL = CHAR(10) ! Correct
|
The Compaq Fortran extension C-string allows certain C-style escape
sequences in char constants that end with a C. For example:
- Compaq Fortran inserts a leading blank when doing list-directed I/O
to an internal file. For example:
CHARACTER*10 C
WRITE(C,*) 'FOO' ! C = ' FOO'
|
- Compaq Fortran 77 and Compaq Fortran produce different output a
real value whose data magnitude is 0 with a G field descriptor. For
example:
X = 0.0
WRITE(*,100) X ! Compaq Fortran 77 prints 0.0000E+00
100 FORMAT(G12.4) ! Compaq Fortran prints 0.000
|
- Compaq Fortran does not allow certain intrinsics (such as SQRT) in
constant expressions for array bounds. For example:
- Compaq Fortran 77 returns UNKNOWN while Compaq Fortran returns
UNDEFINED when the ACCESS, BLANK, and FORM characteristics can not be
determined. For example:
INQUIRE(20,ACCESS=acc,BLANK=blk,FORM=form)
|
- Compaq Fortran does not allow an extraneous parenthesis in I/O
lists. For example:
write(*,*) ((i,i=1,1),(j,j=1,2))
|
- Compaq Fortran does not allow control characters within quoted
strings. For example, the assignment statement in the following program
is incorrect because it contains the character Ctrl/C.
character*5 c
c = 'ab^cef'
end
|
- Compaq Fortran does not recognize certain hexadecimal and octal
constants in DATA statements, such as those used in the following
program:
INTEGER I, J
DATA I/O20101/, J/Z20/
TYPE *, I, J
END
|
- Compaq Fortran, like Compaq Fortran 77, supports the use of
character literal constants (such as 'ABC' or "ABC") in numeric
contexts, where they are treated as Hollerith constants.
Compaq
Fortran 77 also allows character PARAMETER constants (typed and
untyped) and character constant expressions (using the // operator) in
numeric constants as an undocumented extension.
Compaq Fortran does
allow character PARAMETER constants in numeric contexts, but does not
allow character expressions. For example, the following is valid for
Compaq Fortran 77, but will result in an error message from Compaq
Fortran:
REAL*8 R
R = 'abc' // 'def'
WRITE (5,*) R
END
|
Compaq Fortran does allow PARAMETER constants:
PARAMETER abcdef = 'abc' // 'def'
REAL*8 R
R = abcdef
WRITE (5,*) R
END
|
- Compaq Fortran 77 namelist output formats character data delimited
with apostrophes. For example, consider:
CHARACTER CHAR4*4
NAMELIST /CN100/ CHAR4
CHAR4 = 'ABCD'
WRITE(20,CN100)
CLOSE (20)
|
This produces the following output file:
$CN100
CHAR4 = 'ABCD'
$END
|
This file is read by:
In contrast, Compaq Fortran produces the following output file by
default:
When read, this generates a
syntax error in NAMELIST input
error. To produce delimited strings from namelist output that can be
read by namelist input, use
DELIM="'"
in the OPEN statement of a Compaq Fortran program.
For More Information:
- On argument passing between Compaq Fortran and Compaq Fortran 77
for Compaq Tru64 UNIX systems, see Section A.5.
- On compatibility between Compaq Fortran for Compaq Tru64 UNIX or
Linux Alpha systems and Compaq Fortran on OpenVMS systems, see
Section A.4.
- On the Compaq Fortran language, see the Compaq Fortran Language Reference Manual.
A.2.3 Improved Compaq Fortran Compiler Diagnostic Detection
The following language features are detected or interpreted differently
by Compaq Fortran and Compaq Fortran 77:
- The Compaq Fortran compiler enforces the constraint that the
"nlist" in an EQUIVALENCE statement must contain at least two
variables. For example:
EQUIVALENCE (X) ! Incorrect
EQUIVALENCE (Y,Z) ! Correct
|
- The Compaq Fortran compiler enforces the constraint that entry
points in a SUBROUTINE must not be typed. For example:
SUBROUTINE ABCXYZ(I)
REAL ABC
I = I + 1
RETURN
ENTRY ABC ! Incorrect
BAR = I + 1
RETURN
ENTRY XYZ ! Correct
I = I + 2
RETURN
END SUBROUTINE
|
- The Compaq Fortran compiler enforces the constraint that a type
must appear before each list in an IMPLICIT statement. For example:
IMPLICIT REAL (A-C), (D-H) ! Incorrect
IMPLICIT REAL (O-S), REAL (T-Z) ! Correct
|
- The Compaq Fortran language disallows passing mismatched actual
arguments to intrinsics with corresponding integer formal arguments.
For example:
R = REAL(.TRUE.) ! Incorrect
R = REAL(1) ! Correct
|
- The Compaq Fortran compiler enforces the constraint that a simple
list element in an I/O list must be a variable or an expression. For
example:
READ (10,100) (I,J,K) ! Incorrect
READ (10,100) I,J,K ! Correct
|
- The Compaq Fortran compiler enforces the constraint that if two
operators are consecutive, the second operator must be a plus or a
minus. For example:
I = J -.NOT.K ! Incorrect
I = J - (.NOT.K) ! Correct
|
- The Compaq Fortran compiler enforces the constraint that character
entities with a length greater than 1 cannot be initialized with a bit
constant in a DATA statement. For example:
CHARACTER*1 C1
CHARACTER*4 C4
DATA C1/'FF'X/ ! Correct
DATA C4/'FFFFFFFF'X/ ! Incorrect
|
- The Compaq Fortran compiler enforces the requirement that edit
descriptors in the FORMAT statement must be followed by a comma or
slash separator. For example:
1 FORMAT (SSF4.1) ! Incorrect
2 FORMAT (SS,F4.1) ! Correct
|
- The Compaq Fortran compiler enforces the constraint that the number
and types of actual and formal statement function arguments must match
(such as incorrect number of arguments). For example:
CHARACTER*4 C,C4,FUNC
FUNC()=C4
C=FUNC(1) ! Incorrect
C=FUNC() ! Correct
|
- The Compaq Fortran compiler detects the use of a format of the form
Ew.dE0 at compile time. For example:
1 format(e16.8e0) ! Compaq Fortran detects error at compile time
write(*,1) 5.0 ! Compaq Fortran 77 compiles but an output
! conversion error occurs at run time
|
- Compaq Fortran detects passing of a statement function to a
routine. For example:
foo(x) = x * 2
call bar(foo)
end
|
- The Compaq Fortran compiler enforces the constraint that a branch
to a statement shared by more than one DO statements must occur from
within the innermost loop. For example:
DO 10 I = 1,10
IF (L1) GO TO 10 ! Incorrect
DO 10 J = 1,10
IF (L2) GO TO 10 ! Correct
10 CONTINUE
|
- The Compaq Fortran compiler enforces the constraint that a file
must contain at least one program unit. For example, a source file
containing only comment lines results in an error at the last line
(end-of-file).
The Compaq Fortran 77 compiler compiles files
containing less than one program unit.
- The Compaq Fortran compiler correctly detects misspellings of the
ASSOCIATEVARIABLE keyword to the OPEN statement. For example:
OPEN(1,ASSOCIATEVARIABLE = I) ! Correct
OPEN(2,ASSOCIATEDVARIABLE = J) ! Incorrect (extra D)
|
- The Compaq Fortran language enforces the constraint that the result
of an operation is determined by the data types of its operands. For
example:
INTEGER*8 I8
I8 = 2147483647 + 1 ! Incorrect. Produces less accurate
! INTEGER*4 result
I8 = 2147483647_8 + 1_8 ! Correct
|
- The Compaq Fortran compiler enforces the constraint that an object
can be typed only once. Compaq Fortran 77 issues a warning message and
uses the first type. For example:
LOGICAL B,B ! Incorrect (B multiply declared)
|
- The Compaq Fortran compiler enforces the constraint that certain
intrinsic procedures defined by the Fortran 95/90 standards cannot be
passed as actual arguments. For example, Compaq Fortran 77 allows most
intrinsic procedures to be passed as actual arguments, but the Compaq
Fortran compiler only allows those defined by the Fortran 95/90
standards (issues an error message).
Consider the following program:
program tstifx
intrinsic ifix,int,sin
call a(ifix)
call a(int)
call a(sin)
stop
end
subroutine a(f)
external f
integer f
print *, f(4.9)
return
end
|
The IFIX and INT intrinsic procedures cannot be passed as actual
arguments (the compiler issues an error message). However, the SIN
intrinsic is allowed to be passed as an actual argument by the Fortran
95/90 standards.
- Compaq Fortran reports character truncation with an error-level
message, not as a warning.
The following program produces an error
message during compilation with Compaq Fortran, whereas Compaq Fortran
77 produces a warning message:
INIT5 = 'ABCDE'
INIT4 = 'ABCD'
INITLONG = 'ABCDEFGHIJKLMNOP'
PRINT 10, INIT5, INIT4, INITLONG
10 FORMAT (' ALL 3 VALUES SHOULD BE THE SAME: ' 3I)
END
|
- If your code invokes Compaq Fortran intrinsic procedures with the
wrong number of arguments or an incorrect argument type, Compaq Fortran
reports this with an error-level message, not with a warning. Possible
causes include:
- A Compaq Fortran intrinsic has been added with the same name as a
user-defined subprogram and the user-defined subprogram needs to be
declared as EXTERNAL.
- An intrinsic that is an extension to an older Fortran standard is
incompatible with a newer standard-conforming intrinsic (for example,
the older RAN function that accepted two arguments).
The following program produces an error message during compilation
with Compaq Fortran, whereas Compaq Fortran 77 produces a warning
message:
INTEGER ANOTHERCOUNT
ICOUNT=0
100 write(6,105) (ANOTHERCOUNT(ICOUNT), INT1=1,10)
105 FORMAT(' correct if print integer values 1 through 10' /10I7)
Q = 1.
R = .23
S = SIN(Q,R)
WRITE (6,110) S
110 FORMAT(' CORRECT = 1.23 RESULT = ',f8.2)
END
!
INTEGER FUNCTION ANOTHERCOUNT(ICOUNT)
ICOUNT=ICOUNT+1
ANOTHERCOUNT=ICOUNT
RETURN
END
REAL FUNCTION SIN(FIRST, SECOND)
SIN = FIRST + SECOND
RETURN
END
|
- Compaq Fortran reports missing commas in FORMAT descriptors with an
error-level message, not as a warning.
The following program
produces an error message during compilation with Compaq Fortran,
whereas Compaq Fortran 77 produces a warning message:
LOGICAL LOG/111/
TYPE 1,LOG
1 FORMAT(' '23X,'LOG='O12)
END
|
In the preceding example, the correct coding (adding the missing
comma) for the FORMAT statement is:
1 FORMAT(' ',23X,'LOG='O12)
|
- Compaq Fortran generates an error when it encounters a 1-character
source line containing a Ctrl/Z character, whereas Compaq Fortran 77
allows such a line (which is treated as a blank line).
- Compaq Fortran detects the use of a character variable within
parentheses in an I/O statement. For example:
CHARACTER*10 CH/'(I5)'/
INTEGER I
READ CH,I ! Acceptable
READ (CH),I ! Generates error message, interpreted as an internal READ
END
|
- Compaq Fortran evaluates the exponentiation operator at compile
time only if the exponent has an integer data type. Compaq Fortran 77
evaluates the exponentiation operator even when the exponent does not
have an integer data type. For example:
PARAMETER ( X = 4.0 ** 1.1)
|
- Compaq Fortran detects an error when evaluating constants
expressions that result in an NaN or Infinity exceptional value, while
Compaq Fortran 77 allows such expressions. For example:
PARAMETER ( X = 4.0 / 0.0 )
|
- Compaq Fortran reports a warning error message when the same
variable is initialized more than once. Compaq Fortran 77 allows
multiple initializations of the same variable without a warning. For
example:
integer i
data i /1/
data i /2/
write (*,*) i
stop
end
|
For More Information:
- On passing arguments and returning function values between
Compaq Fortran and Compaq Fortran 77, see Section A.5.
- On Compaq Fortran procedure calling and argument passing, see
Section 11.1.
- On compatibility between Compaq Fortran for Compaq Tru64 UNIX
systems and Compaq Fortran 77 on OpenVMS systems, see Section A.4.
- On the Compaq Fortran language, see the Compaq Fortran Language Reference Manual.
A.2.4 Compiler Command-Line Differences
Compaq Fortran 77 (
f77
command) and Compaq Fortran (
f90
command) share most of the same command-line options. The following
options are provided only by Compaq Fortran 77 (not by Compaq Fortran):
-
-assume backslash
-
-f77
-
-ident
-
-show xref
(same as
-cross_reference
)
-
-stand keyword
-
-warn informational
-
-warn nounreachable
The following options are provided only by Compaq Fortran (not by
Compaq Fortran 77):
-
-align recnbyte
-
-annotations
-
-assume buffered_io
-
-assume gfullpath
-
-assume minus0
-
-f77rtl
-
-fixed
-
-free
-
-fpconstant
-
-fuse_xref
(TU*X ONLY)
-
-hpf
(TU*X ONLY) and associated HPF parallel
options, including
-assume bigarrays
,
-assume nozsize
,
-nearest_neighbor
,
-nohpf_main
,
-show hpf
, and
-warn hpf
-
-intconstant
-
-ladebug
-
-module
-
-mp
(TU*X ONLY)
-
-omp
(TU*X ONLY) and assorted OpenMP parallel
options including
-assume pthreads_lock
and
-check omp_bindings
-
-std
(performs Fortran 95/90 standards checking, whereas the Compaq Fortran
77
-stand keyword
performs FORTRAN 77 and NTT MIA standards checking)
-
-warn granularity
The
f77
command by default executes the Compaq Fortran 90 compiler and uses the
various
DECF90_
environment variables. To execute the Compaq Fortran 77 compiler, use
the
f77
command with the
-old_f77
option. This option must be the first text on the command line after
f77
.
A.3 Language Compatibility with Compaq Visual Fortran
The following language features found in Compaq Visual Fortran (and
Microsoft Fortran Powerstation Version 4) are now supported by Compaq
Fortran:
- # Constants. Constants using a base other than 10.
- C Strings. NULL terminated strings contain C-style escape sequences.
- Conditional Compilation And Metacommand Expressions ($define,
$undefine, $if, $elseif, $else, $endif).
- $FREEFORM, $NOFREEFORM, $FIXEDFORM. Source file format.
- $INTEGER, $REAL. Selects size.
- $FIXEDFORMLINESIZE. Line length for fixed form source.
- $STRICT, $NOSTRICT. F90 conformance.
- $PACK. Structure packing.
- $ATTRIBUTES ALIAS. External name for a subprogram or common block.
- $ATTRIBUTES C, STDCALL. Calling and naming conventions.
- $ATTRIBUTES VALUE, REFERENCE. Calling conventions.
- \ Descriptor. Prevents writing an end-of-record mark.
- Ew.dDe and Gw.dDe Edit Descriptors. Similar to Ew.dEe and Gw.dEe.
- 7200 Character Statement Length.
- Free form infinite line length.
- $DECLARE and $NODECLARE == IMPLICIT NONE.
- $ATTRIBUTES EXTERN. Variable allocated in another source file.
- $ATTRIBUTES VARYING. Variable number of arguments.
- $ATTRIBUTES ALLOCATABLE. Allocatable array.
- Mixing Subroutines/Functions in Generic Interfaces.
- $MESSAGE. Output message during compilation.
- $LINE == C's #line.
- INT1. Converts to one byte integer by truncating.
- INT2. Converts to two byte integer by truncating.
- INT4. Converts to four byte integer by truncating.
- COTAN. Returns cotangent.
- DCOTAN. Returns double precision cotangent.
- IMAG. Returns the imaginary part of complex number.
- IBCHNG. Reverses value of bit.
- ISHA. Shifts arithmetically left or right.
- ISHC. Performs a circular shift.
- ISHL. Shifts logically left or right.
A.4 Compatibility with Compaq Fortran 77 and Compaq Fortran for OpenVMS Systems
This section provides compatibility information for those who:
- Port Compaq Fortran 77 and Compaq Fortran applications from OpenVMS
systems to Compaq Fortran on Compaq Tru64 UNIX or Linux Alpha Systems
- Design Compaq Fortran applications to run on multiple platforms,
including OpenVMS and Compaq Tru64 UNIX or Linux Alpha systems
If your primary concern is the design and development of Compaq Fortran
applications for only Compaq Tru64 UNIX (or other U*X) systems,
consider skipping this section.
This section discusses the following topics:
- Compaq Fortran 77 extensions for OpenVMS systems that are not
supported by this version of Compaq Fortran 77 or Compaq Fortran on
Compaq Tru64 UNIX or Linux Alpha Systems ( Section A.4.1)
- Porting Compaq Fortran data files from an OpenVMS system to a
Compaq Tru64 UNIX or Linux Alpha system ( Section A.4.2)
- Nonnative VAX floating-point representations, provided for those
converting unformatted OpenVMS floating-point data ( Section A.4.3)
A.4.1 Language Features Specific to Compaq Fortran 77 and Compaq Fortran for OpenVMS Systems
Some extensions to the FORTRAN-77 standard provided by Compaq Fortran
77 and Compaq Fortran for OpenVMS Systems are specific to the OpenVMS
operating system, VAX architecture, or certain products on OpenVMS
systems. Such extensions are not included in Compaq Fortran 77 or
Compaq Fortran on Compaq Tru64 UNIX or Linux Alpha Systems.
For information on language compatibility between Compaq Fortran and
Compaq Fortran 77 without regard to operating system or architecture
differences, see Section A.2.
Compaq Fortran 77 and Compaq Fortran products for OpenVMS systems
include:
- Compaq Fortran Version 7.4 for OpenVMS Alpha Systems
- Compaq Fortran 77 Version 7.4 for OpenVMS Alpha Systems
- Compaq Fortran 77 Version 6.6 for OpenVMS VAX Systems (previously
called VAX FORTRAN)
Unless otherwise noted, the following list describes the Compaq Fortran
77 extensions in Compaq Fortran 77 and/or Compaq Fortran for OpenVMS
systems that are not supported by Compaq Fortran for Compaq
Tru64 UNIX Systems:
- DICTIONARY statement
The DICTIONARY and related support for the
CDD/Repository (common data dictionary) product are not provided by
Compaq Fortran or Compaq Fortran 77 for Compaq Tru64 UNIX Systems.
- Support for indexed sequential files
I/O statement specifiers
for indexed file (keyed access) record I/O using OpenVMS OPEN and
INQUIRE statement specifiers are not provided by Compaq Fortran or
Compaq Fortran 77 for Compaq Tru64 UNIX or Linux Systems, as follows:
ACCESS=
'
KEYED
'
|
EXTENDSIZE
|
INITIALSIZE
|
KEY
|
NOSPANBLOCKS
|
ORGANIZATION=
'
INDEXED
'
|
SHARED
|
|
- FORSYSDEF symbol definitions for OpenVMS systems
The parameter
definitions of run-time messages found in FORSYSDEF.TLB library module
FORIOSDEF on OpenVMS systems are provided in the file
/usr/include/foriosdef.f
(see Section 8.2.2) on Compaq Tru64 UNIX Systems. On Compaq Tru64 UNIX
and Linux Alpha systems, Compaq Fortran and Compaq Fortran 77 provides
jacket routines to simplify calling system calls and library routines
(see Chapter 12).
- The INCLUDE statement option of including text from text libraries.
On Compaq Tru64 UNIX and Linux Alpha systems, OpenVMS text
libraries are not supported.
- The %DESCR built-in function (for OpenVMS character descriptors).
On Compaq Tru64 UNIX and Linux Alpha systems, character data is
passed by address and hidden length. For information about calling or
being called by procedures written in other languages, see
Chapter 11.
- Run-time default I/O units spelled as FOR0nn.dat, SYS$INPUT, and so
on
In Compaq Fortran and Compaq Fortran 77 on Compaq Tru64 UNIX and
Linux Alpha systems, these are environment variables FORTn,
stdin
,
stdout
, and so forth (see Section 7.5).
- VAX floating-point formats and related selection of the
floating-point format in memory
Only IEEE floating-point formats
are supported in memory on Compaq Tru64 UNIX Alpha systems. (Compaq
proprietary VAX floating-point formats are not supported in memory.)
You can request conversion of unformatted files containing VAX
floating-point formats into the appropriate IEEE memory format during
record I/O (see Chapter 10).
On OpenVMS VAX systems, you
specify the floating-point format to be used in memory with either the
option [NO]G_FLOATING in the OPTIONS statement or the qualifier
/[NO]G_FLOATING on the FORTRAN command line.
On OpenVMS Alpha
systems, you specify the floating-point format to be used in memory
using the /FLOAT qualifier on the FORTRAN command line.
- Stream record format differences
With Compaq Fortran 77 and Compaq Fortran for OpenVMS systems, the
Stream record type is delimited by CR-LF character sequence (carriage
control and line feed characters). In Compaq Fortran for Compaq Tru64
UNIX systems, the Stream record type uses no delimiters.
For more
information on compatible record types, see Section A.4.2.
- Other differences related to the OpenVMS operating system and the
Compaq Tru64 UNIX and Linux operating systems
When parsing file specifications for the OPEN, INQUIRE, and INCLUDE
statements, keep in mind that file names are case-sensitive on Compaq
Tru64 UNIX and Linux systems and that OpenVMS file specification syntax
differs from pathname syntax.
For the INCLUDE statement, the
network node names (terminated by "::"), logical names
(usually terminated by ":"), and other OpenVMS file
specification components are not recognized. Instead, the INCLUDE
statement should specify a pathname, possibly with an absolute
directory path.
- The OpenVMS operating system provides various system services (SYS$
prefix) and run-time library routines (LIB$, SMG$, and other prefixes)
that are not supported on Compaq Tru64 UNIX and Linux systems. Compaq
Tru64 UNIX systems support system calls and library routines with
similar functions (but different names).
To make programs more
portable to other operating systems, wherever possible you should use
standard-conforming Compaq Fortran intrinsic routines in place of
routines specific to a particular operating system.
For more
information on specifying files, see Section 7.5.3.
The following language and VAX architecture features are associated
only with Compaq Fortran 77 on OpenVMS VAX Systems (previously called
VAX FORTRAN) and are not supported by Compaq Fortran for Compaq Tru64
UNIX and Compaq Fortran for Linux Alpha systems:
- Directed decomposition features and CPAR$ directives for parallel
processing
CPAR$ directives are treated as comments (ignored).
Parallel processing capabilities (appropriate
f90
options, OpenMP, Compaq Fortran parallel, and HPF data mapping
directives) are provided by Compaq Fortran.
- OPTIONS statement options /BLAS, /NOBLAS, /CHECK=ALIGNMENT,
/CHECK=NOALIGNMENT, /CHECK=ASSERTION, /CHECK=NOASSERTION, /G_FLOAT, and
/NOG_FLOAT
You can specify some of these options by using the
corresponding
f90
command-line options. The OPTIONS statement is treated as a comment
(ignored).
- CDEC$ performance directives ASSERT and NOVECTOR are treated as
comments (ignored).
- The REAL*16 floating-point data type
On VAX systems, REAL*16
data is in H_float format. On Alpha systems, REAL*16 data is in the
native IEEE style X_float; so are both halves (real and imaginary) of
COMPLEX*32 data.
- The following subroutines for PDP-11 compatibility:
ASSIGN
CLOSE
ERRSET
|
ERRTST
FDBSET
IRAD50
|
RAD50
R50ASC
USEREX
|
- Radix-50 constants and character set
- The BLAS routines
Similar basic linear algebra routines are
provided in the Compaq Extended Mathematical Library (CXML) product
(see Section 5.1.1).
The following language and VAX architecture features are interpretation
differences between Compaq Fortran and Compaq Fortran 77 on Alpha
systems and Compaq Fortran 77 on OpenVMS VAX Systems (previously called
VAX FORTRAN):
- Random number generator (RAN)
The RAN function (one argument)
generates a different pattern of numbers in Compaq Fortran than in
Compaq Fortran 77 on OpenVMS VAX Systems for the same random seed.
Compaq Fortran and Compaq Fortran 77 use the same random seed. (The RAN
and RANDU functions are provided for Compaq Fortran 77 on OpenVMS VAX
Systems compatibility. See Compaq Fortran Language Reference Manual.)
- Hollerith constants in formatted I/O statements
Compaq Fortran
77 on OpenVMS VAX Systems and Compaq Fortran behave differently if
either of the following occurs:
- Two different I/O statements refer to the same CHARACTER PARAMETER
constant as their format specifier. For example:
CHARACTER*(*) FMT2
PARAMETER (FMT2='(10Habcdefghij)')
READ (5, FMT2)
WRITE (6, FMT2)
|
- Two different I/O statements use the identical character constant
as their format specifier. For example:
READ (5, '(10Habcdefghij)')
WRITE (6, '(10Habcdefghij)')
|
In Compaq Fortran 77 for OpenVMS VAX Systems, the parameter value
obtained by the READ statement is modified. The parameter value
modified by the READ statement is used as the output of the WRITE
statement (FMT2 is ignored). However, in Compaq Fortran, the parameter
value is not modified (the parameter value read by the READ
statement has no effect on the parameter value written by the WRITE
statement.)
For More Information:
- On language compatibility information about Compaq Fortran for
Compaq Tru64 UNIX systems and Compaq Fortran 77, see Section A.2.2.
- On language interpretation differences between Compaq Fortran for
Compaq Tru64 UNIX systems and Compaq Fortran 77, see Section A.2.3.
- About the Compaq Fortran language, see the Compaq Fortran Language Reference Manual.
A.4.2 OpenVMS Data Porting Considerations
When porting data between systems running the Compaq Tru64 UNIX and
Linux Alpha operating systems and systems running the OpenVMS operating
system, the file formats and the floating-point representations may
differ.
The file and record formats of Compaq Fortran 77 on Compaq Tru64 UNIX
systems are compatible with Compaq Fortran on Compaq Tru64 UNIX and
Linux Alpha systems; they share the same language run-time I/O
environment (see Chapter 7).
OpenVMS Fortran1 files containing only character, integer,
or logical data do not need field-by-field conversion, but the record
types must match. The segmented record type is the same on OpenVMS
Fortran systems and Compaq Fortran on Compaq Tru64 UNIX or Linux Alpha
systems. Certain other record types, such as variable-length records,
differ between OpenVMS systems and Compaq Fortran on Compaq Tru64 UNIX
or Linux Alpha systems.
Table A-2 summarizes the OpenVMS Fortran record types and their
equivalent record types in Compaq Fortran on Compaq Tru64 UNIX or Linux
Alpha systems.
Table A-2 Equivalent Record Types for OpenVMS Fortran and Compaq Fortran on Compaq Tru64 UNIX or Linux Alpha Systems
OpenVMS Fortran Record Type |
Compaq Tru64 UNIX Fortran Record Type |
Comments |
Fixed-length
|
None
|
Equivalent (must be copied correctly) if you use sequential access and
you specify the
-vms
option when compiling the Compaq Fortran
file. Otherwise, convert the file to a different record type.
|
Variable-length
|
None
|
Not equivalent.
Convert the file to a different record type.
|
Segmented
|
Segmented
|
Equivalent (must be copied correctly). Segmented data files
can contain formatted or unformatted data.
|
Stream
|
None
|
Not equivalent. Convert the file to
a different record type.
|
Stream_CR
|
Stream_CR
|
Equivalent (must be copied correctly).
|
Stream_LF
|
Stream_LF
|
Equivalent (must be copied correctly).
|
A.4.2.1 Matching Record Types
To match record types, there are several options:
- For the Segmented, Stream_CR, and Stream_LF record types, you do
not need to convert the files.
- For fixed-length records where you will only use sequential access,
use the
-vms
option when compiling the Compaq Fortran program that will access the
OpenVMS Fortran files. For fixed-length records where you will use
direct access, convert the files to a different record format.
- For incompatible record types, convert the files by writing a
OpenVMS Fortran or C conversion program or by using the ANALYZE/RMS/FDL
and CONVERT/FDL (or EXCHANGE/FDL) commands for an appropriate file. For
instance, convert the OpenVMS Fortran file to the segmented record type.
A.4.2.2 Copying Files
Equivalent record types must be copied carefully to preserve control
information and record characteristics. For example:
- Do not use the ASCII transfer mode for binary files.
- Segmented files must be copied in a manner that preserves record
length information.
To transfer (copy) the files, choose one of the following methods:
- From an NFS mounted disk, use the
cp
command (see cp(1)).
- Perform a DECnet copy from a Compaq Tru64 UNIX or Linux Alpha
system running the appropriate optional network software using
dcp
(see dcp(8)). Use the
dcp -i
option when you want to preserve record format information.
- Perform a copy from a Compaq Tru64 UNIX or Linux Alpha system with
rcp
, possibly by using an intermediate node running the appropriate
optional network software when using a version of the OpenVMS operating
system that does not support a compatible network protocol (optional
product).
- Use
ftp
from a Compaq Tru64 UNIX or Linux Alpha system to copy a file between a
Compaq Tru64 UNIX or Linux Alpha system and an OpenVMS system. Use the
binary
or
ascii
command to set the mode before you copy (get or put) the file. For
example, use the ftp
binary
command before copying an unformatted file (such as the segmented
record type).
- Perform a DECnet copy from an OpenVMS system with the EXCHANGE
command with the /NETWORK and /TRANSFER=BLOCK qualifiers with a Compaq
Tru64 UNIX system. To convert the file to Stream_LF format during the
copy operation, use /TRANSFER=(BLOCK,RECORD_SEPARATOR=LF) instead of
/TRANSFER=BLOCK, or specify the /FDL qualifier to the EXCHANGE command
to specify the record type.
In addition to using the correct record type and carefully transferring
the files, the data inside unformatted records may need to be
converted. OpenVMS Fortran data files that contain VAX binary
floating-point data must be converted before they can be accessed by a
Compaq Fortran program. There are several methods:
- On an OpenVMS system, a Fortran program can convert files
containing unformatted data to files containing formatted data. Once
the files contain formatted data, they can be read by the appropriate
Compaq Fortran programs.
However, converting unformatted data to formatted data may result in a
loss of accuracy for unformatted floating-point data.
- On an OpenVMS VAX system, a Compaq Fortran 77 program can read and
write files containing unformatted data by using the Compaq Fortran
conversion capabilities described in DEC Fortran User Manual for OpenVMS VAX Systems.
- On an OpenVMS Alpha system, a Fortran program can read and write
files containing unformatted data by using the Compaq Fortran
conversion capabilities described in the Compaq Fortran User Manual
for OpenVMS Alpha Systems.
A Compaq Fortran 77 for OpenVMS
Alpha Systems program can also use the CVT$CONVERT_FLOAT routine to
convert individual floating-point fields.
- On a Compaq Tru64 UNIX or Linux Alpha system, a Compaq Fortran
program can read and write files containing unformatted data using the
Compaq Fortran conversion capabilities described in Section 10.3. A
program using the Compaq Fortran conversion capabilities can also
convert such data to other formats.
If you need to convert unformatted floating-point data, keep in mind
that Compaq Fortran 77 for OpenVMS VAX programs (VAX hardware) store
the following:
- REAL*4 or COMPLEX*8 data in VAX F_float format
- REAL*8 or COMPLEX*16 data in either VAX D_float or G_float format
- REAL*16 data in VAX H_float format
In contrast, Compaq Fortran programs running on the Compaq Tru64 UNIX
or Linux Alpha operating system on Alpha hardware store the following:
- REAL*4 or COMPLEX*8 data in IEEE S_float format
- REAL*8 or COMPLEX*16 data in IEEE T_float format
- REAL*16 data or COMPLEX*32 data in native (IEEE style) X_float
format
Compaq Fortran 77 and Compaq Fortran for OpenVMS Alpha programs store
floating-point data in the format specified by the /FLOAT qualifier:
- REAL*4 or COMPLEX*8 data in VAX F_float or IEEE S_float format
- REAL*8 or COMPLEX*16 data in VAX D_float, VAX G_float, or IEEE
T_float format
- REAL*16 data or COMPLEX*32 data in native (IEEE style) X_float
format
For information on Compaq Fortran data types, see Chapter 9.
For More Information:
- On Compaq Fortran I/O, see Chapter 7.
- About the Compaq Fortran language, see the Compaq Fortran Language Reference Manual.
A.4.3 Nonnative VAX Floating-Point Representations
This section provides information about VAX floating-point data
formats. You can convert unformatted files from OpenVMS systems by
using the methods described in Chapter 10.
On OpenVMS VAX systems, single-precision data (such as REAL*4) is
stored in VAX F_float format and double-precision data (such as REAL*8)
data can be stored in either VAX D_float or VAX G_float formats,
depending on whether the /G_FLOATING qualifier was specified on the
FORTRAN command line (see the DEC Fortran User Manual for OpenVMS VAX Systems).
On OpenVMS Alpha systems, you can specify the floating-point format in
memory by using the /FLOAT qualifier (see the DEC Fortran User Manual for OpenVMS AXP Systems).
Single-precision data on OpenVMS Alpha systems is stored in either VAX
F_float or IEEE S_float formats; double-precision data can be stored in
VAX D_float, VAX G_float, or IEEE T_float formats.
REAL*16 (extended precision) data is always stored in IEEE style
X_float format on Alpha systems.
With VAX floating-point data types, the binary radix point is to the
left of the most-significant bit.
A.4.3.1 VAX F_float REAL (KIND=4) or REAL*4
Intrinsic REAL (KIND=4) or REAL*4 F_float data occupies four contiguous
bytes. Bits are labeled from the right, 0 through 31, as shown in
Figure A-1.
Figure A-1 VAX F_float REAL (KIND=4) or REAL*4 Representation
The form of REAL (KIND=4) or REAL*4 F_float data is sign magnitude,
where:
- Bit 15 is the sign bit (0 for positive numbers, 1 for negative
numbers).
- Bits 14:7 are a binary exponent in excess 128 notation (binary
exponents from --127 to 127 are represented by binary 1 to 255).
- Bits 6:0 and 31:16 are a normalized 24-bit fraction with the
redundant most significant fraction bit not represented.
When converting unformatted F_float data from an OpenVMS system, the
approximate range is 0.293873588E--38 to 1.7014117E38. The precision is
approximately one part in 2**23, typically seven decimal digits.
A.4.3.2 VAX G_float REAL (KIND=8) or REAL*8
Intrinsic REAL (KIND=8) or REAL*8 (same as DOUBLE PRECISION) G_float
data occupies eight contiguous bytes. The bits are labeled from the
right, 0 through 63, as shown in Figure A-2.
Figure A-2 VAX G_float REAL (KIND=8) or REAL*8 Representation
The form of REAL (KIND=8) or REAL*8 G_float data is sign magnitude,
where:
- Bit 15 is the sign bit (0 for positive numbers, 1 for negative
numbers).
- Bits 14:4 are a binary exponent in excess 1024 notation (binary
exponents from --1023 to 1023 are represented by the binary 1 to 2047).
- Bits 3:0 and 63:16 are a normalized 53-bit fraction with the
redundant most significant fraction bit not represented.
When converting unformatted G_float data from an OpenVMS system, the
approximate range is 0.5562684646268004D--308 to
0.89884656743115785407D308. The precision of G_float data is
approximately one part in 2**52, typically 15 decimal digits.
A.4.3.3 VAX D_float REAL (KIND=8) or REAL*8
Intrinsic REAL (KIND=8) or REAL*8 (same as DOUBLE PRECISION) D_float
data occupies eight contiguous bytes. Bits are labeled from the right,
0 through 63, as shown in Figure A-3.
Figure A-3 VAX D_float REAL (KIND=8) or REAL*8 Representation
The form of REAL (KIND=8) or REAL*8 D_float data is identical to an
F_float real number, except for an additional 32 low-significance
fraction bits. The exponent conventions and approximate range of values
are the similar to those for F_float.
When converting unformatted D_float data from an OpenVMS system, the
approximate range is 0.2938735877055719D--38 to 1.70141183460469229D38.
The precision is approximately one part in 2**55, typically 16 decimal
digits.
A.4.3.4 VAX F_float COMPLEX (KIND=4) or COMPLEX*8
Intrinsic COMPLEX (KIND=4) or COMPLEX*8 (single-precision COMPLEX) data
in VAX F_float format occupies eight contiguous bytes containing a pair
of REAL*4 values. The low-order four bytes contain REAL*4 data that
represents the real part of the complex number. The high-order four
bytes contain REAL (KIND=4) or REAL*4 data that represents the
imaginary part of the complex number. Figure A-4 shows a COMPLEX*8
number in F_float format.
Figure A-4 VAX F_float COMPLEX (KIND=4) or COMPLEX*8 Representation
The limits for REAL (KIND=4) or REAL*4 apply to the two separate real
and imaginary parts of a COMPLEX (KIND=4) or COMPLEX*8 number. Like
REAL (KIND=4) or REAL*4 numbers, the sign bit representation is 0
(zero) for positive numbers and 1 for negative numbers.
A.4.3.5 VAX G_float and D_float COMPLEX (KIND=8) or COMPLEX*16
Intrinsic COMPLEX (KIND=8) or COMPLEX*16 (same as DOUBLE COMPLEX) data
occupies 16 contiguous bytes containing a pair of REAL*8 or REAL
(KIND=8) values. COMPLEX (KIND=8) or COMPLEX*16 data from an OpenVMS
system is in one of the following REAL*8 or REAL (KIND=8) formats:
- VAX G_float format
- VAX D_float format
The low-order eight bytes contain REAL (KIND=8) or REAL*8 data that
represents the real part of the complex data. The high-order eight
bytes contain REAL (KIND=8) or REAL*8 data that represents the
imaginary part of the complex data, as shown in Figure A-5 (for
G_float) and Figure A-6 (for D_float).
Figure A-5 VAX G_float COMPLEX (KIND=8) or COMPLEX*16 Representation
Figure A-6 VAX D_float COMPLEX (KIND=8) or COMPLEX*16 Representation
The limits for REAL (KIND=8) or REAL*8 apply to the two separate real
and imaginary parts of a COMPLEX (KIND=8) or COMPLEX*16 number. Like
REAL (KIND=8) or REAL*8 numbers, the sign bit representation is 0
(zero) for positive numbers and 1 for negative numbers.
A.4.3.6 VAX H_float Representation
The REAL (KIND=16) or REAL*16 VAX H_float data format is used only on
OpenVMS VAX systems. On Alpha systems, REAL (KIND=16) extended
precision data is always stored in Alpha X_float format.
With VAX floating-point data types, the binary radix point is to the
left of the most-significant bit.
As shown in Figure A-7, REAL*16 H_float data is 16 contiguous bytes
starting on an arbitrary byte boundary. The bits are labeled from the
right, 0 through 127.
Figure A-7 VAX H_float REAL*16 Representation (VAX Systems)
The form of an H_float REAL*16 data is sign magnitude with bit 15 the
sign bit, bits 14:0 an excess 16384 binary exponent, and bits 127:16 a
normalized 113-bit fraction with the redundant most significant
fraction bit not represented.
The value of H_float data is in the approximate range 0.84*10**--4932
through 0.59*10**4932. The precision of H_float data is approximately
one part in 2**112 or typically 33 decimal digits.
For More Information:
- On converting unformatted data files, see Chapter 10.
- On native floating-point ranges, see Table 9-1.
Note
1 OpenVMS Fortran refers collectively
to VAX FORTRAN, Compaq Fortran 77 for OpenVMS Alpha Systems, and Compaq
Fortran 77 for OpenVMS VAX Systems
|
A.5 Calling Between Compaq Fortran 77 and Compaq Fortran
On Compaq Tru64 UNIX systems, you can call a Compaq Fortran 77
subprogram from Compaq Fortran or call a Compaq Fortran subprogram from
Compaq Fortran 77 (with a few exceptions). A Compaq Fortran 77
procedure and a Compaq Fortran procedure can also perform I/O to the
same unit number.
A.5.1 Argument Passing and Function Return Values
The recommended rules for passing arguments and function return values
between Compaq Fortran 77 and Compaq Fortran procedures are as follows:
- If possible, express the following Compaq Fortran features with the
Compaq Fortran 77 language:
- Function references
- CALL statements
- Function definitions
- Subroutine definitions
Avoid using Compaq Fortran language features not available in
Compaq Fortran 77. Since Compaq Fortran is a superset of Compaq Fortran
77, specifying the procedure interface using the Compaq Fortran 77
language helps ensure that calls between the two languages will succeed.
- Not all data types in Compaq Fortran have equivalent Compaq Fortran
77 data types. The following Compaq Fortran features should not be used
between Compaq Fortran and Compaq Fortran 77 procedures, because they
are not supported by Compaq Fortran 77:
- COMPLEX*32 data
- Derived-type (user-defined) data, which has no equivalent in Compaq
Fortran 77.
- Compaq Fortran data with the POINTER attribute, which has no
equivalent in Compaq Fortran 77. The pointer data type supported by
Compaq Fortran 77 is not equivalent to Compaq Fortran pointer data.
Because Compaq Fortran supports the pointer data type supported by
Compaq Fortran 77, you can use Compaq Fortran 77 pointer data types in
both Compaq Fortran and Compaq Fortran 77. (In some cases, you can
create Compaq Fortran 77 pointer data in a Compaq Fortran procedure
using the %LOC function.)
Compaq Fortran arrays with the POINTER
attribute are passed by array descriptor. A program written in Compaq
Fortran 77 needs to interpret the array descriptor format generated by
a Compaq Fortran 90 array with the POINTER attribute (see
Section 11.1.7).
- Compaq Fortran assumed-shape arrays.
Compaq Fortran assumed-shape arrays are passed by array descriptor. A
program written in Compaq Fortran 77 needs to interpret the array
descriptor format generated by a Compaq Fortran assumed-shape array
(see Section 11.1.7).
You can use Compaq Fortran record structures, which are supported
by Compaq Fortran 77 and Compaq Fortran as an extension to the Fortran
95/90 standards.
For more information on how Compaq Fortran handles
arguments and function return values, see Section 11.1.4.
- Make sure the sizes of INTEGER, LOGICAL, REAL, and COMPLEX
declarations match.
For example, Compaq Fortran declarations of
REAL (KIND=4) and INTEGER (KIND=4) match Compaq Fortran 77 declarations
of REAL*4 and INTEGER*4. For COMPLEX values, a Compaq Fortran
declaration of COMPLEX (KIND=4) matches a Compaq Fortran 77 declaration
of COMPLEX*8; COMPLEX (KIND=8) matches COMPLEX*16. Compaq Fortran 77
does not have COMPLEX*32 declarations.
Your source programs may
contain INTEGER, LOGICAL, REAL, or COMPLEX declarations without a kind
parameter (or size specifier). In this case, when compiling the Compaq
Fortran procedures (
f90
command) and Compaq Fortran 77 procedures (
f77
command), either omit the options or specify the equivalent options for
controlling the sizes of these declarations.
For more information
on these options (the same for
f90
and
f77
), see Section 3.53 for INTEGER and LOGICAL declarations,
Section 3.78 for REAL and COMPLEX declarations, and Section 3.34
for DOUBLE PRECISION declarations.
- Compaq Fortran uses the same argument-passing conventions as Compaq
Fortran 77 on Compaq Tru64 UNIX systems (see Section 11.1.4).
- You can return nearly all function return values from a Compaq
Fortran function to a calling Compaq Fortran 77 routine, with the
following exceptions:
- You cannot return Compaq Fortran pointer data from Compaq Fortran
to a Compaq Fortran 77 calling routine.
- You cannot return Compaq Fortran user-defined data types from a
Compaq Fortran function to a Compaq Fortran 77 calling routine.
Example A-1 and Example A-2 show passing an array from a
Compaq Fortran program to a Compaq Fortran 77 subroutine that prints
its value.
Example A-1 shows the Compaq Fortran program (file
array_to_f77.f90
). It passes the same argument as a target and a pointer. In both
cases, it is received by reference by the Compaq Fortran 77 subroutine
as a target (regular) argument. The interface block in Example A-1
is not needed, but does allow data type checking.
Example A-1 Compaq Fortran Program Calling a
Compaq Fortran 77 Subroutine |
! Pass arrays to f77 routine. File: array_to_f77.f90
! this interface block is not required, but must agree
! with actual procedure. It can be used for type checking.
interface ! Procedure interface block
subroutine meg(a)
integer :: a(3)
end subroutine
end interface
integer, target :: x(3)
integer, pointer :: xp(:)
x = (/ 1,2,3 /)
xp => x
call meg(x) ! Call f77 subroutine twice.
call meg(xp)
end
|
Example A-2 shows the Compaq Fortran 77 subprogram called by the
Compaq Fortran program (file
array_f77.f
).
Example A-2 Compaq Fortran 77 Subroutine
Called by a Compaq Fortran Program |
! Get array argument from F90. File: array_f77.f
subroutine meg(a)
integer a(3)
print *,a
end
|
These files (shown in Example A-1 and Example A-2) might be
compiled, linked, and run as follows:
% f77 -c array_f77.f
% f90 -o array_to_f77 array_to_f77.f90 array_f77.o
% array_to_f77
1 2 3
1 2 3
|
In Example A-1, because array a is not defined as a pointer in the
interface block, the Compaq Fortran pointer variable xp is passed as
target data by reference (address of the target data).
However, if the interface to the dummy argument had the POINTER
attribute, the variable xp would be passed by descriptor. This
descriptor would not work with the Compaq Fortran 77 program shown in
Example A-2.
For More Information:
- On how Compaq Fortran handles arguments and function return values,
see Section 11.1.4.
- On explicit interfaces, see the Compaq Fortran Language Reference Manual.
- On compatibility between the Compaq Fortran and Compaq Fortran 77
languages, see Appendix A.
- On other aspects of the Compaq Fortran language, see the
Compaq Fortran Language Reference Manual.
A.5.2 Using Data Items in Common Blocks
To make global data available across Compaq Fortran and Compaq Fortran
77 procedures, use common blocks.
Common blocks are supported by both Compaq Fortran 77 and Compaq
Fortran, but modules are not supported by Compaq Fortran 77. Some
suggestions about using common blocks follow:
- Use the same COMMON statement to ensure that the data
items match in order, type, and size.
If multiple Compaq Fortran
procedures will use the same common block, declare the data in a module
and reference that module with a USE statement where needed.
If
Compaq Fortran 77 procedures use the same common block as the Compaq
Fortran procedures and the common block is declared in a module,
consider modifying the Compaq Fortran 77 source code as follows:
- Replace the common block declaration with the appropriate USE
statement.
- Recompile the Compaq Fortran 77 source code with the
f90
command.
- Specify the same alignment characteristics with the
-align
option when compiling both Compaq Fortran procedures (
f90
command) and Compaq Fortran 77 procedures (
f77
command).
When compiling the source files with more than one
f90
or
f77
command, consistently use the
-align dcommons
or
-align commons
option. This naturally aligns data items in a common block and ensures
consistent format of the common block.
- Make sure the sizes of INTEGER, LOGICAL, REAL, and COMPLEX
declarations match.
For example, Compaq Fortran declarations of
REAL (KIND=4) and INTEGER (KIND=4) match Compaq Fortran 77 declarations
of REAL*4 and INTEGER*4. For COMPLEX values, a Compaq Fortran
declaration of COMPLEX (KIND=4) matches a Compaq Fortran 77 declaration
of COMPLEX*8; COMPLEX (KIND=8) matches COMPLEX*16. Fortran 77 does not
have COMPLEX*32 data.
Your source programs may contain INTEGER,
LOGICAL, REAL, or COMPLEX declarations without a kind parameter or size
specifier. In this case, either omit or specify the same options that
control the sizes of these declarations when compiling the procedures
with multiple commands (same rules as Section A.5.1).
A.5.3 I/O to the Same Unit Number
Compaq Fortran and Compaq Fortran 77 share the same run-time system, so
you can perform I/O to the same unit number with Compaq Fortran and
Compaq Fortran 77 procedures. For instance, a Compaq Fortran main
program can open the file, a Compaq Fortran 77 function can issue READ
or WRITE statements to the same unit, and the Compaq Fortran main
program can close the file.
For More Information:
- On the Compaq Fortran language, see the Compaq Fortran Language Reference Manual.
- On passing arguments, function return values, and the contents of
registers on Compaq Tru64 UNIX systems, see the Compaq Tru64 UNIX Calling Standard for Alpha Systems.
- On Compaq Fortran intrinsic data types, see Chapter 9.
- On Compaq Fortran I/O, see Chapter 7.