Redefining loop variables in old FORTRAN?

I’m modernizing some old code — one of the most interesting Fortran pastimes for me.

This one program has what seems to me to be (always has been ?) invalid code:

   10 do I = 1, NMAX
        ...
        call RCF(A, B, C, I)
        ...
   10 continue

where the procedure RCF() is defined as something like

      SUBROUTINE RCF(A, B, C, I)
      ...
      IF(CONDITION) GO TO 80
      ...
  80  I = -M
      END

Has redefining the loop variable ever been valid ? I think M ends up being positive and the loop variable I would then be negative, outside of the bounds [1, NMAX]. My guess is that CONDITION was just never met and that this would either

  1. Cause a runtime error
  2. Fortuitously exit the loop 10

Maybe the behavior was compiler dependent because this was never part of the standard ? I haven’t read anything that indicates otherwise, but maybe I haven’t looked hard enough.

It was not valid in f77 to modify the loop index. I don’t think it was valid before that either, but I’m unsure.

Regarding actual implementations, these are not defined by the standard, the standard only defines the behavior of the loop, not how that behavior is achieved. But in practice, most compilers compute the trip count before the loop, and then decrement that trip count until it reaches zero. The do variable is sometimes updated according to the do loop triple (if the compiler can see that it is necessary to do so), but sometimes the loop variable is just ignored (the memory location is not updated, or maybe it is not actually associated with a memory location).

In the code you show, the do variable is modified, so it is not conforming. The compiler is not required to recognize this, it is up to the programmer to do the right ting. Anything can happen in this case, the correct number of do loop iterations might be performed anyway, the changed do index could be ignored in the rest of the loop, or the compiler could start WW III.

2 Likes

Quotation from the 2018 Fortran Standard:

" 11.1.7.4.3 The execution cycle:"

“2 Except for the incrementation of the DO variable that occurs in step (3), the DO variable shall neither be redefined nor become undefined while the DO construct is active.”

1 Like

Modification of the control (loop) variable is not allowed in Fortran 66 either. In Section 7.1.2.8.2 (lines 54-57 of p15)

The control variable, initial parameter, terminal parameter and incrementation parameter of a DO may not be redefined during the execution of the range or extended range of that DO.

It was not valid even in f66 to modify the loop index: section 7.1.2.8.2 says inter alia
“The control variable, initial parameter, terminal parameter, and incrementation parameter of a DO may not be redefined during the execution of the range or extended range of that DO.” McCracken’s “A guide to FORTRAN programming” (Wiley, 1961); Section 6.3 Rules 4 and 5 on p.38,39 has the same prohibition in different words. (Both allow for what f66 calls “extended range”. F77 11.10.8 seems to forbid the pre-77 extended range possibility which allowed transfer of control out of a loop and back in provided that f66 7.1.2.8.2 was satisfied.)

1 Like

This is a case were having an explicit interface would help the compiler find such bugs at compile time. If procedure RCF’s interface was explicit, and there was an intent attribute on the I argument, INTENT(IN) would be legal. However if the argument were INTENT(OUT) or INTENT(INOUT) the error would be caught.

1 Like

In the mid 70’s, I did receive a significant (CDC pre-F77) equation ordering code for searching for an ordered list of linked nodes, using “DO 10 I = 1,NMAX” where the “nmax” number of identified nodes was increasing during the loop. The loop terminated when I exceeded the number of identified nodes, which was not known at the start of the loop.
It worked on all compilers that I used at the time, but had to be restructured when converting to F77.

Typically, “Old FORTRAN” prior to F77 did not conform to a “Fortran 66” standard but to the Fortran rules for the range of hardware the programmer was using. Unfortunately, it was not common for codes to document which hardware (rules) was used to develop the code.
I rarely used DEC/Vax hardware, as their Fortran rules were significantly different to those of the hardware I was using, mostly CDC and Pr1me.
The acceptance of the Fortran 77 standard was a significant change in this approach.

Old FORTRAN DO loops need to be carefully tested. This example of changing the DO variable in a called routine was an annoying feature of some early codes.

1 Like

One of the first steps I took was adding argument intents and explicit interfaces (and of course disabling implicit variable typing), which led me right here. These small (in this case) steps took care of >90% of the warnings and errors. I might have missed this entirely without having done so.

1 Like


from Programmer's Reference Manual October 15, 1956

I don’t think you can get “older” than that.

I would surround the call to RCF with some copy-in, copy-out assignments, and check if the fourth argument has been modified after RCF. If it has, you should at least log it somewhere so the user can disregard any computations after that point.

3 Likes

@themos

There were many contradicting documents during that period and basically FORTRAN programmers did what their specific compiler allowed. There were many extensions that differed between hardware compilers.
Indeed, the Fortran 66 Standard, was not a generally recognised reference document for the language. That was the significant change that came with the Fortran 77 standard, where hardware suppliers agreed to embrace a more portable approach that users were requesting.

Your quoting from a “Programmer’s Reference Manual” ignores the reality of using FORTRAN in the 60’s and 70’s, the glory days of old FORTRAN.

1 Like

And yet that was the OP question in fact, he pointed out himself that compilers at least some compilers allowed it, but was wondering if the standard has anything to say on the issue so the quote of the Fortran 66 manual is the right answer whether was widely adopted or not is the correct answer. The standard did not allow it but compilers implemented anyway.

Putting aside the fact that I think we can all agree this is horrible practice, especially in modern Fortran or even Fortune 77 where you could have while loops

1 Like
ian@ian-Latitude-E7440:~$ nano loopmodify.f
ian@ian-Latitude-E7440:~$ f77 loopmodify.f
ian@ian-Latitude-E7440:~$ ./a.out
           1
           3
           5
           7
           9
ian@ian-Latitude-E7440:~$ cat loopmodify.f
        integer i
        do i = 1, 10
        print *,i
        call increment(i)
        end do
        end program
        
        subroutine increment(j)
        j = j+ 1
        return
        end subroutine 
       
ian@ian-Latitude-E7440:~$ 
1 Like

I forgot about f77, thanks. Looks like the loop runs at most iend - istart + 1 times in the following case for me :

  program test

  istart = 1
  iend   = 10

  loop_counter = istart - 1

  write(*, '(A)') " loop_index  loop_counter "

  do loop_index = istart, iend

    loop_counter = loop_counter + 1

    if(loop_index .eq. 5) call sub(loop_index)

    write(*, '(I3, 9X, I3)') loop_index, loop_counter

  end do

  end

  subroutine sub(J)
    J = -5
  end

with output

 loop_index  loop_counter
  1           1
  2           2
  3           3
  4           4
 -5           5
 -4           6
 -3           7
 -2           8
 -1           9
  0          10

Forgive the implicit typing — it feels thematically appropriate here.

There is one other difference between f77 and pre-f77 loops that has not been discussed. The m1, m2, and m3 variables were not allowed to be modified within the loop body in pre-f77 fortran. This is presumably in order to allow the compiler to use these variables in order to increment the do index variable. However, in f77 and later, it is allowed to modify these variables, and those modifications have no affect on how the do index is incremented. This is because in f77 and later, m1, m2, and m3 in the do statement are treated as expressions (i.e. as if they had parentheses around them), and the values of those expressions at the time the do statement is executed must be saved and used by the compiler for the subsequent index increments.

@RonShepard,
The point I was trying to make is that “pre-F77” was a time where FORTRAN rules varied significantly between hardware platforms. Some compilers I used did allow the m1, m2, and m3 variables to change, especially given the way that one-pass DO loops were implemented.
It was not the case that the variables were not allowed to be modified, especially for the compilers I used at that time, Control Data and Pr1me especially and also probably Microsoft Fortran (not sure what the first incarnation of this was called?)
IBM may have been an exception, but in my limited experience, it was a difficult compiler to use, which only got worse with F77.

I meant that the f66 fortran standard did not allow the variables to be modified within the loop, while the f77 and later standard did allow modifications.

The one-trip do loop issue is another matter that is worth mentioning in this context. Pre-f77 fortran required the trip count, as determined by m1, m2, and m3, to be positive, and it was the responsibility of the programmer to ensure that the condition was satisfied. The old standard did not define the behavior when this requirement was violated. I think most compilers of that era executed the loop body once with negative or zero trip counts, but that behavior was either an extension (if documented) or just undocumented behavior, it was not mandated by the standard. If the programmer wanted the do body to be executed zero times, he had to test and branch around the loop manually. F77 allowed zero and negative trip counts, and the loop body was required to be executed zero times in such cases. In my opinion, the f77 (and later) behavior was the best approach, despite the conflict with the common one-trip extension. Even with modern compilers, there is often a “one-trip” option that can be set in order to force do loops to conform to the previous nonstandard/nonspecified behavior. If a programmer wants one-trip behavior with modern fortran (f90 and later), a standard approach is to use a “do while” loop rather than a do loop.

1 Like

The CDC FTN compiler did have an ANSI flagger option though. I used it a lot when trying to make code more portable. Their later FTN5 (Fortran 77 compatible) compiler also had the option. I’m pretty sure the U of Minnesota MNF and M77 compilers also had a similar option.

CDC was also pretty good about marking their extensions in their Reference Manuals.

When they moved from FTN to FTN5, they dropped a number of non-Standard extensions. To help with migrating codes, they provided a tool called F45.

I should look in the CDC manuals on bitsavers to see if there were messages issued when messing with the loop variables. Could also boot up Desktop Cyber and directly ask the compilers. But don’t have time this morning.

Ron, You are challenging my memory of pre F77, but loop count became a thing only when F77 redefined a DO loop control.

Prior to F77, most (probably not all) compilers did the exit test at the end of each cycle, based on the current values of “i”, m2 and m3, so if any of these changed in the previous cycle the DO would adjust it’s finish state. Certainly the CDC, Pr1me and HP compilers behaved in this way.
From memory, I think pre-f77 IBM FORTRAN was an outlier as it did manage DO loops in a different way, but I only used the Watford compiler on IBM 7040 for a short time.

F77 introduced a trip count and prohibited any change to “i”, m2 or m3, and “replaced” the exit test with a trip count test. ( hence the new problem of trip count overflow in do i = -huge(i),huge(i), which has produced so many unnecessary threads for poorly designed DO loops ! )

Single trip DO remains a compiler option to this day, although now few of us appreciate the history.

I don’t think this is correct. As described in various posts above in this discussion, pre-f77 versions of fortran did not allow any of the loop variables to be changed within the loop (or within the extended do loop, which was allowed then). F77 still did not allow the loop index to be changed, but the other loop parameters could be changed.

Perusing the FTN Reference Manual (http://www.bitsavers.org/pdf/cdc/Tom_Hunter_Scans/Fortran_Extended_4_Ref_Man_60497800J_Jun83.pdf page 4-8), it says:

The control variable must not be redefined in the range of a DO; such redefinition causes a fatal-to-execution
diagnostic to be issued. The control variable should likewise not be redefined in the extended range; such
redefinition causes the results of execution to be unpredictable.

The indexing parameters should not be redefined in either the range or the extended range of a DO. In
either case, the results of execution are unpredictable. Redefinition in the range of the DO causes an
informative diagnostic to be issued.

The F45 conversion aid program is documented to flag lines of code for manual conversion when the DO control variable was modified within the loop. However it does not detect modification of the control variable in an extended range. (Extended range was deleted from the Fortran 77 Standard, but FTN5 still supported it.)

The FTN5 Reference Manual also says similar things. But as @RonShepard notes, modifying the m1, m2, m3 indexing parameters after the trip count has been established is allowed in Fortran 77. So FTN5 allows it.