[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

HP Fortran for OpenVMS
Language Reference Manual


Previous Contents Index

7.5 CONTINUE Statement

The CONTINUE statement is primarily used to terminate a labeled DO construct when the construct would otherwise end improperly with either a GO TO, arithmetic IF, or other prohibited control statement.

The CONTINUE statement takes the following form:


  • CONTINUE

The statement by itself does nothing and has no effect on program results or execution sequence.

The following example shows a CONTINUE statement:


    DO 150 I = 1,40
40  Y = Y + 1
    Z = COS(Y)
    PRINT *, Z
    IF (Y .LT. 30) GO TO 150
    GO TO 40
150 CONTINUE

7.6 DO Constructs

The DO construct controls the repeated execution of a block of statements or constructs. (This repeated execution is called a loop.)

The number of iterations of a loop can be specified in the initial DO statement in the construct, or the number of iterations can be left indefinite by a simple DO ("DO forever") construct or DO WHILE statement.

The EXIT and CYCLE statements modify the execution of a loop. An EXIT statement terminates execution of a loop, while a CYCLE statement terminates execution of the current iteration of a loop. For example:



DO
  READ (EUNIT, IOSTAT=IOS) Y
  IF (IOS /= 0) EXIT
  IF (Y < 0) CYCLE
  CALL SUB_A(Y)
END DO

If an error or end-of-file occurs, the DO construct terminates. If a negative value for Y is read, the program skips to the next READ statement.

For More Information:

7.6.1 Forms for DO Constructs

A DO construct takes one of the following forms:

Block Form


  • [name:] DO [label][,] [loop-control]
  • block
  • [label] term-stmt

Nonblock Form


  • DO label[,] [loop-control]

name

Is the name of the DO construct.

label

Is a statement label identifying the terminal statement.

loop-control

Is a DO iteration (see Section 7.6.2.1) or a (DO) WHILE statement (see Section 7.6.3).

block

Is a sequence of zero or more statements or constructs.

term-stmt

Is the terminal statement for the construct.

Rules and Behavior

A block DO construct is terminated by an END DO or CONTINUE statement. If the block DO statement contains a label, the terminal statement must be identified with the same label. If no label appears, the terminal statement must be an END DO statement.

If a construct name is specified in a block DO statement, the same name must appear in the terminal END DO statement. If no construct name is specified in the block DO statement, no name can appear in the terminal END DO statement.

A nonblock DO construct is terminated by an executable statement (or construct) that is identified by the label specified in the nonblock DO statement. A nonblock DO construct can share a terminal statement with another nonblock DO construct. A block DO construct cannot share a terminal statement.

The following cannot be terminal statements for nonblock DO constructs:

  • CONTINUE (allowed if it is a shared terminal statement)
  • CYCLE
  • END (for a program or subprogram)
  • EXIT
  • GO TO (unconditional or assigned)
  • Arithmetic IF
  • RETURN
  • STOP

The nonblock DO construct is an obsolescent feature in Fortran 95 and Fortran 90.

Examples

The following example shows equivalent block DO and nonblock DO constructs:


   DO I = 1, N                ! Block DO
     TOTAL = TOTAL + B(I)
   END DO

   DO 20 I = 1, N             ! Nonblock DO
20 TOTAL = TOTAL + B(I)

The following example shows a simple block DO construct (contains no iteration count or DO WHILE statement):


DO
  READ *, N
  IF (N == 0) STOP
  CALL SUBN
END DO

The DO block executes repeatedly until the value of zero is read. Then the DO construct terminates.

The following example shows a named block DO construct:


LOOP_1: DO I = 1, N
          A(I) = C * B(I)
        END DO LOOP_1

The following example shows a nonblock DO construct with a shared terminal statement:


   DO 20 I = 1, N
   DO 20 J = 1 + I, N
20 RESULT(I,J) = 1.0 / REAL(I + J)

For More Information:

On obsolescent features in Fortran 95 and Fortran 90, see Appendix A.

7.6.2 Execution of DO Constructs

The range of a DO construct includes all the statements and constructs that follow the DO statement, up to and including the terminal statement. If the DO construct contains another construct, the inner (nested) construct must be entirely contained within the DO construct.

Execution of a DO construct differs depending on how the loop is controlled, as follows:

  • For simple DO constructs, there is no loop control. Statements in the DO range are repeated until the DO statement is terminated explicitly by a statement within the range.
  • For iterative DO statements, loop control is specified as do-var = expr1, expr2 [,expr3]. An iteration count specifies the number of times the DO range is executed. (For more information on iteration loop control, see Section 7.6.2.1.)
  • For DO WHILE statements, loop control is specified as a DO range. The DO range is repeated as long as a specified condition remains true. Once the condition is evaluated as false, the DO construct terminates. (For more information on the DO WHILE statement, see Section 7.6.3.)

7.6.2.1 Iteration Loop Control

DO iteration loop control takes the following form:


  • do-var = expr1, expr2 [,expr3]

do-var

Is the name of a scalar variable of type integer or real. It cannot be the name of an array element or structure component.

expr

Is a scalar numeric expression of type integer or real. If it is not the same type as do-var, it is converted to that type.

Rules and Behavior

A DO variable or expression of type real is a deleted feature in Fortran 95; it was obsolescent in Fortran 90. HP Fortran fully supports features deleted in Fortran 95.

The following steps are performed in iteration loop control:

  1. The expressions expr1, expr2, and expr3 are evaluated to respectively determine the initial, terminal, and increment parameters.
    The increment parameter (expr3) is optional and must not be zero. If an increment parameter is not specified, it is assumed to be of type default integer with a value of 1.
  2. The DO variable (do-var) becomes defined with the value of the initial parameter (expr1).
  3. The iteration count is determined as follows:
    MAX(INT((expr2 - expr1 + expr3) / expr3), 0)

    The iteration count is zero if either of the following is true:
    expr1 > expr2 and expr3 > 0
    expr1 < expr2 and expr3 < 0
  4. The iteration count is tested. If the iteration count is zero, the loop terminates and the DO construct becomes inactive. (A compiler option can affect this; see the HP Fortran for OpenVMS User Manual for more information.) If the iteration count is nonzero, the range of the loop is executed.
  5. The iteration count is decremented by one, and the DO variable is incremented by the value of the increment parameter, if any.

After termination, the DO variable retains its last value (the one it had when the iteration count was tested and found to be zero).

The DO variable must not be redefined or become undefined during execution of the DO range.

If you change variables in the initial, terminal, or increment expressions during execution of the DO construct, it does not affect the iteration count. The iteration count is fixed each time the DO construct is entered.

Examples

The following example specifies 25 iterations:


DO 100 K=1,50,2

K=49 during the final iteration, K=51 after the loop.

The following example specifies 27 iterations:


DO 350 J=50,-2,-2

J=--2 during the final iteration, J=--4 after the loop.

The following example specifies 9 iterations:


DO NUMBER=5,40,4

NUMBER=37 during the final iteration, NUMBER=41 after the loop. The terminating statement of this DO loop must be END DO.

For More Information:

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

7.6.2.2 Nested DO Constructs

A DO construct can contain one or more complete DO constructs (loops). The range of an inner nested DO construct must lie completely within the range of the next outer DO construct. Nested nonblock DO constructs can share a labeled terminal statement.

Figure 7-2 shows correctly and incorrectly nested DO constructs.

Figure 7-2 Nested DO Constructs


In a nested DO construct, you can transfer control from an inner construct to an outer construct. However, you cannot transfer control from an outer construct to an inner construct.

If two or more nested DO constructs share the same terminal statement, you can transfer control to that statement only from within the range of the innermost construct. Any other transfer to that statement constitutes a transfer from an outer construct to an inner construct, because the shared statement is part of the range of the innermost construct.

7.6.2.3 Extended Range

A DO construct has an extended range if both of the following are true:

  • The DO construct contains a control statement that transfers control out of the construct.
  • Another control statement returns control back into the construct after execution of one or more statements.

The range of the construct is extended to include all executable statements between the destination statement of the first transfer and the statement that returns control to the construct.

The following rules apply to a DO construct with extended range:

  • A transfer into the range of a DO statement is permitted only if the transfer is made from the extended range of that DO statement.
  • The extended range of a DO statement must not change the control variable of the DO statement.

Figure 7-3 illustrates valid and invalid extended range control transfers.

Figure 7-3 Control Transfers and Extended Range


7.6.3 DO WHILE Statement

The DO WHILE statement executes the range of a DO construct while a specified condition remains true. The statement takes the following form:


  • DO [label][,] WHILE (expr)

label

Is a label specifying an executable statement in the same program unit.

expr

Is a scalar logical expression enclosed in parentheses.

Rules and Behavior

Before each execution of the DO range, the logical expression is evaluated. If it is true, the statements in the body of the loop are executed. If it is false, the DO construct terminates and control transfers to the statement following the loop.

If no label appears in a DO WHILE statement, the DO WHILE loop must be terminated with an END DO statement.

You can transfer control out of a DO WHILE loop but not into a loop from elsewhere in the program.

Examples

The following example shows a DO WHILE statement:


CHARACTER*132 LINE
...
I = 1
DO WHILE (LINE(I:I) .EQ. ' ')
  I = I + 1
END DO

The following examples show required and optional END DO statements:

Required Optional
DO WHILE (I .GT. J) DO 10 WHILE (I .GT. J)
ARRAY(I,J) = 1.0 ARRAY(I,J) = 1.0
I = I - 1 I = I - 1
END DO 10 END DO

7.6.4 CYCLE Statement

The CYCLE statement interrupts the current execution cycle of the innermost (or named) DO construct.

The CYCLE statement takes the following form:


  • CYCLE [name]

name

Is the name of the DO construct.

Rules and Behavior

When a CYCLE statement is executed, the following occurs:

  1. The current execution cycle of the named (or innermost) DO construct is terminated.
    If a DO construct name is specified, the CYCLE statement must be within the range of that construct.
  2. The iteration count (if any) is decremented by 1.
  3. The DO variable (if any) is incremented by the value of the increment parameter (if any).
  4. A new iteration cycle of the DO construct begins.

Any executable statements following the CYCLE statement (including a labeled terminal statement) are not executed.

A CYCLE statement can be labeled, but it cannot be used to terminate a DO construct.

Examples

The following example shows a CYCLE statement:



DO I =1, 10
  A(I) = C + D(I)
  IF (D(I) < 0) CYCLE    ! If true, the next statement is omitted
  A(I) = 0               ! from the loop and the loop is tested again.
END DO

7.6.5 EXIT Statement

The EXIT statement terminates execution of a DO construct. It takes the following form:


  • EXIT [name]

name

Is the name of the DO construct.

Rules and Behavior

The EXIT statement causes execution of the named (or innermost) DO construct to be terminated.

If a DO construct name is specified, the EXIT statement must be within the range of that construct.

Any DO variable present retains its last defined value.

An EXIT statement can be labeled, but it cannot be used to terminate a DO construct.

Examples

The following example shows an EXIT statement:



LOOP_A : DO I = 1, 15
  N = N + 1
  IF (N > I) EXIT LOOP_A
END DO LOOP_A

7.7 END Statement

The END statement marks the end of a program unit. It takes one of the following forms:


  • END [PROGRAM [program-name]]
  • END [FUNCTION [function-name]]
  • END [SUBROUTINE [subroutine-name]]
  • END [MODULE [module-name]]
  • END [BLOCK DATA [block-data-name]]

For internal procedures and module procedures, you must specify the FUNCTION and SUBROUTINE keywords in the END statement; otherwise, the keywords are optional.

In main programs, function subprograms, and subroutine subprograms, END statements are executable and can be branch target statements. If control reaches the END statement in these program units, the following occurs:

  • In a main program, execution of the program terminates.
  • In a function or subroutine subprogram, a RETURN statement is implicitly executed.

The END statement cannot be continued in a program unit, and no other statement in the program unit can have an initial line that appears to be the program unit END statement.

The END statements in a module or block data program unit are nonexecutable.

For More Information:

7.8 IF Construct and Statement

The IF construct conditionally executes one block of statements or constructs.

The IF statement conditionally executes one statement.

The decision to transfer control or to execute the statement or block is based on the evaluation of a logical expression within the IF statement or construct.

For More Information:

On the arithmetic IF statement, see Section 7.2.4.

7.8.1 IF Construct

The IF construct conditionally executes one block of constructs or statements depending on the evaluation of a logical expression. (This construct was called a block IF statement in FORTRAN 77.)

The IF construct takes the following form:


  • [name:] IF (expr) THEN
  • block
  • [ELSE IF (expr) THEN [name]
  • block]...
  • [ELSE [name]
  • block]
  • END IF [name]

name

Is the name of the IF construct.

expr

Is a scalar logical expression enclosed in parentheses.

block

Is a sequence of zero or more statements or constructs.

Rules and Behavior

If a construct name is specified at the beginning of an IF THEN statement, the same name must appear in the corresponding END IF statement. The same construct name must not be used for different named constructs in the same scoping unit.

Depending on the evaluation of the logical expression, one block or no block is executed. The logical expressions are evaluated in the order in which they appear, until a true value is found or an ELSE or END IF statement is encountered.

Once a true value is found or an ELSE statement is encountered, the block immediately following it is executed and the construct execution terminates.

If none of the logical expressions evaluate to true and no ELSE statement appears in the construct, no block in the construct is executed and the construct execution terminates.

Note

No additional statement can be placed after the IF THEN statement in a block IF construct. For example, the following statement is invalid in the block IF construct:


IF (e) THEN I = J


This statement is translated as the following logical IF statement:


IF (e) THENI = J

You cannot use branching statements to transfer control to an ELSE IF statement or ELSE statement. However, you can branch to an END IF statement from within the IF construct.

Figure 7-4 shows the flow of control in IF constructs.

Figure 7-4 Flow of Control in IF Constructs


You can include an IF construct in the statement block of another IF construct, if the nested IF construct is completely contained within a statement block. It cannot overlap statement blocks.

Examples

The following example shows the simplest form of an IF construct:

Form Example
IF (expr) THEN IF (ABS(ADJU) .GE. 1.0E-6) THEN
block TOTERR = TOTERR + ABS(ADJU)
  QUEST = ADJU/FNDVAL
END IF END IF

This construct conditionally executes the block of statements between the IF THEN and the END IF statements.

The following example shows an IF construct containing an ELSE statement:

Form Example
IF (expr) THEN IF (NAME .LT. 'N') THEN
block1 IFRONT = IFRONT + 1
  FRLET(IFRONT) = NAME(1:2)
ELSE ELSE
block2 IBACK = IBACK + 1
END IF END IF

Block1 consists of all the statements between the IF THEN and ELSE statements. Block2 consists of all the statements between the ELSE and the END IF statements.

If the value of the character variable NAME is less than ' N ' , block1 is executed. If the value of NAME is greater than or equal to ' N ' , block2 is executed.

The following example shows an IF construct containing an ELSE IF THEN 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. B/2.) THEN
block2 D = B/2.
  F = A - B/2.
END IF END IF


Previous Next Contents Index