Chapter 8. Controlling Execution

A program performs its computation by executing the statements in sequence from beginning to end. Control constructs and branching statements modify this normal sequential execution of a program. The modification can select blocks of statements and constructs for execution or repetition, or can transfer control to another statement in the program.

As outlined in Chapter 2, “Fortran Concepts and Terms”, the statements and constructs making up a program are of two sorts, nonexecutable and executable. The nonexecutable statements establish the environment under which the program runs. The executable statements and executable constructs, some of which are action statements, perform computations, assign values, perform input/output (I/O) operations, or control the sequence in which the other executable statements and constructs are executed. This chapter describes the latter group of executable statements, the control statements and control constructs.

Control constructs and control statements alter the usual sequential execution order of statements and constructs in a program. This execution order is called the normal execution sequence. The control constructs are block constructs and consist of the IF construct, the DO construct, and the CASE construct. A nonblock form of the DO construct is also available. Individual statements that alter the normal execution sequence include the CYCLE and EXIT statements which are special statements for DO constructs, branch statements such as arithmetic IF statements, various forms of GO TO statements, and the statements that cause execution to cease such as the STOP and PAUSE statements.

With any of the block constructs, a construct name can be used to identify the construct and to identify which DO construct, particularly in a nest of DO constructs, is being terminated or cycled when using the EXIT or CYCLE statements.

8.1. The Execution Sequence

There is an established execution sequence for action statements in a Fortran program. Normally, a program or subprogram begins with the first executable statement in that program or subprogram and continues with the next executable statement in the order in which these statements appear. However, there are executable constructs and statements that cause statements to be executed in an order that is different from the order in which they appear in the program. These are either control constructs or branching statements.

There are two basic ways to affect the execution sequence. One is to use an executable construct that selects a block of statements and constructs for execution. The second is to execute a statement that branches to a specific statement in the program. In almost all cases, the use of constructs will result in programs that are more readable and maintainable, so constructs are discussed first, followed by branching statements.

8.2. Blocks and Executable Constructs

A control construct consists of one or more blocks of statements and constructs and the control logic that explicitly or implicitly encloses these blocks. Based on a control condition, a block of statements and constructs is selected for execution. A block is a sequence of zero or more statements and constructs, and it is defined as follows:

 

block

is

[ execution_part_construct  ... ]

A block of statements and constructs is treated as a whole. Either the block as a whole is executed or it is not executed. Whether or not the block is executed is determined by expressions in the control logic of the construct. Note that not every statement or construct in the block need be executed; for example, a branch statement early in the block can prevent subsequent statements in the block from being executed. This is still considered a complete execution of the block.

An executable construct consists of one or more blocks of statements surrounded by control statements. The construct usually contains an initial statement before a block and a terminal statement after the block. The construct includes conditions that determine which block in the construct is executed.

There are three executable constructs that contain blocks:

  • IF construct

  • CASE construct

  • DO construct

There is also a construct called the WHERE construct that controls array assignment for individual elements (masked array assignment) as opposed to controlling flow of the program statements. Even though it looks like a control construct, it really is a construct for unconditional but masked array assignment. For information on masked array assignment, see Section 7.5.4 in Chapter 7.

Construct names are described in the introductory material for blocks and also with each construct and statement that uses them. The name, if used, must appear on the same line as the initial statement of the construct and a matching name must appear on the terminal statement of the construct.

Some of the general rules and restrictions that apply to blocks and control of blocks are as follows:

  • The statements of a block are executed in order unless there is a control construct or statement within the block that changes the sequential order.

  • A block, as an integral unit, must be completely contained within a construct.

  • A block can be empty; that is, it can contain no statements or constructs at all.

  • A branching or control construct within a block that transfers to a statement or construct within the same block is permitted.

  • Branching to a statement or construct within a block from outside the block is prohibited. (Even branching to the first executable statement within a block from outside the block is prohibited.)

  • Exiting from a block can be done from anywhere within the block.

  • References to procedures are permitted within a block.

8.3. IF Construct and IF Statement

An IF construct selects at most one block of statements and constructs within the construct for execution. The IF statement controls the execution of only one statement; in previous Fortran standards it was called the logical IF statement. The arithmetic IF statement is not the same as the IF statement; it is a branching statement that is designated as obsolescent.

8.3.1. The IF Construct

The IF construct contains one or more executable blocks. At most one block is executed. It is possible for no block to be executed when there is no ELSE statement.

8.3.1.1. Form of the IF Construct

The IF construct is defined as follows:

 

if_construct

is

if_then_stmt
    block
  [ else_if_stmt
    block ] ...
  [ else_stmt
    block ]
end_if_stmt

 

if_then_stmt

is

[ if_construct_name :] IF (scalar_logical_expr) THEN

 

else_if_stmt

is

ELSE IF (scalar_logical_expr) THEN [ if_construct_name ]

 

else_stmt

is

ELSE [ if_construct_name ]

 

end_if_stmt

is

END IF [ if_construct_name ]

Branching to an ELSE IF or an ELSE statement is prohibited.

Branching to an END IF statement is allowed from any block within the IF construct.

If a construct name appears on the IF-THEN statement, the same name must appear on the corresponding END IF statement.

The construct names on the ELSE IF and ELSE statements are optional, but if present must be the same name as the one on the IF-THEN statement. If one such ELSE IF or ELSE statement has a construct name, the others are not required to have a construct name.

The same construct name must not be used for different named constructs in the same scoping unit; thus, two IF constructs must not be both named INNER in the same executable part, for example.

8.3.1.2. Execution of the IF Construct

The logical expressions are evaluated in order until one is found to be true. The block following the first true condition is executed, and the execution of the IF construct terminates. Subsequent true conditions in the construct have no effect. There may be no logical expressions found to be true in the construct. In this case, the block following the ELSE statement is executed if there is one; otherwise, no block in the construct is executed.

Figure 8-1 indicates the execution flow for an IF construct.

Figure 8-1. Execution flow for an IF construct

Execution flow for an  IF construct

Example:

IF (I < J) THEN
   X = Y + 5.0
ELSE IF (I > 100) THEN
   X = 0.0
   Y = -1.0
ELSE
   X = -1.0
   Y = 0.0
END IF

If I is less than J, the statement X = Y + 5.0 is executed and execution proceeds following the END IF statement. If I .GE. J and if I > 100, the two statements following the ELSE IF statement are executed and execution proceeds following the END IF statement. If neither of these conditions is true, the block after the ELSE statement is executed.

8.3.2. IF Statement

The IF statement controls a single action statement, as opposed to a block of statements.

8.3.2.1. Form of the IF Statement

The IF statement is defined as follows:

 

if_stmt

is

IF (scalar_logical_expr) action_stmt

Example:

IF (S < T) S = 0.0

8.3.2.2. Execution of the IF Statement

The scalar logical expression is evaluated. If true, the action statement is executed. If false, the action statement is not executed, and control passes to the next statement in the program.

The action statement must not be an IF statement or an END statement for a program, function, or subroutine. Note that the action statement cannot be any of the other END statements, such as END DO because they are not action statements.

If the logical expression contains a function reference, its evaluation may have side effects that modify the action statement.

A complete list of the action statements can be found in Section 2.5 in Chapter 2. Action statements change the definition state of variables or the condition of the I/O system, or are control statements. Specification statements such as type declaration statements, FORMAT statements, and ENTRY statements are not action statements. Note that constructs are not action statements.

8.4. CASE Construct

The CASE construct, like the IF construct, consists of a number of blocks, of which at most one is selected for execution. The selection is based on the value of the scalar expression in the SELECT CASE statement at the beginning of the construct; the value of this expression is called the case index. The case selected is the one for which the case index matches a case selector value in a CASE statement. There is an optional default case that, in effect, matches all values not matched by any other CASE statement in the construct.

8.4.1. Form of the CASE Construct

The general form of the CASE construct is as follows:

[ case_construct_name : ] SELECT CASE (case_expression)
  [ CASE (case_value_range_list) [ case_construct_name ]
    block ] ...
  [ CASE DEFAULT [ case_construct_name ]
    block ]
END SELECT [ case_construct_name ]

The case construct is defined as follows:

 

case_construct

is

select_case_stmt
  [ case_stmt
    block ] ...
end_select_stmt

 

select_case_stmt

is

[ case_construct_name : ] SELECT CASE (case_expr)

 

case_stmt

is

CASE case_selector [ case_construct_name ]

 

end_select_stmt

is

END SELECT [ case_construct_name ]

 

case_expr

is

scalar_int_expr

 

 

or

scalar_char_expr

 

 

or

scalar_logical_expr

 

case_selector

is

(case_value_range_list)

 

 

or

DEFAULT

 

case_value_range

is

case_value

 

 

or

case_value :

 

 

or

: case_value

 

 

or

case_value : case_value

 

case_value

is

scalar_int_initialization_expr

 

 

or

scalar_char_initialization_expr

 

 

or

scalar_logical_initialization_expr

The statement containing the keywords SELECT CASE is called the SELECT CASE statement. The statement beginning with the keyword CASE is called the CASE statement. The statement beginning with the keywords END SELECT is called the END SELECT statement. A case value range list enclosed in parenthesis or the DEFAULT keyword is called a case selector.

If a construct name is present on a SELECT CASE statement, it must also appear on the END SELECT statement.

Any of the case selector statements may or may not have a construct name. If one does, it must be the same name as the construct name on the SELECT CASE statement.

A CASE statement with the case selector DEFAULT is optional. If it is present, it is not required to be the last CASE statement.

The case_expr must be a scalar expression of type integer, character, or logical.

Within a particular CASE construct, the case expression and all case values must be of the same type and must have the same kind type parameter values. If the character type is used, different character lengths are allowed.

Each case_value must be a scalar initialization expression of the same type as the case expression. An initialization expression is an expression that can be evaluated at compile time; that is, essentially, a constant expression.

The colon forms of the case values expressing a range can be used for expressions in the construct of type integer and character but not type logical. For example, the following CASE statement would select all character strings that collate between BOOK and DOG, inclusive:

CASE ('BOOK':'DOG')

After expression evaluation, there must be no more than one case selector that matches the case index. In other words, overlapping case values and case ranges are prohibited.

Branching to the END SELECT statement is allowed only from within the construct. Branching to a CASE statement is prohibited; branching to the SELECT CASE statement is allowed, however.

The following example shows the CASE construct:

! Compute the area with a formula  appropriate for
! the shape of the object
FIND_AREA: &
   SELECT CASE (OBJECT)
     CASE (CIRCLE)
         AREA = PI * RADIUS ** 2
     CASE (SQUARE)
         AREA = SIDE * SIDE
     CASE (RECTANGLE)
         AREA = LENGTH * WIDTH
     CASE DEFAULT
        PRINT*, "Unable to compute area."
   END SELECT  FIND_AREA

8.4.2. Execution of the CASE Construct

The case index (the scalar expression) in the SELECT CASE statement is evaluated in anticipation of matching one of the case values preceding the blocks. The case index must match at most one of the selector values. The block following the case matched is executed, the CASE construct terminates, and control passes to the next executable statement or construct following the END SELECT statement of the construct. If no match occurs and the CASE DEFAULT statement is present, the block after the CASE DEFAULT statement is selected. If there is no CASE DEFAULT statement, the CASE construct terminates, and the next executable statement or construct following the END SELECT statement of the construct is executed. If the case value is a single value, a match occurs if the index is equal to the case value (determined by the rules used in evaluating the equality or equivalence operator). If the case value is a range of values, there are three possibilities to determine a match depending on the form of the range:

Case value range

Condition for a match

case_value 1 : case_value2

case_value 1case_index case_value2

case_value :

case_value case_index

: case_value

case_value case_index

Figure 8-2, illustrates the execution of a CASE construct.

Figure 8-2. Execution flow for a CASE construct

Execution flow for a  CASE construct

Example 1:

INDEX = 2
SELECT CASE (INDEX)
  CASE (1)
     X = 1.0
  CASE (2)
     X = 2.0
  CASE DEFAULT
     X = 99.0
END SELECT

The case expression INDEX has the value 2. The block following the case value of 2 is executed; that is, the statement X = 2.0 is executed, and execution of the CASE construct terminates.

Example 2:

COLOR = 'GREEN'
SELECT CASE (COLOR)
  CASE ('RED')
     STOP
  CASE ('YELLOW')
     CALL  PROCEED_IF_YOU_CAN_SAFELY
  CASE ('GREEN')
     CALL  GO_AHEAD
END SELECT

This example uses selectors of type character. The expression COLOR has the value GREEN, and therefore the procedure GO_AHEAD is executed. When it returns, the execution of the CASE statement terminates, and the executable statement after the END SELECT statement executes next.

8.5. DO Construct

The DO construct controls the number of times a sequence of statements and constructs within the range of a loop is executed. There are three steps in the execution of a DO construct:

  1. If execution of the DO construct is controlled by a DO variable, the expressions representing the parameters that determine the number of times the range is to be executed are evaluated (step 1 of Figure 8-3).

  2. A decision is made as to whether the range of the loop is to be executed (step 2 of Figure 8-3).

  3. If appropriate, the range of the loop is executed (step 3a of Figure 8-3); the DO variable, if present, is updated (step 3b of Figure 8-3); and step 2 is repeated.

    Figure 8-3. Execution flow for a DO construct

    Execution flow for a  DO construct

DO loop execution can be controlled by a DO variable that is incremented a certain number of times as prescribed in the initial DO statement, a DO WHILE construct, or a simple DO.

There are two basic forms of the DO construct, the block DO and the nonblock DO.

Modern programming practice favors the block DO form, so the block DO form is the recommended construct. The nonblock DO form is obsolescent. The block DO contains all of the functionality of the nonblock DO and vice versa. Indeed, both forms of DO construct permit the DO WHILE and DO forever forms of loops. The feature distinguishing the two forms is that the block DO construct is always terminated by an END DO or CONTINUE statement whereas the nonblock DO construct either terminates with an action statement or shares a termination statement with another nonblock DO construct.

The following example shows a block DO construct:

DO I = 1, N
  SUM = SUM + A(I)
END DO

8.5.1. Form of the Block DO Construct

The block DO construct is a DO construct that terminates with an END DO statement or a CONTINUE statement that is not shared with another DO construct.

The block DO construct is defined as follows:

 

block_do_construct

is

do_stmt
  do_block
end_do

 

do_stmt

is

label_do_stmt

 

 

or

nonlabel_do_stmt

 

label_do_stmt

is

[ do_construct_name : ] DO label [ loop_control ]

 

nonlabel_do_stmt

is

[ do_construct_name : ] DO [ loop_control ]

 

loop_control

is

[, ] do_variable = scalar_int_expr

 

 

 

  scalar_int_expr [ , scalar_int_expr ]

 

 

or

[ , ] WHILE (scalar_logical_expr)

 

do_variable

is

scalar_int_variable

 

do_block

is

block

 

end_do

is

end_do_stmt

 

 

or

continue_stmt

 

end_do_stmt

is

END DO [ do_construct_name ]

The DO variable must be a scalar named variable of type integer. (This excludes variables that are array elements, structures, and components of structures.)

Each scalar numeric expression in the loop control must be of type integer.

If the DO statement of a block DO construct has a construct name, the corresponding end_do must be an END DO statement that has the same construct name. If the DO statement of a block DO construct does not have a construct name, the corresponding end_do must not have a construct name.

If the DO statement does not contain a label, the corresponding end_do must be an END DO statement. If the DO statement does contain a label, the corresponding end_do must be identified with the same label. By definition, a block DO construct cannot share its terminal statement with another DO construct, even if it is a labeled statement. If a DO construct does share its terminal statement with another DO construct, it is a nonblock DO construct. Refer to the following examples:

SUM = 0.0
DO I = 1, N
  SUM = SUM + X(I) ** 2
END DO

FOUND = .FALSE.
I = 0
DO WHILE (.NOT. FOUND .AND. I < LIMIT )
  IF (KEY == X(I))  THEN
    FOUND = .TRUE.
  ELSE
    I = I + 1
  END IF
END DO

NUM_ITERS = 0
DO
  ! F and F_PRIME are functions
  X1 = X0 - F(X0) / F_PRIME(X0)
  IF (ABS(X1-X0) < SPACING(X0) .OR. &
      NUM_ITERS > MAX_ITERS)  EXIT
  X0 = X1
  NUM_ITERS = NUM_ITERS + 1
END DO

INNER_PROD = 0.0
DO 10 I = 1, 10
   INNER_PROD = INNER_PROD + X(I) * Y(I)
10 CONTINUE

LOOP: DO I = 1, N
        Y(I) = A * X(I) + Y(I)
      END DO LOOP

Although a DO construct can have both a label and a construct name, use of both is not in the spirit of modern programming practice where the use of labels is minimized.

8.5.2. Form of the Nonblock DO Construct

The nonblock DO construct is a DO construct that either shares a terminal statement with another DO construct, or the terminal statement is an action statement. The nonblock DO construct always uses a label to specify the terminal statement of the construct.


Note: The Fortran standard has declared the nonblock DO construct to be obsolescent.

The nonblock DO construct that ends with an action statement is defined as follows:

 

nonblock_do_construct

is

action_term_do_construct

 

 

or

outer_shared_do_construct

 

action_term_do_construct

is

label_do_stmt
  do_body
  do_term_action_stmt

 

do_body

is

[ execution_part_construct ] ...

 

do_term_action_stmt

is

action_stmt

The nonblock DO construct that shares a termination statement is defined as follows:

 

nonblock_do_construct

is

action_term_do_construct

 

 

or

outer_shared_do_construct

 

outer_shared_do_construct

is

label_do_stmt
  do_body
  shared_term_do_construct

 

shared_term_do_construct

is

outer_shared_do_construct

 

 

or

inner_shared_do_construct

 

inner_shared_do_construct

is

label_do_stmt
  do_body
  do_term_shared_stmt

 

do_term_shared_stmt

is

action_stmt

The last statement in a nonblock DO construct (the statement in which the loop label is defined), is called the DO termination or terminal statement of that construct.

An action_term_do_construct is a nonblock DO construct that does not share its DO termination with any other nonblock DO construct. An outer_shared_do_construct is a nonblock DO construct that shares its DO termination with at least one inner nonblock DO construct.

The DO termination of an action_term_do_construct must not be one of the following:

  • A GO TO statement

  • A RETURN statement

  • A STOP statement

  • An EXIT statement

  • A CYCLE statement

  • An END statement for a program or subprogram

  • An arithmetic IF statement

Note that a do_term_action_stmt is an action_stmt. A CONTINUE statement is an action_stmt, but by definition, if a DO construct ends with a CONTINUE statement, it is a block DO construct. Also note that a do_term_action_stmt cannot be any kind of END statement; END statements other than program or subprogram END statements are not specifically named in the preceding list because they are not action_stmts.

The DO termination must be identified with a label and the corresponding DO statement must refer to the same label.

The DO termination of an outer_shared_do_construct must not be a GO TO statement, a RETURN statement, a STOP statement, an EXIT statement, a CYCLE statement, an END statement for a program or subprogram, an arithmetic IF statement, or an assigned GO TO statement. Note that DO termination cannot be any other END statement because the other END statements are not action_stmts.

The DO termination must be identified with a label and all DO statements of the shared termination DO construct must refer to the same label.

The following are examples of DO constructs that are nonblock DO constructs because the DO terminations are action statements.

   PROD = 1.0
   DO 10 I = 1, N
10   PROD = PROD * P(I)

   FOUND = .FALSE.
   I = 0
   DO 10 WHILE (.NOT. FOUND .AND. I < LIMIT)
     I = I + 1
10   FOUND = KEY == X(I)

The following are examples of DO constructs that are nonblock DO constructs because the DO terminations are shared.

   DO 10 I = 1, N
     DO 10 J = 1, N
10     HILBERT(I, J) = 1.0 / REAL(I + J)

   DO 20 I = 1, N
     DO 20 J = I+1, N
       T = A(I, J); A(I, J) = A(J, I); A(J, I) = T
20 CONTINUE

8.5.3. Range of a DO Construct

The range of a DO construct consists of all statements and constructs following the DO statement, bounded by and including the terminal statement. The DO range can contain constructs, such as an IF construct, a CASE construct, or another DO construct, but the inner construct or constructs must be entirely enclosed within the nearest outer construct. If the range of a DO construct contains another construct, the constructs are said to be nested.

A branch to a statement within the range of a DO construct is diagnosed by the compiler as being unsafe.


Note: The Fortran standard prohibits a branch into the range of a DO construct.


8.5.4. Active and Inactive DO Constructs

A DO construct is either active or inactive. A DO construct becomes active when the DO statement is executed. A DO construct becomes inactive when any one of the following situations occurs:

  • The iteration count is zero at the time it is tested.

  • The WHILE condition is false at the time it is tested.

  • An EXIT statement is executed that causes an exit from the DO construct or any DO construct containing the DO construct.

  • A CYCLE statement is executed that causes cycling of any DO construct containing the DO construct.

  • There is a transfer of control out of the DO construct.

  • A RETURN statement in the DO construct is executed.

  • The program terminates for any reason.

8.5.5. Execution of DO Constructs

There are three forms of DO constructs, each with its own rules for execution: a DO construct with an iteration count, a DO WHILE construct, and a simple DO construct.

8.5.5.1. DO Construct with an Iteration Count

In this case, an iteration count controls the number of times the range of the loop is executed.

The general form of a DO statement using an iteration count is as follows:

DO [ label ] [ , ] do_variable = start_expr, end_expr [, inc_expr ]

The DO variable and the expressions may be of type integer. The following are examples of the iterative DO statement:

DO 10 I = 1, N
DO, J = -N, N
DO K = N, 1, -1

8.5.5.1.1. The Iteration Count

An iteration count is established for controlling the number of times the program executes the range of the DO construct. This is done by evaluating the expressions start_expr, end_expr , and inc_expr, and converting these values to the type of the DO variable. For example, let m1, m 2, and m3 be the values obtained:

  • m1 is the initial value of the DO variable

  • m2 is the terminal value the DO variable may assume

  • m3 is an optional parameter, specifying the DO variable increment

The value of m3 must not be zero. If expression3 is not present, m3 is given the value 1. The iteration count is calculated from the following formula:

MAX (INT ((m2 - m1 + m3) / m3), 0 )

Note that the iteration count is 0 if one of the following conditions is true:

  • m1 > m2 and m 3 > 0

  • m1 < m2 and m 3 < 0

8.5.5.1.2. Controlling Execution of the Range of the DO Construct

The steps that control the execution of the range of the DO construct are as follows:

  1. The DO variable is set to m1, the initial parameter (step 1 of Figure 8-3).

  2. The iteration count is tested (step 2 of Figure 8-3). If it is 0, the DO construct terminates.

  3. If the iteration count is not 0, the range of the DO construct is executed (step 3a of Figure 8-3). The iteration count is decremented by 1, and the DO variable is incremented by m3 (step 3b of Figure 8-3). Steps 2 and 3 are repeated until the iteration count is 0.

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

The DO variable must not be redefined or become undefined during the execution of the range of the DO construct. Note that changing the variables used in the expressions for the loop parameters during the execution of the DO construct does not change the iteration count; it is fixed when execution of the DO construct starts.

  N = 10
  SUM = 0.0
  DO 2 I = 1, N
     SUM = SUM + X(I)
     N = N + 1
2 CONTINUE

The loop is executed 10 times; after execution I=11 and N=20.

X = 20.
DO I = 1, 2
   DO J = 1, 5
   X = X + 1.0
END DO
END DO

The inner loop is executed 10 times. After completion of the outer DO construct, J=6, I=3, and X=30.

If the second DO statement had been the following, the inner DO construct would not have executed at all; X would remain equal to 20; J would equal 5, its initial value; and I would be equal to 3:

DO J = 5, 1

8.5.5.2. DO WHILE Construct

The DO WHILE form of the DO construct provides the ability to repeat the DO range while a specified condition remains true.

The general form of the DO WHILE statement is as follows:

DO [ label ] [ , ] WHILE (expression)

The following examples show the DO WHILE statement:

DO WHILE( K >= 4 )
DO 20 WHILE( .NOT. FOUND )

The DO range is executed repeatedly. Prior to each execution of the DO range, the logical expression is evaluated. If it is true, the range is executed; if it is false, the DO WHILE construct terminates.

SUM = 0.0
I = 0
DO WHILE (I < 5)
   I = I + 1
   SUM = SUM + I
END DO

The loop would execute five times, after which SUM = 15.0 and I = 5.

8.5.5.3. Simple DO Construct

A DO construct without any loop control provides the ability to repeat statements in the DO range until the DO construct is terminated explicitly by some statement within the range. When the end of the DO range is reached, the first executable statement of the DO range is executed next.

The form of the simple DO statement is as follows:

DO [ label ]

Example:

DO
   READ *, DATA
   IF (DATA < 0) STOP
   CALL PROCESS (DATA)
END DO

The DO range executes repeatedly until a negative value of DATA is read, at which time the DO construct (and the program, in this case) terminates. The previous example, rewritten using a label, appears as follows:

    DO 100
       READ *, DATA
       IF (DATA <0) STOP
       CALL PROCESS(DATA)
100 CONTINUE

8.5.6. Altering the Execution Sequence Within the Range of a DO Construct

There are two statements that can appear only in the range of a DO construct that alter the execution sequence of the DO construct. One is the EXIT statement; the other is the CYCLE statement. Other statements, such as branch statements, the RETURN statement, and the STOP statement, also alter the execution sequence but are not restricted to DO constructs as are the EXIT and CYCLE statements.

8.5.6.1. EXIT Statement

The EXIT statement immediately causes termination of the DO construct. No further action statements within the range of the DO construct are executed. It can appear in either the block or nonblock form of the DO construct, except that it must not be the DO termination of the nonblock form.

The EXIT statement is defined as follows:

 

exit_stmt

is

EXIT [ do_construct_name ]

If the EXIT statement has a construct name, it must be within the DO construct with the same name; when it is executed, the named DO construct is terminated as well as any DO constructs containing the EXIT statement and contained within the named DO construct.

If the EXIT statement does not have a construct name, the innermost DO construct in which the EXIT statement appears is terminated.

Example 1: In the following example, the DO construct has a construct name, LOOP_8; the DO range is executed repeatedly until the condition in the IF statement is met, when the DO construct terminates:

LOOP_8 : DO
   ...
   IF (TEMP == INDEX) EXIT LOOP_8
   ...
END DO LOOP_8

Example 2: In the following example, when the EXIT statement in the IF statement is executed, both the inner loop and the outer loop are terminated:

OUTER_LOOP:  DO I = 1, 10
INNER_LOOP:  DO J = 1, 10
               ...
               IF (TEMP == INDEX) EXIT OUTER_LOOP
               ...
               END DO INNER_LOOP
               ...
             END DO OUTER_LOOP

8.5.6.1.1. CYCLE Statement

In contrast to the EXIT statement, which terminates execution of the DO construct entirely, the CYCLE statement interrupts the execution of the DO range and begins a new cycle of the DO construct, with appropriate adjustments made to the iteration count and DO variable, if present. It can appear in either the block or nonblock form of the DO construct, except it must not be the DO termination of the nonblock form. When the CYCLE statement is executed in the nonblock form, the DO termination is not executed.

The CYCLE statement is defined as follows:

 

cycle_stmt

is

CYCLE [ do_construct_name ]

If the CYCLE statement has a construct name, it must be within the DO construct with the same name; when it is executed, the execution of the named DO construct is interrupted, and any DO construct containing the CYCLE statement and contained within the named DO construct is terminated.

If the CYCLE statement does not have a construct name, the innermost DO construct in which the CYCLE statement appears is interrupted.

The CYCLE statement can be used with any form of the DO statement and causes the next iteration of the DO range to begin, if permitted by the condition controlling the loop.

Upon interruption of the DO construct, if there is a DO variable, it is updated and the iteration count is decremented by 1. Then, in all cases, the processing of the next iteration begins.

In the following example, the loop is executed as long as INDEX is nonnegative. If INDEX is negative, the loop is terminated. If INDEX is 0, the latter part of the loop is skipped.

DO
   . . .
   INDEX = . . .
   . . .
   IF (INDEX < 0) EXIT
   IF (INDEX == 0) CYCLE
   . . .
END DO

8.6. Branching

Branching is a transfer of control from the current statement to another statement or construct in the program unit. A branch alters the execution sequence. This means that the statement or construct immediately following the branch is usually not executed. Instead, some other statement or construct is executed, and the execution sequence proceeds from that point. The terms branch statement and branch target statement are used to distinguish between the transfer statement and the statement to which the transfer is made.

An example of branching is provided by the GO TO statement. It is used to transfer control to a statement in the execution sequence that is usually not the next statement in the program, although this is not prohibited.

The statements that can be branch target statements are those classified as action statements plus the IF-THEN statement, SELECT CASE statement, DO statement, WHERE statement, and a few additional statements in limited situations.

The additional statements that can be branch targets in limited contexts are as follows:

  • An END SELECT statement, provided the branch is taken from within the CASE construct.

  • A DO termination, provided the branch is taken from within the DO construct.

  • An END IF statement, provided that the branch is taken from within the IF construct.

The standard does not permit a branch to a statement within a block from outside the block. The compiler, however, permits these branches; such branches are diagnosed as being unsafe.


Note: The Fortran standard does not permit branches into executable blocks.


8.6.1. Use of Labels in Branching

A statement label is a means of identifying the branch target statement. Any statement in a Fortran program can have a label. However, if a branch statement refers to a statement label, some statement in the program unit must have that label, and the statement label must be on an allowed branch target statement.

As described in Section 3.2.5 in Chapter 3, a label is a string of from one to five decimal digits; leading zeros are not significant. Note that labels can be used in both free and fixed source forms.

8.6.2. GO TO Statement

The GO TO statement is an unconditional branching statement that alters the execution sequence.

8.6.2.1. Form of the GO TO Statement

The GO TO statement is defined as follows:

 

goto_stmt

is

GO TO label

The label must be a branch target statement in the same scoping unit as the GO TO statement (that is, in the same program unit, excluding labels on statements in internal procedures, derived-type definitions, and interface blocks).

8.6.2.2. Execution of the GO TO Statement

When the GO TO statement is executed, the next statement that is executed is the branch target statement identified with the label specified. Execution proceeds from that point.

GO TO 200   ! This is an unconditional branch and
            ! always goes to 200.
            !
X = 1.0     ! Because this statement follows a GO
            ! TO statement and is unlabeled, it is
            ! not reachable.
GO TO 10
GO TO 010   ! 10 and 010 are the same label.  

8.6.3. Computed GO TO Statement

The computed GO TO statement transfers to one of a set of branch target statements based on the value of an integer expression, selecting the branch target from a list of labels. The CASE construct provides a similar functionality in a more structured form.


Note: The Fortran standard has declared the computed GO TO statement to be obsolescent.


The computed GO TO statement is defined as follows:

 

computed_goto_stmt

is

GO TO (label_list) [ , ] scalar_int_expr

If there are n labels in the list and the expression has one of the values from 1 to n, the value identifies a statement label in the list: the first, second, ... , or nth label. A branch to the statement with that label is executed.

If the value of the expression is less than 1 or greater than n, no branching occurs and execution continues with the next executable statement or construct following the computed GO TO statement.

Each label in the list must be the label of a branch target statement in the same scoping unit as the computed GO TO statement.

A label can appear more than once in the list of target labels.

GO TO ( 10, 20 ), SWITCH
GO TO ( 100, 200, 3, 33 ),  2*I-J

In the following example, if SWITCH has the value 1 or 3, the assignment statement labeled 10 is executed; if it has the value 2, the assignment statement labeled 11 is executed. If it has a value less than 1 or greater than 3, the assignment statement Y = Z is executed, because it is the next statement after the computed GO TO statement, and the statement with label 10 is executed next.

   SWITCH = . . .
   GO TO (10, 11, 10) SWITCH
   Y = Z
10 X = Y + 2.
   . . .
11 X = Y

8.6.4. CONTINUE Statement

The CONTINUE statement is defined as follows:

 

continue_stmt

is

CONTINUE

Typically, the statement has a label and is used for DO termination; however, it can serve as some other place holder in the program or as a branch target statement. It can appear without a label. The statement by itself does nothing and has no effect on the execution sequence or on program results. The following are examples of CONTINUE statements:

100 CONTINUE
CONTINUE

8.6.5. STOP Statement

The STOP statement terminates the program whenever and wherever it is executed. The STOP statement is defined as follows:

 

stop_stmt

is

STOP [ stop_code ]

 

stop_code

is

scalar_char_constant

EXT

 

or

digit ...

The character constant or list of digits identifying the STOP statement is optional and is called a stop code.

When the stop_code is a string of digits, leading zeros are not significant; 10 and 010 are the same stop_code. You can specify from 1 to 80 digits.

The stop code is accessible following program termination. The compiler sends it to the standard error file (stderr). The following are examples of STOP statements:

STOP
STOP 'Error #823'
STOP 20


Note: The Fortran standard specifies from 1 to 5 digits in the stop_code.


8.7. Arithmetic IF Statement (Obsolescent)

The arithmetic IF statement is a three-way branching statement based on an arithmetic expression.

The arithmetic IF statement is defined as follows:

R840

arithmetic_if_stmt

is

IF (scalar_numeric_expr) label, label, label

The same label can appear more than once in an arithmetic IF statement.

The numeric expression must not be of type complex.

Each statement label must be the label of a branch target statement in the same scoping unit as the arithmetic IF statement itself.

The execution begins with the evaluation of the expression. If the expression is negative, the branch is to the first label; if zero, to the second label; and if positive, to the third label.

The following example shows an arithmetic IF statement:

     READ *, DATA
     IF(DATA) 10, 20, 30
10   PRINT *, 'NEGATIVE VALUE'
     ...
20   PRINT *, 'ZERO VALUE'
     ...
30   PRINT *, 'POSTIVE VALUE'
     ...