Fortran 77 character array and comparison

Hi guys!
I come here from Java world. I need to convert some fortran 77 code to Java. Below is the Fortran code. Variable NACA looks very strange for me. It appears as parameter in subroutine, and then declared as CHARACTER*4 NACA, and next declared as DIMENSION NACA(80). What does this mean? What does the comparison IF(NACA(8).EQ.A4H1) NA=5 mean? Thanks a lot.

      SUBROUTINE DECODE(NACA,NA,X,LLL,IUM)
C
C****  READ USER INPUT NACA DESIGNATION AND DECODE
C
      LOGICAL IEQL,IPOINT
      CHARACTER*4 LET,NUM,A4H1,A4H4,A4H5,A4H6,A4HS
      CHARACTER*4 NACA
      DIMENSION X(50),IUM(10)
      DIMENSION NACA(80),LET(6),IVAL(10),NUM(10)
      DATA LET / '    ', 'A   ', '-   ', '=   ', '.   ', ',   '/
      DATA NUM / '1   ', '2   ', '3   ', '4   ', '5   ',
     1           '6   ', '7   ', '8   ', '9   ', '0   '/
      DATA IVAL/1,2,3,4,5,6,7,8,9,0/
      DATA A4H1,A4H4,A4H5,A4H6,A4HS/'1   ','4   ','5   ','6   ','S   '/
C
      IEQL=.FALSE.
      IPOINT=.FALSE.
      IF(NACA(8).EQ.A4H1)NA=5
      IF(NACA(8).EQ.A4H4)NA=1
      IF(NACA(8).EQ.A4H5)NA=3
      IF(NACA(8).EQ.A4H6)NA=6
      IF(NACA(8).EQ.A4HS)NA=7
      JCOUNT=0
      ICOUNT=0
      DO 1000 L=1,10
      IUM(L)=IVAL(10)
 1000 CONTINUE
      IF(NA.EQ.6) GO TO 1030
      IF(NA.EQ.7)GO TO 1060
C
C ... DECODE NACA 1,4 AND 5 SERIES
C
      DO 1020 ICOL=10,80
      ICOUNT=ICOUNT+1
      IF(ICOUNT.GT.10) GO TO 1120
      DO 1010 INUM=1,10
      IF(NACA(ICOL).EQ.NUM(INUM)) IUM(ICOUNT)=IVAL(INUM)
 1010 CONTINUE
      IF(NACA(ICOL).EQ.LET(1)) ICOUNT=ICOUNT-1
      IF(NACA(ICOL).EQ.LET(3).AND.NA.NE.5) NA=NA+1
      IF(NACA(ICOL).EQ.LET(5)) ICOUNT=ICOUNT-1
 1020 CONTINUE
      GO TO 1120
C
C ... DECODE NACA 6 SERIES
C
 1030 DO 1050 ICOL=10,80
      ICOUNT=ICOUNT+1
      IF(ICOUNT.GT.8) GO TO 1120
      DO 1040 INUM=1,10
      IF(NACA(ICOL).EQ.NUM(INUM)) IUM(ICOUNT)=IVAL(INUM)
 1040 CONTINUE
      IF(ICOUNT.EQ.3.AND.NACA(ICOL).EQ.LET(2)) ICOUNT=ICOUNT+1
      IF(ICOUNT.EQ.4.AND.NACA(ICOL).EQ.LET(2)) IUM(ICOUNT)=IVAL(1)
      IF(ICOUNT.GT.4.AND.NACA(ICOL).EQ.LET(2)) ICOUNT=ICOUNT-1
      IF(NACA(ICOL).EQ.LET(1)) ICOUNT=ICOUNT-1
      IF(NACA(ICOL).EQ.LET(6)) ICOUNT=ICOUNT-1
      IF(NACA(ICOL).EQ.LET(3).AND.ICOUNT.EQ.3) ICOUNT=ICOUNT+1
      IF(NACA(ICOL).EQ.LET(4)) IEQL=.TRUE.
      IF(IEQL.AND..NOT.IPOINT) ICOUNT=ICOUNT-1
      IF(NACA(ICOL).EQ.LET(1).AND.IEQL.AND..NOT.IPOINT) ICOUNT=ICOUNT+1
      IF(NACA(ICOL).EQ.LET(5)) IPOINT=.TRUE.
 1050 CONTINUE
      GO TO 1120
C
C ... DECODE SUPERSONIC SERIES
C
 1060 CONTINUE
      ICOUNT=0
      NCOUNT=2
      DO 1110 ICOL=10,80
      IF(ICOUNT.EQ.10)GO TO 1110
      IF(NACA(ICOL).EQ.LET(1).AND.ICOL.EQ.80)GO TO 1090
      IF(NACA(ICOL).EQ.LET(1))GO TO 1110
      DO 1070 INUM=1,10
      IF(NACA(ICOL).NE.NUM(INUM))GO TO 1070
      NCOUNT=NCOUNT+1
      IF(NCOUNT.GT.3)GO TO 1110
      ICOUNT=ICOUNT+1
      IUM(ICOUNT)=IVAL(INUM)
      GO TO 1080
 1070 CONTINUE
      IF(NACA(ICOL).EQ.LET(3).AND.ICOUNT.GT.0)GO TO 1090
      IF(NACA(ICOL).EQ.LET(5).AND.ICOUNT.GT.0)GO TO 1100
 1080 IF(ICOL.EQ.80)GO TO 1090
      GO TO 1110
 1090 CONTINUE
      IF(NCOUNT.EQ.0)ICOUNT=ICOUNT+3
      IF(NCOUNT.EQ.1)IUM(ICOUNT+1)=IUM(ICOUNT)
      IF(NCOUNT.EQ.1)IUM(ICOUNT)=0
      IF(NCOUNT.EQ.1)ICOUNT=ICOUNT+2
      IF(NCOUNT.EQ.2)ICOUNT=ICOUNT+1
      IF(ICOUNT.EQ.1)NCOUNT=0
      IF(NCOUNT.GT.0)NCOUNT=0
      GO TO 1110
 1100 CONTINUE
      IF(NCOUNT.EQ.0)ICOUNT=ICOUNT+2
      IF(NCOUNT.EQ.0)NCOUNT=2
      IF(NCOUNT.EQ.1)IUM(ICOUNT+1)=IUM(ICOUNT)
      IF(NCOUNT.EQ.1)IUM(ICOUNT)=0
      IF(NCOUNT.EQ.1)ICOUNT=ICOUNT+1
      IF(NCOUNT.EQ.1)NCOUNT=2
 1110 CONTINUE
C
 1120 CONTINUE
C
C  GET X-COORDINATES WHERE AIRFOIL COORDINATES ARE TO BE CALCULATED
C    X SPACING IS CLOSEST IN THE NEIGHBORHOOD OF THE L.E.
C
      DELX=0.00100
      X(1)=0.0
      DO 1130 LI=2,50
      LLL=LI
      X(LI)=X(LI-1)+DELX
      IF(X(LI) .GE. .0059) DELX=.002
      IF(X(LI) .GT. .009) DELX=.010
      IF(X(LI) .GT. .059) DELX=.020
      IF(X(LI) .GT. .419) DELX=.030
      IF(X(LI) .GT. .449) DELX=.050
      IF(X(LI) .GT. .799) DELX=.020
      IF(X(LI) .GE. 1.00) GO TO 1140
 1130 CONTINUE
 1140 CONTINUE
      X(LLL)=1.0
      RETURN
      END

The types of variables are not declared in the argument lists in Fortran. So the subsequent statement declares the type of NACA (in this case a character variable of length 4). Also, in Fortran the type and other attributes of a variable may be declared in separate statements. Thus, NACA is an array of length 4 characters with size 80. In modern Fortran the declaration would look like

character(len=4), intent(in) :: naca(80)

The statement IF(NACA(8).EQ.A4H1) NA=5 is a conditional statement. If the element in position 8 of NACA is equal to the value in A4H1 (which from the data statement above appears to be "1 ", then assign NA the value 5.

Welcome to the Fortran world. Hope we can help.

Edit: I got the size wrong initially.

2 Likes

Hi Tran Hung,

You could try using a Fortran to Java (or Java bytecode) compiler like F2J which was built to translate BLAS and LAPACK. Since the compiler follows a set of formal rules, ideally it would give stronger guarantees in terms of correctness of the translation, compared to a manual conversion. Obviously, this doesn’t protect you from any bugs that may be lurking in the original Fortran program.

Best wishes,
Ivan

1 Like

If you are dealing with the old NACA 4, 5 or 6 digit airfoil series, you need to look at the NACA456 routines at Ralph Carmichael’s Public Domain Aeronautical Software (PDAS) site:

Ralph has translated the old NASA codes of Ladson and Brooks from 1974-1975 to Fortran 90. I think he has routines for doing something similar to what the OP is trying to do.

There is also a MATLAB code that is a wrapper around Carmichaels code.
See:

The MATLAB source is available by clicking on the Functions folder and then cut and pasteing with an editor to a text file.

Not sure where the OP got his code but it looks like an old NASA report of some kind.

You might also look at the NASA Glenn FoilSym program which is Javascript I think. There is a version that runs offline.

https://www.grc.nasa.gov/www/k-12/freesoftware_page.htm

The source code for all the NASA Glenn applets is at:

1 Like

Thanks for reply. Why the following code prints 1111, but not the 8-th element (must be 8888)?

      PROGRAM TEST
      CHARACTER*4 naca
      DIMENSION naca(80)
      naca='111122223333444455556666777788889999'
      Print *, naca(8)

      END PROGRAM TEST

The program declares an array of 80 character variables in naca, each with length 4, and it sets each of them to ‘1111’. gfortran -Wall -Wextra says

xtest.f90:4:49:

    4 |       naca='111122223333444455556666777788889999'
      |                                                 1
Warning: CHARACTER expression will be truncated in assignment (4/36) at (1) [-Wcharacter-truncation]

ETA: Here is a program that prints a substring.

      PROGRAM TEST
      CHARACTER*36 naca
      naca='111122223333444455556666777788889999'
      Print *, naca(29:32)
      END PROGRAM TEST

Output: 8888

1 Like

Change this print statement to

print *, naca

and you should understand what the code is doing.

1 Like

Thanks.