[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

HP Fortran for OpenVMS
Language Reference Manual


Previous Contents Index

If A is greater than B, block1 is executed. If A is not greater than B, but A is greater than B/2, block2 is executed. If A is not greater than B and A is not greater than B/2, neither block1 nor block2 is executed. Control transfers directly to the next executable statement after the END IF statement.

The following example shows an IF construct containing several ELSE IF THEN statements and an ELSE statement:

Form Example
IF (expr) THEN IF (A .GT. B) THEN
block1 D = B
  F = A - B
ELSE IF (expr) THEN ELSE IF (A .GT. C) THEN
block2 D = C
  F = A - C
ELSE IF (expr) THEN ELSE IF (A .GT. Z) THEN
block3 D = Z
  F = A - Z
ELSE ELSE
block4 D = 0.0
  F = A
END IF END IF

If A is greater than B, block1 is executed. If A is not greater than B but is greater than C, block2 is executed. If A is not greater than B or C but is greater than Z, block3 is executed. If A is not greater than B, C, or Z, block4 is executed.

The following example shows a nested IF construct:

Form Example
IF (expr1) THEN IF (A .LT. 100) THEN
block1 INRAN = INRAN + 1
IF (expr2) THEN IF (ABS(A-AVG) .LE. 5.) THEN
block1a INAVG = INAVG + 1
ELSE ELSE
block1b OUTAVG = OUTAVG + 1
END IF END IF
ELSE ELSE
block2 OUTRAN = OUTRAN + 1
END IF END IF

If A is less than 100, the code immediately following the IF is executed. This code contains a nested IF construct. If the absolute value of A minus AVG is less than or equal to 5, block1a is executed. If the absolute value of A minus AVG is greater than 5, block1b is executed.

If A is greater than or equal to 100, block2 is executed, and the nested IF construct (in block1) is not executed.

The following example shows a named IF construct:



BLOCK_A: IF (D > 0.0) THEN        ! Initial statement for named construct

  RADIANS = ACOS(D)               ! These two statements
  DEGREES = ACOSD(D)              !       form a block

END IF BLOCK_A                    ! Terminal statement for named construct

7.8.2 IF Statement

The IF statement conditionally executes one statement based on the value of a logical expression. (This statement was called a logical IF statement in FORTRAN 77.)

The IF statement takes the following form:


  • IF (expr) stmt

expr

Is a scalar logical expression enclosed in parentheses.

stmt

Is any complete, unlabeled, executable Fortran statement, except for the following:
  • A CASE, DO, IF, FORALL, or WHERE construct
  • Another IF statement
  • The END statement for a program, function, or subroutine

When an IF statement is executed, the logical expression is evaluated first. If the value is true, the statement is executed. If the value is false, the statement is not executed and control transfers to the next statement in the program.

Examples

The following examples show valid IF statements:


IF (J.GT.4 .OR. J.LT.1) GO TO 250

IF (REF(J,K) .NE. HOLD) REF(J,K) = REF(J,K) * (-1.5D0)

IF (ENDRUN) CALL EXIT

7.9 PAUSE Statement

The PAUSE statement temporarily suspends program execution until the user or system resumes execution. The PAUSE statement is a deleted feature in Fortran 95; it was obsolescent in Fortran 90. HP Fortran fully supports features deleted in Fortran 95.

The PAUSE statement takes the following form:


  • PAUSE [pause-code]

pause-code

Is an optional message. It can be either of the following:
  • A scalar character constant of type default character.
  • A string of up to six digits; leading zeros are ignored. (Fortran 90 and FORTRAN 77 limit digits to five.)

Rules and Behavior

If you specify pause-code, the PAUSE statement displays the specified message and then displays the default prompt.

If you do not specify pause-code, the system displays the following default message:


FORTRAN PAUSE

The system prompt is then displayed.

Effect on OpenVMS Systems

The effect of PAUSE differs depending on whether the program is an interactive or batch process, as follows:

  • If a program is an interactive process, the program is suspended until you enter one of the following commands:
    • CONTINUE resumes execution at the next executable statement.
    • DEBUG resumes execution under control of the OpenVMS Debugger.
    • EXIT terminates execution.

    In general, most other commands also terminate execution.
  • If a program is a batch process, the program is not suspended. If you specify a value for pause-code, this value is written to SYS$OUTPUT.

Examples

The following examples show valid PAUSE statements:


PAUSE 701
PAUSE 'ERRONEOUS RESULT DETECTED'

For More Information:

  • On obsolescent features in Fortran 95 and Fortran 90, as well as features deleted in Fortran 95, see Appendix A.

7.10 RETURN Statement

The RETURN statement transfers control from a subprogram to the calling program unit.

The RETURN statement takes the following form:


  • RETURN [expr]

expr

Is a scalar expression that is converted to an integer value if necessary.

The expr is only allowed in subroutines; it indicates an alternate return. (An alternate return is an obsolescent feature in Fortran 95 and Fortran 90.)

Rules and Behavior

When a RETURN statement is executed in a function subprogram, control is transferred to the referencing statement in the calling program unit.

When a RETURN statement is executed in a subroutine subprogram, control is transferred to the first executable statement following the CALL statement that invoked the subroutine, or to the alternate return (if one is specified).

Examples

The following shows how alternate returns can be used in a subroutine:


   CALL CHECK(A, B, *10, *20, C)
   ...
10 ...
20 ...
   SUBROUTINE CHECK(X, Y, *, *, C)
   ...
50   IF (X) 60, 70, 80
60   RETURN
70   RETURN 1
80   RETURN 2
   END

The value of X determines the return, as follows:

  • If X < 0, a normal return occurs and control is transferred to the first executable statement following CALL CHECK in the calling program.
  • If X == 0, the first alternate return (RETURN 1) occurs and control is transferred to the statement identified with label 10.
  • If X > 0, the second alternate return (RETURN 2) occurs and control is transferred to the statement identified with label 20.

Note that an asterisk (*) specifies the alternate return. An ampersand (&) can also specify an alternate return in a CALL statement, but not in a subroutine's dummy argument list.

For More Information:

  • On the CALL statement, see Section 7.3.
  • On obsolescent features in Fortran 95 and Fortran 90, see Appendix A.

7.11 STOP Statement

The STOP statement terminates program execution before the end of the program unit. It takes the following form:


  • STOP [stop-code]

stop-code

Is an optional message. It can be either of the following:
  • A scalar character constant of type default character.
  • A string of up to six digits; leading zeros are ignored. (Fortran 95/90 and FORTRAN 77 limit digits to five.)

Effect on OpenVMS Systems

If you specify stop-code, the STOP statement displays the specified message at your terminal, terminates program execution, and returns control to the operating system.

If you do not specify stop-code, no message is displayed.

Examples

The following examples show valid STOP statements:


STOP 98
STOP 'END OF RUN'

DO
  READ *, X, Y
  IF (X > Y) STOP 5555
END DO


Chapter 8
Program Units and Procedures

This chapter describes:

8.1 Overview

A Fortran 95/90 program consists of one or more program units. There are four types of program units:

  • Main program
    The program unit that denotes the beginning of execution. It may or may not have a PROGRAM statement as its first statement.
  • External procedures
    Program units that are either user-written functions or subroutines.
  • Modules
    Program units that contain declarations, type definitions, procedures, or interfaces that can be shared by other program units.
  • Block data program units
    Program units that provide initial values for variables in named common blocks.

A program unit does not have to contain executable statements; for example, it can be a module containing interface blocks for subroutines.

A procedure can be invoked during program execution to perform a specific task. There are several kinds of procedures, as follows:

Kind of Procedure Description
External Procedure A procedure that is not part of any other program unit.
Module Procedure A procedure defined within a module
Internal Procedure 1 A procedure (other than a statement function) contained within a main program, function, or subroutine
Intrinsic Procedure A procedure defined by the Fortran language
Dummy Procedure A dummy argument specified as a procedure or appearing in a procedure reference
Statement function A computing procedure defined by a single statement

1The program unit that contains an internal procedure is called its host.

A function is invoked in an expression using the name of the function or a defined operator. It returns a single value (function result) that is used to evaluate the expression.

A subroutine is invoked in a CALL statement or by a defined assignment statement. It does not directly return a value, but values can be passed back to the calling program unit through arguments (or variables) known to the calling program.

Recursion (direct or indirect) is permitted for functions and subroutines.

A procedure interface refers to the properties of a procedure that interact with or are of concern to the calling program. A procedure interface can be explicitly defined in interface blocks. All program units, except block data program units, can contain interface blocks.

For More Information:

8.2 Main Program

A Fortran program must include one main program. It takes the following form:


  • [PROGRAM name]
  • [specification-part]
  • [execution-part]
  • [CONTAINS
  • internal-subprogram-part]
  • END [PROGRAM [name]]

name

Is the name of the program.

specification-part

Is one or more specification statements, except for the following:
  • INTENT (or its equivalent attribute)
  • OPTIONAL (or its equivalent attribute)
  • PUBLIC and PRIVATE (or their equivalent attributes)

An automatic object must not appear in a specification statement. If a SAVE statement is specified, it has no effect.

execution-part

Is one or more executable constructs or statements, except for ENTRY or RETURN statements.

internal-subprogram-part

Is one or more internal subprograms (defining internal procedures). The internal-subprogram-part is preceded by a CONTAINS statement.

Rules and Behavior

The PROGRAM statement is optional. Within a program unit, a PROGRAM statement can be preceded only by comment lines or an OPTIONS statement.

The END statement is the only required part of a program. If a name follows the END statement, it must be the same as the name specified in the PROGRAM statement.

The program name is considered global and must be unique. It cannot be the same as any local name in the main program or the name of any other program unit, external procedure, or common block in the executable program.

A main program must not reference itself (either directly or indirectly).

Examples

The following is an example of a main program:


PROGRAM TEST
  INTEGER C, D, E(20,20)     ! Specification part
  CALL SUB_1                 ! Executable part
...
CONTAINS
  SUBROUTINE SUB_1           ! Internal subprogram
  ...
  END SUBROUTINE SUB_1
END PROGRAM TEST

For More Information:

On the default name for a main program, see the HP Fortran for OpenVMS User Manual.

8.3 Modules and Module Procedures

A module contains specifications and definitions that can be used by one or more program units. For the module to be accessible, the other program units must reference its name in a USE statement, and the module entities must be public.

A module takes the following form:


  • MODULE name
  • [specification-part]
  • [CONTAINS
  • module-subprogram
  • [module-subprogram]...]
  • END [MODULE [name]]

name

Is the name of the module.

specification-part

Is one or more specification statements, except for the following:
  • ENTRY
  • FORMAT
  • AUTOMATIC (or its equivalent attribute)
  • INTENT (or its equivalent attribute)
  • OPTIONAL (or its equivalent attribute)
  • Statement functions

An automatic object must not appear in a specification statement.

module-subprogram

Is a function or subroutine subprogram that defines the module procedure. A function must end with END FUNCTION and a subroutine must end with END SUBROUTINE.

A module subprogram can contain internal procedures.

Rules and Behavior

If a name follows the END statement, it must be the same as the name specified in the MODULE statement.

The module name is considered global and must be unique. It cannot be the same as any local name in the main program or the name of any other program unit, external procedure, or common block in the executable program.

A module is host to any module procedures it contains, and entities in the module are accessible to the module procedures through host association.

A module must not reference itself (either directly or indirectly).

You can use the PRIVATE attribute to restrict access to procedures or variables within a module.

Although ENTRY statements, FORMAT statements, and statement functions are not allowed in the specification part of a module, they are allowed in the specification part of a module subprogram.

Any executable statements in a module can only be specified in a module subprogram.

A module can contain one or more procedure interface blocks, which let you specify an explicit interface for an external subprogram or dummy subprogram.

When creating a MODULE that contains datatype declarations, it is recommended that such declarations explicitly specify the kind of the datatype. If an explicit kind is omitted, the MODULE's declarations will be interpreted according to the command-line options in effect when the MODULE is imported, which may result in unintended behavior.

Every module subprogram of any HPF module must be of the same extrinsic kind as its host, and any module subprogram whose extrinsic kind is not given explicitly is assumed to be of that extrinsic kind.

Examples

The following example shows a simple module that can be used to provide global data:


MODULE MOD_A
  INTEGER :: B, C
  REAL E(25,5)
END MODULE MOD_A
...
SUBROUTINE SUB_Z
  USE MOD_A               ! Makes scalar variables B and C, and array
  ...                     !   E available to this subroutine
END SUBROUTINE SUB_Z

The following example shows a module procedure:


MODULE RESULTS
...
CONTAINS
  FUNCTION MOD_RESULTS(X,Y)  ! A module procedure
  ...
  END FUNCTION MOD_RESULTS
END MODULE RESULTS

The following example shows a module containing a derived type:


MODULE EMPLOYEE_DATA
  TYPE EMPLOYEE
    INTEGER ID
    CHARACTER(LEN=40) NAME
  END TYPE EMPLOYEE
END MODULE

The following example shows a module containing an interface block:


MODULE ARRAY_CALCULATOR
  INTERFACE
    FUNCTION CALC_AVERAGE(D)
      REAL :: CALC_AVERAGE
      REAL, INTENT(IN) :: D(:)
    END FUNCTION
  END INTERFACE
END MODULE ARRAY_CALCULATOR

The following example shows a derived-type definition that is public with components that are private:


MODULE MATTER
  TYPE ELEMENTS
    PRIVATE
    INTEGER C, D
  END TYPE
...
END MODULE MATTER

In this case, components C and D are private to type ELEMENTS, but type ELEMENTS is not private to MODULE MATTER. Any program unit that uses the module MATTER can declare variables of type ELEMENTS, and pass as arguments values of type ELEMENTS.

This design allows you to change components of a type without affecting other program units that use the module.

If a derived type is needed in more than one program unit, the definition should be placed in a module and accessed by a USE statement whenever it is needed, as follows:


MODULE STUDENTS
  TYPE STUDENT_RECORD
  ...
  END TYPE
CONTAINS
  SUBROUTINE COURSE_GRADE(...)
  TYPE(STUDENT_RECORD) NAME
  ...
  END SUBROUTINE
END MODULE STUDENTS
...

PROGRAM SENIOR_CLASS
  USE STUDENTS
  TYPE(STUDENT_RECORD) ID
  ...
END PROGRAM

Program SENIOR_CLASS has access to type STUDENT_RECORD, because it uses module STUDENTS. Module procedure COURSE_GRADE also has access to type STUDENT_RECORD, because the derived-type definition appears in its host.

For More Information:


Previous Next Contents Index