[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

HP Fortran for OpenVMS
Language Reference Manual


Previous Contents Index

8.8.1 Optional Arguments

Dummy arguments can be made optional if they are declared with the OPTIONAL attribute. In this case, an actual argument does not have to be supplied for it in a procedure reference.

Positional arguments (if any) must appear first in an actual argument list, followed by keyword arguments (if any). If an optional argument is the last positional argument, it can simply be omitted if desired.

However, if the optional argument is to be omitted but it is not the last positional argument, keyword arguments must be used for any subsequent arguments in the list.

The following example shows optional arguments:


PROGRAM RESULT
TEST_RESULT = LGFUNC(A, B=D)
...
CONTAINS
  FUNCTION LGFUNC(G, H, B)
    OPTIONAL H, B
    ...
  END FUNCTION
END

In the function reference, A is a positional argument associated with required dummy argument G. The second actual argument D is associated with optional dummy argument B by its keyword name (B). No actual argument is associated with optional argument H.

There are two intrinsics you can use to determine arguments:

8.8.1.1 Using the PRESENT Intrinsic Function

You can use the PRESENT intrinsic function to determine if an actual argument is associated with an optional dummy argument in a particular reference.

Optional arguments must be defined in explicit procedure interfaces so that appropriate argument associations can be made for the PRESENT to work.

See Example 8-1.

Example 8-1 Use of the PRESENT Intrinsic With a Defined Interface

!  Compile /NOOPT to avoid inlining
!
           SUBROUTINE CHECK (X, Y)
             REAL X, Z
             REAL, OPTIONAL :: Y

             IF (PRESENT (Y)) THEN
               WRITE(6,10)
10             FORMAT(1X, "Y is present")
               Z = Y
             ELSE
               WRITE(6,20)
20             FORMAT(1X, "Y is NOT present")
               Z = X * 2
             END IF
             TYPE *,Z
           END

           PROGRAM MAIN
!
! Define CHECK's interface here inside the caller, so MAIN knows how to call it
!
           INTERFACE
                SUBROUTINE CHECK(U,V)
                REAL U
                REAL, OPTIONAL :: V
                END SUBROUTINE
           END INTERFACE

           WRITE (6,100)
100        FORMAT(1X, "Call with a Y")
           CALL CHECK (15.0, 12.0)      ! Causes B to be set to 12.0
           WRITE (6,200)
200        FORMAT(1X, "Call without a Y")
           CALL CHECK (15.0)            ! Causes B to be set to 30.0
           END
$ f90/noop example
$ lin example
$ r example
Call with a Y
Y is present
  12.00000
Call without a Y
Y is NOT present
  30.00000
$

The implementation of PRESENT depends on the caller passing a null reference value for any omitted actual argument. This is true even for trailing omitted actual arguments. In this regard, the PRESENT intrinsic does not take advantage of the shortened argument list convention allowed in the OpenVMS Calling Standard. On the calling side, it is the explicit declaration of the full interface that tells the caller how many actual arguments must be provided in any call, even when fewer arguments are written in the source.

8.8.1.2 Using the IARGCOUNT Intrinsic Function

You can use the IARGCOUNT intrinsic function to return the count of actual arguments passed to the routine. With IARGCOUNT, there is no requirement for the caller to see an explicit interface.

See Example 8-2.

Example 8-2 Use of the IARGCOUNT Intrinsic

!  Compile /NOOPT to prevent inlining !
!
           SUBROUTINE CHECK (X, Y)
             REAL X, Z
             REAL, OPTIONAL :: Y

             IF (IARGCOUNT() .GT. 1) THEN
               WRITE(6,10)
10             FORMAT(1X, "Y is present")
               Z = Y
             ELSE
               WRITE(6,20)
20             FORMAT(1X, "Y is NOT present")
               Z = X * 2
             END IF
             TYPE *,Z
           END

           PROGRAM MAIN
           INTEGER I
           CHARACTER C(4)
           REAL    R
           EQUIVALENCE(I,C,R)

           WRITE (6,100)
100        FORMAT(1X, "Call with a Y")
           CALL CHECK (15.0, 12.0)      ! Causes B to be set to 12.0
           WRITE (6,200)
200        FORMAT(1X,"Call without a Y")
           CALL CHECK (15.0)            ! Causes B to be set to 30.0
           END
$ f90/noop example2
$ lin example2
$ r example2
Call with a Y
Y is present
  12.00000
Call without a Y
Y is NOT present
  30.00000
$

For More Information:

8.8.2 Array Arguments

Arrays are sequences of elements. Each element of an actual array is associated with the element of the dummy array that has the same position in array element order.

If the dummy argument is an explicit-shape or assumed-size array, the size of the dummy argument array must not exceed the size of the actual argument array.

The type and kind parameters of an explicit-shape or assumed-size dummy argument must match the type and kind parameters of the actual argument, but their ranks need not match.

If the dummy argument is an assumed-shape array, the size of the dummy argument array is equal to the size of the actual argument array. The associated actual argument must not be an assumed-size array or a scalar (including a designator for an array element or an array element substring).

If the actual argument is an array section with a vector subscript, the associated dummy argument must not be defined.

The declaration of an array used as a dummy argument can specify the lower bound of the array.

Although most types of arrays can be used as dummy arguments, allocatable arrays cannot be dummy arguments. Allocatable arrays can be used as actual arguments.

Dummy argument arrays declared as assumed-shape, deferred-shape, or pointer arrays require an explicit interface visible to the caller.

For More Information:

8.8.3 Pointer Arguments

An argument is a pointer if it is declared with the POINTER attribute.

When a procedure is invoked, the dummy argument pointer receives the pointer association status of the actual argument. If the actual argument is currently associated, the dummy argument becomes associated with the same target.

If both the dummy and actual arguments are pointers, an explicit interface is required.

A dummy argument that is a pointer can be associated only with an actual argument that is a pointer. However, an actual argument that is a pointer can be associated with a nonpointer dummy argument. In this case, the actual argument is associated with a target and the dummy argument, through argument association, also becomes associated with that target.

If the dummy argument does not have the TARGET or POINTER attribute, any pointers associated with the actual argument do not become associated with the corresponding dummy argument when the procedure is invoked.

If the dummy argument has the TARGET attribute, and is either a scalar or assumed-shape array, and the corresponding actual argument has the TARGET attribute but is not an array section with a vector subscript, the following occurs:

  • Any pointer associated with the actual argument becomes associated with the corresponding dummy argument when the procedure is invoked.
  • Any pointers associated with the dummy argument remain associated with the actual argument when execution of the procedure completes.

If the dummy argument has the TARGET attribute, and is an explicit-shape or assumed-size array, and the corresponding actual argument has the TARGET attribute but is not an array section with a vector subscript, association of actual and corresponding dummy arguments when the procedure is invoked or when execution is completed is processor dependent.

If the dummy argument has the TARGET attribute and the corresponding actual argument does not have that attribute or is an array section with a vector subscript, any pointer associated with the dummy argument becomes undefined when execution of the procedure completes.

For More Information:

  • On general rules for procedure argument association, see Section 8.8.
  • On pointers, see Section 5.15.
  • On pointer assignment, see Section 4.2.3.
  • On the TARGET attribute, see Section 5.18.
  • On passing pointers as arguments, see the HP Fortran for OpenVMS User Manual.

8.8.4 Assumed-Length Character Arguments

An assumed-length character argument is a dummy argument that assumes the length attribute of its corresponding actual argument. An asterisk (*) specifies the length of the dummy character argument.

A character array dummy argument can also have an assumed length. The length of each element in the dummy argument is the length of the elements in the actual argument. The assumed length and the array declarator together determine the size of the assumed-length character array.

The following example shows an assumed-length character argument:


INTEGER FUNCTION ICMAX(CVAR)
  CHARACTER*(*) CVAR
  ICMAX = 1
  DO I=2,LEN(CVAR)
    IF (CVAR(I:I) .GT. CVAR(ICMAX:ICMAX)) ICMAX=I
  END DO
  RETURN
END

The function ICMAX finds the position of the character with the highest ASCII code value. It uses the length of the assumed-length character argument to control the iteration. Intrinsic function LEN determines the length of the argument.

The length of the dummy argument is determined each time control transfers to the function. The length of the actual argument can be the length of a character variable, array element, substring, or expression. Each of the following function references specifies a different length for the dummy argument:


CHARACTER VAR*10, CARRAY(3,5)*20
...
I1 = ICMAX(VAR)
I2 = ICMAX(CARRAY(2,2))
I3 = ICMAX(VAR(3:8))
I4 = ICMAX(CARRAY(1,3)(5:15))
I5 = ICMAX(VAR(3:4)//CARRAY(3,5))

For More Information:

8.8.5 Character Constant and Hollerith Arguments

If an actual argument is a character constant (for example, 'ABCD' ), the corresponding dummy argument must be of type character. If an actual argument is a Hollerith constant (for example, 4HABCD), the corresponding dummy argument must have a numeric data type.

The following example shows character and Hollerith constants being used as actual arguments:


SUBROUTINE S(CHARSUB, HOLLSUB, A, B)
EXTERNAL CHARSUB, HOLLSUB
...
CALL CHARSUB(A, 'STRING')
CALL HOLLSUB(B, 6HSTRING)

The subroutines CHARSUB and HOLLSUB are themselves dummy arguments of the subroutine S. Therefore, the actual argument 'STRING' in the call to CHARSUB must correspond to a character dummy argument, and the actual argument 6HSTRING in the call to HOLLSUB must correspond to a numeric dummy argument.

For More Information:

On general rules for procedure argument association, see Section 8.8.

8.8.6 Alternate Return Arguments

Alternate return (dummy) arguments can appear in a subroutine argument list. They cause execution to transfer to a labeled statement rather than to the statement immediately following the statement that called the routine. The alternate return is indicated by an asterisk (*). (An alternate return is an obsolescent feature in Fortran 95 and Fortran 90.)

There can be any number of alternate returns in a subroutine argument list, and they can be in any position in the list.

An actual argument associated with an alternate return dummy argument is called an alternate return specifier; it is indicated by an asterisk (*), or ampersand (&) followed by the label of an executable branch target statement in the same scoping unit as the CALL statement.

Alternate returns cannot be declared optional.

In Fortran 95/90, you can also use the RETURN statement to specify alternate returns.

The following example shows alternate return actual and dummy arguments:


CALL MINN(X, Y, *300, *250, Z)
....
SUBROUTINE MINN(A, B, *, *, C)

For More Information:

8.8.7 Dummy Procedure Arguments

If an actual argument is a procedure, its corresponding dummy argument is a dummy procedure. Dummy procedures can appear in function or subroutine subprograms.

The actual argument must be the specific name of an external, module, intrinsic, or another dummy procedure. If the specific name is also a generic name, only the specific name is associated with the dummy argument. Not all specific intrinsic procedures can appear as actual arguments. (For more information, see Table 9-1.)

The actual argument and corresponding dummy procedure must both be subroutines or both be functions.

If the interface of the dummy procedure is explicit, the type and kind parameters, and rank of the associated actual procedure must be the same as that of the dummy procedure.

If the interface of the dummy procedure is implicit and the procedure is referenced as a subroutine, the actual argument must be a subroutine or a dummy procedure.

If the interface of the dummy procedure is implicit and the procedure is referenced as a function or is explicitly typed, the actual argument must be a function or a dummy procedure.

Dummy procedures can be declared optional, but they must not be declared with an intent.

The following is an example of a procedure used as an argument:


REAL FUNCTION LGFUNC(BAR)
  INTERFACE
    REAL FUNCTION BAR(Y)
      REAL, INTENT(IN) :: Y
    END
  END INTERFACE
  ...
  LGFUNC = BAR(2.0)
  ...
END FUNCTION LGFUNC

For More Information:

On general rules for procedure argument association, see Section 8.8.

8.8.8 References to Generic Procedures

Generic procedures are procedures with different specific names that can be accessed under one generic (common) name. In FORTRAN 77, generic procedures were limited to intrinsic procedures. In Fortran 95/90, you can use generic interface blocks to specify generic properties for intrinsic and user-defined procedures.

If you refer to a procedure by using its generic name, the selection of the specific routine is based on the number of arguments and the type and kind parameters, and rank of each argument.

All procedures given the same generic name must be subroutines, or all must be functions. Any two must differ enough so that any invocation of the procedure is unambiguous.

The following sections describe references to generic intrinsic functions and show an example of using intrinsic function names.

For More Information:

  • On user-defined generic procedures, see Section 8.9.3.
  • On the rules for unambiguous procedure references, see Section 15.3.
  • On the rules for resolving ambiguous procedure references, see Section 15.4.
  • On intrinsic procedures, see Chapter 9.

8.8.8.1 References to Generic Intrinsic Functions

The generic intrinsic function name COS lists six specific intrinsic functions that calculate cosines: COS, DCOS, QCOS, CCOS, CDCOS, and CQCOS. These functions return different values: REAL(4), REAL(8), REAL(16), COMPLEX(4), COMPLEX(8), and COMPLEX(16), respectively.

If you invoke the cosine function by using the generic name COS, the compiler selects the appropriate routine based on the arguments that you specify. For example, if the argument is REAL(4), COS is selected; if it is REAL(8), DCOS is selected; and if it is COMPLEX(4), CCOS is selected.

You can also explicitly refer to a particular routine. For example, you can invoke the double-precision cosine function by specifying DCOS.

Procedure selection occurs independently for each generic reference, so you can use a generic reference repeatedly in the same program unit to access different intrinsic procedures.

You cannot use generic function names to select intrinsic procedures if you use them as follows:

  • The name of a statement function
  • A dummy argument name, a common block name, or a variable or array name

When an intrinsic function is passed as an actual argument to a procedure, its specific name must be used, and when called, its arguments must be scalar. Not all specific intrinsic functions can appear as actual arguments. (For more information, see Table 9-1.)

Generic procedure names are local to the program unit that refers to them, so they can be used for other purposes in other program units.

Normally, an intrinsic procedure name refers to the Fortran 95/90 library procedure with that name. However, the name can refer to a user-defined procedure when the name appears in an EXTERNAL statement.

Note

If you call an intrinsic procedure by using the wrong number of arguments or an incorrect argument type, the compiler assumes you are referring to an external procedure. For example, intrinsic procedure SIN requires one argument; if you specify two arguments, such as SIN(10,4), the compiler assumes SIN is external and not intrinsic.

Except when used in an EXTERNAL statement, intrinsic procedure names are local to the program unit that refers to them, so they can be used for other purposes in other program units. The data type of an intrinsic procedure does not change if you use an IMPLICIT statement to change the implied data type rules.

Intrinsic and user-defined procedures cannot have the same name if they appear in the same program unit.

Examples

Example 8-3 shows the local and global properties of an intrinsic function name. It uses intrinsic function SIN as the:

  • Name of a statement function
  • Generic name of an intrinsic function
  • Specific name of an intrinsic function
  • Name of a user-defined function

Example 8-3 Using and Redefining an Intrinsic Function Name

   !     Compare ways of computing sine

         PROGRAM SINES
           DOUBLE PRECISION X, PI
           PARAMETER (PI=3.141592653589793238D0)
           COMMON V(3)

(1)   !     Define SIN as a statement function

           SIN(X) = COS(PI/2-X)
           DO X = -PI, PI, 2*PI/100

(2)   !     Reference the statement function SIN

             WRITE (6,100) X, V, SIN(X)
           END DO
           CALL COMPUT(X)
   100     FORMAT (5F10.7)
         END

         SUBROUTINE COMPUT(Y)
           DOUBLE PRECISION Y

(3)   !     Use intrinsic function SIN as an actual argument

           INTRINSIC SIN
           COMMON V(3)

(4)   !     Define generic reference to double-precision sine

           V(1) = SIN(Y)

(5)   !     Use intrinsic function SIN as an actual argument

           CALL SUB(REAL(Y),SIN)
         END

         SUBROUTINE SUB(A,S)

(6)   !     Declare SIN as name of a user function

           EXTERNAL SIN

(7)   !     Declare SIN as type DOUBLE PRECISION

           DOUBLE PRECISION SIN
           COMMON V(3)

(8)   !     Evaluate intrinsic function SIN

           V(2) = S(A)

(9)   !     Evaluate user-defined SIN function

           V(3) = SIN(A)
         END

(10)   !     Define the user SIN function

         DOUBLE PRECISION FUNCTION SIN(X)
           INTEGER FACTOR
           SIN = X - X**3/FACTOR(3) + X**5/FACTOR(5)     &
               - X**7/FACTOR(7)
         END

         INTEGER FUNCTION FACTOR(N)
           FACTOR = 1
           DO I=N,1,-1
             FACTOR = FACTOR * I
           END DO
         END


Previous Next Contents Index