Compaq Fortran 77 Release Notes for OpenVMS VAX Systems
 *HyperReader
  Next     Previous     Contents     Examples     Tables     Close     Help  
  2.6  New and Changed Features in V6.1

  This section provides highlights of new and changed features
  in Compaq Fortran 77 Version 6.1.

  2.6.1  POINTER Statement Now Supported

  The POINTER statement is now supported as described
  in the DEC Fortran Language Reference Manual        .  See
  Example 2-2    for an example using POINTER.

                                Note

      If apointee is an adjustable array and the program
      unit contains one or more ENTRY statements, vari-
      ables used in the adjustable array bounds expression(s)
      must be present in all entry point argument lists or
      be in COMMON, otherwise results are unpredictable.

      For example:

            SUBROUTINE  BADSUB  (N)
            REAL  P_ARRAY(N)
            POINTER  (P,P_ARRAY)
         .
         .
         .
            ENTRY  BADENTRY  (J)   !  N  not  defined  at  entry
         .
         .
         .

      It is not necessary that the pointer be defined at all
      entry points, only that the bounds information be
      determinable.
      A pointee may also be an assumed-size array.

  2.6.2  Recursive Function References Now Permitted
  The documented restriction that recursive function refer-
  ences were not permitted, even with /RECURSIVE specified,
  has been removed.  However, within a function subprogram,
  the name of the function when used other than in a refer-
  ence (call) to that function, refers to the return value variable
  and not the function itself.  Consider the following modifica-
  tion of routine AST_ROUTINE from example D.2 from the

  DEC Fortran User Manual for OpenVMS VAX Systems           :
        INTEGER  FUNCTION  AST_ROUTINE

     .
     .
     .
  !  Reenable  the  AST
  !
        QIO_STATUS  =  SYS$QIOW  (,
       1   %VAL(CHANNEL),
       2   %VAL(IO$_SETMODE  .OR.  IOS$M_CTRLCAST),
       3   IOSB,
       4   AST_ROUTINE,,,,,)
     .
     .
     .

  Since the use of the name AST_ROUTINE in the SYS$QIOW
  call is not a function reference, the function return variable is
  passed which is not desired.  For uses of this nature, it would
  still be necessary to use a separate routine to reference the
  function name as an external symbol.

  However, with the CDEC$ ALIAS feature added in version
  V6.2, this could be successfully rewritten as follows:

        INTEGER  FUNCTION  AST_ROUTINE
  CDEC$  ALIAS  AST_ROUTINE,  LCL_AST_ROUTINE
     .

     .
     .
  !  Reenable  the  AST
  !
        QIO_STATUS  =  SYS$QIOW  (,
       1   %VAL(CHANNEL),
       2   %VAL(IO$_SETMODE  .OR.  IOS$M_CTRLCAST),
       3   IOSB,
       4   LCL_AST_ROUTINE,,,,,)
     .
     .
     .

  The CDEC$ ALIAS directive creates an alternate name

  LCL_AST_ROUTINE which can be used to reference
  the enclosing function rather than its return value.  See
  Section 2.5.4for more information.

  Example 2-1    is an example showing a valid use of recursive
  function references:

  2.6.3  New Non-Native Data in I/O CONVERT Options
  To support the exchange of 16-byte IEEE-style floating type
  data with Digital Fortran for OpenVMS Alpha and Digital

  UNIX, the non-native data in I/O support has been en-
  hanced to provide for conversion between this new type,
  called X_float, and the native VAX H_float type.  If one of
  the existing IEEE keywords (LITTLE_ENDIAN or BIG_
  ENDIAN) is specified as the CONVERT type, X_float val-
  ues in the external data file will be converted to or from

  VAX H_float when a REAL       *16 variable is written or read
  during unformatted I/O. The Alpha X_float type is little-
  endian, meaning that the least-significant fraction bit is in
  the lowest-addressed byte, but BIG_ENDIAN can be used to
  access REAL   *16 data from compatible non-Digital systems
  which use the big-endian form, where the least-significant
  fraction bit is in the highest-addressed byte.

  In addition, Digital Fortran for OpenVMS Alpha will support
  the combination of the IEEE X_float type along with VAX F
  /D or F/G float.  These combinations can be specified using the
  new CONVERT keywords 'FDX' and 'FGX', respectively.

  These keywords can also be used in the /CONVERT compile
  command or OPTIONS statement qualifier, as well as the
  FOR$CONVERT_nnn logical name.

  The Alpha X_float type has a 15-bit exponent and 113-bit
  fraction and has a similar range and precision to VAX H_
  float.

  2.6.4  New Argument List Inquiry Functions
  The compiler now supports two new intrinsic functions for
  returning information about the argument list to a called
  routine, IARGCOUNT and IARGPTR.

  IARGCOUNT takes no arguments; it returns the count
  of actual arguments supplied by the caller of the routine
  as an INTEGER     *4 value.  Note that if the routine is a
  CHARACTER or COMPLEX           * 16 function that the count
  includes the extra argument used for passing the return
  function value.

  IARGPTR takes no arguments; it returns the INTEGER          *4
  address of the beginning of the actual argument list; that is,
  the contents of register AP upon entry to the routine.  Note
  that the actual argument list is architecture-specific; on
  VAX systems it is an array of longwords whereas on Alpha
  systems it is an array of quadwords.

  IARGCOUNT and IARGPTR can be used in the executable
  section of any program unit, including a main program.
  They cannot be used in statement functions or in declarations,
  nor can their names be passed as actual arguments.
                                Note

      Omission of arguments in a call to a Fortran routine
      violates the Fortran-77 standard and may be non-
      portable.  Digital Fortran does not support omission of
      arguments which have CHARACTER type or which
      are used in adjustable array bounds expressions.  See
      alsoSection 1.4.2 for additional requirements when
      arguments are omitted.

  Example 2-2    demonstrates the use of the IARGCOUNT and
  IARGPTR intrinsics as well as of the POINTER statement:

  2.6.5  LOC Intrinsic Function Alternative to %LOC Built-In
  For improved compatibility with Fortran implementations on
  non-Digital platforms, Version V6.1 adds the LOC intrinsic
  function which has the same purpose and can be used in the
  same manner as the %LOC built-in function.  See the de-
  scription of %LOC in the   DEC Fortran Language Reference

  Manual   for additional information and restrictions.  The LOC
  function name may not be passed as an actual argument.

  2.6.6  New /DEBUG=PARAMETERS Command Qualifier

  In previous versions, the compiler would make known to the
  debugger only those PARAMETER constants which were ac-
  tually used in a program unit.  This was to prevent the object
  module and thus the executable image file from becoming
  very large if a large number of PARAMETER constants
  were defined, even if few were used (for example, if the

  DECwindows Motif INCLUDE files were used.)

  In response to a number of users who requested the ability to
  have the compiler make known to the debugger all defined
  PARAMETER constants, a new keyword, PARAMETERS,
  has been added to the /DEBUG command qualifier.

  If PARAMETERS=USED is specified, the compiler makes
  known to the debugger only those PARAMETER con-
  stants which were actually used.  This is the default.  If
  PARAMETERS=ALL is specified, all PARAMETER constants
  are made known to the debugger.

  As of Compaq Fortran 77 Version 6.3, the NONE keyword is
  also accepted.  SeeSection 2.3.2 for details.

  /DEBUG, without any value, is now equivalent to /DEBUG=(PARAMETERS=USED,SYMBOLS,TRACEBACK).
  /DEBUG=ALL is equivalent to /DEBUG=PARAMETERS=ALL,SYMBOLS,TRACEBACK),
  as is /DEBUG=PARAMETERS.

  2.6.7  Diagnostics For Possible Programming Errors

  Version 6.1 adds four new keywords to the /WARNINGS
  qualifier:

  *   [NO]UNCALLED - If UNCALLED is in effect, the com-
      piler issues informational diagnostics for any statement
      functions which are defined but never called.  Checking
      for uncalled statement functions does not occur when

      /DESIGN=PLACEHOLDERS is in effect and placeholders
      are seen.  NOUNCALLED suppresses such diagnostics.
      UNCALLED is the default.

  *   [NO]UNINITIALIZED - The compiler's detection
      of uninitialized variables, introduced in Version 6.0
      (see Section 2.8.15) can now be controlled from the
      command line.  If UNINITIALIZED is in effect, the
      compiler warns of uses of uninitialized variables.

      Checking for uninitialized variables does not occur
      when /DESIGN=PLACEHOLDERS is in effect and
      placeholders are seen, nor when /NOOPTIMIZE is in
      effect.  NOUNINITIALIZED suppresses such warnings.

      UNINITIALIZED is the default.

  *   [NO]UNUSED - If UNUSED is in effect, the compiler
      issues informational diagnostics for variables which are
      declared but not used.  Variables in COMMON or which
      appear in an EQUIVALENCE statement are not flagged.
      Checking for unused variables does not occur when
      /DESIGN=PLACEHOLDERS is in effect and placehold-
      ers are seen.  NOUNUSED suppresses such diagnostics.

      UNUSED is the default.

  *   [NO]USAGE - If USAGE is in effect, the compiler issues
      informational diagnostics when it detects programming
      usages which, though allowed by Digital Fortran, are of-
      ten indicative of a programming error.  At present, these
      are:

      *   Passing an identifier, which was previously used as
          an intrinsic routine, as an actual argument with-
          out having named that identifier in an INTRINSIC
          statement.  The FORTRAN-77 standard requires
          such intrinsics to be named in an INTRINSIC state-
          ment, but Digital Fortran relaxes that rule.  In many
          cases, such use indicates a programming error where
          an array name was intended instead.  If an intrin-
          sic routine was intended, name it in an INTRINSIC
          statement.

      *   A branch into an inner DO-loop or an IF block.
          Although this might be valid if the FORTRAN 66 "ex-
          tended range of a DO loop" feature was being used,
          it generally indicates a programming error.  A com-
          mon case involves two or more DO loops which share
          a common termination.  In such cases, the shared
          termination statement is considered to belong to the
          innermost DO loop.  For example:

                DO  100  I=1,10
                IF  (condition)  GOTO  100
                  DO  100  J=1,10
             .
             .
             .
          100    CONTINUE

          In this example, the shared loop termination label 100
          is considered to belong to the innermost loop, thus the

          GOTO is invalid.  This error can lead to unpredictable
          results, or sometimes, programs which appear to
          work but which break when moved to other platforms
          or some other change is made.
      NOUSAGE suppresses such diagnostics.  USAGE is the
      default.

  2.6.8  Directives Now Flagged Using
         /STANDARD=SOURCE_FORM

  The compiler now issues the "Extension to FORTRAN-77:
  nonstandard statement type" (EXT_STMT) diagnostic for

  CDEC$ and CPAR$ directives only if /STANDARD=SOURCE_
  FORM is in effect.  In previous versions, directives, which
  are statements appearing as a special form of comment,
  would be flagged if /STANDARD=SYNTAX was in ef-
  fect.  The change was made so as to more reasonably re-
  flect the degree of standards conformance in the source
  program.  Since directives look like comments, they are
  not interpreted as statements by non-Digital compilers.
  Note that if /STANDARD is specified without any key-
  words, /STANDARD=(SYNTAX,SEMANTICS,NOSOURCE_

  FORM,NOMIA) is used.

  A related change is that if SOURCE_FORM is specified,
  SYNTAX is implied.  Previously, /STANDARD=SOURCE_
  FORM would mean NOSYNTAX,NOSEMANTICS.

  2.6.9  Run-Time Libraries Can Be Installed Separately
  The installation procedure now allows the user to install only
  the updated Run-Time Libraries; previously the Run-Time
  Libraries were provided only if the compiler was also in-
  stalled.  This option is useful if it is desired to run programs
  linked against the enhanced Run-Time Libraries on other
  OpenVMS VAX systems which do not have the compiler
  installed, or to reinstall the Run-Time Library support af-
  ter a new version of OpenVMS VAX was installed.  See the

  Installation Guide for more details.

  2.6.10  Machine Code Listing and Debugger Changes

  The machine code section of the listing file has been enhanced
  to indicate variables which have been allocated to registers.
  In VAX FORTRAN V5, the compiler did not list the names of
  such variables, simply denoting them as "Rn".  Digital Fortran
  V6.0 would often use the name of the variable instead, but
  this could be confusing if the reader was not aware that the
  variable was in a register.  The compiler now suffixes such
  variable names with "%Rn".

  Table 2-2  shows how different types of variables are shown in
  the machine code listing.  Note that the machine code listing
  is meant as informational to the reader, and is not intended
  to be processed by the VAX MACRO assembler.

  In many cases, the compiler will create a local copy of for-
  mal arguments and COMMON variables and will use the
  notation of local variables for them.

  Another change, which was introduced in VAX FORTRAN-

  HPO, is that the compiler can now tell the debugger when a
  variable was allocated to a register.  Previously, the debugger
  would give a message that the variable was "optimized away"
  for such cases.  This makes it somewhat easier to debug opti-
  mized code, but the debugger information for such variables
  is not completely reliable and Digital still recommends us-
  ing the /NOOPTIMIZE compile command qualifier, where
  possible, when debugging.

  2.6.11  HELP/MESSAGE Database for Fortran Compiler and
          Run-Time Diagnostics

  OpenVMS VAX V6.0 provides a new command HELP
  /MESSAGE which provides simple access to the descrip-
  tion of error messages and other diagnostics, including the
  ability to automatically display a description of the most
  recent error (whose status value is in the DCL symbol
  $STATUS). The Digital Fortran product provides the file

  SYS$HELP:FORTRAN$MSGHLP.MSGHLP$DATA which
  supplies descriptions of the Fortran compiler and run-time
  diagnostics for use with HELP/MESSAGE.

  To add the Fortran messages to the list of known HELP
  /MESSAGE databases, you must define the logical name
  MSGHLP$LIBRARY  to be a search list that names each of the
  available databases, including the OpenVMS VAX supplied
  database SYS$HELP:MSGHLP$LIBRARY.MSGHLP$DATA.
  This logical name can be defined in the system startup
  procedure.  For example:

  $  DEFINE/SYSTEM  MSGHLP$LIBRARY  SYS$HELP:MSGHLP$LIBRARY,-
     SYS$HELP:FORTRAN$MSGHLP

  See the OpenVMS System Messages:  Companion Guide for
  Help Message Users    for more information on the HELP
  /MESSAGE feature.

  Next     Previous     Contents     Examples     Tables     Close     Help     ~Off