What is going to do this old FORTRAN snippet?

I have found in a very old FORTRAN (all uppercase on purpose) code this snippet:

      IF(IRANK-N)17,19,19
   17 II=JJ
      DO 19 I=KK,N
      II=II+M
      MM=II-L
      A(II)=A(II)-HOLD*A(MM)
      IF(DABS(A(II))-DABS(PIV))19,19,18
   18 PIV=A(II)
      IR=J
      IC=I
   19 CONTINUE

What happens if IRANK == N?
It goes beyond the loop or it starts the loop?

Thanks.

As far as I understand, it goes beyond the loop.

If you, @FortranFan, agree that the transfer to the label 19 from the if statement is not starting the loop, I believe you.

ifort complains with:

error #6526: A branch to a do-term-shared-stmt has occurred from outside the range of the corresponding inner-shared-do-construct.   [19]
      DO 19 I=KK,N
---------^

While, gfortran 7.3 accepts it (I know it’s a very old version but I cannot install a new one).
So I was confused when the compiler is saying that it is a jump inside the loop.

@egio ,

This “very old FORTRAN … code” appears equivalent to:

      SUBROUTINE SUB(IRANK, N)
      IF (IRANK-N) 17,19,19
 17   CONTINUE
      PRINT *, "LET US REPEAT 3 TIMES THAT" 
      DO 19 I = 1, 3
         PRINT *, "ARITHMETIC IF IS DELETED FROM THE FORTRAN STANDARD!" 
 19   CONTINUE
      RETURN
      END SUBROUTINE
      N = 1
      IRANK = 0
      CALL SUB(IRANK, N)
      IRANK = 1
      CALL SUB(IRANK, N)
      END 

that gfortran appears to work with as a “legacy extension” - see the warning below, “Legacy Extension: Label at (1) is not in the same block as the GOTO statement at (2)”:

C:\temp>gfortran p.f -o p.exe
l.f:2:72:

    2 |       IF (IRANK-N) 17,19,19
      |                                                                        1
Warning: Fortran 2018 deleted feature: Arithmetic IF statement at (1)
l.f:7:3:

    2 |       IF (IRANK-N) 17,19,19
      |                                                                        2
......
    7 |  19   CONTINUE
      |   1
Warning: Legacy Extension: Label at (1) is not in the same block as the GOTO statement at (2)
l.f:7:3:

    2 |       IF (IRANK-N) 17,19,19
      |                                                                        2
......
    7 |  19   CONTINUE
      |   1
Warning: Legacy Extension: Label at (1) is not in the same block as the GOTO statement at (2)

C:\temp>p.exe
 LET US REPEAT 3 TIMES THAT
 ARITHMETIC IF IS DELETED FROM THE FORTRAN STANDARD!
 ARITHMETIC IF IS DELETED FROM THE FORTRAN STANDARD!
 ARITHMETIC IF IS DELETED FROM THE FORTRAN STANDARD!

Now, imagine the original code as follows with the DO construct following statement 17 using a different label for the DO than 19:

      SUBROUTINE SUB(IRANK, N)
      IF (IRANK-N) 17,19,19
 17   CONTINUE
      PRINT *, "LET US REPEAT 3 TIMES THAT" 
      DO 18 I = 1, 3
         PRINT *, "ARITHMETIC IF IS DELETED FROM THE FORTRAN STANDARD!" 
 18   CONTINUE
      RETURN
 19   CONTINUE
      RETURN
      END SUBROUTINE
      N = 1
      IRANK = 0
      CALL SUB(IRANK, N)
      IRANK = 1
      CALL SUB(IRANK, N)
      END 

Give this a try - chances are gfortran will issue no “legacy extension” warnings and IFORT will issue no errors.

Never mind the arithmetic IF statement, rightly condemned to archaeology, the interesting thing here is where control goes when you jump to the end of a DO loop. We have found many of these.

  1. where the GOTO statement (or IF statement or alternate return) is inside the scope of the DO loop.
  2. where the GOTO statement is outside the DO loop.

If the GOTO statement is inside the DO loop, the expected behaviour is that the current iteration of the DO loop ends and the next iteration begins. Many compilers have been tested to verify this behaviour and no exceptions have been observed.

If the GOTO statement is outside the DO loop, the behaviour depends on the compiler in use. The following have been observed:

  1. The statement at the end of the loop is not executed. Control enters the DO loop at the DO statement, initialising the DO loop control variables (e.g. VAX/VMS).
  2. The statement at the end of the loop is executed. Control then remains in the DO loop without initialising the DO loop control variable (e.g. DEC VMS for Alpha AXP).
  3. The compiler generates a warning or error for a jump into a DO loop (e.g. DEC Visual Fortran).
  4. The statement at the end of the DO loop is executed, and control then continues from that statement without entering the DO loop (Gould-SEL (now Encore) Concept-32).

I have quoted from a page in the fpt reference manual which was written a long time ago - hence the compiler examples. I expect most compilers to behave like case 3 above, but there is still quite a lot of VMS and MPS about.

fpt handles these situations by separating the labelled destinations into two CONTINUE statements. See: http://simconglobal.com/fpt_ref_separate_do_goto_labels.html