DIGITAL Fortran 90
User Manual for 
 DIGITAL 
UNIX Systems
A.2 Compatibility with DIGITAL Fortran 77 for DIGITAL UNIX Systems
This section provides compatibility information for those porting 
DIGITAL Fortran 77 applications from DIGITAL UNIX systems. It discusses 
the following topics:
  - Major language features for compatibility with DIGITAL Fortran 77 
  for Digital UNIX systems ( Section A.2.1)
  
- Language differences between DIGITAL Fortran 90 and DIGITAL Fortran 
  77, including DIGITAL Fortran 77 extensions on Digital UNIX Systems 
  that are not supported by this version of DIGITAL Fortran 90 on DIGITAL 
  UNIX Systems ( Section A.2.2)
  
- Language features detected during compilation differently by 
  DIGITAL Fortran 90 than DIGITAL Fortran 77 for Digital UNIX Systems 
  ( Section A.2.3)
A.2.1 Major Language Features for Compatibility with DIGITAL Fortran 77 for  Digital UNIX Systems
On Digital UNIX systems, to simplify porting applications from DIGITAL 
Fortran 77 to DIGITAL Fortran 90, DIGITAL Fortran 90 Version 5.n supports the 
following DIGITAL Fortran 77 extensions that are not part of the 
Fortran 90 standard:
  - 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, DIGITAL Fortran 90 Version 5.n also 
supports the following DIGITAL Fortran 77 features:
  - DIGITAL Fortran 77 compilation control statements and directives 
  (see the DIGITAL 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 DIGITAL Fortran 77 and DIGITAL Fortran 90 
  routines and a common run-time environment. For example, a DIGITAL 
  Fortran 77 procedure and a DIGITAL Fortran 90 procedure can perform I/O 
  to the same unit number (see Section 11.3).
  
- 
foriosdef.for
 symbolic parameter definitions for use with run-time (IOSTAT) error 
 handling (see Chapter 8).
For More Information:
On the DIGITAL Fortran 90 language, see the DIGITAL Fortran Language Reference Manual.
A.2.2 Language Features Provided Only by DIGITAL Fortran 77 for DIGITAL UNIX  Systems
This section lists DIGITAL Fortran 77 extensions to the FORTRAN-77 
standard that are not included in DIGITAL Fortran 90 Version 5.n for 
DIGITAL UNIX Systems. Where appropriate, this list indicates equivalent 
DIGITAL Fortran 90 language features.
DIGITAL Fortran 90 conforms to the Fortran 90 standard, which is a superset 
of the FORTRAN-77 standard. DIGITAL Fortran 90 provides many but not all of 
the FORTRAN-77 extensions provided by DIGITAL Fortran 77.
The following FORTRAN-77 extensions provided by DIGITAL Fortran 77 on 
Digital UNIX systems are not provided by DIGITAL Fortran 90 in 
Version 5.n:
  - Octal notation for integer constants is not part of the DIGITAL 
  Fortran 90 Language. DIGITAL 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 DIGITAL Fortran 90 
 |  
 
- The DIGITAL Fortran 90 language does not allow field names 
  specified in the STRUCTURE statement to be the same as intrinsic or 
  user defined operators. For example:
 
  
    | 
 
  STRUCTURE /FOO/ 
     INTEGER EQ          ! Incorrect 
  END STRUCTURE 
 |  
 
- The DIGITAL Fortran 90 compiler discards leading zeros for "disp" 
  in the STOP statement. For example:
 
  
    | 
 
  STOP 001   ! Prints 1 instead of 001 
 |  
 
- The DIGITAL Fortran 90 language prohibits dummy arguments with 
  nonconstant bounds from being a namelist item. For example:
 
  
    | 
 
 SUBROUTINE FOO(A,N) 
   DIMENSION A(N),B(10) 
   NAMELIST /N1/ A        ! Incorrect 
   NAMELIST /N2/ B        ! Correct 
 END SUBROUTINE                       
 |  
 
-  When a single-precision constant is assigned to a double-precision 
  variable, DIGITAL Fortran 77 evaluates the constant in double 
  precision. The Fortran 90 standard requires that the constant be 
  evaluated in single precision. 
 When a single-precision constant is 
  assigned to a double-precision variable with DIGITAL Fortran 90, 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, DIGITAL Fortran 77 assigns identical values to D1 and 
 D2, whereas DIGITAL Fortran 90 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 DIGITAL Fortran 90 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, DIGITAL Fortran 90 uses the 
  syntax for namelist external records specified by the Fortran 90 
  standard, rather than the DIGITAL Fortran 77 syntax (an extension to 
  the FORTRAN-77 and Fortran 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
 |  
 
 DIGITAL Fortran 90 accepts Fortran 90 namelist syntax and DIGITAL 
    Fortran 77 namelist syntax for reading records.
- The DIGITAL Fortran 90 language does not include C-style escape 
  sequences. For example:
 
  
    | 
 
  CHARACTER NL 
  NL = '\n'              ! Incorrect 
  NL = CHAR(10)          ! Correct 
 |  
 
- DIGITAL Fortran 90 inserts a leading blank when doing list-directed 
  I/O to an internal file. For example:
 
  
    | 
 
  CHARACTER*10 C 
  WRITE(C,*) 'FOO'    ! C = ' FOO' 
 |  
 
- DIGITAL Fortran 77 and DIGITAL Fortran 90 produce different output 
  a real value whose data magnitude is 0 with a G field descriptor. For 
  example:
 
  
    | 
 
     X = 0.0 
     WRITE(*,100) X     ! DIGITAL Fortran 77 prints 0.0000E+00 
100  FORMAT(G12.4)      ! DIGITAL Fortran 90 prints 0.000 
 |  
 
- DIGITAL Fortran 90 does not allow certain intrinsics (such as SQRT) 
  in constant expressions for array bounds. For example:
 
- DIGITAL Fortran 77 returns UNKNOWN while DIGITAL Fortran 90 returns 
  UNDEFINED when the ACCESS, BLANK, and FORM characteristics can not be 
  determined. For example:
 
  
    | 
 
  INQUIRE(20,ACCESS=acc,BLANK=blk,FORM=form) 
 |  
 
- DIGITAL Fortran 90 does not allow an extraneous parenthesis in I/O 
  lists. For example:
 
  
    | 
 
  write(*,*) ((i,i=1,1),(j,j=1,2)) 
 |  
 
- DIGITAL Fortran 90 does not allow control characters within quoted 
  strings. For example, if a Ctrl/C appears in a text string:
 
  
    | 
 
  character*5 c 
  c = 'ab^cef' 
  end 
 |  
 
- DIGITAL Fortran 90 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    
 |  
 
- DIGITAL Fortran 90, like DIGITAL Fortran 77, supports the use of 
  character literal constants (such as 'ABC' or "ABC") in numeric 
  contexts, where they are treated as Hollerith constants. 
 DIGITAL 
  Fortran 77 also allows character PARAMETER constants (typed and 
  untyped) and character constant expressions (using the // operator) in 
  numeric constants as an undocumented extension.
 DIGITAL Fortran 90 
  does allow character PARAMETER constants in numeric contexts, but does 
  not allow character expressions. For example, the following is valid 
  for DIGITAL Fortran 77, but will result in an error message from 
  DIGITAL Fortran 90:
 
  
    | 
 
   REAL*8 R 
   R = 'abc' // 'def' 
   WRITE (5,*) R 
   END 
 |  
 
 DIGITAL Fortran 90 does allow PARAMETER constants:
 
  
    | 
 
  PARAMETER abcdef = 'abc' // 'def' 
  REAL*8 R 
  R = abcdef 
  WRITE (5,*) R 
  END 
 |  
 
- DIGITAL 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, DIGITAL Fortran 90 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 DIGITAL 
    Fortran 90 program.
For More Information:
  - On argument passing between DIGITAL Fortran 90 and DIGITAL Fortran 77 
  for DIGITAL UNIX systems, see Section 11.3.
  
- On compatibility between DIGITAL Fortran 90 for DIGITAL UNIX systems 
  and DIGITAL Fortran 77 on OpenVMS systems, see Section A.4.
  
- About the DIGITAL Fortran 90 language, see the DIGITAL Fortran Language Reference Manual.
A.2.3 Improved DIGITAL Fortran 90 Compiler Diagnostic  Detection
The following language features are detected or interpreted differently 
by DIGITAL Fortran 90 Version 5.n and DIGITAL Fortran 77:
  - The DIGITAL Fortran 90 compiler enforces the constraint that a 
  function cannot be the target of a CALL statement. For example:
 
  
    | 
 
  REAL X 
  CALL X()      ! Incorrect 
  CALL Y()      ! Correct 
 |  
 
- The DIGITAL Fortran 90 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 DIGITAL Fortran 90 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 DIGITAL Fortran 90 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 DIGITAL Fortran 90 language disallows passing mismatched actual 
  arguments to intrinsics with corresponding integer formal arguments. 
  For example:
 
  
    | 
 
  R = REAL(.TRUE.)    ! Incorrect 
  R = REAL(1)         ! Correct 
 |  
 
- The DIGITAL Fortran 90 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 DIGITAL Fortran 90 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 DIGITAL Fortran 90 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 DIGITAL Fortran 90 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 DIGITAL Fortran 90 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 DIGITAL Fortran 90 compiler detects the use of a format of the 
  form Ew.dE0 at compile time. For example:
 
  
    | 
 
1   format(e16.8e0)   ! DIGITAL Fortran 90 detects error at compile time 
    write(*,1) 5.0    ! DIGITAL Fortran 77 compiles but an output 
                      !    conversion error occurs at run time 
 |  
 
- DIGITAL Fortran 90 detects passing of a statement function to a 
  routine. For example:
 
  
    | 
 
  foo(x) = x * 2 
  call bar(foo) 
  end 
 |  
 
- The DIGITAL Fortran 90 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 DIGITAL Fortran 90 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 DIGITAL Fortran 77 compiler compiles files 
  containing less than one program unit.
- The DIGITAL Fortran 90 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 DIGITAL Fortran 90 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 DIGITAL Fortran 90 compiler enforces the constraint that an 
  object can be typed only once. DIGITAL Fortran 77 issues a warning 
  message and uses the first type. For example:
 
  
    | 
 
  LOGICAL B,B             ! Incorrect (B multiply declared) 
 |  
 
- The DIGITAL Fortran 90 compiler enforces the constraint that 
  certain intrinsic procedures defined by the Fortran 90 standard cannot 
  be passed as actual arguments. For example, DIGITAL Fortran 77 allows 
  most intrinsic procedures to be passed as actual arguments, but the 
  DIGITAL Fortran 90 compiler only allows those defined by the Fortran 90 
  standard (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 
    90 standard.
- DIGITAL Fortran 90 reports character truncation with an error-level 
  message, not as a warning. 
 The following program produces an error 
  message during compilation with DIGITAL Fortran 90, whereas DIGITAL 
  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 DIGITAL Fortran 90 intrinsic procedures with 
  the wrong number of arguments or an incorrect argument type, DIGITAL 
  Fortran 90 reports this with an error-level message, not with a 
  warning. Possible causes include:
  
    - A DIGITAL Fortran 90 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 DIGITAL Fortran 90, whereas DIGITAL 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 
 |  
 
- DIGITAL Fortran 90 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 DIGITAL 
  Fortran 90, whereas DIGITAL 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) 
 |  
 
- DIGITAL Fortran 90 generates an error when it encounters a 
  1-character source line containing a Ctrl/Z character, whereas DIGITAL 
  Fortran 77 allows such a line (which is treated as a blank line).
  
- DIGITAL Fortran 90 does not detect an extra comma in an I/O 
  statement when the
-std
 option is specified, whereas DIGITAL Fortran 77 with the
-stand
 option identifies an extra comma as an extension. For example:
 
- DIGITAL Fortran 90 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 
 |  
 
- DIGITAL Fortran 90 evaluates the exponentiation operator at compile 
  time only if the exponent has an integer data type. DIGITAL 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) 
 |  
 
- DIGITAL Fortran 90 detects an error when evaluating constants 
  expressions that result in an NaN or Infinity exceptional value, while 
  DIGITAL Fortran 77 allows such expressions. For example:
 
  
    | 
 
 PARAMETER ( X = 4.0 / 0.0 ) 
 |  
 
- DIGITAL Fortran 90 reports a warning error message when the same 
  variable is initialized more than once. DIGITAL 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 
  DIGITAL Fortran 90 and DIGITAL Fortran 77, see Section 11.3.
  
- On DIGITAL Fortran 90 procedure calling and argument passing, see 
  Section 11.1.
  
- On compatibility between DIGITAL Fortran 90 for DIGITAL UNIX systems 
  and DIGITAL Fortran 77 on OpenVMS systems, see Section A.4.
  
- On the DIGITAL Fortran 90 language, see the DIGITAL Fortran Language Reference Manual.