When are parentheses significant in Fortran?

My understanding is that in languages like Python or C++, you are free to use or not use parentheses around an expression. I recently learned this is not always the case in Fortran. Two examples I am aware of:

associate(x => y) ! x is read-write
associate(x => (y)) ! x is read-only

and

subroutine f(x)
integer, intent(out) :: x
...
end subroutine

call f(a) ! Allowed
call f((a)) ! Not allowed, cannot pass an expression to intent(out) arg.

Besides these two examples, is there any other place in Fortran when () is significant?

In most other cases, it does not matter whether you put extra parentheses or not, such as:

a = (x)
a = x
a = (1+2)
a = 1+2
...
1 Like

The point is that an expression may consist of a single variable name (in which case it is the value of the variable), but a single name can also appear in a context where it is actually a reference (for lack of a better word) to the variable.

2 Likes

And do not forget the special meanings parenthesis have for complex values and implied DO constructs, and what copying or reordering can occur because a reformatter changes the parenthesis. Try something
like “write(,)((i,i=1,10))” or “write(,)(((i),i=1,10))” as some simple examples; versus "write(,)(i,i=1,10). Even if the call f((a),…) worked because A was intent(in) there is a good chance an unneeded copy would have been made of A, depending on how much optimization opportunities the compiler acts on.

Parentheses can be used to change the order of operations, of course.

Related to one of your code examples, parentheses can be used to create a copy of a variable. If you have subroutine twice(x,y) that sets y to 2*x, and you want to use it double x, you can do so with call twice((x),x).

3 Likes

That is a nice trick - even though it would probably be misunderstood soon enough :slight_smile:

1 Like

This does not compile for me with gfortran:

write(*,*)((i,i=1,10))
end

I get:

a.f90:1:13:

    1 | write(*,*)((i,i=1,10))
      |             1
Error: Expected a right parenthesis in expression at (1)

Yes, (1.+2.)+3. is different to 1.+(2.+3.).

It seems that (expr) vs expr is only different if expr is a variable and it is used in the contexts above.

Thanks for this! Another such example.

regarding ((i,i=1,10)) not compiling – that is not surprising, as it could not resolve the implied DO into a complex constant definition, which is probably what it was trying to do, although the message is a little vague. Having just reported a few issues with parentheses added by LFortran a while ago when trying the fmt options I though you might want to know some of the times it would be fatal to insert otherwise harmless-looking “redundant” parenthesis.

1 Like

Nice but so easy to overlook; which might have been part of the path to the common extension of %REF and %VAL to make it more explicit; but I have seen a lot of code that does not do what you show and especially with older code without interfaces have it cause problems when both parameters get changed by the function; although a lot of compilers had flags to warn about that, so definitely worth noting. I am not positive the compiler would not be free to ignore the parens though; anyone know of a passage in the standard that says that HAS to generate a copy and not pass by reference (although I’ll bet it works on almost all compilers, I am wondering if it HAS to to be standard-complaint).

Some Fortran luminaries discussed in comp.lang.fortran in 1999 the meaning of something like
call twice((x),x). I do think it’s valid, and I got the idea of using () to create an expression from one of them and have not encountered problems with this use, for at least gfortran, g95, and Intel Fortran.

1 Like

A very interesting read on some subtle issues. Used to keep a large list of things to avoid that included something like this and resurrected a little piece of it to try to break a few things; and ifort and gfortran worked great numerically, as you mentioned; and nvfortran failed on a scoping issue, not the parenthesis; although everyone but ifort got some intentionally troublesome formats wrong. gfortran(1) just put out a little whitespace I think it technically should not; nvfortran lost it on some non-advancing I/O issues but that was really not part of the core test here. Things have come a long way. A devilish simple test like this used to quickly segfault a lot of compilers. I still will tend to avoid this even though it is elegant and “should work” because of some of the same misgivings as described in that discussion, as dated as it might seem at first glance. So without really expecting anyone to care about the code, a little tweek of an old “dusty corners” test only showed one numeric problem over what I would expect (in nvfortran) and it is quite a combination of bad ideas that it takes to trigger it. Ignoring the I/O issues (ifort had none, and gfortran had a relatively trivial one on a real dusty corner) I used this and everyone passed on the parenthesis issues, so I can’t point to anywhere it did not work (although trying to figure out what the answer “should be” even with such simple logic shows why to avoid some of the things done here!). I was actually pleased at how well the compilers produced what I would hope they would “under the circumstances”: …

   ! Travel the well-worn road ...
!
! If the same variable is used as an argument more than once in the same
! statement, beware.
! 
! If a function changes any argument values passed to it beware.
!
! beware of scope in contained procedures if using a variable also passed in

! WARNING: THIS CODE IS MEANT TO BREAK THINGS, NOT SHOW HOW TO DO ! THINGS

program puzzling
character(len=*),parameter :: gen_nvbug1='(g0.8,1x)'
character(len=*),parameter :: gen_nvbug2='(*(g0.8,1x),"never get here ")'
character(len=*),parameter :: gen_nvbug3='(*(g0.8,1x),/)'
character(len=*),parameter :: gfortran_bug='(":",2(g0.8,1x),/)'
character(len=*),parameter :: gen='(":",*(g0.8,1x))'
real,target :: x
pointer :: xxx

   !!write(*,gen,advance='no') 'parenthesis '
   x=2; write(*,gen,advance='no') change(change(x,x),x),x
   x=2; write(*,gen,advance='no') change(change((x),x),x),x
   x=2; write(*,gen,advance='no') change(change((x),(x)),x),x
   x=2; write(*,gen,advance='no') change(change((x),(x)),(x)),x
   x=2; write(*,gen,advance='no') change(change((x),(x)),(x)),(x)
   write(*,*)

   !!write(*,gen,advance='no') 'associate   '
   associate (xx => x)
   x=2; write(*,gen,advance='no') change(change(x,x),x),x
   x=2; write(*,gen,advance='no') change(change(xx,x),x),x
   x=2; write(*,gen,advance='no') change(change(xx,xx),x),x
   x=2; write(*,gen,advance='no') change(change(xx,xx),xx),x
   x=2; write(*,gen,advance='no') change(change(xx,xx),xx),xx
   end associate
   write(*,*)

   !!write(*,gen,advance='no') 'pointer     '
   xxx => x
   x=2; write(*,gen,advance='no') change(change(x,x),x),x
   x=2; write(*,gen,advance='no') change(change(xxx,x),x),x
   x=2; write(*,gen,advance='no') change(change(xxx,xxx),x),x
   x=2; write(*,gen,advance='no') change(change(xxx,xxx),xxx),x
   x=2; write(*,gen,advance='no') change(change(xxx,xxx),xxx),xxx
   write(*,*)

contains
   function change(a,b) result(c)
   real :: a,b,c
      b=a+b
      c=b**2
      x=x+2
   end function change
end program puzzling
gfortran
:484.00000 24.000000 :484.00000 24.000000 :400.00000 22.000000 :400.00000 6.0000000 :400.00000 6.0000000 
:484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 
:484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 
ifort
:484.00000 24.000000 :484.00000 24.000000 :400.00000 22.000000 :400.00000 6.0000000 :400.00000 6.0000000 
:484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 
:484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 
nvfortran
:484.00000 24.000000 :484.00000 24.000000 :400.00000 22.000000 :324.00000 6.0000000 :324.00000 6.0000000 
:484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 
:484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 

Really only posted this in case anyone else wants to run it on another compiler. It would be nice to get the same answers as gfortran(1) and ifort(1).

2 Likes

With the NAG compiler, and maximum runtime checking (-C=all -C=undefined -gline -g), we get

Runtime Error: /tmp/puzzling.f90, line 51: Assignment to B affects dummy argument A
Program terminated by fatal error
/tmp/puzzling.f90, line 51: Error occurred in PUZZLING:CHANGE
/tmp/puzzling.f90, line 22: Called by PUZZLING

With no checking

:484.00000 24.000000 :484.00000 24.000000 :400.00000 22.000000 :400.00000 6.0000000 :400.00000 6.0000000
:484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000
:484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000 :484.00000 24.000000

1 Like

Nice catch by NAG, and reasonable answers. I did not mention I just used the fpm debug defaults; but I got no pertinent compile or runtime errors using

fpm run -compiler ifort
 + ifort -c app/main.f90 -warn all -check all -error-limit 1 -O0 -g -assume byterecl -traceback 
app/main.f90(34): warning #6717: This name has not been given an explicit type.   [XXX]
   xxx => x

fpm run -compiler nvfortran
 + nvfortran -c app/main.f90 -Minform=inform -Mbackslash -g -Mbounds -Mchkptr -Mchkstk -traceback 

fpm run -compiler gfortran
 + gfortran -c app/main.f90 -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g -fcheck=bounds -fcheck=array-temps -fbacktrace -fcoarray=single 

I will double-check if there are a few other flags I should have added; but kudos to NAG on that one which potentially could be hard to find in real code. The defaults fpm would have used for NAG are

-g -C=all -O0 -gline -coarray=single -PIC

so one take-away is whether the default should also include -C=undefined.

1 Like

The -C=undefined is not necessary to catch this particular error. That option has a significant resource footprint so it is a last-resort and can only be used when all called code is Fortran and compiled with that flag on. We at NAG tend to have two levels of debug/rt-check builds: “1/light” and “2/heavy”.

1 Like