Elegant way to pass large number of arguments to subroutine

Hey,

I’m aware there’s no limit to the number of arguments that can be passed to a procedure, but I was wondering if there’s an elegant/clean way to pass a large number (~40) of arguments. For similar situations I used namelists in the past, but I wondered if there’s another, more elegant way of doing it.

Thanks in advance.

Packaging some variables into derived types, and pass a few derived type arguments instead of many individual arguments is a way. But it has to make sense in terms of data representation.

Another way is to define some module variables, which are used by both the callers and the callees. But one must be careful with this approach, as it can make the code more obscure (it’s no longer clear which variables a given routine has access to).

5 Likes

Put your variables into a module

program myMain
use mySharedData
integer iSum
iSum=i1+i2
...

end

module mySharedData
integer :: I1,I2 
real      :: f(100)
...
end
1 Like

A solution in line with what @PierU suggested, assuming that some of the arguments may have “default” values.

module demo
implicit none
type :: optional_args
   ! long list of arguments go here
end type
contains

   subroutine eval(arg1,arg2,extra)
      integer :: arg1, arg2
      type(optional_args), optional :: extra

      if (present(extra)) then
      ! ...
      else
         ! use default values
         ! ...
      end if
   end subroutine
end module

program main
   use demo
   type(optional_args), allocatable :: extras
   logical :: condition
    ! ... 
   if (condition) extras = args()
   call eval(1,2,extra=extras)
contains
   function args()
      type(optional_args) :: args
      ! ... values could be read from a file
      
   end function
end program
1 Like

Thank you all. I think packaging them into derived types makes the most sense as I can categorise and structure them better (as I’ve done via namelists in the past).

1 Like

When defining derived types to hold the argument lists, for arrays, you can use the move_alloc() intrinsic to temporarily “move” an array into a derived type, then make the subroutine call, and then afterwards move the array back to its normal variable. This “move” is a shallow copy, the data doesn’t actually move, it is only the metadata. The main limitation of this approach is that the original array must be allocatable (e.g. not a pointer, or automatic, etc., array).

4 Likes

It may also make the code not thread-safe. Which may or may not important, depending on the application.

3 Likes

That’s correct, I forgot mentioning that. This actually doesn’t prevent multithreading the code inside the routine, but this can be problem if the call to the routine is itself in a parallel region.

1 Like

Yes, I typically let the number of arguments grow, say 10 - 15, and once it becomes hard to manage, and I keep repeating the same arguments over and over in many subroutines, I create a derived type and just pass that, since if, say, 3 arguments keep being passed together all the time, it usually means that they are related somehow, so it’s not a bad design to put them in a derived type.

3 Likes

I agree with this argument, but there is a downside that should be mentioned. If those related variables are all placed in a derived type, then they end up all having the same intent in the subroutine. In their original form as separate arguments, they could each have their own intent. The intent declarations have several purposes, from telling the compiler which optimizations are allowed, to telling the compiler to warn you if you violate an intent, to telling other programmers which variables are changed within a routine. The programmer loses all that when the variables are combined into a single derived type.

4 Likes

Yes, they have to have the same intent and also lifetime. Good candidates are array members of a CSR sparse matrix, or various solver options, or mesh data, etc.

While the standard does not specify a limit, an individual “processor” (compiler) may have such a limit (allowed under the “complexity” caveat in the standard.) I agree with those who suggest bundling arguments into a derived type - if nothing else, passing a large number of arguments can hurt performance.

1 Like

Maybe some enhancement of associate might be useful? Something like…

subroutine mysub( x, y, opts )
  ...
  type(options_t) :: opts  !! no intent here (intentionally)

  associate( &
    rho, in => opts % density_of_foo, &
    pres, out => opts % pressure_of_foo )
 ...
1 Like

Well, you can already sort of do that, no enhancement required:

subroutine mysub( x, y, opts )
  ...
  type(options_t) :: opts  !! no intent here (intentionally)

  associate( &
    rho => (opts % density_of_foo), &    ! intent(in)
    pres => opts % pressure_of_foo &    ! intent(inout)
  )
 ...
1 Like

Perhaps it is counter-intuitive that when something gets large that it can be helpful to make it larger but using keyword=value syntax and only putting one or a few values on a line can make it much more legible and maintainable. I was not a huge fan of keywords and thought using the name would be a maintenance problem but find myself using it more and more, not just when optional arguments are present. I find myself using the kludge/trick I first saw on this forum to force keyword usage so the calls are more descriptive. This is assuming good keywords have been chosen, which make the call must more self-describing. Using descriptive variable names makes complex calls more legible and maintainable as well. Contained procedures can be used for making complex calls as, particularly when there are a lot of scratch variables and placeholders needed in calls to older interfaces. A BLOCK/ENDBLOCK could be used as well to place declarations near the call but I find contained procedures work well. On the one hand it is more verbose, but the additional verbosity is often self-descriptive and makes the call clearer, not more confusing. Because the variables are in the same scope you do not have to pass the entities to the contained routine unless you want to.

6 Likes

Yeah, I think parentheses could be used for making the RHS to an expression, but my concern is how various compilers handle it internally, particularly whether a temporary is created or not. Because I often use nested derived types + make a short-hand “alias” to some derived-type components inside a routine (via associate), I would like to avoid possible creation of temporaries (not only due to performance, but to guarantee that the variables point to the same underlying data). Because of this concern, I am currently avoiding the use of this “enclose with parentheses” pattern…

1 Like

You’re probably right about performance when it comes to nested and/or array components —but primitive scalars should be fine.

I usually don’t create procedures so big that I would end up losing track of the arguments’ usage.

Maybe a better approach to controlling intent would be to use CONTAINed procedures according to its single responsibility, e.g.:

subroutine mysub( x, y, opts )
  ...
  type(options_t) :: opts  !! no intent here (intentionally)

  call calculate_pressure(opts%density_of_foo, opts%pressure_of_foo)
  call compute_weights(x, y, ...)
  ...
contains
  elemental subroutine calculate_pressure(density, pressure)
    real(wp), intent(in) :: density
    real(wp), intent(out) :: pressure
    ...
  end subroutine
  subroutine compute_weights(x, y, ...)
  ...
  end subroutine
end subroutine mysub
1 Like