VMS Help  —  FORTRAN
the subroutine. The array declarator for a dummy argument can itself contain integer values that are dummy arguments or are references to a common block, providing for adjustable size arrays in subroutines. The upper bound of the array declarator for a dummy argument can be specified as an asterisk, in which case the upper bound of the dummy argument assumes the size of the upper bound of the actual argument. The size in a character string declarator for a dummy argument can be specified as an asterisk in parentheses, in which case the size of the actual argument is passed to the dummy argument. The values of the actual arguments in the invoking program unit become the values of the dummy arguments in the function. If you modify a dummy argument, the corresponding actual argument in the invoking program unit is also modified; the actual argument must be a variable if it is to be modified. If the actual argument is a character constant, the dummy argument can be either character or numeric in type, unless the name of the subprogram being invoked is a dummy argument in the invoking program unit. If the actual argument is a Hollerith constant, the dummy argument must be numeric.

62.82  –  TARGET

  Specifies that an object can become the target of a pointer.

  The TARGET attribute can be specified in a type declaration
  statement or TARGET statement, and takes one of the following
  forms:

  Type Declaration Statement:

   type, [att-ls,] TARGET [,att-ls] :: obj [spec] [,obj [spec]]...

  Statement:

   TARGET [::] obj [spec] [,obj [spec]]...

     type      Is a data type specifier.

     att-ls    Is an optional list of attribute specifiers.

     obj       Is the name of an object.  The object must
               not be declared with the PARAMETER attribute.

     spec      Is an array specification.

  A pointer is associated with a target by pointer assignment or by
  an ALLOCATE statement.

  If an object does not have the TARGET attribute or has not been
  allocated (using an ALLOCATE statement), no part of it can be
  accessed by a pointer.

  The TARGET attribute is compatible with the ALLOCATABLE, AUTOMATIC,
  DIMENSION, INTENT, OPTIONAL, PRIVATE, PUBLIC, SAVE, STATIC, and
  VOLATILE attributes.

  EXAMPLES:

  The following example shows type declaration statements specifying
  the TARGET attribute:

     TYPE(SYSTEM), TARGET :: FIRST
     REAL, DIMENSION(20, 20), TARGET :: C, D

  The following is an example of a TARGET statement:

     TARGET :: C(50, 50), D

62.83  –  TYPE

  Transfers output data from internal storage to external records
  that are sequentially accessed.

62.83.1  –  Formatted

  Translates data from binary to character format as specified by the
  format specifications.  Statement format:

     TYPE f[,iolist]

     f       Is a format specifier not prefaced by FMT=.

     iolist  Are the names of the variables from which the
             data is transferred, listed in the order of transfer.

62.83.2  –  List-directed

  Translates data from binary to character format according to the
  data types of the variables in the I/O list.  Statement format:

     TYPE *[,iolist]

     *       Specifies list-directed formatting.

     iolist  Are the names of the variables from which the data
             is transferred, listed in the order of transfer.

62.83.3  –  Namelist

  Translates data from binary to character format according to the
  data types of the list entities in the corresponding NAMELIST
  statement.  Statement format:

     TYPE n

     n  Is a namelist group name not prefaced by NML=.

62.84  –  Type declaration

  Explicitly specifies the properties of data objects or functions.

  Type declarations must precede all executable statements, can be
  declared only once, and cannot be used to change the type of a
  symbolic name that has already been implicitly assumed to be
  another type.

  Type declaration statements can initialize data in the same way as
  the DATA statement:  by having values, bounded by slashes, listed
  immediately after the symbolic name of the entity.

62.84.1  –  Numeric

  Statement format:

     type[*n] [[,att]...::] v [*n][/clist/][,v [*n][/clist/]]...

     type   Is any of the following data type specifiers:

            BYTE (equivalent to INTEGER*1)  DOUBLE PRECISION
            LOGICAL                         COMPLEX
            INTEGER                         DOUBLE COMPLEX
            REAL

     n      Is an integer that specifies (in bytes) the length
            of "v".  It overrides the length that is implied by
            the data type.

            The value of n must specify an acceptable length
            for the type of "v" (see the HP Fortran for OpenVMS
            Language Reference Manual).  BYTE, DOUBLE PRECISION,
            and DOUBLE COMPLEX data types have one acceptable
            length; thus, for these data types, the "n" specifier
            is invalid.

            If an array declarator is used, the "n" specifier
            must be positioned immediately after the array name.

     att    Is one of the following attribute specifiers:

            ALLOCATABLE       POINTER
            AUTOMATIC         PRIVATE
            DIMENSION         PUBLIC
            EXTERNAL          SAVE
            INTENT            STATIC
            INTRINSIC         TARGET
            OPTIONAL          VOLATILE
            PARAMETER

     v      Is the name of a data object or function.  It can
            optionally be followed by:

            o An array specification, if the object is an array
            o A character length, if the object is of type
              character
            o An initialization expression or, for pointer
              objects, =>NULL()

     clist  Is a list of constants, as in a DATA statement.  If
            "v" is the symbolic name of a constant, the "clist"
            cannot be present.

  A numeric data type declaration statement can define arrays by
  including array specifications in the list.

  A numeric type declaration statement can assign initial values to
  variables or arrays if it specifies a list of constants (the
  "clist").  The specified constants initialize only the variable or
  array that immediately precedes them.  The "clist" cannot have more
  than one item unless it initializes an array.  When the "clist"
  initializes an array, it must contain a value for every element in
  the array.

  If =>NULL() appears for a pointer, the pointer's initial
  association status is disassociated.

  In a function declaration, an array must be a deferred-shape array
  if it has the POINTER attribute; otherwise, it must be an
  explicit-shape array.

  The double colon separator (::) is required only if the declaration
  contains an attribute specifier or an initialization expression;
  otherwise it is optional.

  The same attribute must not appear more than once in a given type
  declaration statement, and an entity cannot be given the same
  attribute more than once in a scoping unit.

  If the PARAMETER attribute is specified, the declaration must
  contain an initialization expression.

  The following objects cannot be initialized in a type declaration
  statement:

   o  A dummy argument

   o  A function result

   o  An object in a named common block (unless the type declaration
      is in a block data program unit)

   o  An object in blank common

   o  An allocatable array

   o  A pointer

   o  An external name

   o  An intrinsic name

   o  An automatic object

   o  An object that has the AUTOMATIC attribute

62.84.2  –  Character

  Format:

     CHARACTER[*len[,] [[,att]...::] v[*len] [/clist/]
                                     [,v[*len] [/clist/]]...

     len    Is an unsigned integer constant, an integer constant
            expression enclosed in parentheses, or an asterisk (*)
            enclosed in parentheses.  The value of "len" specifies
            the length of the character data elements.

     att    Is one of the following attribute specifiers:

            ALLOCATABLE       POINTER
            AUTOMATIC         PRIVATE
            DIMENSION         PUBLIC
            EXTERNAL          SAVE
            INTENT            STATIC
            INTRINSIC         TARGET
            OPTIONAL          VOLATILE
            PARAMETER

     v      Is the symbolic name of a constant, variable, array,
            statement function or function subprogram, or array
            specification. The name can optionally be followed by
            a data type length specifier (*len or *(*)).

     clist  Is a list of constants, as in a DATA statement.  If
            "v" is the symbolic name of a constant, "clist" must
            not be present.

  If you use CHARACTER*len, "len" is the default length specification
  for that list.  If an item in that list does not have a length
  specification, the item's length is "len".  However, if an item
  does have a length specification, it overrides the default length
  specified in CHARACTER*len.

  When an asterisk length specification *(*) is used for a function
  name or dummy argument, it assumes the length of the corresponding
  function reference or actual argument.  Similarly, when an asterisk
  length specification is used for the symbolic name of a constant,
  the name assumes the length of the actual constant it represents.
  For example, STRING assumes a 9-byte length in the following
  statements:

     CHARACTER*(*) STRING
     PARAMETER (STRING = 'VALUE IS:')

  The length specification must range from 1 to 65535.  If no length
  is specified, a length of 1 is assumed.

  Character type declaration statements can define arrays if they
  include array specifications in their list.  The array
  specification goes first if both an array specification and a
  length are specified.

  A character type declaration statement can assign initial values to
  variables or arrays if it specifies a list of constants (the
  clist).  The specified constants initialize only the variable or
  array that immediately precedes them.  The "clist" cannot have more
  than one element unless it initializes an array.  When the "clist"
  initializes an array, it must contain a value for every element in
  the array.

  In a function declaration, an array must be a deferred-shape array
  if it has the POINTER attribute; otherwise, it must be an
  explicit-shape array.

  The double colon separator (::) is required only if the declaration
  contains an attribute specifier or an initialization expression;
  otherwise it is optional.

  The same attribute must not appear more than once in a given type
  declaration statement, and an entity cannot be given the same
  attribute more than once in a scoping unit.

  If the PARAMETER attribute is specified, the declaration must
  contain an initialization expression.

  The following objects cannot be initialized in a type declaration
  statement:

   o  A dummy argument

   o  A function result

   o  An object in a named common block (unless the type declaration
      is in a block data program unit)

   o  An object in blank common

   o  An allocatable array

   o  A pointer

   o  An external name

   o  An intrinsic name

   o  An automatic object

   o  An object that has the AUTOMATIC attribute

                                 NOTE

          The CHARACTER*len form for a CHARACTER  declaration
          is obsolescent in Fortran 95.  VSI Fortran flags
          obsolescent features, but fully supports them.

62.85  –  UNION

  See STATEMENTS STRUCTURE (subheads TYPE_DECLARATIONS and
  UNION_DECLARATIONS) in this Help file.

62.86  –  UNLOCK

  Frees the current record (that is, the last record read) in an
  indexed, relative, or sequential file.  By default, a record is
  locked when it is read.  The lock is normally held until your
  program performs another I/O operation on the unit (for example,
  rewriting the record, reading another record, or closing the file).

  Statement format:

     UNLOCK ([UNIT=]u[,ERR=s][,IOSTAT=ios])
     UNLOCK u

     u    An integer variable or constant specifying the
          logical unit number of the file, optionally
          prefaced by UNIT=.  UNIT= is required if unit is
          not the first I/O specifier.

     s    The label of a statement to which control is
          transferred if an error condition occurs.

     ios  A scalar default integer variable that is
          defined as a positive integer if an error occurs
          and zero if no error occurs.

62.87  –  USE

  Gives a program unit accessibility to public entities in a module.
  It takes one of the following forms:

     USE name [, rename-ls]
     USE name, ONLY : [only-ls]

     name       Is the name of the module.

     rename-ls  Is one or more items having the following
                form:

        local-name => mod-name

        local-name  Is the name of the entity in the program
                    unit using the module.

        mod-name    Is the name of a public entity in the module.

     only-ls   Is the name of a public entity in the module
               or a generic identifier (a generic name, defined
               operator, or defined assignment).

               An entity in the "only-ls" can also take the form:

        [local-name =>] mod-name

  If the USE statement is specified without the ONLY option, the
  program unit has access to all public entities in the named module.

  If the USE statement is specified with the ONLY option, the program
  unit has access to only those entities following the option.

  If more than one USE statement for a given module appears in a
  scoping unit, the following rules apply:

   o  If one USE statement does not have the ONLY option, all public
      entities in the module are accessible, and any "rename-ls"s and
      "only-ls"s are interpreted as a single, concatenated
      "rename-ls".

   o  If all the USE statements have ONLY options, all the "only-ls"s
      are interpreted as a single, concatenated "only-ls".  Only
      those entities named in one or more of the "only-ls"s are
      accessible.

  If two or more generic interfaces that are accessible in a scoping
  unit have the same name, the same operator, or are both
  assignments, they are interpreted as a single generic interface.
  Otherwise, multiple accessible entities can have the same name only
  if no reference to the name is made in the scoping unit.

  The local names of entities made accessible by a USE statement must
  not be respecified with any attribute other than PUBLIC or PRIVATE.
  The local names can appear in namelist group lists, but not in a
  COMMON or EQUIVALENCE statement.

  EXAMPLES:

  The following shows examples of the USE statement:

    MODULE MOD_A
      INTEGER :: B, C
      REAL E(25,5), D(100)
    END MODULE MOD_A
    ...
    SUBROUTINE SUB_Y
      USE MOD_A, DX => D, EX => E   ! Array D has been renamed
                                    ! DX and array E
      ...                           ! has been renamed EX. Scalar
                                    ! variables B
    END SUBROUTINE SUB_Y            ! and C are also available to
    ...                             ! this subroutine (using their
                                    ! module names).
    SUBROUTINE SUB_Z
      USE MOD_A, ONLY: B, C         ! Only scalar variables B and
                                    ! C are
      ...                           ! available to this subroutine
    END SUBROUTINE SUB_Z
    ...

  The following example shows a module containing common blocks:

    MODULE COLORS
      COMMON /BLOCKA/ C, D(15)
      COMMON /BLOCKB/ E, F
      ...
    END MODULE COLORS
    ...
    FUNCTION HUE(A, B)
      USE COLORS
      ...
    END FUNCTION HUE

  The USE statement makes all of the variables in the common blocks
  in module COLORS available to the function HUE.

  To provide data abstraction, a user-defined data type and
  operations to be performed on values of this type can be packaged
  together in a module.  The following example shows such a module:

    MODULE CALCULATION
      TYPE ITEM
        REAL :: X, Y
      END TYPE ITEM

      INTERFACE OPERATOR (+)
        MODULE PROCEDURE ITEM_CALC
      END INTERFACE

    CONTAINS
      FUNCTION ITEM_CALC (A1, A2)
        TYPE(ITEM) A1, A2, ITEM_CALC
        ...
      END FUNCTION ITEM_CALC
      ...
    END MODULE CALCULATION

    PROGRAM TOTALS
    USE CALCULATION
    TYPE(ITEM) X, Y, Z
      ...
      X = Y + Z
      ...
    END

  The USE statement allows program TOTALS access to both the type
  ITEM and the extended intrinsic operator + to perform calculations.

62.88  –  VIRTUAL

  See COMPATIBILITY_FEATURES in this Help file.

62.89  –  VOLATILE

  Prevents specified variables, arrays, and common blocks from being
  optimized during compilation.

  The VOLATILE attribute can be specified in a type declaration
  statement or VOLATILE statement, and takes one of the following
  forms:

  Type Declaration Statement:

   type, [att-ls,] VOLATILE [,attr-ls] :: obj [,obj]...

  Statement:

   VOLATILE obj [,obj]...

     type      Is a data type specifier.

     attr-ls   Is an optional list of attribute specifiers.

     obj       Is the name of an object or a common block
               enclosed in slashes.

  A variable or COMMON block must be declared VOLATILE if it can be
  read or written in a way that is not visible to the compiler.  For
  example:

   o  If an operating system feature is used to place a variable in
      shared memory (so that it can be accessed by other programs),
      the variable must be declared VOLATILE.

   o  If a variable is modified by a routine called by the operating
      system when an asynchronous event occurs, the variable must be
      declared VOLATILE.

  If an array is declared VOLATILE, each element in the array becomes
  volatile.  If a common block is declared VOLATILE, each variable in
  the common block becomes volatile.

  If an object of derived type is declared VOLATILE, its components
  become volatile.

  If a pointer is declared VOLATILE, the pointer itself becomes
  volatile.

  A VOLATILE statement cannot specify the following:

   o  A procedure

   o  A function result

   o  A namelist group

  The VOLATILE attribute is compatible with the ALLOCATABLE,
  AUTOMATIC, DIMENSION, INTENT, OPTIONAL, POINTER, PRIVATE, PUBLIC,
  SAVE, STATIC, and TARGET attributes.

62.90  –  WHERE

  Permits masked array assignment, which lets you perform an array
  operation on selected elements.  This kind of assignment masks the
  evaluation of expressions and assignment of values in array
  assignment statements, according to the value of a logical array
  expression.

  WHERE can be specified as a construct or statement.  Format:

  Statement form:

    WHERE (mask-expr1) assign-stmt

  Construct form:

    [name :] WHERE (mask-expr1)
       [where-body-stmt]...
    [ELSEWHERE (mask-expr2) [name]
       [where-body-stmt]...]
    [ELSEWHERE [name]
       [where-body-stmt]...]
    END WHERE [name]

    name             Is the name of the WHERE construct.

    mask-expr1       Are logical array expressions (called
    mask-expr2       mask expressions).

    assign-stmt      Is an assignment statement of the form:

                     array variable = array expression

    where-body-stmt  Is one of the following:
                     o An "assign-stmt"
                     o A WHERE statement or construct

  If a construct name is specified in a WHERE statement, the same
  name must appear in the corresponding END WHERE statement.  The
  same construct name can optionally appear in any ELSEWHERE
  statement in the construct.  (ELSEWHERE cannot specify a different
  name.)

  In each assignment statement, the mask expression, the variable
  being assigned to, and the expression on the right side, must all
  be conformable.  Also, the assignment statement cannot be a defined
  assignment.

  Each mask expression in the WHERE construct must be conformable.

  Only the WHERE statement (or the first line of the WHERE construct)
  can be labeled as a branch target statement.

  The following is an example of a WHERE statement:

    INTEGER A, B, C
    DIMENSION A(5), B(5), C(5)
    DATA A /0,1,1,1,0/
    DATA B /10,11,12,13,14/
    C = -1

    WHERE(A .NE. 0) C = B / A

  The resulting array C contains:  -1,11,12,13, and -1.

  The assignment statement is only executed for those elements where
  the mask is true.  Think of the mask expression in this example as
  being evaluated first into a logical array which has the value true
  for those elements where A is positive.

  This array of trues and falses is applied to the arrays A, B and C
  in the assignment statement.  The right side is only evaluated for
  elements for which the mask is true; assignment on the left side is
  only performed for those elements for which the mask is true.  The
  elements for which the mask is false do not get assigned a value.

  In a WHERE construct the mask expression is evaluated first and
  only once.  Every assignment statement following the WHERE is
  executed as if it were a WHERE statement with "mask-expr1" and
  every assignment statement following the ELSEWHERE is executed as
  if it were a WHERE statement with ".NOT.  mask-expr1".  If
  ELSEWHERE specifies "mask-expr2", it is executed as "(.NOT.
  mask-expr1) .AND.  mask-expr2".

  You should be careful if the statements have side effects, or
  modify each other or the mask expression.

  The following is an example of the WHERE construct:

    DIMENSION PRESSURE(1000), TEMP(1000), PRECIPITATION(1000)
    WHERE(PRESSURE .GE. 1.0)
      PRESSURE = PRESSURE + 1.0
      TEMP = TEMP - 10.0
    ELSEWHERE
      PRECIPITATION = .TRUE.
    ENDWHERE

  The mask is applied to the arguments of functions on the right side
  of the assignment if they are considered to be elemental functions.
  Only elemental intrinsics are considered elemental functions.
  Transformational intrinsics, inquiry intrinsics, and functions or
  operations defined in the subprogram are considered to be
  nonelemental functions.

  Consider the following example using LOG, an elemental function:

    WHERE(A .GT. 0)  B = LOG(A)

  The mask is applied to A, and LOG is executed only for the positive
  values of A.  The result of the LOG is assigned to those elements
  of B where the mask is true.

  Consider the following example using SUM, a nonelemental function:

    REAL A, B
    DIMENSION A(10,10), B(10)
    WHERE(B .GT. 0.0)  B = SUM(A, DIM=1)

  Since SUM is nonelemental, it is evaluated fully for all of A.
  Then, the assignment only happens for those elements for which the
  mask evaluated to true.

  Consider the following example:

    REAL A, B, C
    DIMENSION A(10,10), B(10), C(10)
    WHERE(C .GT. 0.0)  B = SUM(LOG(A), DIM=1)/C

  Because SUM is nonelemental, all of its arguments are evaluated
  fully regardless of whether they are elemental or not.  In this
  example, LOG(A) is fully evaluated for all elements in A even
  though LOG is elemental.  Notice that the mask is applied to the
  result of the SUM and to C to determine the right side.  One way of
  thinking about this is that everything inside the argument list of
  a nonelemental function does not use the mask, everything outside
  does.

62.91  –  WRITE

  Transfers data from internal storage to user-specified external
  logical units (such as disks, printers, terminals, and pipes) or
  internal files.

  The meanings of the symbolic abbreviations used to represent the
  parameters in the WRITE statement syntax are as follows:

     extu    Is the logical unit or internal file optionally
     or      prefaced by UNIT=.  UNIT= is required if unit is
     intu    not the first element in the clist.

     fmt     Specifies whether formatting is to be used for data
             editing, and if it is, the format specification or an
             asterisk (*) to indicate list-directed formatting.
             The "fmt" is optionally prefaced by FMT=, if "fmt"
             is the second parameter in the clist and the first
             parameter is a logical or internal unit specifier
             without the optional keyword UNIT=.

     nml     Is the namelist group specification for namelist I/O.
             Optionally prefaced by NML=.  NML= is required if
             namelist is not the second I/O specifier.

     rec     Is the cell number of a record to be accessed directly.
             Optionally prefaced by REC= or by an apostrophe (').

     iostat  Is the name of a variable to contain the completion
             status of the I/O operation. Prefaced by IOSTAT=.

     err     Is the label of a statement to which control is
             transferred in the event of an error. Prefaced by
             ERR=.

     end     Is the label of a statement to which control is
             transferred in the event of an end of file. Prefaced
             by END=.

     adv     Specifies advancing (ADVANCE='YES') or nonadvancing
             input (ADVANCE='NO').  The default is 'YES'.

     iolist  Are the names of the variables, arrays, array elements,
             or character substrings from which or to which data
             will be transferred.  Optionally an implied-DO list.

  The control-list parameters are "extu" (or "intu"), "fmt", "nml",
  "rec", "iostat", "err", "end", and "adv".  The I/O list parameter
  is "iolist".

62.91.1  –  Sequential

62.91.1.1  –  Formatted

  Formatted sequential WRITE statement format:

     WRITE (extu,fmt [,adv][,err][,iostat]) [iolist]

  Writes to a specified external unit.  Translates the data from
  binary to character format as specified by "fmt".

62.91.1.2  –  List-directed

  List-directed sequential WRITE statement format:

     WRITE (extu,*[,iostat][,err]) [iolist]

  Writes to a specified external unit.  Translates the data from
  binary to character format according to the data types of the
  variables in the I/O list.

62.91.1.3  –  Namelist

  Namelist sequential WRITE statement format:

     WRITE (extu,nml[,iostat][,err])

  Writes to a specified external unit.  Translates the data from
  binary to character format according to the data types of the list
  entities in the corresponding NAMELIST statement.

62.91.1.4  –  Unformatted

  Unformatted sequential WRITE statement format:

     WRITE (extu[,iostat][,err]) [iolist]

  Writes to a specified external unit.  Does not translate the data.

62.91.2  –  Direct

62.91.2.1  –  Formatted

  Formatted direct WRITE statement format:

     WRITE (extu,rec,fmt[,iostat][,err]) [iolist]

  Writes to a specified external unit.  Translates the data from
  binary to character format as specified by "fmt".

62.91.2.2  –  Unformatted

  Unformatted direct WRITE statement format:

    WRITE (extu,rec[,iostat][,err]) [iolist]

  Writes to a specified external unit.  Does not translate the data.

62.91.3  –  Internal

  Internal WRITE statement format:

     WRITE (intu[,fmt][,err][,iostat]) [iolist]

  Writes to a specified character variable.  Translates the data from
  binary to character format as specified by "fmt".

62.91.4  –  Indexed

62.91.4.1  –  Formatted

  Formatted indexed WRITE statement format:

     WRITE (extu,fmt,[,err][,iostat]) [iolist]

  Writes to a specified external unit.  Translates the data from
  binary to character format as specified by "fmt".

62.91.4.2  –  Unformatted

  Unformatted indexed WRITE statement format:

     WRITE (extu,[,err][,iostat]) [iolist]

  Writes to a specified external unit.  Does not translate the data.
Close Help