Ending a do loop with continue

A modified example of Ron’s code demonstrates a difficulty that was encountered when converting from old DO syntax to new DO … END DO syntax.

In the old DO syntax, a GOTO to the 200 “end” statement would goto the end of the DO and also perform this last statement in the DO. However in this example, the “goto 200” could not be replaced with a CYCLE statement, as it would skip the 200 end statement".

The use of this type of calculated end statement in old FORTRAN code was often used and requires some care when converting to modern syntax. The two DO loops also share the same calculated end statement, which adds to the conversion complexity.
Back in that day, concise coding like this was a goal.
We just don’t write those sorts of DO loops any more.

PS : In this thread, there are lots of old style DO loops with illegal syntax !!

Your example was not legal Fortran 66 - even if some compilers didn’t do good semantic checking and allowed it to pass. From section 7.1.2.8.2 of the Fortran 66 Standard:

If a statement is the terminal statement of more than
one DO statement, the statement label of that terminal
statement may not be used in any GO TO or arithmetic
IF statement that occurs anywhere but in the range of
the most deeply contained DO with that terminal state¬
ment.

If the compiler didn’t catch the bad GOTO in your example, a naive coder would think it was somehow acceptable - even though its possible meaning is ambiguous. By avoiding shared DO termination and using END DOs and CYCLE (perhaps with construct names) the meaning is clear and concise.

Back in the 1970s, I was shocked when I first turned on the ANSI flagger on the code we were developing. (~50k lines of finite element analysis code in F66.) It was with the CDC FTN compiler. None of the other compilers we were using had such an option. Although we didn’t follow all of its advice, particularly with respect to subscript expressions which were later loosened in Fortran 77, we did eliminate a lot of non-Standardisms.

This was not implemented in any FORTRAN compiler I used. I used FTN on IBM 7040, CDC, Pr1me, HP 1000 and quite a few others and never had the limitation you quote. The Fortran 66 Standard was not a well known or used document. Today (in 2024) is the first time I have seen this restriction !

Certainly F77+ changed the way DO loops can be easily used and also provided a more consistent syntax for DO, which prior FORTRAN implementations did not have.
The changes at F77 broke many earlier codes which had to be modified, so F77 was not upwardly compatible. This is different to claims for more recent Fortran versions ?

I too developed finite element analysis and graphics in FTN, but always required extensions to achieve a functional solution.

We ran into three interesting cases of labelled DO loops migrating code from Gould-SEL MPX and from VMS. The code is shown below:

        PROGRAM t_labels
        
        IMPLICIT NONE
        
        INTEGER :: i,j
        
!       DO loop to a labelled executable statement
        DO 100 i=1,3
100     WRITE(*,'("Executable labelled end of DO, i:",I3)')i

!       2 DO loops ending on the same label
        DO 200 i=1,2
           DO 200 j= 1,2
200     WRITE(*,
     1   '("2 DO loops to the same labelled WRITE, i,j:",2I3)')i,j
     
!       Jump to the end of a DO loop from within the loop
        DO 300 i=1,3
           IF (i .EQ. 2) GOTO 300
           WRITE(*,'("Within the DO loop")')
300     WRITE(*,'("End of the DO loop with jump within",I3)')i

!       Jump from outside to the terminating label of a DO loop
        IF (i .GT. 0) GOTO 400
        DO 400 i = 1,3
        WRITE(*,'("Within DO loop with jump from outside",I3)')i
400     CONTINUE

        END PROGRAM t_labels

The fpt commands to deal with these are:

% change DO CONTINUE to DO ENDDO
% remove labels from executable statements
% separate DO and GOTO destination labels

The code then becomes:

PROGRAM t_labels
!
        IMPLICIT NONE
!
        INTEGER :: i,j
!
!       DO loop to a labelled executable statement
        DO 1000 i = 1,3
           WRITE (*,'("Executable labelled end of DO, i:",I3)')i
1000    ENDDO
!
!       2 DO loops ending on the same label
        DO 1020 i = 1,2
           DO 1010 j = 1,2
              WRITE (*,                                                       &
               '("2 DO loops to the same labelled WRITE, i,j:",2I3)')i,j
1010       ENDDO
1020    ENDDO
!------------^-----------------------------------------------------------------
!!! FPT - 2311 GOTO references from inside DO loop directed to different label
!------------------------------------------------------------------------------
!
!       Jump to the end of a DO loop from within the loop
        DO 1040 i = 1,3
           IF (i .EQ. 2) GOTO 1030
           WRITE (*,'("Within the DO loop")')
1030       CONTINUE
           WRITE (*,'("End of the DO loop with jump within",I3)')i
1040    ENDDO
!------------^-----------------------------------------------------------------
!!! FPT - 2311 GOTO references from inside DO loop directed to different label
!------------------------------------------------------------------------------
!
!       Jump from outside to the terminating label of a DO loop
        IF (i .GT. 0) GOTO 1060
        DO 1050 i = 1,3
           WRITE (*,'("Within DO loop with jump from outside",I3)')i
1050    ENDDO
1060    CONTINUE
!---------------^--------------------------------------------------------------
!!! FPT - 2309 GOTO references from outside DO loop directed to different label
!------------------------------------------------------------------------------
!
END PROGRAM t_labels

The repositioning of the labels is important. If the labelled statement terminates a DO loop the repositioned label goes after the executable statement. If it is the target of a GOTO (or equivalent) it goes before the statement. If both, fpt splits the label into 2 labels, one before and one after.

The last case, jumping from outside a loop to the terminating label, is mercifully thrown out by modern compilers (e.g. gfortran, ifort, ifx). The Gould-SEL MPX compiler jumps over the loop and keeps going. The VMS compilers jumped into the loop without initialising the loop control variable. Good luck with that!

fpt will do this systematically through a large code. You are welcome to try it - see http://simconglobal.com.

2 Likes

I do not see any similar restrictions in the f77 standard. The only text I see in f77 is:

11.10.8 Transfer into the Range of a DO-Loop. Transfer of control into the range of a DO-loop from outside the range is not permitted.

This restriction does eliminate “extended do range” which f66 allowed, but it seems like it allows other branches within the do range in what seems to be an unambiguous way.

Is there any other text in f77 that governs this situation?

I think it was only the extended range do loops that were eliminated. F77 allowed many new possibilities, including negative loop control variables, expressions as loop control variables, and zero-trip do loops, but those were not allowed in f66 so these changes were all upward compatible.

1 Like

That is a really good question. Although I could read it either way, it seems that F77 relaxed this a bit. (And nothing mentioned elsewhere - such as Section B11.) I looked through the CDC FTN5 (Fortran 77) Reference Manual and it seems to allow the GOTO from the outer loop body - without shading the description as a non-Standard feature:

A terminal statement that is shared by more than one DO
loop can be referenced in a GO TO or IF statement in the
range of any of the loops, provided the referencing loop is
active, as illustrated in figure 4-30. If the terminal
statement is referenced in an inactive loop, results are
undefined.

The Cray cft77 reference manual never mentions it.

Nonetheless, it seems like a risky move. Consider if the terminal statement contained an expression which used the inner loops control variable. Or the case that @Jcollins mentioned in his fourth example where the VAX VMS compiler apparently gets confused with the possibility of an extended range DO branching back into the (uninitialized) loop.

Fortran 90 basically declared the whole nonblock DO construct obsolescent, and Fortran 2018 deleted it entirely.

I really need to play with fpt. It looks like you’ve done some great things with it. Have you ever tried running slatec through it?

The Fortran 95 Standard, in section 8.1.4.2 “Range of the DO construct” states in the second paragraph:

The range of a nonblock DO construct consists of the do-body and the following DO termination. The end of such a range is not bounded by a particular statement as for the other executable constructs (e.g., END IF); nevertheless, the range satisfies the rules for blocks (8.1.1). Transfer of control into the do-body or to the DO termination from outside the range is prohibited; in particular, it is permitted to branch to a non-term-shared-stmt only from within the range of the corresponding inner-shared-do-construct.

Similar language is in the F2003 Standard (section 8.1.6.2) and F2008 Standard (section 8.1.6.4).

I don’t have a copy of the F90 Standard handy, so can’t check it.

There you go: fortran90.org

Thank you for the link! Same exact section number and text in the F90 Standard as in F95.

I think that situation would be allowed, provided of course that the variable is defined at the time the statement is executed. It could be defined, for example, by previous iterations through the loop or it could be defined completely outside of the loop. I guess the question is what exactly is allowed regarding branches for a shared termination statement?

This is not accurate. ISO/IEC 1539 document dated 1991 toward Fortran 90 standard revision allowed do-construct-name. The 1991 revision listed the following example with an outer and an inner loop with some notes on the semantics around CYCLE and EXIT statements:

You are correct. This mistake was already pointed out by @jwmwalrus in the posting immediately after mine.

F66 is pretty explicit about not allowing a branch to a shared termination from anywhere but in the innermost loop sharing the termination. What intrigues me is the seeming loosening of the language in F77, but then tightening it back up using other words in F90. And no mention in the Compatibilities sections. (Unlike, say, F77 allowing real-type loop control variables, then F90 disallowing them again.)

I’ve no idea what went on when they were editing the F77 document. Perhaps there was an accidental omission, and some later interpretation fixed it for F90…