Evaluating all a function's arguments

The F2018 standard says three things that are not obviously consistent, about whether a function reference must always evaluate all the function’s arguments.
10.1.7 says that some operands in an expression need not be evaluated if the value of the expression can be determined otherwise.
15.5.3 requires all actual arguments in a function reference to be evaluated.
16.2.3 says that any element not selected by the mask need not be defined at the
time the function is invoked.

In the program below merge has three scalar arguments; ifort evaluates all three, gfortran evaluates the useful two. Which is right?

program testmerge9
  implicit none
  integer i
  logical:: x(2)=(/.true., .false./), y ! avoiding [ ] allows f95 option
  do i = 1,2
     y = merge(tstuff(),fstuff(),x(i))
     print *,y
  end do
contains
  logical function tstuff()
    print *,'tstuff'
    tstuff = .true.
  end function tstuff
  
  logical function fstuff()
    print *,'fstuff'
    fstuff = .false.
  end function fstuff
end program testmerge9
1 Like

I have noticed this behavior, too (not sure if it was gfortran or ifort or both). I hope it is a compiler bug, not presumably a flaw in the standard. My original impression was that the compiler would translate merge(tstuff(), fstuff(), x(i)) to,

if (x(i)) then
    tstuff()
else
    fstuff()
end if

But that does not seem to be the case.

Of course kargl’s gfortran patch, which I imagine would force merge to evaluate all its arguments, is standard-conforming, because 16.2.3 permits but does not require evaluation of one not selected by mask to be omitted. But would gfortran then give a run-time or compile-time error with a program like this one, where I thought calculating one of the arguments might cause trouble?

! Must merge evaluate all 3 arguments?
program testmerge1
use iso_fortran_env, only: compiler_version,compiler_options
  implicit none
  real :: x(3) = [-8,0,8],y
  integer i
  print *,'Compiler version = ',compiler_version()
  print *,'Compiler options = ',compiler_options()
  do i = 1,3
     y = merge(xpos(x(i)),xneg(x(i)),x(i)>=0)
     print "(2(A,F4.1),A)",'x = ',x(i),' = (',y,')**3'
  end do
contains
  real function xpos(x)
    real,intent(in) :: x
    print *,'xpos'
    xpos = x**(1.0/3.0)
  end function xpos
  real function xneg(x)
    real,intent(in) :: x
    print *,'xneg'
    xneg = -((-x)**(1.0/3.0))
  end function xneg
end program testmerge1

By the way, ifort printed both xpos and xneg each time, but without an error message. Its output was

 Compiler version = 
 Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel
 (R) 64, Version 2021.6.0 Build 20220226_000000
 Compiler options = 
 -stand f18 -L/opt/intel//oneapi/compiler/latest/lib/pkgconfig/../..//linux/comp
 iler/lib/intel64/ -liomp5 -assume protect_parens -check all -fmath-errno -ftrap
 uv -traceback -warn interface -standard-semantics -warn nostderrors -check noar
 g_temp_created -O0 -g -o testmerge1.f90oi
 xpos
 xneg
x = -8.0 = (-2.0)**3
 xpos
 xneg
x =  0.0 = ( 0.0)**3
 xpos
 xneg
x =  8.0 = ( 2.0)**3

Although I started using Fortran when it was called FORTRAN II, I am woefully ignorant about what’s under any compiler’s hood. So I now have to ask if Kargl’s patch to gfortran is still the right one to offer, because of the difference he identified between the cases of scalar and array masks.