Default value for optional argument

To provide a default value for an optional argument, Jannis Teunissen has proposed the syntax

subroutine test(n)
integer, intent(in), optional :: n = 10 ! Default is 10

Note that this syntax is also used to initialize variables with the ‘save’ attribute, but since that attribute does not apply to optional arguments it should be fine.

I think present(n) could be defined as .true. in this case, regardless of whether test was called with argument n. Currently my code is full of

subroutine test(n)
integer, intent(in), optional :: n
integer :: n_
n_ = default(10,n)

where default is a function I have defined with an optional 2nd argument. Often I forget to use n instead of n_ later in the subroutine, causing a run-time error when the subroutine is called with argument n. The proposed syntax would be more concise and less error-prone.

4 Likes

what happens then to this:

subroutine t_1(n)
  integer, intent(in), optional :: n = 10
  call t_2(n)

subroutine t_2(n)
  integer, intent(in), optional :: n
  if(present(n)) then
    write(*,*) "i am here"
  else
    write(*,*) "i am not here"
  endif

If, as I suggested, present(n) is .true. in subroutine t_1, regardless of how the subroutine was called, then present(n) would also be .true. in suboutine t_2, so “I am here” would be printed.

precisely, and, imho, that would make the suggested syntax as bug prone as the current one. Even worse, the current implementation yields a segfault, whereas the suggested would yield a hard to track result deviation.

btw a maybe simpler solution to your problem might be:

subroutine test(n)
integer, intent(in), optional :: n
integer :: n_=10
if(present(n)) n_=n

same number of lines, but no necessity for function inlining or across file optimization if default is defined somewhere else.

1 Like

A feature of Fortran is that In your code, n_ has the SAVE attribute, which I do not want.

sure you are right. However I still wouldn’t go the default way since

integer :: n_
n_=10;if(present(n)) n_=n

would do the trick … might be a matter of taste and whether you are chasing milliseconds.

1 Like

See the related discussion and proposal on the j3-fortran GitHub page:

I believe this is already under consideration for Fortran 202y.

1 Like

In addition to @ivanpribec 's comment, I would like to add the following (ongoing) proposal 's revision, as welll as the function optval implemented in stdlib. Here is an example on how it could be used:

program demo_optval
    use stdlib_optval, only: optval
    implicit none
    print *, root(64.0)
! 8.0
    print *, root(64.0, 3)
! 4.0
contains
    real function root(x, n)
        real, intent(in) :: x
        integer, intent(in), optional :: n
        root = x**(1.0/optval(n, 2))
    end function root
end program demo_optval

The optval function is certainly not hpc compatible, but I presume you know that.

My aim was mainly to complete the info provided by Ivan, since it was done around the J3 proposal led by @milancurcic . It also seems that stdlib optval is similar to @Beliavsky 's default function.
I agree that having something in the standard would be useful. Meanwhile, any ideas how to improve such a function to be, e.g., hpc-compatible?

I would recommend to NOT use a default value with an optional argument at all; nor to do any calculation with optional arguments: the optional argument must be present to be allocated. Instead:

if (present(n)) then
this % n = n
else ! default:
this % n = 10
end if

Indeed, the initial proposal and implementation of stdlib_optval is based on a code snippet @Beliavsky posted to comp.lang.fortran some time ago in a thread very much like this one. It’s a smart use of the fact that the presence/absence of an optional argument propagates down the call stack.

1 Like

What do you mean? I can see not wanting to stick optval calls deep in the innards of hot loops, etc. But is it much worse than using optional arguments at all in those contexts?

I wasn’t aware of that. Thank you for the information.

Take the code block below, but put every code block INTO ITS OWN FILE.

module mod_1
contains
 function optval(x,y) result(z)
   real(kind=8), intent(in), optional :: x
   real(kind=8), intent(in) :: y
   real(kind=8) :: z
   if(present(x)) then
     z=x
   else
     z=y
   end if
 end function optval
end module mod_1
module mod_2
  use mod_1, only: optval
contains
  subroutine sub1(r2i,t,s)
    real(kind=8), intent(inout) :: r2i(:,:)
    real(kind=8), intent(in) :: t
    real(kind=8), intent(in), optional :: s
    integer :: i,j
    do i=1,size(r2i,2)
      do j=1,size(r2i,1)
        if(r2i(j,i)>t) r2i(j,i)=r2i(j,i)/optval(s,3.0D0)
      end do
    end do
  end subroutine sub1
  subroutine sub2(r2i,t,s)
    real(kind=8), intent(inout) :: r2i(:,:)
    real(kind=8), intent(in) :: t
    real(kind=8), intent(in), optional :: s
    integer :: i,j
    do i=1,size(r2i,2)
      do j=1,size(r2i,1)
        if(present(s)) then
          if(r2i(j,i)>t) r2i(j,i)=r2i(j,i)/s
        else
          if(r2i(j,i)>t) r2i(j,i)=r2i(j,i)/3.0D0
        end if
      end do
    end do
  end subroutine sub2
end module mod_2

and

program test
  use mod_2, only: sub1, sub2
  implicit none
  real(kind=8), allocatable :: x(:,:)
  real(kind=8) :: t1,t2
  integer :: i
  allocate(x(1000000,100))
  do i=1,4
    call random_number(x)
    call cpu_time(t1)
    call sub2(x,0.2D0)
    call cpu_time(t2)
    write(*,"(*(g0:"",""))") "t1: ", i, t2-t1
  end do
  do i=1,4
    call random_number(x)
    call cpu_time(t1)
    call sub1(x,0.2D0)
    call cpu_time(t2)
    write(*,"(*(g0:"",""))") "t2: ", i, t2-t1
  end do
end program test

compile with

#!/bin/bash
fc=ifort
$fc -O3 -c sub1.f90
$fc -O3 -c sub2.f90
$fc -O3 -c main.f90
$fc -O3 -o test main.o sub1.o sub2.o

and check what you get.

I got:

t1: ,1,.9718500000000008E-01
t1: ,2,.9703800000000018E-01
t1: ,3,.9721100000000016E-01
t1: ,4,.9707200000000027E-01
t2: ,1,.4253720000000003
t2: ,2,.4263209999999997
t2: ,3,.4262069999999998
t2: ,4,.4255380000000004

This is of course an oversimplified example and there are several fixes to this particular code of which some are trivial, others not.

However, in more complex examples or when functions like optval sit in large libraries there is no guarantee that these fixes works.

I understand that the stdlib optval functionality is meant to make fortran more handy. But an inexperienced programmer or somebody not familiar with 2500 pages of ifort manual may come to the conclusion that stdlib is anything else than hpc.

3 Likes

I wonder what this is measuring. I don’t have ifort in front of me right now to check, but I’d guess that optval should be getting inlined. Then the only difference would the order of the two if-tests. Or I could be dead wrong.

Note to self: look at the disassembly of sub1 versus sub2 when I get time

In any case, hopefully no one is silly enough to evaluate stdlib’s HPC suitability based on a convenience function. It’s documented as such. And there’s the silver lining that if someone does use it in a place that it gums up control flow, it will show up hot in a profiler. Whereas if you’d made that mistake by hand, it might be harder to find.

1 Like

It might be worth keeping in mind: And with the modern Fortran dialects, it is even not too hard to make inefficient code

Thats were the problem is. You must switch on across file optimization explicitly. And I found often enough that it doesn’t change anything because doesn’t matter what flags you set in the end the compiler decides what to inline, and when optval sit in a large library the chance is rather high that it doesn’t get inlined.

I don’t really want to digress too much further on this specific test, but the point is taken.

Bringing things back around the original topic: It seems to me like one benefit of having syntax for default values is that the compiler will always be able to see

integer, intent(in), optional :: n = 10

(or whatever syntax) and know the relationship between n and 10 explicitly, whereas with user-written approaches like optval or explicit if (present(...)) checks, that special relationship has to be inferred and in practice seems not to come to light until run time.

As for syntax, it seems too similar to initializing (and SAVE’ing) local variables, even though the semantics are totally different. Not sure if these have been proposed already but:

jammed into optional attribute
integer, intent(in), optional(10) :: n

as a new attribute
integer, intent(in), optional, default(10) :: n

or F77-style statement, a la PARAMETER:

integer, intent(in), optional :: n
default (n=10)

The last two kind of make sense together. If the default value is brief to write, put it as an attribute. If it’s a longer expression, like an array constructor or a derived type constructor, use the statement form.

@rcs,

Please note though what you show is not very reflective of situations in a HPC computing domain.

At the very least anyone looking at the code can retry with the following trivial changes and my hunch is no differences will be noticeable:

  subroutine sub1(r2i,t,s)
    real(kind=8), intent(inout) :: r2i(:,:)
    real(kind=8), intent(in) :: t
    real(kind=8), intent(in), optional :: s
    integer :: i,j
    associate ( s_ => optval(s, 3D0) )
        do i=1,size(r2i,2)
          do j=1,size(r2i,1)
              if(r2i(j,i)>t) r2i(j,i)=r2i(j,i)/s_
          end do
        end do
    end associate
  end subroutine sub1
  subroutine sub2(r2i,t,s)
    real(kind=8), intent(inout) :: r2i(:,:)
    real(kind=8), intent(in) :: t
    real(kind=8), intent(in), optional :: s
    integer :: i,j
    real(kind=kind(s)) :: s_
    s_ = 3.0D0 ; if ( present(s) ) s_ = s
    do i=1,size(r2i,2)
      do j=1,size(r2i,1)
        if(r2i(j,i)>t) r2i(j,i)=r2i(j,i)/s_
      end do
    end do
  end subroutine sub2

@nshaffer , @ivanpribec, et al.,

Please note if you’re keen on getting something into the language standard itself, far more convincing use cases will be needed. Almost anyone on a Fortran standard committee, particularly those with compiler implementation responsibilities, will likely find it unconvincing to add further semantics and syntax to the base language with the kind of examples that are given. The options already available in the language including with generic interfaces might come across as more than adequate for such cases.