f18-llvm-project icon indicating copy to clipboard operation
f18-llvm-project copied to clipboard

semantic error: Format expression must be default character or integer

Open oroppas opened this issue 4 years ago • 9 comments

/mis/itmprt.f:112:21: error: Format expression must be default character or integer
       & WRITE  (OTPE,CORE) (ICORE(I),I=NS,NP)

gfortran gives

./mis/itmprt.f:112.20:

     & WRITE  (OTPE,CORE) (ICORE(I),I=NS,NP)                            
                    1
Warning: Legacy Extension: Non-character in FORMAT tag at (1)

oroppas avatar Jun 23 '21 14:06 oroppas

Note to myself: this is showstopper to compile https://github.com/nasa/NASTRAN-95

oroppas avatar Jun 30 '21 09:06 oroppas

We're going to have to see more context. How is CORE declared?

klausler avatar Jul 12 '21 17:07 klausler

The error can be reproduced by the following piece of code:

      SUBROUTINE ITMPRT (OTPE)

      INTEGER         OTPE
      DIMENSION       ICORE(4)
      COMMON /ZZZZZZ/ CORE(1)
      EQUIVALENCE     (ICORE(1),CORE(1))

      INUM = NZ/2 - 1
      NS   = INUM + 1
      NP   = INUM - 1

      WRITE  (OTPE,CORE) (ICORE(I),I=NS,NP)

      END

oroppas avatar Jul 12 '21 18:07 oroppas

It's a valid message for that code snippet. I'm not sure what the original code was trying to accomplish.

klausler avatar Jul 12 '21 18:07 klausler

flang says error and gfortran says warning. Which one is the correct behavior?

oroppas avatar Jul 12 '21 18:07 oroppas

It is not a standard-conforming program, but it may be using a non-standard extension that f18 doesn't support. So both messages may be correct. If it's an extension that f18 should support, I'll need to see more context to understand what was supposed to happen. I suspect that a non-character array has been initialized or assigned with a Hollerith value that constitutes a format specification, but I can't be sure given what I'm been shown.

klausler avatar Jul 12 '21 18:07 klausler

Hmm, I'm not very familiar with NASTRAN-95, either. But I'm not surprised if NASTRAN uses non-standard extension.

oroppas avatar Jul 12 '21 18:07 oroppas

CORE is assigned as follows

      CORE(1) = OPAREN

with OPAREN

      EQUIVALENCE     (CCORE,CORE)
      EQUIVALENCE     (ICORE(1),CORE(1))
      DATA    OPAREN, CPAREN,EC,EC1,EC2,INTGC,ALPHC,ALPHC1,CONT,UNED,D/
     1        4H(1X , 4H)   ,4H,1P,,4HE13.,4H6   ,4H,I13,4H,9X,,4HA4  ,
     2        4HCONT, 4HINUE,4HD   /
      DATA    BLANK , SUBS,ITM/4H    ,4HSUBS,4HTRUC,4HTURE,4HITEM/
      DATA    EQSS  / 4HEQSS/, BGSS/4HBGSS/, CSTM/4HCSTM /,
     1        PLTS  / 4HPLTS/, LODS/4HLODS/, LOAP/4HLOAP /

Similar to #883?

oroppas avatar Jul 12 '21 18:07 oroppas

Thank you. Yes, it's the same non-standard extension. There's no good source work-around, so we'll just have to support it.

klausler avatar Jul 12 '21 18:07 klausler