I suggest you attempt a mockup of your expected scenario(s) including the operations of the form tmp = f(a, b) or tmp = f(a) and review your needs vis-a-vis the copy of the standard you have and chances are you can figure out by yourself what works best you.
Otherwise, it’s likely readers offer you possible options that you bat away because they don’t fit what you have in mind that you haven’t quite explained here.
For example, there is also the option since Fortran 90 with a generic interface to external procedures:
module m
implicit none
private
interface
real function fx(x)
implicit none
real, intent(in) :: x
end function
real function fxy(x, y)
implicit none
real, intent(in) :: x
real, intent(in) :: y
end function
end interface
interface f !<-- Generic interface to external procedures
procedure :: fx !<-- External procedure
procedure :: fxy !<-- ditto
end interface
public :: sub
contains
subroutine sub( n, x, y, z )
integer, intent(in) :: n
real, intent(in) :: x
real, intent(in) :: y
real, intent(inout) :: z
if ( n == 1 ) then
z = f(x) !<-- invoke generic interface with one argument
else
z = f(x, y) !<-- invoke generic interface with two arguments
end if
end subroutine sub
end module
but then you may say external procedures are not what you have in mind. For external procedures may appear so passé when the caller side looks like so:
! Caller side code below
real function fx(x)
! External procedure for fx
implicit none
real, intent(in) :: x
fx = -x
end function
real function fxy(x, y)
! External procedure for fxy
implicit none
real, intent(in) :: x, y
fxy = x + y
end function
program p
use m, only : sub
implicit none
real :: a, b, c
a = 1.0; b = 2.0
call sub(1, a, b, c )
print *, "with n = 1: c = ", c, "; expected is -1.0"
call sub(2, a, b, c )
print *, "with n =/= 1: c = ", c, "; expected is 3.0"
end program
And for which Fortran 90-conforming compilers should give:
C:\temp>gfortran -c -Wall p.f90
C:\temp>gfortran -Wall p.f90 -o p.exe
C:\temp>p.exe
with n = 1: c = -1.00000000 ; expected is -1.0
with n =/= 1: c = 3.00000000 ; expected is 3.0
So then a reader might suggest to you to work around the semantics that lead to external procedures in this solution by adopting Fortran 2003 (and later) option with C interoperability and the bind(C, name= clause and you may not like that either given what that entails with working with C interoperable functions that are authored in Fortran for use in Fortran-only code!!