Previous | Contents | Index |
This appendix provides compatibility information between Compaq Fortran (Fortran 90/95) and Compaq Fortran 77 for OpenVMS Systems. It discusses the following topics:
Table A-1 summarizes the compatibility of Compaq Fortran (CF, which supports the Fortran 95, 90, 77, and 66 standards) and Compaq Fortran 77 (CF77) on multiple platforms (architecture/operating system pairs).
Compaq Fortran (CF) is available on Compaq OpenVMS Alpha Systems, Compaq Tru64 UNIX (formerly DIGITAL UNIX) Alpha systems, Linux Alpha systems, and as Compaq Visual Fortran (CVF) on Windows systems.
Compaq Fortran (CF), Compaq Visual Fortran (CVF), or Compaq Fortran 77 (CF77) for ... Systems | ||||||
---|---|---|---|---|---|---|
Language Feature | CF UNIX Alpha | CF Linux Alpha | CVF Windows x86 | CF OpenVMS Alpha | CF77 OpenVMS Alpha | CF77 OpenVMS VAX |
Linking against static and shared libraries | X | X | X | X | X | X |
Create code for shared libraries | X | X | X | X | X | X |
Recursive code support | X | X | X | X | X | X |
AUTOMATIC and STATIC statements | X | X | X | X | X | X |
STRUCTURE and RECORD declarations | X | X | X | X | X | X |
INTEGER*1, *2, *4 | X | X | X | X | X | X |
LOGICAL*1, *2, *4 | X | X | X | X | X | X |
INTEGER*8 and LOGICAL*8 | X | X | X | X | ||
REAL*4, *8 | X | X | X | X | X | X |
REAL*16 1 | X | X | X | X | X | |
COMPLEX*8, *16 | X | X | X | X | X | X |
COMPLEX*32 2 | X | X | X | X | ||
POINTER (CRAY-style) | X | X | X | X | X | X |
INCLUDE statements | X | X | X | X | X | X |
IMPLICIT NONE statements | X | X | X | X | X | X |
Data initialization in type declarations | X | X | X | X | X | X |
Automatic arrays | X | X | X | X | X | |
VOLATILE statements | X | X | X | X | X | X |
NAMELIST-directed I/O | X | X | X | X | X | X |
31-character names including $ and _ | X | X | X | X | X | X |
Source listing with machine code | X | X | X | X | X | X |
Debug statements in source | X | X | X | X | X | X |
Bit constants to initialize data and use in arithmetic | X | X | X | X | X | X |
DO WHILE and END DO statements | X | X | X | X | X | X |
Built-in functions %LOC, %REF, %VAL | X | X | X | X | X | X |
SELECT CASE construct | X | X | X | X | X | |
EXIT and CYCLE statements | X | X | X | X | X | |
Variable FORMAT expressions (VFEs) | X | X | X | X | X | X |
! marks end-of-line comment | X | X | X | X | X | X |
Optional run-time bounds checking for arrays and substrings | 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 |
Fortran 90/95 standards checking | X | X | X | X | ||
FORTRAN-77 standards checking | X | X | ||||
IEEE exception handling | 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 | |
CDD/Repository DICTIONARY support | X | X | ||||
KEYED access and INDEXED files | X | X | X | |||
Parallel decomposition | X 3,4 | 4 | 4 | 4 | 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) | 5 | 5 | 5 | 5 | 5 | X |
DATE_AND_TIME returns 4-digit year | 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 6 | X | X | X | X |
To simplify porting Compaq Fortran 77 applications from OpenVMS VAX systems to Compaq Fortran on OpenVMS Alpha Systems, the following features (extensions) are provided with Compaq Fortran:
http://www.compaq.com/fortran |
This section lists Compaq Fortran 77 extensions to the FORTRAN-77 standard that are interpretation differences or are not included in Compaq Fortran for OpenVMS Alpha Systems. Where appropriate, this list indicates equivalent Compaq Fortran language features.
Compaq Fortran conforms to the Fortran 90 and Fortran 95 standards. The Fortran 90 standard is a superset of the FORTRAN-77 standard. The Fortran 95 standard deletes some FORTRAN-77 features from the Fortran 90 standard. Compaq Fortran fully supports all of these deleted features (see the Compaq Fortran Language Reference Manual).
Compaq Fortran provides many but not all of the FORTRAN-77 extensions
provided by Compaq Fortran 77.
A.3.1 Compaq Fortran 77 for OpenVMS Language Features Not Implemented
The following FORTRAN-77 extensions provided by Compaq Fortran 77 on OpenVMS systems (both Alpha and VAX hardware) are not provided by Compaq Fortran for OpenVMS Alpha Systems:
I = "0014 ! Assigns 12 to I, not supported by Compaq Fortran |
SUBROUTINE FOO(A,N) DIMENSION A(N),B(10) NAMELIST /N1/ A ! Incorrect NAMELIST /N2/ B ! Correct END SUBROUTINE |
INTEGER I, J DATA I/O20101/, J/Z20/ TYPE *, I, J END |
Certain language features are available in Compaq Fortran 77 for OpenVMS VAX Systems, but are not supported in Compaq Fortran for OpenVMS Alpha Systems. These features include features supported by the VAX architecture, VAX hardware support, and older language extensions.
ASSIGN
CLOSE ERRSET |
ERRTST
FDBSET IRAD50 |
RAD50
R50ASC USEREX |
The following language features are available in Compaq Fortran 77 for OpenVMS VAX Systems, but are not supported in Compaq Fortran because of architectural differences between Alpha systems and VAX systems:
The following FORTRAN-77 extensions provided by Compaq Fortran 77 on OpenVMS systems (both Alpha and VAX hardware) are interpreted differently by Compaq Fortran.
STOP 001 ! Prints 1 instead of 001 |
REAL*8 D1,D2 DATA D1 /2.71828182846182/ ! Incorrect - only REAL*4 value DATA D2 /2.71828182846182D0/ ! Correct - REAL*8 value |
EXTERNAL SUM REAL A(10),B(10) S = SUM(A) ! Correct - invokes external function T = DOT_PRODUCT(A,B) ! Incorrect - invokes intrinsic function |
INTEGER I NAMELIST /N/ I I = 5 PRINT N END |
$ FORTRAN TEST.F $ LINK TEST $ RUN TEST &N I = 5 / |
$ FORTRAN /OLDF77 TEST.F $ LINK TEST $ RUN TEST $N I = 5 $END |
CHARACTER*2 CRLF CRLF = '\r\n' ! Incorrect CRLF = '\r\n'C ! Correct CRLF = CHAR(13)//CHAR(10) ! Standard-conforming alternative |
CHARACTER*10 C WRITE(C,*) 'FOO' ! C = ' FOO' |
X = 0.0 WRITE(*,100) X ! Compaq Fortran 77 prints 0.0000E+00 100 FORMAT(G12.4) ! Compaq Fortran prints 0.000 |
REAL A(SQRT(31.5)) END |
INQUIRE(20,ACCESS=acc,BLANK=blk,FORM=form) |
write(*,*) ((i,i=1,1),(j,j=1,2)) |
character*5 c c = 'ab\nef' ! not allowed c = 'ab\nef'C ! allowed end |
REAL*8 R R = 'abc' // 'def' WRITE (6,*) R END |
PARAMETER abcdef = 'abc' // 'def' REAL*8 R R = abcdef WRITE (6,*) R END |
CHARACTER CHAR4*4 NAMELIST /CN100/ CHAR4 CHAR4 = 'ABCD' WRITE(20,CN100) CLOSE (20) |
$CN100 CHAR4 = 'ABCD' $END |
READ (20, CN100) |
&CN100 CHAR4 = ABCD / |
The following language features are interpreted differently in Compaq Fortran 77 for OpenVMS VAX Systems and Compaq Fortran for OpenVMS Alpha Systems:
CHARACTER*(*) FMT2 PARAMETER (FMT2='(10Habcdefghij)') READ (5, FMT2) WRITE (6, FMT2) |
READ (5, '(10Habcdefghij)') WRITE (6, '(10Habcdefghij)') |
The following language features are detected differently by Compaq Fortran than Compaq Fortran 77:
EQUIVALENCE (X) ! Incorrect EQUIVALENCE (Y,Z) ! Correct |
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 |
IMPLICIT REAL (A-C), (D-H) ! Incorrect IMPLICIT REAL (O-S), REAL (T-Z) ! Correct |
R = REAL(.TRUE.) ! Incorrect R = REAL(1) ! Correct |
READ (10,100) (I,J,K) ! Incorrect READ (10,100) I,J,K ! Correct |
I = J -.NOT.K ! Incorrect I = J - (.NOT.K) ! Correct |
CHARACTER*1 C1 CHARACTER*4 C4 DATA C1/'FF'X/ ! Correct DATA C4/'FFFFFFFF'X/ ! Incorrect |
1 FORMAT (SSF4.1) ! Incorrect 2 FORMAT (SS,F4.1) ! Correct |
CHARACTER*4 C,C4,FUNC FUNC()=C4 C=FUNC(1) ! Incorrect C=FUNC() ! Correct |
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 |
foo(x) = x * 2 call bar(foo) end |
DO 10 I = 1,10 IF (L1) GO TO 10 ! Incorrect DO 10 J = 1,10 IF (L2) GO TO 10 ! Correct 10 CONTINUE |
OPEN(1,ASSOCIATEVARIABLE = I) ! Correct OPEN(2,ASSOCIATEDVARIABLE = J) ! Incorrect (extra D) |
INTEGER*8 I8 I8 = 2147483647+1 ! Incorrect. Produces less accurate ! INTEGER*4 result from integer overflow I8 = 2147483647_8 + 1_8 ! Correct |
LOGICAL B,B ! Incorrect (B multiply declared) |
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 |
INIT5 = 'ABCDE' INIT4 = 'ABCD' INITLONG = 'ABCDEFGHIJKLMNOP' PRINT 10, INIT5, INIT4, INITLONG 10 FORMAT (' ALL 3 VALUES SHOULD BE THE SAME: ' 3I) END |
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 |
LOGICAL LOG/111/ TYPE 1,LOG 1 FORMAT(' '23X,'LOG='O12) END |
1 FORMAT(' ',23X,'LOG='O12) |
WRITE(*,*) , P(J) |
CHARACTER*10 CH/'(I5)'/ INTEGER I READ CH,I ! Acceptable READ (CH),I ! Generates error message, interpreted as an internal READ END |
PARAMETER ( X = 4.0 ** 1.1) |
PARAMETER ( X = 4.0 / 0.0 ) |
http://www.compaq.com/fortran |
This section summarizes the differences between Compaq Fortran and Compaq Fortran 77 for OpenVMS Systems command lines.
The following commands initiate compilation on OpenVMS systems:
Platform | Language | Command |
---|---|---|
OpenVMS Alpha systems | Compaq Fortran | FORTRAN |
OpenVMS Alpha systems | Compaq Fortran 77 | FORTRAN/OLD_F77 |
OpenVMS VAX systems | Compaq Fortran 77 | FORTRAN |
On Compaq Tru64 UNIX Alpha systems, Compaq Fortran uses the f90 and f77 commands, and Compaq Fortran 77 uses the f77 -old_f77 command.
Most qualifiers are the same between Compaq Fortran for OpenVMS Alpha
systems and Compaq Fortran 77 for OpenVMS Alpha systems.
A.5.1 Qualifiers Not Available on OpenVMS VAX Systems
Table A-2 lists Compaq Fortran compiler qualifiers that have no equivalent Compaq Fortran 77 Version 6.4 for OpenVMS VAX Systems qualifiers.
Qualifier | Description |
---|---|
/ALIGNMENT=
[NO]SEQUENCE |
Specifies that components of derived types with the SEQUENCE attribute will obey whatever alignment rules are currently in use (see Section 2.3.3). |
/ANNOTATION | TBS (see Section 2.3.5). |
/ARCHITECTURE= keyword | Specifies the type of Alpha architecture code instructions generated for a particular program unit being compiled (see Section 2.3.6). |
/ASSUME=ALT_PARAM 1 | Allows the alternate syntax for PARAMETER statements. The alternate form has no parentheses surrounding the list, and the form of the constant, rather than implicit or explicit typing, determines the data type of the variable (see Section 2.3.7). |
/ASSUME=FP_CONSTANT 1 | Controls whether constants are evaluated in single or double precision (see Section 2.3.7). Compaq Fortran 77 always evaluates single-precision constants in double precision. |
/ASSUME=MINUS0 1 | Controls whether the compiler uses Fortran 95 standard semantics for the IEEE floating-point value of -0.0 (minus zero) in the SIGN intrinsic, if the processor is capable of distinguishing the difference between -0.0 and +0.0 (see Section 2.3.7). |
/ASSUME=PROTECT_CONSTANTS | Specifies whether constant actual arguments can be changed (see Section 2.3.7). |
/BY_REF_CALL | Allows character constant actual arguments to be associated with numeric dummy arguments (allowed by Compaq Fortran 77 for OpenVMS VAX Systems; see Section 2.3.9). |
/CHECK=ARG_TEMP_CREATED | Issues a run-time warning message and continues execution if a temporary is created for an array actual argument (see Section 2.3.11). |
/CHECK=FP_EXCEPTIONS | Controls whether messages about IEEE floating-point exceptional values are reported at run time (see Section 2.3.11). |
/CHECK=POWER | Controls whether the compiler evaluates and returns a result for certain arithmetic expressions containing floating- point numbers and exponentiation (see Section 2.3.11). |
/DOUBLE_SIZE | Makes DOUBLE PRECISION declarations REAL (KIND=16) instead of REAL (KIND=8) (see Section 2.3.16). |
/FAST | Sets several qualifiers that improve run-time performance (see Section 2.3.20). |
/FLOAT | Controls the format used for floating-point data (REAL or COMPLEX) in memory, including the selection of either VAX F_float or IEEE S_float for KIND=4 data and VAX G_float, VAX D_float, or IEEE T_float for KIND=8 data (see Section 2.3.21). Compaq Fortran 77 for OpenVMS VAX Systems provides the /[NO]G_FLOAT qualifier. |
/GRANULARITY | Controls the granularity of data access for shared data (see Section 2.3.22). |
/IEEE_MODE | Controls how floating-point exceptions are handled for IEEE data (see Section 2.3.23). |
/INTEGER_SIZE | Controls the size of INTEGER and LOGICAL declarations (see Section 2.3.25). |
/MODULE | Controls where module files (.F90$MOD) are placed. If you omit this qualifier or specify /NOMODULE, the .F90$MOD files are placed in your current default directory (see Section 2.3.30). |
/NAMES | Controls whether external names are converted to uppercase, lowercase, or as is (see Section 2.3.31). |
/OPTIMIZE | Most keywords are not available on Compaq Fortran 77 for OpenVMS VAX Systems, including INLINE, LOOPS, PIPELINE, TUNE, and UNROLL (see Section 2.3.34). |
/REAL_SIZE | Controls the size of REAL and COMPLEX declarations (see Section 2.3.36). |
/REENTRANCY | Specifies whether code generated for the main program and Fortran procedures it calls will rely on threaded or asynchronous reentrancy (see Section 2.3.38). |
/ROUNDING_MODE | Controls how floating-point calculations are rounded for IEEE data (see Section 2.3.39). |
/SEPARATE_COMPILATION |
Controls whether the Compaq Fortran compiler:
For more information, see Section 2.3.40. |
/SEVERITY 1 | Changes compiler diagnostic warning messages to have a severity of error instead of warning (see Section 2.3.41). |
/SOURCE_FORM | Controls whether the compiler expects free or fixed form source (see Section 2.3.43). |
/STANDARD | Flags extensions to the Fortran 90 or Fortran 95 standards (see Section 2.3.44). |
/SYNTAX_ONLY | Requests that only syntax checking occurs and no object file is created (see Section 2.3.46). |
/WARNINGS | Certain keywords are not available on Compaq Fortran 77 for OpenVMS VAX Systems (see Section 2.3.50). |
/VMS | Requests that Compaq Fortran use certain Compaq Fortran 77 for OpenVMS VAX Systems conventions (see Section 2.3.49). |
This section summarizes Compaq Fortran 77 for OpenVMS VAX Systems compiler options that have no equivalent Compaq Fortran options.
Table A-3 lists compilation options that are specific to Compaq Fortran 77 for OpenVMS VAX Systems Version 6.4.
Compaq Fortran 77 for OpenVMS VAX Systems Qualifier | Description |
---|---|
/BLAS=(INLINE,MAPPED) | Specifies whether Compaq Fortran 77 for OpenVMS VAX Systems recognizes and inlines or maps the Basic Linear Algebra Subroutines (BLAS). |
/CHECK=ASSERTIONS | Enables or disables assertion checking. |
/DESIGN=[NO]COMMENTS
/DESIGN=[NO]PLACEHOLDERS |
Analyzes program for design information. |
/DIRECTIVES=DEPENDENCE | Specifies whether specified compiler directives are used at compilation. |
/PARALLEL=(MANUAL or AUTOMATIC) | Supports parallel processing. |
/SHOW=(DATA_DEPENDENCIES,DICTIONARY,LOOPS) |
Control whether the listing file includes:
|
/VECTOR | Requests vector processing. |
/WARNINGS=INLINE | Controls whether the compiler prints informational diagnostic messages when it is unable to generate inline code for a reference to an intrinsic routine. Other /WARNINGS keywords are only available with Compaq Fortran 77 for OpenVMS VAX Systems, including TRUNCATED_SOURCE. |
All CPAR$ directives and certain CDEC$ directives associated with directed (manual) decomposition and their associated qualifiers or keywords are also specific to Compaq Fortran 77 for OpenVMS VAX Systems.
Compaq Fortran provides the ability to interoperate with translated shared images. That is, when creating a native Compaq Fortran image, you can add certain qualifiers to the FORTRAN and LINK command lines to allow the resulting image to interoperate with translated shared images at image activation (run time).
To allow the use of translated shared images:
The created executable image contains code that allows the resulting executable image to interoperate with shared (installed) images, including allowing the Compaq Fortran 77 for OpenVMS VAX Systems RTL (FORRTL_TV) to work with the Compaq Fortran RTL (DEC$FORRTL).
See Migrating an Applications from OpenVMS VAX to OpenVMS
Alpha.
A.7 Porting Compaq Fortran 77 for OpenVMS VAX Systems Data
Record types are identical for Compaq Fortran 77 on OpenVMS VAX systems and Compaq Fortran on OpenVMS Alpha systems.
If you need to convert unformatted floating-point data, keep in mind that Compaq Fortran 77 for OpenVMS VAX Systems programs (VAX hardware) stores:
Compaq Fortran programs (running on Alpha hardware) store REAL*4, REAL*8, COMPLEX*8, and COMPLEX*16 data in one of the formats shown in Table A-4 and REAL*16 data in X_float format.
Data Declaration | OpenVMS VAX Formats | OpenVMS Alpha Formats |
---|---|---|
REAL*4 and COMPLEX*8 | VAX F_float | VAX F_float or IEEE S_float |
REAL*8 and COMPLEX*16 | VAX D_float or VAX G_float | VAX D_float 1, VAX G_float, or IEEE T_float |
REAL*16 | VAX H_float | X_float format. You can convert VAX H_float REAL*16 data to Alpha X_float format. |
The floating-point data types supported by Compaq Fortran on OpenVMS Alpha systems are described in Chapter 8.
Example A-1 shows the use of the CVT$CONVERT_FLOAT RTL routine to convert VAX S_float data to VAX F_float format. This allows the converted value to be used as an argument to the LIB$WAIT routine.
The parameter definitions used in the CVT$CONVERT_FLOAT argument list (such as CVT$K_IEEE_S) are included from the $CVTDEF library module in FORSYSDEF. The S_float value read as an argument is contained in the variable F_IN; the F_float value is returned by CVT$CONVERT_FLOAT to variable F_OUT.
Example A-1 Using the CVT$CONVERT_FLOAT Routine |
---|
! This program converts IEEE S_float data to VAX F_float format ! ! Compile with: $ F90/FLOAT=IEEE_FLOAT ! PROGRAM CONVERT INCLUDE '($CVTDEF)' REAL(KIND=4) F_IN REAL(KIND=4) F_OUT INTEGER ISTAT F_IN = 20.0 PRINT *,' Sample S_float input value is ', F_IN ISTAT=CVT$CONVERT_FLOAT(F_IN, %VAL(CVT$K_IEEE_S), F_OUT, & %VAL(CVT$K_VAX_F), %VAL(CVT$M_ROUND_TO_NEAREST)) PRINT *,'Return status ISTAT',ISTAT ! IF (.NOT. ISTAT) CALL LIB$SIGNAL(%VAL(ISTAT)) PRINT *, ' Waiting for specified time ' CALL LIB$WAIT (F_OUT) STOP END PROGRAM CONVERT |
This section describes the REAL*16 VAX H_float data formats used on OpenVMS VAX systems. On Alpha systems, REAL*16 (extended precision) data is always stored in IEEE X_float format.
With VAX floating-point data types, the binary radix point is to the left of the most-significant bit.
The REAL*16 H_float format is available only on OpenVMS VAX systems; REAL*16 on Alpha systems use X_float format (see Section 8.4.4).
As shown in Figure A-1, 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-1 VAX H_float REAL*16 Representation (VAX Systems)
The form of a REAL*16 (H_float) 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.
Previous | Next | Contents | Index |