Redefining loop variables in old FORTRAN?

emacs was too big (disk space!) so it was only installed on a few machines, and several divisions had their own administrators who rarely were amendable to adding software. Once X11 was available and some terminal translators we created key mappings for xterm and expanded the terminal definition to support function keys and made keymappings so you hit the same keys in every editor for all basic commands. It worked great; but there were years before where emacs was not available. At one time one of the classes I taught was emacs but (a long story) I cannot even remember anything but the basics and use vim for everything. There were so many quirks in the old Fortrans that still come up now and then when we revisit old codes. One of the oddest was pre-F77 the CDC compiler let you set the first value in an array without subscripts. When that code was resurrected A=1 for array A was now legal code code but set the entire array to one instead of the first variable. Had to go through the function of the code in a long discussion to prove the bug they were seeing was because it should be A(1)=1; hundreds of those kind of quirks that really do not matter unless looking at very old code or algorithms in old documents; but we do a lot of that; hopefully hardly anyone does anymore. So this topic about changing counters inside a loop and loops always tripping once is something I have seen way too many times needing to be sorted out.
As discussed above you can get some odd behaviors doing it. Call a function that changes I in the loop and it might cause an error, might change it for the remainder of that loop but reset it to the incremented value at the top of the next pass or successfully change it just for starters. So it is really nice when the compiler catches it; particularly when resurrecting old code. When you wanted to be able to do that in the past you typically just used a GOTO instead of a DO, as in

i=1
10 continue
if (j=11) then
   i=i+1
else
   i=i+2
endif
if (i .gt. 100)goto 20
goto 10
continue 20

But since GOTO is a four-letter word now-adays probably a DO WHILE is preferred(?)

I=1
DO WHILE (I <=100)
   if(K==30)I=I+1
   I=I+1
END DO

Occasionally I do wish
there was a neater Fortran construct where
it was legal, perhaps something like

DO (I=1; i<=100; i=i+1)
   if(K==30)I=I+1
END DO

Had you run the code through CDC’s F45 conversion aid, this was one of the extensions it noticed, and automatically corrected.

The example in the F45 Reference Manual shows:

      DIMENSION A(10), AA(2,4), AAA(5,5,5)
      B = A
      BB = AA(3)
      BBB = AAA(3,2)

being converted to:

      DIMENSION A(10), AA(2,4), AAA(5,5,5)
      B = A(1)
      BB = AA(3,1)
      BBB = AAA(3,2,1)

(Guess it didn’t check for the out of bounds leading subscript in the BB = AA(3,1) case…)

Backwards GOTOs, in your example “goto 10”, generally indicate a loop construct. So some form of DO is really called for instead. As you show, DO WHILE and END DO works. A DO and END DO with a test inside which conditionally does an EXIT also works. The nice thing about the EXIT version is you can exit a nested set of loops with a single statement.

I think there were quite a few of these. In 1970’s, I wrote my own line editor in Fortran, based on the Pr1me line editor (also in Fortran), as I wanted a different approach to remembered commands and it also enabled multiple commands per line.
It was mainly used for generating text data files. The best feature was being able to use the “gmodify” command to the end of the file. At that time most of our programs used a fixed layout data file, which were easier to generate with a line editor.
I continue to use it today, although Excel + Fortran code can readily generate large sets of fixed layout data.

When the code was resurrected was long after the CDC compiler was available; but that f45 manual would definitely have been handy. For a very long time I had copies of all the Fortran and later C manuals for every platform which helped with porting many codes, particularly ones containing proprietary procedures; as without the manuals it was often not clear what a subroutine (sometimes with 20 parameters) did exactly. I do not remember that f45 command but it sounds like it would have been very useful. When we phased out a particular platform we always created an application called EXODUS that would help identify and (when possible) automatically migrate files. It expanded UPDATE files, converted ASCII 6/12 to ASCII8, and so on. For the CDC 7600 and NOS migrations it sounds like we missed using a valuable tool. It was only a few years ago there was an on-line discussion where people were very confused by what had happened to some old files they were resurrecting and I realized they had ASCII6/12 files and gave them the old routine to convert them. Reasonably, they had never heard of it and were very distrustful of the files because they thought they had undergone some strange corruption. I wonder if f45 caught the original issue of the post, at least in the simple cases where it is done directly in the loop.

Ha! I still have a subroutine for the CDC modify command that emulates the command line history editing and Xedit editor modify command that we still use in some column-based editing filter programs and interactive command line editing functions. The original was in COMPASS and a lot of people were just starting to use higher level languages. It originally was spaghetti code because the first Fortran version was pre-F77; but the commenting style still smacks heavily of machine code days.

Summary
!>
!!##NAME
!!    modif(3f) - [M_strings:EDITING] emulate the MODIFY command from the
!!    line editor XEDIT
!!    (LICENSE:PD)
!!
!!##SYNOPSIS
!!
!!    subroutine modif(cline,cmod)
!!
!!     character(len=*) :: cline ! input string to change
!!     ! directive provides directions on changing string
!!     character(len=*) :: cmod
!!
!!##DESCRIPTION
!!   MODIF(3f) Modifies the line currently pointed at using a directive
!!   that acts much like a line editor directive.
!!   Primarily used to create interactive utilities such as input history
!!   editors for interactive line-mode programs.
!!
!!   the modify directives are as follows-
!!
!!    DIRECTIVE EXPLANATION
!!
!!    ^STRING#   Causes the string of characters between the ^ and the
!!               next # to be inserted before the characters pointed to
!!               by the ^. an ^ or & within the string is treated as a
!!               regular character. If the closing # is not specified,
!!               MODIF(3f) inserts the remainder of the line as if a # was
!!               specified after the last nonblank character.
!!
!!               There are two exceptions. the combination ^# causes a #
!!               to be inserted before the character pointed to by the
!!               ^, and an ^ as the last character of the directives
!!               causes a blank to be inserted.
!!
!!    #          (When not the first # after an ^) causes the character
!!               above it to be deleted.
!!
!!    &          Replaces the character above it with a space.
!!
!!    (SPACE)    A space below a character leaves it unchanged.
!!
!!    Any other character replaces the character above it.
!!
!!##EXAMPLES
!!
!!   Example input/output:
!!
!!    THE INPUT LINE........ 10 THIS STRING  TO BE MORTIFD
!!    THE DIRECTIVES LINE...        ^ IS THE#        D#  ^IE
!!    ALTERED INPUT LINE.... 10 THIS IS THE STRING  TO BE MODIFIED
!!
!!   Sample program:
!!
!!    program demo_modif
!!    use M_strings, only : modif
!!    implicit none
!!    character(len=256)           :: line
!!    integer                      :: ios
!!    integer                      :: count
!!    integer                      :: COMMAND_LINE_LENGTH
!!    character(len=:),allocatable :: COMMAND_LINE
!!       ! get command name length
!!       call get_command_argument(0,length=count)
!!       ! get command line length
!!       call get_command(length=COMMAND_LINE_LENGTH)
!!       ! allocate string big enough to hold command line
!!       allocate(character(len=COMMAND_LINE_LENGTH+200) :: COMMAND_LINE)
!!       ! get command line as a string
!!       call get_command(command=COMMAND_LINE)
!!       ! trim leading spaces just in case
!!       COMMAND_LINE=adjustl(COMMAND_LINE)
!!       ! remove command name
!!       COMMAND_LINE=adjustl(COMMAND_LINE(COUNT+2:))
!!       INFINITE: do
!!          read(*,'(a)',iostat=ios)line
!!          if(ios /= 0)exit
!!          call modif(line,COMMAND_LINE)
!!          write(*,'(a)')trim(line)
!!       enddo INFINITE
!!    end program demo_modif
!!
!!##AUTHOR
!!    John S. Urban
!!
!!##LICENSE
!!    Public Domain
subroutine modif(cline,mod)

!$@(#) M_strings::modif(3f): Emulate the MODIFY command from the line editor XEDIT

!
! MODIF
! =====
! ACTION- MODIFIES THE LINE CURRENTLY POINTED AT. THE INPUT STRING CLINE IS ASSUMED TO BE LONG ENOUGH TO ACCOMMODATE THE CHANGES
!         THE MODIFY DIRECTIVES ARE AS FOLLOWS-
!
!   DIRECTIVE                       EXPLANATION
!   ---------                       ------------
!   ^STRING#   CAUSES THE STRING OF CHARACTERS BETWEEN THE ^ AND THE
!              NEXT  # TO BE INSERTED BEFORE THE CHARACTERS POINTED TO
!              BY THE ^. AN ^ OR & WITHIN THE STRING IS TREATED AS A
!              REGULAR CHARACTER. IF THE CLOSING # IS NOT SPECIFIED,
!              MODIF(3f) INSERTS THE REMAINDER OFTHELINE AS IF A # WAS
!              SPECIFIED AFTER THE LAST NONBLANK CHARACTER.
!
!              THERE ARE TWO EXCEPTIONS. THE COMBINATION ^# CAUSES A #
!              TO BE INSERTED BEFORE THE CHARACTER POINTED TO BY THE
!              ^,  AND AN ^ AS THE LAST CHARACTER OF THE DIRECTIVES
!              CAUSES A BLANK TO BE INSERTED.
!
!   #          (WHEN NOT THE FIRST # AFTER AN ^) CAUSES THE CHARACTER
!              ABOVE IT TO BE DELETED.
!
!   &          REPLACES THE CHARACTER ABOVE IT WITH A SPACE.
!
!   (SPACE)    A SPACE BELOW A CHARACTER LEAVES IT UNCHANGED.
!
!   ANY OTHER CHARACTER REPLACES THE CHARACTER ABOVE IT.
!
! EXAMPLE-
! THE INPUT LINE........ 10 THIS STRING  TO BE MORTIFD
! THE DIRECTIVES LINE...        ^ IS THE#        D#  ^IE
! ALTERED INPUT LINE.... 10 THIS IS THE STRING  TO BE MODIFIED
!CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
character(len=*)            :: cline        !STRING TO BE MODIFIED
character(len=*),intent(in) :: mod          !STRING TO DIRECT MODIFICATION
character(len=len(cline))   :: cmod
character(len=3),parameter  :: c='#&^'      !ASSIGN DEFAULT EDIT CHARACTERS
integer                     :: maxscra      !LENGTH OF SCRATCH BUFFER
character(len=len(cline))   :: dum2         !SCRATCH CHARACTER BUFFER
logical                     :: linsrt       !FLAG FOR INSERTING DATA ON LINE
integer :: i, j, ic, ichr, iend, lmax, lmx1
maxscra=len(cline)
   cmod=trim(mod)
   lmax=min0(len(cline),maxscra)         !DETERMINE MAXIMUM LINE LENGTH
   lmx1=lmax-1                           !MAX LINE LENGTH -1
   dum2=' '                              !INITIALIZE NEW LINE
   linsrt=.false.                        !INITIALIZE INSERT MODE
   iend=len_trim(cmod)                   !DETERMINE END OF MODS
   i=0                                   !CHAR COUNTER FOR MOD LINE CMOD
   ic=0                                  !CHAR COUNTER FOR CURRENT LINE CLINE
   ichr=0                                !CHAR COUNTER NEW LINE DUM2
11 continue
   i=i+1                                 !NEXT CHAR IN MOD LINE
   if(ichr > lmx1)goto 999              !IF TOO MANY CHARS IN NEW LINE
   if(linsrt) then                       !IF INSERTING NEW CHARS
      if(i > iend) cmod(i:i)=c(1:1)     !FORCE END OF INSERT MODE
      if(cmod(i:i) == c(1:1))then        !IF END OF INSERT MODE
         linsrt=.false.                  !RESET INSERT MODE FLAG
         if(ic+1 == i)then               !NULL INSERT STRING
            ichr=ichr+1                  !INCREMENT COUNTER FOR NEW LINE
            dum2(ichr:ichr)=c(1:1)       !INSERT INSERT MODE TERMINATOR
         endif
         do j=ic,i                       !LOOP OF NUMBER OF CHARS INSERTED
            ichr=ichr+1                  !INCREMENT COUNTER FOR NEW LINE
            if(ichr > lmax)goto 999     !IF AT BUFFER LIMIT, QUIT
            dum2(ichr:ichr)=cline(j:j)   !APPEND CHARS FROM ORIG LINE
         enddo                           !...WHICH ALIGN WITH INSERTED CHARS
         ic=i                            !RESET CHAR COUNT TO END OF INSERT
         goto 1                          !CHECK NEW LINE LENGTH AND CYCLE
      endif                              !END OF TERMINATED INSERT LOGIC
      ichr=ichr+1                        !INCREMENT NEW LINE COUNT
      dum2(ichr:ichr)=cmod(i:i)          !SET NEWLINE CHAR TO INSERTED CHAR
   else                                  !IF NOT INSERTING CHARACTERS
      ic=ic+1                            !INCREMENT ORIGINAL LINE COUNTER
      if(cmod(i:i) == c(1:1))goto 1      !IF DELETE CHAR. NO COPY AND CYCLE
      if(cmod(i:i) == c(3:3))then        !IF BEGIN INSERT MODE
         linsrt=.true.                   !SET INSERT FLAG TRUE
         goto 1                          !CHECK LINE LENGTH AND CONTINUE
      endif                              !IF NOT BEGINNING INSERT MODE
      ichr=ichr+1                        !INCREMENT NEW LINE COUNTER
      if(cmod(i:i) == c(2:2))then        !IF REPLACE WITH BLANK
         dum2(ichr:ichr)=' '             !SET NEWLINE CHAR TO BLANK
         goto 1                          !CHECK LINE LENGTH AND CYCLE
      endif                              !IF NOT REPLACE WITH BLANK
      if(cmod(i:i) == ' ')then           !IF BLANK, KEEP ORIGINAL CHARACTER
         dum2(ichr:ichr)=cline(ic:ic)    !SET NEW CHAR TO ORIGINAL CHAR
      else                               !IF NOT KEEPING OLD CHAR
         dum2(ichr:ichr)=cmod(i:i)       !REPLACE ORIGINAL CHAR WITH NEW
      endif                              !END CHAR KEEP OR REPLACE
   endif                                 !END INSERT OR NO-INSERT
1  continue
   if(i < lmax)goto 11                  !CHECK FOR END OF LINE REACHED
                                         !AND CYCLE IF OK
999   continue
   cline=dum2                            !SET ORIGINAL CHARS TO NEW CHARS
end subroutine modif                     !RETURN
1 Like

You can view a copy of the F45 manual here: https://bitsavers.org/pdf/cdc/cyber/lang/fortran/60483000C_Fortran_Extended_Version_4_to_Fortran_Version_5_Conversion_Aid_Program_Version_1_Reference_Mar83.pdf

F45 was a deck in the FTN5 UPDATE OLDPL. So it was automatically installed as part of the FTN5 installation process. The manual documents the DO loop changes, and what it could detect and warn about, in the chapter on “Manual Conversions”. (Chapter 4, pdf page 31.)

The CDC site I was working at ca 1980-1984 was stuck on KRONOS for a long time, so couldn’t install FTN5. Our initial foray into Fortran 77 was via the U of Minnesota M77 compiler - which was based on their MNF compiler. When we finally upgraded to NOS 1.4, we finally had access to FTN5 (and F45).

For a long time I’d thought that CDC’s FTN5 was the first Fortran 77 compiler on the market. It was released in 1979. But the unix f77 compiler was even earlier.

The Fortran Wiki has a listing of compiler manuals. I just added F45. Anyone can add other manuals.

1 Like

@Beliavsky
Thanks for this, I now have a copy of the Pr1me FTN compiler manual, which I have not seen for 40 years.
With regard to DO loops, it refers to “m2<=m1”, which is a bit confusing ?
What it doesn’t say is what happens if i,m2 or m3 are changed. What we all did back then was test it to find out what happened, (which was no error report), then went on with using it.
The manual also refers to the F66 standard, which I never read.
It also referred to short and long integers ( *2 and *4 ); No 1-byte or 8-byte integers in those days.

It is amazing to see what was not available then.

1 Like

Not everybody was doing that. I have always tried sticking to standard or de-facto standard features : one of the reasons is that when I started programming all codes were supposed to run on 4 different platforms, so portability was a strong requirement.

@PierU, what version of old FORTRAN did you use ?
Although “de-facto” standard features covers a fairly broard scope, especially if considering Vax FORTRAN !

I would expect most examples of old FORTRAN code would include use of the extensions available in the compiler being used for it’s development. Unfortunately, not all codes acknowledged the development compiler…

When I started, it was FORTRAN 77.

What I mean by “de-facto standard” were extensions that were available in most of the compilers and that were consequently “portable”. So NOT considering a specific single compiler.

My impression of most of the compilers back in the '70s (I wrote my first PDP-8 “Fortran” program in ~1970) was they were fortunate if they could generate sensible code from sensible input. Certainly supporting Fortran 66 syntax was important. (Though PDP-8 Fortran didn’t even do that.) However complete syntax checking was not the greatest, and semantic checking much less so. Large mainframe compilers (e.g., IBM and the BUNCH) were better at diagnosing things than small mini-computer vendors like DEC. The latter simply couldn’t afford the memory and processing time.

Detection of illegal modification of loop control variable and m1/m2/m3 falls squarely into semantic analysis. That is an area where compilers ranged from non-existent to fairly complete analysis. Over time, newer compilers tend to discover more issues than older compilers - especially when optimizations are enabled.

So there is a big difference between whether something is “supported” (based on an older version of a compiler not diagnosing it) or whether it really is supported (because the Standard or vendor explicitly says it is). Areas where the Standard and the vendor are silent can not be depended upon in the long run.

When looking at old FORTRAN code, it is more important to recognise what was done, rather than what should have been done.
The Fortran 77 standard made a significant change to the way that DO loops were interpreted, so if you are looking at pre-F77 code, you need to check for the different way that DO loops were commonly used prior to F77.
Telling FORTRAN users in 60’s and 70’s that they broke unenforced rules is not the issue.
The Fortran 66 standard was not a document that many FORTRAN programmers used in the 60’s and 70’s, or were aware of.
There has been a more recent emphasis in compilers to identifying the changes to i,m1,m2 and m3 to help with renewing this old FORTRAN.
It is amazing to think that the FORTRAN compiler of that time was loaded from a tape drive or a deck of cards. Not much room for semantic checking !

The most significant difference was that extended range loops were allowed in f66 but not in f77. Except for that, every legal f66 do loop does exactly the same thing in f77, f90, and so on. The other changes introduced in f77 were upward compatible with f66 because restrictions were relaxed, not added. Namely, f77 allowed the m1, m2, and m3 variables to have nonpositive values, they could be changed within the loop, and it defined the value of the loop index variable upon exit. I think the loop index value was not defined in f66 after loop exit, so it was not allowed to reference it in that undefined state.