VMS Help  —  FORTRAN  Statements  OPTIONAL
  Permits dummy arguments to be omitted in a procedure reference.

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

  Type Declaration Statement:

   type, [att-ls,] OPTIONAL [,att-ls] :: d-arg [,d-arg]...

  Statement:

   OPTIONAL [::] d-arg [,d-arg]...

     type      Is a data type specifier.

     att-ls    Is an optional list of attribute specifiers.

     d-arg     Is the name of a dummy argument.

  The OPTIONAL attribute can only appear in the scoping unit of a
  subprogram or an interface body, and can only be specified for
  dummy arguments.

  A dummy argument is "present" if it associated with an actual
  argument.  A dummy argument that is not optional must be present.
  You can use the PRESENT intrinsic function to determine whether an
  optional dummy argument is associated with an actual argument.

  To call a procedure that has an optional argument, you must use an
  explicit interface.

  The OPTIONAL attribute is compatible with the DIMENSION, EXTERNAL,
  INTENT, POINTER, TARGET, and VOLATILE attributes.

  EXAMPLES:

  The following example shows a type declaration statement specifying
  the OPTIONAL attribute:

    SUBROUTINE TEST(A)
    REAL, OPTIONAL, DIMENSION(-10:2) :: A
    END SUBROUTINE

  The following is an example of the OPTIONAL statement:

         SUBROUTINE TEST(A, B, L, X)
         OPTIONAL :: B
         INTEGER A, B, L, X

         IF (PRESENT(B)) THEN        ! Printing of B is conditional
            PRINT *, A, B, L, X      !   on its presence
         ELSE
            PRINT *, A, L, X
         ENDIF
         END SUBROUTINE

         INTERFACE
            SUBROUTINE TEST(ONE, TWO, THREE, FOUR)
             INTEGER ONE, TWO, THREE, FOUR
             OPTIONAL :: TWO
           END SUBROUTINE
         END INTERFACE

         INTEGER I, J, K, L

         I = 1
         J = 2
         K = 3
         L = 4

         CALL TEST(I, J, K, L)            ! Prints:  1  2  3  4
         CALL TEST(I, THREE=K, FOUR=L)    ! Prints:  1  3  4
         END

  Note that in the second call to subroutine TEST, the second
  positional (optional) argument is omitted.  In this case, all
  following arguments must be keyword arguments.
Close Help