Is there another function in Fortran like `merge` that does not evaluate its arguments?

The merge function does not evaluate its arguments, unless they are needed. Here is a simple test program, that passes:

program test_merge
implicit none
integer :: i, j

i = merge(f1(), f2(), .true.)
if (j /= 1) error stop
if (i /= 10) error stop
i = merge(f1(), f2(), .false.)
if (j /= 2) error stop
if (i /= 20) error stop

contains

    integer function f1() result(r)
    j = 1
    r = 10
    end function

    integer function f2() result(r)
    j = 2
    r = 20
    end function

end program

And it shows that either f1() or f2() is called, but not both.

Is there another intrinsic function in Fortran that behaves this way, or is merge the only one?

Is that a consistent behavior across all compilers? I have learned from experience that at least Intel and GNU merge() implementations do not behave similarly.

1 Like

I don’t think that behavior is required by the standard. The standard has always allowed much freedom regarding expression evaluations and function references to compilers.

I think the new ? conditional expression is an exception to this rule. I think that syntax does evaluate its expressions conditionally.

1 Like

Good question, I only tried GFortran.

I looked into the standard for merge and it doesn’t seem to say anything about the evaluation order there. So I am guessing some other general parts of the standard applies here.

I agree with others that this should not counted on. In general I suggest using

MERGE(TSOURCE, FSOURCE, MASK)

only when both TSOURCE and FSOURCE can be quickly evaluated (not requiring calculation, such as constants or the values of variables) regardless of the value of MASK. Otherwise use an if block.

1 Like

Thanks. The reason I am asking is with regarding how LFortran should implement this. Right now we evaluate both arguments, but we are investigating what should be ideally done.

That program is totally in undefined behavior territory. All expressions that are actual arguments are evaluated before a procedure is invoked. It does not say in what order though. So it is undefined what value j will have after execution of those merge calls. Any compiler that is eliding the evaluations is not standards conforming (although probably because people wanted/asked for it). But of course that’s why we added the new conditional expression to the standard.

i = (MASK ? T_EXPR : F_EXPR)

The standard says that only the selected expression is evaluated.

Just to be clear, merge should be considered equivalent to

tval = t_expr
fval = f_expr
if (mask) then
  var = tval
else
  var = fval
end if

not

if (mask) then
  var = t_expr
else
  var = f_expr
end if
1 Like

We (committee) discussed this in great detail at one point. While MERGE looks like a good candidate for an equivalent of the ? operator in other languages, indeed the standard does not say you should not evaluate all the arguments. As mentioned above, the new conditional expressions in F23 do fill this need.

1 Like

@everythingfunctional excellent, your code examples are extremely helpful. Two more questions.

First: is var = (MASK ? T_EXPR : F_EXPR) equivalent to:

if (mask) then
  var = t_expr
else
  var = f_expr
end if

Second: assuming var = merge(t_expr, f_expr, mask) is equivalent to:

tval = t_expr
fval = f_expr
if (mask) then
  var = tval
else
  var = fval
end if

Then we can use the following test that should be conforming:

program test_merge
implicit none
integer :: i, test

test = 0
i = merge(f1(), f2(), .true.)
print *, i, test
test = 0
i = merge(f1(), f2(), .false.)
print *, i, test

contains

    integer function f1() result(r)
    test = test + 1
    r = 10
    end function

    integer function f2() result(r)
    test = test + 2
    r = 20
    end function

end program

In here, we assume that both arguments get evaluated, in any order, and so the sum must be equal to 3. Is this code conforming?

Here are the results in LFortran and GFortran:

$ gfortran a.f90 && ./a.out
          10           1
          20           2
$ lfortran a.f90 
10 3
20 3

So LFortran evaluates both arguments, while GFortran only evaluates those needed for merge.

Yes.

Once the interpretation of a numeric intrinsic operation is established, the processor may evaluate any mathematically equivalent expression, provided that the integrity of parentheses is not violated.

Two expressions of a numeric type are mathematically equivalent if, for all possible values of their primaries, their mathematical values are equal. However, mathematically equivalent expressions of numeric type can produce different computational results.

I’m not sure it’s well defined what the value of test should be. I’ll see if I can find something, but that may still be in UB territory.

Edit:

Found it.

If a statement contains a function reference in a part of an expression that need not be evaluated, all entities that would have become defined in the execution of that reference become undefined at the completion of evaluation of the expression containing the function reference.

At the end of evaluating each merge expression, test is undefined.

2 Likes

@everythingfunctional thank you, very interesting.

As a user, if I want to have a well-defined behavior, all functions that I use in expressions should thus be side-effects-free (pure) and probably also deterministic (simple). Then it doesn’t matter if the compiler evaluates them or not, and it satisfies your last condition, that the test global becomes “undefined”.

That’s been my contention for a while now. If it’s not pure (at least), you have no idea where you can put calls to it safely. I.e

integer :: i
i = 0
print *, foo() + foo()
contains
function foo()
  integer :: foo
  print *, i
  i = i + 1
  foo = i
end function
end

Will explode but,

integer :: i, tmp
i = 0
tmp = foo()
tmp = tmp + foo()
print *, tmp
contains
function foo()
  integer :: foo
  print *, i
  i = i + 1
  foo = i
end function
end

Will work just fine. Seeing the latter code (especially if the actual definition of foo is far away) you’d naively think, “why can’t I simplify this and rewrite it like the former?” and then scratch your head for a while when it didn’t work.

1 Like

I’m probably wrong about this but I always thought that one of the reasons MERGE was introduced was to provide a standard alternative to the old Cray CVMG family of functions (CVMGT and its friends) that provided a way to vectorize loops with conditional branches when normal IF blocks would inhibit vectorization.

2 Likes

I’m curious how that would be possible. You’re still going to have to pack the vector registers, and when there’s a conditional that’s going to need checking. Maybe the available vector registers can be divided among the branches of the conditional and filled up as the array is traversed, only evaluating either at the end of the array or when the allocated registers are full.

See

https://cpe.ext.hpe.com/docs/cce/man3/cvmg.3i.html

If you run into an old code that ran on a XMP or a C90 there are probably CVMG statements in it. As to how it works, you will have to ask a Crayon. Since the syntax for CVMGT and MERGE are the same, I think MERGE can be used as a direct replacement for CVMGT. If MERGE actually works the same as CVMGT in enableing vectorization is the question. Might just have been added to allow codes to compile with non-Cray compilers.

When if ever is a compiler allowed to rewrite

foo() + foo()

as

2*foo()

and evaluate foo() only once? You could write a function

function ran() result(y)
real :: y
call random_number(y)
end function ran

where you would not want

ran() + ran()

to be replaced by

2*ran()

1 Like

Some information is given under the -faggressive-function-elimination option

1 Like

The merge question has been with us for some time. Over 10 years ago I asked the Fortran 90 list COMP-FORTRAN-90@JISCMAIL.AC.UK about it and received a good answer explaining why it would not be easy to make the change I was hoping for. Note that both the f2008 standard 12.5.3 in force then, and the f2023 standard 15.5.3 in force now, require that when a function is invoked, all actual argument expressions are evaluated. I quote the correspondence:

On Nov 27, 2013, at 13:41 , John Harper harper@MSOR.VUW.AC.NZ wrote:

  x = merge(tsource,fsource,mask)

Is there any chance that a future standard might require tsource to be
evaluated if and only if mask is true, and fsource to be evaluated if and
only if mask is false?

Also, keep in mind that all of these arguments can be arrays, and elements
from both tsource and fsource can be required to fill in the result
depending on the values of corresponding elements of mask. It would get
rather complicated to write the rules for conditional evaluation here.

Steve Lionel
Intel Developer Support
Merrimack, NH

@Beliavsky, @everythingfunctional see this thread for more “fun” examples of side-effect-free, but not deterministic functions and what it leads to:

I started following the comp.lang.fortran newsgroup in the early 1990s, when f77 was still the dominant dialect and f90 compilers were not yet common, and this issue was discussed often even at that time. There was a newsgroup FAQ document, and I think that was one of the topics discussed there too. I remember arguments on both sides of the issue that seemed to make sense, but I think the final conclusion was that the fortran standard (f77 at that time), allowed the compiler maximum flexibility to do it either way. This was more or less explicit when the issue involved function evaluations within an expression, such as the foo()+foo() in your example. Another numerical example is an expression that involves n*foo() when n is either a literal zero or a variable that has the value zero. I think things were a little less certain when the function evaluations were not in a single expression but spread over several statements. In that case, the issue was how much “dead code” the compiler was allowed to recognize and to eliminate. In addition to numerical examples, there are also some common situations involving logical expressions with function references.

There is also the issue of “mathematical” equivalence, which is a little unclear in some of these cases. Consider the example given above with a uniform random number function ran(). Is 2*ran() mathematically equivalent to ran()+ran()? 2*ran() produces a uniform random number in the range 0.<=x<2. However, ran()+ran() produces a number in that same range but with a triangular distribution. [Think of the distribution of values produced from two dice.] Is that difference in distributions a “mathematical” or a “numerical” one?

Often, the difference isn’t so much the function result, but the side effects (as in some of the examples in this discussion).

One thing I remember about those discussions was that it was not going to be possible to please everyone, or even to please one programmer all the time. Sometimes you want the functions to be always evaluated (for their side effects, etc.), and sometimes you want the compiler to optimize away the unnecessary functions and to produce efficient code.

My personal take away from this is that if you always want the side effects, then use a subroutine, not a function, and if you want the absolute optimal code, then hand optimize it yourself, don’t expect the compiler to read your mind.

I think this is probably correct. However, it was only the semantics of the result of the instruction that was included, the MERGE intrinsic is not required to emulate exactly the Cray hardware. Thus a compiler is free to either evaluate all the arguments and then mask, or to use the mask to conditionally evaluate the arguments, depending on what hardware is available, what optimization options are invoked at the time, and so on.