3

I am new in Fortran. So I need help. I'm using gfortran on SUSE to compile my code and receive the following error:

200 IF ( ID .EQ. 4HEOT ) GO TO 20
               1

Error: Operands of logical operator '.eq.' at (1) are INTEGER(4)/HOLLERITH

Main file for code is attached in the below link where at 1818 line shows the error.

My file's link is: https://files.engineering.com/getfile.aspx?folder=cd6961f3-d38b-4e61-a43d-269fa18c7d11&file=sfeng.f

How to fix this one?

For simplified/minimal example, I have added here the code:

      SUBROUTINE CDRD ( II )

      IMPLICIT DOUBLE PRECISION (A-H,O-Z)
c     ohad 15/7/08
c      IMPLICIT INTEGER*8 (I-N)
      IMPLICIT INTEGER*4 (I-N)

C*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=C
C     THIS SUBROUTINE READS PROPULSION SYSTEM DRAG DATA.               C
C                                                                      C
C     USE NON-ZERO "II" TO WRITE TABLE DATA.                           C
C*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=*=C

      CHARACTER*80    TITLE, CDFILE
      DIMENSION       A(100),IREP(30),IDD(4)

      COMMON /UNITS / IU5, IU6, IU7, IU8, IU9, IU16, IU17, IU18
      COMMON /CYUNIT/ IU3, IU4, IU10, IU11, IU12, IU13, IU14, IU15
      COMMON /CYICOM/ IENG, IPRINT, NPRINT, NPDRY, NPAB, NITMAX,
     1                IVAT, LIMCD
      COMMON /CDSIZE/ CDNOZ(5000)
      COMMON /ICDTAB/ ICDDAT(10), NTBL
      COMMON /CDLOC/  LOCCD(5)
      COMMON /CDFIL / CDFILE, A10, A9REF, A10REF, XNOZ, XNREF, RCRV,
     1                NAB, NABREF
C======================================================================C
      IU12  = 12
      IUNIT = IU12
      OPEN (UNIT=IUNIT, FILE=CDFILE, STATUS='OLD', ERR=9992)
      REWIND (IUNIT)
      NTBL = 0
      NMAX = 5000
      MR   = 0
      IF ( NTBL .EQ. 0 ) THEN
        LOC = 1
        DO 10 M = 1,NMAX
   10   CDNOZ(M) = 0.
      ENDIF

   20 READ (IU12, 5000, END=400, ERR=6666 ) IP, ITABNO, TITLE

   30 IF(ITABNO .EQ. 0) THEN
        NREM = NMAX-LOC
        IF ( II .GT. 0 ) THEN
          WRITE(IU6,5010) NTBL
          WRITE(IU6,5020) (N, ICDDAT(N), LOCCD(N), N = 1,NTBL)
          WRITE(IU6,5030) NMAX, NREM
        ENDIF
        IF( MR .GT. 0 ) WRITE(IU6,5040) (IREP(IQ), IQ = 1,MR)
        RETURN
      ELSE
        NTBL = NTBL+1
        ICDDAT(NTBL) = ITABNO
        LOCCD(NTBL)  = LOC
        IF ( NTBL .GT. 1 ) THEN
          DO 40 I = 2,NTBL
            IF ( ITABNO .EQ. ICDDAT(I-1) ) GO TO 50
   40     CONTINUE
          GO TO 150
   50     MLOC = LOCCD(I-1)
          ILOC = MLOC
          LOCCD(I-1) = LOC
          NTBL = NTBL - 1
          MR   = MR + 1
          IREP(MR) = ITABNO
          LIBLOC = 100000
          DO 60 IRK = 1,NTBL
            LIBRA = LOCCD(IRK)
            IF ( (LIBRA .GE. MLOC) .AND. (LIBRA .LT. LIBLOC) )
     *                                  LIBLOC = LIBRA
   60     CONTINUE
          LEO = LIBLOC - MLOC
          IF ( LEO .NE. 0 ) THEN
            IZAR = LOC - 1
            DO 70 I = LIBLOC,IZAR
              CDNOZ(MLOC) = CDNOZ(I)
              MLOC = MLOC + 1
   70       CONTINUE
            DO 80 I = 1,NTBL
              LLOC = LOCCD(I)
              IF ( LLOC .GT. ILOC ) LOCCD(I) = LLOC - LEO
   80       CONTINUE
          ENDIF
          DO 90 I = MLOC,LOC
   90     CDNOZ(I) = 0.
          LOC = MLOC
        ENDIF
      ENDIF

  150 IF ( II .GT. 0 ) THEN
        WRITE ( IU6, 5060 ) ITABNO, TITLE
        IP = 1
      ENDIF

      ICC = 0
      LZ  = LOC
      DO 180 ICL = 1,4
  180 IDD(ICL) = 4H    
  190 IDL = ID
      READ (IU12, 5070, END=200, ERR=6666 ) ID, N, (A(I), I = 1,N)
  200 IF ( ID .EQ. 4HEOT ) GO TO 20
      ICC = ICC + 1
      IF ( ICC .LE. 4 )      IDD(ICC) = ID
      IF ( ID  .EQ. IDL )    GO TO 280
      IF ( ID  .NE. IDD(4) ) GO TO 210
      IF ( IDL .EQ. IDD(2) ) GO TO 280
      LOC = LE
      L = LX
      GO TO 220
  210 CDNOZ(LOC) = N
      L  = LOC
      IF ( ID .EQ. IDD(3) ) LX = L
      IF ( ID .NE. IDD(2) ) GO TO 260
      LY = L
      LZ = LZ + 1
      GO TO 260

C ... WRITE THE TABULAR DATA.
  220 IF ( IP .NE. 0 ) THEN
        LY = LY+1
        WRITE(IU6,5080) IDD(1), CDNOZ(LZ), IDD(2), CDNOZ(LY)
        JF = 0
        M  = N
        LF = LX
  240   NP = M
        IF ( M .GT. 8 ) NP = 8
        M  = M - NP
        LE = LF + NP
        LF = LF + 1
        WRITE(IU6,5090) IDD(3), (CDNOZ(I), I = LF,LE)
        LF = LE
        JE = JF + NP
        JF = JF + 1
        WRITE(IU6,5090) IDD(4), (A(I), I = JF,JE)
        JF = JE
        IF( M .GT. 0 ) GO TO 240
      ENDIF

  260 DO 270 I = 1,N
        LOC = LOC + 1
        CDNOZ(LOC) = A(I)
  270 CONTINUE
      LE = LOC
      IF ( ID .EQ. IDD(4) ) CDNOZ(LOC+2) = 1.
      LOC = L + 2*N + 6
      IF ( LOC .GT. NMAX ) GO TO 300
      GO TO 190
  280 CDNOZ(LOC) = CDNOZ(LX)
      L = LOC
      DO 290 I = 1,N
        LOC = LOC + 1
        CDNOZ(LOC) = CDNOZ(LX+I)
  290 CONTINUE
      GO TO 220
  300 WRITE(IU6,5100) ITABNO
      ITABNO = 0
      GO TO 30

  400 CONTINUE
      ITABNO = 0
      GO TO 30

 6666 CONTINUE
      WRITE(IU6,6669) IU12
      STOP

 5000 FORMAT (I1,I4,A)
 5010 FORMAT (//,33X,'TABLE DATA INPUT SUMMARY, ',I3,' TABLES',//,
     1    28X,'TABLE NUMBER  REFERENCE NUMBER   ARRAY LOCATION')
 5020 FORMAT (33X,I2,12X,I5,14X,I5)
 5030 FORMAT (/,36X,'DATA STORAGE ALLOCATION ',I7,/,
     1          36X,'DATA STORAGE NOT USED   ',I7,/)
 5040 FORMAT(10X,'THE FOLLOWING TABLES HAVE BEEN REPLACED',10(I5,','))
 5060 FORMAT (//,3X,I4,A,/)
 5070 FORMAT(A4,I3,3X,(T11,7F10.0))
 5080 FORMAT(1X,A4,' = ',E13.5,1X,A4,' = ',E13.5)
 5090 FORMAT(20X,A4,1X,8E13.5)
 5100 FORMAT (' ********* TABLE OVER FLOW, TABLE ',I5,' NOT LOADED')
 6669 FORMAT(/,' ERROR READING ENGINE TABULAR INPUT DATA FROM UNIT',
     *       I3,'.',/,' PROGRAM ABORTED IN SUBROUTINE TABRD.')

 9992 CONTINUE
      WRITE(IU6,9999) 'ERROR OPENING THE INPUT FILE ', CDFILE,
     *       ' AS UNIT ', IUNIT, '.',
     *              'PROGRAM ABORTED IN SUBROUTINE CDRD.'
 9999 FORMAT(//,1X,2A,/,A,I2,A,/,1X,A,/)
      STOP
      END
Khan
  • 41
  • 1
  • 5
  • I don't know why EQ is not acting as it should be. – Khan Aug 07 '18 at 19:22
  • What are the Hollerith constants? – Khan Aug 07 '18 at 19:31
  • `4HEOT ` is a Hollerith constant. It is what we would now call `"EOT "`. For us to provide more help you should give more context (see [mcve] - and yes this does require effort). Also, many users here may be reluctant to provide help for code which was obsolete more than 40 years ago. – francescalus Aug 07 '18 at 19:38
  • Thanks, @francescalus . I have added the minimum portion of the code in my post. I am not understanding that why the numeric number is 4 in the first letter when there is only "EOT"-3 letters and what does it mean by EOT? – Khan Aug 07 '18 at 20:33
  • There is a space after `EOT`. – francescalus Aug 07 '18 at 20:35

3 Answers3

5

You are obtaining an error because your code uses non-standard FORTRAN 77 code that your compiler (gfortran) does not support.

As gfortran detects, you are using a Hollerith constant, 4HEOT.

Hollerith was the predecessor of the character type. The last Fortran standard that allowed the use of Holleriths was FORTRAN 66 (ANSI X3.9-1966). Despite not being a part of the FORTRAN 77 standard, it contained an Appendix C with recommendations to processors that wanted to provide it as an extension. The use you make of the Hollerith does not even follow those recommendations, in particular:

C3. Restrictions on Hollerith Constants

A Hollerith constant may appear only in a DATA statement and in the argument list of a CALL statement.

So what is going on?

The relevant statements of your code are

      IMPLICIT INTEGER*4 (I-N)
      READ (IU12, 5070, END=200, ERR=6666 ) ID, N, (A(I), I = 1,N)
  200 IF ( ID .EQ. 4HEOT ) GO TO 20
 5070 FORMAT(A4,I3,3X,(T11,7F10.0))
  1. Variable ID is implicitly declared as a 4-byte integer using the non-standards conforming integer*4 syntax (see Fortran: integer*4 vs integer(4) vs integer(kind=4) for more on that).

  2. The READ statement assigns a value to ID using the A4 edit descriptor. This is the way Appendix C of the FORTRAN 77 standard allowed to read a Hollerith variable:

    C1. Hollerith data type

    Hollerith is a data type; however, a symbolic name must not be of type Hollerith. Hollerith data, other than constants, are identified under the guise of a name of type integer, real, or logical. They must not be identified under the guise of type character. [...]

    A Hollerith datum is a string of characters. [...] The blank character is significant in a Hollerith datum. Hollerith data may have an internal representation that is different from that of other data types.

    An entity of type integer, real, or logical may be defined with a Hollerith value by means of a DATA statement (C4) or READ statement (C6). [...] When an entity of type integer, real, or logical is defined with a Hollerith value, the entity and its associates become undefined for use as an integer, real, or logical datum.

    C6. A Editing of Hollerith Data

    The Aw edit descriptor may be used with Hollerith data when the input/output list item is of type integer, real, or logical. On input, the input list item will become defined with Hollerith data. On output, the list item must be defined with Hollerith data.

    Editing is as described for Aw editing of character data except that len is the maximum number of characters that can be stored in a single numeric storage unit.

    So now the integer variable ID contains Hollerith data that describes 4 characters. With one character per byte, and ID defined as a 4-bytes variable, that seems fine.

  3. The IF statement compares the Hollerith variable ID with the Hollerith constant 4HEOT (probably to check if you are at an End Of Table, given the context). That does not seem to be supported even by the suggested standard extension, but, hey, in the end we have two strings made of 4 characters, so deciding whether they are equal or not should not be very difficult. It's just a pitty that gfortran has never been told how to do so (ironic mode off).

How can you fix this?

I can think of a number of possibilities (in addition to finding the person who wrote this code, who is likely to be retired, and nicely asking him to fix it). The best solution for the future is Option 1:

Option 1

Rewrite the code by introducing new character variables so that all I/O with character edit descriptors (A[w]) correspond to listed character variables. Replace the problematic Hollerith constant by the character constant "EOT ".

Option 2

Some Fortran compilers are happy reading and writing integers using character edit descriptors, and are not particularly good at remembering that those integers are Hollerith variables rather than actual integers. Use one of those compilers (e.g., gfortran): as you saw, it thought that ID was still an integer, not a Hollerith. Therefore, assume that ID stays an integer, and that the read operation just reads the 4-character variable into it.

In this case, you can replace the Hollerith constant with the integer it would encode to. You can do this, e.g., by defining

      DATA ID_EOT/4HEOT /

Now ID_EOT has an integer value (probably ICHAR("E")+256*(ICHAR("O")+256*(ICHAR("T")+256*ICHAR(" ")))) and you can replace your problematic IF statement by

  200 IF ( ID .EQ. ID_EOT ) GO TO 20

This option is not standards compliant, and therefore not portable and likely to cause problems in the future (to you or other people) similar to the one you are experiencing now. However, it would at least conform to a written recommendation on how to implement the extension, which is better than what you have now.

The following compilers (versions checked) seem to support a DATA statement with a Hollerith: Intel (17.0.4), gfortran (7.3.0), CRAY (8.5.8), PGI (18.4), NAG (6.2), and Sun (8.8). Except for the NAG compiler, all of them seem to allow to read/write an integer with a character edit descriptor. Note that testing was very limited, just to the 4HEOT constant.

Option 3

Use a compiler that can cope with your code - I believe Intel Fortran can compile and run it.

This option is not standards compliant, and therefore not portable and likely to cause problems in the future (to you or other people) similar to the one you are experiencing now. It does not even conform to the extension recommendation in Appendix C of the FORTRAN 77 standard. It is the option that requires less work, at the cost of not improving anything and keeping the problem intact for the future - when fewer people that ever coded in FORTRAN 66 will be alive.

jme52
  • 1,123
  • 9
  • 18
0

As the compiler error says, you are comparing an integer with a HOLLERITH, that I just discovered is a string of character used before FORTRAN77 ! You cannot compare an integer with a string.

If you want to transform the string in integer using read, see here.

If you want to compare the strings, use write instead.

0

There are a couple of workarounds. Of course it's possible to change all Hollerith constants to CHARACTER variables, but it's a little problematic given that Hollerith arguments to subprograms don't pass an extra hidden length along with them the way CHARACTER arguments do. How a Hollerith constant behaves in expressions, in compilers that support this syntax, is in general inconsistent, poorly documented, and pretty much unsupported. In DATA statements maybe better supported, but don't count on that.

gfortran says that they support Hollerith constants as function arguments, but the classic conversion functions like INT that were the first to support BOZ literals don't work: see my example below. If you like the sound of distant maniacal laughter you could send a bug report to bugzilla about this. I had more success with TRANSFER and also with an assignment:

program holler
   use ISO_FORTRAN_ENV
   integer(INT32) ID
! holler.txt should exist in the current directory
! and contain at least 4 characters
   open(10,file='holler.txt',status='old')
   read(10,'(A4)') ID
!   write(*,'(*(g0))') 'ID == 4HEOT  = ',ID == 4HEOT ! Fails
!   write(*,'(*(g0))') 'ID == 4HEOT  = ',ID == int(4HEOT ,KIND(ID)) ! Fails
   write(*,'(*(g0))') 'ID == 4HEOT  = ',ID == transfer(4HEOT ,ID) ! Success
   BLOCK
      integer(kind(ID)) compare
      compare = 4HEOT ! Note trailing space
      write(*,'(*(g0))') 'ID == 4HEOT  = ',ID == compare ! Success
   END BLOCK
end program holler
user5713492
  • 954
  • 5
  • 11
  • IMHO, using a Hollerith constant (FORTRAN 66, extension in FORTRAN 77) as an argument to the TRANSFER intrinsic function (introduced in the Fortran 95 standard) is like trying to leave a donkey for a couple of hours in the car parking of The Shard: it may work, but it will involve mixing items that belong to disconnected eras, there are no rules about it at all, and it is likely that it is either not supported or not extensively validated. Using a Hollerith in a DATA statement makes much more sense, as that was part of the 66 standard so should have been supported and validated at some point. – jme52 Aug 08 '18 at 19:22
  • The use of a Hollerith inside of a BLOCK (introduced in Fortran 2008) is even more shocking, but I understand that was for clarity in the example... – jme52 Aug 08 '18 at 19:26
  • @ripero if you think `Hollerith` is significantly supported or validated in any context, well... But that hasn't been my experience. It's crufty enough that it really can't be trusted in my opinion. In fact `TRANSFER` was an example given in [the gfortran manual](https://gcc.gnu.org/onlinedocs/gfortran/Hollerith-constants-support.html#Hollerith-constants-support). – user5713492 Aug 09 '18 at 03:03
  • I updated my answer with some info on compilers. It would be great if you could provide some insights on how Holleriths fail when they seem to be supported. I wouldn't trust Holleriths myself - and please let's not go into BOZ literals... – jme52 Aug 09 '18 at 06:32
  • @ripero I don't think I'll have time just now, I'm really busy. But busy is good. If you just read the available documentation for a given compiler you will find that it's pretty ambiguous in this area and not really consistent with what the compiler does. Vendors have a lot on their plate just trying to support things like parameterized derived types and transformational intrinsics in constant expressions and I would rather they allocated their efforts in support of standard-conforming code. – user5713492 Aug 09 '18 at 06:50