Redundant parenthesis, parenthesis used to force evaluation as an expression, and other things to be cautious about

I have seen several posts showing how to use parenthesis for valid uses such as passing a variable by value and forcing a variable to be used as an expression in in an ASSOCIATE and so on … all valid uses but I would just like to caution that compilers have a lot of bugs (or sometimes “extensions”) regarding parenthesis. Just as one example (based on some real code) and three compilers …

    program testit
complex :: c1, c2
real,parameter :: r1=20.0, r2=30.0
c1=10.0
c2=-10.0
write(*,*)(c1*r2,0.0)
write(*,*)(r1*r2,0.0)
write(*,*)(r1,r2)
end program testit
(base) urbanjs@venus:/tmp$ gfortran xx.f90&&./a.out
xx.f90:6:17:

    6 | write(*,*)(c1*r2,0.0)
      |                 1
Error: Expected a right parenthesis in expression at (1)
xx.f90:7:17:

    7 | write(*,*)(r1*r2,0.0)
      |                 1
Error: Expected a right parenthesis in expression at (1)
(base) urbanjs@venus:/tmp$ ifort xx.f90&&./a.out
 (300.0000,0.0000000E+00)  0.0000000E+00
   600.0000      0.0000000E+00
 (20.00000,30.00000)
(base) urbanjs@venus:/tmp$ nvfortran xx.f90&&./a.out
 (300.0000,0.000000)    0.000000    
    600.0000        0.000000    
    20.00000        30.00000 

complex constants are involved in the most common non-standard behaviors.

1 Like

And LFortran:

$ lfortran xx.f90 
code generation error: ComplexConstructor with runtime arguments not implemented yet.

So it sees it as a complex number, just the LLVM backend doesn’t have this implemented yet. I noticed that GFortran doesn’t even allow it, so I wasn’t in rush providing an implementation for this, beyond the parsing and semantics.

Well, it does get confusing but gfortran does get the standard one OK; and so does ifort. Only nvfortran gets this one wrong:

program testit
real,parameter :: con1=10.0, con2=20.0
write(*,*)(con1,con2)
end program testit

nvfortran ignores the parens and prints two reals, but gfortran and ifort get this one write and get a complex constant. If con1 and con2 were not parameters I believe gfortran is correct and considers it an error; but ifort and nvfortran ignore them like they were not there; it should only be a valid complex constant if it has constant values; last I looked it was a little vague about what (con1) should be; which I have seen several errors on in the past; is that a complex value with only the real value specified or is that an expression? I am not sure but I think the standard now specifically indicates a complex constant must be of the form (A,B) with A and B both constants but I have not checked lately. So it is particularly confusing when ifort and nvfortran ignore the parens, because that means (A,B) is two reals in the WRITE if A and B are not constant, but a complex value if A and B are constant. I need to reread the latest standard again to be positive; but a lot of compilers have treated parenthesis differently over the years so I avoid redundant parens and use cmplx even though (10.0,20.0) is much briefer. The worst one I remember reporting was one
where (A,B) was treated as an implied do loop with no limit, like a DO with no counter and caused an infinite loop. I think it is better than in the past, but as the example shows it still is not a bad idea to double check anywhere (value(s)) is used.

1 Like

LFortran also works on this example and produces a complex number.

That’s what I thought then, just could not get through that many levels and still be sure
(or just quit reading :>). You’ve gone through that a lot more, so I think you might have forgotten that the standard is not exactly a casual read! I have just encountered so many problems over the years with parenthesis I tend to be very cautious in their use. Once bitten … .

Thanks!

I agree. My one exception is I prefer them around anything using powers like (2**3)**4 in all languages.

The example here is valid. Named (PARAMETER) constants ARE constants. The rules for a complex constant are:

R718 complex-literal-constant is ( real-part , imag-part )

R719 real-part is signed-int-literal-constant
or signed-real-literal-constant
or named-constant
R720 imag-part is signed-int-literal-constant
or signed-real-literal-constant
or named-constant

I agree that (c1*r2,0.0) is NOT a complex constant.

1 Like

Not really. With ifort, you can request diagnostics if it detects source doesn’t conform to a particular standard, but the default behavior is always whatever current standard it supports F2018 at present.) If you don’t ask for standards warnings, you always get the current standard. There are some -assume options to affect behaviors that changed (or became specified) in later standards, and an option to support F66 syntax (such as EXTERNAL*).

I should have shown the output. This was supposed to be showing ifort and gfortran print that as a complex value (correctly), but nvfortran (incorrectly) prints that as two real values. The first time I tried something like c1=(10.0**2,0.0) and it did not work I was confused, but upon reflection realized an expression using all constant values is not technically a constant and have avoided that since.

 program testit
real,parameter :: con1=10.0, con2=20.0
write(*,*)(con1,con2)
end program testit
gfortran aa.f90&&./a.out;ifort aa.f90&&./a.out;nvfortran aa.f90&&./a.out
             (10.0000000,20.0000000)
 (10.00000,20.00000)
    10.00000        20.00000    

Maybe nvfortran prints complex values that way with * format? Otherwise, it would be strange, as if (con1,con2) is not a complex constant, what could it be? There is no comma-operator in Fortran (as it is in C), AFAIK.

Well, that really does not detract much from being wary of parenthesis, does it? …

nfortran xx.f90&&./a.out
```fortran
program testit
real,parameter :: con1=10.0, con2=20.0
complex :: c1=(30.0,40.0)
write(*,*)(con1,con2),c1,(1,2)
end program testit
10.00000        20.00000      (30.00000,40.00000)  (1.000000,2.000000)

Indeed. Extraneous commas accepted in various places is ie another
common extension (sometimes useful).

Just for the record, the diagnostics printed by GNU Fortran isn’t the only
possibility. But a compiler has to guess what the programmer wants to do.

The fragment “c1*r2,0.0” in the first WRITE statement could also be an
‘io-implied-do-object-list’. So, after comma, an ‘io-implied-do-control’
could follow and in that case the ‘)’ would be an unexpected token.

Below is an example where the ‘output-item’ is an ‘io-implied-do’ :

program testit
complex :: c1, c2
real,parameter :: r1=20.0, r2=30.0
c1=10.0
c2=-10.0
write(*,*)(c1*r2,0.0,i=1,2)
!write(*,*)(r1*r2,0.0)
!write(*,*)(r1,r2)
end program testit

What would happen if you added
c1 = (con1, con2)
to your snippet? If () around con1/2 are really ignored in write, it should be an error. Another possible test would be sending (con1, con2) as an actual argument to a procedure expecting a complex.

Those more serious issues appear to work properly; so passing (con1,con2) results in a complex value being passed, as well as “c1=(con1,con2)” works as expected.