Testing whether an argument is PRESENT is very fast

An alternative to writing a procedure with an OPTIONAL argument is to write some module procedures sharing an interface, handling the cases where the argument is or is not supplied. In the latter case, although more code is written, the cost of checking whether an argument is PRESENT at run time is not incurred. I wrote a toy code to see how fast a function with an optional argument is compared to the alternative, by calling each version 10^8 times. The difference on my PC with gfortran -O3 or ifort -O3 is not noticeable, certainly less than 0.1s. I conclude that one should not worry about calling procedures with optional arguments even in inner loops where they are called many times. Are there counterexamples?

module optional_mod
implicit none
interface sd ! simulate an optional argument
   module procedure sd_calc_mean,sd_given_mean
end interface sd
contains
pure function sd_opt(x,xmean) result(xsd)
real, intent(in)           :: x(:)
real, intent(in), optional :: xmean
real                       :: xsd
real                       :: xmean_
if (present(xmean)) then
   xmean_ = xmean
else
   xmean_ = sum(x)/size(x)
! in production code should check that size(x) > 0
end if
xsd = sqrt(sum((x-xmean_)**2)/(size(x)-1))
end function sd_opt
!
pure function sd_calc_mean(x) result(xsd)
real, intent(in)           :: x(:)
real                       :: xsd
real                       :: xmean_
xmean_ = sum(x)/size(x)
xsd = sqrt(sum((x-xmean_)**2)/(size(x)-1))
end function sd_calc_mean
!
pure function sd_given_mean(x,xmean) result(xsd)
real, intent(in)           :: x(:)
real, intent(in)           :: xmean
real                       :: xsd
xsd = sqrt(sum((x-xmean)**2)/(size(x)-1))
end function sd_given_mean
end module optional_mod
!
program test_sd
use optional_mod
implicit none
integer, parameter :: n = 5, niter = 10**8
real :: x(n),xsd
integer :: iter
logical, parameter :: call_sd_opt = .true. ! toggle this
if (call_sd_opt) then
   do iter=1,niter
      call random_number(x(n))
      xsd = sd_opt(x)
   end do
else
   do iter=1,niter
      call random_number(x(n))
      xsd = sd(x)
   end do
end if
print*,"xsd =",xsd
print*,"call_sd_opt =",call_sd_opt
end program test_sd
2 Likes

I guess in most cases (pass by reference) the present function will boil down to a check whether a pointer is not null.

While not intuitive, you can actually pass optional arguments by value. If I recall correctly GFortran will pass an additional descriptor with the value dummy argument for handling the presence of the argument.

very Interesting to note thanks. I have such speed thoughts many times but force myself to ignore them and just write the code that makes the most sense to read and is easiest to implement and maintain. Based on experience I don’t worry about speed at the microscopic level I only look harder when the overall result of a block of code is noticeably slow. In such cases it is usually a poor choice of algorithm that is the problem rather than minor code design choices. I love optional args as when maintaining old code you can add an extra parameter to a call to make some variation of functionality for a new instance and do it is such a way as to have no impact on the existing instances of the call.

1 Like

Thanks for this, it’s also something I’ve wondered for a while but never got around to testing. As a heavy user of optional args, this makes me happy! :+1:

For a procedure without the BIND attribute, a dummy with the VALUE argument passes an temporary, definable copy of the actual argument. It is not passing “by value” and OPTIONAL is fine.

For a procedure with the BIND attribute, where VALUE really does mean pass by value, OPTIONAL is not allowed in combination with VALUE:

C865 A dummy argument of a procedure with the BIND attribute shall not have both the OPTIONAL and VALUE attributes.

2 Likes

In this case when the procedure and main program are in the same compilation unit it seems pretty straightforward to eliminate the “dead” branch, delivering exactly the same performance. Can you try compiling the procedure with optional arguments and main program in separate compilation units, and linking the objects separately (with and without link time optimization)?

1 Like

I really don’t think much of any meaningful insights can be gained from the kinds of micro tests like in the original post here.

In actual practice, the technical community who get enamored by the OPTIONAL argument feature and who write code for engineering and scientific applications tend to create subroutines “from hell” with two or more optional dummy arguments, often much higher in number. Like the one in this thread, albeit a made-up example in Modern Fortran Explained (8th Edition incorporating 2018).

The challenge then ain’t the immeasurably small cost with the PRESENT intrinsic, rather the entire edifice of extremely convoluted program logic and workflow that accompanies the handling of optional parameters and corresponding program data that then leads not only to certain run-time cost but also an unbearably larger one with code readability and program maintenance and support.

Its straightforward to see what gfortran is doing. Compile your code but add -fdump-tree-all as an option. You’ll get a lot of extra output files but look for the one that ends in .original, this is a translation of fortran into C (or is it GIMPLE?)

Given a subroutine like this:

subroutine sub_int_opt(x)
    integer, optional, intent(in) :: x
	
    if(present(x)) then

gets translated into:

void sub_int_opt (integer(kind=4) * x)
{
  if (x != 0B)
    {

Which is just a null pointer check.

An optional, value like this:

	subroutine sub_int_opt_val(x)
		integer, optional, intent(in),value :: x
	
		if(present(x)) then

Is translated to:

void sub_int_opt_val (integer(kind=4) x, logical(kind=1) _x)
{
  if ((logical(kind=4)) _x)
    {

Which is gfortran just adding an extra 1 byte argument as a flag to test for the presence.

So in both cases you would expect the cost of an optional argument is basically zero.

4 Likes