Fortran 90 compilers (except Elf 90) are supposed to compile older programs. The real problem you will have is with sloppy, unstructured code. Part of the problem is with a lack of more structured constructs. Other times, programmers have done things just because you could get away with it, or else to save time or space (a once critical resource) when using a particular compiler.
These comments apply to FORTRAN IV (also known as Fortran 66), and Fortran 77, unless otherwise indicated.
ICOUNT, ALOG, XLENGTH
IMPLICIT NONE
to catch anything you have overlooked. Avoid meaningless names like I, J, K.
Use ROW, COL, COUNT instead.
DO 33 I=1,N A(I) = I 33 CONTINUEPrior to Fortran 77, this would be executed at least once, even if N was 0. Today we would use END DO instead of specifing the range with a statement number. Good form:
DO Row = 1, MaxRow MyArray(Row) = Row END DO
Old New Meaning .EQ. == equal to .NE. /= not equal to .LT. < less than .LE. <= less than or equal .GT. > greater than .GE. >= greater than or equal
In the beginning, Fortran programs were punched on cards. This made it advisable to punch a sequence number on each card, so in case the deck was dropped, it could be put back in order using a card sorter (really neat machine!). Columns 73-80 were reserved for this purpose. In those days we were as careful about this as now we are at making backup files. The main problem is, that if a statement extends beyond column 72, those characters are ignored.
Comments are indicated by C in column 1. Columns 1-5 are reserved for statement numbers, and column 6, if punched, indicates continuation. So the Fortran statements are in columns 7-72. Here is a snippit of code that actually has sequence numbers. They were put there by a tape update program.
DO 101 I = 1, NFB UCF.48 NFR(I) = NFRT(I) UCF.49 101 CONTINUE UCF.50 I = 1 UCF.51 CALL GENT(SFI,DTS,NT,UTS,TSAVE) ALLP17 C PEAK S-RATE UCF.68 I = 1 UCF.72 C CHECK FOR PEAK IN NONSTANDARD FRAME UCF.73 IF (IOJD.GT.0 .AND. IOJD.LE.NFB) I = NFB - IOJD + 1 UCF.74
Fortran variable names are limited to 6 characters, since that is how many characters fit in a 36-bit word on the IBM 709 computer used by Backus and Ziller.
The rule about spaces was simple. "Spaces don't count. They can be used freely to improve readability." But they were not separators. This meant that GOTO could be written GO TO or even G OT O. It also required a greater use of special characters, some of which we still see today:
.AND. IF (X.EQ.23) GO TO 45Even worse, a familiar DO statement, should the comma be replaced with a period, would be completely misinterpreted, no error message resulting. According to folklore, just such an error caused a space probe intended for Venus to be lost.
DO 33 I = 1,100 DO 33 I = 1.100 DO33I=1.100The last line being how the compiler sees it. DO33I is now a new variable with implicit type REAL, and it is assigned the value 1.1, no sweat. Too bad.
Back at the time of Fortran IV, the logical IF statement was introduced. It has a logical expression, followed by any self-contained statement, which is executed conditionally if the expression is .TRUE.
IF (I .GT. 0 .AND. I .LE. N) ARRY (I) = TEMP IF (ID .EQ. -9999) GO TO 76
The arithmetic IF statement goes way back to Fortran II. It is a three-way branch, depending on whether the arithmetic value in ( )'s is negative, zero, or positive.
In this example, the array M could better be named Boundry. A Fortran 90 translation is on the right. It looks like the index of the A(I) before each zero value gets stored as a boundry.
SUBROUTINE SMARK( A, N, M) C STORE INDICES OF FRAME BOUNDARIES DIMENSION A(70), M(6) M(1) = 1 J= 1 DO 20 I =2,N DO I = 2, N IF (A(I)) 20, 21, 20 IF (A(I) == 0) THEN 21 J = J + 1 J = J + 1 IF(J - 7) 22, 20, 20 ELSE IF (J < 7) THEN 22 M(J) = I Boundry(J) = I 20 CONTINUE END IF RETURN END DO ENDSMARK was programmed by Alicia Ewing about 1963 on an IBM 7094 at the Lawrence Radiation Laboratory in Berkeley, Calif. It is part of a large program for analysis of lipoprotein patterns in an analytic ultracentrifuge. It would make more sense in that context. We can see it is quite well behaved, getting all its values from arguments, and returning boundries M with no side effects.
21 LFLAG=0 NP = MIN0(NP,6) 22 WRITE (4,903) 903 FORMAT (' 1. FIRST FRAME NO. = ',$) CALL READIN(NFF) IF (LFLAG.EQ.1) GO TO 30 23 WRITE (4,904) 904 FORMAT (' 2. LAST FRAME NO. = ',$) CALL READIN(NLF) 30 WRITE (4,905) 905 FORMAT (' ERROR? IF SO, ENTER LINE #; IF NOT, 0 ',$) CALL READIN(LINE) IF (LINE.EQ.0) GO TO 35 IF (LINE.GT.2) GO TO 30 LFLAG=1 GO TO (22,23),LINE 35 FRC=.TRUE.You will note the extensive comments explaining the logic of this program. We first read the values NFF (Number_of_First_Frame) and NLF (National_Liberation_Front), then ask for a line number that needs correcting, or 0 if all is well. Should one of the numbered lines be indicated, we branch to the code for entering it again. Since we don't want to enter everything again, LFLAG is used to skip the other entries after correction. Is this all clear? I hope you can do better than this!
Old Fortran's way of making data global was by using COMMON blocks. The names of the COMMON blocks, as well as names of subprograms, are known to the linker. A COMMON block has a list of variables. At best, in all the declarations of the same COMMON block in different subprograms, the variables have the same type, shape, and use. At worst, they can be unrelated, of differing types, and possibly in conflict. It was sometimes necessary to save space by letting different subroutines use the same common blocks in different ways. Problems would result if one subroutine then assumed that values were preserved between calls.
In the following example, some variables that are in effect constant, are stored in COMMON, and used by a subroutine. The whole common block declaration has to be included, in order to reference the correct location in the block. A compiler has no way of checking this.
SUBROUTINE STOX(S,T,X,N) STOX2 COMMON /FX/ NT,NTD,NFR(5),EC,EL,GZERO STOX3 COMMON /XMACH/ DELT(10),EFACT(3),XZERO,XSC,EMAG(3),CSC STOX4 DIMENSION S(70), T(70), X(70) STOX5 DO 10 I = 1,N STOX6 XT = GZERO - S(I)*XSC*T(I) STOX7 X(I) = EXP(XT) STOX8 10 CONTINUE STOX9 RETURN STOX10 END STOX11Only GZERO and XSC are needed, since they are in different COMMON blocks, we need the declarations of both of them.
By browsing the code, I found that GZERO is set in the main program while XSC and XZERO are initialized by DATA statements in a BLOCK DATA unit. This is how you had to initialize variables (not protected against change) in those days. One wonders why GZERO was placed in another COMMON block.
GZERO = ALOG(XZERO) UCF.37LOG, the natural logarithm, used to be called ALOG so classical programmers would recognize its type REAL.
BLOCK DATA ALLRUN BLOC2 C THESE VALUES IN COMMON FOR ALL RUNS, EXCEPT AREA MAG BLOC3 COMMON /XMACH/ DELT(10),EFACT(3),XZERO,XSC,EMAG(3),CSC BLOC4 C BLOC7 DATA DELT / -1.3634, 0.0, 2.0, 6.0, 8.0, 14.0, 22.0, 30.0, 48.0, BLOC8 1 64.0 / BLOC9 DATA (EFACT(I) ,I = 1,3)/ 10.97, 11.64, 11.69/ BLOC10 DATA XZERO, XSC / 7.2120, 0.00018232/ BLOC11 DATA CSC /.00008881/ BLOC12 C ........ there was more ......In Fortran 90 we can define a module, so subprograms can USE it:
MODULE All_Runs REAL, PARAMETER :: Delta_Time(10) = & (/ -1.3634, 0.0, 2.0, 6.0, 8.0, 14.0, 22.0, 30.0, 48.0, 64.0 /) REAL, PARAMETER :: Enlargment_Factor(3) = (/ 10.97, 11.64, 11.69/) REAL, PARAMETER :: X_zero = 7.2120, & XSC = 0.00018232, & !!wish we knew what it is CSC = 0.00008881, & G_zero = LOG(X_zero) !!a constant expression END MODULE All_RunsNow if there is code that changes any of these values, the compiler will let us know about it. We can then reevaluate our assumption that the value is constant.
Up to top of this document
Back to Fortran notes
Back to Lin Jensen's home page.