Optional subroutine input: best practice

I often have the case where a subroutine/function needs computation-intensive data that could be already available from other classes/parts of the code. To do so, I use optional inputs in this way:

  • I set it as target
  • Instantiate a pointer inside the routine
  • either point to it, or allocate a new one, if not available

It feels a bit verbose but it works. Is this a good practice? How/if can this be improved? Thanks for any comments!

subroutine mySub(a,b,c,optData)
   ! [...]
   type(blabla), optional, intent(in), target :: optData

   ! Local variables
   type(blabla), pointer :: locData

   if (present(optData)) then 
      locData => optData
   else
      allocate(locData); ! [...] create data
   endif

   ! [perform routine]
   
   ! Finalize data
   if (present(optData)) then 
      nullify(locData)
   else
      deallocate(locData)
   endif

end subroutine
1 Like

With this particular usage pattern I do not think you can simplify things much further. The only thing is that the nullification is not required.
An alternative is to have two versions of the routine (one that accepts the work data from a caller and another that sets up the temporary work data). They would then call a common one that does the actual work, but that does not seem less verbose ;). You do isolate the data management part from the actual calculation though.

I would prefer:

subroutine mySub(a,b,c,optData)
   ! [...]
   type(blabla), optional, intent(in), target :: optData
   ! Local variables
   type(blabla), allocatable, target :: allData
   type(blabla), pointer :: locData

   if (present(optData)) then 
      locData => optData
   else
      allocate(allData); ! [...] create data
      locData => allData
   endif

   ! [perform routine]
   
end subroutine

So that I’m not managing the memory, and there is just one if at the beginning at the price of one additional variable.

3 Likes

Interesting take: maybe, instead of having two variables (locData, allData) that do exactly the same thing, one could just simplify the garbage collection part like @Arjen is suggesting, like

subroutine mySub(a,b,c,optData)
   ! [...]
   type(blabla), optional, intent(in), target :: optData

   ! Local variables
   type(blabla), pointer :: locData

   if (present(optData)) then 
      locData => optData
   else
      allocate(locData); ! [...] create data
   endif

   ! [perform routine]
   
   ! Finalize data
   if (.not.present(optData)) deallocate(locData)

end subroutine

But then you have to manage memory and pay attention to deallocate all the allocated memory with two ifs that may be far away one from the other.

I definitely prefer to have two variable, to allocate memory using an allocatable, and use a pointer just to point to one or another array. I think is better to have two variables than two ifs.

I think that one should avoid to allocate memory by a pointer if another way to allocate memory is possible (using of course an allocatable).

But, of course, this is just a personal opinion. :slight_smile:

1 Like

I have tended towards the definition of two (or more) separate procedures in a generic interface rather than use optional arguments. From the outside the usage appears the same, i.e. the procedure can be called with or without certain arguments, but has several benefits (IMO).

  1. it reduces the necessity of additional local variables
  2. simplifies the control flow
  3. in the case of multiple optional arguments, where the presence of one requires the presence of another, eliminates the possibility of calling the procedure with one but not the other.

The added boiler-plate/verbosity seems low cost compared to the benefits.

1 Like

I also prefer the use of generic interfaces as much as possible for these situations and to add to the above list of reasons: an optional argument is resolved at runtime (in the general case) whereas a generic interface is resolved at compile time. It is a small overhead for checking the optional argument but it could become significant in hot loops.

1 Like

I would say, it depends.

The number of procedures will increase exponentially (2^N) with the number of optional arguments while the number of lines in the procedure with pointers and allocatables increase linearly with the number of optional arguments.

So you’re trying to avoid usage of optional variables as much as possible;
this is interesting, as it seems like that’s the preferred option in other languages like C++.

I’m not sure what happens with compilers, I would bet that they optimized out presence of optional keywords like they do with parameters when called across the code; at least, within the same module!

I use optional quite a lot, but for this case I would do like @everythingfunctional suggested and make two procedures where the one without the extra argument would allocate the data and call the other version:

interface foo
    module procedure foo_no_data 
    module procedure foodata 
end interface 

and

subroutine foo_no_data() 
    integer, allocatable :: arr(:) 
    allocate(arr(100))
    call foo(arr) 
end subroutine 


subroutine foo_data(arr) 
    integer, intent(inout) :: arr(:) 
    
   ! Do stuff here
end subroutine 

This way the decision to allocate data or not will done at compile time and not runtime which will possibly give a tiny tiny bit of better performance. Since the two procedures typically will be in the same module the compiler could easily inline the call foo in foo_no_data as well.

The situations where I like optional a lot is to control behaviour where invoking the procedure without the optional arguments would represent the “sane defaults”:

subroutine modify_arg(i, delta, print_stdout) 
    integer, intent(inout) :: i
    integer, optional, intent(in) :: delta
    logical, optional, intent(in) :: print_result

    integer :: the_delta 
    logical :: is_print_result

    the_delta = 1
    if (present(delta)) the_delta = delta
    is_print_result =.false.
    if (present(print_result)) is_print_result = print_result

    i = i + the_delta 
    if (is_print_result) then 
      write(*, *) i
    end if
end subroutine 

When refactoring old code one could easily end up with a lot of special cases which you can enable with optional arguments while keeping your preferred way easy to use.

I have used this approach along with some of the other options that have been suggested. I just wanted to add one other thing to consider. Sometimes you might call the routine with an argument, but that actual argument itself is optional and is not present. As far as the compiler is concerned, the argument is there, but as far as the subroutine is concerned, the dummy argument is not present. Thus the choice between generic interfaces and tests using PRESENT() can be different, and might even result in errors because of the mismatched argument association.